xref: /llvm-project/flang/test/Semantics/elemental01.f90 (revision 67081badfc65b8b60622314dd698834ffcfdbfa9)
1! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
2! Tests ELEMENTAL subprogram constraints C15100-15102
3
4!ERROR: An ELEMENTAL subroutine may not have an alternate return dummy argument
5elemental subroutine altret(*)
6end subroutine
7
8elemental subroutine arrarg(a)
9  !ERROR: A dummy argument of an ELEMENTAL procedure must be scalar
10  real, intent(in) :: a(1)
11end subroutine
12
13elemental subroutine alloarg(a)
14  !ERROR: A dummy argument of an ELEMENTAL procedure may not be ALLOCATABLE
15  real, intent(in), allocatable :: a
16end subroutine
17
18elemental subroutine coarg(a)
19  !ERROR: A dummy argument of an ELEMENTAL procedure may not be a coarray
20  real, intent(in) :: a[*]
21end subroutine
22
23elemental subroutine ptrarg(a)
24  !ERROR: A dummy argument of an ELEMENTAL procedure may not be a POINTER
25  real, intent(in), pointer :: a
26end subroutine
27
28impure elemental subroutine barearg(a)
29  !ERROR: A dummy argument of an ELEMENTAL procedure must have an INTENT() or VALUE attribute
30  real :: a
31end subroutine
32
33elemental function arrf(n)
34  integer, value :: n
35  !ERROR: The result of an ELEMENTAL function must be scalar
36  real :: arrf(n)
37end function
38
39elemental function allof(n)
40  integer, value :: n
41  !ERROR: The result of an ELEMENTAL function may not be ALLOCATABLE
42  real, allocatable :: allof
43end function
44
45elemental function ptrf(n)
46  integer, value :: n
47  !ERROR: The result of an ELEMENTAL function may not be a POINTER
48  real, pointer :: ptrf
49end function
50
51module m
52  integer modvar
53  type t
54    character(:), allocatable :: c
55  end type
56  type pdt(L)
57    integer, len :: L
58  end type
59  type container
60    class(pdt(:)), allocatable :: c
61  end type
62 contains
63  !ERROR: Invalid specification expression for elemental function result: dependence on value of dummy argument 'n'
64  elemental character(n) function bad1(n)
65    integer, intent(in) :: n
66  end
67  !ERROR: Invalid specification expression for elemental function result: non-constant inquiry function 'len' not allowed for local object
68  elemental character(x%c%len) function bad2(x)
69    type(t), intent(in) :: x
70  end
71  !ERROR: Invalid specification expression for elemental function result: non-constant type parameter inquiry not allowed for local object
72  elemental character(x%c%L) function bad3(x)
73    class(container), intent(in) :: x
74  end
75  elemental character(len(x)) function ok1(x) ! ok
76    character(*), intent(in) :: x
77  end
78  elemental character(modvar) function ok2(x) ! ok
79    character(*), intent(in) :: x
80  end
81  elemental character(len(x)) function ok3(x) ! ok
82    character(modvar), intent(in) :: x
83  end
84  elemental character(storage_size(x)) function ok4(x) ! ok
85    class(*), intent(in) :: x
86  end
87end
88