xref: /llvm-project/flang/test/Semantics/resolve102.f90 (revision 7605ad8a2f95e3b37de83e7fb3d320efc74e0ccc)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2
3! Tests for circularly defined procedures
4!ERROR: Procedure 'sub' is recursively defined.  Procedures in the cycle: 'sub', 'p2'
5subroutine sub(p2)
6  PROCEDURE(sub) :: p2
7end subroutine
8
9subroutine circular
10  procedure(sub) :: p
11  contains
12    !ERROR: Procedure 'sub' is recursively defined.  Procedures in the cycle: 'p', 'sub', 'p2'
13    subroutine sub(p2)
14      procedure(p) :: p2
15    end subroutine
16end subroutine circular
17
18!ERROR: Procedure 'foo' is recursively defined.  Procedures in the cycle: 'foo', 'r'
19function foo() result(r)
20  !ERROR: Procedure 'r' is recursively defined.  Procedures in the cycle: 'foo', 'r'
21  procedure(foo), pointer :: r
22end function foo
23
24subroutine iface
25  !ERROR: Procedure 'p' is recursively defined.  Procedures in the cycle: 'p', 'sub', 'p2'
26  procedure(sub) :: p
27  interface
28    !ERROR: Procedure 'sub' is recursively defined.  Procedures in the cycle: 'p', 'sub', 'p2'
29    subroutine sub(p2)
30      import p
31      procedure(p) :: p2
32    end subroutine
33  end interface
34  call p(sub)
35end subroutine
36
37subroutine mutual
38  Procedure(sub1) :: p
39  contains
40    !ERROR: Procedure 'sub1' is recursively defined.  Procedures in the cycle: 'p', 'sub1', 'arg'
41    !ERROR: Procedure 'sub1' is recursively defined.  Procedures in the cycle: 'sub1', 'arg', 'sub', 'p2'
42    !ERROR: Procedure 'sub1' is recursively defined.  Procedures in the cycle: 'sub1', 'arg'
43    Subroutine sub1(arg)
44      procedure(sub1) :: arg
45    End Subroutine
46
47    Subroutine sub(p2)
48      Procedure(sub1) :: p2
49    End Subroutine
50End subroutine
51
52subroutine mutual1
53  Procedure(sub1) :: p
54  contains
55    !ERROR: Procedure 'sub1' is recursively defined.  Procedures in the cycle: 'p', 'sub1', 'arg', 'sub', 'p2'
56    !ERROR: Procedure 'sub1' is recursively defined.  Procedures in the cycle: 'sub1', 'arg', 'sub', 'p2'
57    Subroutine sub1(arg)
58      procedure(sub) :: arg
59    End Subroutine
60
61    !ERROR: Procedure 'sub' is recursively defined.  Procedures in the cycle: 'sub1', 'arg', 'sub', 'p2'
62    Subroutine sub(p2)
63      Procedure(sub1) :: p2
64    End Subroutine
65End subroutine
66
67subroutine twoCycle
68  !ERROR: The interface for procedure 'p1' is recursively defined
69  !ERROR: The interface for procedure 'p2' is recursively defined
70  procedure(p1) p2
71  procedure(p2) p1
72end subroutine
73
74subroutine threeCycle
75  !ERROR: The interface for procedure 'p1' is recursively defined
76  !ERROR: The interface for procedure 'p2' is recursively defined
77  procedure(p1) p2
78  !ERROR: The interface for procedure 'p3' is recursively defined
79  procedure(p2) p3
80  procedure(p3) p1
81end subroutine
82
83module mutualSpecExprs
84contains
85  pure integer function f(n)
86    integer, intent(in) :: n
87    real arr(g(n))
88    f = size(arr)
89  end function
90  pure integer function g(n)
91    integer, intent(in) :: n
92    !ERROR: Procedure 'f' is referenced before being sufficiently defined in a context where it must be so
93    real arr(f(n))
94    g = size(arr)
95  end function
96end
97
98module genericInSpec
99  interface int
100    procedure ifunc
101  end interface
102 contains
103  function ifunc(x)
104    integer a(int(kind(1))) ! generic is ok with most compilers
105    integer(size(a)), intent(in) :: x
106    ifunc = x
107  end
108end
109