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 Dec 3, 2024
1 parent 2b33e62 commit 96619fa
Show file tree
Hide file tree
Showing 5 changed files with 95 additions and 17 deletions.
21 changes: 21 additions & 0 deletions test/llvm_ir_correct/tbaa_multimod_01.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
! This test contians two files, tbaa_multimod_01.f90 and tbaa_multimod_01_input.f90
! RUN: %flang -emit-llvm -c -O3 %s -o %t.bc
! RUN: %flang -emit-llvm -c -O3 %S/tbaa_multimod_01_input.f90 -o %t2.bc
! RUN: llvm-link -o %t3.bc %t.bc %t2.bc
! RUN: opt -aa-trace -O3 -o - %t3.bc 2>&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
25 changes: 25 additions & 0 deletions test/llvm_ir_correct/tbaa_multimod_01_input.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
! A part of the test provided in tbaa_multimod_01.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
17 changes: 17 additions & 0 deletions test/llvm_ir_correct/tbaa_multimod_02.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
! This test contians two files, tbaa_multimod_02.f90 and tbaa_multimod_02_input.f90
! RUN: %flang -emit-llvm -c -O3 %s -o %t.bc
! RUN: %flang -emit-llvm -c -O3 %S/tbaa_multimod_02_input.f90 -o %t2.bc
! RUN: llvm-link -o %t3.bc %t.bc %t2.bc
! RUN: opt -aa-trace -O3 -o - %t3.bc 2>&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
13 changes: 13 additions & 0 deletions test/llvm_ir_correct/tbaa_multimod_02_input.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
! A part of the test provided in tbaa_multimod_02.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
36 changes: 19 additions & 17 deletions tools/flang2/flang2exe/cgmain.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -10,29 +10,30 @@
\brief Main source module to translate into LLVM
*/

#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <string>
#include "cgmain.h"
#include "cg.h"
#include "dinit.h"
#include "dtypeutl.h"
#include "ll_ftn.h"
#include "exp_rte.h"
#include "error.h"
#include "machreg.h"
#include "dinit.h"
#include "cg.h"
#include "mach.h"
#include "exp_rte.h"
#include "expand.h"
#include "fih.h"
#include "pd.h"
#include "llutil.h"
#include "lldebug.h"
#include "go.h"
#include "sharedefs.h"
#include <stdlib.h>
#include <stdio.h>
#include <string.h>
#include "llassem.h"
#include "ll_ftn.h"
#include "ll_write.h"
#include "expand.h"
#include "outliner.h"
#include "llassem.h"
#include "lldebug.h"
#include "llutil.h"
#include "mach.h"
#include "machreg.h"
#include "mth.h"
#include "outliner.h"
#include "pd.h"
#include "sharedefs.h"
#if defined(SOCPTRG)
#include "soc.h"
#endif
Expand Down Expand Up @@ -2643,7 +2644,8 @@ 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 96619fa

Please sign in to comment.