c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / deferred_character_5.f90
blob44818849ce1a8127049eb7e483f1f7bf46d0dd77
1 ! { dg-do run }
3 ! Tests that PR63932 stays fixed.
5 ! Contributed by Valery Weber <valeryweber@hotmail.com>
7 module mod
8 type :: t
9 character(:), allocatable :: c
10 integer :: i
11 contains
12 procedure, pass :: get
13 end type t
14 type :: u
15 character(:), allocatable :: c
16 end type u
17 contains
18 subroutine get(this, a)
19 class(t), intent(in) :: this
20 character(:), allocatable, intent(out), optional :: a
21 if (present (a)) a = this%c
22 end subroutine get
23 end module mod
25 program test
26 use mod
27 type(t) :: a
28 type(u) :: b
29 a%c = 'something'
30 call a%get (a = b%c)
31 if (b%c .ne. 'something') STOP 1
32 end program test