compiler/tests/PPCVerificationTest.st
changeset 438 20598d7ce9fa
child 451 989570319d14
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/compiler/tests/PPCVerificationTest.st	Thu Apr 30 23:43:14 2015 +0200
@@ -0,0 +1,113 @@
+"{ 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'.
+	result := normalParser parse: source.
+	
+	result isPetitFailure not ifTrue: [ 
+		compiledParser := self compiledJavaSyntax.
+		self assert: (compiledParser parse: source withContext: self context)
+			  equals: result
+	]
+! !
+
+!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 methods do: [ :m |
+		source := m sourceCode.
+		self assert: (normalParser parse: source) 
+			  equals: (compiledParser parse: source withContext: self context). 
+	].
+!
+
+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). 
+	].
+! !
+