Tutorial für Entwickler

Dies ist ein Tutorial für alle, die entweder LFortran entwickeln oder darauf aufbauende Werkzeuge erstellen wollen.

Einführung

LFortran ist um zwei unabhängige Module herum aufgebaut, AST und ASR, die beide eigenständig sind (völlig unabhängig vom Rest von LFortran), und die Benutzer werden ermutigt, sie unabhängig für andere Anwendungen zu verwenden und darauf aufbauende Werkzeuge zu erstellen:

  • Abstract Syntax Tree (AST): Represents any Fortran source code, strictly based on syntax, no semantic is included. The AST module can convert itself to Fortran source code.

  • Abstract Semantic Representation (ASR): Represents a valid Fortran source code, all semantic is included. Invalid Fortran code is not allowed (an error will be given). The ASR module can convert itself to an AST.

Abstrakter Syntaxbaum (AST)

Fortran source code can be parsed into an AST using the src_to_ast() function:

[1]:
integer function f(a, b) result(r)
integer, intent(in) :: a, b
r = a + b
end function

We can pretty print it using the %%showast magic:

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

We can convert AST to Fortran source code using %%showfmt:

[3]:
%%showfmt
integer function f(a, b) result(r)
integer, intent(in) :: a, b
r = a + b
end function
integer function f(a, b) result(r)
integer, intent(in) :: a, b
r = a + b
end function f

All AST nodes and their arguments are described in AST.asdl.

Abstrakte semantische Repräsentation (ASR)

We can pretty print using the %%showasr magic:

[4]:
%%showasr
integer function f(a, b) result(r)
integer, intent(in) :: a, b
r = a + b
end function
(TranslationUnit
    (SymbolTable
        1
        {
            f:
                (Function
                    (SymbolTable
                        3
                        {
                            a:
                                (Variable
                                    3
                                    a
                                    []
                                    In
                                    ()
                                    ()
                                    Default
                                    (Integer 4)
                                    ()
                                    Source
                                    Public
                                    Required
                                    .false.
                                ),
                            b:
                                (Variable
                                    3
                                    b
                                    []
                                    In
                                    ()
                                    ()
                                    Default
                                    (Integer 4)
                                    ()
                                    Source
                                    Public
                                    Required
                                    .false.
                                ),
                            r:
                                (Variable
                                    3
                                    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 3 a)
                    (Var 3 b)]
                    [(Assignment
                        (Var 3 r)
                        (IntegerBinOp
                            (Var 3 a)
                            Add
                            (Var 3 b)
                            (Integer 4)
                            ()
                        )
                        ()
                    )]
                    (Var 3 r)
                    Public
                    .false.
                    .false.
                    ()
                )
        })
    []
)

All ASR nodes and their arguments are described in ASR.asdl.