nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr93678.f90
blob403bedd0c4fdd911cd9bd1d9a041b9dfdfb319bb
1 ! { dg-do compile }
2 ! Test the fix for PR93678 in which the charlen for the 'unpackbytes'
3 ! vtable field was incomplete and caused the ICE as indicated.
4 ! Contributed by Luis Kornblueh <mail.luis@web.de>
6 ! The testcase was reduced by various gfortran regulars.
7 module mo_a
8 implicit none
9 type t_b
10 integer :: i
11 contains
12 procedure :: unpackbytes => b_unpackbytes
13 end type t_b
14 contains
15 function b_unpackbytes (me) result (res)
16 class(t_b), intent(inout) :: me
17 character :: res(1)
18 res = char (me%i)
19 end function b_unpackbytes
20 subroutine b_unpackint (me, c)
21 class(t_b), intent(inout) :: me
22 character, intent(in) :: c
23 ! print *, b_unpackbytes (me) ! ok
24 if (any (me% unpackbytes () .ne. c)) stop 1 ! ICEd here
25 end subroutine b_unpackint
26 end module mo_a
28 use mo_a
29 class(t_b), allocatable :: z
30 allocate (z, source = t_b(97))
31 call b_unpackint (z, "a")
32 end