xref: /llvm-project/flang/test/Semantics/resolve108.f90 (revision 502e7690c3c9698a6982a490f6bf92b0fd24d10f)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2! Tests attempts at forward references to local names in a FUNCTION prefix
3
4! This case is not an error, but will elicit bogus errors if the
5! result type of the function is badly resolved.
6module m1
7  type t1
8    sequence
9    integer not_m
10  end type
11 contains
12  type(t1) function foo(n)
13    integer, intent(in) :: n
14    type t1
15      sequence
16      integer m
17    end type
18    foo%m = n
19  end function
20end module
21
22subroutine s1
23  use :: m1, only: foo
24  type t1
25    sequence
26    integer m
27  end type
28  type(t1) x
29  x = foo(234)
30  print *, x
31end subroutine
32
33module m2
34  integer, parameter :: k = kind(1.e0)
35 contains
36  real(kind=k) function foo(n)
37    integer, parameter :: k = kind(1.d0)
38    integer, intent(in) :: n
39    foo = n
40  end function
41end module
42
43subroutine s2
44  use :: m2, only: foo
45  !If we got the type of foo right, this declaration will fail
46  !due to an attempted division by zero.
47  !WARNING: INTEGER(4) division by zero
48  !ERROR: Must be a constant value
49  integer, parameter :: test = 1 / (kind(foo(1)) - kind(1.d0))
50end subroutine
51
52module m3
53  real(kind=kind(1.0e0)) :: x
54 contains
55  real(kind=kind(x)) function foo(x)
56    real(kind=kind(1.0d0)) x
57    !WARNING: INTEGER(4) division by zero
58    !ERROR: Must be a constant value
59    integer, parameter :: test = 1 / (kind(foo) - kind(1.d0))
60    foo = n
61  end function
62end module
63
64module m4
65 contains
66  real(n) function foo(x)
67    !ERROR: 'foo' is not an object that can appear in an expression
68    integer, parameter :: n = kind(foo)
69    real(n), intent(in) :: x
70    !ERROR: 'x' is not an object that can appear in an expression
71    foo = x
72  end function
73end module
74