compiler/PPCCodeBlock.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 17 Aug 2015 12:13:16 +0100
changeset 515 b5316ef15274
parent 502 1e45d3c96ec5
child 516 3b81c9e53352
permissions -rw-r--r--
Updated to PetitCompiler-JanKurs.160, PetitCompiler-Tests-JanKurs.112, PetitCompiler-Extras-Tests-JanKurs.25, PetitCompiler-Benchmarks-JanKurs.17 Name: PetitCompiler-JanKurs.160 Author: JanKurs Time: 17-08-2015, 09:52:26.291 AM UUID: 3b4bfc98-8098-4951-af83-a59e2585b121 Name: PetitCompiler-Tests-JanKurs.112 Author: JanKurs Time: 16-08-2015, 05:00:32.936 PM UUID: 85613d47-08f3-406f-9823-9cdab451e805 Name: PetitCompiler-Extras-Tests-JanKurs.25 Author: JanKurs Time: 16-08-2015, 05:00:10.328 PM UUID: 09731810-51a1-4151-8d3a-56b636fbd1f7 Name: PetitCompiler-Benchmarks-JanKurs.17 Author: JanKurs Time: 05-08-2015, 05:29:32.407 PM UUID: e544b5f1-bcf8-470b-93a6-d2363e4dfc8a

"{ 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.
    self codeIndent.
    self addOnLine: string.

    "Modified: / 01-06-2015 / 22:58:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

addOnLine: string
    buffer nextPutAll: string.
!

nl
    ^ buffer nextPut: Character cr
! !

!PPCCodeBlock methodsFor:'code generation'!

code: aStringOrBlockOrRBParseNode
    self codeNl.
    self codeOnLine: aStringOrBlockOrRBParseNode
    
    "Created: / 01-06-2015 / 21:07:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-06-2015 / 05:52:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

codeIndent
    self codeIndent:indentation

    "Created: / 01-06-2015 / 22:58:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

codeIndent: level
    ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[ 
        level * 4 timesRepeat: [ buffer nextPut: Character space  ].
    ] ifFalse:[ 
        level timesRepeat: [ buffer nextPut: Character tab  ].
    ].

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

codeNl
    self add: ''.
!

codeOnLine: aStringOrBlockOrRBParseNode
    aStringOrBlockOrRBParseNode isString ifTrue:[ 
        self emitCodeAsString: aStringOrBlockOrRBParseNode
    ] ifFalse:[
        (aStringOrBlockOrRBParseNode isKindOf: RBProgramNode) ifTrue:[ 
            self emitCodeAsRBNode: aStringOrBlockOrRBParseNode.
        ] ifFalse:[  
            self emitCodeAsBlock: aStringOrBlockOrRBParseNode
        ].
    ].
! !

!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."

    buffer := String new writeStream.
    indentation := 1.
    temporaries := OrderedCollection new.

    "Modified: / 01-06-2015 / 20:57:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 18-06-2015 / 06:04:21 / 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: [ aStream 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>"
!

sourceOn: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:[
                aStream 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 methodsFor:'private'!

emitCodeAsBlock: aBlock
    aBlock value
!

emitCodeAsRBNode: anRBNode
    anRBNode isSequence ifTrue:[
        anRBNode temporaries do:[:e |  
            (temporaries includes: e name) ifFalse:[ 
                temporaries add: e name
            ].
        ].
        anRBNode statements do:[:e|
            self 	add: (self formatRBNode: e); 
                    addOnLine: '.'.
        ].
    ] ifFalse:[  
        buffer nextPutAll: anRBNode formattedCode.  
    ].

!

emitCodeAsString: aString
    self addOnLine: aString
!

formatRBNode: anRBNode
    | formatter |
    formatter := anRBNode formatterClass new.
    formatter indent: indentation.
    ^ formatter format: anRBNode 
! !