AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / pointer_intent_9.f90
blob30ddd0283597f4ca0dbf3ce087e08f81557e1d1e
1 ! { dg-do compile }
2 ! PR fortran/103418
3 ! Validate checks for dummy arguments with INTENT(IN), pointer attribute
5 module m
6 type t
7 real, pointer :: a, b(:)
8 end type t
9 contains
10 subroutine s1 (a, b, c, d, e)
11 real, pointer, intent(in) :: a, b(:)
12 type(t), intent(in) :: c
13 class(t), intent(in) :: d
14 type(t), pointer, intent(in) :: e
15 real, pointer :: pa, pb(:)
16 call random_number (a) ! legal
17 call random_number (b)
18 call cpu_time (a)
19 call system_clock (count_rate=a)
20 call random_number (c% a)
21 call random_number (c% b)
22 call random_number (d% a)
23 call random_number (d% b)
24 call random_number (e% a)
25 call random_number (e% b)
26 call move_alloc (a, pa) ! { dg-error "must be ALLOCATABLE" }
27 call move_alloc (b, pb) ! { dg-error "must be ALLOCATABLE" }
28 allocate (a) ! { dg-error "pointer association context" }
29 allocate (b(10)) ! { dg-error "pointer association context" }
30 allocate (c% a) ! { dg-error "pointer association context" }
31 allocate (c% b(10)) ! { dg-error "pointer association context" }
32 end subroutine s1
33 end module