nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / dec_init_2.f90
blob2563c2ff6537b47dcfcb507a9c0bb929c66ba732
1 ! { dg-do run }
2 ! { dg-options "-fdec-structure -finit-derived -finit-integer=42 -finit-real=nan -finit-logical=true -finit-character=32" }
3 ! { dg-add-options ieee }
5 ! Test -finit-derived with DEC structure and union.
8 subroutine dummy(i1,r1,c1,l1,i2,r2,c2,l2)
9 implicit none
10 integer, intent(in) :: i1
11 real, intent(in) :: r1
12 character, intent(in) :: c1
13 logical, intent(in) :: l1
14 integer, intent(inout) :: i2
15 real, intent(inout) :: r2
16 character, intent(inout) :: c2
17 logical, intent(inout) :: l2
18 print *, i1, i2, l1, l2, ichar(c1), ichar(c2), r1, r2
19 if ( i1 .ne. 42 .or. i2 .ne. 42 ) STOP 1
20 if ( (.not. l1) .or. (.not. l2) ) STOP 2
21 if ( c1 .ne. achar(32) .or. c2 .ne. achar(32) ) STOP 3
22 if ( (.not. isnan(r1)) .or. (.not. isnan(r2)) ) STOP 4
23 end subroutine
25 ! Nb. the current implementation decides the -finit-* flags are meaningless
26 ! with components of a union, so we omit the union test here.
28 structure /s2/
29 integer i2
30 real r2
31 character c2
32 logical l2
33 end structure
35 structure /s1/
36 logical l1
37 real r1
38 character c1
39 integer i1
40 record /s2/ y
41 end structure
43 record /s1/ x
45 call dummy (x.i1, x.r1, x.c1, x.l1, x.y.i2, x.y.r2, x.y.c2, x.y.l2)
47 end