! This test checks lowering of OpenACC update directive. ! RUN: bbc -fopenacc -emit-hlfir %s -o - | FileCheck %s subroutine acc_update integer :: async = 1 real, dimension(10, 10) :: a, b, c logical :: ifCondition = .TRUE. ! CHECK: %[[A:.*]] = fir.alloca !fir.array<10x10xf32> {{{.*}}uniq_name = "{{.*}}Ea"} ! CHECK: %[[DECLA:.*]]:2 = hlfir.declare %[[A]] ! CHECK: %[[B:.*]] = fir.alloca !fir.array<10x10xf32> {{{.*}}uniq_name = "{{.*}}Eb"} ! CHECK: %[[DECLB:.*]]:2 = hlfir.declare %[[B]] ! CHECK: %[[C:.*]] = fir.alloca !fir.array<10x10xf32> {{{.*}}uniq_name = "{{.*}}Ec"} ! CHECK: %[[DECLC:.*]]:2 = hlfir.declare %[[C]] !$acc update host(a) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_A]] : !fir.ref>){{$}} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) if_present ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_A]] : !fir.ref>) attributes {ifPresent}{{$}} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update self(a) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_A]] : !fir.ref>){{$}} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {dataClause = #acc, name = "a", structured = false} !$acc update host(a) if(.true.) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: %[[IF1:.*]] = arith.constant true ! CHECK: acc.update if(%[[IF1]]) dataOperands(%[[DEVPTR_A]] : !fir.ref>){{$}} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) if(ifCondition) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: %[[IFCOND:.*]] = fir.load %{{.*}} : !fir.ref> ! CHECK: %[[IF2:.*]] = fir.convert %[[IFCOND]] : (!fir.logical<4>) -> i1 ! CHECK: acc.update if(%[[IF2]]) dataOperands(%[[DEVPTR_A]] : !fir.ref>){{$}} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) host(b) host(c) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: %[[DEVPTR_B:.*]] = acc.getdeviceptr varPtr(%[[DECLB]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "b", structured = false} ! CHECK: %[[DEVPTR_C:.*]] = acc.getdeviceptr varPtr(%[[DECLC]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "c", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_A]], %[[DEVPTR_B]], %[[DEVPTR_C]] : !fir.ref>, !fir.ref>, !fir.ref>){{$}} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} ! CHECK: acc.update_host accPtr(%[[DEVPTR_B]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLB]]#1 : !fir.ref>) {name = "b", structured = false} ! CHECK: acc.update_host accPtr(%[[DEVPTR_C]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLC]]#1 : !fir.ref>) {name = "c", structured = false} !$acc update host(a) host(b) device(c) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: %[[DEVPTR_B:.*]] = acc.getdeviceptr varPtr(%[[DECLB]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "b", structured = false} ! CHECK: %[[DEVPTR_C:.*]] = acc.update_device varPtr(%[[DECLC]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {name = "c", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_C]], %[[DEVPTR_A]], %[[DEVPTR_B]] : !fir.ref>, !fir.ref>, !fir.ref>){{$}} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} ! CHECK: acc.update_host accPtr(%[[DEVPTR_B]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLB]]#1 : !fir.ref>) {name = "b", structured = false} !$acc update host(a) async ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_A]] : !fir.ref>) attributes {async} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) wait ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_A]] : !fir.ref>) attributes {wait} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) async wait ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_A]] : !fir.ref>) attributes {async, wait} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) async(1) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: [[ASYNC1:%.*]] = arith.constant 1 : i32 ! CHECK: acc.update async([[ASYNC1]] : i32) dataOperands(%[[DEVPTR_A]] : !fir.ref>) ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) async(async) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: [[ASYNC2:%.*]] = fir.load %{{.*}} : !fir.ref ! CHECK: acc.update async([[ASYNC2]] : i32) dataOperands(%[[DEVPTR_A]] : !fir.ref>) ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) wait(1) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: [[WAIT1:%.*]] = arith.constant 1 : i32 ! CHECK: acc.update wait([[WAIT1]] : i32) dataOperands(%[[DEVPTR_A]] : !fir.ref>) ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) wait(queues: 1, 2) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: [[WAIT2:%.*]] = arith.constant 1 : i32 ! CHECK: [[WAIT3:%.*]] = arith.constant 2 : i32 ! CHECK: acc.update wait([[WAIT2]], [[WAIT3]] : i32, i32) dataOperands(%[[DEVPTR_A]] : !fir.ref>) ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) wait(devnum: 1: queues: 1, 2) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: [[WAIT4:%.*]] = arith.constant 1 : i32 ! CHECK: [[WAIT5:%.*]] = arith.constant 2 : i32 ! CHECK: [[WAIT6:%.*]] = arith.constant 1 : i32 ! CHECK: acc.update wait_devnum([[WAIT6]] : i32) wait([[WAIT4]], [[WAIT5]] : i32, i32) dataOperands(%[[DEVPTR_A]] : !fir.ref>) ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) device_type(default, host) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_A]] : !fir.ref>) attributes {device_types = [#acc.device_type, #acc.device_type]} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} !$acc update host(a) device_type(*) ! CHECK: %[[DEVPTR_A:.*]] = acc.getdeviceptr varPtr(%[[DECLA]]#1 : !fir.ref>) bounds(%{{.*}}, %{{.*}}) -> !fir.ref> {dataClause = #acc, name = "a", structured = false} ! CHECK: acc.update dataOperands(%[[DEVPTR_A]] : !fir.ref>) attributes {device_types = [#acc.device_type]} ! CHECK: acc.update_host accPtr(%[[DEVPTR_A]] : !fir.ref>) bounds(%{{.*}}, %{{.*}}) to varPtr(%[[DECLA]]#1 : !fir.ref>) {name = "a", structured = false} end subroutine acc_update