Remove old autovect-branch by moving to "dead" directory.
[official-gcc.git] / old-autovect-branch / gcc / testsuite / gfortran.dg / namelist_15.f90
blob50f02927ce5d29e11633e807b3aef8df7c3de130
1 !{ dg-do run }
2 ! Tests arrays of derived types containing derived type arrays whose
3 ! components are character arrays - exercises object name parser in
4 ! list_read.c. Checks that namelist output can be reread.
5 ! provided by Paul Thomas - pault@gcc.gnu.org
7 module global
8 type :: mt
9 character(len=2) :: ch(2) = (/"aa","bb"/)
10 end type mt
11 type :: bt
12 integer :: i(2) = (/1,2/)
13 type(mt) :: m(2)
14 end type bt
15 end module global
17 program namelist_15
18 use global
19 type(bt) :: x(2)
21 namelist /mynml/ x
23 open (10, status = "scratch")
24 write (10, '(A)') "&MYNML"
25 write (10, '(A)') " x = 3, 4, 'dd', 'ee', 'ff', 'gg',"
26 write (10, '(A)') " 4, 5, 'hh', 'ii', 'jj', 'kk',"
27 write (10, '(A)') " x%i = , ,-3, -4"
28 write (10, '(A)') " x(2)%m(1)%ch(2) ='q',"
29 write (10, '(A)') " x(2)%m(2)%ch(1)(1) ='w',"
30 write (10, '(A)') " x%m%ch(:)(2) = 'z','z','z','z','z','z','z','z',"
31 write (10, '(A)') "&end"
33 rewind (10)
34 read (10, nml = mynml, iostat = ier)
35 if (ier .ne. 0) print *, 'First read.' !call abort ()
36 close (10)
38 open (10, status = "scratch", delim='apostrophe')
39 write (10, nml = mynml)
40 rewind (10)
42 read (10, nml = mynml, iostat = ier)
43 if (ier .ne. 0) print *, 'Second read.' !call abort ()
44 close(10)
46 if (.not. ((x(1)%i(1) == 3) .and. &
47 (x(1)%i(2) == 4) .and. &
48 (x(1)%m(1)%ch(1) == "dz") .and. &
49 (x(1)%m(1)%ch(2) == "ez") .and. &
50 (x(1)%m(2)%ch(1) == "fz") .and. &
51 (x(1)%m(2)%ch(2) == "gz") .and. &
52 (x(2)%i(1) == -3) .and. &
53 (x(2)%i(2) == -4) .and. &
54 (x(2)%m(1)%ch(1) == "hz") .and. &
55 (x(2)%m(1)%ch(2) == "qz") .and. &
56 (x(2)%m(2)%ch(1) == "wz") .and. &
57 (x(2)%m(2)%ch(2) == "kz"))) call abort ()
59 end program namelist_15