compiler/TSemanticAnalyser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 16 Sep 2015 05:29:43 +0100
changeset 11 6d39860d0fdb
parent 9 569bf5707c7e
child 13 97090c2baa33
permissions -rw-r--r--
First shot on #ifTrie:ifFalse: special form

"{ Package: 'jv:tea/compiler' }"

"{ NameSpace: Smalltalk }"

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

!TSemanticAnalyser class methodsFor:'documentation'!

documentation
"
    This is the very first pass on the code. Its responsibility is:
    * initialize bindings including types (except for message sends as those
      depends on type analysis)
    * initialize scopes (i.e, assign scopes and populate them
      with variables)

    [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)                                
                       + (currentScope isMethodScope 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: / 02-09-2015 / 08:58:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TSemanticAnalyser methodsFor:'visitor-double dispatching'!

acceptBlockNode: aBlockNode
    | scope |
    aBlockNode parent isSpecialFormNode ifTrue:[ 
        scope := currentScope subScope: aBlockNode.
    ] ifFalse:[ 
        scope := TScope new.
    ].
    aBlockNode scope: scope.
    super acceptBlockNode: aBlockNode

    "Created: / 25-08-2015 / 22:30:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-09-2015 / 14:04:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptLiteralNode: aRBLiteralNode
    | value |

    super acceptLiteralNode: aRBLiteralNode.
    value := aRBLiteralNode value.
    value isInteger ifTrue:[ 
        aRBLiteralNode binding: (TConstantBinding value: value type: (context environment binding lookupClassSIntegerW) type).
        ^ 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: / 15-09-2015 / 08:27:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptMethodNode: aMethodNode
    | scope bindingForSelf |

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

    aMethodNode scope: scope.

    super acceptMethodNode: aMethodNode

    "Created: / 25-08-2015 / 22:29:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-09-2015 / 09:30:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptVariableNode: aVariableNode
    aVariableNode binding: (aVariableNode scope lookupVariable: aVariableNode name).
    super acceptVariableNode: aVariableNode

    "Created: / 25-08-2015 / 23:00:34 / 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'
! !