xref: /llvm-project/flang/test/Lower/module_definition.f90 (revision c1654c38e8b82a075613fd60f19a179b1c7df2a2)
1! RUN: bbc -emit-fir %s -o - | FileCheck %s
2
3! Test lowering of module that defines data that is otherwise not used
4! in this file.
5
6! Module defines variable in common block without initializer
7module modCommonNoInit1
8  ! Module variable is in blank common
9  real :: x_blank
10  common // x_blank
11  ! Module variable is in named common, no init
12  real :: x_named1
13  common /named1/ x_named1
14end module
15! CHECK-LABEL: fir.global common @__BLNK__(dense<0> : vector<4xi8>) {alignment = 4 : i64} : !fir.array<4xi8>
16! CHECK-LABEL: fir.global common @named1_(dense<0> : vector<4xi8>) {alignment = 4 : i64} : !fir.array<4xi8>
17
18! Module defines variable in common block with initialization
19module modCommonInit1
20  integer :: i_named2 = 42
21  common /named2/ i_named2
22end module
23! CHECK-LABEL: fir.global @named2_ {alignment = 4 : i64} : tuple<i32> {
24  ! CHECK: %[[init:.*]] = fir.insert_value %{{.*}}, %c42{{.*}}, [0 : index] : (tuple<i32>, i32) -> tuple<i32>
25  ! CHECK: fir.has_value %[[init]] : tuple<i32>
26
27! Module m1 defines simple data
28module m1
29  real :: x
30  integer :: y(100)
31end module
32! CHECK: fir.global @_QMm1Ex : f32
33! CHECK: fir.global @_QMm1Ey : !fir.array<100xi32>
34
35! Module modEq1 defines data that is equivalenced and not used in this
36! file.
37module modEq1
38  ! Equivalence, no initialization
39  real :: x1(10), x2(10), x3(10)
40  ! Equivalence with initialization
41  real :: y1 = 42.
42  real :: y2(10)
43  equivalence (x1(1), x2(5), x3(10)), (y1, y2(5))
44end module
45! CHECK-LABEL: fir.global @_QMmodeq1Ex1 : !fir.array<76xi8>
46! CHECK-LABEL: fir.global @_QMmodeq1Ey1 : !fir.array<10xi32> {
47  ! CHECK: %[[undef:.*]] = fir.undefined !fir.array<10xi32>
48  ! CHECK: %[[v1:.*]] = fir.insert_on_range %0, %c0{{.*}} from (0) to (3) : (!fir.array<10xi32>, i32) -> !fir.array<10xi32>
49  ! CHECK: %[[v2:.*]] = fir.insert_value %1, %c1109917696{{.*}}, [4 : index] : (!fir.array<10xi32>, i32) -> !fir.array<10xi32>
50  ! CHECK: %[[v3:.*]] = fir.insert_on_range %2, %c0{{.*}} from (5) to (9) : (!fir.array<10xi32>, i32) -> !fir.array<10xi32>
51  ! CHECK: fir.has_value %[[v3]] : !fir.array<10xi32>
52
53! Test defining two module variables whose initializers depend on each others
54! addresses.
55module global_init_depending_on_each_other_address
56  type a
57    type(b), pointer :: pb
58  end type
59  type b
60    type(a), pointer :: pa
61  end type
62  type(a), target :: xa
63  type(b), target :: xb
64  data xa, xb/a(xb), b(xa)/
65end module
66! CHECK-LABEL: fir.global @_QMglobal_init_depending_on_each_other_addressExb
67  ! CHECK: fir.address_of(@_QMglobal_init_depending_on_each_other_addressExa)
68! CHECK-LABEL: fir.global @_QMglobal_init_depending_on_each_other_addressExa
69  ! CHECK: fir.address_of(@_QMglobal_init_depending_on_each_other_addressExb)
70