1 |
694 |
jeremybenn |
! { dg-do run }
|
2 |
|
|
|
3 |
|
|
module nml_47
|
4 |
|
|
type :: mt
|
5 |
|
|
character(len=2) :: c012345678901234567890123456789012345678901234567890123456789h(2) = (/"aa","bb"/)
|
6 |
|
|
end type mt
|
7 |
|
|
type :: bt
|
8 |
|
|
integer :: i(2) = (/1,2/)
|
9 |
|
|
type(mt) :: m(2)
|
10 |
|
|
end type bt
|
11 |
|
|
end module nml_47
|
12 |
|
|
|
13 |
|
|
program namelist_47
|
14 |
|
|
use nml_47
|
15 |
|
|
type(bt) :: x(2)
|
16 |
|
|
character(140) :: teststring
|
17 |
|
|
namelist /mynml/ x
|
18 |
|
|
|
19 |
|
|
teststring = " x(2)%m%c012345678901234567890123456789012345678901234567890123456789h(:)(2:2) = 'z','z',"
|
20 |
|
|
call writenml (teststring)
|
21 |
|
|
teststring = " x(2)%m(2)%c012345678901234567890123456789012345678901234567890123456789h(:)(2) = 'z','z',"
|
22 |
|
|
call writenml (teststring)
|
23 |
|
|
teststring = " x(2)%m(2)%c012345678901234567890123456789012345678901234567890123456789h(:)(:3) = 'z','z',"
|
24 |
|
|
call writenml (teststring)
|
25 |
|
|
teststring = " x(2)%m(2)%c012345678901234567890123456789012345678901234567890123456789h(1:2)(k:) = 'z','z',"
|
26 |
|
|
call writenml (teststring)
|
27 |
|
|
|
28 |
|
|
contains
|
29 |
|
|
|
30 |
|
|
subroutine writenml (astring)
|
31 |
|
|
character(140), intent(in) :: astring
|
32 |
|
|
character(300) :: errmessage
|
33 |
|
|
integer :: ierror
|
34 |
|
|
|
35 |
|
|
open (10, status="scratch", delim='apostrophe')
|
36 |
|
|
write (10, '(A)') "&MYNML"
|
37 |
|
|
write (10, '(A)') astring
|
38 |
|
|
write (10, '(A)') "/"
|
39 |
|
|
rewind (10)
|
40 |
|
|
read (10, nml = mynml, iostat=ierror, iomsg=errmessage)
|
41 |
|
|
if (ierror == 0) call abort
|
42 |
|
|
print '(a)', trim(errmessage)
|
43 |
|
|
close (10)
|
44 |
|
|
|
45 |
|
|
end subroutine writenml
|
46 |
|
|
|
47 |
|
|
end program namelist_47
|
48 |
|
|
! { dg-output "Multiple sub-objects with non-zero rank in namelist object x%m%c012345678901234567890123456789012345678901234567890123456789h(\n|\r\n|\r)" }
|
49 |
|
|
! { dg-output "Missing colon in substring qualifier for namelist variable x%m%c012345678901234567890123456789012345678901234567890123456789h(\n|\r\n|\r)" }
|
50 |
|
|
! { dg-output "Substring out of range for namelist variable x%m%c012345678901234567890123456789012345678901234567890123456789h(\n|\r\n|\r)" }
|
51 |
|
|
! { dg-output "Bad character in substring qualifier for namelist variable x%m%c012345678901234567890123456789012345678901234567890123456789h(\n|\r\n|\r)" }
|
52 |
|
|
! { dg-final { cleanup-modules "nml_47" } }
|