Portability: fixes for Smalltalk/X
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 05 May 2015 16:25:23 +0200
changeset 451 989570319d14
parent 450 914c2567c987
child 453 bd5107faf4d6
Portability: fixes for Smalltalk/X
compiler/tests/PPCNodeTest.st
compiler/tests/PPCVerificationTest.st
--- a/compiler/tests/PPCNodeTest.st	Tue May 05 15:07:56 2015 +0200
+++ b/compiler/tests/PPCNodeTest.st	Tue May 05 16:25:23 2015 +0200
@@ -112,12 +112,16 @@
 !PPCNodeTest methodsFor:'tests - converting'!
 
 testConvertBlock
-	| parser tree |
-	parser := [ :ctx | [ctx atEnd] whileFalse ] asParser.
-	tree := parser asCompilerTree.
-	
-	self assert: tree type: PPCPluggableNode.
-	self assert: tree block asString = '[ :ctx | [ ctx atEnd ] whileFalse ]'.
+        | parser tree |
+        parser := [ :ctx | [ctx atEnd] whileFalse ] asParser.
+        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/PPCVerificationTest.st	Tue May 05 15:07:56 2015 +0200
+++ b/compiler/tests/PPCVerificationTest.st	Tue May 05 16:25:23 2015 +0200
@@ -9,6 +9,7 @@
 	category:'PetitCompiler-Tests-Core'
 !
 
+
 !PPCVerificationTest class methodsFor:'as yet unclassified'!
 
 resources
@@ -58,17 +59,19 @@
 !
 
 testJavaTimer
-	| compiledParser normalParser source |
-	normalParser := self javaSyntax.
-	
-	source := FileStream fileNamed: '../java-src/java/util/Timer.java'.
-	result := normalParser parse: source.
-	
-	result isPetitFailure not ifTrue: [ 
-		compiledParser := self compiledJavaSyntax.
-		self assert: (compiledParser parse: source withContext: self context)
-			  equals: result
-	]
+        | compiledParser normalParser source |
+        normalParser := self javaSyntax.
+        
+        source := (FileStream fileNamed: '../java-src/java/util/Timer.java') asString.
+        result := normalParser parse: source.
+        
+        result isPetitFailure not ifTrue: [ 
+                compiledParser := self compiledJavaSyntax.
+                self assert: (compiledParser parse: source withContext: self context)
+                          equals: result
+        ]
+
+    "Modified: / 05-05-2015 / 16:20:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPCVerificationTest methodsFor:'tests - verification Smalltalk'!
@@ -88,26 +91,51 @@
 !
 
 testSmalltalkClass
-	| compiledParser normalParser source |
-	normalParser := self smalltalkGrammar.
-	compiledParser := self compiledSmalltalkGrammar.
-	
-	Class methods do: [ :m |
-		source := m sourceCode.
-		self assert: (normalParser parse: source) 
-			  equals: (compiledParser parse: source withContext: self context). 
-	].
+    | compiledParser normalParser source |
+
+    normalParser := self smalltalkGrammar.
+    compiledParser := self compiledSmalltalkGrammar.        
+    Class methodDictionary do: [ :m |
+        source := m sourceCode.
+        ((Smalltalk respondsTo: #isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
+            m hasPrimitiveCode ifTrue:[
+                source := nil.
+            ]
+        ].
+        source notNil ifTrue:[
+            self assert: (normalParser parse: source) 
+                 equals: (compiledParser parse: source withContext: self context). 
+        ]
+    ].
+
+    "Modified: / 05-05-2015 / 16:21:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 testSmalltalkObject
-	| compiledParser normalParser source |
-	normalParser := self smalltalkGrammar.
-	compiledParser := self compiledSmalltalkGrammar.
-	
-	Object methods do: [ :m |
-		source := m sourceCode.
-		self assert: (normalParser parse: source) 
-			  equals: (compiledParser parse: source withContext: self context). 
-	].
+    | compiledParser normalParser source |
+
+    normalParser := self smalltalkGrammar.
+    compiledParser := self compiledSmalltalkGrammar.    
+    Object methodDictionary do: [ :m |
+        source := m sourceCode.
+        ((Smalltalk respondsTo: #isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
+            m hasPrimitiveCode ifTrue:[
+                source := nil.
+            ]
+        ].
+        source notNil ifTrue:[
+            self assert: (normalParser parse: source) 
+                 equals: (compiledParser parse: source withContext: self context). 
+        ]
+    ].
+
+    "Modified (format): / 05-05-2015 / 16:22:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!PPCVerificationTest class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+