PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / dtio_33.f90
blob2deca43db90c033bb0b470fac7994eb436c8df24
1 ! { dg-do run }
2 ! PR84389 rejected valid use of ':' in format
3 module m
4 type :: t
5 integer :: i
6 contains
7 procedure, pass(this) :: write_t
8 generic, public :: write(formatted) => write_t
9 end type
10 contains
11 subroutine write_t(this, lun, iotype, vlist, istat, imsg)
12 ! argument definitions
13 class(t), intent(in) :: this
14 integer, intent(in) :: lun
15 character(len=*), intent(in) :: iotype
16 integer, intent(in) :: vlist(:)
17 integer, intent(out) :: istat
18 character(len=*), intent(inout) :: imsg
19 write(lun, fmt=*, iostat=istat, iomsg=imsg) "Hello World!"
20 end subroutine write_t
21 end module
22 program p
23 use m, only : t
24 character(50) :: str
25 type(t) :: foo(2)
26 write(str, "(*(dt:,','))") foo
27 if (str.ne." Hello World!, Hello World!") stop 1
28 end program