Open konradha opened 2 years ago
Some notes:
The problematic function seems to be CreateGEP
in libasr/codegen/llvm_utils.cpp
. There seems to be a bug in how a double precision
variable is initialized that is named identical to an intrinsic:
(value) %zexp = alloca double, align 8
(wrapped) i32 0 i32 2
(zexp
is an intrinsic; ZEXP
in swilk.f
is a double precision variable; the "wrapped" value are the content of the idx
container in CreateGEP
).
So here's the minimal reproducer called t_llvmir_double.f:
program main
double precision zexp,z
zexp(z) = dexp(z)
end program
gfortran -fdump-parse-tree t_llvmir_double.f
yields
Namespace: A-H: (REAL 4) I-N: (INTEGER 4) O-Z: (REAL 4)
procedure name = main
symtree: 'dexp' || symbol: 'dexp'
type spec : (REAL 4)
attributes: (PROCEDURE INTRINSIC-PROC FUNCTION IMPLICIT-TYPE ARRAY-OUTER-DEPENDENCY)
result: dexp
symtree: 'main' || symbol: 'main'
type spec : (UNKNOWN 0)
attributes: (PROGRAM PUBLIC SUBROUTINE IS-MAIN-PROGRAM)
symtree: 'z' || symbol: 'z'
type spec : (REAL 8)
attributes: (VARIABLE )
symtree: 'zexp' || symbol: 'zexp'
type spec : (REAL 8)
attributes: (PROCEDURE STATEMENT-PROC FUNCTION)
value: __exp_r8[[((main:z))]]
Formal arglist: z
code:
and LFortran's corresponding ASR looks like this:
(TranslationUnit
(SymbolTable
1
{
iso_c_binding:
(IntrinsicModule lfortran_intrinsic_iso_c_binding),
iso_fortran_env:
(IntrinsicModule lfortran_intrinsic_iso_fortran_env),
lfortran_intrinsic_builtin:
(IntrinsicModule lfortran_intrinsic_builtin),
lfortran_intrinsic_math:
(IntrinsicModule lfortran_intrinsic_math),
main:
(Program
(SymbolTable
2
{
dexp:
(ExternalSymbol
2
dexp
4 dexp
lfortran_intrinsic_math
[]
dexp
Private
),
z:
(Variable
2
z
Local
()
()
Default
(Real 8 [])
Source
Public
Required
.false.
),
zexp:
(Variable
2
zexp
Local
()
()
Default
(Real 8 [])
Source
Public
Required
.false.
)
})
main
[]
[(=
(ArrayItem
(Var 2 zexp)
[(()
(Var 2 z)
())]
(Real 8 [])
()
)
(FunctionCall
2 dexp
()
[((Var 2 z))]
(Real 8 [])
()
()
)
()
)]
)
})
[]
)
I think this is an example of a statement function, which we need to implement according to https://github.com/lfortran/lfortran/issues/814.
When trying to compile
scipy/stats/statlib/swilk.f
from current main, LFortran yields an empty object file -- upon inspection and runninglfortran --implicit-typing --fixed-form --show-llvm --indent ../../scipy/scipy/stats/statlib/swilk.f
we seeand core gets dumped.