aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / pure_formal_3.f90
blob6e3b8585058fa20962b733aef3bcc082f48ca278
1 ! { dg-do compile }
3 ! Clean up, made when working on PR fortran/52864
5 ! Test some PURE and intent checks - related to pointers.
6 module m
7 type t
8 end type t
9 integer, pointer :: x
10 class(t), pointer :: y
11 end module m
13 pure subroutine foo()
14 use m
15 call bar(x) ! { dg-error "cannot appear in a variable definition context" }
16 call bar2(x) ! { dg-error "is local to a PURE procedure and has the POINTER attribute" }
17 call bb(y) ! { dg-error "is local to a PURE procedure and has the POINTER attribute" }
18 contains
19 pure subroutine bar(x)
20 integer, pointer, intent(inout) :: x
21 end subroutine
22 pure subroutine bar2(x)
23 integer, pointer :: x
24 end subroutine
25 pure subroutine bb(x)
26 class(t), pointer, intent(in) :: x
27 end subroutine
28 end subroutine