PPExpressionParser.st
changeset 4 90de244a7fa2
parent 0 739fe9b7253e
child 11 e6e33e8fe655
--- a/PPExpressionParser.st	Mon Sep 12 19:48:53 2011 +0200
+++ b/PPExpressionParser.st	Fri Jan 13 12:22:50 2012 +0100
@@ -1,4 +1,4 @@
-"{ Package: 'squeak:petitparser' }"
+"{ Package: 'stx:goodies/petitparser' }"
 
 PPDelegateParser subclass:#PPExpressionParser
 	instanceVariableNames:'operators'
@@ -10,16 +10,16 @@
 PPExpressionParser comment:'A PPExpressionParser is a parser to conveniently define an expression grammar with prefix, postfix, and left- and right-associative infix operators.
 The following code initializes a parser for arithmetic expressions. First we instantiate an expression parser, a simple parser for expressions in parenthesis and a simple parser for integer numbers.
 	expression := PPExpressionParser new.
-	parens := $( asParser token trim , expression , $) asParser token trim 
+	parens := $( asParser token trim , expression , $) asParser token trim
 		==> [ :nodes | nodes second ].
 	integer := #digit asParser plus token trim
 		==> [ :token | token value asInteger ].
-	
+
 Then we define on what term the expression grammar is built on:
 	expression term: parens / integer.
-	
-Finally we define the operator-groups in descending precedence. Note, that the action blocks receive both, the terms and the parsed operator in the order they appear in the parsed input. 
-	
+
+Finally we define the operator-groups in descending precedence. Note, that the action blocks receive both, the terms and the parsed operator in the order they appear in the parsed input.
+
 	expression
 		group: [ :g |
 			g prefix: $- asParser token trim do: [ :op :a | a negated ] ];
@@ -34,7 +34,7 @@
 		group: [ :g |
 			g left: $+ asParser token trim do: [ :a :op :b | a + b ].
 			g left: $- asParser token trim do: [ :a :op :b | a - b ] ].
-		
+
 After evaluating the above code the ''expression'' is an efficient parser that evaluates examples like:
 	expression parse: ''-8++''.
 	expression parse: ''1+2*3''.
@@ -44,9 +44,9 @@
 	expression parse: ''8/(4/2)''.
 	expression parse: ''2^2^3''.
 	expression parse: ''(2^2)^3''.
-	
+
 Instance Variables:
-	operators	<Dictionary>	The operators defined in the current group.'
+	operators       <Dictionary>    The operators defined in the current group.'
 !
 
 
@@ -76,10 +76,10 @@
 			ifTrue: [ term ]
 			ifFalse: [
 				self
-					perform: selector with: term 
+					perform: selector with: term
 					with: (list size = 1
 						ifTrue: [ list first first ==> [ :operator | Array with: list first second with: operator ] ]
-						ifFalse: [ 
+						ifFalse: [
 							list
 								inject: PPChoiceParser new
 								into: [ :choice :each | choice / (each first ==> [ :operator | Array with: each second with: operator ]) ] ]) ] ]
@@ -102,17 +102,17 @@
 
 group: aOneArgumentBlock
 	"Defines a priority group by evaluating aOneArgumentBlock."
-	
+
 	operators := Dictionary new.
-	parser := [ 
+	parser := [
 		aOneArgumentBlock value: self.
-	 	self buildOn: parser ]
+		self buildOn: parser ]
 			ensure: [ operators := nil ]
 !
 
 left: aParser do: aThreeArgumentBlock
 	"Define an operator aParser that is left-associative. Evaluate aThreeArgumentBlock with the first term, the operator, and the second term."
-	
+
 	self operator: #build:left: parser: aParser do: aThreeArgumentBlock
 !
 
@@ -130,13 +130,13 @@
 
 right: aParser do: aThreeArgumentBlock
 	"Define an operator aParser that is right-associative. Evaluate aThreeArgumentBlock with the first term, the operator, and the second term."
-	
+
 	self operator: #build:right: parser: aParser do: aThreeArgumentBlock
 !
 
 term: aParser
 	"Defines the initial term aParser of the receiver."
-	
+
 	parser isNil
 		ifTrue: [ parser := aParser ]
 		ifFalse: [ self error: 'Unable to redefine the term.' ]
@@ -145,5 +145,5 @@
 !PPExpressionParser class methodsFor:'documentation'!
 
 version_SVN
-    ^ '$Id: PPExpressionParser.st,v 1.1 2011-08-18 18:56:17 cg Exp $'
+    ^ '$Id: PPExpressionParser.st,v 1.2 2012-01-13 11:22:50 cg Exp $'
 ! !