compiler/tests/PPCCompilerTest.st
changeset 422 116d2b2af905
parent 421 7e08b31e0dae
child 438 20598d7ce9fa
--- a/compiler/tests/PPCCompilerTest.st	Mon Nov 24 00:09:23 2014 +0000
+++ b/compiler/tests/PPCCompilerTest.st	Wed Apr 15 11:28:09 2015 +0100
@@ -1,5 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/compiler/tests' }"
 
+"{ NameSpace: Smalltalk }"
+
 PPAbstractParserTest subclass:#PPCCompilerTest
 	instanceVariableNames:'parser result context'
 	classVariableNames:''
@@ -611,48 +613,6 @@
 	self assert: parser parse: 'zorg' end: 0.	
 !
 
-testGuard1
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: $a asParser.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char = $a ])).
-!
-
-testGuard2
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: #letter asParser.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char isLetter ])).
-!
-
-testGuard3
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: #letter asParser not.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char isLetter not ])).
-!
-
-testGuard4
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: (#letter asParser, #word asParser star).
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char isLetter ])).
-!
-
-testGuard5
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: 'foo' asParser.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | char = $f ])).
-!
-
-testGuard6
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: ('foo' asParser trimmingToken asCompilerTree optimizeTree).
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | (char = $f) ]))
-!
-
-testGuard7
-	| charSet |
-	charSet := PPCCompiler new guardCharSet: ('foo' asParser trimmingToken / 'bar' asParser trimmingToken) asCompilerTree optimizeTree.
-	self assert: (charSet equals: (PPCharSetPredicate on: [ :char | (char = $f) or: [ char = $b ]] )).
-!
-
 testGuardSmalltlakToken
 	parser := (#letter asParser, #word asParser star) smalltalkToken compileWithParameters: { #profile -> true }.
 	self assert: parser parse: 'bar'.
@@ -678,46 +638,6 @@
 	self assert: parser parse: ' ab'.
 ! !
 
-!PPCCompilerTest methodsFor:'tests - verification'!
-
-testClass
-        | compiledParser normalParser source |
-        normalParser := PPSmalltalkGrammar new.
-        compiledParser := normalParser compile.
-        
-        Class methodsDo: [ :m |
-                source := m sourceCode.
-                self assert: (normalParser parse: source) 
-                          equals: (compiledParser parse: source withContext: self context). 
-        ].
-
-    "Modified: / 05-11-2014 / 23:18:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testObject
-        | compiledParser normalParser source |
-        normalParser := PPSmalltalkGrammar new.
-        compiledParser := normalParser compile.
-        
-        Object methodsDo: [ :m |
-                source := m sourceCode.
-                self assert: (normalParser parse: source) 
-                          equals: (compiledParser parse: source withContext: self context). 
-        ].
-
-    "Modified: / 30-10-2014 / 23:22:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-testWhitespace
-	| compiledParser normalParser source |
-	normalParser := PPSmalltalkGrammar new.
-	compiledParser := normalParser compile.
-	
-	source := '  foo ^ 1'.
-	self assert: (normalParser parse: source) 
-		  equals: (compiledParser parse: source withContext: self context).
-! !
-
 !PPCCompilerTest class methodsFor:'documentation'!
 
 version_HG