diff --git a/test/directives/align_array_variable.f90 b/test/directives/align_array_variable.f90 new file mode 100644 index 00000000000..d1dcd16d989 --- /dev/null +++ b/test/directives/align_array_variable.f90 @@ -0,0 +1,140 @@ +! RUN: %flang -O0 -S -emit-llvm %s -o - | FileCheck %s + +! CHECK: %struct[[BLOCK1:\.BSS[0-9]+]] = type <{ [356 x i8] }> +! CHECK: %struct[[BLOCK2:\.BSS[0-9]+]] = type <{ [612 x i8] }> +! CHECK: %struct[[BLOCK3:\.BSS[0-9]+]] = type <{ [1124 x i8] }> +! CHECK: %struct[[BLOCK4:\.BSS[0-9]+]] = type <{ [2148 x i8] }> +! CHECK: %struct[[BLOCK5:_module_align_array_[0-9]+_]] = type <{ [228 x i8] }> +! CHECK: @[[BLOCK1]] = internal global %struct[[BLOCK1]] zeroinitializer, align 256 +! CHECK: @[[BLOCK2]] = internal global %struct[[BLOCK2]] zeroinitializer, align 512 +! CHECK: @[[BLOCK3]] = internal global %struct[[BLOCK3]] zeroinitializer, align 1024 +! CHECK: @[[BLOCK4]] = internal global %struct[[BLOCK4]] zeroinitializer, align 2048 +! CHECK: @[[BLOCK5]] = common global %struct[[BLOCK5]] zeroinitializer, align 128 + +module module_align_array +implicit none + + !DIR$ ALIGN 128 + integer, dimension (5,5) :: v1, v2 + + interface + module subroutine module_interface_subroutine() + end subroutine module_interface_subroutine + end interface + +end module module_align_array + +submodule (module_align_array) submodule_align_array + + contains + module subroutine module_interface_subroutine() + + !DIR$ ALIGN 256 + integer, dimension (5,5) :: v3, v4 + + v3(1, 1) = 101 +! CHECK: store i32 101, ptr @[[BLOCK1]], align + + v3(5, 5) = 102 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK1]], i64 96 +! CHECK: store i32 102, ptr %[[TEMP]], align + + v4(1, 1) = 103 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK1]], i64 256 +! CHECK: store i32 103, ptr %[[TEMP]], align + + v4(5, 5) = 104 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK1]], i64 352 +! CHECK: store i32 104, ptr %[[TEMP]], align + + end subroutine module_interface_subroutine +end submodule submodule_align_array + + + +program align +use module_align_array +implicit none + + !DIR$ ALIGN 512 + integer, dimension (5,5) :: v5, v6 + + v5(1, 1) = 201 +! CHECK: store i32 201, ptr @[[BLOCK2]], align + + v5(5, 5) = 202 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK2]], i64 96 +! CHECK: store i32 202, ptr %[[TEMP]], align + + v6(1, 1) = 203 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK2]], i64 512 +! CHECK: store i32 203, ptr %[[TEMP]], align + + v6(5, 5) = 204 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK2]], i64 608 +! CHECK: store i32 204, ptr %[[TEMP]], align + + v1(1, 1) = 81 +! CHECK: store i32 81, ptr @[[BLOCK5]], align + + v1(5, 5) = 82 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK5]], i64 96 +! CHECK: store i32 82, ptr %[[TEMP]], align + + v2(1, 1) = 83 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK5]], i64 128 +! CHECK: store i32 83, ptr %[[TEMP]], align + + v2(5, 5) = 84 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK5]], i64 224 +! CHECK: store i32 84, ptr %[[TEMP]], align + +end program align + + +subroutine subroutine_align() + + !DIR$ ALIGN 1024 + integer, dimension (5,5) :: v7, v8 + + v7(1, 1) = 401 +! CHECK: store i32 401, ptr @[[BLOCK3]], align + + v7(5, 5) = 402 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK3]], i64 96 +! CHECK: store i32 402, ptr %[[TEMP]], align + + v8(1, 1) = 403 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK3]], i64 1024 +! CHECK: store i32 403, ptr %[[TEMP]], align + + v8(5, 5) = 404 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK3]], i64 1120 +! CHECK: store i32 404, ptr %[[TEMP]], align + + return +end subroutine subroutine_align + + +function function_align() + + !DIR$ ALIGN 2048 + integer, dimension (5,5) :: v9, v10 + + v9(1, 1) = 801 +! CHECK: store i32 801, ptr @[[BLOCK4]], align + + v9(5, 5) = 802 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK4]], i64 96 +! CHECK: store i32 802, ptr %[[TEMP]], align + + v10(1, 1) = 803 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK4]], i64 2048 +! CHECK: store i32 803, ptr %[[TEMP]], align + + v10(5, 5) = 804 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK4]], i64 2144 +! CHECK: store i32 804, ptr %[[TEMP]], align + + return +end function function_align diff --git a/test/directives/align_character_variable.f90 b/test/directives/align_character_variable.f90 new file mode 100644 index 00000000000..907b670a77f --- /dev/null +++ b/test/directives/align_character_variable.f90 @@ -0,0 +1,97 @@ +! RUN: %flang -O0 -S -emit-llvm %s -o - | FileCheck %s + +! CHECK: %struct[[BLOCK1:\.STATICS[0-9]+]] = type <{ [10 x i8] } +! CHECK: %struct[[BLOCK2:\.STATICS[0-9]+]] = type <{ [10 x i8] } +! CHECK: %struct[[BLOCK3:\.STATICS[0-9]+]] = type <{ [10 x i8] } +! CHECK: %struct[[BLOCK4:\.STATICS[0-9]+]] = type <{ [10 x i8] } +! CHECK: %struct[[BLOCK5:_module_align_character_[0-9]+_]] = type <{ [10 x i8] } +! CHECK: %struct[[BLOCK6:_module_align_character_[0-9]+_]] = type <{ [10 x i8] } +! CHECK: @[[BLOCK1]] = internal global %struct[[BLOCK1]] <{{[^>]+}}>, align 256 +! CHECK: @[[BLOCK2]] = internal global %struct[[BLOCK2]] <{{[^>]+}}>, align 512 +! CHECK: @[[BLOCK3]] = internal global %struct[[BLOCK3]] <{{[^>]+}}>, align 1024 +! CHECK: @[[BLOCK4]] = internal global %struct[[BLOCK4]] <{{[^>]+}}>, align 2048 +! CHECK: @[[BLOCK5]] = common global %struct[[BLOCK5]] zeroinitializer, align 128 +! CHECK: @[[BLOCK6]] = global %struct[[BLOCK6]] <{{[^>]+}}>, align 128 + +module module_align_character +implicit none + + !DIR$ ALIGN 128 + character(len=10) :: v1, v2 = "128" + + interface + module subroutine module_interface_subroutine() + end subroutine module_interface_subroutine + end interface + +end module module_align_character + +submodule (module_align_character) submodule_align_character + + contains + module subroutine module_interface_subroutine() + + !DIR$ ALIGN 256 + character(len=10) :: v3, v4 = "256" +! CHECK: %[[V3:v3_[0-9]+]] = alloca [10 x i8], align 256 + + v3 = "101" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr %[[V3]], align + + v4 = "102" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr @[[BLOCK1]], align + + end subroutine module_interface_subroutine +end submodule submodule_align_character + +program align +use module_align_character +implicit none + + !DIR$ ALIGN 512 + character(len=10) :: v5, v6 = "512" +! CHECK: %[[V5:v5_[0-9]+]] = alloca [10 x i8], align 512 + + v5 = "201" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr %[[V5]], align + + v6 = "202" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr @[[BLOCK2]], align + + v1 = "81" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr @[[BLOCK5]], align + + v2 = "82" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr @[[BLOCK6]], align + +end program align + +subroutine subroutine_align() + + !DIR$ ALIGN 1024 + character(len=10) :: v7, v8 = "1024" +! CHECK: %[[V7:v7_[0-9]+]] = alloca [10 x i8], align 1024 + + v7 = "401" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr %[[V7]], align + + v8 = "402" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr @[[BLOCK3]], align + + return +end subroutine subroutine_align + +function function_align() + + !DIR$ ALIGN 2048 + character(len=10) :: v9, v10 = "2048" +! CHECK: %[[V9:v9_[0-9]+]] = alloca [10 x i8], align 2048 + + v9 = "801" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr %[[V9]], align + + v10 = "802" +! CHECK: store volatile i64 %{{[0-9]+}}, ptr @[[BLOCK4]], align + + return +end function function_align diff --git a/test/directives/align_derived_variable.f90 b/test/directives/align_derived_variable.f90 new file mode 100644 index 00000000000..e2ea5c7fb43 --- /dev/null +++ b/test/directives/align_derived_variable.f90 @@ -0,0 +1,165 @@ +! RUN: %flang -O0 -S -emit-llvm %s -o - | FileCheck %s + +! CHECK: %struct[[BLOCK1:\.BSS[0-9]+]] = type <{ [264 x i8] }> +! CHECK: %struct[[BLOCK2:\.BSS[0-9]+]] = type <{ [520 x i8] }> +! CHECK: %struct[[BLOCK3:\.BSS[0-9]+]] = type <{ [1032 x i8] }> +! CHECK: %struct[[BLOCK4:\.BSS[0-9]+]] = type <{ [2056 x i8] }> +! CHECK: %struct[[BLOCK5:_module_align_derived_[0-9]+_]] = type <{ [136 x i8] }> +! CHECK: @[[BLOCK1]] = internal global %struct[[BLOCK1]] zeroinitializer, align 256 +! CHECK: @[[BLOCK2]] = internal global %struct[[BLOCK2]] zeroinitializer, align 512 +! CHECK: @[[BLOCK3]] = internal global %struct[[BLOCK3]] zeroinitializer, align 1024 +! CHECK: @[[BLOCK4]] = internal global %struct[[BLOCK4]] zeroinitializer, align 2048 +! CHECK: @[[BLOCK5]] = common global %struct[[BLOCK5]] zeroinitializer, align 128 + +module module_align_derived +implicit none + + type T1 + integer(kind=2) :: f1 + integer(kind=4) :: f2 + end type T1 + + !DIR$ ALIGN 128 + type(T1) :: v1, v2 + + interface + module subroutine module_interface_subroutine() + end subroutine module_interface_subroutine + end interface + +end module module_align_derived + +submodule (module_align_derived) submodule_align_derived + + contains + module subroutine module_interface_subroutine() + + type T3 + integer(kind=2) :: f1 + integer(kind=4) :: f2 + end type T3 + + !DIR$ ALIGN 256 + type(T3) :: v3, v4 + + v3%f1 = 101 +! CHECK: store i16 101, ptr @[[BLOCK1]], align + + v3%f2 = 102 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK1]], i64 4 +! CHECK: store i32 102, ptr %[[TEMP]], align + + v4%f1 = 103 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK1]], i64 256 +! CHECK: store i16 103, ptr %[[TEMP]], align + + v4%f2 = 104 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK1]], i64 260 +! CHECK: store i32 104, ptr %[[TEMP]], align + + end subroutine module_interface_subroutine +end submodule submodule_align_derived + + + +program align +use module_align_derived +implicit none + + type T5 + integer(kind=2) :: f1 + integer(kind=4) :: f2 + end type T5 + + !DIR$ ALIGN 512 + type(T5) :: v5, v6 + + v5%f1 = 201 +! CHECK: store i16 201, ptr @[[BLOCK2]], align + + v5%f2 = 202 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK2]], i64 4 +! CHECK: store i32 202, ptr %[[TEMP]], align + + v6%f1 = 203 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK2]], i64 512 +! CHECK: store i16 203, ptr %[[TEMP]], align + + v6%f2 = 204 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK2]], i64 516 +! CHECK: store i32 204, ptr %[[TEMP]], align + + v1%f1 = 81 +! CHECK: store i16 81, ptr @[[BLOCK5]], align + + v1%f2 = 82 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK5]], i64 4 +! CHECK: store i32 82, ptr %[[TEMP]], align + + v2%f1 = 83 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK5]], i64 128 +! CHECK: store i16 83, ptr %[[TEMP]], align + + v2%f2 = 84 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK5]], i64 132 +! CHECK: store i32 84, ptr %[[TEMP]], align + +end program align + + +subroutine subroutine_align() + + type T7 + integer(kind=2) :: f1 + integer(kind=4) :: f2 + end type T7 + + !DIR$ ALIGN 1024 + type(T7) :: v7, v8 + + v7%f1 = 401 +! CHECK: store i16 401, ptr @[[BLOCK3]], align + + v7%f2 = 402 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK3]], i64 4 +! CHECK: store i32 402, ptr %[[TEMP]], align + + v8%f1 = 403 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK3]], i64 1024 +! CHECK: store i16 403, ptr %[[TEMP]], align + + v8%f2 = 404 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK3]], i64 1028 +! CHECK: store i32 404, ptr %[[TEMP]], align + + return +end subroutine subroutine_align + + +function function_align() + + type T9 + integer(kind=2) :: f1 + integer(kind=4) :: f2 + end type T9 + + !DIR$ ALIGN 2048 + type(T9) :: v9, v10 + + v9%f1 = 801 +! CHECK: store i16 801, ptr @[[BLOCK4]], align + + v9%f2 = 802 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK4]], i64 4 +! CHECK: store i32 802, ptr %[[TEMP]], align + + v10%f1 = 803 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK4]], i64 2048 +! CHECK: store i16 803, ptr %[[TEMP]], align + + v10%f2 = 804 +! CHECK: %[[TEMP:[0-9]+]] = getelementptr i8, ptr @[[BLOCK4]], i64 2052 +! CHECK: store i32 804, ptr %[[TEMP]], align + + return +end function function_align diff --git a/test/directives/align_not_supported.f90 b/test/directives/align_not_supported.f90 new file mode 100644 index 00000000000..a8d7225c43e --- /dev/null +++ b/test/directives/align_not_supported.f90 @@ -0,0 +1,35 @@ +! RUN: %flang -O0 -c %s 2>&1 | FileCheck %s + +program align +implicit none + + !DIR$ ALIGN alignment + type T1 + integer(kind=2) :: f1 + integer(kind=4) :: f2 + end type T1 +! CHECK: F90-W-0280-Syntax error in directive ALIGN: non-integer alignment + + !DIR$ ALIGN -3 + type T2 + integer(kind=2) :: f1 + integer(kind=4) :: f2 + end type T2 +! CHECK: F90-W-0280-Syntax error in directive ALIGN: non-integer alignment + + !DIR$ ALIGN 0 + type T3 + integer(kind=2) :: f1 + integer(kind=4) :: f2 + end type T3 +! CHECK: F90-W-0280-Syntax error in directive ALIGN: non-power-of-2 alignment + + !DIR$ ALIGN 3 + type T4 + integer(kind=2) :: f1 + integer(kind=4) :: f2 + end type T4 +! CHECK: F90-W-0280-Syntax error in directive ALIGN: non-power-of-2 alignment + + +end program align diff --git a/test/flang2/Inputs/nop.ilm b/test/flang2/Inputs/nop.ilm index 471716655af..1abd9621716 100644 --- a/test/flang2/Inputs/nop.ilm +++ b/test/flang2/Inputs/nop.ilm @@ -1,5 +1,5 @@ ENDINLINE -TOILM version 1/55 +TOILM version 1/56 I:0 S:629 D:57 @@ -14,13 +14,13 @@ fihx:1 tag:0 parent:0 flags:0 lineno:1 srcline:1 level:0 next:0 0: 7:nop.f90 3:n procedure:Subroutine d:6 I4 d:7 I8 -s:609 c n d:6 h- 0 0: -s:611 c n d:6 h- 1 0: -s:624 E E d:0 c+ a- a- a:0 C- d- d:0 c:0 e:2 i:0 l:1 m- p- r- e- r:0 p- p- s- d- c- n- c:0 r:0 p:0 a:0 v:0 i:0 i- c- d- a- v- h- 3:nop -s:627 L n d:0 c+ a- f- v- r:0 a:0 7:%L99999 -s:629 c n d:7 h- 7fffffff ffffffff 0: +s:609 c n d:6 p:0 h- 0 0: +s:611 c n d:6 p:0 h- 1 0: +s:624 E E d:0 p:0 c+ a- a- a:0 C- d- d:0 c:0 e:2 i:0 l:1 m- p- r- e- r:0 p- p- s- d- c- n- c:0 r:0 p:0 a:0 v:0 i:0 i- c- d- a- v- h- 3:nop +s:627 L n d:0 p:0 c+ a- f- v- r:0 a:0 7:%L99999 +s:629 c n d:7 p:0 h- 7fffffff ffffffff 0: end -AST2ILM version 1/55 +AST2ILM version 1/56 i0: BOS l1 n1 n0 i4: NOP i5: -------------------- @@ -37,7 +37,7 @@ i4: FILE n2 n1 n1000 i8: END i9: -------------------- end -DIRECTIVES version 1/55 +DIRECTIVES version 1/56 A:1 rou: -------------------- z diff --git a/tools/flang1/flang1exe/dtypeutl.c b/tools/flang1/flang1exe/dtypeutl.c index 0afcc2e0ddd..b24f3576fa2 100644 --- a/tools/flang1/flang1exe/dtypeutl.c +++ b/tools/flang1/flang1exe/dtypeutl.c @@ -1288,6 +1288,14 @@ alignment_of_var(int sptr) align = ta; } #endif + /* + * If alignment of variable set by `!DIR$ ALIGN alignment` + * in flang1 is smaller than its original, then this pragma + * should have no effect. + */ + if (align < PALIGNG(sptr)) { + align = PALIGNG(sptr) - 1; + } return align; } /* alignment_of_var */ diff --git a/tools/flang1/flang1exe/exterf.c b/tools/flang1/flang1exe/exterf.c index 510d602ed3e..465908c0115 100644 --- a/tools/flang1/flang1exe/exterf.c +++ b/tools/flang1/flang1exe/exterf.c @@ -2337,10 +2337,11 @@ export_symbol(int sptr) lzprintf(outlz, "S %d", sptr); if (exportmode) lzprintf(outlz, " %d", HASHLKG(sptr)); - lzprintf(outlz, " %d %d %d %d %d %d %d %d", stb.stg_base[sptr].stype, + lzprintf(outlz, " %d %d %d %d %d %d %d %d %d", stb.stg_base[sptr].stype, stb.stg_base[sptr].sc, stb.stg_base[sptr].b3, stb.stg_base[sptr].b4, stb.stg_base[sptr].dtype, stb.stg_base[sptr].symlk, - stb.stg_base[sptr].scope, stb.stg_base[sptr].nmptr); + stb.stg_base[sptr].scope, stb.stg_base[sptr].nmptr, + stb.stg_base[sptr].palign); #undef PUTFIELD #undef PUTISZ_FIELD diff --git a/tools/flang1/flang1exe/global.h b/tools/flang1/flang1exe/global.h index 2967568d609..cb4ea757e08 100644 --- a/tools/flang1/flang1exe/global.h +++ b/tools/flang1/flang1exe/global.h @@ -207,7 +207,7 @@ typedef struct { LOGICAL endian; LOGICAL terse; int dollar; /* defines the char to which '$' is translated */ - int x[251]; /* x flags */ + int x[252]; /* x flags */ LOGICAL quad; /* quad align "unconstrained objects" if sizeof >= 16 */ int anno; LOGICAL qa; /* TRUE => -qa appeared on command line */ diff --git a/tools/flang1/flang1exe/interf.c b/tools/flang1/flang1exe/interf.c index 050250fb90e..b1a9faaa0f0 100644 --- a/tools/flang1/flang1exe/interf.c +++ b/tools/flang1/flang1exe/interf.c @@ -74,7 +74,7 @@ interf_init() * https://github.com/flang-compiler/flang/issues/1043 */ #if DEBUG && !defined(_WIN64) - assert(sizeof(SYM) / sizeof(INT) == 44, "bad SYM size", + assert(sizeof(SYM) / sizeof(INT) == 46, "bad SYM size", sizeof(SYM) / sizeof(INT), 4); assert(sizeof(AST) / sizeof(int) == 19, "interf_init:inconsistent AST size", sizeof(AST) / sizeof(int), 2); @@ -2500,6 +2500,7 @@ import(lzhandle *fdlz, WantPrivates wantPrivates, int ivsn) ps->symlk = get_num(10); ps->sym.scope = get_num(10); ps->sym.nmptr = get_num(10); + ps->sym.palign = get_num(10); ps->flags1 = get_num(16); ps->flags2 = get_num(16); @@ -5406,6 +5407,7 @@ fill_sym(SYMITEM *ps, int sptr) GETFIELD(lineno); GETFIELD(w39); GETFIELD(w40); + GETFIELD(palign); #undef GETFIELD stb.stg_base[sptr].uname = 0; } /* fill_sym */ diff --git a/tools/flang1/flang1exe/lower.h b/tools/flang1/flang1exe/lower.h index 73385d7b30c..b3ca30d6d9d 100644 --- a/tools/flang1/flang1exe/lower.h +++ b/tools/flang1/flang1exe/lower.h @@ -132,9 +132,12 @@ * pass elemental field for subprogram when emitting ST_ENTRY. * * For ST_PROC, pass IS_PROC_PTR_IFACE flag. + * + * 23.12 -- 1.56 + * All of 1.55 + PALIGN */ #define VersionMajor 1 -#define VersionMinor 55 +#define VersionMinor 56 void lower(int); void lower_end_contains(void); diff --git a/tools/flang1/flang1exe/lowersym.c b/tools/flang1/flang1exe/lowersym.c index f32d7005845..c7906b874fe 100644 --- a/tools/flang1/flang1exe/lowersym.c +++ b/tools/flang1/flang1exe/lowersym.c @@ -3705,6 +3705,7 @@ lower_symbol(int sptr) } else #endif putval("dtype", dtype); + putval("palign", PALIGNG(sptr)); /* type specific information */ switch (stype) { case ST_ARRAY: diff --git a/tools/flang1/flang1exe/semant.c b/tools/flang1/flang1exe/semant.c index b2c8d2ae1dd..119a494b2ef 100644 --- a/tools/flang1/flang1exe/semant.c +++ b/tools/flang1/flang1exe/semant.c @@ -836,6 +836,11 @@ semant1(int rednum, SST *top) * ::= */ case STMT1: + /* + * `!DIR$ ALIGN alignment` pragma should only take effect within the + * scope of the statement, so flang1 need to clear the flg.x[251] here. + */ + flg.x[251] = 0; break; /* ------------------------------------------------------------------ */ @@ -9759,6 +9764,12 @@ semant1(int rednum, SST *top) SST_GDTYPEP(RHS(1), sem.gdtype); SST_GTYP(RHS(1), sem.gty); + /* + * When declaring a variable's symbol, flang1 should store + * the alignment from `!DIR$ ALIGN alignment` pragma to + * the symbol. + */ + PALIGNP(sptr, flg.x[251]); break; /* ------------------------------------------------------------------ */ diff --git a/tools/flang1/flang1exe/symacc.c b/tools/flang1/flang1exe/symacc.c index 35d77c51879..030d6d81f75 100644 --- a/tools/flang1/flang1exe/symacc.c +++ b/tools/flang1/flang1exe/symacc.c @@ -43,7 +43,7 @@ sym_init_first(void) * https://github.com/flang-compiler/flang/issues/1043 */ #ifndef _WIN64 - assert(sizeof_SYM == 44, "bad SYM size", sizeof_SYM, ERR_Fatal); + assert(sizeof_SYM == 46, "bad SYM size", sizeof_SYM, ERR_Fatal); #endif if (stb.stg_base == NULL) { diff --git a/tools/flang1/flang1exe/symacc.h b/tools/flang1/flang1exe/symacc.h index 1ec557cd152..45c5dfe0177 100644 --- a/tools/flang1/flang1exe/symacc.h +++ b/tools/flang1/flang1exe/symacc.h @@ -166,6 +166,7 @@ typedef struct SYM { INT lineno; INT w39; INT w40; + INT palign; } SYM; /* symbol table data declarations: */ diff --git a/tools/flang1/utils/symtab/symini.cpp b/tools/flang1/utils/symtab/symini.cpp index 02e5b223326..54e81da1a51 100644 --- a/tools/flang1/utils/symtab/symini.cpp +++ b/tools/flang1/utils/symtab/symini.cpp @@ -1057,7 +1057,8 @@ class SyminiFE90 : public UtilityApplication fprintf(out1, "\t 0,\n"); fprintf(out1, "#endif\n"); - fprintf(out1, "\t %5d, %5d, %5d\n", xp->lineno, xp->w39, xp->w40); + fprintf(out1, "\t %5d, %5d, %5d, %5d\n", xp->lineno, xp->w39, + xp->w40, xp->palign); fprintf(out1, "\t},\n"); } diff --git a/tools/flang1/utils/symtab/symtab.n b/tools/flang1/utils/symtab/symtab.n index 539ab7f93c7..331555ad9db 100644 --- a/tools/flang1/utils/symtab/symtab.n +++ b/tools/flang1/utils/symtab/symtab.n @@ -359,6 +359,8 @@ field will locate the original name. Flags per symbol (named f65 through f96). .SF flags4 w37 Flags per symbol (named f97 through f128). +.SF PALIGN w41 +Store the symbol's alignment value specified by align pragma in the form of '!DIR$ ALIGN alignment'. Other Fields .ul .nr II \n(iiu diff --git a/tools/flang2/docs/xflag.n b/tools/flang2/docs/xflag.n index 6aaa021dc3c..08fd0e91118 100644 --- a/tools/flang2/docs/xflag.n +++ b/tools/flang2/docs/xflag.n @@ -5573,6 +5573,9 @@ where, n = flg.x[249] .XF "250:" Set number of bigbuffers for multi-buffer memory management for AMD GPU. (moved to 202) + .XF "251:" -(NOT available - check declaration in global.h for flg.x[], all compilers) +Reserved to save an alignment passed by pragma `!DIR$ ALIGN alignment` +.XF "252:" +(NOT available - check declaration in global.h for flg.x[], all compilers) diff --git a/tools/flang2/flang2exe/dtypeutl.cpp b/tools/flang2/flang2exe/dtypeutl.cpp index 552931a8876..cade9cc5010 100644 --- a/tools/flang2/flang2exe/dtypeutl.cpp +++ b/tools/flang2/flang2exe/dtypeutl.cpp @@ -557,9 +557,21 @@ align_unconstrained(DTYPE dtype) int alignment_sym(SPTR sym) { - if (QALNG(sym)) - return dtypeinfo[TY_DBLE].align; - return alignment(DTYPEG(sym)); + int align; + if (QALNG(sym)) { + align = dtypeinfo[TY_DBLE].align; + } else { + align = alignment(DTYPEG(sym)); + } + /* + * If alignment of symbol set by `!DIR$ ALIGN alignment` + * in flang1 is smaller than its original, then this pragma + * should have no effect. + */ + if (align < PALIGNG(sym)) { + align = PALIGNG(sym) - 1; + } + return align; } int diff --git a/tools/flang2/flang2exe/llassem.cpp b/tools/flang2/flang2exe/llassem.cpp index 22fa8552b34..d47ee8f74b9 100644 --- a/tools/flang2/flang2exe/llassem.cpp +++ b/tools/flang2/flang2exe/llassem.cpp @@ -858,7 +858,7 @@ void assem_init(void) { INT nmptr; - SPTR sptr; + SPTR sptr, cmem; int align8, mod_or_sub, subprog; char *typed; @@ -927,6 +927,22 @@ assem_init(void) } } free(typed); + + /* + * Update the alignment for cmn. + * + * To align the symbol set by `!DIR$ ALIGN alignment` pragma + * in flang1, flang should align both its symbol's offset + * in AG and AG's alignment in memory. + * + * Here we update the AG_ALIGN(ag) to ensure cmn is aligned + * in memory to the maximum alignment among all symbols in + * the cmn. + */ + for (cmem = CMEMFG(sptr); cmem > NOSYM; cmem = SYMLKG(cmem)) { + AG_ALIGN(gblsym) = AG_ALIGN(gblsym) > PALIGNG(cmem) ? + AG_ALIGN(gblsym) : PALIGNG(cmem); + } } /* ag_local gets allocated and deallocate for every function */ @@ -1171,6 +1187,7 @@ assemble_end(void) free(AG_CMBLKINITDATA(gblsym)); AG_CMBLKINITDATA(gblsym) = NULL; } else { + int align; fprintf(ASMFIL, "%%struct%s = type < { %s } > \n", name, typed); if (strstr(cpu_llvm_module->target_triple, "windows-msvc") != NULL) { fprintf(ASMFIL, "@%s = %s global %%struct%s ", name, @@ -1179,8 +1196,17 @@ assemble_end(void) fprintf(ASMFIL, "@%s = %s global %%struct%s ", name, AG_ISMOD(gblsym) ? "external" : "common", name); } + + /* + * cmn should align with its corresponding AG's alignment, + * so that all symbols within the cmn align with the alignment set by + * `!DIR$ ALIGN alignment` pragma in flang1 as long as the symbol's + * offset in AG aligns with the specified alignment. + */ + align = + align_value > AG_ALIGN(tdefsym) ? align_value : AG_ALIGN(tdefsym); fprintf(ASMFIL, "%s, align %d", - AG_ISMOD(gblsym) ? "" : " zeroinitializer", align_value); + AG_ISMOD(gblsym) ? "" : " zeroinitializer", align); } for (llObjtodbgFirst(listp, &i); !llObjtodbgAtEnd(&i); llObjtodbgNext(&i)) { @@ -1521,12 +1547,22 @@ write_bss(void) char *bss_nm = bss_name; if (gbl.bss_addr) { + /* + * BSS should align with its corresponding AG's alignment, so that + * all symbols within the BSS align with the alignment set by + * `!DIR$ ALIGN alignment` pragma in flang1 as long as the symbol's + * offset in AG aligns with the specified alignment. + */ + int align = 32; + for (SPTR sptr = gbl.bssvars; sptr > NOSYM; sptr = SYMLKG(sptr)) { + align = align > PALIGNG(sptr) ? align : PALIGNG(sptr); + } fprintf(ASMFIL, "%%struct%s = type <{[%" ISZ_PF "d x i8]}>\n", bss_nm, gbl.bss_addr); fprintf(ASMFIL, "@%s = %s %%struct%s <{[%" ISZ_PF "d x i8] " - "zeroinitializer }> , align 32", - bss_nm, type_str, bss_nm, gbl.bss_addr); + "zeroinitializer }> , align %d", + bss_nm, type_str, bss_nm, gbl.bss_addr, align); ll_write_object_dbg_references(ASMFIL, cpu_llvm_module, bss_dbg_list); bss_dbg_list = NULL; fputc('\n', ASMFIL); @@ -1582,6 +1618,17 @@ write_statics(void) DSRT *dsrtp; int count = 0; char *static_nm = static_name; + int align = 16; + + /* + * statics should align with its corresponding AG's alignment, so that + * all symbols within the BSS align with the alignment set by + * `!DIR$ ALIGN alignment` pragma in flang1 as long as the symbol's + * offset in AG aligns with the specified alignment. + */ + for (SPTR sptr = gbl.statics; sptr > NOSYM; sptr = SYMLKG(sptr)) { + align = align > PALIGNG(sptr) ? align : PALIGNG(sptr); + } if (lcl_inits) { if (DBGBIT(5, 32)) { @@ -1599,7 +1646,7 @@ write_statics(void) fprintf(ASMFIL, "%%struct%s = type <{ %s }>\n", static_nm, type_only); fprintf(ASMFIL, "@%s = %s %%struct%s <{ ", static_nm, type_str, static_nm); process_dsrt(lcl_inits, gbl.saddr, typed, false, 0); - fprintf(ASMFIL, " }>, align 16"); + fprintf(ASMFIL, " }>, align %d", align); ll_write_object_dbg_references(ASMFIL, cpu_llvm_module, static_dbg_list); static_dbg_list = NULL; fputc('\n', ASMFIL); @@ -1609,8 +1656,8 @@ write_statics(void) (long)gbl.saddr); fprintf(ASMFIL, "@%s = %s %%struct%s <{ [%ld x i8] zeroinitializer }>" - ", align 16", - static_name, type_str, static_name, (long)gbl.saddr); + ", align %d", + static_name, type_str, static_name, (long)gbl.saddr, align); ll_write_object_dbg_references(ASMFIL, cpu_llvm_module, static_dbg_list); static_dbg_list = NULL; fputc('\n', ASMFIL); @@ -1700,6 +1747,7 @@ write_comm(void) for (sptr = gbl.cmblks; sptr > NOSYM; sptr = SYMLKG(sptr)) { SPTR cmem; + int align; first_data = 1; process_sptr(sptr); @@ -1745,6 +1793,14 @@ write_comm(void) else gbl.asmfil = cmn_blk_ir; + /* + * cmn should align with its corresponding AG's alignment, + * so that all symbols within the cmn align with the alignment set by + * `!DIR$ ALIGN alignment` pragma in flang1 as long as the symbol's + * offset in AG aligns with the specified alignment. + */ + align = align_value > AG_ALIGN(gblsym) ? align_value : AG_ALIGN(gblsym); + fprintf(ASMFIL, "%%struct%s = type < { %s } > \n", name, type_only); fprintf(ASMFIL, "@%s = global %%struct%s", name, name); fprintf(ASMFIL, " < { "); @@ -1753,7 +1809,7 @@ write_comm(void) DSRTP(sptr, NULL); - fprintf(ASMFIL, ", align %d", align_value); + fprintf(ASMFIL, ", align %d", align); for (cmem = CMEMFG(sptr); cmem > NOSYM; cmem = SYMLKG(cmem)) { if (MIDNUMG(cmem)) /* some member does not have midnum/no name */ @@ -4232,19 +4288,29 @@ unsigned align_of_var(SPTR sptr) { DTYPE dtype = DTYPEG(sptr); - if (!PDALN_IS_DEFAULT(sptr)) - return 1u << PDALNG(sptr); - if (QALNG(sptr)) - return 4 * align_of(DT_INT); - if (dtype) { + int align = 0; + if (!PDALN_IS_DEFAULT(sptr)) { + align = 1u << PDALNG(sptr); + } else if(QALNG(sptr)) { + align = 4 * align_of(DT_INT); + } else if (dtype) { if (flg.quad && !DESCARRAYG(sptr) && zsize_of(dtype) >= MIN_ALIGN_SIZE) { - return DATA_ALIGN + 1; + align = DATA_ALIGN + 1; + } else { + align = align_of(dtype); } - return align_of(dtype); + } else if(STYPEG(sptr) == ST_PROC) {/* No DTYPE */ + align = align_of(DT_ADDR); } - if (STYPEG(sptr) == ST_PROC) /* No DTYPE */ - return align_of(DT_ADDR); - return 0; + /* + * If alignment of variable set by `!DIR$ ALIGN alignment` + * in flang1 is smaller than its original, then this pragma + * should have no effect. + */ + if (align < PALIGNG(sptr)) { + align = PALIGNG(sptr); + } + return align; } static void @@ -4312,6 +4378,16 @@ assn_static_off(SPTR sptr, DTYPE dtype, ISZ_T size) } else { a = align_unconstrained(dtype); } + /* + * To align the symbol set by `!DIR$ ALIGN alignment` pragma in flang1, + * flang should align both its symbol's offset in AG and AG's alignment + * in memory. + * + * The following code ensures the alignment of the symbol's offset in AG. + */ + if (a < PALIGNG(sptr)) { + a = PALIGNG(sptr) - 1; + } addr = ALIGN(addr, a); ADDRESSP(sptr, addr); if (DINITG(sptr)) { diff --git a/tools/flang2/flang2exe/symacc.cpp b/tools/flang2/flang2exe/symacc.cpp index 2713d438086..616b92bd0f1 100644 --- a/tools/flang2/flang2exe/symacc.cpp +++ b/tools/flang2/flang2exe/symacc.cpp @@ -43,7 +43,7 @@ sym_init_first(void) * https://github.com/flang-compiler/flang/issues/1043 */ #ifndef _WIN64 - assert(sizeof_SYM == 36, "bad SYM size", sizeof_SYM, ERR_Fatal); + assert(sizeof_SYM == 38, "bad SYM size", sizeof_SYM, ERR_Fatal); #endif if (stb.stg_base == NULL) { diff --git a/tools/flang2/flang2exe/symacc.h b/tools/flang2/flang2exe/symacc.h index 0303d238117..dc8bbcae98f 100644 --- a/tools/flang2/flang2exe/symacc.h +++ b/tools/flang2/flang2exe/symacc.h @@ -157,6 +157,7 @@ typedef struct SYM { INT w30; INT w31; INT w32; + INT palign; } SYM; /* symbol table data declarations: */ diff --git a/tools/flang2/flang2exe/upper.cpp b/tools/flang2/flang2exe/upper.cpp index b319dd5755d..811c4451a83 100644 --- a/tools/flang2/flang2exe/upper.cpp +++ b/tools/flang2/flang2exe/upper.cpp @@ -2040,6 +2040,7 @@ read_symbol(void) SPTR sptr = getSptrVal("symbol"); bool has_alias = false; char *alias_name; + int palign; #if DEBUG if (sptr > symbolcount) { fprintf(stderr, "Symbol count was %d, but new symbol number is %d\n", @@ -2050,6 +2051,7 @@ read_symbol(void) stype = getSymType(); sclass = getSCKind(); dtype = getDtypeVal("dtype"); + palign = getval("palign"); #if DEBUG if (dtype > datatypecount) { fprintf(stderr, "Datatype count was %d, but new datatype is %d\n", @@ -3301,6 +3303,9 @@ read_symbol(void) ++errors; break; } + if (newsptr != SPTR_NULL) { + PALIGNP(newsptr, palign); + } Trace((" newsptr = %d", newsptr)); } /* read_symbol */ diff --git a/tools/flang2/flang2exe/upper.h b/tools/flang2/flang2exe/upper.h index 15de01c4e82..aaff9c7372c 100644 --- a/tools/flang2/flang2exe/upper.h +++ b/tools/flang2/flang2exe/upper.h @@ -136,13 +136,16 @@ * pass elemental field for subprogram when emitting ST_ENTRY. * * For ST_PROC, receive IS_PROC_PTR_IFACE flag. + * + * 23.12 -- 1.56 + * All of 1.55 + PALIGN */ #include "gbldefs.h" #include "semant.h" #define VersionMajor 1 -#define VersionMinor 55 +#define VersionMinor 56 /** \brief ... diff --git a/tools/flang2/utils/symtab/symini.cpp b/tools/flang2/utils/symtab/symini.cpp index eb9ddf530f5..568f948388d 100644 --- a/tools/flang2/utils/symtab/symini.cpp +++ b/tools/flang2/utils/symtab/symini.cpp @@ -497,8 +497,8 @@ class SyminiF90 : public UtilityApplication fprintf(out1, "%d,", 0 /*xp->f*/); } fprintf(out1, "\n"); - fprintf(out1, "\t %d, %d, %d, %d, %d, %d, %d,},\n", xp->w26, xp->w27, - xp->w28, xp->w29, xp->w30, xp->w31, xp->w32); + fprintf(out1, "\t %d, %d, %d, %d, %d, %d, %d, %d,},\n", xp->w26, + xp->w27, xp->w28, xp->w29, xp->w30, xp->w31, xp->w32, xp->palign); } fprintf(out1, "};\n\n"); fprintf(out1, "static char init_names[INIT_NAMES_SIZE] = {"); diff --git a/tools/flang2/utils/symtab/symtab.n b/tools/flang2/utils/symtab/symtab.n index c51d0b16779..4cf7fd8805e 100644 --- a/tools/flang2/utils/symtab/symtab.n +++ b/tools/flang2/utils/symtab/symtab.n @@ -307,6 +307,8 @@ Flags per symbol (named f33 through f64). Flags per symbol (named f65 through f96). .SF flags4 w25 Flags per symbol (named f97 through f128). +.SF PALIGN w33 +Store the symbol's alignment value specified by align pragma in the form of '!DIR$ ALIGN alignment'. .nr II \n(iiu .nr ii 0 .lp diff --git a/tools/shared/pragma.c b/tools/shared/pragma.c index dc871a708f3..67c44f1224a 100644 --- a/tools/shared/pragma.c +++ b/tools/shared/pragma.c @@ -1053,7 +1053,28 @@ do_sw(void) case SW_ESCTYALIAS: break; case SW_ALIGN: - break; + if (gtok() != T_INT) { + int backup_nowarn = gbl.nowarn; + gbl.nowarn = false; + error((error_code_t)280, ERR_Warning, lineno, + "ALIGN: non-integer alignment", 0); + gbl.nowarn = backup_nowarn; + return true; + } + + /* check whether the alignment is power of 2 */ + if (itok <= 0 || ((itok & (itok - 1)) != 0)) { + int backup_nowarn = gbl.nowarn; + gbl.nowarn = false; + error((error_code_t)280, ERR_Warning, lineno, + "ALIGN: non-power-of-2 alignment", 0); + gbl.nowarn = backup_nowarn; + return true; + } + + TR1("SW_ALIGN alignment[%d]\n", itok); + flg.x[251] = itok; + return true; case SW_BOUNDS: if (no_specified) { bclr(DIR_OFFSET(currdir, x[70]), 0x02); diff --git a/tools/shared/utils/global.h b/tools/shared/utils/global.h index 88484013ba6..86d0605b48d 100644 --- a/tools/shared/utils/global.h +++ b/tools/shared/utils/global.h @@ -204,7 +204,7 @@ typedef struct { int endian; int terse; int dollar; /* defines the char to which '$' is translated */ - int x[251]; /* x flags */ + int x[252]; /* x flags */ bool quad; /* quad align "unconstrained objects" if sizeof >= 16 */ int anno; bool qa; /* TRUE => -qa appeared on command line */ diff --git a/tools/shared/utils/symacc.c b/tools/shared/utils/symacc.c index 7fc4eb0aff2..ab64e73a864 100644 --- a/tools/shared/utils/symacc.c +++ b/tools/shared/utils/symacc.c @@ -56,9 +56,9 @@ sym_init_first(void) */ #if !defined(_WIN64) #if defined(PGHPF) - assert(sizeof_SYM == 44, "bad SYM size", sizeof_SYM, ERR_Fatal); + assert(sizeof_SYM == 46, "bad SYM size", sizeof_SYM, ERR_Fatal); #else - assert(sizeof_SYM == 36, "bad SYM size", sizeof_SYM, ERR_Fatal); + assert(sizeof_SYM == 38, "bad SYM size", sizeof_SYM, ERR_Fatal); #endif #endif // _WIN64 diff --git a/tools/shared/utils/symacc.h b/tools/shared/utils/symacc.h index a80c4753e9c..02f906884d7 100644 --- a/tools/shared/utils/symacc.h +++ b/tools/shared/utils/symacc.h @@ -180,6 +180,7 @@ typedef struct SYM { INT w30; INT w31; INT w32; + INT palign; } SYM; #endif @@ -256,6 +257,7 @@ typedef struct SYM { INT lineno; INT w39; INT w40; + INT palign; } SYM; #endif diff --git a/tools/shared/utils/symutil.cpp b/tools/shared/utils/symutil.cpp index cc9747d53e5..c9fa3378529 100644 --- a/tools/shared/utils/symutil.cpp +++ b/tools/shared/utils/symutil.cpp @@ -111,9 +111,9 @@ class Symutil : public UtilityApplication std::vector attrnames; #if defined(PGHPF) - static const int SYMLEN = 40; + static const int SYMLEN = 41; #else - static const int SYMLEN = 32; + static const int SYMLEN = 33; #endif // Generate run time checking code for symbol table field access macros.