PPExpressionParser.st
changeset 4 90de244a7fa2
parent 0 739fe9b7253e
child 11 e6e33e8fe655
equal deleted inserted replaced
3:e1b11f74e142 4:90de244a7fa2
     1 "{ Package: 'squeak:petitparser' }"
     1 "{ Package: 'stx:goodies/petitparser' }"
     2 
     2 
     3 PPDelegateParser subclass:#PPExpressionParser
     3 PPDelegateParser subclass:#PPExpressionParser
     4 	instanceVariableNames:'operators'
     4 	instanceVariableNames:'operators'
     5 	classVariableNames:''
     5 	classVariableNames:''
     6 	poolDictionaries:''
     6 	poolDictionaries:''
     8 !
     8 !
     9 
     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.
    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.
    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.
    12 	expression := PPExpressionParser new.
    13 	parens := $( asParser token trim , expression , $) asParser token trim 
    13 	parens := $( asParser token trim , expression , $) asParser token trim
    14 		==> [ :nodes | nodes second ].
    14 		==> [ :nodes | nodes second ].
    15 	integer := #digit asParser plus token trim
    15 	integer := #digit asParser plus token trim
    16 		==> [ :token | token value asInteger ].
    16 		==> [ :token | token value asInteger ].
    17 	
    17 
    18 Then we define on what term the expression grammar is built on:
    18 Then we define on what term the expression grammar is built on:
    19 	expression term: parens / integer.
    19 	expression term: parens / integer.
    20 	
    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. 
    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 	
    22 
    23 	expression
    23 	expression
    24 		group: [ :g |
    24 		group: [ :g |
    25 			g prefix: $- asParser token trim do: [ :op :a | a negated ] ];
    25 			g prefix: $- asParser token trim do: [ :op :a | a negated ] ];
    26 		group: [ :g |
    26 		group: [ :g |
    27 			g postfix: ''++'' asParser token trim do: [ :a :op | a + 1 ].
    27 			g postfix: ''++'' asParser token trim do: [ :a :op | a + 1 ].
    32 			g left: $* asParser token trim do: [ :a :op :b | a * b ].
    32 			g left: $* asParser token trim do: [ :a :op :b | a * b ].
    33 			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 |
    34 		group: [ :g |
    35 			g left: $+ asParser token trim do: [ :a :op :b | a + b ].
    35 			g left: $+ asParser token trim do: [ :a :op :b | a + b ].
    36 			g left: $- asParser token trim do: [ :a :op :b | a - b ] ].
    36 			g left: $- asParser token trim do: [ :a :op :b | a - b ] ].
    37 		
    37 
    38 After evaluating the above code the ''expression'' is an efficient parser that evaluates examples like:
    38 After evaluating the above code the ''expression'' is an efficient parser that evaluates examples like:
    39 	expression parse: ''-8++''.
    39 	expression parse: ''-8++''.
    40 	expression parse: ''1+2*3''.
    40 	expression parse: ''1+2*3''.
    41 	expression parse: ''1*2+3''.
    41 	expression parse: ''1*2+3''.
    42 	expression parse: ''(1+2)*3''.
    42 	expression parse: ''(1+2)*3''.
    43 	expression parse: ''8/4/2''.
    43 	expression parse: ''8/4/2''.
    44 	expression parse: ''8/(4/2)''.
    44 	expression parse: ''8/(4/2)''.
    45 	expression parse: ''2^2^3''.
    45 	expression parse: ''2^2^3''.
    46 	expression parse: ''(2^2)^3''.
    46 	expression parse: ''(2^2)^3''.
    47 	
    47 
    48 Instance Variables:
    48 Instance Variables:
    49 	operators	<Dictionary>	The operators defined in the current group.'
    49 	operators       <Dictionary>    The operators defined in the current group.'
    50 !
    50 !
    51 
    51 
    52 
    52 
    53 !PPExpressionParser methodsFor:'private'!
    53 !PPExpressionParser methodsFor:'private'!
    54 
    54 
    74 		list := operators at: selector ifAbsent: [ #() ].
    74 		list := operators at: selector ifAbsent: [ #() ].
    75 		list isEmpty
    75 		list isEmpty
    76 			ifTrue: [ term ]
    76 			ifTrue: [ term ]
    77 			ifFalse: [
    77 			ifFalse: [
    78 				self
    78 				self
    79 					perform: selector with: term 
    79 					perform: selector with: term
    80 					with: (list size = 1
    80 					with: (list size = 1
    81 						ifTrue: [ list first first ==> [ :operator | Array with: list first second with: operator ] ]
    81 						ifTrue: [ list first first ==> [ :operator | Array with: list first second with: operator ] ]
    82 						ifFalse: [ 
    82 						ifFalse: [
    83 							list
    83 							list
    84 								inject: PPChoiceParser new
    84 								inject: PPChoiceParser new
    85 								into: [ :choice :each | choice / (each first ==> [ :operator | Array with: each second with: operator ]) ] ]) ] ]
    85 								into: [ :choice :each | choice / (each first ==> [ :operator | Array with: each second with: operator ]) ] ]) ] ]
    86 !
    86 !
    87 
    87 
   100 
   100 
   101 !PPExpressionParser methodsFor:'specifying'!
   101 !PPExpressionParser methodsFor:'specifying'!
   102 
   102 
   103 group: aOneArgumentBlock
   103 group: aOneArgumentBlock
   104 	"Defines a priority group by evaluating aOneArgumentBlock."
   104 	"Defines a priority group by evaluating aOneArgumentBlock."
   105 	
   105 
   106 	operators := Dictionary new.
   106 	operators := Dictionary new.
   107 	parser := [ 
   107 	parser := [
   108 		aOneArgumentBlock value: self.
   108 		aOneArgumentBlock value: self.
   109 	 	self buildOn: parser ]
   109 		self buildOn: parser ]
   110 			ensure: [ operators := nil ]
   110 			ensure: [ operators := nil ]
   111 !
   111 !
   112 
   112 
   113 left: aParser do: aThreeArgumentBlock
   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."
   114 	"Define an operator aParser that is left-associative. Evaluate aThreeArgumentBlock with the first term, the operator, and the second term."
   115 	
   115 
   116 	self operator: #build:left: parser: aParser do: aThreeArgumentBlock
   116 	self operator: #build:left: parser: aParser do: aThreeArgumentBlock
   117 !
   117 !
   118 
   118 
   119 postfix: aParser do: aTwoArgumentBlock
   119 postfix: aParser do: aTwoArgumentBlock
   120 	"Define a postfix operator aParser. Evaluate aTwoArgumentBlock with the term and the operator."
   120 	"Define a postfix operator aParser. Evaluate aTwoArgumentBlock with the term and the operator."
   128 	self operator: #build:prefix: parser: aParser do: aTwoArgumentBlock
   128 	self operator: #build:prefix: parser: aParser do: aTwoArgumentBlock
   129 !
   129 !
   130 
   130 
   131 right: aParser do: aThreeArgumentBlock
   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."
   132 	"Define an operator aParser that is right-associative. Evaluate aThreeArgumentBlock with the first term, the operator, and the second term."
   133 	
   133 
   134 	self operator: #build:right: parser: aParser do: aThreeArgumentBlock
   134 	self operator: #build:right: parser: aParser do: aThreeArgumentBlock
   135 !
   135 !
   136 
   136 
   137 term: aParser
   137 term: aParser
   138 	"Defines the initial term aParser of the receiver."
   138 	"Defines the initial term aParser of the receiver."
   139 	
   139 
   140 	parser isNil
   140 	parser isNil
   141 		ifTrue: [ parser := aParser ]
   141 		ifTrue: [ parser := aParser ]
   142 		ifFalse: [ self error: 'Unable to redefine the term.' ]
   142 		ifFalse: [ self error: 'Unable to redefine the term.' ]
   143 ! !
   143 ! !
   144 
   144 
   145 !PPExpressionParser class methodsFor:'documentation'!
   145 !PPExpressionParser class methodsFor:'documentation'!
   146 
   146 
   147 version_SVN
   147 version_SVN
   148     ^ '$Id: PPExpressionParser.st,v 1.1 2011-08-18 18:56:17 cg Exp $'
   148     ^ '$Id: PPExpressionParser.st,v 1.2 2012-01-13 11:22:50 cg Exp $'
   149 ! !
   149 ! !