compiler/TLLVMCodeGenerator.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 22 Sep 2015 17:43:38 +0100
changeset 14 fa42d3f1a578
parent 12 d716a8181fc1
child 15 10a95d798b36
permissions -rw-r--r--
Removed syntax for inline assembly, use <primitive: [:asm | ... ]> syntax. This one is easier to implement and less introusive, syntax-wise. And follows Smalltalk tradiiton.

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

"{ NameSpace: Smalltalk }"

TCompilerPass subclass:#TLLVMCodeGenerator
	instanceVariableNames:'function asm'
	classVariableNames:'SelectorSpecialCharMappingTable'
	poolDictionaries:''
	category:'Languages-Tea-Compiler-Internals'
!

!TLLVMCodeGenerator class methodsFor:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    "/ please change as required (and remove this comment)

    SelectorSpecialCharMappingTable := Dictionary withKeysAndValues:
                #($+ 'pl'
                  $- 'mi'
                  $* 'mu'
                  $/ 'di'
                  $, 'co'
                  $@ 'at'
                  $< 'le'
                  $> 'gr'
                  $= 'eq'
                  $~ 'ne'
                  $| 'pi'
                  $\ 'mo'
                  $& 'am').

    "Modified: / 11-07-2015 / 09:24:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TLLVMCodeGenerator class methodsFor:'utilities'!

llvmFunctionNameForClass: class selector: selector      
    "For given class name and selector, returns the name 
     used by LLVM"

    ^ String streamContents:[ :s|
        s nextPutAll: '__M_L_'.
        s nextPutAll: (class theNonMetaclass name copyReplaceAll: $: with: $_).
        class isMeta ifTrue:[ 
            s nextPutAll: '_class'
        ].
        s nextPut: $_.
        selector isBinarySelector ifTrue:[ 
            selector do:[:c |     
                s nextPutAll: (SelectorSpecialCharMappingTable at: c)
            ].
        ] ifFalse:[ 
            selector do:[:c |  
                c isAlphaNumeric ifTrue:[ 
                    s nextPut: c 
                ] ifFalse:[
                    s nextPut: $_.
                    c == $: ifFalse:[ 
                        c codePoint printOn: s.
                    ]
                ].
            ]
        ].
    ].

    "
    TLLVMIREmitPass llvmFunctionNameForClass: TLLVMIREmitPass class selector: #llvmFunctionNameForClass:selector: 
    TLLVMIREmitPass llvmFunctionNameForClass: SmallInteger selector: #+
    TLLVMIREmitPass llvmFunctionNameForClass: Object selector: #~=

    "

    "Created: / 30-08-2015 / 09:23:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-08-2015 / 07:04:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TLLVMCodeGenerator methodsFor:'visiting'!

visitArgument: anRBVariableNode
    | binding |

    binding := anRBVariableNode binding.
    binding isArgumentBinding ifTrue:[ 
        (function parameterAt: binding index) name: anRBVariableNode name.
    ] ifFalse:[ 
        self notYetImplemented.
    ].

    "Created: / 02-09-2015 / 08:43:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TLLVMCodeGenerator methodsFor:'visitor-double dispatching'!

acceptArrayNode: anArrayNode
    self notYetImplemented

    "Created: / 31-08-2015 / 10:14:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptAssignmentNode: anAssignmentNode 
    self notYetImplemented

    "Created: / 31-08-2015 / 10:14:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptBlockNode: aBlockNode 
    self notYetImplemented

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

acceptCascadeNode: aCascadeNode 
    self notYetImplemented

    "Created: / 31-08-2015 / 10:14:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptIfTrueIfFalseNode: node 
    | condition thenBody thenBlock thenResult elseBody elseBlock elseResult joinBlock result |

    condition := self visitNode: node receiver.  
    thenBody  := node arguments first body.
    thenBlock := function addBasicBlock.

    elseBody  := node arguments second body.
    elseBlock := function addBasicBlock.

    asm if: condition then: thenBlock else: elseBlock.
    "/ Code true-branch
    asm block: thenBlock.
    thenResult := self visitNode: thenBody.
    thenResult isReturnInst ifFalse:[  
        joinBlock notNil ifTrue:[ joinBlock function addBasicBlock ].
        asm br: joinBlock.
    ].

    "/ Code false-branch
    asm block: elseBlock.
    elseResult := self visitNode: elseBody.
    elseResult isReturnInst ifFalse:[  
        joinBlock notNil ifTrue:[ joinBlock function addBasicBlock ].
        asm br: joinBlock.
    ].
    joinBlock notNil ifTrue:[ 
        asm block: joinBlock.
    ].

    "Created: / 15-09-2015 / 11:59:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-09-2015 / 05:28:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptInlineAssemblyNode: aTInlineAssemblyNode
    | emitMethodNode emitMethod|

    emitMethodNode := RBMethodNode new.
    emitMethodNode arguments: (aTInlineAssemblyNode arguments collect:[ :e|e copy]) , { RBVariableNode named: 'zelf' } , (aTInlineAssemblyNode topNode arguments collect:[ :e|e copy]).
    emitMethodNode body: aTInlineAssemblyNode body copy.
    emitMethodNode variableNodesDo:[ :variableNode |
        variableNode name = 'self' ifTrue:[ 
            variableNode name: 'zelf'.
        ].
    ].
    emitMethodNode selector:(String streamContents: [ :s | emitMethodNode arguments size timesRepeat:[s nextPutAll:'_:'] ]).
    emitMethod := Compiler compile: emitMethodNode formattedCode forClass: UndefinedObject install: false.
    emitMethod
        valueWithReceiver: nil
        arguments: { asm } , ((1 to: function numArgs) collect: [ :i | function parameterAt: i ])

    "Created: / 02-09-2015 / 06:53:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-09-2015 / 10:30:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptLiteralNode: aLiteralNode
    ^ aLiteralNode binding asLLVMValueInModule: context module.

    "Created: / 31-08-2015 / 10:13:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 31-08-2015 / 12:20:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptMessageNode: aMessageNode
    | receiver arguments methodFunction |

    receiver := self visitNode: aMessageNode receiver.
    arguments := aMessageNode arguments collect: [:argument | self visitNode: argument ].
    methodFunction := aMessageNode binding asLLVMValueInModule: context module.  

    ^ asm call: methodFunction _: { receiver } , arguments

    "Created: / 31-08-2015 / 10:13:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 15-09-2015 / 07:14:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptMethodNode: aMethodNode 
    function := aMethodNode binding asLLVMValueInModule: context module.
    asm := function builder.
    super acceptMethodNode: aMethodNode

    "Created: / 31-08-2015 / 09:42:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-09-2015 / 07:17:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 15-09-2015 / 08:17:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptOptimizedNode: anOptimizedNode 
    self notYetImplemented

    "Created: / 31-08-2015 / 10:13:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptPragmaNode: aPragmaNode
    self notYetImplemented

    "Created: / 31-08-2015 / 10:13:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptReturnNode: aReturnNode 
    | value |

    value := self visitNode: aReturnNode value.
    ^ asm ret: value.

    "Created: / 31-08-2015 / 10:13:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-09-2015 / 06:08:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptSTXPrimitiveCCodeNode: aPrimitiveCCodeNode
    self notYetImplemented

    "Created: / 31-08-2015 / 10:13:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptSTXPrimitiveValueCCodeNode: aPrimitiveValueCCodeNode
    self notYetImplemented

    "Created: / 31-08-2015 / 10:13:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptVariableNode: aVariableNode
    self notYetImplemented

    "Created: / 31-08-2015 / 10:13:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !


TLLVMCodeGenerator initialize!