compiler/tests/PPCVerificationTest.st
changeset 453 bd5107faf4d6
parent 451 989570319d14
parent 452 9f4558b3be66
child 454 a9cd5ea7cc36
--- a/compiler/tests/PPCVerificationTest.st	Tue May 05 16:25:23 2015 +0200
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,141 +0,0 @@
-"{ Package: 'stx:goodies/petitparser/compiler/tests' }"
-
-"{ NameSpace: Smalltalk }"
-
-PPAbstractParserTest subclass:#PPCVerificationTest
-	instanceVariableNames:'parser result context resource'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'PetitCompiler-Tests-Core'
-!
-
-
-!PPCVerificationTest class methodsFor:'as yet unclassified'!
-
-resources
-	^ (OrderedCollection with: PPCompiledJavaResource with: PPCompiledSmalltalkGrammarResource)
-		addAll: super resources;
-		yourself
-! !
-
-!PPCVerificationTest methodsFor:'tests - verification Java'!
-
-compiledJavaSyntax
-	^ (Smalltalk at: #PPCompiledJavaSyntax) new
-!
-
-compiledSmalltalkGrammar
-	^ (Smalltalk at: #PPCompiledSmalltalkGrammar) new
-!
-
-context	
-	^ context := PPCProfilingContext new
-!
-
-javaSyntax
-	^ PPJavaSyntax new
-!
-
-setUp
-	super setUp.
-!
-
-smalltalkGrammar
-	^ PPSmalltalkGrammar new
-!
-
-testJava
-	| compiledParser normalParser |
-	normalParser := self javaSyntax.
-	compiledParser := self compiledJavaSyntax.
-	
-	PPCBenchmarkResources new javaSourcesBig do: [ :source |
-		result := normalParser parse: source.
-		result isPetitFailure not ifTrue: [ 
-			self assert: (compiledParser parse: source withContext: self context)
-				  equals: result
-		]
-	].
-!
-
-testJavaTimer
-        | 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'!
-
-testSmalltalk
-	| compiledParser normalParser expected actual |
-	normalParser := self smalltalkGrammar.
-	compiledParser := self compiledSmalltalkGrammar.
-	
-	PPCBenchmarkResources new smalltalkSourcesBig do: [ :source |
-		expected := normalParser parse: source.
-		expected isPetitFailure ifFalse: [ 
-	 		actual := (compiledParser parse: source withContext: self context). 
-			self assert: expected equals: actual.
-		]
-	].
-!
-
-testSmalltalkClass
-    | 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 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> $'
-! !
-