compiler/PPCCodeGen.st
changeset 515 b5316ef15274
parent 502 1e45d3c96ec5
child 524 f6f68d32de73
equal deleted inserted replaced
502:1e45d3c96ec5 515:b5316ef15274
     2 
     2 
     3 "{ NameSpace: Smalltalk }"
     3 "{ NameSpace: Smalltalk }"
     4 
     4 
     5 Object subclass:#PPCCodeGen
     5 Object subclass:#PPCCodeGen
     6 	instanceVariableNames:'compilerStack compiledParser methodCache currentMethod constants
     6 	instanceVariableNames:'compilerStack compiledParser methodCache currentMethod constants
     7 		returnVariable arguments idCache'
     7 		returnVariable arguments idGen'
     8 	classVariableNames:''
     8 	classVariableNames:''
     9 	poolDictionaries:''
     9 	poolDictionaries:''
    10 	category:'PetitCompiler-Compiler-Codegen'
    10 	category:'PetitCompiler-Compiler-Codegen'
    11 !
    11 !
    12 
    12 
    50 
    50 
    51 currentReturnVariable
    51 currentReturnVariable
    52     ^ currentMethod returnVariable 
    52     ^ currentMethod returnVariable 
    53 !
    53 !
    54 
    54 
       
    55 idGen
       
    56     ^ idGen
       
    57 !
       
    58 
       
    59 idGen: anObject
       
    60     idGen := anObject
       
    61 !
       
    62 
    55 ids
    63 ids
    56     ^ idCache keys
    64     ^ idGen ids
    57 !
    65 !
    58 
    66 
    59 methodCategory
    67 methodCategory
    60     ^ 'generated'
    68     ^ 'generated'
    61 !
    69 !
   142     currentMethod code: aStringOrBlockOrRBParseNode
   150     currentMethod code: aStringOrBlockOrRBParseNode
   143 
   151 
   144     "Created: / 01-06-2015 / 23:49:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   152     "Created: / 01-06-2015 / 23:49:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   145 !
   153 !
   146 
   154 
       
   155 codeAssert: aCode
       
   156     self add: 'self assert: (', aCode, ').'.
       
   157 !
       
   158 
   147 codeAssign: code to: variable
   159 codeAssign: code to: variable
   148     self assert: variable isNil not.
   160     self assert: variable isNil not.
   149     
   161     
   150     "TODO JK: Hack alert, whatever is magic constant!!"
   162     "TODO JK: Hack alert, whatever is magic constant!!"
   151     (variable == #whatever) ifFalse: [ 
   163     (variable == #whatever) ifFalse: [ 
   162     tmpVarirable := returnVariable.
   174     tmpVarirable := returnVariable.
   163     returnVariable := aString.
   175     returnVariable := aString.
   164     method := [
   176     method := [
   165             aBlock value
   177             aBlock value
   166         ] ensure:[ returnVariable := tmpVarirable ].
   178         ] ensure:[ returnVariable := tmpVarirable ].
       
   179     self assert: (method isKindOf: PPCMethod).	
   167     method isInline ifTrue:[
   180     method isInline ifTrue:[
   168         self callOnLine:method
   181         self callOnLine:method
   169     ] ifFalse:[
   182     ] ifFalse:[
   170         self codeEvaluateAndAssign:(method call) to:aString.
   183         self codeEvaluateAndAssign:(method call) to:aString.
   171     ]
   184     ]
   177     currentMethod codeBlock: contents
   190     currentMethod codeBlock: contents
   178 
   191 
   179     "Created: / 01-06-2015 / 22:35:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   192     "Created: / 01-06-2015 / 22:35:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   180 !
   193 !
   181 
   194 
       
   195 codeCall: aMethod
       
   196     self assert: (aMethod isKindOf: PPCMethod).
       
   197     self add: aMethod call.
       
   198 !
       
   199 
   182 codeClearError
   200 codeClearError
   183     self add: 'self clearError.'.
   201     self add: 'self clearError.'.
   184 !
   202 !
   185 
   203 
   186 codeComment: string
   204 codeComment: string
   210     
   228     
   211     "TODO JK: Hack alert, whatever is magic constant!!"
   229     "TODO JK: Hack alert, whatever is magic constant!!"
   212     (variable == #whatever) ifFalse: [ 
   230     (variable == #whatever) ifFalse: [ 
   213         "Do not assign, if somebody does not care!!"
   231         "Do not assign, if somebody does not care!!"
   214         self add: variable, ' ', selector,' ', argument.
   232         self add: variable, ' ', selector,' ', argument.
   215  		] ifTrue: [ 
   233  	] ifTrue: [ 
   216         "In case argument has a side effect"
   234         "In case argument has a side effect"
   217  				self add: argument	
   235  		self add: argument	
   218     ]
   236     ]
   219 !
   237 !
   220 
   238 
   221 codeEvaluateAndAssign: argument to: variable
   239 codeEvaluateAndAssign: argument to: variable
   222     self assert: variable isNil not.
   240     self assert: variable isNil not.
   225     (variable == #whatever) ifFalse: [ 
   243     (variable == #whatever) ifFalse: [ 
   226         "Do not assign, if somebody does not care!!"
   244         "Do not assign, if somebody does not care!!"
   227         self add: variable ,' := ', argument.
   245         self add: variable ,' := ', argument.
   228     ] ifTrue: [ 
   246     ] ifTrue: [ 
   229         "In case an argument has a side effect"
   247         "In case an argument has a side effect"
   230  		self add: argument.	
   248         self add: argument.	
   231     ]
   249     ]
   232 !
   250 !
   233 
   251 
   234 codeHalt
   252 codeHalt
   235     self add: 'self halt. '
   253     self add: 'self halt. '
   252 !
   270 !
   253 
   271 
   254 codeIf: condition then: then else: else
   272 codeIf: condition then: then else: else
   255     currentMethod 
   273     currentMethod 
   256         add: '(';
   274         add: '(';
   257         code: condition;
   275         codeOnLine: condition;
   258         addOnLine: ')'.
   276         addOnLine: ')'.
   259     then notNil ifTrue:[ 
   277     then notNil ifTrue:[ 
   260         currentMethod 
   278         currentMethod 
   261             addOnLine:' ifTrue:';
   279             addOnLine:' ifTrue: ';
   262             codeBlock: then.
   280             codeBlock: then.
   263     ].
   281     ].
   264     else notNil ifTrue:[ 
   282     else notNil ifTrue:[ 
   265         currentMethod 
   283         currentMethod 
   266             addOnLine:' ifFalse:';
   284             addOnLine:' ifFalse: ';
   267             codeBlock: else.
   285             codeBlock: else.
   268     ].
   286     ].
   269     self codeDot.
   287     self codeDot.
   270 
   288 
   271     "Created: / 01-06-2015 / 22:43:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   289     "Created: / 01-06-2015 / 22:43:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   289 
   307 
   290     "Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   308     "Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   291     "Modified: / 23-04-2015 / 20:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   309     "Modified: / 23-04-2015 / 20:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   292 !
   310 !
   293 
   311 
       
   312 codeOnLIne:aStringOrBlockOrRBParseNode
       
   313     currentMethod codeOnLine: aStringOrBlockOrRBParseNode
       
   314 
       
   315     "Created: / 01-06-2015 / 23:49:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   316 !
       
   317 
       
   318 codeParsedValueOf: aBlock 
       
   319     | tmpVarirable  method |
       
   320 
       
   321     self assert: aBlock isBlock.	
       
   322     tmpVarirable := returnVariable.
       
   323     returnVariable := #whatever.
       
   324     method := [
       
   325         aBlock value
       
   326     ] ensure:[ returnVariable := tmpVarirable ].
       
   327     self assert: returnVariable == tmpVarirable.
       
   328     self assert: (method isKindOf: PPCMethod).
       
   329     
       
   330     self codeCall: method.
       
   331 !
       
   332 
   294 codeProfileStart
   333 codeProfileStart
   295     self add: 'context methodInvoked: #', currentMethod methodName, '.'
   334     self add: 'context methodInvoked: #', currentMethod methodName, '.'
   296 
   335 
   297     "Created: / 01-06-2015 / 21:17:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   336     "Created: / 01-06-2015 / 21:17:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   298 !
   337 !
   303     "Created: / 01-06-2015 / 21:19:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   342     "Created: / 01-06-2015 / 21:19:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   304 !
   343 !
   305 
   344 
   306 codeReturn
   345 codeReturn
   307    currentMethod isInline ifTrue: [
   346    currentMethod isInline ifTrue: [
   308 		"If inlined, the return variable already holds the value"
   347 				"If inlined, the return variable already holds the value"
   309 	] ifFalse: [
   348 		] ifFalse: [
   310 		arguments profile ifTrue:[ 
   349 				arguments profile ifTrue:[ 
   311 			self codeProfileStop.
   350 						self codeProfileStop.
   312 		]. 
   351 				]. 
   313 		self add: '^ ', currentMethod returnVariable  
   352 				self add: '^ ', currentMethod returnVariable  
   314 	].
   353 		].
   315 
   354 
   316 	"Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   355 		"Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   317 	"Modified: / 01-06-2015 / 21:49:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   356 		"Modified: / 01-06-2015 / 21:49:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   318 !
   357 !
   319 
   358 
   320 codeReturn: code
   359 codeReturn: code
   321     " - returns whatever is in code OR
   360     " - returns whatever is in code OR
   322       - assigns whatever is in code into the returnVariable"
   361       - assigns whatever is in code into the returnVariable"
   331 
   370 
   332     "Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   371     "Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   333     "Modified: / 01-06-2015 / 21:48:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   372     "Modified: / 01-06-2015 / 21:48:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   334 !
   373 !
   335 
   374 
       
   375 codeReturnParsedValueOf: aBlock 
       
   376     | tmpVarirable  method |
       
   377 
       
   378     self assert:aBlock isBlock.	
       
   379     tmpVarirable := returnVariable.
       
   380     method := aBlock value. 
       
   381     self assert: returnVariable == tmpVarirable.
       
   382     self assert: (method isKindOf: PPCMethod).
       
   383     method isInline ifTrue:[
       
   384         self callOnLine:method.
       
   385         self codeReturn: returnVariable.
       
   386     ] ifFalse:[
       
   387         self codeReturn: method call.
       
   388         
       
   389     ]
       
   390 
       
   391     "Created: / 23-04-2015 / 18:21:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   392 !
       
   393 
   336 codeStoreValueOf: aBlock intoVariable: aString
   394 codeStoreValueOf: aBlock intoVariable: aString
   337     | tmpVarirable method |
   395     | tmpVarirable method |
   338     self assert: aBlock isBlock.
   396     self assert: aBlock isBlock.
   339     self assert: aString isNil not.
   397     self assert: aString isNil not.
   340     
   398     
   392     ^toUse
   450     ^toUse
   393 
   451 
   394     "Modified: / 10-05-2015 / 07:29:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   452     "Modified: / 10-05-2015 / 07:29:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   395 !
   453 !
   396 
   454 
   397 idFor: object
   455 idFor: anObject
   398     self assert: (object canHavePPCId).
   456     ^ idGen idFor: anObject
   399     ^ self idFor: object prefixed: object prefix suffixed: object suffix
   457 !
       
   458 
       
   459 idFor: anObject defaultName: defaultName
       
   460     ^ idGen idFor: anObject defaultName: defaultName
   400 !
   461 !
   401 
   462 
   402 idFor: object prefixed: prefix
   463 idFor: object prefixed: prefix
   403     ^ self idFor: object prefixed: prefix suffixed: ''
   464     ^ self idFor: object prefixed: prefix suffixed: ''
   404 !
   465 !
   405 
   466 
   406 idFor: object prefixed: prefix suffixed: suffix
   467 idFor: object prefixed: prefix suffixed: suffix
       
   468     self error: 'Should no longer be used'.
       
   469     "
   407     | name id |
   470     | name id |
   408     ^ idCache at: object ifAbsentPut: [ 
   471     ^ idCache at: object ifAbsentPut: [ 
   409         ((object canHavePPCId) and: [object name isNotNil]) ifTrue: [ 
   472         ((object canHavePPCId) and: [object name isNotNil]) ifTrue: [ 
   410             "Do not use prefix, if there is a name"
   473             ""Do not use prefix, if there is a name""
   411             name := self asSelector: (object name asString).
   474             name := self asSelector: (object name asString).
   412             id := (name, suffix) asSymbol.
   475             id := (name, suffix) asSymbol.
   413             
   476             
   414             "Make sure, that the generated ID is uniqe!!"
   477             ""Make sure, that the generated ID is uniqe!!""
   415             (idCache includes: id) ifTrue: [ 
   478             (idCache includes: id) ifTrue: [ 
   416                 (id, '_', idCache size asString) asSymbol 
   479                 (id, '_', idCache size asString) asSymbol 
   417             ] ifFalse: [ 
   480             ] ifFalse: [ 
   418                 id
   481                 id
   419             ]
   482             ]
   420         ] ifFalse: [ 
   483         ] ifFalse: [ 
   421             (prefix, '_', (idCache size asString), suffix) asSymbol
   484             (prefix, '_', (idCache size asString), suffix) asSymbol
   422         ]
   485         ]
   423     ]
   486     ]
       
   487     "
       
   488 
       
   489     "Modified: / 17-08-2015 / 12:00:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   424 !
   490 !
   425 
   491 
   426 idFor: object suffixed: suffix
   492 idFor: object suffixed: suffix
   427     self assert: (object isKindOf: PPCNode) description: 'Shold use PPCNode for ids'.
   493     self assert: (object isKindOf: PPCNode) description: 'Shold use PPCNode for ids'.
   428     ^ self idFor: object prefixed: object prefix suffixed: suffix effect: #none
   494     ^ self idFor: object prefixed: object prefix suffixed: suffix effect: #none
       
   495 !
       
   496 
       
   497 numberIdFor: object
       
   498     ^ idGen numericIdFor: object
   429 ! !
   499 ! !
   430 
   500 
   431 !PPCCodeGen methodsFor:'initialization'!
   501 !PPCCodeGen methodsFor:'initialization'!
   432 
   502 
   433 copy: parser
   503 copy: parser
   439     super initialize.
   509     super initialize.
   440 
   510 
   441     compilerStack := Stack new.
   511     compilerStack := Stack new.
   442     methodCache := IdentityDictionary new.
   512     methodCache := IdentityDictionary new.
   443     constants := Dictionary new.
   513     constants := Dictionary new.
   444     idCache := IdentityDictionary new.
   514     idGen := PPCIdGenerator new.
   445 ! !
   515 ! !
   446 
   516 
   447 !PPCCodeGen methodsFor:'profiling'!
   517 !PPCCodeGen methodsFor:'profiling'!
   448 
   518 
   449 profileTokenRead: tokenName
   519 profileTokenRead: tokenName
   466     ^ methodCache at: id ifPresent: block
   536     ^ methodCache at: id ifPresent: block
   467 !
   537 !
   468 
   538 
   469 checkCache: id
   539 checkCache: id
   470     | method  |
   540     | method  |
   471     
   541     self flag: 'deprecated?'.
   472     "self halt: 'deprecated?'."
       
   473     
   542     
   474     "Check if method is hand written"
   543     "Check if method is hand written"
   475     method := compiledParser ifNotNil: [ compiledParser compiledMethodAt: id ifAbsent: [ nil ] ].
   544     method := compiledParser ifNotNil: [ compiledParser compiledMethodAt: id ifAbsent: [ nil ] ].
   476     method ifNotNil: [ ^ PPCCompiledMethod new id: id; yourself ].
   545     method ifNotNil: [ ^ PPCCompiledMethod new id: id; yourself ].
   477     
   546     
   533     "Modified: / 01-06-2015 / 21:37:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   602     "Modified: / 01-06-2015 / 21:37:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   534 !
   603 !
   535 
   604 
   536 stopMethod
   605 stopMethod
   537    self cache: currentMethod methodName as: currentMethod.
   606    self cache: currentMethod methodName as: currentMethod.
   538 	
       
   539 	"arguments profile ifTrue: [ Transcript show: currentMethod code; cr. ]."
   607 	"arguments profile ifTrue: [ Transcript show: currentMethod code; cr. ]."
   540 	^ self pop.
   608 	^ self pop.
   541 
   609 
   542 	"Modified: / 01-06-2015 / 21:38:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   610 	"Modified: / 01-06-2015 / 21:38:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   543 !
   611 !