This is the mail archive of the gcc-bugs@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]

ICE in g77 using -fnoemulate-complex on mips-sgi-irix6.2


As reported in http://www.cygnus.com/ml/egcs-bugs/1999-Jan/0334.html,
this program gives the wrong answer when compiled with g77  -O2
using recent snapshots on mips-sgi-irix.  

The problem is derived from the LAPACK testsuite, and seems responsible 
for a number of single precision complex test failures.

I have now found that it:
   works with "-O1 -fnoemulate-complex"
   gives an ICE with "-O2 -fnoemulate-complex"
Perhaps the two problems are related.

Compiler output and gdb backtrace attached.  Happy to follow up,
but don't know how

+++++++++++++++++++++++++++++++++++++++++
(Mr) David Billinghurst
Comalco Research Centre
PO Box 316, Thomastown, Vic, Australia, 3074
Phone:	+61 3 9469 0642
FAX:	+61 3 9462 2700
Email:	David.Billinghurst@riotinto.com.au 

##################################################################
      program labug2
      implicit none

*  This program gives the wrong answer on mips-sgi-irix6.2
*  when compiled with g77 -O2 from egcs-19981226 
*  (and several previous) snapshots
*
*  Works with:  -O1
*               egcs-1.1.1 with -O2
*
*  Originally derived from LAPACK test suite.
*
*  David Billinghurst, (David.Billinghurst@riotinto.com.au)
*  31 December 1998
* 
*
      complex x(1), ap(1), half
      half  = 0.5 
      x(1)  = 0.0
      ap(1) =  half
      call  cspr( 1, x, ap )

*     Is the answer correct?
      if ( abs(ap(1)-half) .gt. 1.0e-5 ) then
         write(6,*) 'AP(1) should be (0.5,0.0)'
         call abort()
      end if
      end

      SUBROUTINE CSPR( N, X, AP )
      INTEGER            N, J
      COMPLEX            AP( N ), X( N )
      DO J = 1, N
         IF( X( J ) .eq. (0.0,0.0) ) THEN
            AP( j ) = AP( j )
         END IF
      END DO
      RETURN
      END
##################################################################

cru200:68%/exd4/billingd/tmp/egcs-19990214/bin/g77 -v -O2
-fno-emulate-complex -Wall -o labug2a-fno-emulate-complex labug2a.f
g77 version egcs-2.93.08 19990214 (gcc2 ss-980929 experimental) (from
FSF-g77 version 0.5.24-19980804)
Driving: /exd4/billingd/tmp/egcs-19990214/bin/g77 -v -O2
-fno-emulate-complex -Wall -o labug2a-fno-emulate-complex labug2a.f -lg2c
-lm
Reading specs from
/exd4/billingd/tmp/egcs-19990214/lib/gcc-lib/mips-sgi-irix6.2/egcs-2.93.08/s
pecs
gcc version egcs-2.93.08 19990214 (gcc2 ss-980929 experimental)
 
/exd4/billingd/tmp/egcs-19990214/lib/gcc-lib/mips-sgi-irix6.2/egcs-2.93.08/f
771 labug2a.f -quiet -dumpbase labug2a.f -O2 -Wall -version -fversion
-fno-emulate-complex -o /var/tmp/ccoOdaaa.s
GNU F77 version egcs-2.93.08 19990214 (gcc2 ss-980929 experimental)
(mips-sgi-irix6.2) compiled by GNU C version egcs-2.93.08 19990214 (gcc2
ss-980929 experimental).
GNU Fortran Front End version 0.5.24-19980804
/exd4/billingd/src/egcs-19990214/gcc/emit-rtl.c:991: Internal compiler error
in function gen_lowpart
Please submit a full bug report to `egcs-bugs@egcs.cygnus.com'.
See <URL:http://egcs.cygnus.com/faq.html#bugreport> for details.



cru200:69%gdb
/exd4/billingd/tmp/egcs-19990214/lib/gcc-lib/mips-sgi-irix6.2/egcs-2.93.08/f
771
GNU gdb 4.17
Copyright 1998 Free Software Foundation, Inc.
GDB is free software, covered by the GNU General Public License, and you are
welcome to change it and/or distribute copies of it under certain
conditions.
Type "show copying" to see the conditions.
There is absolutely no warranty for GDB.  Type "show warranty" for details.
This GDB was configured as "mips-sgi-irix6.2"...
(gdb) break emit-rtl.c:991
Breakpoint 1 at 0x1015b3a8: file
/exd4/billingd/src/egcs-19990214/gcc/emit-rtl.c, line 991.
(gdb) run labug2a.f -quiet -dumpbase labug2a.f -O2 -Wall -version -fversion
-fno
-emulate-complex -o labug2a.s 
Starting program:
/exd4/billingd/tmp/egcs-19990214/lib/gcc-lib/mips-sgi-irix6.2/egcs-2.93.08/f
771 labug2a.f -quiet -dumpbase labug2a.f -O2 -Wall -version -fversion
-fno-emulate-complex -o labug2a.s
GNU F77 version egcs-2.93.08 19990214 (gcc2 ss-980929 experimental)
(mips-sgi-irix6.2) compiled by GNU C version egcs-2.93.08 19990214 (gcc2
ss-980929 experimental).
GNU Fortran Front End version 0.5.24-19980804

Breakpoint 1, gen_lowpart (mode=DImode, x=0x10365368)
    at /exd4/billingd/src/egcs-19990214/gcc/emit-rtl.c:991
991         abort ();

(gdb) list
986           return change_address (x, mode, plus_constant (XEXP (x, 0),
offset));
987         }
988       else if (GET_CODE (x) == ADDRESSOF)
989         return gen_lowpart (mode, force_reg (GET_MODE (x), x));
990       else
991         abort ();
992     }
993     
994     /* Like `gen_lowpart', but refer to the most significant part. 
995        This is used to access the imaginary part of a complex number.
*/

(gdb) p lineno
$1 = 35

(gdb) p input_filename
$2 = 0x103552a4 "labug2a.f"

(gdb) bt
#0  gen_lowpart (mode=DImode, x=0x10365368)
    at /exd4/billingd/src/egcs-19990214/gcc/emit-rtl.c:991
#1  0x1013370c in store_bit_field (str_rtx=0x0, bitsize=64, bitnum=0, 
    fieldmode=SCmode, value=0x10365368, align=4, total_size=-1)
    at /exd4/billingd/src/egcs-19990214/gcc/expmed.c:575
#2  0x1011d074 in store_field (target=0x10365188, bitsize=64, bitpos=0, 
    mode=SCmode, exp=0x10343030, value_mode=VOIDmode, unsignedp=0, align=4, 
    total_size=-1, alias_set=0)
    at /exd4/billingd/src/egcs-19990214/gcc/expr.c:4660
#3  0x1011a0ac in expand_assignment (to=0x10343000, from=0x10343030, 
    want_value=0, suggest_reg=991)
    at /exd4/billingd/src/egcs-19990214/gcc/expr.c:3360
#4  0x101241e4 in expand_expr (exp=0x10343048, target=0x1034d988, 
    tmode=VOIDmode, modifier=EXPAND_NORMAL)
    at /exd4/billingd/src/egcs-19990214/gcc/expr.c:7874
#5  0x10106ff0 in expand_expr_stmt (exp=0x10343048)
    at /exd4/billingd/src/egcs-19990214/gcc/stmt.c:1698
#6  0x10044aa0 in ffecom_expand_let_stmt (dest=0x103632a8,
source=0x10361050)
    at /exd4/billingd/src/egcs-19990214/gcc/f/com.c:11680
#7  0x100bd8fc in ffeste_R737A (dest=0x103632a8, source=0x10361050)
    at /exd4/billingd/src/egcs-19990214/gcc/f/ste.c:2187
#8  0x100b1614 in ffestd_stmt_pass_ ()
    at /exd4/billingd/src/egcs-19990214/gcc/f/std.c:746
#9  0x100b2870 in ffestd_exec_end ()
    at /exd4/billingd/src/egcs-19990214/gcc/f/std.c:1496
#10 0x100a53b0 in ffestc_shriek_subroutine_ (ok=true)
    at /exd4/billingd/src/egcs-19990214/gcc/f/stc.c:4935
#11 0x100affa8 in ffestc_R1225 (name=0x0)
    at /exd4/billingd/src/egcs-19990214/gcc/f/stc.c:12425
#12 0x100a60d0 in ffestc_end ()
    at /exd4/billingd/src/egcs-19990214/gcc/f/stc.c:5658
#13 0x10086564 in ffestb_end3_ (t=0x10363da8)
    at /exd4/billingd/src/egcs-19990214/gcc/f/stb.c:3206
#14 0x10085fe8 in ffestb_end (t=0x10363da8)
    at /exd4/billingd/src/egcs-19990214/gcc/f/stb.c:2985
#15 0x10081794 in ffesta_second_ (t=0x10363da8)
    at /exd4/billingd/src/egcs-19990214/gcc/f/sta.c:1359
#16 0x1007a6ec in ffelex_send_token_ ()
    at /exd4/billingd/src/egcs-19990214/gcc/f/lex.c:1694
#17 0x10078864 in ffelex_finish_statement_ ()
    at /exd4/billingd/src/egcs-19990214/gcc/f/lex.c:973
#18 0x1007c108 in ffelex_file_fixed (wf=0x0, f=0xfb4aa88)
    at /exd4/billingd/src/egcs-19990214/gcc/f/lex.c:3056
#19 0x100d4658 in ffe_file (wf=0x103552a0, f=0xfb4aa88)
    at /exd4/billingd/src/egcs-19990214/gcc/f/top.c:544
#20 0x1007f764 in yyparse ()
    at /exd4/billingd/src/egcs-19990214/gcc/f/parse.c:79
#21 0x100d8a5c in compile_file (name=0x7fff3050 "labug2a.f")
    at /exd4/billingd/src/egcs-19990214/gcc/toplev.c:2974
#22 0x100dd1f0 in main (argc=12, argv=0x7fff2f14)
    at /exd4/billingd/src/egcs-19990214/gcc/toplev.c:5273



Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]