[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / modfile10.f90
blob857b9c96d885748de6212052edb88534b6e94f01
1 ! RUN: %S/test_modfile.sh %s %t %flang_fc1
2 ! REQUIRES: shell
3 ! Test writing procedure bindings in a derived type.
5 module m
6 interface
7 subroutine a(i, j)
8 integer :: i, j
9 end subroutine
10 end interface
11 type, abstract :: t
12 integer :: i
13 contains
14 procedure(a), deferred, nopass :: q
15 procedure(b), deferred, nopass :: p, r
16 end type
17 type t2
18 integer :: x
19 contains
20 private
21 final :: c
22 procedure, non_overridable :: d
23 end type
24 type, abstract :: t2a
25 contains
26 procedure(a), deferred, public, nopass :: e
27 end type
28 type t3
29 sequence
30 integer i
31 real x
32 double precision y
33 double complex z
34 end type
35 contains
36 subroutine b()
37 end subroutine
38 subroutine c(x)
39 type(t2) :: x
40 end subroutine
41 subroutine d(x)
42 class(t2) :: x
43 end subroutine
44 subroutine test
45 type(t2) :: x
46 call x%d()
47 end subroutine
48 end module
50 !Expect: m.mod
51 !module m
52 ! interface
53 ! subroutine a(i,j)
54 ! integer(4)::i
55 ! integer(4)::j
56 ! end
57 ! end interface
58 ! type,abstract::t
59 ! integer(4)::i
60 ! contains
61 ! procedure(a),deferred,nopass::q
62 ! procedure(b),deferred,nopass::p
63 ! procedure(b),deferred,nopass::r
64 ! end type
65 ! type::t2
66 ! integer(4)::x
67 ! contains
68 ! procedure,non_overridable,private::d
69 ! final::c
70 ! end type
71 ! type,abstract::t2a
72 ! contains
73 ! procedure(a),deferred,nopass::e
74 ! end type
75 ! type::t3
76 ! sequence
77 ! integer(4)::i
78 ! real(4)::x
79 ! real(8)::y
80 ! complex(8)::z
81 ! end type
82 !contains
83 ! subroutine b()
84 ! end
85 ! subroutine c(x)
86 ! type(t2)::x
87 ! end
88 ! subroutine d(x)
89 ! class(t2)::x
90 ! end
91 ! subroutine test()
92 ! end
93 !end
95 ! Ensure the type is emitted before its use
96 module m2
97 private s
98 type :: t
99 contains
100 procedure :: foo
101 end type
102 abstract interface
103 subroutine s(x)
104 import
105 type(t) :: x
106 end subroutine
107 end interface
108 contains
109 subroutine foo(x)
110 class(t) :: x
111 end subroutine
112 end module
113 !Expect: m2.mod
114 !module m2
115 ! type::t
116 ! contains
117 ! procedure::foo
118 ! end type
119 ! private::s
120 ! abstract interface
121 ! subroutine s(x)
122 ! import::t
123 ! type(t)::x
124 ! end
125 ! end interface
126 !contains
127 ! subroutine foo(x)
128 ! class(t)::x
129 ! end
130 !end