Skip to content

Commit

Permalink
[Flang2] Fix duplicate TBAA type systems across modules
Browse files Browse the repository at this point in the history
    In Flang, functions within the same module are assigned unique TBAA type system IDs based on their order, but functions in different modules can unintentionally receive the same ID, leading to incorrect non-aliasing results. This commit resolves the issue by appending a hash of the module name to each function type system metadata, ensuring unique type systems across modules and preventing aliasing errors.
  • Loading branch information
1997alireza committed Nov 6, 2024
1 parent 2b33e62 commit 53ccbcf
Show file tree
Hide file tree
Showing 5 changed files with 71 additions and 1 deletion.
24 changes: 24 additions & 0 deletions test/llvm_ir_correct/tbaa_multimod_01_callee.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
! A part of the test provided in tbaa_multimod_01_caller.f90
! Empty RUN and CHECK to prevent error
! RUN: echo "NoCheck" | FileCheck %s
! CHECK: NoCheck
subroutine modify1(arr)
implicit none
real, intent(inout) :: arr(:)
arr(0) = arr(0) + 0.5
end subroutine modify1

subroutine modify2(arr)
implicit none
real, intent(inout) :: arr(:)
arr(2) = arr(2) + 1.5
end subroutine modify2

subroutine printout(arr)
implicit none
real, intent(in) :: arr(:)
integer :: i
do i = 1, size(arr)
print arr(i), " "
enddo
end subroutine printout
18 changes: 18 additions & 0 deletions test/llvm_ir_correct/tbaa_multimod_01_caller.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
! This test contians two files, tbaa_multimod_01_caller.f90 and tbaa_multimod_01_callee.f90
! RUN: %flang -Wl,-mllvm,-aa-trace -fuse-ld=lld -flto=full -O3 %s %S/tbaa_multimod_01_callee.f90 -o - 2>&1 1>- | FileCheck %s
! CHECK-NOT: End ptr getelementptr (%struct.BSS1, ptr @.BSS1, i64 -1, i32 0, i64 16) @ LocationSize::precise(16), ptr inttoptr (i64 56 to ptr) @ LocationSize::precise(8) = NoAlias

program main
implicit none
integer, parameter :: n = 5
real :: arr(n)
integer :: i
i = 0
arr = 3.2
arr(i) = 4
call modify1(arr)
call modify2(arr)

arr(i) = arr(i) + 2.5
call printout(arr)
end program main
12 changes: 12 additions & 0 deletions test/llvm_ir_correct/tbaa_multimod_02_callee.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
! A part of the test provided in tbaa_multimod_02_caller.f90
! Empty RUN and CHECK to prevent error
! RUN: echo "NoCheck" | FileCheck %s
! CHECK: NoCheck
subroutine to_load(arr)
implicit none
real, intent(inout) :: arr(:)
real :: var
var = arr(0)
var = var * 2
print var
end subroutine to_load
14 changes: 14 additions & 0 deletions test/llvm_ir_correct/tbaa_multimod_02_caller.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
! This test contians two files, tbaa_multimod_02_caller.f90 and tbaa_multimod_02_callee.f90
! RUN: %flang -Wl,-mllvm,-aa-trace -fuse-ld=lld -flto=full -O3 %s %S/tbaa_multimod_02_callee.f90 -o - 2>&1 1>- | FileCheck %s
! CHECK-NOT: End ptr getelementptr inbounds (%struct.BSS1, ptr @.BSS1, i64 0, i32 0, i64 16) @ LocationSize::precise(4), ptr inttoptr (i64 56 to ptr) @ LocationSize::precise(8) = NoAlias

program main
implicit none
integer, parameter :: n = 5
real :: arr(n)
integer :: i
arr = 1
call to_load(arr)
arr(0) = 4
call to_load(arr)
end program main
4 changes: 3 additions & 1 deletion tools/flang2/flang2exe/cgmain.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,8 @@
#include "symfun.h"
#include "ilidir.h"
#include "fdirect.h"
#include <string>
#include <hash_map>

#ifdef OMP_OFFLOAD_LLVM
#include "ompaccel.h"
Expand Down Expand Up @@ -2643,7 +2645,7 @@ get_omnipotent_pointer(LL_Module *module)
const char *baseName = "Flang FAA";
const char *const omniName = "unlimited ptr";
const char *const unObjName = "unref ptr";
snprintf(baseBuff, 32, "%s %x", baseName, funcId);
snprintf(baseBuff, 32, "%s %zx %x", baseName, std::hash<std::string>{}(current_module->module_name), funcId);
s0 = ll_get_md_string(module, baseBuff);
r0 = ll_get_md_node(module, LL_PlainMDNode, &s0, 1);
a[0] = ll_get_md_string(module, unObjName);
Expand Down

0 comments on commit 53ccbcf

Please sign in to comment.