parsers/smalltalk/extensions.st
changeset 385 44a36ed4e484
child 390 17ba167b8ee1
equal deleted inserted replaced
384:a613ecf5d2a1 385:44a36ed4e484
       
     1 "{ Package: 'stx:goodies/petitparser/parsers/smalltalk' }"!
       
     2 
       
     3 !PPParser methodsFor:'*petitsmalltalk-operations'!
       
     4 
       
     5 smalltalkToken
       
     6 	^ PPSmalltalkTokenParser on: self
       
     7 ! !
       
     8 
       
     9 !RBProgramNode methodsFor:'*petitsmalltalk-accessing'!
       
    10 
       
    11 addComments: aCollectionOfIntervals
       
    12 	(aCollectionOfIntervals isNil or: [ aCollectionOfIntervals isEmpty ])
       
    13 		ifFalse: [ self comments: self comments , aCollectionOfIntervals ]
       
    14 ! !
       
    15 
       
    16 !RBValueToken methodsFor:'*PetitSmalltalk-Test'!
       
    17 
       
    18 inputValue
       
    19 	self flag: 'ugly hack to deal with PPToken #value deprecation '.
       
    20 	^ self value
       
    21 ! !
       
    22 
       
    23 !stx_goodies_petitparser_parsers_smalltalk class methodsFor:'documentation'!
       
    24 
       
    25 extensionsVersion_HG
       
    26 
       
    27     ^ '$Changeset: <not expanded> $'
       
    28 ! !