c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / move_alloc_9.f90
blob4c5144c9e461cb51a662c80e59a85d3bc95f9868
1 ! { dg-do compile }
3 ! Test diagnostic for MOVE_ALLOC:
4 ! FROM=type, TO=class is OK
5 ! FROM=class, TO=type is INVALID
7 module m2
8 type, abstract :: t2
9 contains
10 procedure(intf), deferred, nopass :: f
11 end type t2
13 interface
14 function intf()
15 import
16 class(t2), allocatable :: intf
17 end function intf
18 end interface
19 end module m2
21 module m3
22 use m2
23 type, extends(t2) :: t3
24 contains
25 procedure,nopass :: f => my_f
26 end type t3
27 contains
28 function my_f()
29 class(t2), allocatable :: my_f
30 end function my_f
31 end module m3
33 subroutine my_test
34 use m3
35 type(t3), allocatable :: x
36 class(t2), allocatable :: y
37 call move_alloc (x, y)
38 end subroutine my_test
40 program testmv1
41 type bar
42 end type
44 type, extends(bar) :: bar2
45 end type
47 class(bar), allocatable :: sm
48 type(bar2), allocatable :: sm2
50 allocate (sm2)
51 call move_alloc (sm,sm2) ! { dg-error "must be polymorphic if FROM is polymorphic" }
53 if (allocated(sm2)) STOP 1
54 if (.not. allocated(sm)) STOP 2
55 end program