compiler/PPCCodeBlock.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 01 Jun 2015 22:02:17 +0100
changeset 477 b18b6cc7aabc
child 478 711c8bc1ec04
permissions -rw-r--r--
Codegen refactoring [1/x]: Introduced a PPCCodeBlock A PPCCodeBlock is an abstraction of a block of statements with temporaries. This will allow for scoped temporary management in code generator - temporary variables could be allocated for block only. (i.e., make them block-temporaries)

"{ Package: 'stx:goodies/petitparser/compiler' }"

"{ NameSpace: Smalltalk }"

Object subclass:#PPCCodeBlock
	instanceVariableNames:'buffer indentation temporaries'
	classVariableNames:''
	poolDictionaries:''
	category:'PetitCompiler-Compiler-Codegen'
!


!PPCCodeBlock class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!PPCCodeBlock methodsFor:'as yet unclassified'!

add: string
    self nl.
    ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[ 
        indentation * 4 timesRepeat: [ buffer nextPut: Character space  ].
    ] ifFalse:[ 
        indentation timesRepeat: [ buffer nextPut: Character tab  ].
    ].
    self addOnLine: string.

    "Modified: / 21-05-2015 / 15:42:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addOnLine: string
    buffer nextPutAll: string.
!

nl
    ^ buffer nextPut: Character cr
! !

!PPCCodeBlock methodsFor:'code generation'!

code: aStringOrBlock
    aStringOrBlock isString ifTrue:[ 
        buffer nextPutAll: aStringOrBlock
    ] ifFalse:[ 
        aStringOrBlock value
    ].

    "Created: / 01-06-2015 / 21:07:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPCCodeBlock methodsFor:'code generation - variables'!

allocateTemporaryVariableNamed:preferredName 
    "Allocate a new variable with (preferably) given name.
     Returns a real variable name that should be used."
    
    (temporaries includes:preferredName) ifFalse:[
        temporaries add:preferredName.
        ^ preferredName
    ] ifTrue:[
        | name |

        name := preferredName , '_' , (temporaries size + 1) printString.
        temporaries add:name.
        ^ name
    ].

    "Created: / 23-04-2015 / 17:37:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-06-2015 / 21:03:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPCCodeBlock methodsFor:'indentation'!

dedent
    indentation := indentation - 1
!

indent 
    indentation := indentation + 1
!

indentationLevel
    ^ indentation
!

indentationLevel: value
    indentation := value
! !

!PPCCodeBlock methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    "/ please change as required (and remove this comment)
    buffer := String new writeStream.
    indentation := 1.
    temporaries := OrderedCollection new.          


    "/ super initialize.   -- commented since inherited method does nothing

    "Modified: / 01-06-2015 / 20:57:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPCCodeBlock methodsFor:'printing and storing'!

codeOn: aStream
    "Dumps generated code on given stream"

    temporaries notEmpty ifTrue:[
        ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[ 
            indentation * 4 timesRepeat: [ aStream nextPut: Character space  ].
        ] ifFalse:[ 
            indentation timesRepeat: [ buffer nextPut: Character tab  ].
        ].
        aStream nextPut: $|.
        temporaries do:[:e | aStream space; nextPutAll: e  ].
        aStream space.
        aStream nextPut: $|. 
        self nl.
        "In Smalltalk/X, there should be a blank line after temporaries"
        ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[ 
            self nl.
        ].
    ].
    aStream nextPutAll: buffer contents

    "Created: / 01-06-2015 / 21:26:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!PPCCodeBlock class methodsFor:'documentation'!

version
    ^ 'Path: stx/goodies/petitparser/compiler/PPCCodeBlock.st, Version: 1.0, User: jv, Time: 2015-06-01T21:57:38.671+01'
!

version_HG
    ^ 'Path: stx/goodies/petitparser/compiler/PPCCodeBlock.st, Version: 1.0, User: jv, Time: 2015-06-01T21:57:38.671+01'
! !