c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / elemental_args_check_5.f90
blobd7445c08395afa1909ba90a527e3c945c76a21c2
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
5 type t
6 end type t
7 type t2
8 end type t2
9 contains
10 elemental subroutine foo0(v) ! OK
11 class(t), intent(in) :: v
12 end subroutine
14 elemental subroutine foo1(w) ! { dg-error "Argument 'w' of elemental procedure at .1. cannot have the ALLOCATABLE attribute" }
15 class(t), allocatable, intent(in) :: w
16 end subroutine
18 elemental subroutine foo2(x) ! { dg-error "Argument 'x' of elemental procedure at .1. cannot have the POINTER attribute" }
19 class(t), pointer, intent(in) :: x
20 end subroutine
22 elemental subroutine foo3(y) ! { dg-error "Coarray dummy argument 'y' at .1. to elemental procedure" }
23 class(t2), intent(in) :: y[*]
24 end subroutine
26 elemental subroutine foo4(z) ! { dg-error "Argument 'z' of elemental procedure at .1. must be scalar" }
27 class(t), intent(in) :: z(:)
28 end subroutine
30 end