compiler/TCodeGenerator.st
changeset 9 569bf5707c7e
parent 8 eec72263ed75
child 10 2b9beeac547e
equal deleted inserted replaced
8:eec72263ed75 9:569bf5707c7e
     1 "{ Package: 'jv:tea/compiler' }"
       
     2 
       
     3 "{ NameSpace: Smalltalk }"
       
     4 
       
     5 TCompilerPass subclass:#TCodeGenerator
       
     6 	instanceVariableNames:'function asm'
       
     7 	classVariableNames:'SelectorSpecialCharMappingTable'
       
     8 	poolDictionaries:''
       
     9 	category:'Languages-Tea-Compiler'
       
    10 !
       
    11 
       
    12 !TCodeGenerator class methodsFor:'initialization'!
       
    13 
       
    14 initialize
       
    15     "Invoked at system start or when the class is dynamically loaded."
       
    16 
       
    17     "/ please change as required (and remove this comment)
       
    18 
       
    19     SelectorSpecialCharMappingTable := Dictionary withKeysAndValues:
       
    20                 #($+ 'pl'
       
    21                   $- 'mi'
       
    22                   $* 'mu'
       
    23                   $/ 'di'
       
    24                   $, 'co'
       
    25                   $@ 'at'
       
    26                   $< 'le'
       
    27                   $> 'gr'
       
    28                   $= 'eq'
       
    29                   $~ 'ne'
       
    30                   $| 'pi'
       
    31                   $\ 'mo'
       
    32                   $& 'am').
       
    33 
       
    34     "Modified: / 11-07-2015 / 09:24:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    35 ! !
       
    36 
       
    37 !TCodeGenerator class methodsFor:'utilities'!
       
    38 
       
    39 llvmFunctionNameForClass: class selector: selector      
       
    40     "For given class name and selector, returns the name 
       
    41      used by LLVM"
       
    42 
       
    43     ^ String streamContents:[ :s|
       
    44         s nextPutAll: '__M_L_'.
       
    45         s nextPutAll: (class theNonMetaclass name copyReplaceAll: $: with: $_).
       
    46         class isMeta ifTrue:[ 
       
    47             s nextPutAll: '_class'
       
    48         ].
       
    49         s nextPut: $_.
       
    50         selector isBinarySelector ifTrue:[ 
       
    51             selector do:[:c |     
       
    52                 s nextPutAll: (SelectorSpecialCharMappingTable at: c)
       
    53             ].
       
    54         ] ifFalse:[ 
       
    55             selector do:[:c |  
       
    56                 c isAlphaNumeric ifTrue:[ 
       
    57                     s nextPut: c 
       
    58                 ] ifFalse:[
       
    59                     s nextPut: $_.
       
    60                     c == $: ifFalse:[ 
       
    61                         c codePoint printOn: s.
       
    62                     ]
       
    63                 ].
       
    64             ]
       
    65         ].
       
    66     ].
       
    67 
       
    68     "
       
    69     TLLVMIREmitPass llvmFunctionNameForClass: TLLVMIREmitPass class selector: #llvmFunctionNameForClass:selector: 
       
    70     TLLVMIREmitPass llvmFunctionNameForClass: SmallInteger selector: #+
       
    71     TLLVMIREmitPass llvmFunctionNameForClass: Object selector: #~=
       
    72 
       
    73     "
       
    74 
       
    75     "Created: / 30-08-2015 / 09:23:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    76     "Modified: / 31-08-2015 / 07:04:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    77 ! !
       
    78 
       
    79 !TCodeGenerator methodsFor:'visiting'!
       
    80 
       
    81 visitArgument: anRBVariableNode
       
    82     | binding |
       
    83 
       
    84     binding := anRBVariableNode binding.
       
    85     binding isArgumentBinding ifTrue:[ 
       
    86         (function parameterAt: binding index) name: anRBVariableNode name.
       
    87     ] ifFalse:[ 
       
    88         self notYetImplemented.
       
    89     ].
       
    90 
       
    91     "Created: / 02-09-2015 / 08:43:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    92 ! !
       
    93 
       
    94 !TCodeGenerator methodsFor:'visitor-double dispatching'!
       
    95 
       
    96 acceptArrayNode: anArrayNode
       
    97     self notYetImplemented
       
    98 
       
    99     "Created: / 31-08-2015 / 10:14:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   100 !
       
   101 
       
   102 acceptAssignmentNode: anAssignmentNode 
       
   103     self notYetImplemented
       
   104 
       
   105     "Created: / 31-08-2015 / 10:14:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   106 !
       
   107 
       
   108 acceptBlockNode: aBlockNode 
       
   109     self notYetImplemented
       
   110 
       
   111     "Created: / 31-08-2015 / 10:14:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   112 !
       
   113 
       
   114 acceptCascadeNode: aCascadeNode 
       
   115     self notYetImplemented
       
   116 
       
   117     "Created: / 31-08-2015 / 10:14:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   118 !
       
   119 
       
   120 acceptInlineAssemblyNode: aTInlineAssemblyNode
       
   121     | emitMethodNode emitMethod|
       
   122 
       
   123     emitMethodNode := RBMethodNode new.
       
   124     emitMethodNode arguments: (aTInlineAssemblyNode arguments collect:[ :e|e copy]) , { RBVariableNode named: 'zelf' } , (aTInlineAssemblyNode topNode arguments collect:[ :e|e copy]).
       
   125     emitMethodNode body: aTInlineAssemblyNode body copy.
       
   126     emitMethodNode variableNodesDo:[ :variableNode |
       
   127         variableNode name = 'self' ifTrue:[ 
       
   128             variableNode name: 'zelf'.
       
   129         ].
       
   130     ].
       
   131     emitMethodNode selector:(String streamContents: [ :s | emitMethodNode arguments size timesRepeat:[s nextPutAll:'_:'] ]).
       
   132     emitMethod := Compiler compile: emitMethodNode formattedCode forClass: UndefinedObject install: false.
       
   133     emitMethod
       
   134         valueWithReceiver: nil
       
   135         arguments: { asm } , ((1 to: function numArgs) collect: [ :i | function parameterAt: i ])
       
   136 
       
   137     "Created: / 02-09-2015 / 06:53:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   138     "Modified: / 02-09-2015 / 10:30:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   139 !
       
   140 
       
   141 acceptLiteralNode: aLiteralNode
       
   142     ^ aLiteralNode binding asLLVMValueInModule: context module.
       
   143 
       
   144     "Created: / 31-08-2015 / 10:13:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   145     "Modified: / 31-08-2015 / 12:20:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   146 !
       
   147 
       
   148 acceptMessageNode: aMessageNode
       
   149     | receiver arguments methodName methodFunction |
       
   150 
       
   151     receiver := self visitNode: aMessageNode receiver.
       
   152     receiver := self visitNode: aMessageNode receiver.
       
   153     arguments := aMessageNode arguments collect: [:argument | self visitNode: argument ].
       
   154 
       
   155     methodName := self class llvmFunctionNameForClass: aMessageNode binding mclass clazz selector: aMessageNode selector.
       
   156     methodFunction := context module getFunctionNamed: methodName.
       
   157 
       
   158     ^ asm call: methodFunction _: { receiver } , arguments
       
   159 
       
   160     "Created: / 31-08-2015 / 10:13:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   161     "Modified: / 03-09-2015 / 07:13:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   162 !
       
   163 
       
   164 acceptMethodNode: aMethodNode 
       
   165     | binding |
       
   166 
       
   167     binding := aMethodNode binding.
       
   168     function := context module 
       
   169                     addFunctionNamed: (self class llvmFunctionNameForClass: currentClass selector: currentMethod selector)      
       
   170                     type: (LLVMType 
       
   171                             function: { binding receiverType asLLVMTypeInModule: context module } ,
       
   172                                        (binding parameterTypes collect:[:t|t asLLVMTypeInModule: context module])
       
   173                             returning: (binding returnType asLLVMTypeInModule: context module)).
       
   174     asm := function builder.
       
   175     (function parameterAt: 1) name: 'self'.
       
   176     super acceptMethodNode: aMethodNode
       
   177 
       
   178     "Created: / 31-08-2015 / 09:42:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   179     "Modified: / 02-09-2015 / 21:31:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   180 !
       
   181 
       
   182 acceptOptimizedNode: anOptimizedNode 
       
   183     self notYetImplemented
       
   184 
       
   185     "Created: / 31-08-2015 / 10:13:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   186 !
       
   187 
       
   188 acceptPragmaNode: aPragmaNode
       
   189     self notYetImplemented
       
   190 
       
   191     "Created: / 31-08-2015 / 10:13:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   192 !
       
   193 
       
   194 acceptReturnNode: aReturnNode 
       
   195     | value |
       
   196 
       
   197     value := self visitNode: aReturnNode value.
       
   198     asm ret: value.
       
   199 
       
   200     "Created: / 31-08-2015 / 10:13:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   201     "Modified: / 31-08-2015 / 12:17:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   202 !
       
   203 
       
   204 acceptSTXPrimitiveCCodeNode: aPrimitiveCCodeNode
       
   205     self notYetImplemented
       
   206 
       
   207     "Created: / 31-08-2015 / 10:13:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   208 !
       
   209 
       
   210 acceptSTXPrimitiveValueCCodeNode: aPrimitiveValueCCodeNode
       
   211     self notYetImplemented
       
   212 
       
   213     "Created: / 31-08-2015 / 10:13:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   214 !
       
   215 
       
   216 acceptVariableNode: aVariableNode
       
   217     self notYetImplemented
       
   218 
       
   219     "Created: / 31-08-2015 / 10:13:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   220 ! !
       
   221 
       
   222 
       
   223 TCodeGenerator initialize!