mirror of
https://github.com/llvm/llvm-project.git
synced 2025-04-26 16:16:07 +00:00

Currently, lowering is promoting main program array and character variables that are not saved into static memory. This causes issues with equivalence initial value images because semantics is relying on IsSaved to build the initial value of variables in static memory. It seems more robust to have IsSaved be the place deciding if a variable needs to be in static memory (except for common block members). Move the logic to decide if a main program variable must be in static memory into evaluate::IsSaved and add two options to semantics to replace the llvm options that were used in lowering: - SaveMainProgram (off by default): save all main program variables. - SaveBigMainProgramVariables (on by default): save all main program variables that are bigger than 32 bytes. The first options is required to run a few old programs that expect all main program variables to be in bss (and therefore zero initialized). The second option is added to allow performance testing: placing big arrays in static memory seems a sane default to avoid blowing up the stack with old programs that define big local arrays in the main program, but since it is easier to prove that an alloca does not escape/is not modified by calls, keeping big arrays on the stack could yield improvements. The logic of SaveBigMainProgramVariables is slightly changed compared to what it was doing in lowering. The old code was placing all arrays and all explicit length characters in static memory. The new code is placing everything bigger than 32 bytes in static memory. This has the advantages of being a simpler logic, and covering the cases of scalar derived type with big array components or many components. Small strings and arrays are now left on the stack (after all, a character(1) can fit in register). Note: I think it could have been nicer to add a single "integer" option to set a threshold to place main program variables in static memory so that this can be fine tuned by the drivers (SaveMainProgram would be implemented by setting it to zero). But the language feature options are not meant to carry integer options. Extending it for this seems an overkill precedent, and placing it in SemanticsContext is weird (it is a too low level option to be a bare member of SemanticsContext in my opinion). So I just rolled my own dices and picked 32 for the sake of simplicity. Differential Revision: https://reviews.llvm.org/D134735
96 lines
2.7 KiB
Fortran
96 lines
2.7 KiB
Fortran
! RUN: bbc -emit-fir -o - %s | FileCheck %s
|
|
|
|
! CHECK-LABEL: func @_QQmain
|
|
program p
|
|
! CHECK-DAG: [[I:%[0-9]+]] = fir.alloca i32 {{{.*}}uniq_name = "_QFEi"}
|
|
! CHECK-DAG: [[N:%[0-9]+]] = fir.alloca i32 {{{.*}}uniq_name = "_QFEn"}
|
|
! CHECK: [[T:%[0-9]+]] = fir.alloca !fir.array<3xi32> {bindc_name = "t", uniq_name = "_QFEt"}
|
|
integer :: n, foo, t(3)
|
|
! CHECK: [[N]]
|
|
! CHECK-COUNT-3: fir.coordinate_of [[T]]
|
|
n = 100; t(1) = 111; t(2) = 222; t(3) = 333
|
|
! CHECK: fir.load [[N]]
|
|
! CHECK: addi {{.*}} %c5
|
|
! CHECK: fir.store %{{[0-9]*}} to [[B:%[0-9]+]]
|
|
! CHECK: [[C:%[0-9]+]] = fir.coordinate_of [[T]]
|
|
! CHECK: fir.call @_QPfoo
|
|
! CHECK: fir.store %{{[0-9]*}} to [[D:%[0-9]+]]
|
|
associate (a => n, b => n+5, c => t(2), d => foo(7))
|
|
! CHECK: fir.load [[N]]
|
|
! CHECK: addi %{{[0-9]*}}, %c1
|
|
! CHECK: fir.store %{{[0-9]*}} to [[N]]
|
|
a = a + 1
|
|
! CHECK: fir.load [[C]]
|
|
! CHECK: addi %{{[0-9]*}}, %c1
|
|
! CHECK: fir.store %{{[0-9]*}} to [[C]]
|
|
c = c + 1
|
|
! CHECK: fir.load [[N]]
|
|
! CHECK: addi %{{[0-9]*}}, %c1
|
|
! CHECK: fir.store %{{[0-9]*}} to [[N]]
|
|
n = n + 1
|
|
! CHECK: fir.load [[N]]
|
|
! CHECK: fir.embox [[T]]
|
|
! CHECK: fir.load [[N]]
|
|
! CHECK: fir.load [[B]]
|
|
! CHECK: fir.load [[C]]
|
|
! CHECK: fir.load [[D]]
|
|
print*, n, t, a, b, c, d ! expect: 102 111 223 333 102 105 223 7
|
|
end associate
|
|
|
|
call nest
|
|
|
|
do i=1,4
|
|
associate (x=>i)
|
|
! CHECK: [[IVAL:%[0-9]+]] = fir.load [[I]] : !fir.ref<i32>
|
|
! CHECK: [[TWO:%.*]] = arith.constant 2 : i32
|
|
! CHECK: arith.cmpi eq, [[IVAL]], [[TWO]] : i32
|
|
! CHECK: ^bb
|
|
if (x==2) goto 9
|
|
! CHECK: [[IVAL:%[0-9]+]] = fir.load [[I]] : !fir.ref<i32>
|
|
! CHECK: [[THREE:%.*]] = arith.constant 3 : i32
|
|
! CHECK: arith.cmpi eq, [[IVAL]], [[THREE]] : i32
|
|
! CHECK: ^bb
|
|
! CHECK: fir.call @_FortranAStopStatementText
|
|
! CHECK: fir.unreachable
|
|
! CHECK: ^bb
|
|
if (x==3) stop 'Halt'
|
|
! CHECK: fir.call @_FortranAioOutputAscii
|
|
print*, "ok"
|
|
9 end associate
|
|
enddo
|
|
end
|
|
|
|
! CHECK-LABEL: func @_QPfoo
|
|
integer function foo(x)
|
|
integer x
|
|
integer, save :: i = 0
|
|
i = i + x
|
|
foo = i
|
|
end function foo
|
|
|
|
! CHECK-LABEL: func @_QPnest(
|
|
subroutine nest
|
|
integer, parameter :: n = 10
|
|
integer :: a(5), b(n)
|
|
associate (s => sequence(size(a)))
|
|
a = s
|
|
associate(t => sequence(n))
|
|
b = t
|
|
! CHECK: cond_br %{{.*}}, [[BB1:\^bb[0-9]]], [[BB2:\^bb[0-9]]]
|
|
! CHECK: [[BB1]]:
|
|
! CHECK: br [[BB3:\^bb[0-9]]]
|
|
! CHECK: [[BB2]]:
|
|
if (a(1) > b(1)) goto 9
|
|
end associate
|
|
a = a * a
|
|
end associate
|
|
! CHECK: br [[BB3]]
|
|
! CHECK: [[BB3]]:
|
|
9 print *, sum(a), sum(b) ! expect: 55 55
|
|
contains
|
|
function sequence(n)
|
|
integer sequence(n)
|
|
sequence = [(i,i=1,n)]
|
|
end function
|
|
end subroutine nest
|