[NFC][RISCV] Remove CFIIndex argument from allocateStack (#117871)
[llvm-project.git] / flang / test / Semantics / modproc01.f90
blob5f45362e95093428bfc347c90e06921850c38dff
1 !RUN: %flang_fc1 -fdebug-dump-symbols %s | FileCheck %s
2 module m
3 type pdt1(k1,l1)
4 integer, kind :: k1
5 integer, len :: l1
6 type(pdt2(k1,l1)), allocatable :: a1
7 end type pdt1
8 type pdt2(k2,l2)
9 integer, kind :: k2
10 integer, len :: l2
11 integer(k2) :: j2
12 type(pdt1(k2,l2)) :: a2(k2)
13 end type pdt2
14 interface
15 module function mf(n,str,x1) result(res)
16 integer, intent(in) :: n
17 character(n), intent(in) :: str
18 type(pdt1(1,n)), intent(in) :: x1
19 type(pdt2(2,n)) :: res
20 end function
21 module subroutine ms(f)
22 procedure(mf) :: f
23 end subroutine
24 end interface
25 integer sm
26 end module
27 !CHECK: mf, MODULE, PUBLIC (Function): Subprogram isInterface result:TYPE(pdt2(k2=2_4,l2=n)) res (INTEGER(4) n,CHARACTER(n,1) str,TYPE(pdt1(k1=1_4,l1=n)) x1)
28 !CHECK: pdt1, PUBLIC: DerivedType components: a1
29 !CHECK: pdt2, PUBLIC: DerivedType components: j2,a2
30 !CHECK: sm, PUBLIC size=4 offset=0: ObjectEntity type: INTEGER(4)
31 !CHECK: DerivedType scope: pdt1
32 !CHECK: a1, ALLOCATABLE: ObjectEntity type: TYPE(pdt2(int(k1,kind=4),int(l1,kind=4)))
33 !CHECK: k1: TypeParam type:INTEGER(4) Kind
34 !CHECK: l1: TypeParam type:INTEGER(4) Len
35 !CHECK: DerivedType scope: pdt2
36 !CHECK: a2: ObjectEntity type: TYPE(pdt1(k1=int(k2,kind=4),l1=int(l2,kind=4))) shape: 1_8:k2
37 !CHECK: j2: ObjectEntity type: INTEGER(int(int(k2,kind=4),kind=8))
38 !CHECK: k2: TypeParam type:INTEGER(4) Kind
39 !CHECK: l2: TypeParam type:INTEGER(4) Len
40 !CHECK: Subprogram scope: mf size=112 alignment=8
41 !CHECK: mf (Function): HostAssoc
42 !CHECK: n, INTENT(IN) size=4 offset=0: ObjectEntity dummy type: INTEGER(4)
43 !CHECK: res size=40 offset=72: ObjectEntity funcResult type: TYPE(pdt2(k2=2_4,l2=n))
44 !CHECK: str, INTENT(IN) size=24 offset=8: ObjectEntity dummy type: CHARACTER(n,1)
45 !CHECK: x1, INTENT(IN) size=40 offset=32: ObjectEntity dummy type: TYPE(pdt1(k1=1_4,l1=n))
46 !CHECK: DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=n)
47 !CHECK: a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=int(l1,kind=4)))
48 !CHECK: k1: TypeParam type:INTEGER(4) Kind init:1_4
49 !CHECK: l1: TypeParam type:INTEGER(4) Len init:n
50 !CHECK: DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=1_4,l2=int(l1,kind=4))
51 !CHECK: a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=1_4,l1=int(l2,kind=4))) shape: 1_8:1_8
52 !CHECK: j2 size=1 offset=0: ObjectEntity type: INTEGER(1)
53 !CHECK: k2: TypeParam type:INTEGER(4) Kind init:1_4
54 !CHECK: l2: TypeParam type:INTEGER(4) Len init:int(l1,kind=4)
55 !CHECK: DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=int(l2,kind=4))
56 !CHECK: a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=int(l1,kind=4)))
57 !CHECK: k1: TypeParam type:INTEGER(4) Kind init:1_4
58 !CHECK: l1: TypeParam type:INTEGER(4) Len init:int(l2,kind=4)
59 !CHECK: DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=2_4,l2=n)
60 !CHECK: a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=int(l2,kind=4))) shape: 1_8:2_8
61 !CHECK: j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
62 !CHECK: k2: TypeParam type:INTEGER(4) Kind init:2_4
63 !CHECK: l2: TypeParam type:INTEGER(4) Len init:n
64 !CHECK: DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=2_4,l1=int(l2,kind=4))
65 !CHECK: a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=2_4,l2=int(l1,kind=4)))
66 !CHECK: k1: TypeParam type:INTEGER(4) Kind init:2_4
67 !CHECK: l1: TypeParam type:INTEGER(4) Len init:int(l2,kind=4)
68 !CHECK: DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=2_4,l2=int(l1,kind=4))
69 !CHECK: a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=int(l2,kind=4))) shape: 1_8:2_8
70 !CHECK: j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
71 !CHECK: k2: TypeParam type:INTEGER(4) Kind init:2_4
72 !CHECK: l2: TypeParam type:INTEGER(4) Len init:int(l1,kind=4)
74 submodule(m) sm
75 contains
76 module procedure mf
77 print *, len(str), x1%k1, x1%l1, res%k2, res%l2
78 allocate(res%a2(1)%a1)
79 res%a2(1)%a1%j2 = 2
80 end procedure
81 module procedure ms
82 ! type(pdt2(2.3)) x
83 ! x = f(3, "abc", pdt1(1,3)())
84 end procedure
85 end submodule
86 !CHECK: Module scope: sm size=0 alignment=1
87 !CHECK: mf, MODULE, PUBLIC (Function): Subprogram result:TYPE(pdt2(k2=2_4,l2=n)) res (INTEGER(4) n,CHARACTER(n,1) str,TYPE(pdt1(k1=1_4,l1=n)) x1) moduleInterface: mf, MODULE, PUBLIC (Function): Subprogram isInterface result:TYPE(pdt2(k2=2_4,l2=n)) res (INTEGER(4) n,CHARACTER(n,1) str,TYPE(pdt1(k1=1_4,l1=n)) x1)
88 !CHECK: Subprogram scope: mf size=112 alignment=8
89 !CHECK: len, INTRINSIC, PURE (Function): ProcEntity
90 !CHECK: n, INTENT(IN) size=4 offset=0: ObjectEntity dummy type: INTEGER(4)
91 !CHECK: res size=40 offset=72: ObjectEntity funcResult type: TYPE(pdt2(k2=2_4,l2=n))
92 !CHECK: str, INTENT(IN) size=24 offset=8: ObjectEntity dummy type: CHARACTER(n,1)
93 !CHECK: x1, INTENT(IN) size=40 offset=32: ObjectEntity dummy type: TYPE(pdt1(k1=1_4,l1=n))
94 !CHECK: DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=2_4,l2=n)
95 !CHECK: a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=int(l2,kind=4))) shape: 1_8:2_8
96 !CHECK: j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
97 !CHECK: k2: TypeParam type:INTEGER(4) Kind init:2_4
98 !CHECK: l2: TypeParam type:INTEGER(4) Len init:n
99 !CHECK: DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=2_4,l1=int(l2,kind=4))
100 !CHECK: a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=2_4,l2=int(l1,kind=4)))
101 !CHECK: k1: TypeParam type:INTEGER(4) Kind init:2_4
102 !CHECK: l1: TypeParam type:INTEGER(4) Len init:int(l2,kind=4)
103 !CHECK: DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=2_4,l2=int(l1,kind=4))
104 !CHECK: a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=int(l2,kind=4))) shape: 1_8:2_8
105 !CHECK: j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
106 !CHECK: k2: TypeParam type:INTEGER(4) Kind init:2_4
107 !CHECK: l2: TypeParam type:INTEGER(4) Len init:int(l1,kind=4)
108 !CHECK: DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=n)
109 !CHECK: a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=int(l1,kind=4)))
110 !CHECK: k1: TypeParam type:INTEGER(4) Kind init:1_4
111 !CHECK: l1: TypeParam type:INTEGER(4) Len init:n
112 !CHECK: DerivedType scope: size=72 alignment=8 instantiation of pdt2(k2=1_4,l2=int(l1,kind=4))
113 !CHECK: a2 size=64 offset=8: ObjectEntity type: TYPE(pdt1(k1=1_4,l1=int(l2,kind=4))) shape: 1_8:1_8
114 !CHECK: j2 size=1 offset=0: ObjectEntity type: INTEGER(1)
115 !CHECK: k2: TypeParam type:INTEGER(4) Kind init:1_4
116 !CHECK: l2: TypeParam type:INTEGER(4) Len init:int(l1,kind=4)
117 !CHECK: DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=int(l2,kind=4))
118 !CHECK: a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=int(l1,kind=4)))
119 !CHECK: k1: TypeParam type:INTEGER(4) Kind init:1_4
120 !CHECK: l1: TypeParam type:INTEGER(4) Len init:int(l2,kind=4)
122 program test
123 use m
124 type(pdt2(2,3)) x
125 x = mf(3, "abc", pdt1(1,3)())
126 ! call ms(mf)
127 end program
128 !CHECK: MainProgram scope: test size=88 alignment=8
129 !CHECK: mf, MODULE (Function): Use from mf in m
130 !CHECK: pdt1: Use from pdt1 in m
131 !CHECK: pdt2: Use from pdt2 in m
132 !CHECK: sm: Use from sm in m
133 !CHECK: x size=88 offset=0: ObjectEntity type: TYPE(pdt2(k2=2_4,l2=3_4))
134 !CHECK: DerivedType scope: size=88 alignment=8 instantiation of pdt2(k2=2_4,l2=3_4)
135 !CHECK: a2 size=80 offset=8: ObjectEntity type: TYPE(pdt1(k1=2_4,l1=3_4)) shape: 1_8:2_8
136 !CHECK: j2 size=2 offset=0: ObjectEntity type: INTEGER(2)
137 !CHECK: k2: TypeParam type:INTEGER(4) Kind init:2_4
138 !CHECK: l2: TypeParam type:INTEGER(4) Len init:3_4
139 !CHECK: DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=2_4,l1=3_4)
140 !CHECK: a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=2_4,l2=3_4))
141 !CHECK: k1: TypeParam type:INTEGER(4) Kind init:2_4
142 !CHECK: l1: TypeParam type:INTEGER(4) Len init:3_4
143 !CHECK: DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=3_4)
144 !CHECK: a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=3_4))
145 !CHECK: k1: TypeParam type:INTEGER(4) Kind init:1_4
146 !CHECK: l1: TypeParam type:INTEGER(4) Len init:3_4
147 !CHECK: DerivedType scope: size=48 alignment=8 instantiation of pdt2(k2=1_4,l2=3_4) sourceRange=0 bytes
148 !CHECK: a2 size=40 offset=8: ObjectEntity type: TYPE(pdt1(k1=1_4,l1=3_4)) shape: 1_8:1_8
149 !CHECK: j2 size=1 offset=0: ObjectEntity type: INTEGER(1)
150 !CHECK: k2: TypeParam type:INTEGER(4) Kind init:1_4
151 !CHECK: l2: TypeParam type:INTEGER(4) Len init:3_4
152 !CHECK: DerivedType scope: size=40 alignment=8 instantiation of pdt1(k1=1_4,l1=3_4) sourceRange=0 bytes
153 !CHECK: a1, ALLOCATABLE size=40 offset=0: ObjectEntity type: TYPE(pdt2(k2=1_4,l2=3_4))
154 !CHECK: k1: TypeParam type:INTEGER(4) Kind init:1_4
155 !CHECK: l1: TypeParam type:INTEGER(4) Len init:3_4