xref: /llvm-project/flang/test/Semantics/generic01.f90 (revision b7a0482a0a72438ceab3239ee1e358f953b688c8)
1! RUN: %flang_fc1 -fdebug-unparse %s 2>&1 | FileCheck %s
2! Tests rules of 15.5.5.2 for generics and explicit intrinsics
3! competing at various scoping levels.
4module m1
5  private
6  public abs
7  interface abs
8    module procedure :: abs_int_redef, abs_noargs
9  end interface
10contains
11  integer function abs_int_redef(j)
12    integer, intent(in) :: j
13    abs_int_redef = j
14  end function
15  integer function abs_noargs()
16    abs_noargs = 0
17  end function
18end module
19
20module m2
21  private
22  public abs
23  interface abs
24    module procedure abs_real_redef
25  end interface
26contains
27  real function abs_real_redef(x)
28    real, intent(in) :: x
29    abs_real_redef = x
30  end function
31end module
32
33module m3
34  use m1, only: abs
35  implicit none
36contains
37  subroutine test1
38    use m2, only: abs
39    !CHECK: abs_int_redef(
40    print *, abs(1)
41    !CHECK: abs_real_redef(
42    print *, abs(1.)
43    !CHECK: 1.41421353816986083984375_4
44    print *, abs((1,1))
45    !CHECK: abs_noargs(
46    print *, abs()
47  end subroutine
48  subroutine test2
49    intrinsic abs ! override some of module's use of m1
50    block
51      use m2, only: abs
52      !CHECK: 1_4
53      print *, abs(1)
54      !CHECK: abs_real_redef(
55      print *, abs(1.)
56      !CHECK: 1.41421353816986083984375_4
57      print *, abs((1,1))
58      !CHECK: abs_noargs(
59      print *, abs()
60    end block
61  end subroutine
62  subroutine test3
63    interface abs
64      module procedure abs_complex_redef ! extend module's use of m1
65    end interface
66    !CHECK: abs_int_redef(
67    print *, abs(1)
68    !CHECK: 1._4
69    print *, abs(1.)
70    !CHECK: abs_complex_redef(
71    print *, abs((1,1))
72    !CHECK: abs_noargs(
73    print *, abs()
74    block
75      intrinsic abs ! override the extension
76      !CHECK: 1.41421353816986083984375_4
77      print *, abs((1,1))
78    end block
79  end subroutine
80  real function abs_complex_redef(z)
81    complex, intent(in) :: z
82    abs_complex_redef = z
83  end function
84  subroutine test4
85    !CHECK: abs(
86    print *, abs(1)
87   contains
88    integer function abs(n) ! override module's use of m1
89      integer, intent(in) :: n
90      abs = n
91    end function
92  end subroutine
93end module
94
95module m4
96 contains
97  integer function abs(n)
98    integer, intent(in) :: n
99    abs = n
100  end function
101  subroutine test5
102    interface abs
103      module procedure abs ! same name, host-associated
104    end interface
105    !CHECK: abs(
106    print *, abs(1)
107  end subroutine
108end module
109