public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug middle-end/30835]  New: ICE with -O2 -ftree-loop-linear
@ 2007-02-17 16:15 jv244 at cam dot ac dot uk
  2007-02-17 20:24 ` [Bug middle-end/30835] " steven at gcc dot gnu dot org
                   ` (4 more replies)
  0 siblings, 5 replies; 6+ messages in thread
From: jv244 at cam dot ac dot uk @ 2007-02-17 16:15 UTC (permalink / raw)
  To: gcc-bugs

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

the following, reduced from PR29975,  causes a gfortran ICE:

MODULE test
  INTEGER, PARAMETER :: dp=KIND(0.0D0), xas_scf_default=1, xas_2s_type=2
  TYPE xas_control_type
    INTEGER :: state_type,nexc_atoms
  END TYPE
  TYPE xas_environment_type
    INTEGER :: scf_method
  END TYPE
CONTAINS
  SUBROUTINE xas_env_init(xas_env, xas_control)
    TYPE(xas_environment_type), POINTER      :: xas_env
    TYPE(xas_control_type)                   :: xas_control
    REAL(dp), DIMENSION(:, :), POINTER       :: sto_alpha

      IF(xas_env%scf_method==xas_scf_default) THEN
        ALLOCATE(sto_alpha(1,0:1),STAT=istat)
      ELSEIF( xas_control%state_type == xas_2s_type ) THEN
        ALLOCATE(sto_alpha(2,0:1),STAT=istat)
      END IF
      DO iat = 1,xas_control%nexc_atoms
        sto_alpha = 0.0_dp
      END DO
  END SUBROUTINE xas_env_init
END MODULE



gfortran -O2 -ftree-loop-linear test.f90
test.f90: In function ‘xas_env_init’:
test.f90:10: internal compiler error: Segmentation fault
Please submit a full bug report,
with preprocessed source if appropriate.
See <URL:http://gcc.gnu.org/bugs.html> for instructions.


-- 
           Summary: ICE with -O2 -ftree-loop-linear
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: middle-end
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: jv244 at cam dot ac dot uk


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


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

* [Bug middle-end/30835] ICE with -O2 -ftree-loop-linear
  2007-02-17 16:15 [Bug middle-end/30835] New: ICE with -O2 -ftree-loop-linear jv244 at cam dot ac dot uk
@ 2007-02-17 20:24 ` steven at gcc dot gnu dot org
  2007-03-11 22:31 ` rakdver at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: steven at gcc dot gnu dot org @ 2007-02-17 20:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from steven at gcc dot gnu dot org  2007-02-17 20:24 -------
(gdb) run
Starting program: ./f951 -O2 -ftree-loop-linear t.f90
 xas_env_init
Analyzing compilation unit
Performing interprocedural optimizations
 <visibility> <early_local_cleanups> <inline> <static-var> <pure-const>
<type-escape-var>Assembling functions:
 xas_env_init
Program received signal SIGSEGV, Segmentation fault.
0x0000000000d17446 in can_convert_to_perfect_nest (loop=0x1147530)
    at ../../trunk/gcc/lambda-code.c:2363
2363                                    if (bb_for_stmt (arg_stmt)->loop_father
(gdb) bt 10
#0  0x0000000000d17446 in can_convert_to_perfect_nest (loop=0x1147530)
    at ../../trunk/gcc/lambda-code.c:2363
#1  0x0000000000d1272b in gcc_loopnest_to_lambda_loopnest (loop_nest=0x1147530,
    inductionvars=0x7ffffff106b8, invariants=0x7ffffff106b0) at
../../trunk/gcc/lambda-code.c:1475
#2  0x0000000000ce2944 in linear_transform_loops () at
../../trunk/gcc/tree-loop-linear.c:322
#3  0x0000000000902b26 in tree_linear_transform () at
../../trunk/gcc/tree-ssa-loop.c:217
#4  0x0000000000729274 in execute_one_pass (pass=0x1048420) at
../../trunk/gcc/passes.c:1055
#5  0x00000000007293be in execute_pass_list (pass=0x1048420) at
../../trunk/gcc/passes.c:1107
#6  0x00000000007293dc in execute_pass_list (pass=0x1048240) at
../../trunk/gcc/passes.c:1108
#7  0x00000000007293dc in execute_pass_list (pass=0x1047700) at
../../trunk/gcc/passes.c:1108
#8  0x0000000000852d84 in tree_rest_of_compilation (fndecl=0x2aaaab14d2a0)
    at ../../trunk/gcc/tree-optimize.c:412
#9  0x0000000000479d6b in gfc_expand_function (fndecl=0x2aaaab14d2a0)
    at ../../trunk/gcc/fortran/f95-lang.c:239
(More stack frames follow...)
(gdb)        


-- 

steven 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-02-17 20:24:42
               date|                            |


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


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

* [Bug middle-end/30835] ICE with -O2 -ftree-loop-linear
  2007-02-17 16:15 [Bug middle-end/30835] New: ICE with -O2 -ftree-loop-linear jv244 at cam dot ac dot uk
  2007-02-17 20:24 ` [Bug middle-end/30835] " steven at gcc dot gnu dot org
@ 2007-03-11 22:31 ` rakdver at gcc dot gnu dot org
  2007-03-12 21:56 ` rakdver at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  4 siblings, 0 replies; 6+ messages in thread
From: rakdver at gcc dot gnu dot org @ 2007-03-11 22:31 UTC (permalink / raw)
  To: gcc-bugs



-- 

rakdver at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |rakdver at gcc dot gnu dot
                   |dot org                     |org
             Status|NEW                         |ASSIGNED
   Last reconfirmed|2007-02-17 20:24:42         |2007-03-11 22:31:17
               date|                            |


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


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

* [Bug middle-end/30835] ICE with -O2 -ftree-loop-linear
  2007-02-17 16:15 [Bug middle-end/30835] New: ICE with -O2 -ftree-loop-linear jv244 at cam dot ac dot uk
  2007-02-17 20:24 ` [Bug middle-end/30835] " steven at gcc dot gnu dot org
  2007-03-11 22:31 ` rakdver at gcc dot gnu dot org
@ 2007-03-12 21:56 ` rakdver at gcc dot gnu dot org
  2007-03-14 16:30 ` jv244 at cam dot ac dot uk
  2007-03-15  8:47 ` burnus at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: rakdver at gcc dot gnu dot org @ 2007-03-12 21:56 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from rakdver at gcc dot gnu dot org  2007-03-12 21:56 -------
Subject: Bug 30835

Author: rakdver
Date: Mon Mar 12 21:56:12 2007
New Revision: 122866

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=122866
Log:
        PR tree-optimization/30835
        * lambda-code.c (can_convert_to_perfect_nest): Check whether
        bb_for_stmt is not NULL before accessing it.


Modified:
    trunk/gcc/ChangeLog
    trunk/gcc/lambda-code.c


-- 


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


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

* [Bug middle-end/30835] ICE with -O2 -ftree-loop-linear
  2007-02-17 16:15 [Bug middle-end/30835] New: ICE with -O2 -ftree-loop-linear jv244 at cam dot ac dot uk
                   ` (2 preceding siblings ...)
  2007-03-12 21:56 ` rakdver at gcc dot gnu dot org
@ 2007-03-14 16:30 ` jv244 at cam dot ac dot uk
  2007-03-15  8:47 ` burnus at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: jv244 at cam dot ac dot uk @ 2007-03-14 16:30 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from jv244 at cam dot ac dot uk  2007-03-14 16:30 -------
(In reply to comment #2)

this issue now seems fixed on trunk for me as well, so I guess this could be
closed.


-- 


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


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

* [Bug middle-end/30835] ICE with -O2 -ftree-loop-linear
  2007-02-17 16:15 [Bug middle-end/30835] New: ICE with -O2 -ftree-loop-linear jv244 at cam dot ac dot uk
                   ` (3 preceding siblings ...)
  2007-03-14 16:30 ` jv244 at cam dot ac dot uk
@ 2007-03-15  8:47 ` burnus at gcc dot gnu dot org
  4 siblings, 0 replies; 6+ messages in thread
From: burnus at gcc dot gnu dot org @ 2007-03-15  8:47 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from burnus at gcc dot gnu dot org  2007-03-15 08:47 -------
(In reply to comment #3)
> this issue now seems fixed on trunk for me as well, so I guess this could be
> closed.
Mark FIXED based on this comment and on the fact that it works with gfortran
4.3, 4.2, 4.1.


-- 

burnus at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2007-03-15  8:47 UTC | newest]

Thread overview: 6+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2007-02-17 16:15 [Bug middle-end/30835] New: ICE with -O2 -ftree-loop-linear jv244 at cam dot ac dot uk
2007-02-17 20:24 ` [Bug middle-end/30835] " steven at gcc dot gnu dot org
2007-03-11 22:31 ` rakdver at gcc dot gnu dot org
2007-03-12 21:56 ` rakdver at gcc dot gnu dot org
2007-03-14 16:30 ` jv244 at cam dot ac dot uk
2007-03-15  8:47 ` 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).