[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / separate-mp01.f90
blob03b27e1d7b23a9376a0f626145f83f9100dd8628
1 ! RUN: %S/test_errors.sh %s %t %flang_fc1
2 ! REQUIRES: shell
4 ! case 1: ma_create_new_fun' was not declared a separate module procedure
5 module m1
6 integer :: i
7 interface ma
8 module function ma_create_fun( ) result(this)
9 integer this
10 end function
11 end interface
12 end module
14 submodule (m1) ma_submodule
15 integer :: j
16 contains
17 module function ma_create_fun() result(this)
18 integer this
19 i = 1
20 j = 2
21 end function
23 !ERROR: 'ma_create_new_fun' was not declared a separate module procedure
24 module function ma_create_new_fun() result(this)
25 integer :: this
26 i = 2
27 j = 1
28 print *, "Hello"
29 end function
30 end submodule
32 ! case 2: 'mb_create_new_sub' was not declared a separate module procedure
33 module m2
34 integer :: i
35 interface mb
36 module subroutine mb_create_sub
37 end subroutine mb_create_sub
38 end interface
39 end module
41 submodule (m2) mb_submodule
42 integer :: j
43 contains
44 module subroutine mb_create_sub
45 integer this
46 i = 1
47 j = 2
48 end subroutine mb_create_sub
50 !ERROR: 'mb_create_new_sub' was not declared a separate module procedure
51 module SUBROUTINE mb_create_new_sub()
52 integer :: this
53 i = 2
54 j = 1
55 end SUBROUTINE mb_create_new_sub
56 end submodule
58 ! case 3: separate module procedure without module prefix
59 module m3
60 interface mc
61 function mc_create( ) result(this)
62 integer :: this
63 end function
64 end interface
65 end module
67 submodule (m3) mc_submodule
68 contains
69 !ERROR: 'mc_create' was not declared a separate module procedure
70 module function mc_create() result(this)
71 integer :: this
72 end function
73 end submodule
75 ! case 4: Submodule having separate module procedure rather than a module
76 module m4
77 interface
78 real module function func1() ! module procedure interface body for func1
79 end function
80 end interface
81 end module
83 submodule (m4) m4sub
84 interface
85 module function func2(b) ! module procedure interface body for func2
86 integer :: b
87 integer :: func2
88 end function
90 real module function func3() ! module procedure interface body for func3
91 end function
92 end interface
93 contains
94 real module function func1() ! implementation of func1 declared in m4
95 func1 = 20
96 end function
97 end submodule
99 submodule (m4:m4sub) m4sub2
100 contains
101 module function func2(b) ! implementation of func2 declared in m4sub
102 integer :: b
103 integer :: func2
104 func2 = b
105 end function
107 real module function func3() ! implementation of func3 declared in m4sub
108 func3 = 20
109 end function
110 end submodule