Merge
authorJan Vrany <jan.vrany@fit.cvut.cz>
Sun, 10 May 2015 06:46:56 +0100
changeset 453 bd5107faf4d6
parent 451 989570319d14 (diff)
parent 452 9f4558b3be66 (current diff)
child 454 a9cd5ea7cc36
Merge
compiler/PPCCodeGenerator.st
compiler/PPCCompiler.st
compiler/PPCFirstPrototype.st
compiler/PPCLLChoiceNode.st
compiler/PPCMethod.st
compiler/PPCOptimizingVisitor.st
compiler/PPCTokenSequenceNode.st
compiler/benchmarks/PPCBenchmarkResources.st
compiler/tests/PPCInliningVisitorTest.st
compiler/tests/PPCNodeCompilingTest.st
compiler/tests/PPCNodeTest.st
compiler/tests/PPCOptimizingTest.st
compiler/tests/PPCOptimizingVisitorTest.st
compiler/tests/PPCProtype1Test.st
compiler/tests/PPCTokenVisitorTest.st
compiler/tests/PPCVerificationTest.st
compiler/tests/PPCompiledExpressionGrammarResource.st
compiler/tests/PPCompiledJavaResource.st
compiler/tests/PPCompiledJavaSyntaxTest.st
compiler/tests/PPCompiledSmalltalkGrammarResource.st
compiler/tests/PPCompiledSmalltalkGrammarTests.st
--- a/Make.proto	Sun May 10 06:28:36 2015 +0100
+++ b/Make.proto	Sun May 10 06:46:56 2015 +0100
@@ -21,7 +21,7 @@
 INCLUDE_TOP=$(TOP)/..
 
 # subdirectories where targets are to be made:
-SUBDIRS= analyzer tests
+SUBDIRS= analyzer parser/smalltalk parser/java compiler
 
 
 # subdirectories where Makefiles are to be made:
--- a/analyzer/Make.proto	Sun May 10 06:28:36 2015 +0100
+++ b/analyzer/Make.proto	Sun May 10 06:46:56 2015 +0100
@@ -108,7 +108,7 @@
 
 
 # build all packages containing referenced classes for this package
-# they are nor needed to compile the package
+# they are not needed to compile the package (but later, to load it)
 references:
 
 
--- a/bmake.bat	Sun May 10 06:28:36 2015 +0100
+++ b/bmake.bat	Sun May 10 06:46:56 2015 +0100
@@ -17,10 +17,22 @@
 @popd
 
 @echo "***********************************"
-@echo "Buildung stx/goodies/petitparser/tests
+@echo "Buildung stx/goodies/petitparser/parser/smalltalk
 @echo "***********************************"
-@pushd tests
+@pushd parser\smalltalk
 @call bmake %1 %2 || exit /b "%errorlevel%"
 @popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parser/java
+@echo "***********************************"
+@pushd parser\java
+@call bmake %1 %2 || exit /b "%errorlevel%"
+@popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler
+@echo "***********************************"
+@pushd compiler
+@call bmake %1 %2 || exit /b "%errorlevel%"
+@popd
--- a/compiler/PPCCodeGenerator.st	Sun May 10 06:28:36 2015 +0100
+++ b/compiler/PPCCodeGenerator.st	Sun May 10 06:46:56 2015 +0100
@@ -179,7 +179,7 @@
     compiler codeReturn: 'failure'.
     compiler add: '].'.
 
-    "Modified: / 23-04-2015 / 15:59:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 05-05-2015 / 14:39:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitAndNode: node
@@ -295,7 +295,7 @@
     ].
     compiler add: '^ self error: ''no choice suitable'''.
 
-    "Modified: / 23-04-2015 / 21:40:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 05-05-2015 / 14:10:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitEndOfFileNode: node
@@ -397,6 +397,8 @@
     compiler smartRestore: node child from: mementoVar.
 
     compiler add: '^ error ifFalse: [ self error ] ifTrue: [ self clearError. nil ]'.
+
+    "Modified: / 05-05-2015 / 14:29:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitOptionalNode: node
@@ -511,13 +513,16 @@
 !
 
 visitStarAnyNode: node
+    | retvalVar sizeVar |
 
-    compiler addVariable: 'retval size'.
-    compiler add: 'size := context size - context position.'.
-    compiler add: 'retval := Array new: size.'.
-    compiler add: '(1 to: size) do: [ :e | retval at: e put: context next ].'.
-    compiler add: '^ retval'.
+    retvalVar := compiler allocateReturnVariable.
+    sizeVar := compiler allocateTemporaryVariableNamed: 'size'.  
+    compiler add: sizeVar , ' := context size - context position.'.
+    compiler add: retvalVar,' := Array new: ',sizeVar,'.'.
+    compiler add: '(1 to: ',sizeVar,') do: [ :e | ',retvalVar,' at: e put: context next ].'.
+    compiler codeReturn.
     
+    "Modified: / 05-05-2015 / 14:13:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 visitStarCharSetPredicateNode: node
--- a/compiler/PPCCompiler.st	Sun May 10 06:28:36 2015 +0100
+++ b/compiler/PPCCompiler.st	Sun May 10 06:46:56 2015 +0100
@@ -379,10 +379,10 @@
 stopMethod
     self cache: currentMethod methodName as: currentMethod.
     
-    arguments profile ifTrue: [ Transcript crShow: currentMethod code ].
+    arguments profile ifTrue: [ Transcript show: currentMethod code; cr. ].
     ^ self pop.
 
-    "Modified: / 23-04-2015 / 18:36:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-05-2015 / 14:18:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 top
--- a/compiler/tests/PPCInliningVisitorTest.st	Sun May 10 06:28:36 2015 +0100
+++ b/compiler/tests/PPCInliningVisitorTest.st	Sun May 10 06:46:56 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Tests-Visitors'
 !
 
+
 !PPCInliningVisitorTest methodsFor:'as yet unclassified'!
 
 assert: object type: class
@@ -108,15 +109,14 @@
 
     result := visitor visit: node.
         
-    ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:
-    [  
-        self skip: 'skipped test, inlining of pluggable nodes not supported!!'.
+    ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[  
+        self skipIf: true description: 'skipped test, inlining of pluggable nodes not supported!!'.
     ].
 
     self assert: result children first type: PPCPluggableNode.
     self assert: result children first isMarkedForInline.
 
-    "Modified: / 23-04-2015 / 12:18:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-05-2015 / 14:22:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testSequenceInline
@@ -172,3 +172,10 @@
     self assert: result child child type: PPCNilNode.
 ! !
 
+!PPCInliningVisitorTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/compiler/tests/PPCNodeTest.st	Sun May 10 06:28:36 2015 +0100
+++ b/compiler/tests/PPCNodeTest.st	Sun May 10 06:46:56 2015 +0100
@@ -163,7 +163,11 @@
     tree := parser asCompilerTree.
     
     self assert: tree type: PPCPluggableNode.
+        ((Smalltalk respondsTo: #isSmalltalkX) and:[Smalltalk isSmalltalkX]) ifFalse:[  
     self assert: tree block asString = '[ :ctx | [ ctx atEnd ] whileFalse ]'.
+        ]
+
+    "Modified: / 05-05-2015 / 16:24:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testConvertChoice
--- a/compiler/tests/PPCompiledExpressionGrammarResource.st	Sun May 10 06:28:36 2015 +0100
+++ b/compiler/tests/PPCompiledExpressionGrammarResource.st	Sun May 10 06:46:56 2015 +0100
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Tests-ExpressionGrammar'
 !
 
+
 !PPCompiledExpressionGrammarResource methodsFor:'as yet unclassified'!
 
 setUp
@@ -20,7 +21,15 @@
     time := Time millisecondsToRun: [
         PPExpressionGrammar new compileWithConfiguration: configuration.
     ].
-    Transcript crShow: 'Expression grammar compiled in: ', time asString, 'ms'.
+    Transcript show: 'Exprssion grammar compiled in: '; show: time asString; show: 'ms'; cr.
+
+    "Modified: / 01-05-2015 / 14:40:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
     
+!PPCompiledExpressionGrammarResource class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
--- a/islands/Make.proto	Sun May 10 06:28:36 2015 +0100
+++ b/islands/Make.proto	Sun May 10 06:46:56 2015 +0100
@@ -108,7 +108,7 @@
 
 
 # build all packages containing referenced classes for this package
-# they are nor needed to compile the package
+# they are not needed to compile the package (but later, to load it)
 references:
 
 
--- a/islands/tests/Make.proto	Sun May 10 06:28:36 2015 +0100
+++ b/islands/tests/Make.proto	Sun May 10 06:46:56 2015 +0100
@@ -106,7 +106,7 @@
 
 
 # build all packages containing referenced classes for this package
-# they are nor needed to compile the package
+# they are not needed to compile the package (but later, to load it)
 references:
 
 
--- a/lccmake.bat	Sun May 10 06:28:36 2015 +0100
+++ b/lccmake.bat	Sun May 10 06:46:56 2015 +0100
@@ -19,4 +19,32 @@
 @call lccmake %1 %2 || exit /b "%errorlevel%"
 @popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parser/smalltalk
+@echo "***********************************"
+@pushd parser\smalltalk
+@call lccmake %1 %2 || exit /b "%errorlevel%"
+@popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parser/java
+@echo "***********************************"
+@pushd parser\java
+@call lccmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler
+@echo "***********************************"
+@pushd compiler
+@call lccmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler/tests
+@echo "***********************************"
+@pushd compiler\tests
+@call lccmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+
--- a/mingwmake.bat	Sun May 10 06:28:36 2015 +0100
+++ b/mingwmake.bat	Sun May 10 06:46:56 2015 +0100
@@ -27,4 +27,32 @@
 @call mingwmake %1 %2 || exit /b "%errorlevel%"
 @popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parser/smalltalk
+@echo "***********************************"
+@pushd parser\smalltalk
+@call mingwmake %1 %2 || exit /b "%errorlevel%"
+@popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parser/java
+@echo "***********************************"
+@pushd parser\java
+@call mingwmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler
+@echo "***********************************"
+@pushd compiler
+@call mingwmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler/tests
+@echo "***********************************"
+@pushd compiler\tests
+@call mingwmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+
--- a/parsers/java/PJEndOfLineCommentsNode.st	Sun May 10 06:28:36 2015 +0100
+++ b/parsers/java/PJEndOfLineCommentsNode.st	Sun May 10 06:46:56 2015 +0100
@@ -23,7 +23,7 @@
 !
 
 printOn: aStream
-	.^	aStream 
+	^	aStream 
 		nextPutAll: 'EndOfLineComment value ==> ';
 		nextPutAll: self comment.
  
--- a/parsers/java/PPJavaTokenParser.st	Sun May 10 06:28:36 2015 +0100
+++ b/parsers/java/PPJavaTokenParser.st	Sun May 10 06:46:56 2015 +0100
@@ -12,29 +12,31 @@
 !PPJavaTokenParser methodsFor:'parsing'!
 
 parseComments: anArray on: aStream
-	
-	| start comments |
-	comments := anArray.
-	[ 
-		| peekTwice |
-	[ aStream atEnd not and: [ aStream peek isSeparator ] ]
-		whileTrue: [ aStream next ].
-	peekTwice := aStream peekTwice.	
-	  ((peekTwice  first = $/) and: 
-		[ (peekTwice second = $*) or: [peekTwice second = $/]])] whileTrue: [
-"		
-		Transcript show: ('position ', aStream position asString, ' char ', aStream next asString); cr.
-"		
-		aStream next.
-		start := aStream position.
-		(aStream next = $*) 
-			ifTrue: [ aStream upToAll: '*/' ]
-			ifFalse: [ 
-				| position |
-				position := aStream position.
-				aStream upToAnyOf: CharacterSet crlf].
-		comments := comments copyWith: (start to: aStream position) ].
-	^ comments
+        
+        | start comments |
+        comments := anArray.
+        [ 
+                | peekTwice |
+        [ aStream atEnd not and: [ aStream peek isSeparator ] ]
+                whileTrue: [ aStream next ].
+        peekTwice := aStream peekTwice. 
+          ((peekTwice  first = $/) and: 
+                [ (peekTwice second = $*) or: [peekTwice second = $/]])] whileTrue: [
+"               
+                Transcript show: ('position ', aStream position asString, ' char ', aStream next asString); cr.
+"               
+                aStream next.
+                start := aStream position.
+                (aStream next = $*) 
+                        ifTrue: [ aStream upToAll: '*/' ]
+                        ifFalse: [ 
+                                | position |
+                                position := aStream position.
+                                aStream upToAnyOf: (String with: (Character codePoint: 13) with: (Character codePoint: 10))].
+                comments := comments copyWith: (start to: aStream position) ].
+        ^ comments
+
+    "Modified: / 21-04-2015 / 17:23:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 parseOn: aPPContext
--- a/stx_goodies_petitparser.st	Sun May 10 06:28:36 2015 +0100
+++ b/stx_goodies_petitparser.st	Sun May 10 06:46:56 2015 +0100
@@ -112,7 +112,10 @@
     ^ #(
         #'stx:goodies/petitparser/analyzer'
         #'stx:goodies/petitparser/tests'
-    )
+        #'stx:goodies/parsers/smalltalk'
+        #'stx:goodies/parsers/java'
+        #'stx:goodies/compiler'
+)
 ! !
 
 !stx_goodies_petitparser class methodsFor:'description - compilation'!
--- a/vcmake.bat	Sun May 10 06:28:36 2015 +0100
+++ b/vcmake.bat	Sun May 10 06:46:56 2015 +0100
@@ -31,4 +31,32 @@
 @call vcmake %1 %2 || exit /b "%errorlevel%"
 @popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parser/smalltalk
+@echo "***********************************"
+@pushd parser\smalltalk
+@call vcmake %1 %2 || exit /b "%errorlevel%"
+@popd
 
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/parser/java
+@echo "***********************************"
+@pushd parser\java
+@call vcmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler
+@echo "***********************************"
+@pushd compiler
+@call vcmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+@echo "***********************************"
+@echo "Buildung stx/goodies/petitparser/compiler/tests
+@echo "***********************************"
+@pushd compiler\tests
+@call vcmake %1 %2 || exit /b "%errorlevel%"
+@popd
+
+