nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / associate_57.f90
blob80c7668417476cbe06cee2336f5e60b0fb25e2f7
1 ! { dg-do compile }
2 ! PR 96386 - this used to cause an ICE.
3 ! Test case by Menno Deij - van Rijswijk.
5 MODULE assoc
7 TYPE Level3
8 INTEGER :: someNumber
9 END TYPE Level3
11 TYPE Level2
12 INTEGER :: nLevel3
13 TYPE (Level3), ALLOCATABLE :: levels3(:)
15 END TYPE Level2
17 TYPE Level1
18 INTEGER :: nLevel2
19 TYPE (Level2), ALLOCATABLE :: levels2(:)
20 END TYPE Level1
22 TYPE outer_type
23 INTEGER :: nLevel1
24 TYPE (Level1), ALLOCATABLE :: levels1(:)
25 END TYPE outer_type
27 TYPE(outer_type), TARGET :: outer
29 CONTAINS
31 SUBROUTINE internal_compiler_error_repro()
33 INTEGER F,B,Z
35 ASSOCIATE(l1 => outer%levels1 ) ! <-- this gives an ICE
36 !ASSOCIATE(l1 => outer%levels1(:) ) ! <-- No ICE if array spec is added
37 DO F=1,outer%nLevel1
38 ASSOCIATE(l2 => l1(F)%levels2 )
39 DO B=1,l2(F)%nLevel3 ! <-- condition for ICE to be triggered
41 END DO
42 END ASSOCIATE
43 END DO
44 END ASSOCIATE
46 END SUBROUTINE internal_compiler_error_repro
47 end module