Compiler in Python: PL / 0 Abstract Syntax Tree (AST)

This goal

Last time understood the pyparsing function needed to create a parse tree. This time, we will generate the third abstract syntax tree (AST).

  1. Break it down into tokens with a parser.
  2. How to create a syntax tree from tokens, create a syntax tree for expressions
  3. Generate an abstract syntax tree (AST) using setParseAction () <-Now here
  4. Follow the AST node to generate the code.

AST node

Keep the following in mind when defining a node:

Then it is an implementation. Create a new file called pl0_nodes.py. This file does not import pyparsing. The base class is just a method that prints the class name, field name and value when printed. Note that this class mimics the ** Python ast.AST node. ** **

pl0_nodes.py


# PL0 Abstract Syntax Tree Nodes
# This file must be free from pyparsing implementation!!

class ASTNode(object):
    _fields = ()

    def __repr__(self):
        return "{}({})".format(
            self.__class__.__name__,
            ', '.join(["%s=%s" % (field, getattr(self, field))
	               for field in self._fields])
	)

Implement VAR as a concrete example. The variable declaration is Variables, and the variable itself is Var.

class Variables(ASTNode):
    _fields = ('variables',)
    def __init__(self, variables):
        self.variables = variables

class Var(ASTNode):
    _fields = ('id',)
    def __init__(self, id):
        self.id = id

I will test it.

x = Var('x')
y = Var('y')

variables = Variables([x, y])

print variables

The result is a nested AST with Variables as vertices:

Variables(variables=[Var(id=x), Var(id=y)])

AST generator

[As I did last time](http://qiita.com/knoguchi/items/6f9b7383b7252a9ebdad#%E3%81%A1%E3%82%87%E3%81%A3%E3%81%A8%E9%AB % 98% E5% BA% A6% E3% 81% AA% E4% BD% BF% E3% 81% 84% E6% 96% B9) You can start the Variables class directly with setParseAction, but then the constructor Since the argument of is a token of pyparsing and it becomes tightly coupled, and I also want to track the declared identifier, I will introduce an AST generator in between.

make_variables is a function called from setParseAction, which creates an object of the Var class while processing the list of variable names in the second token in a loop. At the same time, the identifier is stored in the symbol table. If you have a symbol table, you can use it for checking errors in double definition of variables and allocating memory when generating code.

pl0_ast.py


from pl0_nodes import Var, Variables

class AstGenerator(object):
    def __init__(self):
        self.symbol_table = {}

    def make_name(self, tokens):
        tokens = tokens.asList()
	assert len(tokens) == 1
        return Name(tokens[0])

    def make_variables(self, tokens):
        tokens = tokens.asList()
	idents = tokens[1]
	variables = []
        for ident in idents:
            node = Var(ident)
            self.symbol_table[ident.id] = node
            variables.append(node)
        return Variables(variables)

Let's actually call it from the parser. Create an instance at the beginning and set variables.setParseAction.

pl0_parser.py


from pl0_ast import AstGenerator

ast = AstGenerator()

...

# 11. var
var_dec = ident
variables = VAR + Group(var_dec + ZeroOrMore(COMMA + var_dec)) + SEMICOLON
variables.setParseAction(ast.make_variables)

When tested, the AST is generated correctly. If you look inside the symbol table, you can see that x and y are variables!

>>> print variables.parseString('VAR x, y;')
[Variables(variables=[Var(id=Name(id=x)), Var(id=Name(id=y))])]

>>> print ast.symbol_table
{'y': Var(id=Name(id=y)), 'x': Var(id=Name(id=x))}

Add code to dump the symbol_table after parsing.

    print "== symbol table =="
    for k, v in ast.symbol_table.items():
        print "%10s  %10s" % (k, v.__class__.__name__)

Let's parse the sample ex1.pl0.

[Variables(variables=[Var(id=Name(id=x)), Var(id=Name(id=squ))]), ['PROCEDURE', Name(id=square), Name(id=squ), [Name(id=x), '*', Name(id=x)]], Name(id=x), '1', 'WHILE', [Name(id=x), '<=', '10'], 'DO', 'CALL', Name(id=square), Name(id=x), [Name(id=x), '+', '1']]
== symbol table ==
         x         Var
       squ         Var

Implemented earnestly

After that, we will implement and stack from the deepest part in sequence. It is easy to test because it requires a minimum of unimplemented dependencies.

assign --assignment statement

Substitution simply sets the right side to the left side.

pl0_nodes.py


class Assign(ASTNode):
    _fields = ('left', 'right')
    def __init__(self, left, right):
        self.left = left
        self.right = right

ast generator

pl0_ast.py


    def make_assign(self, tokens):
        tokens = tokens.asList()
        left = tokens[0]
        right = tokens[1]
        return Assign(left, right)

Looking at the test result of the identifier,': ='was displayed, but since it is a wreckage at the time of parsing, let's Suppress.

pl0_parser.py


ASSIGN = Suppress(':=')

...

# 5. assignment
assign_statement = ident + ASSIGN + expression
assign_statement.setParseAction(ast.make_assign)

test.

[Variables(variables=[Var(id=Name(id=x)), Var(id=Name(id=squ))]), ['PROCEDURE', Name(id=square), Assign(left=Name(id=squ), right=[Name(id=x), '*', Name(id=x)])], Assign(left=Name(id=x), right=1), 'WHILE', [Name(id=x), '<=', '10'], 'DO', 'CALL', Name(id=square), Assign(left=Name(id=x), right=[Name(id=x), '+', '1'])]
== symbol table ==
         x         Var
       squ         Var

call-procedure call

Currently, call only takes procedure, but if you extend it to callable, you can also implement a function.

pl0_nodes.py


class Call(ASTNode):
    _fields = ('procedure',)
    def __init__(self, procedure):
        self.procedure = procedure

pl0_ast.py


    def make_call(self, tokens):
        tokens = tokens.asList()
        ident = tokens[1]
	return Call(ident)

pl0_parser.py


call_statement.setParseAction(ast.make_call)

test results.

[Variables(variables=[Var(id=Name(id=x)), Var(id=Name(id=squ))]), ['PROCEDURE', Name(id=square), Assign(left=Name(id=squ), right=[Name(id=x), '*', Name(id=x)])], Assign(left=Name(id=x), right=1), 'WHILE', [Name(id=x), '<=', '10'], 'DO', Call(procedure=Name(id=square)), Assign(left=Name(id=x), right=[Name(id=x), '+', '1'])]
== symbol table ==
         x         Var
       squ         Var

if statement

The IF statement takes a conditional expression and the body to be executed.

pl0_nodes.py


class If(ASTNode):
    _fields = ('condition', 'body')
    def __init__(self, condition, body):
        self.condition = test
        self.body = body

Ignore tokens [2] because it contains'THEN'. It was okay to Suppress all the reserved words. It may be difficult to debug.

pl0_ast.py


    def make_if(self, tokens):
        tokens = tokens.asList()
        condition = tokens[1]
        body = tokens[3]
        return If(condition, body)

pl0_parser.py


if_statement.setParseAction(ast.make_if)

When I thought about testing ..., there was no IF statement in ex1.pl0, so I will test it appropriately. There seems to be no problem.

>>> print if_statement.parseString('IF a = b THEN call c')
[If(condition=[Name(id=a), '=', Name(id=b)], body=Call(procedure=Name(id=c)))]

while statement

It is exactly the same as the IF statement.

class While(ASTNode):
    _fields = ('condition', 'body')
    def __init__(self, condition, body):
        self.condition = condition
        self.body = body

pl0_ast.py


    def make_while(self, tokens):
        tokens = tokens.asList()
        condition = tokens[1]
        body = tokens[3]
        return While(condition, body)

pl0_parser.py


while_statement.setParseAction(ast.make_while)

test

[Variables(variables=[Var(id=Name(id=x)), Var(id=Name(id=squ))]), ['PROCEDURE', Name(id=square), Assign(left=Name(id=squ), right=[Name(id=x), '*', Name(id=x)])], Assign(left=Name(id=x), right=1), While(condition=[Name(id=x), '<=', '10'], body=Call(procedure=Name(id=square)))]
== symbol table ==
         x         Var
       squ         Var

multi statements --Complex sentences

BEGIN-END is a collection of multiple sentences. Since setParseAction cannot be set with a parser transcribed from the original BNF, I have put it together.

pl0_parser.py


# 9. statement
multi_statements = BEGIN.suppress() + statement + ZeroOrMore(SEMICOLON + statement) + END.suppress()

statement << Optional(assign_statement
                      | call_statement
                      | multi_statements
                      | if_statement
                      | while_statement
)

multi_statements.setParseAction(ast.make_multi_statements)

pl0_nodes.py


class MultiStatements(ASTNode):
    _fields = ('statements',)
    def __init__(self, statements):
        self.statements = statements

pl0_ast.py


    def make_multi_statements(self, tokens):
        tokens = tokens.asList()
        return MultiStatements(tokens)

test results.

[Variables(variables=[Var(id=Name(id=x)), Var(id=Name(id=squ))]), ['PROCEDURE', Name(id=square), MultiStatements(statements=[Assign(left=Name(id=squ), right=[Name(id=x), '*', Name(id=x)])])], MultiStatements(statements=[Assign(left=Name(id=x), right=1), While(condition=[Name(id=x), '<=', '10'], body=MultiStatements(statements=[Call(procedure=Name(id=square)), Assign(left=Name(id=x), right=[Name(id=x), '+', '1'])]))])]
== symbol table ==
         x         Var
       squ         Var

const, var, procedure

I implemented the following with the same pattern.

constants.setParseAction(ast.make_constants)
variables.setParseAction(ast.make_variables)
procedures.setParseAction(ast.make_procedures)

test

[Variables(variables=[Var(id=Name(id=x)), Var(id=Name(id=squ))]), Procedures(procedures=[Procedure(id=Name(id=square), body=MultiStatements(statements=[Assign(left=Name(id=squ), right=[Name(id=x), '*', Name(id=x)])]))]), MultiStatements(statements=[Assign(left=Name(id=x), right=1), While(condition=[Name(id=x), '<=', '10'], body=MultiStatements(statements=[Call(procedure=Name(id=square)), Assign(left=Name(id=x), right=[Name(id=x), '+', '1'])]))])]
== symbol table ==
         x         Var
    square   Procedure
       squ         Var

block

The block has an Optional field, so you can't tell what's set just by the token position. I couldn't think of a good way, so I decided to use isinstance () to determine the type of the class. Each statement class changes its parent class from ASTNode to Statement class.

pl0_nodes.py


class Statement(ASTNode):
    pass

class MultiStatements(Statement):
class Assign(Statement):
class If(Statement):
class While(Statement):
class Call(Statement):

class Block(ASTNode):
    _fields = ('constants', 'variables', 'procedures', 'statements')
    def __init__(self, constants, variables, procedures, statements):
        self.constants = constants
        self.variables = variables
	self.procedures = procedures
	self.statements = statements

pl0_ast.py


   def make_block(self, tokens):
        constants = None
        variables = None
        procedures = None
        statements = None
        for token in tokens.asList():
            if isinstance(token, Constants):
                const = token
            elif isinstance(token, Variables):
                var = token
            elif isinstance(token, Procedures):
                procedures = token
            elif isinstance(token, Statement):
                statements = token
            else:
                raise ValueError(token)

        return Block(constants, variables, procedures, statements)

test results. It is nested with the Program () node as the apex. It's difficult to shape, so I shaped it by hand.

Program(
 block=
  Block(
   constants=
   variables=
   procedures=
    Procedures(
     procedures=
      Procedure(
       id=
        'square'
       body=
        Block(
         constants=
         variables=
         procedures=
         statements=
          MultiStatements(
           statements=
            Assign(
             left=
              'squ'
             right=
              'x'
              *
              'x'
            )
          )
        )
      )
    )
   statements=
    MultiStatements(
     statements=
      Assign(
       left=
        'x'
       right=
        1
      )
      While(
       condition=
        'x'
        <=
        10
       body=
        MultiStatements(
         statements=
          Call(
           procedure=
            'square'
          )
          Assign(
           left=
            'x'
           right=
            'x'
            +
            1
          )
        )
      )
    )
  )
)
== symbol table ==
         x         Var
    square   Procedure
       squ         Var

AST completed ...? No, the formula is still a list of tokens.

expression --expression

Last time I looked at infixNotation for pyparsing, but if you add an argument, you can do the same thing as setParseAction.

Click here for the current status.

pl0_parser_before.py


expression = infixNotation(
    factor,
    [
     	(oneOf("+ -"), UNARY, opAssoc.RIGHT),
        (oneOf("* /"), BINARY, opAssoc.LEFT),
        (oneOf("+ -"), BINARY, opAssoc.LEFT),
    ]
)

Add a callback.

pl0_parser_after.py


expression = infixNotation(
    factor,
    [
     	(oneOf("+ -"), UNARY, opAssoc.RIGHT, ast.make_unary_op),  
        (oneOf("* /"), BINARY, opAssoc.LEFT, ast.make_binary_op),
        (oneOf("+ -"), BINARY, opAssoc.LEFT, ast.make_binary_op),
    ]
)

condition = infixNotation(
    expression,
    [
        (ODD, UNARY, opAssoc.RIGHT, ast.make_unary_op),
        (oneOf("< <= > >="), BINARY, opAssoc.LEFT, ast.make_binary_op),
        (oneOf("= #"), BINARY, opAssoc.LEFT, ast.make_binary_op),
    ]
)

make_binary_op changes the node class to be instantiated by the operator symbol. Also, when multiple equal operators are consecutive, pyparsing sends a token [1 + 2 + 3], so I wrote a function called convert () to convert it to a binary operation. This will convert it to the format [[1 + 2] + 3] and generate an AST called Add (Add (1, 2), 3).

result

[Program(block=Block(constants=None, variables=None, procedures=Procedures(procedures=[Procedure(id=Name(id=square), body=Block(constants=None, variables=None, procedures=None, statements=MultiStatements(statements=[Assign(left=Name(id=squ), right=Mult(left=Name(id=x), right=Name(id=x)))])))]), statements=MultiStatements(statements=[Assign(left=Name(id=x), right=1), While(condition=LtE(left=Name(id=x), right=10), body=MultiStatements(statements=[Call(procedure=Name(id=square)), Assign(left=Name(id=x), right=Add(left=Name(id=x), right=1))]))])))]
== symbol table ==
         x         Var
    square   Procedure
       squ         Var

Source code

pl0_parser.py


# -*- coding: utf-8 -*-
from pyparsing import *
from pl0_ast import AstGenerator

ast = AstGenerator()

LPAR, RPAR, COMMA, SEMICOLON, DOT = map(Suppress, "(),;.")
ASSIGN = Suppress(':=')

# 1. reserved keyword
(CONST, VAR, PROCEDURE, CALL, BEGIN, END, IF, THEN, WHILE, DO, ODD) = map(CaselessKeyword,
"CONST, VAR, PROCEDURE, CALL, BEGIN, END, IF, THEN, WHILE, DO, ODD".replace(",", "").split())
keyword = MatchFirst((CONST, VAR, PROCEDURE, CALL, BEGIN, END, IF, THEN, WHILE, DO, ODD))

# 2. identifier
ident = ~keyword + Word(alphas, alphanums + "_")

# 3. expression
number = Regex(r"\d+(\.\d*)?([eE][+-]?\d+)?")
UNARY, BINARY, TERNARY = 1, 2, 3
factor = ident | number
expression = infixNotation(
    factor,
    [
        (oneOf("+ -"), UNARY, opAssoc.RIGHT, ast.make_unary_op),  #Code has the highest priority
        (oneOf("* /"), BINARY, opAssoc.LEFT, ast.make_binary_op),  #Multiplication and division take precedence over addition and subtraction
        (oneOf("+ -"), BINARY, opAssoc.LEFT, ast.make_binary_op),
    ]
)

# 4. condition
#condition = ODD + expression | expression + oneOf('= # < <= > >=') + expression
condition = infixNotation(
    expression,
    [
        (ODD, UNARY, opAssoc.RIGHT, ast.make_unary_op),
        (oneOf("< <= > >="), BINARY, opAssoc.LEFT, ast.make_binary_op),
        (oneOf("= #"), BINARY, opAssoc.LEFT, ast.make_binary_op),
    ]
)

# 5. assignment
assign_statement = ident + ASSIGN + expression

# 6. call
call_statement = CALL + ident

# 7. if-then
statement = Forward()
if_statement = IF + condition + THEN + statement

# 8. while-do
while_statement = WHILE + condition + DO + statement

# 9. statement
multi_statements = BEGIN.suppress() + statement + ZeroOrMore(SEMICOLON + statement) + END.suppress()

statement << Optional(assign_statement
                      | call_statement
                      | multi_statements
                      | if_statement
                      | while_statement
)

# 10. const
const_dec = Group(ident + "=" + number)
constants = CONST + Group(const_dec + ZeroOrMore(COMMA + const_dec)) + SEMICOLON

# 11. var
var_dec = ident
variables = VAR + Group(var_dec + ZeroOrMore(COMMA + var_dec)) + SEMICOLON

# 12. procedure
block = Forward()
procedure_dec = Group(PROCEDURE + ident + SEMICOLON + block + SEMICOLON)
procedures = OneOrMore(procedure_dec)

# 13. block
block << Optional(constants) + Optional(variables) + Optional(procedures) + statement

# 14. program
program = block + DOT

# set callbacks
ident.setParseAction(ast.make_name)
assign_statement.setParseAction(ast.make_assign)
call_statement.setParseAction(ast.make_call)
if_statement.setParseAction(ast.make_if)
while_statement.setParseAction(ast.make_while)
multi_statements.setParseAction(ast.make_multi_statements)
constants.setParseAction(ast.make_constants)
variables.setParseAction(ast.make_variables)
procedures.setParseAction(ast.make_procedures)
block.setParseAction(ast.make_block)
program.setParseAction(ast.make_program)

if __name__ == '__main__':
    import sys
    with open(sys.argv[1], 'r') as fp:
        txt = fp.read()
        res = program.parseString(txt)
        print res

    print "== symbol table =="
    for k, v in ast.symbol_table.items():
        print "%10s  %10s" % (k, v.__class__.__name__)

pl0_ast.py


from pl0_nodes import *

class AstGenerator(object):
    """
    Generates AST.
    This class is tightly coupled with the pl0_paser.
    """
    def __init__(self):
        self.symbol_table = {}

    def make_name(self, tokens):
        tokens = tokens.asList()
        assert len(tokens) == 1
        return Name(tokens[0])

    def make_constants(self, tokens):
        tokens = tokens.asList()
        constants = []
        for token in tokens[1]:
            lhs = token[0]
            rhs = token[2]
            node = Const(id=lhs, value=rhs)
            self.symbol_table[lhs.id] = node
            constants.append(node)
        return Constants(constants)

    def make_variables(self, tokens):
        tokens = tokens.asList()
        idents = tokens[1]
        variables = []
        for ident in idents:
            node = Var(ident)
            self.symbol_table[ident.id] = node
            variables.append(node)
        return Variables(variables)

    def make_procedures(self, tokens):
        tokens = tokens.asList()
        procedures = []
        for token in tokens:
            name, body = token[1], token[2]
            node = Procedure(name, body)
            self.symbol_table[name.id] = node
            procedures.append(node)
        return Procedures(procedures)

    # statements
    def make_multi_statements(self, tokens):
        tokens = tokens.asList()
        return MultiStatements(tokens)

    def make_if(self, tokens):
        tokens = tokens.asList()
        condition = tokens[1]
        body = tokens[3]
        return If(condition, body)

    def make_while(self, tokens):
        tokens = tokens.asList()
        condition = tokens[1]
        body = tokens[3]
        return While(condition, body)

    def make_call(self, tokens):
        tokens = tokens.asList()
        ident = tokens[1]
        return Call(ident)

    def make_assign(self, tokens):
        tokens = tokens.asList()
        left = tokens[0]
        right = tokens[1]
        return Assign(left, right)

    # unary operators
    def make_unary_op(self, tokens=None):
        tokens = tokens.asList()[0]
        op = tokens[0]
        _op_map = {
            'ODD': Odd,
            '-': Neg
            }
        cls = _op_map[op]
        return cls(op, tokens[1])

    # binary operators
    def make_binary_op(self, tokens):
        _op_map = {
            'ODD': Odd,
            '+': Add,
            '-': Sub,
            '*': Mult,
            '/': Div,
            '<': Lt,
            '<=': LtE,
            '>': Gt,
            '>=': GtE,
            '=': Eq,
            '#': Ne,
        }

        def convert(l):
            stack = []
            l = iter(l)
            for e in l:
                if e in _op_map:
                    cls = _op_map[e]
                    left = stack.pop()
                    right = next(l)
                    stack.append(cls(left, e, right))
                else:
                    stack.append(e)
            return stack.pop()

        tokens = tokens.asList()[0]
        return convert(tokens)

    # block
    def make_block(self, tokens):
        constants = None
        variables = None
        procedures = None
        statements = None
        for token in tokens.asList():
            if isinstance(token, Constants):
                const = token
            elif isinstance(token, Variables):
                var = token
            elif isinstance(token, Procedures):
                procedures = token
            elif isinstance(token, Statement):
                statements = token
            else:
                raise ValueError(token)

        return Block(constants, variables, procedures, statements)

    # program
    def make_program(self, tokens):
        tokens = tokens.asList()
        assert len(tokens) == 1, len(tokens)
        block = tokens[0]
        return Program(block)

pl0_nodes.py


# PL0 Abstract Syntax Tree Nodes
# This file must be free from pyparsing implementation!!

class ASTNode(object):
    SPACER = " "
    _fields = ()

    def __repr__(self):
        return "{}({})".format(
            self.__class__.__name__,
            ', '.join(["%s=%s" % (field, getattr(self, field))
                       for field in self._fields])
        )
    
    def _p(self, v, indent):
        print "{}{}".format(self.SPACER * indent, v)
        
    def dumps(self, indent=0):
        self._p(self.__class__.__name__ + '(', indent)
        for field in self._fields:
            self._p(field + '=', indent + 1)
            value = getattr(self, field)
            if type(value) == list:
                for value2 in value:
                    if isinstance(value2, ASTNode):
                        value2.dumps(indent + 2)
                    else:
                        self._p(value2, indent + 2)
            else:
                if value:
                    if isinstance(value, ASTNode):
                        value.dumps(indent + 2)
                    else:
                        self._p(value, indent + 2)
        self._p(')', indent)
                    

# Literals
class Num(ASTNode):
    _fields = ('n',)

    def __init__(self, n):
        self.n = n


# Variables
class Name(ASTNode):
    _fields = ('id',)

    def __init__(self, id):
        self.id = id

    def dumps(self, indent=0):
        print "{}'{}'".format(self.SPACER * indent, self.id)

        
class Const(ASTNode):
    _fields = ('id', 'value',)

    def __init__(self, id, value):
        self.id = id
        self.value = value


class Constants(ASTNode):
    _fields = ('constants',)

    def __init__(self, constants):
        self.constants = constants


# Expressions
class Expr(ASTNode):
    _fields = ('value',)

    def __init__(self, value):
        self.value = value


# unary operators
class UnaryOp(ASTNode):
    _fields = ('op', 'right')

    def __init__(self, op, right):
        self.op = op
        self.right = right


class Odd(UnaryOp):
    pass

class Neg(UnaryOp):
    pass

class Not(UnaryOp):
    pass


# binary operatos
class BinOp(ASTNode):
    _fields = ('left', 'right')
    def __init__(self, left, op, right):
        self.left = left
        self.right = right


class Add(BinOp):
    pass


class Sub(BinOp):
    pass


class Mult(BinOp):
    pass


class Div(BinOp):
    pass


class And(BinOp):
    pass


class Or(BinOp):
    pass

class Eq(BinOp):
    pass


class Ne(BinOp):
    pass


class Lt(BinOp):
    pass


class LtE(BinOp):
    pass


class Gt(BinOp):
    pass


class GtE(BinOp):
    pass


# statement
class Statement(ASTNode):
    pass


class MultiStatements(Statement):
    _fields = ('statements',)
    def __init__(self, statements):
        self.statements = statements


class Assign(Statement):
    _fields = ('left', 'right')
    def __init__(self, left, right):
        self.left = left
        self.right = right


# control flow
class If(Statement):
    _fields = ('condition', 'body')
    def __init__(self, condition, body):
        self.condition = condition
        self.body = body


class While(Statement):
    _fields = ('condition', 'body')
    def __init__(self, condition, body):
        self.condition = condition
        self.body = body


class Call(Statement):
    _fields = ('procedure',)
    def __init__(self, procedure):
        self.procedure = procedure


# Declaration
class Var(ASTNode):
    _fields = ('id',)
    def __init__(self, id):
        self.id = id


class Variables(ASTNode):
    _fields = ('variables',)

    def __init__(self, variables):
        self.variables = variables


class Procedure(ASTNode):
    _fields = ('id', 'body')
    def __init__(self, id, body):
        self.id = id
        self.body = body

class Procedures(ASTNode):
    _fields = ('procedures',)
    def __init__(self, procedures):
        self.procedures = procedures


# block
class Block(ASTNode):
    _fields = ('constants', 'variables', 'procedures', 'statements')
    def __init__(self, constants, variables, procedures, statements):
        self.constants = constants
        self.variables = variables
        self.procedures = procedures
        self.statements = statements


# Program
class Program(ASTNode):
    _fields = ('block',)
    def __init__(self, block):
        self.block = block

bonus

Wikipedia PL / 0 sample code

ex2.pl0


CONST
  m =  7,
  n = 85;

VAR
  x, y, z, q, r;

PROCEDURE multiply;
VAR a, b;

BEGIN
  a := x;
  b := y;
  z := 0;
  WHILE b > 0 DO BEGIN
    IF ODD b THEN z := z + a;
    a := 2 * a;
    b := b / 2;
  END
END;

PROCEDURE divide;
VAR w;
BEGIN
  r := x;
  q := 0;
  w := y;
  WHILE w <= r DO w := 2 * w;
  WHILE w > y DO BEGIN
    q := 2 * q;
    w := w / 2;
    IF w <= r THEN BEGIN
      r := r - w;
      q := q + 1
    END
  END
END;

PROCEDURE gcd;
VAR f, g;
BEGIN
  f := x;
  g := y;
  WHILE f # g DO BEGIN
    IF f < g THEN g := g - f;
    IF g < f THEN f := f - g;
  END;
  z := f
END;

BEGIN
  x := m;
  y := n;
  CALL multiply;
  x := 25;
  y :=  3;
  CALL divide;
  x := 84;
  y := 36;
  CALL gcd;
END.

Perspective result

[Program(block=Block(constants=None, variables=None, procedures=Procedures(procedures=[Procedure(id=Name(id=multiply), body=Block(constants=None, variables=None, procedures=None, statements=MultiStatements(statements=[Assign(left=Name(id=a), right=Name(id=x)), Assign(left=Name(id=b), right=Name(id=y)), Assign(left=Name(id=z), right=0), While(condition=Gt(left=Name(id=b), right=0), body=MultiStatements(statements=[If(condition=Odd(op=ODD, right=Name(id=b)), body=Assign(left=Name(id=z), right=Add(left=Name(id=z), right=Name(id=a)))), Assign(left=Name(id=a), right=Mult(left=2, right=Name(id=a))), Assign(left=Name(id=b), right=Div(left=Name(id=b), right=2))]))]))), Procedure(id=Name(id=divide), body=Block(constants=None, variables=None, procedures=None, statements=MultiStatements(statements=[Assign(left=Name(id=r), right=Name(id=x)), Assign(left=Name(id=q), right=0), Assign(left=Name(id=w), right=Name(id=y)), While(condition=LtE(left=Name(id=w), right=Name(id=r)), body=Assign(left=Name(id=w), right=Mult(left=2, right=Name(id=w)))), While(condition=Gt(left=Name(id=w), right=Name(id=y)), body=MultiStatements(statements=[Assign(left=Name(id=q), right=Mult(left=2, right=Name(id=q))), Assign(left=Name(id=w), right=Div(left=Name(id=w), right=2)), If(condition=LtE(left=Name(id=w), right=Name(id=r)), body=MultiStatements(statements=[Assign(left=Name(id=r), right=Sub(left=Name(id=r), right=Name(id=w))), Assign(left=Name(id=q), right=Add(left=Name(id=q), right=1))]))]))]))), Procedure(id=Name(id=gcd), body=Block(constants=None, variables=None, procedures=None, statements=MultiStatements(statements=[Assign(left=Name(id=f), right=Name(id=x)), Assign(left=Name(id=g), right=Name(id=y)), While(condition=Ne(left=Name(id=f), right=Name(id=g)), body=MultiStatements(statements=[If(condition=Lt(left=Name(id=f), right=Name(id=g)), body=Assign(left=Name(id=g), right=Sub(left=Name(id=g), right=Name(id=f)))), If(condition=Lt(left=Name(id=g), right=Name(id=f)), body=Assign(left=Name(id=f), right=Sub(left=Name(id=f), right=Name(id=g))))])), Assign(left=Name(id=z), right=Name(id=f))])))]), statements=MultiStatements(statements=[Assign(left=Name(id=x), right=Name(id=m)), Assign(left=Name(id=y), right=Name(id=n)), Call(procedure=Name(id=multiply)), Assign(left=Name(id=x), right=25), Assign(left=Name(id=y), right=3), Call(procedure=Name(id=divide)), Assign(left=Name(id=x), right=84), Assign(left=Name(id=y), right=36), Call(procedure=Name(id=gcd))])))]
== symbol table ==
         a         Var
         b         Var
    divide   Procedure
         g         Var
         f         Var
         m       Const
         n       Const
         q         Var
  multiply   Procedure
         r         Var
         w         Var
         y         Var
         x         Var
         z         Var
       gcd   Procedure

Recommended Posts

Compiler in Python: PL / 0 Abstract Syntax Tree (AST)
Compiler in Python: PL / 0 syntax tree
Compiler in Python: PL / 0 parser
How to parse Java source code with AST (Abstract Syntax Tree) using ANTLR and Python
Algorithm (segment tree) in Python (practice)
Getting Started with Python's ast Module (Following the Abstract Syntax Tree)
Output tree structure of files in Python
Differences in syntax between Python and Java
Draw a tree in Python 3 using graphviz
Delayed segment tree in Python (debug request)
Manipulate namespaced XML in Python (Element Tree)
An introduction to Python's AST (Abstract Syntax Tree) starting from just one line
Learn the design pattern "Abstract Factory" in Python
Quadtree in Python --2
CURL in python
Metaprogramming in Python
Python 3.3 in Anaconda
Geocoding in python
SendKeys in Python
Python ast library
Meta-analysis in Python
Unittest in python
Discord in Python
DCI in Python
quicksort in python
nCr in python
N-Gram in Python
Programming in python
Plink in Python
Constant in python
with syntax (Python)
Lifegame in Python.
FizzBuzz in Python
Sqlite in python
StepAIC in Python
N-gram in python
LINE-Bot [0] in Python
Csv in python
Disassemble in Python
Reflection in Python
Constant in python
nCr in Python.
format in python
Scons in Python3
Puyo Puyo in python
python in virtualenv
PPAP in Python
Quad-tree in Python
Python syntax-control syntax
Reflection in Python
Chemistry in Python
Hashable in python
DirectLiNGAM in Python
LiNGAM in Python
Flatten in python
flatten in python
2. Multivariate analysis spelled out in Python 7-3. Decision tree [regression tree]
2. Multivariate analysis spelled out in Python 7-1. Decision tree (scikit-learn)