* tree-loop-distribution.c (struct partition): New field recording
[official-gcc.git] / gcc / testsuite / gfortran.dg / dtio_29.f03
blob46961e4ccc4969eb30edd7c50617d906d1c0fa4c
1 ! { dg-do compile }
2 ! PR80484 Three syntax errors involving derived-type I/O
3 module dt_write_mod
4    type, public :: B_type
5       real :: amount
6    end type B_type
7    interface write (formatted)
8       procedure :: Write_b
9    end interface
10 contains
12 subroutine Write_b &
13    (amount, unit, b_edit_descriptor, v_list, iostat, iomsg)
15    class (B_type), intent(in) :: amount
16    integer, intent(in) :: unit
17    character (len=*), intent(in) :: b_edit_descriptor
18    integer, dimension(:), intent(in) :: v_list
19    integer, intent(out) :: iostat
20    character (len=*), intent(inout) :: iomsg
21    write (unit=unit, fmt="(f9.3)", iostat=iostat) amount%amount
23 end subroutine Write_b
25 end module dt_write_mod
27 program test
28    use dt_write_mod, only: B_type  , write(formatted)
29    implicit none
31    real :: wage = 15.10
32    integer :: ios
33    character(len=99) :: iom = "OK"
35    write (unit=*, fmt="(DT'$$$Z.##')", iostat=ios, iomsg=iom) &
36      B_type(wage), B_type(wage)
37    print *, trim(iom)
38    write (unit=*, fmt="(2DT'$$$Z.##')", iostat=ios, iomsg=iom) &
39      B_type(wage), B_type(wage)
40    print *, trim(iom)
41    write (unit=*, fmt="(3DT'$$$Z.##')", iostat=ios, iomsg=iom) &
42      B_type(wage), B_type(wage)
43    print *, trim(iom)
44    write (unit=*, fmt="(DT'$$$Z.##'/)", iostat=ios, iomsg=iom) &
45      B_type(wage), B_type(wage)
46    print *, trim(iom)
47 end program test