public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/29267]  New: ICE in operand_subword_force, at emit-rtl.c:1353
@ 2006-09-28 10:12 franke dot daniel at gmail dot com
  2006-09-28 13:10 ` [Bug fortran/29267] " rguenth at gcc dot gnu dot org
                   ` (16 more replies)
  0 siblings, 17 replies; 18+ messages in thread
From: franke dot daniel at gmail dot com @ 2006-09-28 10:12 UTC (permalink / raw)
  To: gcc-bugs

$> cat ice.f90
PROGRAM test_ice
  CHARACTER(len=255), DIMENSION(1,2)  :: a
  a = reshape((/ "x", to_string(1.0) /), (/ 1, 2 /))

  CONTAINS
    CHARACTER(32) FUNCTION to_string(x)
      REAL, INTENT(in) :: x
      WRITE(to_string, FMT="(F6.3)") x
    END FUNCTION
END PROGRAM

$> gfortran-4.2 -g -Wall ice.f90
ice.f90: In function ‘MAIN__’:
ice.f90:3: internal compiler error: in operand_subword_force, at
emit-rtl.c:1353
Please submit a full bug report,

$> gfortran -v 
Using built-in specs.
Target: i686-pc-linux-gnu
Configured with: ../gcc/configure
--prefix=/home/daniel/nfs/packages/i686-pc-linux-gnu/gcc-4.2-svn
--enable-threads=posix --enable-shared --with-system-zlib
--enable-languages=c,c++,fortran
Thread model: posix
gcc version 4.2.0 20060914 (experimental)

Initially reported here:
http://gcc.gnu.org/ml/fortran/2006-09/msg00335.html
(the testcase above is a reduced version of that posted to the ML)


-- 
           Summary: ICE in operand_subword_force, at emit-rtl.c:1353
           Product: gcc
           Version: 4.2.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: franke dot daniel at gmail dot com
  GCC host triplet: i686-pc-linux-gnu


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
@ 2006-09-28 13:10 ` rguenth at gcc dot gnu dot org
  2006-10-04  7:00 ` fxcoudert at gcc dot gnu dot org
                   ` (15 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2006-09-28 13:10 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from rguenth at gcc dot gnu dot org  2006-09-28 13:09 -------
Confirmed.

(gdb) bt
#0  fancy_abort (
    file=0xc80d78 "/space/rguenther/src/svn/trunk/gcc/emit-rtl.c", line=1353, 
    function=0xc80ef0 "operand_subword_force")
    at /space/rguenther/src/svn/trunk/gcc/diagnostic.c:642
#1  0x000000000061cc08 in operand_subword_force (op=0x2b22e2375be0, offset=0, 
    mode=QImode) at /space/rguenther/src/svn/trunk/gcc/emit-rtl.c:1353
#2  0x00000000006351a6 in store_bit_field (str_rtx=0x2b22e2375ba0, 
    bitsize=256, bitnum=0, fieldmode=QImode, value=0x2b22e2362f40)
    at /space/rguenther/src/svn/trunk/gcc/expmed.c:582
#3  0x000000000065441b in store_field (target=0x2b22e2375ba0, bitsize=256, 
    bitpos=0, mode=BLKmode, exp=0x2b22e23639a0, type=0x2b22e2359d10, 
    alias_set=0) at /space/rguenther/src/svn/trunk/gcc/expr.c:5591
#4  0x000000000064d0e2 in expand_assignment (to=0x2b22e235a300, 
    from=0x2b22e23639a0) at /space/rguenther/src/svn/trunk/gcc/expr.c:4141
#5  0x000000000066d9cf in expand_expr_real_1 (exp=0x2b22e235b870, target=0x0, 
    tmode=VOIDmode, modifier=EXPAND_NORMAL, alt_rtl=0x0)
    at /space/rguenther/src/svn/trunk/gcc/expr.c:8603
#6  0x000000000065a675 in expand_expr_real (exp=0x2b22e235b870, 
    target=0x2b22e2284400, tmode=VOIDmode, modifier=EXPAND_NORMAL, alt_rtl=0x0)
    at /space/rguenther/src/svn/trunk/gcc/expr.c:6700
(gdb) up
#1  0x000000000061cc08 in operand_subword_force (op=0x2b22e2375be0, offset=0, 
    mode=QImode) at /space/rguenther/src/svn/trunk/gcc/emit-rtl.c:1353
1353      gcc_assert (result);
(gdb) list
1348          else
1349            op = force_reg (mode, op);
1350        }
1351
1352      result = operand_subword (op, offset, 1, mode);
1353      gcc_assert (result);
1354
1355      return result;
1356    }
1357    ^L

We're asking for a QImode subword at offset 0 of
(mem/s/j:BLK (plus:DI (reg:DI 112)
        (reg:DI 96 [ D.1297 ])) [0 S32 A8])

in expansion of

(*D.1297)[S.20D.1298] = D.1302


4.0 fails differently:

gcc40-g/gcc> ./f951 -quiet ../../gcc41-g/gcc/t.f90 
../../gcc41-g/gcc/t.f90: In function 'MAIN__':
../../gcc41-g/gcc/t.f90:8: internal compiler error: in gfc_conv_function_call,
at fortran/trans-expr.c:1108
Please submit a full bug report,
with preprocessed source if appropriate.
See <URL:http://gcc.gnu.org/bugs.html> for instructions.


-- 

rguenth at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
           Keywords|                            |ice-on-invalid-code
   Last reconfirmed|0000-00-00 00:00:00         |2006-09-28 13:09:57
               date|                            |


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
  2006-09-28 13:10 ` [Bug fortran/29267] " rguenth at gcc dot gnu dot org
@ 2006-10-04  7:00 ` fxcoudert at gcc dot gnu dot org
  2006-10-06 20:36 ` tobi at gcc dot gnu dot org
                   ` (14 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: fxcoudert at gcc dot gnu dot org @ 2006-10-04  7:00 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from fxcoudert at gcc dot gnu dot org  2006-10-04 06:59 -------
I think this code is valid. Changing to ice-on-valid-code.


-- 

fxcoudert at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   GCC host triplet|i686-pc-linux-gnu           |
           Keywords|ice-on-invalid-code         |ice-on-valid-code
   Last reconfirmed|2006-09-28 13:09:57         |2006-10-04 06:59:59
               date|                            |


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
  2006-09-28 13:10 ` [Bug fortran/29267] " rguenth at gcc dot gnu dot org
  2006-10-04  7:00 ` fxcoudert at gcc dot gnu dot org
@ 2006-10-06 20:36 ` tobi at gcc dot gnu dot org
  2006-10-06 20:37 ` tobi at gcc dot gnu dot org
                   ` (13 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: tobi at gcc dot gnu dot org @ 2006-10-06 20:36 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from tobi at gcc dot gnu dot org  2006-10-06 20:36 -------
Slightly reduced testcase, gives the same ice:
 implicit character*32 (a-z)                                                    
  CHARACTER(len=255), DIMENSION(1,2)  :: a                                      
  a = reshape((/ "x", to_string(1.0) /), (/ 1, 2 /))                            
END PROGRAM                                                                     



-- 


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (2 preceding siblings ...)
  2006-10-06 20:36 ` tobi at gcc dot gnu dot org
@ 2006-10-06 20:37 ` tobi at gcc dot gnu dot org
  2006-10-06 21:01 ` tobi at gcc dot gnu dot org
                   ` (12 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: tobi at gcc dot gnu dot org @ 2006-10-06 20:37 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from tobi at gcc dot gnu dot org  2006-10-06 20:37 -------
Another interesting variation:
schluter@pcl247:~/src/pr/29267> cat t.f90
 implicit character*32 (a-z)
  CHARACTER(len=255), DIMENSION(1,2)  :: a
  a = reshape((/ to_string(1.0) /), (/ 1, 2 /))
END PROGRAM
schluter@pcl247:~/src/pr/29267> ~/src/gcc/build/gcc/f951 t.f90
 MAIN__
t.f90:1: fatal error: gfc_todo: Not Implemented: complex character array
constructors
compilation terminated.
schluter@pcl247:~/src/pr/29267> 


-- 


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (3 preceding siblings ...)
  2006-10-06 20:37 ` tobi at gcc dot gnu dot org
@ 2006-10-06 21:01 ` tobi at gcc dot gnu dot org
  2006-10-06 21:42 ` tobi at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: tobi at gcc dot gnu dot org @ 2006-10-06 21:01 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from tobi at gcc dot gnu dot org  2006-10-06 21:01 -------
Actually this is invalid code.  The string lengths in the constructor are
different, even though they have to be the same.  See 4.5 in the F95 standard.


-- 

tobi at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Keywords|ice-on-valid-code           |ice-on-invalid-code


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (4 preceding siblings ...)
  2006-10-06 21:01 ` tobi at gcc dot gnu dot org
@ 2006-10-06 21:42 ` tobi at gcc dot gnu dot org
  2006-10-07  7:09 ` franke dot daniel at gmail dot com
                   ` (10 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: tobi at gcc dot gnu dot org @ 2006-10-06 21:42 UTC (permalink / raw)
  To: gcc-bugs



-- 

tobi at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |tobi at gcc dot gnu dot org
                   |dot org                     |
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2006-10-04 06:59:59         |2006-10-06 21:42:33
               date|                            |


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (5 preceding siblings ...)
  2006-10-06 21:42 ` tobi at gcc dot gnu dot org
@ 2006-10-07  7:09 ` franke dot daniel at gmail dot com
  2006-10-09 11:15 ` tobi at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: franke dot daniel at gmail dot com @ 2006-10-07  7:09 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from franke dot daniel at gmail dot com  2006-10-07 07:09 -------
Tobi,
> Actually this is invalid code.  The string lengths in the constructor are
> different, even though they have to be the same.  
please try the testcase in the orignal PR with idental string lengths. It will
crash gfortran as well.

OTOH, 
  a(1,1) = "x"
  a(1,2) = to_string(1.0)
should work even if 
  CHARACTER(len=255), DIMENSION(1,2) :: a
and
  CHARACTER(len=32) FUNCTION to_string(x),
so, why is an equivalent assignment through the array constructor invalid?


-- 


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (6 preceding siblings ...)
  2006-10-07  7:09 ` franke dot daniel at gmail dot com
@ 2006-10-09 11:15 ` tobi at gcc dot gnu dot org
  2006-10-13 15:54 ` franke dot daniel at gmail dot com
                   ` (8 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: tobi at gcc dot gnu dot org @ 2006-10-09 11:15 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from tobi at gcc dot gnu dot org  2006-10-09 11:14 -------
(In reply to comment #6)
> please try the testcase in the orignal PR with idental string lengths. It will
> crash gfortran as well.

Works for me.  Please provide a testcase.
schluter@pcl247:~/src/pr/29267> cat t.f90
! implicit character*32 (b-z)
  CHARACTER(len=255), DIMENSION(2)  :: a
  a = reshape((/ "12345678901234567890123456789012", to_string(1.0) /),
shape(a))
  print *, a
  CONTAINS
    CHARACTER(32) FUNCTION to_string(x)
      REAL, INTENT(in) :: x
      WRITE(to_string, FMT="(F6.3)") x
    END FUNCTION
END PROGRAM
schluter@pcl247:~/src/pr/29267> ~/src/gcc/build/gcc/f951 t.f90
 MAIN__ to_string
Execution times (seconds)
 parser                :   0.01 (100%) usr   0.00 ( 0%) sys   0.01 (100%) wall 
   132 kB (18%) ggc
 TOTAL                 :   0.01             0.00             0.01              
 740 kB
Extra diagnostic checks enabled; compiler may run slowly.
Configure with --disable-checking to disable checks.
schluter@pcl247:~/src/pr/29267> 

> so, why is an equivalent assignment through the array constructor invalid?

Because the standard says so, I already quoted the relevant part.


-- 


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (7 preceding siblings ...)
  2006-10-09 11:15 ` tobi at gcc dot gnu dot org
@ 2006-10-13 15:54 ` franke dot daniel at gmail dot com
  2006-10-13 19:19 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
                   ` (7 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: franke dot daniel at gmail dot com @ 2006-10-13 15:54 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from franke dot daniel at gmail dot com  2006-10-13 15:54 -------
As requested in comment #7, a testcase for equal string lengths (identical to
original PR but to_string() returns CHARACTER(len=255) instead of
CHARACTER(len=32)):

$> cat cat pr29267.f90
PROGRAM test_ice
  CHARACTER(len=255), DIMENSION(1,2)  :: a
  a = reshape((/ "x", to_string(1.0) /), (/ 1, 2 /))

  CONTAINS
    CHARACTER(len=255) FUNCTION to_string(x)
      REAL, INTENT(in) :: x
      WRITE(to_string, FMT="(F6.3)") x
    END FUNCTION
END PROGRAM

$> gfortran-4.2 -g -Wall pr29267.f90
pr29267.f90: In function 'MAIN__':
pr29267.f90:3: internal compiler error: in operand_subword_force, at
emit-rtl.c:1353

$> gfortran-4.2 -v
Using built-in specs.
Target: i686-pc-linux-gnu
Configured with: ../gcc/configure --prefix=$mylocalprefix --enable-bootstrap
--enable-threads=posix --enable-shared --with-system-zlib
--enable-languages=c,fortran --disable-nls --program-suffix=-4.2
Thread model: posix
gcc version 4.2.0 20061013 (experimental)


-- 


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (8 preceding siblings ...)
  2006-10-13 15:54 ` franke dot daniel at gmail dot com
@ 2006-10-13 19:19 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
  2006-10-14  8:46 ` franke dot daniel at gmail dot com
                   ` (6 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: Tobias dot Schlueter at physik dot uni-muenchen dot de @ 2006-10-13 19:19 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from Tobias dot Schlueter at physik dot uni-muenchen dot de  2006-10-13 19:19 -------
Subject: Re:  ICE in operand_subword_force, at
        emit-rtl.c:1353

franke dot daniel at gmail dot com <gcc-bugzilla@gcc.gnu.org> wrote on  
Fri, 13 Oct 2006:

> As requested in comment #7, a testcase for equal string lengths (identical to
> original PR but to_string() returns CHARACTER(len=255) instead of
> CHARACTER(len=32)):

Oh, that's what you meant with equal lengths  :-)  This is indeed not  
required by the standard.

And indeed, this triggers the same bug: the ICE has nothing to do with  
the assignment, it is the code dealing with the array constructor that  
is making us ICE.

Thanks!

----------------------------------------------------------------
This message was sent using IMP, the Internet Messaging Program.


-- 


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (9 preceding siblings ...)
  2006-10-13 19:19 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
@ 2006-10-14  8:46 ` franke dot daniel at gmail dot com
  2006-10-16 10:52 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
                   ` (5 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: franke dot daniel at gmail dot com @ 2006-10-14  8:46 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #10 from franke dot daniel at gmail dot com  2006-10-14 08:46 -------
Don't know whether it makes any difference - but if it is the array constructor
that crashes because of unequal string lengths within its arguments, why is
there no problem with this code?

PROGRAM test_constructor
  CHARACTER(len=32), DIMENSION(1,2)  :: a
  a = reshape((/ "one arg", "another arg" /), (/ 1, 2 /))
END PROGRAM

(Also compare with #3)


-- 


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


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

* [Bug fortran/29267] ICE in operand_subword_force, at emit-rtl.c:1353
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (10 preceding siblings ...)
  2006-10-14  8:46 ` franke dot daniel at gmail dot com
@ 2006-10-16 10:52 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
  2006-10-26 20:29 ` [Bug fortran/29267] different length non-constant strings in array constructors ICE tobias dot burnus at physik dot fu-berlin dot de
                   ` (4 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: Tobias dot Schlueter at physik dot uni-muenchen dot de @ 2006-10-16 10:52 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #11 from Tobias dot Schlueter at physik dot uni-muenchen dot de  2006-10-16 10:52 -------
Subject: Re:  ICE in operand_subword_force, at
        emit-rtl.c:1353

franke dot daniel at gmail dot com <gcc-bugzilla@gcc.gnu.org> wrote on  
Sat, 14 Oct 2006:
> Don't know whether it makes any difference - but if it is the array   
> constructor
> that crashes because of unequal string lengths within its arguments, why is
> there no problem with this code?
>
> PROGRAM test_constructor
>   CHARACTER(len=32), DIMENSION(1,2)  :: a
>   a = reshape((/ "one arg", "another arg" /), (/ 1, 2 /))
> END PROGRAM

Because this doesn't trigger the buggy codepath :-)  Sometime in the  
past someone went to some lengths to support this kind of invalid  
code.  Had they read the standard closely, they could have saved  
themselves some work.

> (Also compare with #3)

I don't see the relation.

Cheers,
- Tobi

----------------------------------------------------------------
This message was sent using IMP, the Internet Messaging Program.


-- 


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


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

* [Bug fortran/29267] different length non-constant strings in array constructors ICE
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (11 preceding siblings ...)
  2006-10-16 10:52 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
@ 2006-10-26 20:29 ` tobias dot burnus at physik dot fu-berlin dot de
  2006-10-27 13:33 ` tobi at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: tobias dot burnus at physik dot fu-berlin dot de @ 2006-10-26 20:29 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #12 from tobias dot burnus at physik dot fu-berlin dot de  2006-10-26 20:29 -------
> > why is there no problem with this code?
> >
> > PROGRAM test_constructor
> >   CHARACTER(len=32), DIMENSION(1,2)  :: a
> >   a = reshape((/ "one arg", "another arg" /), (/ 1, 2 /))
> > END PROGRAM
> 
> Because this doesn't trigger the buggy codepath :-) Sometime in the  
> past someone went to some lengths to support this kind of invalid  
> code.  Had they read the standard closely, they could have saved  
> themselves some work.

The question is whether one wants to support such code or not?

NAG f95 gives an error even with -dusty. sunf95 gives an error. g95 and ifort
compile by default, but with -std=f95 / -stand f95 the give an error / warning
(respectively).
gfortran does not give such warning/error.
See also: bug 27998


-- 


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


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

* [Bug fortran/29267] different length non-constant strings in array constructors ICE
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (12 preceding siblings ...)
  2006-10-26 20:29 ` [Bug fortran/29267] different length non-constant strings in array constructors ICE tobias dot burnus at physik dot fu-berlin dot de
@ 2006-10-27 13:33 ` tobi at gcc dot gnu dot org
  2006-10-28 13:09 ` tobias dot burnus at physik dot fu-berlin dot de
                   ` (2 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: tobi at gcc dot gnu dot org @ 2006-10-27 13:33 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #13 from tobi at gcc dot gnu dot org  2006-10-27 13:33 -------
Thanks for the pointer to the other PR.  Do g95 and ifort also compile the
original testcase and do The Right Thing?

I didn't have time to fix this after I assigned myself to it, so unassigining.


-- 

tobi at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
  BugsThisDependsOn|                            |27998
         AssignedTo|tobi at gcc dot gnu dot org |unassigned at gcc dot gnu
                   |                            |dot org
             Status|ASSIGNED                    |NEW


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


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

* [Bug fortran/29267] different length non-constant strings in array constructors ICE
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (13 preceding siblings ...)
  2006-10-27 13:33 ` tobi at gcc dot gnu dot org
@ 2006-10-28 13:09 ` tobias dot burnus at physik dot fu-berlin dot de
  2007-12-07 22:12 ` reichelt at gcc dot gnu dot org
  2007-12-07 22:43 ` burnus at gcc dot gnu dot org
  16 siblings, 0 replies; 18+ messages in thread
From: tobias dot burnus at physik dot fu-berlin dot de @ 2006-10-28 13:09 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #14 from tobias dot burnus at physik dot fu-berlin dot de  2006-10-28 13:09 -------
> Do g95 and ifort also compile the original testcase and do The Right Thing?

No. g95 has a run-time error, ifort garbage at the beginning (but no crash);
f95 and sunf95 don't compile.

gfortran: ICE for "x", for "x    ": compiles, but garbage (extra 1.000) at run
time, for "x"//31characters: ok like all the other compilers


> g95 ice29267.f90
> ./a.out
Fortran runtime error: Inconsistent string size in array constructor

> ifort ice4.f90
> ./a.out # with print *, a:
 xw~D#&#65533;*'@x$&#65533;
  1.000

NAGf95:
Array constructor values have differing CHARACTER lengths (1 and 32)
sunf95:
Line = 3, Column = 23: ERROR: Array constructor values of type character must
all have the same length.


-- 


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


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

* [Bug fortran/29267] different length non-constant strings in array constructors ICE
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (14 preceding siblings ...)
  2006-10-28 13:09 ` tobias dot burnus at physik dot fu-berlin dot de
@ 2007-12-07 22:12 ` reichelt at gcc dot gnu dot org
  2007-12-07 22:43 ` burnus at gcc dot gnu dot org
  16 siblings, 0 replies; 18+ messages in thread
From: reichelt at gcc dot gnu dot org @ 2007-12-07 22:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #15 from reichelt at gcc dot gnu dot org  2007-12-07 22:12 -------
Btw, the original testcase started compiling on mainline between 2007-07-16 and
2007-08-15. It now compiles and runs without error.


-- 

reichelt at gcc dot gnu dot org changed:

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


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


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

* [Bug fortran/29267] different length non-constant strings in array constructors ICE
  2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
                   ` (15 preceding siblings ...)
  2007-12-07 22:12 ` reichelt at gcc dot gnu dot org
@ 2007-12-07 22:43 ` burnus at gcc dot gnu dot org
  16 siblings, 0 replies; 18+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-12-07 22:43 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #16 from burnus at gcc dot gnu dot org  2007-12-07 22:43 -------
> Btw, the original testcase started compiling on mainline between 2007-07-16 and
> 2007-08-15. It now compiles and runs without error.

Cool. And for -std=f95/f2003 the invalid code is rejected.
=> CLOSE. I think (hope?) thate the testsuite covers this PR..


-- 

burnus at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2007-12-07 22:43 UTC | newest]

Thread overview: 18+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2006-09-28 10:12 [Bug fortran/29267] New: ICE in operand_subword_force, at emit-rtl.c:1353 franke dot daniel at gmail dot com
2006-09-28 13:10 ` [Bug fortran/29267] " rguenth at gcc dot gnu dot org
2006-10-04  7:00 ` fxcoudert at gcc dot gnu dot org
2006-10-06 20:36 ` tobi at gcc dot gnu dot org
2006-10-06 20:37 ` tobi at gcc dot gnu dot org
2006-10-06 21:01 ` tobi at gcc dot gnu dot org
2006-10-06 21:42 ` tobi at gcc dot gnu dot org
2006-10-07  7:09 ` franke dot daniel at gmail dot com
2006-10-09 11:15 ` tobi at gcc dot gnu dot org
2006-10-13 15:54 ` franke dot daniel at gmail dot com
2006-10-13 19:19 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
2006-10-14  8:46 ` franke dot daniel at gmail dot com
2006-10-16 10:52 ` Tobias dot Schlueter at physik dot uni-muenchen dot de
2006-10-26 20:29 ` [Bug fortran/29267] different length non-constant strings in array constructors ICE tobias dot burnus at physik dot fu-berlin dot de
2006-10-27 13:33 ` tobi at gcc dot gnu dot org
2006-10-28 13:09 ` tobias dot burnus at physik dot fu-berlin dot de
2007-12-07 22:12 ` reichelt at gcc dot gnu dot org
2007-12-07 22:43 ` burnus 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).