parsers/smalltalk/PPSmalltalkWhitespaceParser.st
changeset 421 7e08b31e0dae
parent 417 3c0a91182e65
--- a/parsers/smalltalk/PPSmalltalkWhitespaceParser.st	Wed Nov 19 10:52:37 2014 +0000
+++ b/parsers/smalltalk/PPSmalltalkWhitespaceParser.st	Mon Nov 24 00:09:23 2014 +0000
@@ -1,7 +1,7 @@
 "{ Package: 'stx:goodies/petitparser/parsers/smalltalk' }"
 
 PPParser subclass:#PPSmalltalkWhitespaceParser
-	instanceVariableNames:'separator'
+	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitSmalltalk-Core'
@@ -19,14 +19,17 @@
 
 initialize
 	super initialize.
-	separator := PPCharSetPredicate on: [ :char | char isSeparator ].
 ! !
 
 !PPSmalltalkWhitespaceParser methodsFor:'parsing'!
 
+name
+	^ 'smalltalk_ws'
+!
+
 parseOn: aPPContext
         "Skip any leading whitespace"
-        [ [aPPContext atEnd not and: [ separator value: aPPContext uncheckedPeek ] ]
+        [ [aPPContext atEnd not and: [  aPPContext uncheckedPeek isSeparator ] ]
                 whileTrue: [ aPPContext next ].
 
         "Check for comment"
@@ -49,7 +52,7 @@
                 ]
         ].
 
-    "Modified: / 07-11-2014 / 01:18:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 21-11-2014 / 10:10:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !PPSmalltalkWhitespaceParser class methodsFor:'documentation'!