Skip to content

Commit

Permalink
[flang2] Generate loads of complex variables with correct alignment
Browse files Browse the repository at this point in the history
flang2 calls the function make_load() to create various types of load
instructions in the LLVM IR output. The function accepts a "flags" argument
of type LL_InstrListFlags which should encode the alignment of the load,
among other things. Apparently, for the IL_LDSCMPLX, IL_LDDCMPLX, and
IL_LDQCMPLX opcodes, the flags had never been computed correctly. This
patch makes such loads consistent with loads of other types, and also adds
a test case.
  • Loading branch information
bryanpkc committed Jul 24, 2024
1 parent 3de1cba commit 8e65ce5
Show file tree
Hide file tree
Showing 2 changed files with 52 additions and 5 deletions.
50 changes: 50 additions & 0 deletions test/llvm_ir_correct/load-alignment.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,50 @@
! Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
! See https://llvm.org/LICENSE.txt for license information.
! SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception

! Check that load instructions are emitted with correct alignment.

! RUN: %flang -S -emit-flang-llvm %s -o %t.ll
! RUN: FileCheck %s < %t.ll

! CHECK: load i8, ptr %in1, align 1
function bpass(in1)
logical(kind=1) :: in1, bpass
bpass = in1
end function bpass

! CHECK: load i32, ptr %in1, align 4
function ipass(in1)
integer(kind=4) :: in1, ipass
ipass = in1
end function ipass

! CHECK: load i64, ptr %in1, align 8
function lpass(in1)
integer(kind=8) :: in1, lpass
lpass = in1
end function lpass

! CHECK: load float, ptr %in1, align 4
function fpass(in1)
real(kind=4) :: in1, fpass
fpass = in1
end function fpass

! CHECK: load double, ptr %in1, align 8
function dpass(in1)
real(kind=8) :: in1, dpass
dpass = in1
end function dpass

! CHECK: load <{float, float}>, ptr %in1, align 8
function cfpass(in1)
complex(kind=4) :: in1, cfpass
cfpass = in1
end function cfpass

! CHECK: load <{double, double}>, ptr %in1, align 16
function cdpass(in1)
complex(kind=8) :: in1, cdpass
cdpass = in1
end function cdpass
7 changes: 2 additions & 5 deletions tools/flang2/flang2exe/cgmain.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -8572,15 +8572,12 @@ gen_llvm_expr(int ilix, LL_Type *expected_type)
ld_ili = ILI_OPND(ilix, 1);
nme_ili = ILI_OPND(ilix, 2);
msz = (MSZ)ILI_OPND(ilix, 3);
flags = opc == IL_LDSCMPLX ? DT_CMPLX
#ifdef TARGET_SUPPORTS_QUADFP
: opc == IL_LDQCMPLX ? DT_QCMPLX
#endif
: DT_DCMPLX;
operand = gen_address_operand(ld_ili, nme_ili, false,
make_ptr_lltype(expected_type), (MSZ)-1);
assert(operand->ll_type->data_type == LL_PTR,
"Invalid operand for cmplx load", ilix, ERR_Fatal);
flags =
ldst_instr_flags_from_dtype_nme(msz_dtype(msz), nme_ili);
operand =
make_load(ilix, operand, operand->ll_type->sub_types[0], msz, flags);
} break;
Expand Down

0 comments on commit 8e65ce5

Please sign in to comment.