summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/namelist_15.f90
diff options
context:
space:
mode:
authorupstream source tree <ports@midipix.org>2015-03-15 20:14:05 -0400
committerupstream source tree <ports@midipix.org>2015-03-15 20:14:05 -0400
commit554fd8c5195424bdbcabf5de30fdc183aba391bd (patch)
tree976dc5ab7fddf506dadce60ae936f43f58787092 /gcc/testsuite/gfortran.dg/namelist_15.f90
downloadcbb-gcc-4.6.4-554fd8c5195424bdbcabf5de30fdc183aba391bd.tar.bz2
cbb-gcc-4.6.4-554fd8c5195424bdbcabf5de30fdc183aba391bd.tar.xz
obtained gcc-4.6.4.tar.bz2 from upstream website;upstream
verified gcc-4.6.4.tar.bz2.sig; imported gcc-4.6.4 source tree from verified upstream tarball. downloading a git-generated archive based on the 'upstream' tag should provide you with a source tree that is binary identical to the one extracted from the above tarball. if you have obtained the source via the command 'git clone', however, do note that line-endings of files in your working directory might differ from line-endings of the respective files in the upstream repository.
Diffstat (limited to 'gcc/testsuite/gfortran.dg/namelist_15.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/namelist_15.f9065
1 files changed, 65 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/namelist_15.f90 b/gcc/testsuite/gfortran.dg/namelist_15.f90
new file mode 100644
index 000000000..e900e71d1
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/namelist_15.f90
@@ -0,0 +1,65 @@
+!{ dg-do run }
+! Tests arrays of derived types containing derived type arrays whose
+! components are character arrays - exercises object name parser in
+! list_read.c. Checks that namelist output can be reread.
+! provided by Paul Thomas - pault@gcc.gnu.org
+
+module global
+ type :: mt
+ character(len=2) :: ch(2) = (/"aa","bb"/)
+ end type mt
+ type :: bt
+ integer :: i(2) = (/1,2/)
+ type(mt) :: m(2)
+ end type bt
+end module global
+
+program namelist_15
+ use global
+ type(bt) :: x(2)
+
+ namelist /mynml/ x
+
+ open (10, status = "scratch", delim='apostrophe')
+ write (10, '(A)') "&MYNML"
+ write (10, '(A)') " x = 3, 4, 'dd', 'ee', 'ff', 'gg',"
+ write (10, '(A)') " 4, 5, 'hh', 'ii', 'jj', 'kk',"
+ write (10, '(A)') " x(1)%i = , ,"
+ write (10, '(A)') " x(2)%i = -3, -4"
+ write (10, '(A)') " x(2)%m(1)%ch(2)(1:1) ='q',"
+ write (10, '(A)') " x(2)%m(2)%ch(1)(1:1) ='w',"
+ write (10, '(A)') " x(1)%m(1)%ch(1:2)(2:2) = 'z','z',"
+ write (10, '(A)') " x(2)%m(1)%ch(1:2)(2:2) = 'z','z',"
+ write (10, '(A)') " x(1)%m(2)%ch(1:2)(2:2) = 'z','z',"
+ write (10, '(A)') " x(2)%m(2)%ch(1:2)(2:2) = 'z','z',"
+ write (10, '(A)') "/"
+
+ rewind (10)
+ read (10, nml = mynml, iostat = ier)
+ if (ier .ne. 0) call abort ()
+ close (10)
+
+ open (10, status = "scratch", delim='apostrophe')
+ write (10, nml = mynml)
+ rewind (10)
+
+ read (10, nml = mynml, iostat = ier)
+ if (ier .ne. 0) call abort ()
+ close(10)
+
+ if (.not. ((x(1)%i(1) == 3) .and. &
+ (x(1)%i(2) == 4) .and. &
+ (x(1)%m(1)%ch(1) == "dz") .and. &
+ (x(1)%m(1)%ch(2) == "ez") .and. &
+ (x(1)%m(2)%ch(1) == "fz") .and. &
+ (x(1)%m(2)%ch(2) == "gz") .and. &
+ (x(2)%i(1) == -3) .and. &
+ (x(2)%i(2) == -4) .and. &
+ (x(2)%m(1)%ch(1) == "hz") .and. &
+ (x(2)%m(1)%ch(2) == "qz") .and. &
+ (x(2)%m(2)%ch(1) == "wz") .and. &
+ (x(2)%m(2)%ch(2) == "kz"))) call abort ()
+
+end program namelist_15
+
+! { dg-final { cleanup-modules "global" } }