blob: fc01bdafe51ed162eed192d30e28a556669f7b53 [file] [log] [blame] [edit]
!RUN: %flang_fc1 -emit-hlfir -fopenmp -mmlir --enable-delayed-privatization-staging=false %s -o - | FileCheck %s --check-prefixes=CHECK,CHECK-NO-FPRIV
!RUN: %flang_fc1 -emit-hlfir -fopenmp -mmlir --enable-delayed-privatization-staging=true %s -o - | FileCheck %s --check-prefixes=CHECK,CHECK-FPRIV
! Check that the complex*4 is passed by value. but complex*8 is passed by
! reference
!CHECK-FPRIV: omp.private {type = firstprivate} @[[PRIV_64:.*]] : complex<f64> copy {
!CHECK-FPRIV: omp.private {type = firstprivate} @[[PRIV_32:.*]] : complex<f32> copy {
!CHECK-LABEL: func.func @_QMmPbar()
!CHECK: %[[V0:[0-9]+]]:2 = hlfir.declare {{.*}} (!fir.ref<complex<f64>>) -> (!fir.ref<complex<f64>>, !fir.ref<complex<f64>>)
!CHECK: %[[V1:[0-9]+]]:2 = hlfir.declare {{.*}} (!fir.ref<complex<f32>>) -> (!fir.ref<complex<f32>>, !fir.ref<complex<f32>>)
!CHECK-FPRIV: %[[V2:[0-9]+]] = omp.map.info var_ptr(%[[V1]]#0 : !fir.ref<complex<f32>>, complex<f32>) {{.*}} capture(ByCopy)
!CHECK-FPRIV: %[[V3:[0-9]+]] = omp.map.info var_ptr(%[[V0]]#0 : !fir.ref<complex<f64>>, complex<f64>) {{.*}} capture(ByRef)
!CHECK-FPRIV: omp.target map_entries(%[[V2]] -> {{.*}}, %[[V3]] -> {{.*}} : !fir.ref<complex<f32>>, !fir.ref<complex<f64>>) private(@[[PRIV_32]] %[[V1]]#0 -> %{{.*}} [map_idx=0], @[[PRIV_64]] %[[V0]]#0 -> %{{.*}} [map_idx=1] : !fir.ref<complex<f32>>, !fir.ref<complex<f64>>) {
!CHECK-NO-FPRIV: %[[V2:[0-9]+]] = omp.map.info var_ptr(%[[V1]]#1 : !fir.ref<complex<f32>>, complex<f32>) {{.*}} capture(ByCopy)
!CHECK-NO-FPRIV: %[[V3:[0-9]+]] = omp.map.info var_ptr(%[[V0]]#1 : !fir.ref<complex<f64>>, complex<f64>) {{.*}} capture(ByRef)
!CHECK-NO-PRIV: omp.target map_entries(%[[V2]] -> {{.*}}, %[[V3]] -> {{.*}} : !fir.ref<complex<f32>>, !fir.ref<complex<f64>>)
module m
implicit none
complex(kind=4) :: cfval = (24, 25)
complex(kind=8) :: cdval = (28, 29)
interface
subroutine foo(x, y)
complex(kind=4) :: x
complex(kind=8) :: y
!$omp declare target
end
end interface
contains
subroutine bar()
implicit none
!$omp target
call foo(cfval, cdval)
!$omp end target
end
end module