public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/33568]  New: ICE with ANINT (with KIND and an array)
@ 2007-09-27  8:08 jellby at yahoo dot com
  2007-09-27 10:39 ` [Bug fortran/33568] " pault at gcc dot gnu dot org
                   ` (6 more replies)
  0 siblings, 7 replies; 8+ messages in thread
From: jellby at yahoo dot com @ 2007-09-27  8:08 UTC (permalink / raw)
  To: gcc-bugs

The following test fails:

$ cat test.f90
PROGRAM Test
  IMPLICIT NONE
  INTEGER, PARAMETER :: DP=8
  REAL(KIND=DP), DIMENSION(1:3) :: A
  A = ANINT ( A , DP )
END PROGRAM Test

$ gfortran -c test.f90
test.f90: In function 'MAIN__':
test.f90:1: internal compiler error: in gfc_trans_assignment_1, at
fortran/trans-expr.c:4052
Please submit a full bug report,
with preprocessed source if appropriate.
See <http://gcc.gnu.org/bugs.html> for instructions.

$ gfortran -v
Using built-in specs.
Target: i386-pc-linux-gnu
Configured with: /home/fx/gfortran_nightbuild/trunk/configure
--prefix=/home/fx/gfortran_nightbuild/irun-20070926
--enable-languages=c,fortran --build=i386-pc-linux-gnu
--enable-checking=release
--with-gmp=/home/fx/gfortran_nightbuild/software
Thread model: posix
gcc version 4.3.0 20070926 (experimental) [trunk revision 128777] (GCC)

It compiles fine if A is a scalar (not an array) or if I don't specify
the "kind" in the ANINT function. AINT fails as well, not so NINT,
FLOOR or CEILING.


-- 
           Summary: ICE with ANINT (with KIND and an array)
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Severity: major
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: jellby at yahoo dot com


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33568


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/33568] ICE with ANINT (with KIND and an array)
  2007-09-27  8:08 [Bug fortran/33568] New: ICE with ANINT (with KIND and an array) jellby at yahoo dot com
@ 2007-09-27 10:39 ` pault at gcc dot gnu dot org
  2007-09-27 11:47 ` pault at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-09-27 10:39 UTC (permalink / raw)
  To: gcc-bugs

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #1: Type: text/plain, Size: 3895 bytes --]



------- Comment #1 from pault at gcc dot gnu dot org  2007-09-27 10:39 -------
Confirmed.  Thanks, Ignacio.

This is the fix (the absence of the KIND working and the regression wrt 4.2
were giveaways):

Index: gcc/fortran/trans-intrinsic.c
===================================================================
*** gcc/fortran/trans-intrinsic.c       (révision 128323)
--- gcc/fortran/trans-intrinsic.c       (copie de travail)
*************** gfc_conv_intrinsic_aint (gfc_se * se, gf
*** 393,399 ****
  {
    tree type;
    tree itype;
!   tree arg;
    tree tmp;
    tree cond;
    mpfr_t huge;
--- 393,399 ----
  {
    tree type;
    tree itype;
!   tree arg[2];
    tree tmp;
    tree cond;
    mpfr_t huge;
*************** gfc_conv_intrinsic_aint (gfc_se * se, gf
*** 448,467 ****

    /* Evaluate the argument.  */
    gcc_assert (expr->value.function.actual->expr);
!   gfc_conv_intrinsic_function_args (se, expr, &arg, 1);

    /* Use a builtin function if one exists.  */
    if (n != END_BUILTINS)
      {
        tmp = built_in_decls[n];
!       se->expr = build_call_expr (tmp, 1, arg);
        return;
      }

    /* This code is probably redundant, but we'll keep it lying around just
       in case.  */
    type = gfc_typenode_for_spec (&expr->ts);
!   arg = gfc_evaluate_now (arg, &se->pre);

    /* Test if the value is too large to handle sensibly.  */
    gfc_set_model_kind (kind);
--- 448,467 ----

    /* Evaluate the argument.  */
    gcc_assert (expr->value.function.actual->expr);
!   gfc_conv_intrinsic_function_args (se, expr, arg, 2);

    /* Use a builtin function if one exists.  */
    if (n != END_BUILTINS)
      {
        tmp = built_in_decls[n];
!       se->expr = build_call_expr (tmp, 1, arg[0]);
        return;
      }

    /* This code is probably redundant, but we'll keep it lying around just
       in case.  */
    type = gfc_typenode_for_spec (&expr->ts);
!   arg[0] = gfc_evaluate_now (arg[0], &se->pre);

    /* Test if the value is too large to handle sensibly.  */
    gfc_set_model_kind (kind);
*************** gfc_conv_intrinsic_aint (gfc_se * se, gf
*** 469,485 ****
    n = gfc_validate_kind (BT_INTEGER, kind, false);
    mpfr_set_z (huge, gfc_integer_kinds[n].huge, GFC_RND_MODE);
    tmp = gfc_conv_mpfr_to_tree (huge, kind);
!   cond = build2 (LT_EXPR, boolean_type_node, arg, tmp);

    mpfr_neg (huge, huge, GFC_RND_MODE);
    tmp = gfc_conv_mpfr_to_tree (huge, kind);
!   tmp = build2 (GT_EXPR, boolean_type_node, arg, tmp);
    cond = build2 (TRUTH_AND_EXPR, boolean_type_node, cond, tmp);
    itype = gfc_get_int_type (kind);

!   tmp = build_fix_expr (&se->pre, arg, itype, op);
    tmp = convert (type, tmp);
!   se->expr = build3 (COND_EXPR, type, cond, tmp, arg);
    mpfr_clear (huge);
  }

--- 469,485 ----
    n = gfc_validate_kind (BT_INTEGER, kind, false);
    mpfr_set_z (huge, gfc_integer_kinds[n].huge, GFC_RND_MODE);
    tmp = gfc_conv_mpfr_to_tree (huge, kind);
!   cond = build2 (LT_EXPR, boolean_type_node, arg[0], tmp);

    mpfr_neg (huge, huge, GFC_RND_MODE);
    tmp = gfc_conv_mpfr_to_tree (huge, kind);
!   tmp = build2 (GT_EXPR, boolean_type_node, arg[0], tmp);
    cond = build2 (TRUTH_AND_EXPR, boolean_type_node, cond, tmp);
    itype = gfc_get_int_type (kind);

!   tmp = build_fix_expr (&se->pre, arg[0], itype, op);
    tmp = convert (type, tmp);
!   se->expr = build3 (COND_EXPR, type, cond, tmp, arg[0]);
    mpfr_clear (huge);
  }

Cheers

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2007-09-27 10:39:02
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33568


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/33568] ICE with ANINT (with KIND and an array)
  2007-09-27  8:08 [Bug fortran/33568] New: ICE with ANINT (with KIND and an array) jellby at yahoo dot com
  2007-09-27 10:39 ` [Bug fortran/33568] " pault at gcc dot gnu dot org
@ 2007-09-27 11:47 ` pault at gcc dot gnu dot org
  2007-09-27 12:09 ` tobi at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-09-27 11:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from pault at gcc dot gnu dot org  2007-09-27 11:46 -------
I might as well take it:-)

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2007-09-27 10:39:02         |2007-09-27 11:46:50
               date|                            |


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33568


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/33568] ICE with ANINT (with KIND and an array)
  2007-09-27  8:08 [Bug fortran/33568] New: ICE with ANINT (with KIND and an array) jellby at yahoo dot com
  2007-09-27 10:39 ` [Bug fortran/33568] " pault at gcc dot gnu dot org
  2007-09-27 11:47 ` pault at gcc dot gnu dot org
@ 2007-09-27 12:09 ` tobi at gcc dot gnu dot org
  2007-09-27 13:59 ` dominiq at lps dot ens dot fr
                   ` (3 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: tobi at gcc dot gnu dot org @ 2007-09-27 12:09 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from tobi at gcc dot gnu dot org  2007-09-27 12:09 -------
Weird, I tried essentially the same patch (where I modeled the code after
gfc_conv_intrinsic_nint), but the failure persisted.  I wonder what's different
now.


-- 

tobi at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |tobi at gcc dot gnu dot org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33568


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/33568] ICE with ANINT (with KIND and an array)
  2007-09-27  8:08 [Bug fortran/33568] New: ICE with ANINT (with KIND and an array) jellby at yahoo dot com
                   ` (2 preceding siblings ...)
  2007-09-27 12:09 ` tobi at gcc dot gnu dot org
@ 2007-09-27 13:59 ` dominiq at lps dot ens dot fr
  2007-09-27 16:18 ` dominiq at lps dot ens dot fr
                   ` (2 subsequent siblings)
  6 siblings, 0 replies; 8+ messages in thread
From: dominiq at lps dot ens dot fr @ 2007-09-27 13:59 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from dominiq at lps dot ens dot fr  2007-09-27 13:59 -------
The patch fixes the test case on this PR, but gives ICE on several of my tests.
The simplest is:

program aint_anint_1

  implicit none

  real(8) :: s = 42.7D0, s1, s2

  s1 = aint(s)
!  s2 = aint(s, kind=4)

end program aint_anint_1

aint_anint_1_red.f90: In function 'MAIN__':
aint_anint_1_red.f90:1: internal compiler error: in
gfc_conv_intrinsic_function_args, at fortran/trans-intrinsic.c:188

Is not there some tests about the shape of the argument(s) missing?

Currently regtesting.


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33568


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/33568] ICE with ANINT (with KIND and an array)
  2007-09-27  8:08 [Bug fortran/33568] New: ICE with ANINT (with KIND and an array) jellby at yahoo dot com
                   ` (3 preceding siblings ...)
  2007-09-27 13:59 ` dominiq at lps dot ens dot fr
@ 2007-09-27 16:18 ` dominiq at lps dot ens dot fr
  2007-09-27 18:40 ` pault at gcc dot gnu dot org
  2007-09-27 18:52 ` pault at gcc dot gnu dot org
  6 siblings, 0 replies; 8+ messages in thread
From: dominiq at lps dot ens dot fr @ 2007-09-27 16:18 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from dominiq at lps dot ens dot fr  2007-09-27 16:18 -------
With the new patch I still have an ICE on:

        real    a
        real*8  c

        print *, (nearest(0.5,-1.0)+0.5)-1.0
        a = 8388609.0
        print '(3(1PG26.9))', a, anint(a), anint(8388609.0)
        a = 8388610.0
        print '(3(1PG26.9))', a, anint(a), anint(8388610.0)
        a = 0.49999992
        print '(3(1PG26.9))', a, anint(a), anint(0.49999992)
        a = 0.49999997
        print '(3(1PG26.9))', a, anint(a), anint(0.49999997)
        print *, a-nearest(0.5,-1.0), (a+0.5)-1.0
        c = 4503599627370498.0d0
        print '(3(1PG26.18))', c, dnint(c), dnint(4503599627370498.0d0)
        c = 4503599627370497.0d0
        print '(3(1PG26.18))', c, dnint(c), dnint(4503599627370497.0d0)
        c = 0.4999999999999999d0
        print '(3(1PG26.18))', c, dnint(c), dnint(0.4999999999999999d0)
        c = 0.49999999999999994d0
        print '(3(1PG26.18))', c, dnint(c), dnint(0.49999999999999994d0)
        end

nint_tst.f90:6: internal compiler error: in gfc_conv_intrinsic_function_args,
at fortran/trans-intrinsic.c:188

I also failures for gfortran.dg/PR19754_2.f90


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33568


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/33568] ICE with ANINT (with KIND and an array)
  2007-09-27  8:08 [Bug fortran/33568] New: ICE with ANINT (with KIND and an array) jellby at yahoo dot com
                   ` (4 preceding siblings ...)
  2007-09-27 16:18 ` dominiq at lps dot ens dot fr
@ 2007-09-27 18:40 ` pault at gcc dot gnu dot org
  2007-09-27 18:52 ` pault at gcc dot gnu dot org
  6 siblings, 0 replies; 8+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-09-27 18:40 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2007-09-27 18:40 -------
Subject: Bug 33568

Author: pault
Date: Thu Sep 27 18:39:55 2007
New Revision: 128843

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=128843
Log:
2007-09-27  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/33568
        * trans-intrinsic.c (gfc_conv_intrinsic_aint): Allow for the 
        possibility of the optional KIND argument by making arg
        an array, counting the number of arguments and using arg[0].

2007-09-27  Paul Thomas  <pault@gcc.gnu.org>

        PR fortran/33568
        * gfortran.dg/anint_1.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/anint_1.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-intrinsic.c
    trunk/gcc/testsuite/ChangeLog


-- 


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33568


^ permalink raw reply	[flat|nested] 8+ messages in thread

* [Bug fortran/33568] ICE with ANINT (with KIND and an array)
  2007-09-27  8:08 [Bug fortran/33568] New: ICE with ANINT (with KIND and an array) jellby at yahoo dot com
                   ` (5 preceding siblings ...)
  2007-09-27 18:40 ` pault at gcc dot gnu dot org
@ 2007-09-27 18:52 ` pault at gcc dot gnu dot org
  6 siblings, 0 replies; 8+ messages in thread
From: pault at gcc dot gnu dot org @ 2007-09-27 18:52 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from pault at gcc dot gnu dot org  2007-09-27 18:52 -------
After a bit of messing around, this is fixed on trunk.

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=33568


^ permalink raw reply	[flat|nested] 8+ messages in thread

end of thread, other threads:[~2007-09-27 18:52 UTC | newest]

Thread overview: 8+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-09-27  8:08 [Bug fortran/33568] New: ICE with ANINT (with KIND and an array) jellby at yahoo dot com
2007-09-27 10:39 ` [Bug fortran/33568] " pault at gcc dot gnu dot org
2007-09-27 11:47 ` pault at gcc dot gnu dot org
2007-09-27 12:09 ` tobi at gcc dot gnu dot org
2007-09-27 13:59 ` dominiq at lps dot ens dot fr
2007-09-27 16:18 ` dominiq at lps dot ens dot fr
2007-09-27 18:40 ` pault at gcc dot gnu dot org
2007-09-27 18:52 ` pault at gcc dot gnu dot org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).