compiler/TLLVMCodeGenerator.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:#TLLVMCodeGenerator
	instanceVariableNames:'function asm'
	classVariableNames:'SelectorSpecialCharMappingTable'
	poolDictionaries:'LLVMAtomicOrdering LLVMAtomicRMWBinOp LLVMAttribute
		LLVMByteOrdering LLVMCallConv LLVMDLLStorageClass
		LLVMIntPredicate'
	category:'Languages-Tea-Compiler-Internals'
!

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

!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 value |

    binding := anRBVariableNode binding.
    binding isArgumentBinding ifTrue:[
        value :=  function parameterAt: binding index.
        value name: binding name.
    ] ifFalse:[ 
        | block allocas |

        allocas := anRBVariableNode scope llvmAllocas.
        block := asm block.
        asm block: allocas.
        value := asm alloca: (binding type asLLVMTypeInModule: context llvmModule)  as: binding name.
        asm block: block.
    ].
    binding llvmValue: value.

    "Created: / 02-09-2015 / 08:43:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-09-2015 / 16:18:03 / 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 
    | value binding |

    value := self visitNode: anAssignmentNode value.
    binding := anAssignmentNode variable binding.
    asm store: value _: binding llvmValue.
    ^ value

    "Created: / 31-08-2015 / 10:14:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 23-09-2015 / 21:52:41 / 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>"
!

acceptIfTrueNode: node 
    | condition thenBody thenBlock thenResult joinBlock result |

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

    joinBlock := function addBasicBlock.

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

    asm block: joinBlock.

    "Created: / 23-09-2015 / 21:57:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptLiteralNode: aLiteralNode
    ^ aLiteralNode binding asLLVMValueInModule: context llvmModule.

    "Created: / 31-08-2015 / 10:13:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-09-2015 / 16:17:51 / 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 llvmModule.  

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

    "Created: / 31-08-2015 / 10:13:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-09-2015 / 16:17:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptMethodNode: aMethodNode 
    | allocas entry |

    function := aMethodNode binding asLLVMValueInModule: context llvmModule.
    allocas := function addBasicBlockNamed: 'allocas'.
    entry := function addBasicBlockNamed: 'entry'.
    aMethodNode scope llvmAllocas: allocas.
    asm := entry builder.
    super acceptMethodNode: aMethodNode.
    "/ Finally, link allocas to entry.
    asm block: allocas.
    asm br: entry.

    "Created: / 31-08-2015 / 09:42:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-09-2015 / 16:17:59 / 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
    aPragmaNode selector = 'primitive:' ifTrue:[ 
        self acceptPrimitiveNode: aPragmaNode  
    ].

    "Created: / 31-08-2015 / 10:13:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-09-2015 / 18:53:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

acceptPrimitiveNode: aPragmaNode
    | primitiveBlock methodIsForMeta emitMethodNode emitMethod |

    primitiveBlock := aPragmaNode arguments first.
    methodIsForMeta := aPragmaNode parent binding mclass isMetaclass.
    emitMethodNode := RBMethodNode new.
    emitMethodNode arguments: 
                        (primitiveBlock arguments collect:[ :e|e copy]) , 
                        (methodIsForMeta ifFalse:[{ RBVariableNode named: 'zelf' }] ifTrue:[#()]) , 
                        (primitiveBlock topNode arguments collect:[ :e|e copy]).
    emitMethodNode body: primitiveBlock 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: self class install: false.
    emitMethod
        valueWithReceiver: nil
        arguments: { asm } , ((1 to: function numArgs) collect: [ :i | function parameterAt: i ])

    "Created: / 22-09-2015 / 18:03:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-09-2015 / 18:58:42 / 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
    | binding |

    binding := aVariableNode binding.
    ^ binding isArgumentBinding ifTrue:[
        binding llvmValue.
    ] ifFalse:[ 
        asm load: binding llvmValue.
    ].

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

acceptWhileTrueNode: node 
    | loopConditionBlock loopConditionBody loopConditionResult loopBodyBody loopBodyBlock loopBodyResult joinBlock |

    loopConditionBody := node receiver body.
    loopConditionBlock := function addBasicBlock.

    loopBodyBody  := node arguments first body.
    loopBodyBlock := function addBasicBlock.

    joinBlock := function addBasicBlock.

    asm br: loopConditionBlock.
    asm block: loopConditionBlock.
    loopConditionResult := self visitNode: loopConditionBody.
    asm if: loopConditionResult then: loopBodyBlock else: joinBlock.
    asm block: loopBodyBlock.
    loopBodyResult := self visitNode: loopBodyBody.
    loopBodyResult isReturnInst ifFalse:[
        asm br: loopConditionBlock
    ].
    asm block: joinBlock

    "Created: / 23-09-2015 / 22:02:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TLLVMCodeGenerator class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !


TLLVMCodeGenerator initialize!