aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/dtio_31.f03
blob: 2a8fa1ead77316bc5d27fd5fa105b61bc0c9f61e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
! { dg-do run }
! { dg-options "-w" }
! PR fortran/79383
! Contributed by Walt Brainerd <walt.brainerd at gmail dot com>
module dollar_mod

   implicit none

   private

   type, public :: dollar_type
      real :: amount
   end type dollar_type

   interface write(formatted)
      procedure :: Write_dollar
   end interface

   public :: write(formatted)

   contains

      subroutine Write_dollar(dollar_value, unit, b_edit_descriptor, &
      &  v_list, iostat, iomsg)

         class(dollar_type), intent(in) :: dollar_value
         integer, intent(in) :: unit
         character(len=*), intent(in) :: b_edit_descriptor
         integer, dimension(:), intent(in) :: v_list
         integer, intent(out) :: iostat
         character(len=*), intent(inout) :: iomsg
         write(unit=unit, fmt="(f9.2)", iostat=iostat) dollar_value%amount
      end subroutine Write_dollar

end module dollar_mod

program test_dollar

   use, non_intrinsic :: dollar_mod, only: dollar_type, write (formatted)
   implicit none

   type(dollar_type), parameter :: wage = dollar_type(15.10)
   character(len=10) str
   write (str, fmt="(DT)") wage
   if(trim(adjustl(str)) /= '15.10') STOP 1

end program test_dollar