PPExpressionParser.st
changeset 0 739fe9b7253e
child 4 90de244a7fa2
equal deleted inserted replaced
-1:000000000000 0:739fe9b7253e
       
     1 "{ Package: 'squeak:petitparser' }"
       
     2 
       
     3 PPDelegateParser subclass:#PPExpressionParser
       
     4 	instanceVariableNames:'operators'
       
     5 	classVariableNames:''
       
     6 	poolDictionaries:''
       
     7 	category:'PetitParser-Tools'
       
     8 !
       
     9 
       
    10 PPExpressionParser comment:'A PPExpressionParser is a parser to conveniently define an expression grammar with prefix, postfix, and left- and right-associative infix operators.
       
    11 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.
       
    12 	expression := PPExpressionParser new.
       
    13 	parens := $( asParser token trim , expression , $) asParser token trim 
       
    14 		==> [ :nodes | nodes second ].
       
    15 	integer := #digit asParser plus token trim
       
    16 		==> [ :token | token value asInteger ].
       
    17 	
       
    18 Then we define on what term the expression grammar is built on:
       
    19 	expression term: parens / integer.
       
    20 	
       
    21 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. 
       
    22 	
       
    23 	expression
       
    24 		group: [ :g |
       
    25 			g prefix: $- asParser token trim do: [ :op :a | a negated ] ];
       
    26 		group: [ :g |
       
    27 			g postfix: ''++'' asParser token trim do: [ :a :op | a + 1 ].
       
    28 			g postfix: ''--'' asParser token trim do: [ :a :op | a - 1 ] ];
       
    29 		group: [ :g |
       
    30 			g right: $^ asParser token trim do: [ :a :op :b | a raisedTo: b ] ];
       
    31 		group: [ :g |
       
    32 			g left: $* asParser token trim do: [ :a :op :b | a * b ].
       
    33 			g left: $/ asParser token trim do: [ :a :op :b | a / b ] ];
       
    34 		group: [ :g |
       
    35 			g left: $+ asParser token trim do: [ :a :op :b | a + b ].
       
    36 			g left: $- asParser token trim do: [ :a :op :b | a - b ] ].
       
    37 		
       
    38 After evaluating the above code the ''expression'' is an efficient parser that evaluates examples like:
       
    39 	expression parse: ''-8++''.
       
    40 	expression parse: ''1+2*3''.
       
    41 	expression parse: ''1*2+3''.
       
    42 	expression parse: ''(1+2)*3''.
       
    43 	expression parse: ''8/4/2''.
       
    44 	expression parse: ''8/(4/2)''.
       
    45 	expression parse: ''2^2^3''.
       
    46 	expression parse: ''(2^2)^3''.
       
    47 	
       
    48 Instance Variables:
       
    49 	operators	<Dictionary>	The operators defined in the current group.'
       
    50 !
       
    51 
       
    52 
       
    53 !PPExpressionParser methodsFor:'private'!
       
    54 
       
    55 build: aParser left: aChoiceParser
       
    56 	^ (aParser separatedBy: aChoiceParser) foldLeft: [ :a :op :b | op first value: a value: op second value: b ]
       
    57 !
       
    58 
       
    59 build: aParser postfix: aChoiceParser
       
    60 	^ aParser , aChoiceParser star map: [ :term :ops | ops inject: term into: [ :result :operator | operator first value: result value: operator second ] ]
       
    61 !
       
    62 
       
    63 build: aParser prefix: aChoiceParser
       
    64 	^ aChoiceParser star , aParser map: [ :ops :term | ops reversed inject: term into: [ :result :operator | operator first value: operator second value: result ] ]
       
    65 !
       
    66 
       
    67 build: aParser right: aChoiceParser
       
    68 	^ (aParser separatedBy: aChoiceParser) foldRight: [ :a :op :b | op first value: a value: op second value: b ]
       
    69 !
       
    70 
       
    71 buildOn: aParser
       
    72 	^ self buildSelectors inject: aParser into: [ :term :selector |
       
    73 		| list |
       
    74 		list := operators at: selector ifAbsent: [ #() ].
       
    75 		list isEmpty
       
    76 			ifTrue: [ term ]
       
    77 			ifFalse: [
       
    78 				self
       
    79 					perform: selector with: term 
       
    80 					with: (list size = 1
       
    81 						ifTrue: [ list first first ==> [ :operator | Array with: list first second with: operator ] ]
       
    82 						ifFalse: [ 
       
    83 							list
       
    84 								inject: PPChoiceParser new
       
    85 								into: [ :choice :each | choice / (each first ==> [ :operator | Array with: each second with: operator ]) ] ]) ] ]
       
    86 !
       
    87 
       
    88 buildSelectors
       
    89 	^ #(build:prefix: build:postfix: build:right: build:left:)
       
    90 !
       
    91 
       
    92 operator: aSymbol parser: aParser do: aBlock
       
    93 	parser isNil
       
    94 		ifTrue: [ ^ self error: 'You did not specify a term when creating the receiver.' ].
       
    95 	operators isNil
       
    96 		ifTrue: [ ^ self error: 'Use #group: to define precedence groups in descending order.' ].
       
    97 	(operators at: aSymbol ifAbsentPut: [ OrderedCollection new ])
       
    98 		addLast: (Array with: aParser asParser with: aBlock)
       
    99 ! !
       
   100 
       
   101 !PPExpressionParser methodsFor:'specifying'!
       
   102 
       
   103 group: aOneArgumentBlock
       
   104 	"Defines a priority group by evaluating aOneArgumentBlock."
       
   105 	
       
   106 	operators := Dictionary new.
       
   107 	parser := [ 
       
   108 		aOneArgumentBlock value: self.
       
   109 	 	self buildOn: parser ]
       
   110 			ensure: [ operators := nil ]
       
   111 !
       
   112 
       
   113 left: aParser do: aThreeArgumentBlock
       
   114 	"Define an operator aParser that is left-associative. Evaluate aThreeArgumentBlock with the first term, the operator, and the second term."
       
   115 	
       
   116 	self operator: #build:left: parser: aParser do: aThreeArgumentBlock
       
   117 !
       
   118 
       
   119 postfix: aParser do: aTwoArgumentBlock
       
   120 	"Define a postfix operator aParser. Evaluate aTwoArgumentBlock with the term and the operator."
       
   121 
       
   122 	self operator: #build:postfix: parser: aParser do: aTwoArgumentBlock
       
   123 !
       
   124 
       
   125 prefix: aParser do: aTwoArgumentBlock
       
   126 	"Define a prefix operator aParser. Evaluate aTwoArgumentBlock with the operator and the term."
       
   127 
       
   128 	self operator: #build:prefix: parser: aParser do: aTwoArgumentBlock
       
   129 !
       
   130 
       
   131 right: aParser do: aThreeArgumentBlock
       
   132 	"Define an operator aParser that is right-associative. Evaluate aThreeArgumentBlock with the first term, the operator, and the second term."
       
   133 	
       
   134 	self operator: #build:right: parser: aParser do: aThreeArgumentBlock
       
   135 !
       
   136 
       
   137 term: aParser
       
   138 	"Defines the initial term aParser of the receiver."
       
   139 	
       
   140 	parser isNil
       
   141 		ifTrue: [ parser := aParser ]
       
   142 		ifFalse: [ self error: 'Unable to redefine the term.' ]
       
   143 ! !
       
   144 
       
   145 !PPExpressionParser class methodsFor:'documentation'!
       
   146 
       
   147 version_SVN
       
   148     ^ '$Id: PPExpressionParser.st,v 1.1 2011-08-18 18:56:17 cg Exp $'
       
   149 ! !