compiler/TSemanticAnalyser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 25 Sep 2015 03:51:15 +0100
changeset 16 17a2d1d9f205
parent 15 10a95d798b36
permissions -rw-r--r--
Added standalone Tea compiler - teak It allows for compilation of .tea files from the command line.

"
    Copyright (C) 2015-now Jan Vrany

    This code is not an open-source (yet). You may use this code
    for your own experiments and projects, given that:

    * all modification to the code will be sent to the
      original author for inclusion in future releases
    * this is not used in any commercial software

    This license is provisional and may (will) change in
    a future.
"
"{ Package: 'jv:tea/compiler' }"

"{ NameSpace: Smalltalk }"

TCompilerPass subclass:#TSemanticAnalyser
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Languages-Tea-Compiler-Internals'
!

!TSemanticAnalyser class methodsFor:'documentation'!

copyright
"
    Copyright (C) 2015-now Jan Vrany

    This code is not an open-source (yet). You may use this code
    for your own experiments and projects, given that:

    * all modification to the code will be sent to the
      original author for inclusion in future releases
    * this is not used in any commercial software

    This license is provisional and may (will) change in
    a future.
"
!

documentation
"
    This is the very first pass on the code. Its responsibility is:
    * initialize bindings 
    * initialize scopes (i.e, assign scopes and populate them
      with variable bindings)

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!TSemanticAnalyser methodsFor:'visiting'!

visitArgument: anRBVariableNode
    | binding |

    anRBVariableNode parent isSequence ifTrue:[ 
        binding := TLocalBinding name:anRBVariableNode name.
    ] ifFalse:[ 
        binding := TArgumentBinding name:anRBVariableNode name.
        binding index: (anRBVariableNode parent arguments indexOf: anRBVariableNode)                                
                       + (anRBVariableNode parent scope hasSelfArgument ifTrue:[1] ifFalse:[0])     
    ].
    anRBVariableNode parent scope addVariable: binding.
    super visitArgument: anRBVariableNode.

    "Created: / 25-08-2015 / 22:51:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-09-2015 / 18:48:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TSemanticAnalyser methodsFor:'visitor-double dispatching'!

acceptBlockNode: aBlockNode
    | scope binding |
    aBlockNode parent isSpecialFormNode ifTrue:[ 
        scope := TScope node: aBlockNode parent: aBlockNode parent scope
    ] ifFalse:[ 
        scope := TScope node: aBlockNode
    ].
    aBlockNode scope: scope.

    binding := TBlockBinding new.
    binding parameterTypes: aBlockNode parameterTypes.
    binding returnType: aBlockNode returnType.
    aBlockNode binding: binding.

    super acceptBlockNode: aBlockNode

    "Created: / 25-08-2015 / 22:30:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-09-2015 / 16:31:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptIfTrueIfFalseNode: node 
    node arguments first isBlock ifFalse:[ 
        context reportSemanticError: 'First argument (true block) of ifTrue:ifFalse: special form is not a block'.
    ] ifTrue:[ 
        node arguments first arguments notEmptyOrNil ifTrue:[ 
            context reportSemanticError: 'First argument (true block) of ifTrue::ifFalse: special form may not have any arguments'.
        ]
    ].  
    node arguments second isBlock ifFalse:[ 
        context reportSemanticError: 'Second argument (false block) of ifTrue:ifFalse: special form is not a block'.
    ] ifTrue:[ 
        node arguments second arguments notEmptyOrNil ifTrue:[ 
            context reportSemanticError: 'Second argument (false block) of ifTrue::ifFalse: special form may not have any arguments'.
        ]
    ].  

    ^ self acceptMessageNode: node.

    "Created: / 23-09-2015 / 14:20:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptIfTrueNode: node
    node arguments first isBlock ifFalse:[ 
        context reportSemanticError: 'Argument (true block) of ifTrue: special form is not a block'.
    ] ifTrue:[ 
        node arguments first arguments notEmptyOrNil ifTrue:[ 
            context reportSemanticError: 'Argument (true block) of ifTrue: special form may not have any arguments'.
        ]
    ].     
    self acceptMessageNode: node

    "Created: / 23-09-2015 / 14:18:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptLiteralNode: aRBLiteralNode
    | value |

    super acceptLiteralNode: aRBLiteralNode.
    value := aRBLiteralNode value.
    value isInteger ifTrue:[ 
        aRBLiteralNode binding: (TConstantBinding value: value).
        ^ self.
    ].
    value isBoolean ifTrue:[ 
        aRBLiteralNode binding: (TConstantBinding value: (value ifTrue:[1] ifFalse:[0]) type: (context environment binding lookupClassBoolean) type).
        ^ self.
    ].
    self erorr: 'Unsupported constant'.

    "Created: / 25-08-2015 / 23:17:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-09-2015 / 07:12:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptMethodNode: aMethodNode
    | scope bindingForSelf |

    scope   := TScope node: aMethodNode.
    bindingForSelf := TArgumentBinding name:'self'.
    bindingForSelf index: 1.
    scope addVariable: bindingForSelf.

    aMethodNode scope: scope.

    super acceptMethodNode: aMethodNode

    "Created: / 25-08-2015 / 22:29:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-09-2015 / 18:31:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptVariableNode: aVariableNode
    | binding |

    binding := aVariableNode scope lookupVariable: aVariableNode name.      
    binding isNil ifTrue:[ 
        context reportSemanticError: ('Undeclared variable %1' bindWith: aVariableNode name).
        ^ self.
    ].
    aVariableNode binding: binding.
    super acceptVariableNode: aVariableNode

    "Created: / 25-08-2015 / 23:00:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-09-2015 / 06:14:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptWhileTrueNode: node
    node receiver isBlock ifFalse:[ 
        context reportSemanticError: 'Receiver (condition) of whileTrue: special form is not a block'.
    ] ifTrue:[ 
        node receiver arguments notEmptyOrNil ifTrue:[ 
            context reportSemanticError: 'Receiver (condition) of whileTrue: special form may not have any arguments'.
        ]
    ].
    node arguments first isBlock ifFalse:[ 
        context reportSemanticError: 'Argument (loop body) of whileTrue: special form is not a block'.
    ] ifTrue:[ 
        node arguments first arguments notEmptyOrNil ifTrue:[ 
            context reportSemanticError: 'Argument (loop body) of whileTrue: special form may not have any arguments'.
        ]
    ].
    super acceptWhileTrueNode: node

    "Created: / 23-09-2015 / 14:10:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TSemanticAnalyser class methodsFor:'documentation'!

version
    ^ 'Path: jv/tea/compiler/TSemanticAnalyzer.st, Version: 1.0, User: jv, Time: 2015-08-31T13:47:58.729+01'
!

version_HG
    ^ 'Path: jv/tea/compiler/TSemanticAnalyzer.st, Version: 1.0, User: jv, Time: 2015-08-31T13:47:58.729+01'
! !