parsers/smalltalk/extensions.st
changeset 385 44a36ed4e484
child 390 17ba167b8ee1
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/parsers/smalltalk/extensions.st	Tue Oct 07 09:42:03 2014 +0100
@@ -0,0 +1,28 @@
+"{ Package: 'stx:goodies/petitparser/parsers/smalltalk' }"!
+
+!PPParser methodsFor:'*petitsmalltalk-operations'!
+
+smalltalkToken
+	^ PPSmalltalkTokenParser on: self
+! !
+
+!RBProgramNode methodsFor:'*petitsmalltalk-accessing'!
+
+addComments: aCollectionOfIntervals
+	(aCollectionOfIntervals isNil or: [ aCollectionOfIntervals isEmpty ])
+		ifFalse: [ self comments: self comments , aCollectionOfIntervals ]
+! !
+
+!RBValueToken methodsFor:'*PetitSmalltalk-Test'!
+
+inputValue
+	self flag: 'ugly hack to deal with PPToken #value deprecation '.
+	^ self value
+! !
+
+!stx_goodies_petitparser_parsers_smalltalk class methodsFor:'documentation'!
+
+extensionsVersion_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !