nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr105456-ruf.f90
blobc176c4aa18c165ee014ea2ab03a027c928376894
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 read (unformatted)
9 module procedure read_unformatted
10 end interface read (unformatted)
11 contains
12 subroutine read_unformatted (dtv, unit, piostat, piomsg)
13 class (char), intent(inout) :: 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 read (unit,fmt='(A1)', advance="no", iostat=piostat, iomsg=piomsg) dtv%ch
20 piostat = 42
21 piomsg="The users message"
22 end subroutine read_unformatted
23 end module sk1
25 program skip1
26 use sk1
27 implicit none
28 type (char) :: x
29 x%ch = 'X'
30 open (10, form='unformatted', status='scratch')
31 write (10) 'X'
32 rewind (10)
33 read (10) x
34 end program skip1
35 ! { dg-output ".*(unit = 10, file = .*)" }
36 ! { dg-output "Fortran runtime error: The users message" }