Files
clang-p2996/flang/test/Lower/OpenMP/taskgroup.f90
Tom Eccles 4cc9437a7e [flang] Set default to -ffpcontract=fast
Following RFC at
https://discourse.llvm.org/t/rfc-ffp-contract-default-value/66301

This adds the `fastmath<contract>` attribute to `fir.call` and some
floating point arithmetic operations (hence the many test changes).
Instead of testing for this specific attribute, I am using a regular
expression to match any attributes.
2022-11-17 15:49:51 +00:00

20 lines
605 B
Fortran

!RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s
!CHECK-LABEL: @_QPomp_taskgroup
subroutine omp_taskgroup
use omp_lib
integer :: allocated_x
!CHECK-DAG: %{{.*}} = fir.alloca i32 {bindc_name = "allocated_x", uniq_name = "_QFomp_taskgroupEallocated_x"}
!CHECK-DAG: %{{.*}} = arith.constant 1 : i32
!CHECK: omp.taskgroup allocate(%{{.*}} : i32 -> %0 : !fir.ref<i32>)
!$omp taskgroup allocate(omp_high_bw_mem_alloc: allocated_x)
!$omp task
!CHECK: fir.call @_QPwork() {{.*}}: () -> ()
call work()
!CHECK: omp.terminator
!$omp end task
!CHECK: omp.terminator
!$omp end taskgroup
end subroutine