[ORC] Merge ostream operators for SymbolStringPtrs into SymbolStringPool.h. NFC.
[llvm-project.git] / flang / test / Semantics / resolve32.f90
blob948493b1615e61bf8c47ba28e40abeb992fd0aa2
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 module m2
3 public s2, s4
4 private s3
5 contains
6 subroutine s2
7 end
8 subroutine s3
9 end
10 subroutine s4
11 end
12 end module
14 module m
15 use m2
16 external bar
17 interface
18 subroutine foo
19 end subroutine
20 end interface
21 abstract interface
22 subroutine absfoo
23 end subroutine
24 end interface
25 integer :: i
26 type t1
27 integer :: c
28 contains
29 !ERROR: The binding of 'a' ('missing') must be either an accessible module procedure or an external procedure with an explicit interface
30 procedure, nopass :: a => missing
31 procedure, nopass :: b => s, s2
32 !ERROR: Type parameter, component, or procedure binding 'c' already defined in this type
33 procedure, nopass :: c
34 !ERROR: DEFERRED is only allowed when an interface-name is provided
35 procedure, nopass, deferred :: d => s
36 !Note: s3 not found because it's not accessible -- should we issue a message
37 !to that effect?
38 !ERROR: 's3' must be either an accessible module procedure or an external procedure with an explicit interface
39 procedure, nopass :: s3
40 procedure, nopass :: foo
41 !ERROR: 'absfoo' must be either an accessible module procedure or an external procedure with an explicit interface
42 procedure, nopass :: absfoo
43 !ERROR: 'bar' must be either an accessible module procedure or an external procedure with an explicit interface
44 procedure, nopass :: bar
45 !ERROR: 'i' must be either an accessible module procedure or an external procedure with an explicit interface
46 procedure, nopass :: i
47 !ERROR: Type parameter, component, or procedure binding 'b' already defined in this type
48 procedure, nopass :: b => s4
49 !ERROR: DEFERRED is required when an interface-name is provided
50 procedure(foo), nopass :: g
51 end type
52 type, abstract :: t1a ! DEFERRED valid only in ABSTRACT derived type
53 contains
54 procedure(foo), nopass, deferred :: e
55 procedure(s), nopass, deferred :: f
56 !ERROR: Type parameter, component, or procedure binding 'f' already defined in this type
57 procedure(foo), nopass, deferred :: f
58 !ERROR: 'bar' must be an abstract interface or a procedure with an explicit interface
59 procedure(bar), nopass, deferred :: h
60 end type
61 type t2
62 integer :: i
63 contains
64 procedure, nopass :: b => s
65 final :: f
66 !ERROR: FINAL subroutine 'i' of derived type 't2' must be a module procedure
67 final :: i
68 end type
69 type t3
70 contains
71 private
72 procedure, nopass :: b => s
73 procedure, nopass, public :: f
74 end type
75 contains
76 subroutine s
77 end
78 subroutine f(x)
79 type(t2) :: x
80 end
81 end module