nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / array_constructor_55.f90
blob52142cb10c091e15276bc026536a5ee314a3cc0d
1 ! { dg-do run }
2 ! PR fortran/66193 - ICE for initialisation of some non-zero-sized arrays
3 ! Testcase by G.Steinmetz
5 program p
6 implicit none
7 call s1
8 call s2
9 call s3
10 call s4
11 contains
12 subroutine s1
13 integer(8), parameter :: z1(2) = 10 + [ integer(8) :: [ integer(4) ::],1,2]
14 integer(8) :: z2(2) = 10 + [ integer(8) :: [ integer(4) ::],1,2]
15 integer(8) :: z3(2)
16 z3 = 10 + [ integer(8) :: [ integer(4) :: ], 1, 2 ]
17 if ( z1(1) /= 11 .or. z1(2) /= 12 ) stop 1
18 if ( z2(1) /= 11 .or. z2(2) /= 12 ) stop 2
19 if ( z3(1) /= 11 .or. z3(2) /= 12 ) stop 3
20 end subroutine s1
22 subroutine s2
23 logical(8), parameter :: z1(3) = .true. .or. &
24 [ logical(8) :: [ logical(4) :: ], .false., .false., .true. ]
25 logical(8) :: z2(3) = .true. .or. &
26 [ logical(8) :: [ logical(4) :: ], .false., .false., .true. ]
27 logical(8) :: z3(3)
28 z3 = .true. .or. &
29 [ logical(8) :: [ logical(4) :: ], .false., .false., .true. ]
30 if ( .not. all(z1) ) stop 11
31 if ( .not. all(z2) ) stop 12
32 if ( .not. all(z3) ) stop 13
33 end subroutine s2
35 subroutine s3
36 real(8), parameter :: eps = 4.0_8 * epsilon(1.0_8)
37 real(8), parameter :: z1(2) = 10. + [ real(8) :: [ real(4) :: ], 1., 2. ]
38 real(8) :: z2(2) = 10. + [ real(8) :: [ real(4) :: ], 1., 2. ]
39 real(8) :: z3(2)
40 z3 = 10.0 + [ real(8) :: [ real(4) :: ], 1.0, 2.0 ]
42 if ( abs(1-z1(1)/11) > eps ) stop 21
43 if ( abs(1-z1(2)/12) > eps ) stop 22
44 if ( abs(1-z2(1)/11) > eps ) stop 23
45 if ( abs(1-z2(2)/12) > eps ) stop 24
46 if ( abs(1-z3(1)/11) > eps ) stop 25
47 if ( abs(1-z3(2)/12) > eps ) stop 26
48 end subroutine s3
50 subroutine s4
51 real, parameter :: x(3) = 2.0 * [real :: 1, (2), 3]
52 real, parameter :: y(2) = [real :: 1, (2)] + 10.0
53 real, parameter :: z(2) = [real ::(1),(2)] + 10.0
54 end subroutine s4
55 end program p