[LLVM] Fix Maintainers.md formatting (NFC)
[llvm-project.git] / flang / test / Lower / common-block.f90
blobb5c1389df45d3542f6379a2c101231ec8ab0fe16
1 ! REQUIRES: flang-supports-f128-math
2 ! RUN: bbc %s -o - | tco | FileCheck %s
3 ! RUN: %flang -emit-llvm -S -mmlir -disable-external-name-interop %s -o - | FileCheck %s
5 ! CHECK: @__BLNK__ = common global [8 x i8] zeroinitializer
6 ! CHECK: @co1_ = common global [16 x i8] zeroinitializer, align 16
7 ! CHECK: @rien_ = common global [1 x i8] zeroinitializer
8 ! CHECK: @with_empty_equiv_ = common global [8 x i8] zeroinitializer
9 ! CHECK: @x_ = global { float, float } { float 1.0{{.*}}, float 2.0{{.*}} }
10 ! CHECK: @y_ = common global [12 x i8] zeroinitializer
11 ! CHECK: @z_ = global { i32, [4 x i8], float } { i32 42, [4 x i8] zeroinitializer, float 3.000000e+00 }
13 ! CHECK-LABEL: _QPs0
14 subroutine s0
15 common // a0, b0
17 ! CHECK: call void @_QPs(ptr @__BLNK__, ptr getelementptr (i8, ptr @__BLNK__, i64 4))
18 call s(a0, b0)
19 end subroutine s0
21 ! CHECK-LABEL: _QPs1
22 subroutine s1
23 common /x/ a1, b1
24 data a1 /1.0/, b1 /2.0/
26 ! CHECK: call void @_QPs(ptr @x_, ptr getelementptr (i8, ptr @x_, i64 4))
27 call s(a1, b1)
28 end subroutine s1
30 ! CHECK-LABEL: _QPs2
31 subroutine s2
32 common /y/ a2, b2, c2
34 ! CHECK: call void @_QPs(ptr @y_, ptr getelementptr (i8, ptr @y_, i64 4))
35 call s(a2, b2)
36 end subroutine s2
38 ! Test that common initialized through aliases of common members are getting
39 ! the correct initializer.
40 ! CHECK-LABEL: _QPs3
41 subroutine s3
42 integer :: i = 42
43 real :: x
44 complex :: c
45 real :: glue(2)
46 real :: y = 3.
47 equivalence (i, x), (glue(1), c), (glue(2), y)
48 ! x and c are not directly initialized, but overlapping aliases are.
49 common /z/ x, c
50 end subroutine s3
52 module mod_with_common
53 integer :: i, j
54 common /c_in_mod/ i, j
55 end module
56 ! CHECK-LABEL: _QPs4
57 subroutine s4
58 use mod_with_common
59 ! CHECK: load i32, ptr @c_in_mod_
60 print *, i
61 ! CHECK: load i32, ptr getelementptr (i8, ptr @c_in_mod_, i64 4)
62 print *, j
63 end subroutine s4
65 ! CHECK-LABEL: _QPs5
66 subroutine s5
67 real r(1:0)
68 common /rien/ r
69 end subroutine s5
71 ! CHECK-LABEL: _QPs6
72 subroutine s6
73 real r1(1:0), r2(1:0), x, y
74 common /with_empty_equiv/ x, r1, y
75 equivalence(r1, r2)
76 end subroutine s6
78 subroutine s7()
79 real(16) r16
80 common /co1/ r16
81 end subroutine