lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / bound_simplification_6.f90
blob31a9bab590cc2235e25ba7eca8f0239be0d37676
1 ! { dg-do compile }
2 ! { dg-additional-options "-fdump-tree-original" }
4 ! PR fortran/66100
5 ! ICE on lbound simplification
7 ! Original test case by Joost VandeVondele <Joost.VandeVondele@mat.ethz.ch>
8 ! Reduced by Thomas Koenig <tkoenig@gcc.gnu.org>
10 MODULE qs_integrate_potential_low
11 INTEGER, PARAMETER :: dp = 8
12 TYPE cell_type
13 REAL(KIND=8) :: h_inv(3,3)
14 END TYPE
15 TYPE(cell_type), POINTER :: cell
16 REAL(KIND=dp), DIMENSION(3) :: rp
17 CONTAINS
18 SUBROUTINE integrate_general_opt()
19 REAL(KIND=dp) :: gp(3)
20 INTEGER :: ng
21 if (any(lbound(cell%h_inv) /= 1)) STOP 1
22 if (any(ubound(cell%h_inv) /= 3)) STOP 2
23 END SUBROUTINE integrate_general_opt
24 END MODULE qs_integrate_potential_low
25 ! { dg-final { scan-tree-dump-not "bound" "original" } }
26 ! { dg-final { scan-tree-dump-not "_gfortran_stop" "original" } }