Rozdíly mezi AST a ASR

Vezměme tento jednoduchý zdrojový kód ve Fortranu:

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
            ())]
            ()
        )]
        [(Assignment
            0
            c
            (- (+ a b) d)
            ()
        )
        (Assignment
            0
            r
            (* c a)
            ()
        )]
        []
        []
    )]
)

AST nemá žádné semantické informace, ale má uzly které reprezentují deklarace jako integer, intent(in) :: a. Proměnné jako a jsou reprezentovány uzlem Name a nejsou ještě propojeny se svými deklaracemi.

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)]
                    [(Assignment
                        (Var 2 c)
                        (IntegerBinOp
                            (IntegerBinOp
                                (Var 2 a)
                                Add
                                (Var 2 b)
                                (Integer 4)
                                ()
                            )
                            Sub
                            (Var 2 d)
                            (Integer 4)
                            ()
                        )
                        ()
                    )
                    (Assignment
                        (Var 2 r)
                        (IntegerBinOp
                            (Var 2 c)
                            Mul
                            (Var 2 a)
                            (Integer 4)
                            ()
                        )
                        ()
                    )]
                    (Var 2 r)
                    Public
                    .false.
                    .false.
                    ()
                )
        })
    []
)

ASR má všechny semantické informace (typy, atd.), uzly jako Function mají tabulku symbolů a nemají uzly s deklaracemi. Proměnné jsou přímo ukazatelé do tabulky symbolů.

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

Diskuze

Nahoře byl jednoduchý příklad. Věci budou jasnější když si rozebereme komplikovanější problémy, jako například:

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 musí reprezentovat všechny use řádky a interface blok a ASR uzly musí být semanticky konzistentní.

ASR, on the other hand, keeps track of the c_desc1_int32, c_desc1_t and f2b_c_wrapper in the symbol table and it knows they are defined in the gfort_interop module, and so ASR does not have any of these declaration nodes.

When converting from ASR to AST, LFortran will create all the appropriate AST declaration nodes automatically and correctly.