OSDN Git Service

2007-12-08 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / namelist_40.f90
1 ! { dg-do run }
2 ! PR33672 Additional runtime checks needed for namelist reads
3 ! Submitted by Jerry DeLisle  <jvdelisle@gcc.gnu.org>
4
5 module global
6   type             ::  mt
7     character(len=2) ::  ch(2) = (/"aa","bb"/)
8   end type mt
9   type             ::  bt
10     integer        ::  i(2) = (/1,2/)
11     type(mt)       ::  m(2)
12   end type bt
13 end module global
14
15 program namelist_40
16   use global
17   type(bt)         ::  x(2)
18   character(40)    ::  teststring 
19   namelist /mynml/ x
20
21   teststring = " x(2)%m%ch(:)(2:2) = 'z','z',"
22   call writenml (teststring)
23   teststring = " x(2)%m(2)%ch(:)(2) = 'z','z',"
24   call writenml (teststring)
25   teststring = " x(2)%m(2)%ch(:)(:3) = 'z','z',"
26   call writenml (teststring)
27   teststring = " x(2)%m(2)%ch(1:2)(k:) = 'z','z',"
28   call writenml (teststring)
29   
30 contains
31
32 subroutine writenml (astring)
33   character(40), intent(in)  :: astring
34   character(300)   :: errmessage
35   integer          :: ierror
36
37   open (10, status="scratch", delim='apostrophe')
38   write (10, '(A)') "&MYNML"
39   write (10, '(A)') astring
40   write (10, '(A)') "/"
41   rewind (10)
42   read (10, nml = mynml, iostat=ierror, iomsg=errmessage)
43   if (ierror == 0) call abort
44   print '(a)', trim(errmessage)
45   close (10)
46
47 end subroutine writenml
48
49 end program namelist_40
50 ! { dg-output "Multiple sub-objects with non-zero rank in namelist object x(\n|\r\n|\r)" }
51 ! { dg-output "Missing colon in substring qualifier for namelist variable x%m%ch(\n|\r\n|\r)" }
52 ! { dg-output "Substring out of range for namelist variable x%m%ch(\n|\r\n|\r)" }
53 ! { dg-output "Bad character in substring qualifier for namelist variable x%m%ch(\n|\r\n|\r)" }
54 ! { dg-final { cleanup-modules "global" } }