PPParser.st
changeset 22 c540c8649226
parent 4 90de244a7fa2
child 92 a95137a3ab6a
--- a/PPParser.st	Sat May 05 00:01:11 2012 +0200
+++ b/PPParser.st	Sat May 05 00:01:24 2012 +0200
@@ -7,11 +7,6 @@
 	category:'PetitParser-Parsers'
 !
 
-PPParser comment:'An abstract parser for all parsers in PetitParser. Subclasses implement #parseOn: to perform the actual recursive-descent parsing. All parsers support a variety of methods to perform an actual parse, see the methods in the #parsing protocol. Parsers are combined with a series of operators that can be found in the #operations protocol.
-Instance Variables:
-	properties      <Dictionary>    Stores additional state in the parser object.'
-!
-
 
 !PPParser class methodsFor:'instance creation'!
 
@@ -33,7 +28,7 @@
 
 name
 	"Answer the production name of the receiver."
-
+	
 	^ self propertyAt: #name ifAbsent: [ nil ]
 !
 
@@ -45,19 +40,19 @@
 
 hasProperty: aKey
 	"Test if the property aKey is present."
-
+	
 	^ properties notNil and: [ properties includesKey: aKey ]
 !
 
 propertyAt: aKey
 	"Answer the property value associated with aKey."
-
+	
 	^ self propertyAt: aKey ifAbsent: [ self error: 'Property not found' ]
 !
 
 propertyAt: aKey ifAbsent: aBlock
 	"Answer the property value associated with aKey or, if aKey isn't found, answer the result of evaluating aBlock."
-
+	
 	^ properties isNil
 		ifTrue: [ aBlock value ]
 		ifFalse: [ properties at: aKey ifAbsent: aBlock ]
@@ -65,7 +60,7 @@
 
 propertyAt: aKey ifAbsentPut: aBlock
 	"Answer the property associated with aKey or, if aKey isn't found store the result of evaluating aBlock as new value."
-
+	
 	^ self propertyAt: aKey ifAbsent: [ self propertyAt: aKey put: aBlock value ]
 !
 
@@ -78,13 +73,13 @@
 
 removeProperty: aKey
 	"Remove the property with aKey. Answer the property or raise an error if aKey isn't found."
-
+	
 	^ self removeProperty: aKey ifAbsent: [ self error: 'Property not found' ]
 !
 
 removeProperty: aKey ifAbsent: aBlock
 	"Remove the property with aKey. Answer the value or, if aKey isn't found, answer the result of evaluating aBlock."
-
+	
 	| answer |
 	properties isNil ifTrue: [ ^ aBlock value ].
 	answer := properties removeKey: aKey ifAbsent: aBlock.
@@ -112,15 +107,15 @@
 
 !PPParser methodsFor:'operations'!
 
-, aParser
+, aParser 
 	"Answer a new parser that parses the receiver followed by aParser."
 
 	^ PPSequenceParser with: self with: aParser
 !
 
-/ aParser
+/ aParser 
 	"Answer a new parser that parses the receiver, if the receiver fails try with aParser (ordered-choice)."
-
+	
 	^ PPChoiceParser with: self with: aParser
 !
 
@@ -144,31 +139,31 @@
 
 max: anInteger
 	"Answer a new parser that parses the receiver at most anInteger times."
-
+	
 	^ PPRepeatingParser on: self max: anInteger
 !
 
 memoized
 	"Answer a new memoized parser, for refraining redundant computations. This ensures polynomial time O(n^4) for left-recursive grammars and O(n^3) for non left-recursive grammars in the worst case. Not necessary for most grammars that are carefully written and in O(n) anyway."
-
+	
 	^ PPMemoizedParser on: self
 !
 
 min: anInteger
 	"Answer a new parser that parses the receiver at least anInteger times."
-
+	
 	^ PPRepeatingParser on: self min: anInteger
 !
 
 min: aMinInteger max: aMaxInteger
 	"Answer a new parser that parses the receiver at least aMinInteger and at most aMaxInteger times."
-
+	
 	^ PPRepeatingParser on: self min: aMinInteger max: aMaxInteger
 !
 
 negate
 	"Answer a new parser consumes any input token but the receiver."
-
+	
 	^ self not , #any asParser ==> #second
 !
 
@@ -192,13 +187,13 @@
 
 plusGreedy: aParser
 	"Answer a new parser that parses the receiver one or more times until it reaches aParser. This is a greedy non-blind implementation of the star operator. aParser is not consumed."
-
+	
 	^ self , (self starGreedy: aParser) map: [ :first :rest | rest copyWithFirst: first ]
 !
 
 plusLazy: aParser
 	"Answer a new parser that parses the receiver one or more times until it reaches aParser. This is a lazy non-blind implementation of the star operator. aParser is not consumed."
-
+	
 	^ self , (self starLazy: aParser) map: [ :first :rest | rest copyWithFirst: first ]
 !
 
@@ -210,7 +205,7 @@
 
 starGreedy: aParser
 	"Answer a new parser that parses the receiver zero or more times until it reaches aParser. This is a greedy non-blind implementation of the star operator. aParser is not consumed."
-
+	
 	| parser |
 	parser := PPChoiceParser new.
 	parser setParsers: (Array
@@ -221,7 +216,7 @@
 
 starLazy: aParser
 	"Answer a new parser that parses the receiver zero or more times until it reaches aParser. This is a lazy non-blind implementation of the star operator. aParser is not consumed."
-
+	
 	| parser |
 	parser := PPChoiceParser new.
 	parser setParsers: (Array
@@ -232,13 +227,13 @@
 
 times: anInteger
 	"Answer a new parser that parses the receiver exactly anInteger times."
-
+	
 	^ self min: anInteger max: anInteger
 !
 
 wrapped
 	"Answer a new parser that is simply wrapped."
-
+	
 	^ PPDelegateParser on: self
 !
 
@@ -252,7 +247,7 @@
 
 delimitedBy: aParser
 	"Answer a new parser that parses the receiver one or more times, separated and possibly ended by aParser."
-
+	
 	^ (self separatedBy: aParser) , (aParser optional) ==> [ :node |
 		node second isNil
 			ifTrue: [ node first ]
@@ -261,12 +256,12 @@
 
 separatedBy: aParser
 	"Answer a new parser that parses the receiver one or more times, separated by aParser."
-
+	
 	^ (PPSequenceParser with: self with: (PPSequenceParser with: aParser with: self) star) ==> [ :nodes |
 		| result |
 		result := Array new: 2 * nodes second size + 1.
 		result at: 1 put: nodes first.
-		nodes second
+		nodes second 
 			keysAndValuesDo: [ :index :pair | result replaceFrom: 2 * index to: 2 * index + 1 with: pair startingAt: 1 ].
 		result ]
 ! !
@@ -293,13 +288,13 @@
 
 flatten
 	"Answer a new parser that flattens the underlying collection."
-
+	
 	^ PPFlattenParser on: self
 !
 
 foldLeft: aBlock
 	"Answer a new parser that that folds the result of the receiver from left-to-right into aBlock. The argument aBlock must take two or more arguments."
-
+	
 	| size args |
 	size := aBlock numArgs.
 	args := Array new: size.
@@ -329,37 +324,37 @@
 
 map: aBlock
 	"Answer a new parser that works on the receiving sequence an passes in each element as a block argument."
-
+	
 	^ self ==> aBlock
 !
 
 token
 	"Answer a new parser that transforms the input to a token."
-
+	
 	^ PPTokenParser on: self
 !
 
 token: aTokenClass
 	"Answer a new parser that transforms the input to a token of class aTokenClass."
-
+	
 	^ self token tokenClass: aTokenClass
 !
 
 trim
 	"Answer a new parser that consumes spaces before and after the receiving parser."
-
+	
 	^ self trimSpaces
 !
 
 trimBlanks
 	"Answer a new parser that consumes blanks before and after the receiving parser."
-
+	
 	^ PPTrimmingParser on: self trimmer: #blank asParser
 !
 
 trimSpaces
 	"Answer a new parser that consumes spaces before and after the receiving parser."
-
+	
 	^ PPTrimmingParser on: self trimmer: #space asParser
 ! !
 
@@ -367,7 +362,7 @@
 
 matches: anObject
 	"Answer if anObject can be parsed by the receiver."
-
+	
 	^ (self parse: anObject) isPetitFailure not
 !
 
@@ -376,7 +371,7 @@
 
 	| result |
 	result := OrderedCollection new.
-	self
+	self 
 		matchesIn: anObject
 		do: [ :each | result addLast: each ].
 	^ result
@@ -390,7 +385,7 @@
 
 matchingRangesIn: anObject
 	"Search anObject repeatedly for the matches of the receiver.  Answer an OrderedCollection of ranges of each match (index of first character to: index of last character)."
-
+	
 	| result |
 	result := OrderedCollection new.
 	self
@@ -401,7 +396,7 @@
 
 matchingRangesIn: anObject do: aBlock
 	"Search anObject repeatedly for the matches of the receiver.  Answer an OrderedCollection of ranges of each match (index of first character to: index of last character)."
-
+	
 	| result |
 	result := OrderedCollection new.
 	[ :stream | stream position + 1 ] asParser , self , [ :stream | stream position ] asParser
@@ -412,13 +407,13 @@
 
 parse: anObject
 	"Parse anObject with the receiving parser and answer the parse-result or an instance of PPFailure."
-
+	
 	^ self parseOn: anObject asPetitStream
 !
 
 parse: anObject onError: aBlock
 	"Parse anObject with the receiving parser and answer the parse-result or answer the result of evaluating aBlock. Depending on the number of arguments of the block it is simply evaluated, evaluated with the failure object, or evaluated with the error message and position."
-
+	
 	| result |
 	result := self parse: anObject.
 	result isPetitFailure
@@ -432,7 +427,7 @@
 
 parseOn: aStream
 	"Parse aStream with the receiving parser and answer the parse-result or an instance of PPFailure. Override this method in subclasses to specify custom parse behavior. Do not call this method from outside, instead use #parse:."
-
+	
 	self subclassResponsibility
 ! !
 
@@ -463,6 +458,14 @@
 
 !PPParser class methodsFor:'documentation'!
 
+version
+    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPParser.st,v 1.3 2012-05-04 22:01:24 vrany Exp $'
+!
+
+version_CVS
+    ^ '$Header: /cvs/stx/stx/goodies/petitparser/PPParser.st,v 1.3 2012-05-04 22:01:24 vrany Exp $'
+!
+
 version_SVN
-    ^ '$Id: PPParser.st,v 1.2 2012-01-13 11:22:50 cg Exp $'
+    ^ '§Id: PPParser.st 2 2010-12-17 18:44:23Z vranyj1 §'
 ! !