Fix compilation failure with C++98 compilers
[official-gcc.git] / gcc / testsuite / gfortran.dg / dtio_31.f03
blob9d622a21b5aa817d96fb100dd92e05cab2aba923
1 ! { dg-do run }
2 ! { dg-options="-w" }
3 ! PR fortran/79383
4 ! Contributed by Walt Brainerd <walt.brainerd at gmail dot com>
5 module dollar_mod
7    implicit none
9    private
11    type, public :: dollar_type
12       real :: amount
13    end type dollar_type
15    interface write(formatted)
16       procedure :: Write_dollar
17    end interface
19    public :: write(formatted)
21    contains
23       subroutine Write_dollar(dollar_value, unit, b_edit_descriptor, &
24       &  v_list, iostat, iomsg)
26          class(dollar_type), intent(in) :: dollar_value
27          integer, intent(in) :: unit
28          character(len=*), intent(in) :: b_edit_descriptor
29          integer, dimension(:), intent(in) :: v_list
30          integer, intent(out) :: iostat
31          character(len=*), intent(inout) :: iomsg
32          write(unit=unit, fmt="(f9.2)", iostat=iostat) dollar_value%amount
33       end subroutine Write_dollar
35 end module dollar_mod
37 program test_dollar
39    use, non_intrinsic :: dollar_mod, only: dollar_type, write (formatted)
40    implicit none
42    type(dollar_type), parameter :: wage = dollar_type(15.10)
43    character(len=10) str
44    write (str, fmt="(DT)") wage
45    if(trim(adjustl(str)) /= '15.10') STOP 1
47 end program test_dollar