[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / test / Semantics / resolve114.f90
blobd7022e697e1109e95c0d13fd6ebb7fbe780f6853
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Allow the same external or intrinsic procedure to be use-associated
3 ! by multiple paths when they are unambiguous.
4 module m1
5 intrinsic :: sin
6 intrinsic :: iabs
7 interface
8 subroutine ext1(a, b)
9 integer, intent(in) :: a(:)
10 real, intent(in) :: b(:)
11 end subroutine
12 subroutine ext2(a, b)
13 real, intent(in) :: a(:)
14 integer, intent(in) :: b(:)
15 end subroutine
16 end interface
17 end module m1
19 module m2
20 intrinsic :: sin, tan
21 intrinsic :: iabs, idim
22 interface
23 subroutine ext1(a, b)
24 integer, intent(in) :: a(:)
25 real, intent(in) :: b(:)
26 end subroutine
27 subroutine ext2(a, b)
28 real, intent(in) :: a(:)
29 integer, intent(in) :: b(:)
30 end subroutine
31 end interface
32 end module m2
34 subroutine s2a
35 use m1
36 use m2
37 procedure(sin), pointer :: p1 => sin
38 procedure(iabs), pointer :: p2 => iabs
39 procedure(ext1), pointer :: p3 => ext1
40 procedure(ext2), pointer :: p4 => ext2
41 end subroutine
43 subroutine s2b
44 use m1, only: x1 => sin, x2 => iabs, x3 => ext1, x4 => ext2
45 use m2, only: x1 => sin, x2 => iabs, x3 => ext1, x4 => ext2
46 use m1, only: iface1 => sin, iface2 => iabs, iface3 => ext1, iface4 => ext2
47 procedure(iface1), pointer :: p1 => x1
48 procedure(iface2), pointer :: p2 => x2
49 procedure(iface3), pointer :: p3 => x3
50 procedure(iface4), pointer :: p4 => x4
51 end subroutine
53 module m3
54 use m1
55 use m2
56 end module
57 subroutine s3
58 use m3
59 procedure(sin), pointer :: p1 => sin
60 procedure(iabs), pointer :: p2 => iabs
61 procedure(ext1), pointer :: p3 => ext1
62 procedure(ext2), pointer :: p4 => ext2
63 end subroutine
65 module m4
66 use m1, only: x1 => sin, x2 => iabs, x3 => ext1, x4 => ext2
67 use m2, only: x1 => sin, x2 => iabs, x3 => ext1, x4 => ext2
68 end module
69 subroutine s4
70 use m4
71 use m1, only: iface1 => sin, iface2 => iabs, iface3 => ext1, iface4 => ext2
72 procedure(iface1), pointer :: p1 => x1
73 procedure(iface2), pointer :: p2 => x2
74 procedure(iface3), pointer :: p3 => x3
75 procedure(iface4), pointer :: p4 => x4
76 end subroutine
78 subroutine s5
79 use m1, only: x1 => sin, x2 => iabs, x3 => ext1, x4 => ext2
80 use m2, only: x1 => tan, x2 => idim, x3 => ext2, x4 => ext1
81 use m1, only: iface1 => sin, iface2 => iabs, iface3 => ext1, iface4 => ext2
82 !ERROR: Reference to 'x1' is ambiguous
83 procedure(iface1), pointer :: p1 => x1
84 !ERROR: Reference to 'x2' is ambiguous
85 procedure(iface2), pointer :: p2 => x2
86 !ERROR: Reference to 'x3' is ambiguous
87 procedure(iface3), pointer :: p3 => x3
88 !ERROR: Reference to 'x4' is ambiguous
89 procedure(iface4), pointer :: p4 => x4
90 end subroutine