llvm-project/flang/test/Lower/OpenMP/threadprivate-common-block-pointer.f90
Tom Eccles e7c6e3557b
[flang][OpenMP] Fix threadprivate pointer variable in common block (#131888)
Fixes #112538

The problem was that the host associated symbol for the threadprivate
variable doesn't have all of the symbol attributes (e.g. POINTER). This
caused the lowering code to generate the wrong type, eventually hitting
an assertion.
2025-03-19 10:12:52 +00:00

32 lines
1.5 KiB
Fortran

! Simple test for lowering of OpenMP Threadprivate Directive with a pointer var
! from a common block.
!RUN: %flang_fc1 -emit-hlfir -fopenmp %s -o - | FileCheck %s
!RUN: bbc -hlfir -emit-hlfir -fopenmp %s -o - | FileCheck %s
! Regression test for a compiler crash
module mmm
integer,pointer::nam1
common /com1/nam1,nam2
!$omp threadprivate(/com1/)
end
use mmm
!$omp parallel copyin(nam1)
!$omp end parallel
end
! CHECK-LABEL: fir.global common @com1_(dense<0> : vector<28xi8>) {alignment = 8 : i64} : !fir.array<28xi8>
! CHECK-LABEL: func.func @_QQmain() {
! CHECK: %[[VAL_0:.*]] = fir.address_of(@com1_) : !fir.ref<!fir.array<28xi8>>
! CHECK: omp.parallel {
! CHECK: %[[VAL_17:.*]] = omp.threadprivate %[[VAL_0]] : !fir.ref<!fir.array<28xi8>> -> !fir.ref<!fir.array<28xi8>>
! CHECK: %[[VAL_18:.*]] = fir.convert %[[VAL_17]] : (!fir.ref<!fir.array<28xi8>>) -> !fir.ref<!fir.array<?xi8>>
! CHECK: %[[VAL_19:.*]] = arith.constant 0 : index
! CHECK: %[[VAL_20:.*]] = fir.coordinate_of %[[VAL_18]], %[[VAL_19]] : (!fir.ref<!fir.array<?xi8>>, index) -> !fir.ref<i8>
! CHECK: %[[VAL_21:.*]] = fir.convert %[[VAL_20]] : (!fir.ref<i8>) -> !fir.ref<!fir.box<!fir.ptr<i32>>>
! CHECK: %[[VAL_22:.*]]:2 = hlfir.declare %[[VAL_21]] {fortran_attrs = #{{.*}}<pointer>, uniq_name = "_QMmmmEnam1"} : (!fir.ref<!fir.box<!fir.ptr<i32>>>) -> (!fir.ref<!fir.box<!fir.ptr<i32>>>, !fir.ref<!fir.box<!fir.ptr<i32>>>)