Skip to content

Commit

Permalink
[flang1][flang2] Add align pragma for derived type and fix shape arra…
Browse files Browse the repository at this point in the history
…y/character type

This patch implements parsing for `!DIR$ ALIGN alignment`, which only
accepts a power-of-2 integer alignment. flang1 will set `flg.x[251]` with the
alignment value if it encounters this pragma. Since the pragma only affects
variables in a single statement, `flg.x[251]` is cleared when the parsing
of the statement is complete. A new `palign` field is added to `struct SYM`
to record a symbol's alignment. The field can be read with `PALIGNG(sptr)`
and written with `PALIGNP(sptr)`. tools/flang1/flang1exe/interf.c and
tools/flang1/flang1exe/exterf.c are updated to store and load symbol
alignment to/from .mod files. tools/flang1/flang1exe/lowersym.c and
tools/flang2/flang2exe/upper.cpp are updated to pass symbol alignment
information via .stb files. The BSS is aligned to the maximum alignment
among all symbols in the BSS; each symbol can then be aligned to smaller
alignment values within the BSS. Alignment of statics and common data
are also supported. Since a new field has been added in `struct SYM`,
the ILM version number is bumped.
  • Loading branch information
JiaweiHawk authored Dec 15, 2023
1 parent 4df6dac commit 7f17301
Show file tree
Hide file tree
Showing 30 changed files with 639 additions and 47 deletions.
140 changes: 140 additions & 0 deletions test/directives/align_array_variable.f90
Original file line number Diff line number Diff line change
@@ -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
97 changes: 97 additions & 0 deletions test/directives/align_character_variable.f90
Original file line number Diff line number Diff line change
@@ -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
Loading

0 comments on commit 7f17301

Please sign in to comment.