xref: /llvm-project/flang/test/Semantics/resolve11.f90 (revision 702a86a8f1e4d96c62574fc8d7dd9ccea243517a)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2module m
3  public i
4  integer, private :: j
5  !ERROR: The accessibility of 'i' has already been specified as PUBLIC
6  private i
7  !WARNING: The accessibility of 'j' has already been specified as PRIVATE
8  private j
9end
10
11module m2
12  interface operator(.foo.)
13    module procedure ifoo
14  end interface
15  public :: operator(.foo.)
16  !ERROR: The accessibility of 'OPERATOR(.foo.)' has already been specified as PUBLIC
17  private :: operator(.foo.)
18  interface operator(+)
19    module procedure ifoo
20  end interface
21  public :: operator(+)
22  !ERROR: The accessibility of 'OPERATOR(+)' has already been specified as PUBLIC
23  private :: operator(+) , ifoo
24contains
25  integer function ifoo(x, y)
26    logical, intent(in) :: x, y
27  end
28end module
29
30module m3
31  type t
32  end type
33  private :: operator(.lt.)
34  interface operator(<)
35    logical function lt(x, y)
36      import t
37      type(t), intent(in) :: x, y
38    end function
39  end interface
40  !ERROR: The accessibility of 'OPERATOR(<)' has already been specified as PRIVATE
41  public :: operator(<)
42  interface operator(.gt.)
43    logical function gt(x, y)
44      import t
45      type(t), intent(in) :: x, y
46    end function
47  end interface
48  public :: operator(>)
49  !ERROR: The accessibility of 'OPERATOR(.GT.)' has already been specified as PUBLIC
50  private :: operator(.gt.)
51end
52
53module m4
54  private
55  type, public :: foo
56  end type
57  interface foo
58    procedure fun
59  end interface
60 contains
61  function fun
62  end
63end
64
65subroutine s4
66  !ERROR: 'fun' is PRIVATE in 'm4'
67  use m4, only: foo, fun
68  type(foo) x ! ok
69  print *, foo() ! ok
70end
71
72module m5
73  public
74  type, private :: foo
75  end type
76  interface foo
77    procedure fun
78  end interface
79 contains
80  function fun
81  end
82end
83
84subroutine s5
85  !ERROR: 'foo' is PRIVATE in 'm5'
86  use m5, only: foo, fun
87  print *, fun() ! ok
88end
89