compiler/TCodeGenerator.st
changeset 9 569bf5707c7e
parent 8 eec72263ed75
child 10 2b9beeac547e
--- a/compiler/TCodeGenerator.st	Mon Sep 14 11:19:10 2015 +0100
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,223 +0,0 @@
-"{ Package: 'jv:tea/compiler' }"
-
-"{ NameSpace: Smalltalk }"
-
-TCompilerPass subclass:#TCodeGenerator
-	instanceVariableNames:'function asm'
-	classVariableNames:'SelectorSpecialCharMappingTable'
-	poolDictionaries:''
-	category:'Languages-Tea-Compiler'
-!
-
-!TCodeGenerator 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>"
-! !
-
-!TCodeGenerator 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>"
-! !
-
-!TCodeGenerator 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>"
-! !
-
-!TCodeGenerator 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>"
-!
-
-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 methodName methodFunction |
-
-    receiver := self visitNode: aMessageNode receiver.
-    receiver := self visitNode: aMessageNode receiver.
-    arguments := aMessageNode arguments collect: [:argument | self visitNode: argument ].
-
-    methodName := self class llvmFunctionNameForClass: aMessageNode binding mclass clazz selector: aMessageNode selector.
-    methodFunction := context module getFunctionNamed: methodName.
-
-    ^ asm call: methodFunction _: { receiver } , arguments
-
-    "Created: / 31-08-2015 / 10:13:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 03-09-2015 / 07:13:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-acceptMethodNode: aMethodNode 
-    | binding |
-
-    binding := aMethodNode binding.
-    function := context module 
-                    addFunctionNamed: (self class llvmFunctionNameForClass: currentClass selector: currentMethod selector)      
-                    type: (LLVMType 
-                            function: { binding receiverType asLLVMTypeInModule: context module } ,
-                                       (binding parameterTypes collect:[:t|t asLLVMTypeInModule: context module])
-                            returning: (binding returnType asLLVMTypeInModule: context module)).
-    asm := function builder.
-    (function parameterAt: 1) name: 'self'.
-    super acceptMethodNode: aMethodNode
-
-    "Created: / 31-08-2015 / 09:42:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 02-09-2015 / 21:31:19 / 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: / 31-08-2015 / 12:17:53 / 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>"
-! !
-
-
-TCodeGenerator initialize!