PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / select_type_25.f90
blob45fe9af7fce5763f89cfcb1f2181f444801526f9
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
4 ! PR fortran/51605
7 subroutine one()
8 type t
9 end type t
10 ! (a) Invalid (was ICEing before)
11 class(t), target :: p1 ! { dg-error "must be dummy, allocatable or pointer" }
12 class(t), pointer :: p2
14 select type(p1)
15 type is(t)
16 p2 => p1
17 class is(t)
18 p2 => p1
19 end select
20 end subroutine one
22 subroutine two()
23 type t
24 end type t
25 class(t), allocatable, target :: p1 ! (b) Valid
26 class(t), pointer :: p2
28 select type(p1)
29 type is(t)
30 p2 => p1
31 class is(t)
32 p2 => p1
33 end select
34 end subroutine two
36 subroutine three()
37 type t
38 end type t
39 class(t), allocatable :: p1 ! (c) Invalid as not TARGET
40 class(t), pointer :: p2
42 select type(p1)
43 type is(t)
44 p2 => p1 ! { dg-error "Pointer assignment target is neither TARGET nor POINTER" }
45 class is(t)
46 p2 => p1 ! { dg-error "Pointer assignment target is neither TARGET nor POINTER" }
47 end select
48 end subroutine three
50 subroutine four()
51 type t
52 end type t
53 class(t), pointer :: p1 ! (d) Valid
54 class(t), pointer :: p2
56 select type(p1)
57 type is(t)
58 p2 => p1
59 class is(t)
60 p2 => p1
61 end select
62 end subroutine four
64 subroutine caf(x)
65 type t
66 end type t
67 class(t) :: x[*]
68 select type(x)
69 type is(t)
70 end select
71 end subroutine caf