Plugins: Add label-text.h to CPPLIB_H so it will be installed [PR115288]
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr105456-wf.f90
blobf1c5350cc00e963cf7cacf7590b6bc99f204fcdc
1 ! { dg-do run }
2 ! { dg-shouldfail "The users message" }
3 module sk1
4 implicit none
5 type char
6 character :: ch
7 end type char
8 interface write (formatted)
9 module procedure write_formatted
10 end interface write (formatted)
11 contains
12 subroutine write_formatted (dtv, unit, iotype, vlist, piostat, piomsg)
13 class (char), intent(in) :: dtv
14 integer, intent(in) :: unit
15 character (len=*), intent(in) :: iotype
16 integer, intent(in) :: vlist(:)
17 integer, intent(out) :: piostat
18 character (len=*), intent(inout) :: piomsg
19 write (unit,fmt='(A1)', advance="no", iostat=piostat, iomsg=piomsg) dtv%ch
20 piostat = 42
21 piomsg="The users message"
22 end subroutine write_formatted
23 end module sk1
25 program skip1
26 use sk1
27 implicit none
28 type (char) :: x
29 x%ch = 'X'
30 open (10, status='scratch')
31 write (10,*) x
32 end program skip1
33 ! { dg-output ".*(unit = 10, file = .*)" }
34 ! { dg-output "Fortran runtime error: The users message" }