Skip to content

Commit fc62659

Browse files
1997alirezabryanpkc
authored andcommitted
[Flang2] Fix duplicate TBAA type systems across modules
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.
1 parent 2b33e62 commit fc62659

File tree

5 files changed

+90
-18
lines changed

5 files changed

+90
-18
lines changed
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
! A part of the test provided in tbaa_multimod_01.f90
2+
3+
subroutine modify1(arr)
4+
implicit none
5+
real, intent(inout) :: arr(:)
6+
arr(0) = arr(0) + 0.5
7+
end subroutine modify1
8+
9+
subroutine modify2(arr)
10+
implicit none
11+
real, intent(inout) :: arr(:)
12+
arr(2) = arr(2) + 1.5
13+
end subroutine modify2
14+
15+
subroutine printout(arr)
16+
implicit none
17+
real, intent(in) :: arr(:)
18+
integer :: i
19+
do i = 1, size(arr)
20+
print arr(i), " "
21+
enddo
22+
end subroutine printout
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
! A part of the test provided in tbaa_multimod_02.f90
2+
3+
subroutine to_load(arr)
4+
implicit none
5+
real, intent(inout) :: arr(:)
6+
real :: var
7+
var = arr(0)
8+
var = var * 2
9+
print var
10+
end subroutine to_load
Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,21 @@
1+
! This test contians two files, tbaa_multimod_01.f90 and Inputs/tbaa_multimod_01_input.f90
2+
! RUN: %flang -emit-llvm -c -O3 %s -o %t.bc
3+
! RUN: %flang -emit-llvm -c -O3 %S/Inputs/tbaa_multimod_01_input.f90 -o %t2.bc
4+
! RUN: llvm-link -o %t3.bc %t.bc %t2.bc
5+
! RUN: opt -aa-trace -O3 -o - %t3.bc 2>&1 | FileCheck %s
6+
! 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
7+
8+
program main
9+
implicit none
10+
integer, parameter :: n = 5
11+
real :: arr(n)
12+
integer :: i
13+
i = 0
14+
arr = 3.2
15+
arr(i) = 4
16+
call modify1(arr)
17+
call modify2(arr)
18+
19+
arr(i) = arr(i) + 2.5
20+
call printout(arr)
21+
end program main
Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
! This test contians two files, tbaa_multimod_02.f90 and Inputs/tbaa_multimod_02_input.f90
2+
! RUN: %flang -emit-llvm -c -O3 %s -o %t.bc
3+
! RUN: %flang -emit-llvm -c -O3 %S/Inputs/tbaa_multimod_02_input.f90 -o %t2.bc
4+
! RUN: llvm-link -o %t3.bc %t.bc %t2.bc
5+
! RUN: opt -aa-trace -O3 -o - %t3.bc 2>&1 | FileCheck %s
6+
! 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
7+
8+
program main
9+
implicit none
10+
integer, parameter :: n = 5
11+
real :: arr(n)
12+
integer :: i
13+
arr = 1
14+
call to_load(arr)
15+
arr(0) = 4
16+
call to_load(arr)
17+
end program main

tools/flang2/flang2exe/cgmain.cpp

Lines changed: 20 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -10,29 +10,30 @@
1010
\brief Main source module to translate into LLVM
1111
*/
1212

13+
#include <stdio.h>
14+
#include <stdlib.h>
15+
#include <string.h>
16+
#include <string>
1317
#include "cgmain.h"
18+
#include "cg.h"
19+
#include "dinit.h"
1420
#include "dtypeutl.h"
15-
#include "ll_ftn.h"
16-
#include "exp_rte.h"
1721
#include "error.h"
18-
#include "machreg.h"
19-
#include "dinit.h"
20-
#include "cg.h"
21-
#include "mach.h"
22+
#include "exp_rte.h"
23+
#include "expand.h"
2224
#include "fih.h"
23-
#include "pd.h"
24-
#include "llutil.h"
25-
#include "lldebug.h"
2625
#include "go.h"
27-
#include "sharedefs.h"
28-
#include <stdlib.h>
29-
#include <stdio.h>
30-
#include <string.h>
31-
#include "llassem.h"
26+
#include "ll_ftn.h"
3227
#include "ll_write.h"
33-
#include "expand.h"
34-
#include "outliner.h"
28+
#include "llassem.h"
29+
#include "lldebug.h"
30+
#include "llutil.h"
31+
#include "mach.h"
32+
#include "machreg.h"
3533
#include "mth.h"
34+
#include "outliner.h"
35+
#include "pd.h"
36+
#include "sharedefs.h"
3637
#if defined(SOCPTRG)
3738
#include "soc.h"
3839
#endif
@@ -2639,11 +2640,12 @@ get_omnipotent_pointer(LL_Module *module)
26392640
LL_MDRef s0;
26402641
LL_MDRef r0;
26412642
LL_MDRef a[3];
2642-
char baseBuff[32];
2643+
char baseBuff[64];
26432644
const char *baseName = "Flang FAA";
26442645
const char *const omniName = "unlimited ptr";
26452646
const char *const unObjName = "unref ptr";
2646-
snprintf(baseBuff, 32, "%s %x", baseName, funcId);
2647+
snprintf(baseBuff, 64, "%s %zx %x", baseName,
2648+
std::hash<std::string>{}(current_module->module_name), funcId);
26472649
s0 = ll_get_md_string(module, baseBuff);
26482650
r0 = ll_get_md_node(module, LL_PlainMDNode, &s0, 1);
26492651
a[0] = ll_get_md_string(module, unObjName);

0 commit comments

Comments
 (0)