view gcc/testsuite/gfortran.dg/dtio_33.f90 @ 144:8f4e72ab4e11

fix segmentation fault caused by nothing next cur_op to end
author Takahiro SHIMIZU <anatofuz@cr.ie.u-ryukyu.ac.jp>
date Sun, 23 Dec 2018 21:23:56 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do run }
! PR84389 rejected valid use of ':' in format
module m
   type :: t
   integer :: i
   contains
      procedure, pass(this) :: write_t
      generic, public :: write(formatted) => write_t
   end type
contains
   subroutine write_t(this, lun, iotype, vlist, istat, imsg)
      ! argument definitions
      class(t), intent(in)            :: this
      integer, intent(in)             :: lun
      character(len=*), intent(in)    :: iotype
      integer, intent(in)             :: vlist(:)
      integer, intent(out)            :: istat
      character(len=*), intent(inout) :: imsg
      write(lun, fmt=*, iostat=istat, iomsg=imsg) "Hello World!"
   end subroutine write_t
end module
program p
   use m, only : t
   character(50) :: str
   type(t) :: foo(2)
   write(str, "(*(dt:,','))") foo
   if (str.ne." Hello World!, Hello World!") stop 1
end program