[flang] Switch spread first argument lowering from asAddr to asBox
authorValentin Clement <clementval@gmail.com>
Mon, 16 Jan 2023 08:37:38 +0000 (09:37 +0100)
committerValentin Clement <clementval@gmail.com>
Mon, 16 Jan 2023 08:38:35 +0000 (09:38 +0100)
Use asBox so no simply contiguous argument do not issue a copy and also
support polymorphic entity out of the box.

Depends on D141667

Reviewed By: jeanPerier, PeteSteinfeld

Differential Revision: https://reviews.llvm.org/D141678

flang/lib/Lower/IntrinsicCall.cpp
flang/test/Lower/Intrinsics/spread.f90

index 46af776..7bb8b55 100644 (file)
@@ -806,7 +806,7 @@ static constexpr IntrinsicHandler handlers[]{
     {"spacing", &I::genSpacing},
     {"spread",
      &I::genSpread,
-     {{{"source", asAddr}, {"dim", asValue}, {"ncopies", asValue}}},
+     {{{"source", asBox}, {"dim", asValue}, {"ncopies", asValue}}},
      /*isElemental=*/false},
     {"sum",
      &I::genSum,
index 11b206a..36947b4 100644 (file)
@@ -1,6 +1,18 @@
-! RUN: bbc -emit-fir %s -o - | FileCheck %s
+! RUN: bbc -emit-fir -polymorphic-type %s -o - | FileCheck %s
 
-! CHECK-LABEL: func @_QPspread_test(
+module spread_mod
+
+type :: p1
+  integer :: a
+end type
+
+type, extends(p1) :: p2
+  integer :: b
+end type
+
+contains
+
+! CHECK-LABEL: func @_QMspread_modPspread_test(
 ! CHECK-SAME: %[[arg0:[^:]+]]: !fir.ref<i32>{{.*}}, %[[arg1:[^:]+]]: !fir.ref<i32>{{.*}}, %[[arg2:[^:]+]]: !fir.ref<i32>{{.*}}, %[[arg3:.*]]: !fir.box<!fir.array<?xi32>>{{.*}}) {
 subroutine spread_test(s,d,n,r)
     integer :: s,d,n
@@ -17,11 +29,11 @@ subroutine spread_test(s,d,n,r)
   ! CHECK-DAG:  %[[a13:.*]] = fir.load %[[a0]] : !fir.ref<!fir.box<!fir.heap<!fir.array<?xi32>>>>
   ! CHECK-DAG:  %[[a15:.*]] = fir.box_addr %[[a13]] : (!fir.box<!fir.heap<!fir.array<?xi32>>>) -> !fir.heap<!fir.array<?xi32>>
   ! CHECK:  fir.freemem %[[a15]]
-  end subroutine
+end subroutine
   
-  ! CHECK-LABEL: func @_QPspread_test2(
-  ! CHECK-SAME: %[[arg0:.*]]: !fir.box<!fir.array<?xi32>>{{.*}}, %[[arg1:[^:]+]]: !fir.ref<i32>{{.*}}, %[[arg2:[^:]+]]: !fir.ref<i32>{{.*}}, %[[arg3:.*]]: !fir.box<!fir.array<?x?xi32>>{{.*}}) {
-  subroutine spread_test2(s,d,n,r)
+! CHECK-LABEL: func @_QMspread_modPspread_test2(
+! CHECK-SAME: %[[arg0:.*]]: !fir.box<!fir.array<?xi32>>{{.*}}, %[[arg1:[^:]+]]: !fir.ref<i32>{{.*}}, %[[arg2:[^:]+]]: !fir.ref<i32>{{.*}}, %[[arg3:.*]]: !fir.box<!fir.array<?x?xi32>>{{.*}}) {
+subroutine spread_test2(s,d,n,r)
     integer :: s(:),d,n
     integer :: r(:,:)
   ! CHECK-DAG:  %[[a0:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?x?xi32>>>
@@ -35,5 +47,23 @@ subroutine spread_test(s,d,n,r)
   ! CHECK-DAG:  %[[a12:.*]] = fir.load %[[a0]] : !fir.ref<!fir.box<!fir.heap<!fir.array<?x?xi32>>>>
   ! CHECK-DAG:  %[[a15:.*]] = fir.box_addr %[[a12]] : (!fir.box<!fir.heap<!fir.array<?x?xi32>>>) -> !fir.heap<!fir.array<?x?xi32>>
   ! CHECK:  fir.freemem %[[a15:.*]]
-  end subroutine
-  
+end subroutine
+
+! CHECK-LABEL: func.func @_QMspread_modPspread_test_polymorphic_source(
+! CHECK-SAME: %[[arg0:.*]]: !fir.ref<!fir.class<!fir.ptr<!fir.array<?x?xnone>>>> {fir.bindc_name = "p"}) {
+subroutine spread_test_polymorphic_source(p)
+  class(*), pointer :: p(:,:)
+  class(*), allocatable :: r(:,:,:)
+  r = spread(p(:,::2), dim=1, ncopies=2)
+! CHECK: %[[res:.*]] = fir.alloca !fir.class<!fir.heap<!fir.array<?x?x?xnone>>>
+! CHECK: %[[load_p:.*]] = fir.load %[[arg0]] : !fir.ref<!fir.class<!fir.ptr<!fir.array<?x?xnone>>>>
+! CHECK: %[[source_box:.*]] = fir.rebox %[[load_p]](%{{.*}}) [%{{.*}}] : (!fir.class<!fir.ptr<!fir.array<?x?xnone>>>, !fir.shift<2>, !fir.slice<2>) -> !fir.class<!fir.array<?x?xnone>>
+! CHECK: %[[embox:.*]] = fir.embox %{{.*}}(%{{.*}}) source_box %[[source_box]] : (!fir.heap<!fir.array<?x?x?xnone>>, !fir.shape<3>, !fir.class<!fir.array<?x?xnone>>) -> !fir.class<!fir.heap<!fir.array<?x?x?xnone>>>
+! CHECK: fir.store %[[embox]] to %[[res]] : !fir.ref<!fir.class<!fir.heap<!fir.array<?x?x?xnone>>>>
+! CHECK: %[[res_box_none:.*]] = fir.convert %[[res]] : (!fir.ref<!fir.class<!fir.heap<!fir.array<?x?x?xnone>>>>) -> !fir.ref<!fir.box<none>>
+! CHECK: %[[source_box_none:.*]] = fir.convert %[[source_box]] : (!fir.class<!fir.array<?x?xnone>>) -> !fir.box<none>
+! CHECK: %{{.*}} = fir.call @_FortranASpread(%[[res_box_none]], %[[source_box_none]], %{{.*}}, %{{.*}}, %{{.*}}, %{{.*}}) fastmath<contract> : (!fir.ref<!fir.box<none>>, !fir.box<none>, i32, i64, !fir.ref<i8>, i32) -> none
+
+end subroutine
+
+end module