c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / dtio_21.f90
blobe8d433c58b2f51a935c8f31e989a43ce8cc5e834
1 ! { dg-do compile }
3 ! PR 78592: [7 Regression] ICE in gfc_find_specific_dtio_proc, at fortran/interface.c:4939
5 ! Contributed by Mikael Morin <morin-mikael@orange.fr>
7 program p
8 type t
9 end type
10 type(t) :: z
11 type, extends(t) :: t2
12 end type
13 class(t2), allocatable :: z2
14 interface write(formatted)
15 procedure wf2
16 module procedure wf ! { dg-error "is neither function nor subroutine" }
17 end interface
18 print *, z
19 allocate(z2)
20 print *, z2
21 contains
22 subroutine wf2(this, a, b, c, d, e) ! { dg-error "must have assumed length" }
23 class(t2), intent(in) :: this
24 integer, intent(in) :: a
25 character(*), intent(in) :: b
26 integer, intent(in) :: c(:)
27 integer, intent(out) :: d
28 character, intent(inout) :: e
29 end subroutine wf2
30 end