compiler/PPCCompiler.st
changeset 502 1e45d3c96ec5
parent 464 f6d77fee9811
child 503 ff58cd9f1f3c
child 515 b5316ef15274
--- a/compiler/PPCCompiler.st	Thu May 21 14:12:22 2015 +0100
+++ b/compiler/PPCCompiler.st	Fri Jul 24 15:06:54 2015 +0100
@@ -17,21 +17,15 @@
 new
     "return an initialized instance"
 
-    ^ self basicNew initializeForCompiledClassName: 'PPGeneratedParser'
-!
-
-newForCompiledClassName: aString
-    "return an initialized instance"
-	self halt: 'deprecated'.
-    ^ self basicNew initializeForCompiledClassName: aString
+    ^ self on: PPCArguments default
 !
 
 on: aPPCArguments
     "return an initialized instance"
 
     ^ self basicNew
-		arguments: aPPCArguments;
-		initializeForCompiledClassName: aPPCArguments name
+                arguments: aPPCArguments;
+                initializeForCompiledClassName: aPPCArguments parserName
 ! !
 
 !PPCCompiler methodsFor:'accessing'!
@@ -71,12 +65,12 @@
 !PPCCompiler methodsFor:'cleaning'!
 
 clean: class
-"	Transcript crShow: 'Cleaning time: ',
+"	Transcript show: ('Cleaning time: ',
     [	
 "		self cleanGeneratedMethods: class.
         self cleanInstVars: class.
         self cleanConstants: class.
-"	] timeToRun asMilliSeconds asString, 'ms'."
+"	] timeToRun asMilliSeconds asString, 'ms'); cr. "
 !
 
 cleanConstants: class
@@ -117,8 +111,16 @@
     currentMethod add: '"', string, '"'.
 !
 
-addConstant: value as: name
+addConstant: value as: name    
+    (constants includesKey: name) ifTrue:[ 
+        (constants at: name) ~= value ifTrue:[ 
+            self error:'Duplicate constant!!'.
+        ].
+        ^ self.
+    ].
     constants at: name put: value
+
+    "Modified: / 29-05-2015 / 07:22:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 addOnLine: string
@@ -171,6 +173,12 @@
 
 !PPCCompiler methodsFor:'code generation - coding'!
 
+code:aStringOrBlockOrRBParseNode
+    currentMethod code: aStringOrBlockOrRBParseNode
+
+    "Created: / 01-06-2015 / 23:49:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 codeAssign: code to: variable
     self assert: variable isNil not.
     
@@ -181,10 +189,42 @@
     ]
 !
 
+codeAssignParsedValueOf:aBlock to:aString 
+    | tmpVarirable  method |
+
+    self assert:aBlock isBlock.
+    self assert:aString isNil not.
+    tmpVarirable := returnVariable.
+    returnVariable := aString.
+    method := [
+            aBlock value
+        ] ensure:[ returnVariable := tmpVarirable ].
+    self assert: (method isKindOf: PPCMethod).
+    method isInline ifTrue:[
+        self callOnLine:method
+    ] ifFalse:[
+        self codeEvaluateAndAssign:(method call) to:aString.
+    ]
+
+    "Created: / 23-04-2015 / 18:21:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+codeBlock: contents
+    currentMethod codeBlock: contents
+
+    "Created: / 01-06-2015 / 22:35:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 codeClearError
     self add: 'self clearError.'.
 !
 
+codeDot
+    self addOnLine:'.'.
+
+    "Created: / 16-06-2015 / 06:09:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 codeError
     self add: 'self error: ''message notspecified''.'.
 !
@@ -204,9 +244,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	
     ]
 !
 
@@ -237,6 +277,45 @@
     "Modified: / 10-05-2015 / 07:39:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+codeIf: condition then: then 
+    self codeIf: condition then: then else: nil
+
+    "Created: / 16-06-2015 / 06:07:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+codeIf: condition then: then else: else
+    currentMethod 
+        add: '(';
+        code: condition;
+        addOnLine: ')'.
+    then notNil ifTrue:[ 
+        currentMethod 
+            addOnLine:' ifTrue:';
+            codeBlock: then.
+    ].
+    else notNil ifTrue:[ 
+        currentMethod 
+            addOnLine:' ifFalse:';
+            codeBlock: else.
+    ].
+    self codeDot.
+
+    "Created: / 01-06-2015 / 22:43:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-06-2015 / 06:09:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+codeIfErrorThen: then
+    ^ self codeIf: 'error' then: then else: nil
+
+    "Created: / 16-06-2015 / 06:06:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+codeIfErrorThen: then else: else
+    ^ self codeIf: 'error' then: then else: else
+
+    "Created: / 16-06-2015 / 06:05:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 codeNextToken
     self add: 'self nextToken.'
 
@@ -244,28 +323,65 @@
     "Modified: / 23-04-2015 / 20:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+codeProfileStart
+    self add: 'context methodInvoked: #', currentMethod methodName, '.'
+
+    "Created: / 01-06-2015 / 21:17:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+codeProfileStop
+    self add: 'context methodFinished: #', currentMethod methodName, '.'
+
+    "Created: / 01-06-2015 / 21:19:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 codeReturn
    currentMethod isInline ifTrue: [
-				"If inlined, the return variable already holds the value"
-		] ifFalse: [
-				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: / 23-04-2015 / 20:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	"Modified: / 01-06-2015 / 21:49:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 codeReturn: code
     " - returns whatever is in code OR
       - assigns whatever is in code into the returnVariable"
-   currentMethod isInline ifTrue:[ 
+    currentMethod isInline ifTrue:[
         self codeEvaluateAndAssign: code to: currentMethod returnVariable. 
-   ] ifFalse: [ 
-        self add: '^ ', code 		
+    ] ifFalse: [ 
+        arguments profile ifTrue:[ 
+            self codeProfileStop.
+        ].   
+        self add: '^ ', code            
     ]
 
     "Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 23-04-2015 / 20:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "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
@@ -419,12 +535,11 @@
     
     currentMethod := PPCInlinedMethod new.
     currentMethod id: id.   
-    currentMethod profile: arguments profile.
     currentMethod returnVariable: returnVariable.
     currentMethod indentationLevel: indentationLevel.
     self push.
 
-    "Modified: / 23-04-2015 / 18:28:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-06-2015 / 21:48:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 startMethod: id
@@ -432,28 +547,29 @@
 
     currentMethod := PPCMethod new.
     currentMethod id: id.
-    currentMethod profile: arguments profile.    
+    arguments profile ifTrue:[ 
+        self codeProfileStart.
+    ].
     self push.      
                 
     self cache: id as: currentMethod.
 
-    "Modified: / 23-04-2015 / 18:36:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-06-2015 / 21:19:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 stopInline
-
     ^ self pop.
 
-    "Modified: / 23-04-2015 / 18:28:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-06-2015 / 21:37:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 stopMethod
-    self cache: currentMethod methodName as: currentMethod.
-    
-    "arguments profile ifTrue: [ Transcript show: currentMethod code; cr. ]."
-    ^ self pop.
+   self cache: currentMethod methodName as: currentMethod.
+	
+	"arguments profile ifTrue: [ Transcript show: currentMethod code; cr. ]."
+	^ self pop.
 
-    "Modified: / 01-05-2015 / 14:18:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+	"Modified: / 01-06-2015 / 21:38:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 top
@@ -462,13 +578,19 @@
 
 !PPCCompiler methodsFor:'code generation - variables'!
 
-allocateReturnVariable
-    "Return a new variable to store parsed value"
+allocateReturnVariable    
+    ^ self allocateReturnVariableNamed: 'retval'
+
+    "Created: / 23-04-2015 / 18:03:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-06-2015 / 17:52:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
 
-   ^ currentMethod allocateReturnVariable 
+allocateReturnVariableNamed: name
+    "Allocate (or return previously allocated one) temporary variable used for
+     storing a parser's return value (the parsed object)"                 
+    ^ currentMethod allocateReturnVariableNamed: name
 
-    "Created: / 23-04-2015 / 17:58:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified (comment): / 23-04-2015 / 21:12:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 15-06-2015 / 18:04:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 allocateTemporaryVariableNamed: preferredName 
@@ -527,7 +649,7 @@
     self initialize.
     compilerStack := Stack new.
     cache := IdentityDictionary new.
-    constants := IdentityDictionary new.
+    constants := Dictionary new.
     ids := IdentityDictionary new.
     
 
@@ -550,6 +672,8 @@
 
 
     Transcript cr; show: 'intialized for: ', aString; cr.
+
+    "Modified: / 26-05-2015 / 17:09:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCCompiler class methodsFor:'documentation'!