[flang][openacc][NFC] Check only HLFIR lowering for atomic tests (#72922)
[llvm-project.git] / flang / test / Lower / common-block.f90
blob3934b71b75694edd789af500d1deaa9591f5be59
1 ! RUN: bbc %s -o - | tco | FileCheck %s
2 ! RUN: %flang -emit-llvm -S -mmlir -disable-external-name-interop %s -o - | FileCheck %s
4 ! CHECK: @__BLNK__ = common global [8 x i8] zeroinitializer
5 ! CHECK: @rien_ = common global [1 x i8] zeroinitializer
6 ! CHECK: @with_empty_equiv_ = common global [8 x i8] zeroinitializer
7 ! CHECK: @x_ = global { float, float } { float 1.0{{.*}}, float 2.0{{.*}} }
8 ! CHECK: @y_ = common global [12 x i8] zeroinitializer
9 ! CHECK: @z_ = global { i32, [4 x i8], float } { i32 42, [4 x i8] zeroinitializer, float 3.000000e+00 }
11 ! CHECK-LABEL: _QPs0
12 subroutine s0
13 common // a0, b0
15 ! CHECK: call void @_QPs(ptr @__BLNK__, ptr getelementptr (i8, ptr @__BLNK__, i64 4))
16 call s(a0, b0)
17 end subroutine s0
19 ! CHECK-LABEL: _QPs1
20 subroutine s1
21 common /x/ a1, b1
22 data a1 /1.0/, b1 /2.0/
24 ! CHECK: call void @_QPs(ptr @x_, ptr getelementptr (i8, ptr @x_, i64 4))
25 call s(a1, b1)
26 end subroutine s1
28 ! CHECK-LABEL: _QPs2
29 subroutine s2
30 common /y/ a2, b2, c2
32 ! CHECK: call void @_QPs(ptr @y_, ptr getelementptr (i8, ptr @y_, i64 4))
33 call s(a2, b2)
34 end subroutine s2
36 ! Test that common initialized through aliases of common members are getting
37 ! the correct initializer.
38 ! CHECK-LABEL: _QPs3
39 subroutine s3
40 integer :: i = 42
41 real :: x
42 complex :: c
43 real :: glue(2)
44 real :: y = 3.
45 equivalence (i, x), (glue(1), c), (glue(2), y)
46 ! x and c are not directly initialized, but overlapping aliases are.
47 common /z/ x, c
48 end subroutine s3
50 module mod_with_common
51 integer :: i, j
52 common /c_in_mod/ i, j
53 end module
54 ! CHECK-LABEL: _QPs4
55 subroutine s4
56 use mod_with_common
57 ! CHECK: load i32, ptr @c_in_mod_
58 print *, i
59 ! CHECK: load i32, ptr getelementptr (i8, ptr @c_in_mod_, i64 4)
60 print *, j
61 end subroutine s4
63 ! CHECK-LABEL: _QPs5
64 subroutine s5
65 real r(1:0)
66 common /rien/ r
67 end subroutine s5
69 ! CHECK-LABEL: _QPs6
70 subroutine s6
71 real r1(1:0), r2(1:0), x, y
72 common /with_empty_equiv/ x, r1, y
73 equivalence(r1, r2)
74 end subroutine s6