compiler/PPCCodeGen.st
changeset 515 b5316ef15274
parent 502 1e45d3c96ec5
child 524 f6f68d32de73
--- a/compiler/PPCCodeGen.st	Fri Jul 24 15:06:54 2015 +0100
+++ b/compiler/PPCCodeGen.st	Mon Aug 17 12:13:16 2015 +0100
@@ -4,7 +4,7 @@
 
 Object subclass:#PPCCodeGen
 	instanceVariableNames:'compilerStack compiledParser methodCache currentMethod constants
-		returnVariable arguments idCache'
+		returnVariable arguments idGen'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-Compiler-Codegen'
@@ -52,8 +52,16 @@
     ^ currentMethod returnVariable 
 !
 
+idGen
+    ^ idGen
+!
+
+idGen: anObject
+    idGen := anObject
+!
+
 ids
-    ^ idCache keys
+    ^ idGen ids
 !
 
 methodCategory
@@ -144,6 +152,10 @@
     "Created: / 01-06-2015 / 23:49:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+codeAssert: aCode
+    self add: 'self assert: (', aCode, ').'.
+!
+
 codeAssign: code to: variable
     self assert: variable isNil not.
     
@@ -164,6 +176,7 @@
     method := [
             aBlock value
         ] ensure:[ returnVariable := tmpVarirable ].
+    self assert: (method isKindOf: PPCMethod).	
     method isInline ifTrue:[
         self callOnLine:method
     ] ifFalse:[
@@ -179,6 +192,11 @@
     "Created: / 01-06-2015 / 22:35:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+codeCall: aMethod
+    self assert: (aMethod isKindOf: PPCMethod).
+    self add: aMethod call.
+!
+
 codeClearError
     self add: 'self clearError.'.
 !
@@ -212,9 +230,9 @@
     (variable == #whatever) ifFalse: [ 
         "Do not assign, if somebody does not care!!"
         self add: variable, ' ', selector,' ', argument.
- 		] ifTrue: [ 
+ 	] ifTrue: [ 
         "In case argument has a side effect"
- 				self add: argument	
+ 		self add: argument	
     ]
 !
 
@@ -227,7 +245,7 @@
         self add: variable ,' := ', argument.
     ] ifTrue: [ 
         "In case an argument has a side effect"
- 		self add: argument.	
+        self add: argument.	
     ]
 !
 
@@ -254,16 +272,16 @@
 codeIf: condition then: then else: else
     currentMethod 
         add: '(';
-        code: condition;
+        codeOnLine: condition;
         addOnLine: ')'.
     then notNil ifTrue:[ 
         currentMethod 
-            addOnLine:' ifTrue:';
+            addOnLine:' ifTrue: ';
             codeBlock: then.
     ].
     else notNil ifTrue:[ 
         currentMethod 
-            addOnLine:' ifFalse:';
+            addOnLine:' ifFalse: ';
             codeBlock: else.
     ].
     self codeDot.
@@ -291,6 +309,27 @@
     "Modified: / 23-04-2015 / 20:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+codeOnLIne:aStringOrBlockOrRBParseNode
+    currentMethod codeOnLine: aStringOrBlockOrRBParseNode
+
+    "Created: / 01-06-2015 / 23:49:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+codeParsedValueOf: aBlock 
+    | tmpVarirable  method |
+
+    self assert: aBlock isBlock.	
+    tmpVarirable := returnVariable.
+    returnVariable := #whatever.
+    method := [
+        aBlock value
+    ] ensure:[ returnVariable := tmpVarirable ].
+    self assert: returnVariable == tmpVarirable.
+    self assert: (method isKindOf: PPCMethod).
+    
+    self codeCall: method.
+!
+
 codeProfileStart
     self add: 'context methodInvoked: #', currentMethod methodName, '.'
 
@@ -305,16 +344,16 @@
 
 codeReturn
    currentMethod isInline ifTrue: [
-		"If inlined, the return variable already holds the value"
-	] ifFalse: [
-		arguments profile ifTrue:[ 
-			self codeProfileStop.
-		]. 
-		self add: '^ ', currentMethod returnVariable  
-	].
+				"If inlined, the return variable already holds the value"
+		] ifFalse: [
+				arguments profile ifTrue:[ 
+						self codeProfileStop.
+				]. 
+				self add: '^ ', currentMethod returnVariable  
+		].
 
-	"Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-	"Modified: / 01-06-2015 / 21:49:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+		"Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+		"Modified: / 01-06-2015 / 21:49:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 codeReturn: code
@@ -333,6 +372,25 @@
     "Modified: / 01-06-2015 / 21:48:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+codeReturnParsedValueOf: aBlock 
+    | tmpVarirable  method |
+
+    self assert:aBlock isBlock.	
+    tmpVarirable := returnVariable.
+    method := aBlock value. 
+    self assert: returnVariable == tmpVarirable.
+    self assert: (method isKindOf: PPCMethod).
+    method isInline ifTrue:[
+        self callOnLine:method.
+        self codeReturn: returnVariable.
+    ] ifFalse:[
+        self codeReturn: method call.
+        
+    ]
+
+    "Created: / 23-04-2015 / 18:21:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 codeStoreValueOf: aBlock intoVariable: aString
     | tmpVarirable method |
     self assert: aBlock isBlock.
@@ -394,9 +452,12 @@
     "Modified: / 10-05-2015 / 07:29:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-idFor: object
-    self assert: (object canHavePPCId).
-    ^ self idFor: object prefixed: object prefix suffixed: object suffix
+idFor: anObject
+    ^ idGen idFor: anObject
+!
+
+idFor: anObject defaultName: defaultName
+    ^ idGen idFor: anObject defaultName: defaultName
 !
 
 idFor: object prefixed: prefix
@@ -404,14 +465,16 @@
 !
 
 idFor: object prefixed: prefix suffixed: suffix
+    self error: 'Should no longer be used'.
+    "
     | name id |
     ^ idCache at: object ifAbsentPut: [ 
         ((object canHavePPCId) and: [object name isNotNil]) ifTrue: [ 
-            "Do not use prefix, if there is a name"
+            ""Do not use prefix, if there is a name""
             name := self asSelector: (object name asString).
             id := (name, suffix) asSymbol.
             
-            "Make sure, that the generated ID is uniqe!!"
+            ""Make sure, that the generated ID is uniqe!!""
             (idCache includes: id) ifTrue: [ 
                 (id, '_', idCache size asString) asSymbol 
             ] ifFalse: [ 
@@ -421,11 +484,18 @@
             (prefix, '_', (idCache size asString), suffix) asSymbol
         ]
     ]
+    "
+
+    "Modified: / 17-08-2015 / 12:00:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 idFor: object suffixed: suffix
     self assert: (object isKindOf: PPCNode) description: 'Shold use PPCNode for ids'.
     ^ self idFor: object prefixed: object prefix suffixed: suffix effect: #none
+!
+
+numberIdFor: object
+    ^ idGen numericIdFor: object
 ! !
 
 !PPCCodeGen methodsFor:'initialization'!
@@ -441,7 +511,7 @@
     compilerStack := Stack new.
     methodCache := IdentityDictionary new.
     constants := Dictionary new.
-    idCache := IdentityDictionary new.
+    idGen := PPCIdGenerator new.
 ! !
 
 !PPCCodeGen methodsFor:'profiling'!
@@ -468,8 +538,7 @@
 
 checkCache: id
     | method  |
-    
-    "self halt: 'deprecated?'."
+    self flag: 'deprecated?'.
     
     "Check if method is hand written"
     method := compiledParser ifNotNil: [ compiledParser compiledMethodAt: id ifAbsent: [ nil ] ].
@@ -535,7 +604,6 @@
 
 stopMethod
    self cache: currentMethod methodName as: currentMethod.
-	
 	"arguments profile ifTrue: [ Transcript show: currentMethod code; cr. ]."
 	^ self pop.