AST 和 ASR 之间的区别

让我们看一个简单的 Fortran 代码:

integer function f(a, b) result(r)
integer, intent(in) :: a, b
integer :: c, d
c = a + b - d
r = c * a
end function

and look at what the AST and ASR look like.

AST

[1]:
%%showast
integer function f(a, b) result(r)
integer, intent(in) :: a, b
integer :: c, d
c = a + b - d
r = c * a
end function
(TranslationUnit [(Function f [(a) (b)] [(AttrType TypeInteger [] () None)] r () () [] [] [] [(Declaration (AttrType TypeInteger [] () None) [(AttrIntent In)] [(a [] [] () None ()) (b [] [] () None ())] ()) (Declaration (AttrType TypeInteger [] () None) [] [(c [] [] () None ()) (d [] [] () None ())] ())] [(= 0 c (- (+ a b) d) ()) (= 0 r (* c a) ())] [])])

AST 没有任何语义信息,但具有表示声明的节点,例如 integer, intent(in) :: a。诸如 a 之类的变量由 Name 节点表示,并且尚未连接到它们的声明。

The AST can also be exported in JSON, including source file name, line and column information: lfortran example.f90 --show-ast --json

ASR

[2]:
%%showasr
integer function f(a, b) result(r)
integer, intent(in) :: a, b
integer :: c, d
c = a + b - d
r = c * a
end function
(TranslationUnit (SymbolTable 1 {f: (Function (SymbolTable 2 {a: (Variable 2 a [] In () () Default (Integer 4 []) Source Public Required .false.), b: (Variable 2 b [] In () () Default (Integer 4 []) Source Public Required .false.), c: (Variable 2 c [] Local () () Default (Integer 4 []) Source Public Required .false.), d: (Variable 2 d [] Local () () Default (Integer 4 []) Source Public Required .false.), r: (Variable 2 r [] ReturnVar () () Default (Integer 4 []) Source Public Required .false.)}) f (FunctionType [(Integer 4 []) (Integer 4 [])] (Integer 4 []) Source Implementation () .false. .false. .false. .false. .false. [] [] .false.) [] [(Var 2 a) (Var 2 b)] [(= (Var 2 c) (IntegerBinOp (IntegerBinOp (Var 2 a) Add (Var 2 b) (Integer 4 []) ()) Sub (Var 2 d) (Integer 4 []) ()) ()) (= (Var 2 r) (IntegerBinOp (Var 2 c) Mul (Var 2 a) (Integer 4 []) ()) ())] (Var 2 r) Public .false. .false.)}) [])

ASR 有所有的语义信息(类型等),像 Function 这样的节点有一个符号表,没有任何声明节点。变量只是指向符号表的指针。

The ASR can also be exported in JSON, including source file name, line and column information: lfortran example.f90 --show-asr --json

讨论

上面是一个简单的例子。对于更复杂的示例,事情变得更加明显,例如:

integer function f2b(a) result(r)
use gfort_interop, only: c_desc1_int32
integer, intent(in) :: a(:)
interface
    integer function f2b_c_wrapper(a) bind(c, name="__mod1_MOD_f2b")
    use gfort_interop, only: c_desc1_t
    type(c_desc1_t), intent(in) :: a
    end function
end interface
r = f2b_c_wrapper(c_desc1_int32(a))
end function

AST 必须代表所有的 use 语句和 interface 块,并保持语义一致。

另一方面,ASR 跟踪符号表中的 c_desc1_int32c_desc1_tf2b_c_wrapper,并且知道它们是在 gfort_interop 模块中定义的,因此 ASR 没有任何这些声明节点。

从 ASR 转换为 AST 时,LFortran 将自动且正确地创建所有适当的 AST 声明节点。