[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / modfile04.f90
blob8cd60978b750f4f6c22ac0c339edc12dc99968fc
1 ! RUN: %S/test_modfile.sh %s %t %flang_fc1
2 ! REQUIRES: shell
3 ! modfile with subprograms
5 module m1
6 type :: t
7 end type
8 contains
10 pure subroutine Ss(x, y) bind(c)
11 logical x
12 intent(inout) y
13 intent(in) x
14 end subroutine
16 real function f1() result(x)
17 x = 1.0
18 end function
20 function f2(y)
21 complex y
22 f2 = 2.0
23 end function
25 end
27 module m2
28 contains
29 type(t) function f3(x)
30 use m1
31 integer, parameter :: a = 2
32 type t2(b)
33 integer, kind :: b = a
34 integer :: y
35 end type
36 type(t2) :: x
37 end
38 function f4() result(x)
39 implicit complex(x)
40 end
41 end
43 ! Module with a subroutine with alternate returns
44 module m3
45 contains
46 subroutine altReturn(arg1, arg2, *, *)
47 real :: arg1
48 real :: arg2
49 end subroutine
50 end module m3
52 !Expect: m1.mod
53 !module m1
54 !type::t
55 !end type
56 !contains
57 !pure subroutine ss(x,y) bind(c, name="ss")
58 !logical(4),intent(in)::x
59 !real(4),intent(inout)::y
60 !end
61 !function f1() result(x)
62 !real(4)::x
63 !end
64 !function f2(y)
65 !complex(4)::y
66 !real(4)::f2
67 !end
68 !end
70 !Expect: m2.mod
71 !module m2
72 !contains
73 !function f3(x)
74 ! use m1,only:t
75 ! type::t2(b)
76 ! integer(4),kind::b=2_4
77 ! integer(4)::y
78 ! end type
79 ! type(t2(b=2_4))::x
80 ! type(t)::f3
81 !end
82 !function f4() result(x)
83 !complex(4)::x
84 !end
85 !end
87 !Expect: m3.mod
88 !module m3
89 !contains
90 !subroutine altreturn(arg1,arg2,*,*)
91 !real(4)::arg1
92 !real(4)::arg2
93 !end
94 !end