Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / modfile34.f90
blob2d6adcb89c9b69c7456c1a53a4e0f7f0a28ce3d1
1 ! RUN: %python %S/test_modfile.py %s %flang_fc1
2 ! Test resolution of type-bound generics.
4 module m1
5 type :: t
6 contains
7 procedure, pass(x) :: add1 => add
8 procedure, nopass :: add2 => add
9 procedure :: add_real
10 generic :: g => add1, add2, add_real
11 end type
12 contains
13 integer(8) pure function add(x, y)
14 class(t), intent(in) :: x, y
15 end
16 integer(8) pure function add_real(x, y)
17 class(t), intent(in) :: x
18 real, intent(in) :: y
19 end
20 subroutine test1(x, y, z)
21 type(t) :: x, y
22 real :: z(x%add1(y))
23 end
24 subroutine test1p(x, y, z)
25 class(t) :: x, y
26 real :: z(x%add1(y))
27 end
28 subroutine test2(x, y, z)
29 type(t) :: x, y
30 real :: z(x%g(y))
31 end
32 subroutine test2p(x, y, z)
33 class(t) :: x, y
34 real :: z(x%g(y))
35 end
36 subroutine test3(x, y, z)
37 type(t) :: x, y
38 real :: z(x%g(y, x))
39 end
40 subroutine test3p(x, y, z)
41 class(t) :: x, y
42 real :: z(x%g(y, x))
43 end
44 subroutine test4(x, y, z)
45 type(t) :: x
46 real :: y
47 real :: z(x%g(y))
48 end
49 subroutine test4p(x, y, z)
50 class(t) :: x
51 real :: y
52 real :: z(x%g(y))
53 end
54 end
56 !Expect: m1.mod
57 !module m1
58 ! type :: t
59 ! contains
60 ! procedure, pass(x) :: add1 => add
61 ! procedure, nopass :: add2 => add
62 ! procedure :: add_real
63 ! generic :: g => add1
64 ! generic :: g => add2
65 ! generic :: g => add_real
66 ! end type
67 !contains
68 ! pure function add(x, y)
69 ! class(t), intent(in) :: x
70 ! class(t), intent(in) :: y
71 ! integer(8) :: add
72 ! end
73 ! pure function add_real(x, y)
74 ! class(t), intent(in) :: x
75 ! real(4), intent(in) :: y
76 ! integer(8) :: add_real
77 ! end
78 ! subroutine test1(x, y, z)
79 ! type(t) :: x
80 ! type(t) :: y
81 ! real(4) :: z(1_8:add(x, y))
82 ! end
83 ! subroutine test1p(x,y,z)
84 ! class(t)::x
85 ! class(t)::y
86 ! real(4)::z(1_8:x%add1(y))
87 ! end
88 ! subroutine test2(x, y, z)
89 ! type(t) :: x
90 ! type(t) :: y
91 ! real(4)::z(1_8:add(x,y))
92 ! end
93 ! subroutine test2p(x,y,z)
94 ! class(t)::x
95 ! class(t)::y
96 ! real(4) :: z(1_8:x%add1(y))
97 ! end
98 ! subroutine test3(x, y, z)
99 ! type(t) :: x
100 ! type(t) :: y
101 ! real(4)::z(1_8:add(y,x))
102 ! end
103 ! subroutine test3p(x,y,z)
104 ! class(t)::x
105 ! class(t)::y
106 ! real(4) :: z(1_8:x%add2(y, x))
107 ! end
108 ! subroutine test4(x, y, z)
109 ! type(t) :: x
110 ! real(4) :: y
111 ! real(4)::z(1_8:add_real(x,y))
112 ! end
113 ! subroutine test4p(x,y,z)
114 ! class(t)::x
115 ! real(4)::y
116 ! real(4) :: z(1_8:x%add_real(y))
117 ! end
118 !end