[flang][openacc] Use OpenACC terminator instead of fir.unreachable after Stop stmt...
[llvm-project.git] / flang / test / Lower / namelist-common-block.f90
blobf47d4c9bd87ea399c5672027d721512b4f920b29
1 ! RUN: bbc -emit-fir -o - %s | FileCheck %s
3 ! Test that allocatable or pointer item from namelist are retrieved correctly
4 ! if they are part of a common block as well.
6 program nml_common
7 integer :: i
8 real, pointer :: p(:)
9 namelist /t/i,p
10 common /c/i,p
12 allocate(p(2))
13 call print_t()
14 contains
15 subroutine print_t()
16 write(*,t)
17 end subroutine
18 end
20 ! CHECK-LABEL: fir.global linkonce @_QFNt.list constant : !fir.array<2xtuple<!fir.ref<i8>, !fir.ref<!fir.box<none>>>> {
21 ! CHECK: %[[CB_ADDR:.*]] = fir.address_of(@c_) : !fir.ref<!fir.array<56xi8>>
22 ! CHECK: %[[CB_CAST:.*]] = fir.convert %[[CB_ADDR]] : (!fir.ref<!fir.array<56xi8>>) -> !fir.ref<!fir.array<?xi8>>
23 ! CHECK: %[[OFFSET:.*]] = arith.constant 8 : index
24 ! CHECK: %[[COORD:.*]] = fir.coordinate_of %[[CB_CAST]], %[[OFFSET]] : (!fir.ref<!fir.array<?xi8>>, index) -> !fir.ref<i8>
25 ! CHECK: %[[CAST_BOX:.*]] = fir.convert %[[COORD]] : (!fir.ref<i8>) -> !fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>
26 ! CHECK: %[[CAST_BOX_NONE:.*]] = fir.convert %[[CAST_BOX]] : (!fir.ref<!fir.box<!fir.ptr<!fir.array<?xf32>>>>) -> !fir.ref<!fir.box<none>>
27 ! CHECK: %[[RES:.*]] = fir.insert_value %{{.*}}, %[[CAST_BOX_NONE]], [1 : index, 1 : index] : (!fir.array<2xtuple<!fir.ref<i8>, !fir.ref<!fir.box<none>>>>, !fir.ref<!fir.box<none>>) -> !fir.array<2xtuple<!fir.ref<i8>, !fir.ref<!fir.box<none>>>>
28 ! CHECK: fir.has_value %[[RES]] : !fir.array<2xtuple<!fir.ref<i8>, !fir.ref<!fir.box<none>>>>