diff --git a/flang/test/Lower/equivalence-1.f90 b/flang/test/Lower/equivalence-1.f90 new file mode 100644 index 0000000000000..17b10eaa18ecb --- /dev/null +++ b/flang/test/Lower/equivalence-1.f90 @@ -0,0 +1,68 @@ +! RUN: bbc -o - %s | FileCheck %s + +! CHECK-LABEL: func @_QPs1 +SUBROUTINE s1 + INTEGER i + REAL r + ! CHECK: = fir.alloca !fir.array<4xi8> {uniq_name = "_QFs1Ei"} + EQUIVALENCE (r,i) + ! CHECK: %[[coor:.*]] = fir.coordinate_of %{{.*}}, %{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK: %[[iloc:.*]] = fir.convert %[[coor]] : (!fir.ref) -> !fir.ptr + ! CHECK-DAG: fir.store %{{.*}} to %[[iloc]] : !fir.ptr + i = 4 + ! CHECK-DAG: %[[floc:.*]] = fir.convert %[[coor]] : (!fir.ref) -> !fir.ptr + ! CHECK: %[[ld:.*]] = fir.load %[[floc]] : !fir.ptr + PRINT *, r +END SUBROUTINE s1 + +! CHECK-LABEL: func @_QPs2 +SUBROUTINE s2 + INTEGER i(10) + REAL r(10) + ! CHECK: %[[arr:.*]] = fir.alloca !fir.array<48xi8> + EQUIVALENCE (r(3),i(5)) + ! CHECK: %[[iarr:.*]] = fir.convert %{{.*}} : (!fir.ref) -> !fir.ptr> + ! CHECK: %[[foff:.*]] = fir.coordinate_of %[[arr]], %{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK: %[[farr:.*]] = fir.convert %[[foff]] : (!fir.ref) -> !fir.ptr> + ! CHECK: %[[ia:.*]] = fir.coordinate_of %[[iarr]], %{{.*}} : (!fir.ptr>, i64) -> !fir.ref + ! CHECK: fir.store %{{.*}} to %[[ia]] : !fir.ref + i(5) = 18 + ! CHECK: %[[fld:.*]] = fir.coordinate_of %[[farr]], %{{.*}} : (!fir.ptr>, i64) -> !fir.ref + ! CHECK: = fir.load %[[fld]] : !fir.ref + PRINT *, r(3) +END SUBROUTINE s2 + +! CHECK-LABEL: func @_QPs3 +SUBROUTINE s3 + REAL r(10) + TYPE t + SEQUENCE + REAL r(10) + END TYPE t + TYPE(t) x + ! CHECK: %[[group:.*]] = fir.alloca !fir.array<40xi8> + EQUIVALENCE (r,x) + ! CHECK: %[[coor:.*]] = fir.coordinate_of %[[group]], %c0 : (!fir.ref>, index) -> !fir.ref + ! CHECK: %[[rloc:.*]] = fir.convert %[[coor]] : (!fir.ref) -> !fir.ptr> + ! CHECK: %[[xloc:.*]] = fir.convert %[[coor]] : (!fir.ref) -> !fir.ptr}>> + ! CHECK: %[[fidx:.*]] = fir.field_index r, !fir.type<_QFs3Tt{r:!fir.array<10xf32>}> + ! CHECK: %[[xrloc:.*]] = fir.coordinate_of %[[xloc]], %[[fidx]] : + ! CHECK: %[[v1loc:.*]] = fir.coordinate_of %[[xrloc]], %c8_i64 : (!fir.ref>, i64) -> !fir.ref + ! CHECK: fir.store %{{.*}} to %[[v1loc]] : !fir.ref + x%r(9) = 9.0 + ! CHECK: %[[v2loc:.*]] = fir.coordinate_of %[[rloc]], %c8_i64 : (!fir.ptr>, i64) -> !fir.ref + ! CHECK: %{{.*}} = fir.load %[[v2loc]] : !fir.ref + PRINT *, r(9) +END SUBROUTINE s3 + +! test that equivalence in main program containing arrays are placed in global memory. +! CHECK: fir.global internal @_QFEa : !fir.array<400000000xi8> + integer :: a, b(100000000) + equivalence (a, b) + b(1) = 42 + print *, a + + CALL s1 + CALL s2 + CALL s3 +END diff --git a/flang/test/Lower/equivalence-2.f90 b/flang/test/Lower/equivalence-2.f90 new file mode 100644 index 0000000000000..476a9a43c5bc0 --- /dev/null +++ b/flang/test/Lower/equivalence-2.f90 @@ -0,0 +1,99 @@ +! RUN: bbc -emit-fir -o - %s | FileCheck %s + +! Check more advanced equivalence cases + +! Several set of local and global equivalences in the same scope +! CHECK-LABEL: @_QPtest_eq_sets +subroutine test_eq_sets + DIMENSION Al(4), Bl(4) + EQUIVALENCE (Al(1), Bl(2)) + ! CHECK-DAG: %[[albl:.*]] = fir.alloca !fir.array<20xi8> + ! CHECK-DAG: %[[alAddr:.*]] = fir.coordinate_of %[[albl]], %c4{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[al:.*]] = fir.convert %[[alAddr]] : (!fir.ref) -> !fir.ptr> + ! CHECK-DAG: %[[blAddr:.*]] = fir.coordinate_of %[[albl]], %c0{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[bl:.*]] = fir.convert %[[blAddr]] : (!fir.ref) -> !fir.ptr> + + + DIMENSION Il(2), Xl(2) + EQUIVALENCE (Il(2), Xl(1)) + ! CHECK-DAG: %[[ilxl:.*]] = fir.alloca !fir.array<12xi8> + ! CHECK-DAG: %[[ilAddr:.*]] = fir.coordinate_of %[[ilxl]], %c0{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[il:.*]] = fir.convert %[[ilAddr]] : (!fir.ref) -> !fir.ptr> + ! CHECK-DAG: %[[xlAddr:.*]] = fir.coordinate_of %[[ilxl]], %c4{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[xl:.*]] = fir.convert %[[xlAddr]] : (!fir.ref) -> !fir.ptr> + + DIMENSION Ag(2), Bg(2) + SAVE Ag, Bg + EQUIVALENCE (Ag(1), Bg(2)) + ! CHECK-DAG: %[[agbg:.*]] = fir.address_of(@_QFtest_eq_setsEag) : !fir.ref> + ! CHECK-DAG: %[[agAddr:.*]] = fir.coordinate_of %[[agbg]], %c4{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[ag:.*]] = fir.convert %[[agAddr]] : (!fir.ref) -> !fir.ptr> + ! CHECK-DAG: %[[bgAddr:.*]] = fir.coordinate_of %[[agbg]], %c0{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[bg:.*]] = fir.convert %[[bgAddr]] : (!fir.ref) -> !fir.ptr> + + DIMENSION Ig(2), Xg(2) + SAVE Ig, Xg + EQUIVALENCE (Ig(1), Xg(1)) + ! CHECK-DAG: %[[igxg:.*]] = fir.address_of(@_QFtest_eq_setsEig) : !fir.ref> + ! CHECK-DAG: %[[igOffset:.*]] = arith.constant 0 : index + ! CHECK-DAG: %[[igAddr:.*]] = fir.coordinate_of %[[igxg]], %c0{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[ig:.*]] = fir.convert %[[igAddr]] : (!fir.ref) -> !fir.ptr> + ! CHECK-DAG: %[[xgAddr:.*]] = fir.coordinate_of %[[igxg]], %c0{{.*}} : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[xg:.*]] = fir.convert %[[xgAddr]] : (!fir.ref) -> !fir.ptr> + + ! CHECK: %[[alCast:.*]] = fir.convert %[[al]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[blCast:.*]] = fir.convert %[[bl]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[ilCast:.*]] = fir.convert %[[il]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[xlCast:.*]] = fir.convert %[[xl]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[agCast:.*]] = fir.convert %[[ag]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[bgCast:.*]] = fir.convert %[[bg]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[xgCast:.*]] = fir.convert %[[xg]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[igCast:.*]] = fir.convert %[[ig]] : (!fir.ptr>) -> !fir.ref> + + call fooc(Al, Bl, Il, Xl, Ag, Bg, Xg, Ig) + ! CHECK: fir.call @_QPfooc(%[[alCast]], %[[blCast]], %[[ilCast]], %[[xlCast]], %[[agCast]], %[[bgCast]], %[[xgCast]], %[[igCast]]) + +end subroutine + + +! Mixing global equivalence and entry +! CHECK-LABEL: @_QPeq_and_entry_foo() +subroutine eq_and_entry_foo + SAVE x, i + DIMENSION :: x(2) + EQUIVALENCE (x(2), i) + call foo1(x, i) + ! CHECK: %[[xi:.*]] = fir.address_of(@_QFeq_and_entry_fooEi) : !fir.ref> + + ! CHECK-DAG: %[[iOffset:.*]] = arith.constant 4 : index + ! CHECK-DAG: %[[iAddr:.*]] = fir.coordinate_of %[[xi]], %[[iOffset]] : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[i:.*]] = fir.convert %[[iAddr]] : (!fir.ref) -> !fir.ptr + + ! CHECK-DAG: %[[xOffset:.*]] = arith.constant 0 : index + ! CHECK-DAG: %[[xAddr:.*]] = fir.coordinate_of %[[xi]], %[[xOffset]] : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[x:.*]] = fir.convert %[[xAddr]] : (!fir.ref) -> !fir.ptr> + call foo2(x, i) + ! CHECK: %[[xCast:.*]] = fir.convert %[[x]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[iCast:.*]] = fir.convert %[[i]] : (!fir.ptr) -> !fir.ref + ! CHECK: fir.call @_QPfoo1(%[[xCast]], %[[iCast]]) : (!fir.ref>, !fir.ref) -> () + entry eq_and_entry_bar + call foo2(x, i) + ! CHECK: %[[xCast2:.*]] = fir.convert %[[x]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[iCast2:.*]] = fir.convert %[[i]] : (!fir.ptr) -> !fir.ref + ! CHECK: fir.call @_QPfoo2(%[[xCast2]], %[[iCast2]]) : (!fir.ref>, !fir.ref) -> () +end + +! CHECK-LABEL: @_QPeq_and_entry_bar() + ! CHECK: %[[xi:.*]] = fir.address_of(@_QFeq_and_entry_fooEi) : !fir.ref> + + ! CHECK-DAG: %[[iOffset:.*]] = arith.constant 4 : index + ! CHECK-DAG: %[[iAddr:.*]] = fir.coordinate_of %[[xi]], %[[iOffset]] : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[i:.*]] = fir.convert %[[iAddr]] : (!fir.ref) -> !fir.ptr + + ! CHECK-DAG: %[[xOffset:.*]] = arith.constant 0 : index + ! CHECK-DAG: %[[xAddr:.*]] = fir.coordinate_of %[[xi]], %[[xOffset]] : (!fir.ref>, index) -> !fir.ref + ! CHECK-DAG: %[[x:.*]] = fir.convert %[[xAddr]] : (!fir.ref) -> !fir.ptr> + ! CHECK-NOT: fir.call @_QPfoo1 + ! CHECK: %[[xCast:.*]] = fir.convert %[[x]] : (!fir.ptr>) -> !fir.ref> + ! CHECK: %[[iCast:.*]] = fir.convert %[[i]] : (!fir.ptr) -> !fir.ref + ! CHECK: fir.call @_QPfoo2(%[[xCast]], %[[iCast]]) : (!fir.ref>, !fir.ref) -> () diff --git a/flang/test/Lower/equivalence-static-init.f90 b/flang/test/Lower/equivalence-static-init.f90 new file mode 100644 index 0000000000000..6b4b0ccff4c5e --- /dev/null +++ b/flang/test/Lower/equivalence-static-init.f90 @@ -0,0 +1,30 @@ +! RUN: bbc -emit-fir -o - %s | FileCheck %s + +! Test explicit static initialization of equivalence storage + +module module_without_init + real :: x(2) + integer :: i(2) + equivalence(i(1), x) +end module +! CHECK-LABEL: fir.global @_QMmodule_without_initEi : !fir.array<8xi8> { + ! CHECK: %0 = fir.undefined !fir.array<8xi8> + ! CHECK: fir.has_value %0 : !fir.array<8xi8> +! CHECK} + + +subroutine test_eqv_init + integer, save :: link(3) + integer :: i = 5 + integer :: j = 7 + equivalence (j, link(1)) + equivalence (i, link(3)) +end subroutine + +! CHECK-LABEL: fir.global internal @_QFtest_eqv_initEi : !fir.array<3xi32> { + ! CHECK: %[[VAL_1:.*]] = fir.undefined !fir.array<3xi32> + ! CHECK: %[[VAL_2:.*]] = fir.insert_value %0, %c7{{.*}}, [0 : index] : (!fir.array<3xi32>, i32) -> !fir.array<3xi32> + ! CHECK: %[[VAL_3:.*]] = fir.insert_value %1, %c0{{.*}}, [1 : index] : (!fir.array<3xi32>, i32) -> !fir.array<3xi32> + ! CHECK: %[[VAL_4:.*]] = fir.insert_value %2, %c5{{.*}}, [2 : index] : (!fir.array<3xi32>, i32) -> !fir.array<3xi32> + ! CHECK: fir.has_value %[[VAL_4]] : !fir.array<3xi32> +! CHECK: }