compiler/PPCCodeGenerator.st
changeset 525 751532c8f3db
parent 516 3b81c9e53352
parent 524 f6f68d32de73
child 529 439c4057517f
equal deleted inserted replaced
523:09afcf28ed60 525:751532c8f3db
     1 "{ Package: 'stx:goodies/petitparser/compiler' }"
     1 "{ Package: 'stx:goodies/petitparser/compiler' }"
     2 
     2 
     3 "{ NameSpace: Smalltalk }"
     3 "{ NameSpace: Smalltalk }"
     4 
     4 
     5 PPCNodeVisitor subclass:#PPCCodeGenerator
     5 PPCNodeVisitor subclass:#PPCCodeGenerator
     6 	instanceVariableNames:'compiler'
     6 	instanceVariableNames:'codeGen'
     7 	classVariableNames:''
     7 	classVariableNames:''
     8 	poolDictionaries:''
     8 	poolDictionaries:''
     9 	category:'PetitCompiler-Visitors'
     9 	category:'PetitCompiler-Visitors-CodeGenerators'
    10 !
    10 !
    11 
    11 
    12 !PPCCodeGenerator class methodsFor:'as yet unclassified'!
    12 !PPCCodeGenerator class methodsFor:'as yet unclassified'!
    13 
    13 
    14 new
    14 new
    23         yourself
    23         yourself
    24 ! !
    24 ! !
    25 
    25 
    26 !PPCCodeGenerator methodsFor:'accessing'!
    26 !PPCCodeGenerator methodsFor:'accessing'!
    27 
    27 
    28 compiler: aPPCCompiler
    28 arguments: args
    29     compiler := aPPCCompiler 
    29     super arguments: args.
       
    30     codeGen arguments: args.
       
    31 !
       
    32 
       
    33 clazz: aPPCClass
       
    34     codeGen clazz: aPPCClass
       
    35 !
       
    36 
       
    37 codeGen
       
    38     ^ codeGen
       
    39 !
       
    40 
       
    41 codeGen: anObject
       
    42     codeGen := anObject
    30 !
    43 !
    31 
    44 
    32 guards
    45 guards
    33     ^ arguments guards
    46     ^ arguments guards
    34 ! !
    47 ! !
    40     | children |
    53     | children |
    41 
    54 
    42     children := choiceNode children.
    55     children := choiceNode children.
    43     useGuards ifTrue:[
    56     useGuards ifTrue:[
    44         self addGuard: (children at: choiceChildNodeIndex) ifTrue: [ 
    57         self addGuard: (children at: choiceChildNodeIndex) ifTrue: [ 
    45                     compiler add: 'self clearError.'.
    58                     codeGen codeClearError.
    46                     compiler 
    59                     codeGen 
    47                           codeAssignParsedValueOf:[ self visit:(children at: choiceChildNodeIndex) ]
    60                           codeEvaluateAndAssign:[ self visit:(children at: choiceChildNodeIndex) ]
    48                           to: resultVar.
    61                           to: resultVar.
    49                     compiler add: 'error ifFalse: [ '.
    62                     codeGen codeIf: 'error' then: nil else: [ 
    50                     compiler codeReturn: resultVar.  
    63                         codeGen codeReturn: resultVar.  
    51                     compiler add: ' ].'.
    64                     ].
    52                 ] ifFalse:[ 
    65                 ] ifFalse:[ 
    53                     compiler add: 'error := true.'.
    66                     codeGen code: 'error := true.'.
    54                 ].
    67                 ].
    55                 compiler add: 'error ifTrue:[ '.
    68                 codeGen codeIf: 'error' then: [ 
    56                 choiceChildNodeIndex < children size ifTrue:[ 
    69                     choiceChildNodeIndex < children size ifTrue:[ 
       
    70                         self generateChoiceChildOf: choiceNode atIndex: choiceChildNodeIndex + 1 useGuards: useGuards storeResultInto: resultVar.
       
    71                     ] ifFalse:[ 
       
    72                         codeGen codeError: 'no choice suitable'.
       
    73                     ].
       
    74                 ].
       
    75     
       
    76     ] ifFalse:[ 
       
    77                 choiceChildNodeIndex <= children size ifTrue:[ 
       
    78                     codeGen codeClearError.
       
    79                     codeGen 
       
    80                           codeEvaluateAndAssignParsedValueOf:[ self visit:(children at: choiceChildNodeIndex) ]
       
    81                           to: resultVar.
       
    82                     codeGen codeIf: 'error' then: nil else: [ 
       
    83                         codeGen codeReturn: resultVar.  
       
    84                     ].
    57                     self generateChoiceChildOf: choiceNode atIndex: choiceChildNodeIndex + 1 useGuards: useGuards storeResultInto: resultVar.
    85                     self generateChoiceChildOf: choiceNode atIndex: choiceChildNodeIndex + 1 useGuards: useGuards storeResultInto: resultVar.
    58                 ] ifFalse:[ 
    86                 ] ifFalse:[ 
    59                     compiler codeError: 'no choice suitable'.
    87                     codeGen codeError: 'no choice suitable'.
    60                 ].
       
    61                 compiler addOnLine: '].'.
       
    62     
       
    63     ] ifFalse:[ 
       
    64                 choiceChildNodeIndex <= children size ifTrue:[ 
       
    65                     compiler add: 'self clearError.'.
       
    66                     compiler 
       
    67                           codeAssignParsedValueOf:[ self visit:(children at: choiceChildNodeIndex) ]
       
    68                           to: resultVar.
       
    69                     compiler add: 'error ifFalse: [ '.
       
    70                     compiler codeReturn: resultVar.  
       
    71                     compiler add: ' ].'.
       
    72                     self generateChoiceChildOf: choiceNode atIndex: choiceChildNodeIndex + 1 useGuards: useGuards storeResultInto: resultVar.
       
    73                 ] ifFalse:[ 
       
    74                     compiler codeError: 'no choice suitable'.
       
    75                 ].
    88                 ].
    76     ].
    89     ].
    77 
    90 
    78     
    91     
    79 !
    92 !
    81 generateSequenceChildOf: sequenceNode atIndex: sequenceNodeChildIndex useMememntoVar: mementoVar storeResultInto: elementVars
    94 generateSequenceChildOf: sequenceNode atIndex: sequenceNodeChildIndex useMememntoVar: mementoVar storeResultInto: elementVars
    82         | child childValueVar |
    95         | child childValueVar |
    83 
    96 
    84         child := sequenceNode children at: sequenceNodeChildIndex.
    97         child := sequenceNode children at: sequenceNodeChildIndex.
    85         childValueVar := elementVars at: sequenceNodeChildIndex.
    98         childValueVar := elementVars at: sequenceNodeChildIndex.
    86         compiler codeAssignParsedValueOf: [ self visit:child ] 
    99         codeGen codeEvaluateAndAssign: [ self visit:child ] 
    87                                       to: childValueVar.
   100                                       to: childValueVar.
    88         child acceptsEpsilon ifFalse: [   
   101         child acceptsEpsilon ifFalse: [   
    89             compiler codeIfErrorThen: [
   102             codeGen codeIfErrorThen: [
    90                 "Handle error in the first element in a special way,
   103                 "Handle error in the first element in a special way,
    91                  because one does not need to do backtracking  if the first element fails."
   104                  because one does not need to do backtracking  if the first element fails."
    92                 (sequenceNodeChildIndex == 1) ifTrue: [                         
   105                 (sequenceNodeChildIndex == 1) ifTrue: [                         
    93                     compiler codeReturn: 'failure'
   106                     codeGen codeReturn: 'failure'
    94                 ] ifFalse: [
   107                 ] ifFalse: [
    95                     compiler smartRestore: sequenceNode from: mementoVar.
   108                     codeGen restore: sequenceNode from: mementoVar.
    96                     compiler codeReturn: 'failure.'.
   109                     codeGen codeReturn: 'failure.'.
    97                 ]
   110                 ]
    98             ] else:[ 
   111             ] else:[ 
    99                 sequenceNode returnParsedObjectsAsCollection ifTrue:[
   112                 sequenceNode returnParsedObjectsAsCollection ifTrue:[
   100                     compiler add: self retvalVar , ' at: ', sequenceNodeChildIndex asString, ' put: ', childValueVar, '.'.
   113                     codeGen code: self retvalVar , ' at: ', sequenceNodeChildIndex asString, ' put: ', childValueVar, '.'.
   101                 ].
   114                 ].
   102                 (sequenceNodeChildIndex < sequenceNode children size) ifTrue:[ 
   115                 (sequenceNodeChildIndex < sequenceNode children size) ifTrue:[ 
   103                     self generateSequenceChildOf: sequenceNode atIndex: sequenceNodeChildIndex + 1 useMememntoVar: mementoVar storeResultInto: elementVars.
   116                     self generateSequenceChildOf: sequenceNode atIndex: sequenceNodeChildIndex + 1 useMememntoVar: mementoVar storeResultInto: elementVars.
   104                 ].
   117                 ].
   105             ]
   118             ]
   106 
   119 
   107         ] ifTrue:[
   120         ] ifTrue:[
   108             sequenceNode returnParsedObjectsAsCollection ifTrue:[
   121             sequenceNode returnParsedObjectsAsCollection ifTrue:[
   109                 compiler add: self retvalVar , ' at: ', sequenceNodeChildIndex asString, ' put: ', childValueVar, '.'.
   122                 codeGen code: self retvalVar , ' at: ', sequenceNodeChildIndex asString, ' put: ', childValueVar, '.'.
   110             ].
   123             ].
   111             (sequenceNodeChildIndex < sequenceNode children size) ifTrue:[ 
   124             (sequenceNodeChildIndex < sequenceNode children size) ifTrue:[ 
   112                     self generateSequenceChildOf: sequenceNode atIndex: sequenceNodeChildIndex + 1 useMememntoVar: mementoVar storeResultInto: elementVars.
   125                     self generateSequenceChildOf: sequenceNode atIndex: sequenceNodeChildIndex + 1 useMememntoVar: mementoVar storeResultInto: elementVars.
   113 
   126 
   114             ].
   127             ].
   115         ]
   128         ]
   116 ! !
   129 ! !
   117 
   130 
   118 !PPCCodeGenerator methodsFor:'guards'!
       
   119 
       
   120 addGuard: node ifTrue: trueBlock ifFalse: falseBlock
       
   121     |  guard id |
       
   122     (self guards not or: [(guard := PPCGuard on: node) makesSense not]) ifTrue: [ ^ false].
       
   123     id := compiler idFor: node.
       
   124 
       
   125 "	falseBlock isNil ifFalse: [ 
       
   126         compiler add: 'context atEnd'.
       
   127         compiler addOnLine: ' ifTrue: ['.
       
   128         compiler indent.
       
   129         falseBlock value.
       
   130         compiler dedent.
       
   131         compiler addOnLine: '].'.
       
   132     ]."
       
   133     
       
   134     guard id: (compiler idFor: guard defaultName: #guard).
       
   135     guard compileGuard: compiler.
       
   136 
       
   137     trueBlock isNil ifFalse: [ 
       
   138         compiler addOnLine: ' ifTrue: ['.
       
   139         compiler indent.
       
   140         trueBlock value.
       
   141         compiler dedent.
       
   142         falseBlock isNil 	ifTrue: [ compiler addOnLine: '].' ]
       
   143                               	ifFalse: [ compiler add: ']'. ]
       
   144     ].
       
   145     falseBlock isNil ifFalse: [ 
       
   146         compiler addOnLine: ' ifFalse: ['.
       
   147         compiler indent.
       
   148         falseBlock value.
       
   149         compiler dedent.
       
   150         compiler addOnLine: '].'.
       
   151     ].
       
   152     ^ true
       
   153 !
       
   154 
       
   155 addGuardTrimming: node
       
   156     |  guard firsts id |
       
   157     (self guards not or: [(guard := PPCGuard on: node) makesSense not]) ifTrue: [ ^ false].
       
   158 
       
   159     id := compiler idFor: node.
       
   160     firsts := node firstSetWithTokens.
       
   161 
       
   162     
       
   163     (firsts allSatisfy: [ :e | e isTrimmingTokenNode ]) ifTrue: [  
       
   164         "If we start with trimming, we should invoke the whitespace parser"
       
   165         self compileTokenWhitespace: firsts anyOne.
       
   166         ^ true
       
   167     ].
       
   168     ^ false
       
   169 ! !
       
   170 
       
   171 !PPCCodeGenerator methodsFor:'hooks'!
   131 !PPCCodeGenerator methodsFor:'hooks'!
   172 
   132 
   173 afterAccept: node retval: retval
   133 afterAccept: node retval: retval
   174     "return the method from compiler"
   134     "return the method from compiler"
   175     ^ self stopMethodForNode: node.
   135     ^ self stopMethodForNode: node.
   184         self error: 'Should not happen!!'
   144         self error: 'Should not happen!!'
   185     ]
   145     ]
   186 !
   146 !
   187 
   147 
   188 openDetected: node
   148 openDetected: node
   189     ^ compiler checkCache: (compiler idFor: node)
   149     ^ codeGen cachedMethod: (codeGen idFor: node)
   190 ! !
   150 ! !
   191 
   151 
   192 !PPCCodeGenerator methodsFor:'private'!
   152 !PPCCodeGenerator methodsFor:'private'!
   193 
   153 
   194 checkBlockIsInlinable: block
   154 checkBlockIsInlinable: block
   228 
   188 
   229         method := aClass lookupSelector: node selector.
   189         method := aClass lookupSelector: node selector.
   230         method isNil ifTrue:[
   190         method isNil ifTrue:[
   231             PPCCompilationError new signalWith: 'oops, no method found (internal error)!!'.        
   191             PPCCompilationError new signalWith: 'oops, no method found (internal error)!!'.        
   232         ].
   192         ].
   233         source := method source.
   193         source := method sourceCode.
   234         source isNil ifTrue:[ 
   194         source isNil ifTrue:[ 
   235             PPCCompilationError new signalWith: 'unavailable source for method ', method printString ,'!!'.        
   195             PPCCompilationError new signalWith: 'unavailable source for method ', method printString ,'!!'.        
   236         ].
   196         ].
   237         "Following actually copies the method to the target class,
   197         "Following actually copies the method to the target class,
   238          though the APU is not nice. This has to be cleaned up"
   198          though the APU is not nice. This has to be cleaned up"
   239         (compiler cachedValue: node selector) isNil ifTrue:[ 
   199         (codeGen cachedMethod: node selector) isNil ifTrue:[ 
   240             compiler cache: node selector as: (PPCMethod new id: node selector; source: source; yourself).
   200             codeGen cacheMethod: (PPCMethod new id: node selector; source: source; yourself) as: node selector.
   241             "Now compile self-sends of the just copied method"
   201             "Now compile self-sends of the just copied method"
   242             self copySelfSentMethodsOf: method parseTree inClass: aClass
   202             self copySelfSentMethodsOf: method parseTree inClass: aClass
   243         ].
   203         ].
   244     ]
   204     ]
   245 
   205 
   247 ! !
   207 ! !
   248 
   208 
   249 !PPCCodeGenerator methodsFor:'support'!
   209 !PPCCodeGenerator methodsFor:'support'!
   250 
   210 
   251 compileTokenWhitespace: node
   211 compileTokenWhitespace: node
   252     compiler add: 'context atWs ifFalse: ['.
   212     codeGen codeIf: 'context atWs' then: nil else: [ 
   253     compiler indent.
   213         codeGen 
   254         compiler 
   214               codeEvaluateAndAssign:[ self visit:node whitespace ]
   255               codeAssignParsedValueOf:[ self visit:node whitespace ]
       
   256               to:#whatever.
   215               to:#whatever.
   257         compiler add: 'context setWs.'.
   216         codeGen code: 'context setWs.'.
   258     compiler dedent.
   217     ]
   259     compiler add: '].'.
       
   260 !
   218 !
   261 
   219 
   262 notCharSetPredicateBody: node
   220 notCharSetPredicateBody: node
   263     | classificationId  classification |
   221     | classificationId  classification |
   264     self error: 'deprecated.'.
   222     self error: 'deprecated.'.
   265     classification := node extendClassification: node predicate classification.
   223     classification := node extendClassification: node predicate classification.
   266     classificationId := (compiler idFor: classification defaultName: #classification).
   224     classificationId := (codeGen idFor: classification defaultName: #classification).
   267     compiler  addConstant: classification as: classificationId.
   225     codeGen  addConstant: classification as: classificationId.
   268     
   226     
   269     compiler addOnLine: '(', classificationId, ' at: context peek asInteger)'.
   227     codeGen addOnLine: '(', classificationId, ' at: context peek asInteger)'.
   270     compiler indent.
   228     codeGen indent.
   271     compiler add: ' ifTrue: [ self error: '' predicate not expected'' ]'.
   229     codeGen add: ' ifTrue: [ self error: '' predicate not expected'' ]'.
   272     compiler add: ' ifFalse: [ nil ].'.
   230     codeGen add: ' ifFalse: [ nil ].'.
   273     compiler dedent.
   231     codeGen dedent.
   274 !
   232 !
   275 
   233 
   276 notMessagePredicateBody: node
   234 notMessagePredicateBody: node
   277     self error: 'deprecated'.
   235     self error: 'deprecated'.
   278     compiler addOnLine: '(context peek ', node message, ')'.
   236     codeGen addOnLine: '(context peek ', node message, ')'.
   279     compiler indent.
   237     codeGen indent.
   280     compiler add: ' ifTrue: [ self error: '' predicate not expected'' ]'.
   238     codeGen add: ' ifTrue: [ self error: '' predicate not expected'' ]'.
   281     compiler add: ' ifFalse: [ nil ].'.
   239     codeGen add: ' ifFalse: [ nil ].'.
   282     compiler dedent.
   240     codeGen dedent.
   283 !
   241 !
   284 
   242 
   285 predicateBody: node
   243 predicateBody: node
   286     | tmpId |
   244     | tmpId |
   287     self error:'deprecated'.
   245     self error:'deprecated'.
   288     tmpId := (compiler idFor: node predicate prefixed: #predicate).
   246     tmpId := (codeGen idFor: node predicate prefixed: #predicate).
   289     compiler addConstant: node predicate as: tmpId.
   247     codeGen addConstant: node predicate as: tmpId.
   290 
   248 
   291     compiler addOnLine: '(context atEnd not and: [ ', tmpId , ' value: context uncheckedPeek])'.
   249     codeGen addOnLine: '(context atEnd not and: [ ', tmpId , ' value: context uncheckedPeek])'.
   292     compiler indent.
   250     codeGen indent.
   293     compiler add: 'ifFalse: [ self error: ''predicate not found'' ]'.
   251     codeGen add: 'ifFalse: [ self error: ''predicate not found'' ]'.
   294     compiler add: 'ifTrue: [ context next ].'.
   252     codeGen add: 'ifTrue: [ context next ].'.
   295     compiler dedent.	
   253     codeGen dedent.	
   296 !
   254 !
   297 
   255 
   298 retvalVar
   256 retvalVar
   299     ^ compiler currentReturnVariable
   257     ^ codeGen currentReturnVariable
   300 
   258 
   301     "Modified: / 15-06-2015 / 18:20:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   259     "Modified: / 15-06-2015 / 18:20:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   302 !
   260 !
   303 
   261 
   304 startMethodForNode:node
   262 startMethodForNode:node
   305     node isMarkedForInline ifTrue:[ 
   263     node isMarkedForInline ifTrue:[ 
   306         compiler startInline: (compiler idFor: node).
   264         codeGen startInline: (codeGen idFor: node).
   307         compiler codeComment: 'BEGIN inlined code of ' , node printString.
   265         codeGen codeComment: 'BEGIN inlined code of ' , node printString.
   308         compiler indent.
   266         codeGen indent.
   309     ] ifFalse:[ 
   267     ] ifFalse:[ 
   310         compiler startMethod: (compiler idFor: node).
   268         codeGen startMethod: (codeGen idFor: node).
   311         compiler codeComment: 'GENERATED by ' , node printString.
   269         codeGen codeComment: 'GENERATED by ' , node printString.
   312         compiler allocateReturnVariable.
   270         codeGen allocateReturnVariable.
   313     ].
   271     ].
   314 
   272 
   315     "Created: / 23-04-2015 / 15:51:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   273     "Created: / 23-04-2015 / 15:51:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   316     "Modified: / 23-04-2015 / 19:13:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   274     "Modified: / 23-04-2015 / 19:13:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   317     "Modified (format): / 15-06-2015 / 18:03:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   275     "Modified (format): / 15-06-2015 / 18:03:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   318 !
   276 !
   319 
   277 
   320 stopMethodForNode:aPPCNode
   278 stopMethodForNode:aPPCNode
   321     ^ aPPCNode isMarkedForInline ifTrue:[ 
   279     ^ codeGen currentMethod isInline ifTrue:[ 
   322 		compiler dedent.
   280                 codeGen dedent.
   323 		compiler add: '"END inlined code of ' , aPPCNode printString , '"'.
   281                 codeGen code: '"END inlined code of ' , aPPCNode printString , '"'.
   324 		compiler stopInline.
   282                 codeGen stopInline.
   325     ] ifFalse:[ 
   283     ] ifFalse:[ 
   326 		compiler stopMethod
   284                 codeGen stopMethod
   327     ].
   285     ].
   328 
   286 
   329     "Created: / 23-04-2015 / 15:51:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   287     "Created: / 23-04-2015 / 15:51:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   330     "Modified: / 23-04-2015 / 18:35:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   288     "Modified: / 23-04-2015 / 18:35:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   331 ! !
   289 ! !
   335 cache: node value: retval
   293 cache: node value: retval
   336     "this is compiler thing, not mine"
   294     "this is compiler thing, not mine"
   337 !
   295 !
   338 
   296 
   339 cachedDetected: node
   297 cachedDetected: node
   340     ^ compiler checkCache: (compiler idFor: node)
   298     ^ codeGen clazz cachedMethod: (codeGen idFor: node)
   341 !
   299 !
   342 
   300 
   343 isCached: node
   301 isCached: node
   344     ^ (compiler checkCache: (compiler idFor: node)) isNil not
   302     ^ (codeGen cachedMethod: (codeGen idFor: node)) isNil not
   345 ! !
   303 ! !
   346 
   304 
   347 !PPCCodeGenerator methodsFor:'visiting'!
   305 !PPCCodeGenerator methodsFor:'visiting'!
   348 
   306 
   349 visitActionNode: node
   307 visitActionNode: node
   421 
   379 
   422     "Block return value is return value of last statement.
   380     "Block return value is return value of last statement.
   423      So if the method is not inline, make last statement a return.
   381      So if the method is not inline, make last statement a return.
   424         if the method is inline, make it assignment to retvalVar."
   382         if the method is inline, make it assignment to retvalVar."
   425     blockBody statements notEmpty ifTrue:["Care for empty blocks - [:t | ] !!"
   383     blockBody statements notEmpty ifTrue:["Care for empty blocks - [:t | ] !!"
   426         compiler currentMethod isInline ifTrue:[ 
   384         codeGen currentMethod isInline ifTrue:[ 
   427             |  assignment |
   385             |  assignment |
   428 
   386 
   429             assignment := RBAssignmentNode variable: (RBVariableNode named: self retvalVar) value:  blockBody statements last.
   387             assignment := RBAssignmentNode variable: (RBVariableNode named: self retvalVar) value:  blockBody statements last.
   430             blockBody replaceNode: blockBody statements last withNode: assignment.
   388             blockBody replaceNode: blockBody statements last withNode: assignment.
   431         ] ifFalse:[  
   389         ] ifFalse:[  
   434             return := RBReturnNode value: blockBody statements last.
   392             return := RBReturnNode value: blockBody statements last.
   435             blockBody replaceNode: blockBody statements last withNode: return.
   393             blockBody replaceNode: blockBody statements last withNode: return.
   436         ].
   394         ].
   437     ].
   395     ].
   438 
   396 
   439     compiler codeAssignParsedValueOf:[ self visit:node child ] to:self retvalVar.
   397     codeGen codeEvaluateAndAssign:[ self visit:node child ] to:self retvalVar.
   440     compiler codeIfErrorThen: [ 
   398     codeGen codeIfErrorThen: [ 
   441         compiler codeReturn: 'failure'. 
   399         codeGen codeReturn: 'failure'. 
   442     ] else: [
   400     ] else: [
   443         compiler code: blockBody.    
   401         codeGen code: blockBody.    
   444     ]
   402     ]
   445 
   403 
   446     "Modified: / 27-07-2015 / 15:49:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   404     "Modified: / 27-07-2015 / 15:49:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   447 !
   405 !
   448 
   406 
   449 visitAndNode: node
   407 visitAndNode: node
   450     | mementoVar |
   408     | mementoVar |
   451     
   409     
   452     mementoVar := compiler allocateTemporaryVariableNamed: 'memento'.
   410     mementoVar := codeGen allocateTemporaryVariableNamed: 'memento'.
   453     compiler smartRemember: node child to: mementoVar.
   411     codeGen remember: node child to: mementoVar.
   454 
   412 
   455     compiler 
   413     codeGen 
   456           codeAssignParsedValueOf:[ self visit:node child ]
   414           codeEvaluateAndAssign:[ self visit:node child ]
   457           to:self retvalVar.
   415           to:self retvalVar.
   458     compiler smartRestore: node child from: mementoVar.
   416     codeGen restore: node child from: mementoVar.
   459 
   417 
   460     compiler codeReturn.
   418     codeGen codeReturn.
   461 
   419 
   462     "Modified: / 23-04-2015 / 15:59:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   420     "Modified: / 23-04-2015 / 15:59:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   463 !
   421 !
   464 
   422 
   465 visitAnyNode: node
   423 visitAnyNode: node
   466 
   424 
   467     compiler codeReturn: 'context next ifNil: [ error := true. ].'.
   425     codeGen codeReturn: 'context next ifNil: [ error := true. ].'.
   468 
   426 
   469     "Modified: / 23-04-2015 / 20:52:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   427     "Modified: / 23-04-2015 / 20:52:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   470 !
   428 !
   471 
   429 
   472 visitCharSetPredicateNode: node
   430 visitCharSetPredicateNode: node
   473 
   431 
   474     | classification classificationId |
   432     | classification classificationId |
   475     classification := node extendClassification: node predicate classification.
   433     classification := node extendClassification: node predicate classification.
   476     classificationId := compiler idFor: classification defaultName: #classification.
   434     classificationId := codeGen idFor: classification defaultName: #classification.
   477     compiler addConstant: classification as: classificationId.
   435     codeGen addConstant: classification as: classificationId.
   478     
   436     
   479     compiler add: '(', classificationId, ' at: context peek asInteger)'.
   437     codeGen codeIf: '(', classificationId, ' at: context peek asInteger)' then: [ 
   480     compiler indent.
   438         codeGen codeReturn: 'context next'.
   481     compiler add: 'ifFalse: ['.
   439     ] else: [ 
   482     compiler codeError: 'predicate not found'.
   440         codeGen codeError: 'predicate not found'.
   483     compiler add: '] ifTrue: [ '.
   441     ]
   484     compiler codeReturn: 'context next'.
       
   485     compiler add: '].'.
       
   486     compiler dedent.
       
   487 !
   442 !
   488 
   443 
   489 visitCharacterNode: node
   444 visitCharacterNode: node
   490     | chid |
   445     | chid |
   491     node character ppcPrintable ifTrue: [ 
   446     node character ppcPrintable ifTrue: [ 
   492         chid := node character storeString 
   447         chid := node character storeString 
   493     ] ifFalse: [ 
   448     ] ifFalse: [ 
   494         chid := compiler idFor: node character defaultName: #char.
   449         chid := codeGen idFor: node character defaultName: #char.
   495         compiler addConstant: (Character value: node character asInteger) as: chid .
   450         codeGen addConstant: (Character value: node character asInteger) as: chid .
   496     ].
   451     ].
   497     
   452     
   498     compiler add: '(context peek == ', chid, ')'.
   453     codeGen codeIf: '(context peek == ', chid, ')' then: [  
   499     compiler indent.
   454         codeGen codeReturn: 'context next'.
   500     compiler add: 'ifFalse: ['.
   455     ] else: [ 
   501     compiler indent.
   456         codeGen codeError: node character asInteger asString, ' expected'.
   502     compiler codeError: node character asInteger asString, ' expected'.
   457     ].
   503     compiler dedent.
       
   504     compiler add: '] ifTrue: [ '.
       
   505     compiler indent.
       
   506     compiler codeReturn: 'context next'.
       
   507     compiler dedent.
       
   508     compiler add: '].'.
       
   509     compiler dedent.
       
   510 !
   458 !
   511 
   459 
   512 visitChild: child of: node
   460 visitChild: child of: node
   513     |  |
   461     |  |
   514 
   462 
   521 !
   469 !
   522 
   470 
   523 visitChoiceNode: node
   471 visitChoiceNode: node
   524     |  whitespaceConsumed useGuards resultVar  |
   472     |  whitespaceConsumed useGuards resultVar  |
   525 
   473 
   526     resultVar := compiler allocateTemporaryVariableNamed: 'element'.
   474     resultVar := codeGen allocateTemporaryVariableNamed: 'element'.
   527     whitespaceConsumed := self addGuardTrimming: node.
   475     whitespaceConsumed := self addGuardTrimming: node.
   528     useGuards := whitespaceConsumed.
   476     useGuards := whitespaceConsumed.
   529     self generateChoiceChildOf: node atIndex: 1 useGuards: useGuards storeResultInto: resultVar
   477     self generateChoiceChildOf: node atIndex: 1 useGuards: useGuards storeResultInto: resultVar
   530     
   478     
   531 
   479 
   532     "Modified: / 29-05-2015 / 07:17:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   480     "Modified: / 29-05-2015 / 07:17:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   533 !
   481 !
   534 
   482 
   535 visitEndOfFileNode: node
   483 visitEndOfFileNode: node
   536     compiler codeReturn: 'context atEnd ifTrue: [ #EOF ] ifFalse: [ self error: ''EOF expected!!'' ].'.
   484     codeGen codeReturn: 'context atEnd ifTrue: [ #EOF ] ifFalse: [ self error: ''EOF expected!!'' ].'.
   537 !
   485 !
   538 
   486 
   539 visitEndOfInputNode: node
   487 visitEndOfInputNode: node
   540 
   488 
   541     compiler 
   489     codeGen 
   542           codeAssignParsedValueOf:[ self visit:node child ]
   490           codeEvaluateAndAssign:[ self visit:node child ]
   543           to:self retvalVar.
   491           to:self retvalVar.
   544     compiler codeIf: 'context atEnd' 
   492     codeGen codeIf: 'context atEnd' 
   545                 then: [ compiler codeReturn ]
   493                 then: [ codeGen codeReturn ]
   546                 else: [ compiler codeError: 'End of input expected' ].
   494                 else: [ codeGen codeError: 'End of input expected' ].
   547         
   495         
   548     "Modified: / 26-05-2015 / 19:03:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   496     "Modified: / 26-05-2015 / 19:03:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   549 !
   497 !
   550 
   498 
   551 visitForwardNode: node
   499 visitForwardNode: node
   552 
   500 
   553     compiler 
   501     codeGen 
   554           codeAssignParsedValueOf:[ self visit:node child ]
   502           codeEvaluateAndAssign:[ self visit:node child ]
   555           to:self retvalVar.
   503           to:self retvalVar.
   556     compiler codeReturn.
   504     codeGen codeReturn.
   557 !
   505 !
   558 
   506 
   559 visitLiteralNode: node
   507 visitLiteralNode: node
   560     | positionVar encodedLiteral |
   508     | positionVar encodedLiteral |
   561     encodedLiteral := node encodeQuotes: node literal.
   509     encodedLiteral := node encodeQuotes: node literal.
   562     positionVar := compiler allocateTemporaryVariableNamed: 'position'.
   510     positionVar := codeGen allocateTemporaryVariableNamed: 'position'.
   563 
   511 
   564     compiler codeAssign: 'context position.' to: positionVar.
   512     codeGen codeAssign: 'context position.' to: positionVar.
   565     compiler add: '((context next: ', node literal size asString, ') = #''', encodedLiteral, ''') ifTrue: ['.
   513     codeGen codeIf: '((context next: ', node literal size asString, ') = #''', encodedLiteral, ''')' then: [
   566     compiler codeReturn: '#''', encodedLiteral, ''' '.
   514         codeGen codeReturn: '#''', encodedLiteral, ''' '.
   567     compiler add: '] ifFalse: ['.
   515     ] else: [  
   568     compiler indent.
   516         codeGen code: 'context position: ', positionVar, '.'.
   569         compiler add: 'context position: ', positionVar, '.'.
   517         codeGen codeError: encodedLiteral,  ' expected' at: positionVar.
   570         compiler codeError: encodedLiteral,  ' expected' at: positionVar.
   518     ].
   571     compiler dedent.
       
   572     compiler add: '].'.
       
   573 !
   519 !
   574 
   520 
   575 visitMappedActionNode: node
   521 visitMappedActionNode: node
   576     | child blockNode blockBody |
   522     | child blockNode blockBody |
   577 
   523 
   581     blockBody := blockNode body.
   527     blockBody := blockNode body.
   582 
   528 
   583     "Block return value is return value of last statement.
   529     "Block return value is return value of last statement.
   584      So if the method is not inline, make last statement a return.
   530      So if the method is not inline, make last statement a return.
   585         if the method is inline, make it assignment to retvalVar."
   531         if the method is inline, make it assignment to retvalVar."
   586     compiler currentMethod isInline ifTrue:[ 
   532     codeGen currentMethod isInline ifTrue:[ 
   587         |  assignment |
   533         |  assignment |
   588 
   534 
   589         assignment := RBAssignmentNode variable: (RBVariableNode named: self retvalVar) value:  blockBody statements last.
   535         assignment := RBAssignmentNode variable: (RBVariableNode named: self retvalVar) value:  blockBody statements last.
   590         blockBody replaceNode: blockBody statements last withNode: assignment.
   536         blockBody replaceNode: blockBody statements last withNode: assignment.
   591     ] ifFalse:[  
   537     ] ifFalse:[  
   614                 variableNode name: self retvalVar.
   560                 variableNode name: self retvalVar.
   615             ].
   561             ].
   616         ]. 
   562         ]. 
   617     ].
   563     ].
   618 
   564 
   619     compiler codeAssignParsedValueOf: [ self visit: child ] to: self retvalVar.
   565     codeGen codeEvaluateAndAssign: [ self visit: child ] to: self retvalVar.
   620     compiler codeIf: 'error' then: [ 
   566     codeGen codeIf: 'error' then: [ 
   621         compiler codeReturn: 'failure'. 
   567         codeGen codeReturn: 'failure'. 
   622     ] else: [
   568     ] else: [
   623         "If the child is sequence and not inlined, extract
   569         "If the child is sequence and not inlined, extract
   624          nodes from returned collection into used-to-be block variables"
   570          nodes from returned collection into used-to-be block variables"
   625         (child isSequenceNode and:[ child returnParsedObjectsAsCollection ]) ifTrue:[
   571         (child isSequenceNode and:[ child returnParsedObjectsAsCollection ]) ifTrue:[
   626             blockNode arguments withIndexDo:[ :arg :idx |
   572             blockNode arguments withIndexDo:[ :arg :idx |
   627                 node child isMarkedForInline ifFalse:[ 
   573                 node child isMarkedForInline ifFalse:[ 
   628                     compiler allocateTemporaryVariableNamed: arg name.
   574                     codeGen allocateTemporaryVariableNamed: arg name.
   629                     compiler codeAssign: (self retvalVar , ' at: ', idx printString) to: arg name.
   575                     codeGen codeAssign: (self retvalVar , ' at: ', idx printString) to: arg name.
   630                 ].
   576                 ].
   631                 compiler addOnLine: '.'; nl.
   577                 codeGen codeOnLine: '.'; codeNl.
   632             ].
   578             ].
   633         ].
   579         ].
   634         compiler code: blockBody.    
   580         codeGen code: blockBody.    
   635     ]
   581     ]
   636 
   582 
   637     "Created: / 02-06-2015 / 17:28:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   583     "Created: / 02-06-2015 / 17:28:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   638     "Modified: / 27-07-2015 / 15:49:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   584     "Modified: / 27-07-2015 / 15:49:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   639 !
   585 !
   640 
   586 
   641 visitMessagePredicateNode: node
   587 visitMessagePredicateNode: node
   642     compiler add: '(context peek ', node message, ') ifFalse: ['.
   588     codeGen codeIf: '(context peek ', node message, ')' then: [
   643     compiler codeError: 'predicate not found'.
   589         codeGen codeReturn: ' context next'.
   644     compiler add: '] ifTrue: [ '.
   590     ] else: [ 
   645     compiler codeReturn: ' context next'.
   591         codeGen codeError: 'predicate not found'.
   646     compiler add: '].'.
   592     ]
   647 
       
   648     "Modified: / 23-04-2015 / 18:39:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   593     "Modified: / 23-04-2015 / 18:39:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   649 !
   594 !
   650 
   595 
   651 visitNilNode: node
   596 visitNilNode: node
   652 
   597 
   653     compiler codeReturn: 'nil.'.
   598     codeGen codeReturn: 'nil.'.
   654 !
   599 !
   655 
   600 
   656 visitNotCharSetPredicateNode: node
   601 visitNotCharSetPredicateNode: node
   657     | classificationId  classification |
   602     | classificationId  classification |
   658     classification := node extendClassification: node predicate classification.
   603     classification := node extendClassification: node predicate classification.
   659     classificationId := (compiler idFor: classification defaultName: #classification).
   604     classificationId := (codeGen idFor: classification defaultName: #classification).
   660     compiler  addConstant: classification as: classificationId.
   605     codeGen  addConstant: classification as: classificationId.
   661     
   606     
   662     compiler addOnLine: '(', classificationId, ' at: context peek asInteger)'.
   607     codeGen codeIf: '(', classificationId, ' at: context peek asInteger)'  then: [ 
   663     compiler indent.
   608         codeGen codeError: 'predicate not expected'.
   664     compiler add: ' ifTrue: ['.
   609     ] else: [ 
   665     compiler codeError: 'predicate not expected'.
   610         codeGen codeReturn: 'nil'.
   666     compiler add: '] ifFalse: ['.
   611     ]
   667     compiler codeReturn: 'nil'.
       
   668     compiler add: '].'.
       
   669     compiler dedent.
       
   670 !
   612 !
   671 
   613 
   672 visitNotCharacterNode: node
   614 visitNotCharacterNode: node
   673     | chid |
   615     | chid |
   674     node character ppcPrintable ifTrue: [ 
   616     node character ppcPrintable ifTrue: [ 
   675         chid := node character storeString 
   617         chid := node character storeString 
   676     ] ifFalse: [ 
   618     ] ifFalse: [ 
   677         chid := compiler idFor: node character defaultName: #char.
   619         chid := codeGen idFor: node character defaultName: #char.
   678         compiler addConstant: (Character value: node character asInteger) as: chid .
   620         codeGen addConstant: (Character value: node character asInteger) as: chid .
   679     ].
   621     ].
   680     
   622     
   681     compiler add: '(context peek == ', chid, ')'.
   623     codeGen codeIf: '(context peek == ', chid, ')' then: [ 
   682     compiler indent.
   624         codeGen codeError: node character asInteger asString, ' not expected'.
   683     compiler add: 'ifTrue: ['.
   625     ] else: [ 
   684     compiler indent.
   626         codeGen codeReturn: 'nil.'.
   685     compiler codeError: node character asInteger asString, ' not expected'.
   627     ].
   686     compiler dedent.
       
   687     compiler add: '] ifFalse: [ '.
       
   688     compiler indent.
       
   689     compiler codeReturn: 'nil.'.
       
   690     compiler dedent.
       
   691     compiler add: '].'.
       
   692     compiler dedent.
       
   693 !
   628 !
   694 
   629 
   695 visitNotLiteralNode: node
   630 visitNotLiteralNode: node
   696     | encodedLiteral size |
   631     | encodedLiteral size |
   697     encodedLiteral := node encodeQuotes: node literal.
   632     encodedLiteral := node encodeQuotes: node literal.
   698     size := node literal size asString.
   633     size := node literal size asString.
   699     
   634     
   700     compiler add: '((context peek: ', size, ') =#''', encodedLiteral, ''')'.
   635     codeGen codeIf: '((context peek: ', size, ') =#''', encodedLiteral, ''')' then: [ 
   701     compiler indent.
   636         codeGen codeError: encodedLiteral, ' not expected'.
   702     compiler add: 'ifTrue: ['.
   637     ] else: [ 
   703     compiler codeError: encodedLiteral, ' not expected'.
   638         codeGen codeReturn: 'nil' .
   704     compiler add: '] ifFalse: [ '.
   639     ]
   705     compiler codeReturn: 'nil' .
       
   706     compiler add: '].'.
       
   707     compiler dedent.
       
   708 !
   640 !
   709 
   641 
   710 visitNotMessagePredicateNode: node
   642 visitNotMessagePredicateNode: node
   711     compiler addOnLine: '(context peek ', node message, ')'.
   643     codeGen codeIf: '(context peek ', node message, ')' then: [ 
   712     compiler indent.
   644         codeGen codeError: 'predicate not expected'.
   713     compiler add: ' ifTrue: [ '.
   645     ] else: [ 
   714     compiler codeError: 'predicate not expected'.
   646         codeGen codeReturn: 'nil'.
   715     compiler add: '] ifFalse: ['.
   647     ]
   716     compiler codeReturn: 'nil'.
       
   717     compiler add: ' ].'.
       
   718     compiler dedent. 
       
   719 !
   648 !
   720 
   649 
   721 visitNotNode: node
   650 visitNotNode: node
   722     | mementoVar |
   651     | mementoVar |
   723 
   652 
   724     mementoVar := compiler allocateTemporaryVariableNamed: 'memento'.
   653     mementoVar := codeGen allocateTemporaryVariableNamed: 'memento'.
   725     compiler smartRemember: node child to: mementoVar.
   654     codeGen remember: node child to: mementoVar.
   726     
   655     
   727     compiler codeAssignParsedValueOf:[ self visit:node child ] to:#whatever.
   656     codeGen codeEvaluateAndAssign:[ self visit:node child ] to:#whatever.
   728     compiler smartRestore: node child from: mementoVar.
   657     codeGen restore: node child from: mementoVar.
   729 
   658 
   730     compiler add: '^ error ifFalse: [ self error ] ifTrue: [ self clearError. nil ]'.
   659     codeGen code: '^ error ifFalse: [ self error ] ifTrue: [ self clearError. nil ]'.
   731 
   660 
   732     "Modified: / 05-05-2015 / 14:29:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   661     "Modified: / 05-05-2015 / 14:29:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   733 !
   662 !
   734 
   663 
   735 visitOptionalNode: node
   664 visitOptionalNode: node
   736     compiler 
   665     codeGen 
   737           codeAssignParsedValueOf:[ self visit:node child ]
   666           codeEvaluateAndAssign:[ self visit:node child ]
   738           to:self retvalVar.
   667           to:self retvalVar.
   739     compiler add: 'error ifTrue: [ '.
   668     codeGen codeIf: 'error' then: [ 
   740     compiler indent.
   669         codeGen codeClearError.
   741     compiler add: 'self clearError. '.
   670         codeGen codeAssign: 'nil.' to: self retvalVar.
   742     compiler codeAssign: 'nil.' to: self retvalVar.
   671     ].
   743     compiler dedent.
   672     codeGen codeReturn.
   744     compiler add: '].'.
       
   745     compiler codeReturn.
       
   746 !
   673 !
   747 
   674 
   748 visitPluggableNode: node
   675 visitPluggableNode: node
   749     | blockId |
   676     | blockId |
   750     blockId := compiler idFor: node block defaultName: #pluggableBlock.
   677     blockId := codeGen idFor: node block defaultName: #pluggableBlock.
   751     
   678     
   752     compiler addConstant: node block as: blockId.
   679     codeGen addConstant: node block as: blockId.
   753     compiler codeReturn: blockId, ' value: context.'.
   680     codeGen codeReturn: blockId, ' value: context.'.
   754 !
   681 !
   755 
   682 
   756 visitPlusNode: node
   683 visitPlusNode: node
   757     | elementVar  |
   684     | elementVar  |
   758                 
   685                 
   759     elementVar := compiler allocateTemporaryVariableNamed:  'element'.
   686     elementVar := codeGen allocateTemporaryVariableNamed:  'element'.
   760      
   687      
   761 "       self tokenGuards ifTrue: [ 
   688 "       self tokenGuards ifTrue: [ 
   762         compiler codeTokenGuard: node ifFalse: [ compiler codeError: 'at least one occurence expected' ].   
   689         compiler codeTokenGuard: node ifFalse: [ compiler codeError: 'at least one occurence expected' ].   
   763     ].
   690     ].
   764 "        
   691 "        
   765     compiler codeAssign: 'OrderedCollection new.' to: self retvalVar.
   692     codeGen codeAssign: 'OrderedCollection new.' to: self retvalVar.
   766     compiler codeAssignParsedValueOf:[ self visit:node child ] to:elementVar.
   693     codeGen codeEvaluateAndAssign:[ self visit:node child ] to:elementVar.
   767 
   694 
   768     compiler add: 'error ifTrue: ['.
   695     codeGen codeIf: 'error' then: [
   769     compiler codeError: 'at least one occurence expected'.
   696         codeGen codeError: 'at least one occurence expected'.
   770     compiler add: '] ifFalse: ['.
   697     ] else: [ 
   771     compiler indent.
       
   772         (self retvalVar ~~ #whatever) ifTrue:[
   698         (self retvalVar ~~ #whatever) ifTrue:[
   773             compiler add: self retvalVar , ' add: ',elementVar , '.'.
   699             codeGen code: self retvalVar , ' add: ',elementVar , '.'.
   774         ].            
   700         ].            
   775         compiler codeAssignParsedValueOf:[ self visit:node child ] to:elementVar.
   701         codeGen codeEvaluateAndAssignParsedValueOf:[ self visit:node child ] to:elementVar.
   776         compiler add: '[ error ] whileFalse: ['.
   702         codeGen code: '[ error ] whileFalse: ['.
   777         compiler indent.
   703         codeGen indent.
   778         (self retvalVar ~~ #whatever) ifTrue:[
   704         (self retvalVar ~~ #whatever) ifTrue:[
   779             compiler add: self retvalVar , ' add: ',elementVar , '.'.
   705             codeGen code: self retvalVar , ' add: ',elementVar , '.'.
   780         ].
   706         ].
   781         compiler codeAssignParsedValueOf:[ self visit:node child ] to:elementVar.
   707         codeGen codeEvaluateAndAssign:[ self visit:node child ] to:elementVar.
   782         compiler dedent.
   708         codeGen dedent.
   783         compiler add: '].'.
   709         codeGen code: '].'.
   784         compiler add: 'self clearError.'.
   710         codeGen code: 'self clearError.'.
       
   711 
   785         (self retvalVar ~~ #whatever) ifTrue:[ 
   712         (self retvalVar ~~ #whatever) ifTrue:[ 
   786             compiler codeReturn: self retvalVar , ' asArray.'.         
   713             codeGen codeReturn: self retvalVar , ' asArray.'.         
   787         ].
   714         ].
   788     compiler dedent.
   715     ].
   789     compiler add: '].'.
       
   790 
       
   791     "Modified: / 26-05-2015 / 19:04:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   716     "Modified: / 26-05-2015 / 19:04:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   792 !
   717 !
   793 
   718 
   794 visitPredicateNode: node
   719 visitPredicateNode: node
   795     | pid |
   720     | pid |
   796     pid := (compiler idFor: node predicate defaultName: #predicate).
   721     pid := (codeGen idFor: node predicate defaultName: #predicate).
   797 
   722 
   798     compiler addConstant: node predicate as: pid.
   723     codeGen addConstant: node predicate as: pid.
   799 
   724 
   800     compiler add: '(context atEnd not and: [ ', pid , ' value: context uncheckedPeek])'.
   725     codeGen codeIf: '(context atEnd not and: [ ', pid , ' value: context uncheckedPeek])' then: [ 
   801     compiler indent.
   726         codeGen code: self retvalVar ,' := context next.'.
   802     compiler add: 'ifFalse: ['.
   727     ] else: [ 
   803     compiler codeError: 'predicate not found'.
   728         codeGen codeError: 'predicate not found'.
   804     compiler add: '] ifTrue: [ ', self retvalVar ,' := context next ].'.
   729     ].
   805     compiler dedent.   
   730     codeGen codeReturn.
   806     compiler codeReturn.
       
   807 
   731 
   808     "Modified: / 23-04-2015 / 21:48:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   732     "Modified: / 23-04-2015 / 21:48:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   809 !
   733 !
   810 
   734 
   811 visitRecognizingSequenceNode: node
   735 visitRecognizingSequenceNode: node
   812     | mementoVar canBacktrack |
   736     | mementoVar canBacktrack |
   813 
   737 
   814     canBacktrack := (node children allButFirst allSatisfy: [:e | e acceptsEpsilon ]) not.
   738     canBacktrack := (node children allButFirst allSatisfy: [:e | e acceptsEpsilon ]) not.
   815 
   739 
   816     canBacktrack ifTrue: [ 
   740     canBacktrack ifTrue: [ 
   817         mementoVar := compiler allocateTemporaryVariableNamed: 'memento'.			
   741         mementoVar := codeGen allocateTemporaryVariableNamed: 'memento'.			
   818         compiler smartRemember: node to: mementoVar.
   742         codeGen remember: node to: mementoVar.
   819     ].
   743     ].
   820 
   744 
   821     compiler 
   745     codeGen 
   822           codeAssignParsedValueOf:[ self visit:(node children at:1) ]
   746           codeEvaluateAndAssign:[ self visit:(node children at:1) ]
   823           to:#whatever.
   747           to:#whatever.
   824     compiler add: 'error ifTrue: [ ^ failure ].'.
   748     codeGen code: 'error ifTrue: [ ^ failure ].'.
   825 
   749 
   826     2 to: (node children size) do: [ :idx  | |child|
   750     2 to: (node children size) do: [ :idx  | |child|
   827         child := node children at: idx.
   751         child := node children at: idx.
   828         compiler codeAssignParsedValueOf:[ self visit:child ] to:#whatever.
   752         codeGen codeEvaluateAndAssignParsedValueOf:[ self visit:child ] to:#whatever.
   829         
   753         
   830         child acceptsEpsilon ifFalse: [   
   754         child acceptsEpsilon ifFalse: [   
   831             compiler add: 'error ifTrue: [ '.
   755             codeGen codeIf: 'error' then: [ 
   832             compiler indent.
   756                 codeGen restore: node from: mementoVar.
   833             compiler smartRestore: node from: mementoVar.
   757                 codeGen code: ' ^ failure .'.
   834             compiler add: ' ^ failure .'.
   758             ]
   835             compiler dedent.
       
   836             compiler add: '].'.
       
   837         ].
   759         ].
   838     ].
   760     ].
   839 !
   761 !
   840 
   762 
   841 visitSequenceNode: node
   763 visitSequenceNode: node
   842 
   764 
   843     | elementVars mementoVar canBacktrack  |
   765     | elementVars mementoVar canBacktrack  |
   844 
   766 
   845     elementVars := node preferredChildrenVariableNames.
   767     elementVars := node preferredChildrenVariableNames.
   846     elementVars do:[:e | 
   768     elementVars do:[:e | 
   847         compiler allocateTemporaryVariableNamed: e.  
   769         codeGen allocateTemporaryVariableNamed: e.  
   848     ].
   770     ].
   849 
   771 
   850     canBacktrack := (node children allButFirst allSatisfy: [:e | e acceptsEpsilon ]) not.
   772     canBacktrack := (node children allButFirst allSatisfy: [:e | e acceptsEpsilon ]) not.
   851 
   773 
   852 "       self addGuardTrimming: node.
   774 "       self addGuardTrimming: node.
   853     self addGuard: node ifTrue: nil ifFalse: [ compiler addOnLine: ' ^ self error' ].
   775     self addGuard: node ifTrue: nil ifFalse: [ compiler addOnLine: ' ^ self error' ].
   854 "
   776 "
   855     canBacktrack ifTrue: [ 
   777     canBacktrack ifTrue: [ 
   856         mementoVar := compiler allocateTemporaryVariableNamed: 'memento'.
   778         mementoVar := codeGen allocateTemporaryVariableNamed: 'memento'.
   857         compiler smartRemember: node to: mementoVar.
   779         codeGen remember: node to: mementoVar.
   858     ].
   780     ].
   859 
   781 
   860     node returnParsedObjectsAsCollection ifTrue:[
   782     node returnParsedObjectsAsCollection ifTrue:[
   861         compiler codeAssign: 'Array new: ', node children size asString, '.' to: self retvalVar.
   783         codeGen codeAssign: 'Array new: ', node children size asString, '.' to: self retvalVar.
   862     ].
   784     ].
   863     self generateSequenceChildOf: node atIndex: 1 useMememntoVar: mementoVar storeResultInto: elementVars.
   785     self generateSequenceChildOf: node atIndex: 1 useMememntoVar: mementoVar storeResultInto: elementVars.
   864     compiler codeReturn
   786     codeGen codeReturn
   865 
   787 
   866     "Modified (comment): / 16-06-2015 / 06:38:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   788     "Modified (comment): / 16-06-2015 / 06:38:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   867 !
   789 !
   868 
   790 
   869 visitStarAnyNode: node
   791 visitStarAnyNode: node
   870     | retvalVar sizeVar |
   792     | retvalVar sizeVar |
   871 
   793 
   872     retvalVar := self retvalVar.
   794     retvalVar := self retvalVar.
   873     sizeVar := compiler allocateTemporaryVariableNamed: 'size'.  
   795     sizeVar := codeGen allocateTemporaryVariableNamed: 'size'.  
   874     compiler add: sizeVar , ' := context size - context position.'.
   796     codeGen code: sizeVar , ' := context size - context position.'.
   875     compiler add: retvalVar,' := Array new: ',sizeVar,'.'.
   797     codeGen code: retvalVar,' := Array new: ',sizeVar,'.'.
   876     compiler add: '(1 to: ',sizeVar,') do: [ :e | ',retvalVar,' at: e put: context next ].'.
   798     codeGen code: '(1 to: ',sizeVar,') do: [ :e | ',retvalVar,' at: e put: context next ].'.
   877     compiler codeReturn.
   799     codeGen codeReturn.
   878 
   800 
   879     "Modified: / 15-06-2015 / 18:53:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   801     "Modified: / 15-06-2015 / 18:53:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   880 !
   802 !
   881 
   803 
   882 visitStarCharSetPredicateNode: node
   804 visitStarCharSetPredicateNode: node
   883     | classification classificationId |
   805     | classification classificationId |
   884     
   806     
   885 
   807 
   886     classification := node extendClassification: node predicate classification.
   808     classification := node extendClassification: node predicate classification.
   887     classificationId := compiler idFor: classification defaultName: #classification.
   809     classificationId := codeGen idFor: classification defaultName: #classification.
   888     compiler addConstant: classification as: classificationId.
   810     codeGen addConstant: classification as: classificationId.
   889     
   811     
   890     compiler codeAssign: 'OrderedCollection new.' to: self retvalVar.	
   812     codeGen codeAssign: 'OrderedCollection new.' to: self retvalVar.	
   891     compiler add: '[ ', classificationId, ' at: context peek asInteger ] whileTrue: ['.
   813     codeGen code: '[ ', classificationId, ' at: context peek asInteger ] whileTrue: ['.
   892     compiler indent.
   814     codeGen indent.
   893     compiler codeEvaluate: 'add:' argument: 'context next.' on: self retvalVar.
   815     codeGen codeEvaluate: 'add:' argument: 'context next.' on: self retvalVar.
   894     compiler dedent.
   816     codeGen dedent.
   895     compiler add: '].'.
   817     codeGen code: '].'.
   896     compiler codeAssign: self retvalVar, ' asArray.' to: self retvalVar.
   818     codeGen codeAssign: self retvalVar, ' asArray.' to: self retvalVar.
   897    compiler codeReturn.
   819    codeGen codeReturn.
   898 !
   820 !
   899 
   821 
   900 visitStarMessagePredicateNode: node
   822 visitStarMessagePredicateNode: node
   901 
   823 
   902     compiler codeAssign: 'OrderedCollection new.' to: self retvalVar.	
   824     codeGen codeAssign: 'OrderedCollection new.' to: self retvalVar.	
   903     compiler add: '[ context peek ', node message, ' ] whileTrue: ['.
   825     codeGen code: '[ context peek ', node message, ' ] whileTrue: ['.
   904     compiler indent.
   826     codeGen indent.
   905     compiler codeEvaluate: 'add:' argument: 'context next.' on: self retvalVar.
   827     codeGen codeEvaluate: 'add:' argument: 'context next.' on: self retvalVar.
   906     compiler dedent.
   828     codeGen dedent.
   907     compiler add: '].'.
   829     codeGen code: '].'.
   908     compiler codeAssign: self retvalVar, ' asArray.' to: self retvalVar.
   830     codeGen codeAssign: self retvalVar, ' asArray.' to: self retvalVar.
   909    compiler codeReturn.
   831    codeGen codeReturn.
   910 !
   832 !
   911 
   833 
   912 visitStarNode: node
   834 visitStarNode: node
   913     | elementVar |
   835     | elementVar |
   914     
   836     
   915     elementVar := compiler allocateTemporaryVariableNamed: 'element'.
   837     elementVar := codeGen allocateTemporaryVariableNamed: 'element'.
   916 
   838     codeGen codeAssign: 'OrderedCollection new.' to: self retvalVar.
   917     self addGuard: node child ifTrue: nil ifFalse: [ compiler codeReturn: '#()' ].
   839 
   918 
   840     codeGen codeEvaluateAndAssign:[ self visit:node child ] to:elementVar.
   919     compiler codeAssignParsedValueOf:[ self visit:node child ] to:elementVar.
   841     codeGen codeIf: 'error' then: [ 
   920     compiler codeIf: 'error' 
   842         codeGen codeClearError.
   921         then: [ 
   843         codeGen codeReturn: self retvalVar, ' asArray.'.
   922             compiler codeClearError.
   844     ].
   923             compiler codeReturn: '#()'.
   845 
   924         ] else: [
   846     codeGen code: '[ error ] whileFalse: ['.
   925             compiler codeAssign: 'OrderedCollection new.' to: self retvalVar.
   847     codeGen indent.
   926         ].
   848     codeGen code: self retvalVar, ' add: ', elementVar, '.'.
   927 
   849     codeGen codeEvaluateAndAssign:[ self visit:node child ] to:elementVar.
   928     compiler add: '[ error ] whileFalse: ['.
   850     codeGen dedent.
   929     compiler indent.
   851     codeGen code: '].'.
   930     compiler add: self retvalVar, ' add: ', elementVar, '.'.
   852     codeGen codeClearError.
   931     compiler codeAssignParsedValueOf:[ self visit:node child ] to:elementVar.
   853     codeGen codeReturn: self retvalVar, ' asArray.'.
   932     compiler dedent.
       
   933     compiler add: '].'.
       
   934     compiler codeClearError.
       
   935     compiler codeReturn: self retvalVar, ' asArray.'.
       
   936 !
   854 !
   937 
   855 
   938 visitSymbolActionNode: node
   856 visitSymbolActionNode: node
   939     | elementVar |
   857     | elementVar |
   940     
   858     
   941     elementVar := compiler allocateTemporaryVariableNamed: 'element'.	
   859     elementVar := codeGen allocateTemporaryVariableNamed: 'element'.	
   942     compiler codeAssignParsedValueOf:[ self visit:node child ] to:elementVar.
   860     codeGen codeEvaluateAndAssign:[ self visit:node child ] to:elementVar.
   943     compiler add: 'error ifFalse: [ '.
   861     codeGen codeIf: 'error' then: [ 
   944     compiler codeReturn: elementVar, ' ', node block asString, '.'.
   862         codeGen codeReturn: 'failure'
   945     compiler add: '] ifTrue: ['.
   863     ] else: [
   946     compiler codeReturn: 'failure'.
   864         codeGen codeReturn: elementVar, ' ', node block asString, '.'.
   947     compiler add: ']'.
   865     ]
   948 !
   866 !
   949 
   867 
   950 visitTokenActionNode: node
   868 visitTokenActionNode: node
   951     "
   869     "
   952         Actually, do nothing, we are in Token mode and the 
   870         Actually, do nothing, we are in Token mode and the 
   953         child does not return any result and token takes only
   871         child does not return any result and token takes only
   954         the input value.
   872         the input value.
   955     "	
   873     "	
   956 
   874 
   957     compiler add: '^ '.
   875     codeGen add: '^ '.
   958     compiler callOnLine: (node child compileWith: compiler).
   876     codeGen callOnLine: (node child compileWith: codeGen).
   959 !
   877 !
   960 
   878 
   961 visitTokenNode: node
   879 visitTokenNode: node
   962     | startVar endVar |
   880     | startVar endVar |
   963     startVar := compiler allocateTemporaryVariableNamed: 'start'.
   881     startVar := codeGen allocateTemporaryVariableNamed: 'start'.
   964     endVar := compiler allocateTemporaryVariableNamed: 'end'.
   882     endVar := codeGen allocateTemporaryVariableNamed: 'end'.
   965     
   883     
   966     compiler profileTokenRead: (compiler idFor: node).
   884     codeGen profileTokenRead: (codeGen idFor: node).
   967     
   885     
   968     compiler codeAssign: 'context position + 1.' to: startVar.
   886     codeGen codeAssign: 'context position + 1.' to: startVar.
   969     compiler codeAssignParsedValueOf:[ self visit:node child ] to:#whatever.
   887     codeGen codeEvaluateAndAssign:[ self visit:node child ] to:#whatever.
   970     compiler add: 'error ifFalse: [ '.
   888     codeGen codeIf: 'error' then: nil else: [
   971     compiler indent.	
   889         codeGen codeAssign: 'context position.' to: endVar.
   972     compiler codeAssign: 'context position.' to: endVar.
   890         codeGen codeReturn: node tokenClass asString, ' on: (context collection) 
   973     
   891                                                                     start: ', startVar, '  
   974     compiler codeReturn: node tokenClass asString, ' on: (context collection) 
   892                                                                     stop: ', endVar, '
   975                                                                 start: ', startVar, '  
   893                                                                     value: nil.'.
   976                                                                 stop: ', endVar, '
   894     ]
   977                                                                 value: nil.'.
       
   978     compiler dedent.
       
   979     compiler add: '].'.
       
   980 !
   895 !
   981 
   896 
   982 visitTokenStarMessagePredicateNode: node
   897 visitTokenStarMessagePredicateNode: node
   983 
   898 
   984     compiler add: '[ context peek ', node message,' ] whileTrue: ['.
   899     codeGen code: '[ context peek ', node message,' ] whileTrue: ['.
   985     compiler indent.
   900     codeGen indent.
   986     compiler add: 'context next'.
   901     codeGen code: 'context next'.
   987     compiler indent.
   902     codeGen indent.
   988     compiler dedent.
   903     codeGen dedent.
   989     compiler add: '].'.
   904     codeGen code: '].'.
   990 !
   905 !
   991 
   906 
   992 visitTokenStarSeparatorNode: node
   907 visitTokenStarSeparatorNode: node
   993 
   908 
   994     compiler add: 'context skipSeparators.'.
   909     codeGen code: 'context skipSeparators.'.
   995 !
   910 !
   996 
   911 
   997 visitTokenWhitespaceNode: node
   912 visitTokenWhitespaceNode: node
   998     compiler codeAssignParsedValueOf:[ self visit:node child ] to:#whatever.
   913     codeGen codeEvaluateAndAssign:[ self visit:node child ] to:#whatever.
   999     compiler codeReturn.
   914     codeGen codeReturn.
  1000 !
   915 !
  1001 
   916 
  1002 visitTrimNode: node
   917 visitTrimNode: node
  1003     | mementoVar |
   918     | mementoVar |
  1004     "TODO: This ignores the TrimmingParser trimmer object!!"
   919     "TODO: This ignores the TrimmingParser trimmer object!!"
  1005 
   920 
  1006     mementoVar := compiler allocateTemporaryVariableNamed:  'memento'.
   921     mementoVar := codeGen allocateTemporaryVariableNamed:  'memento'.
  1007 
   922 
  1008     compiler smartRemember: node child to: mementoVar.
   923     codeGen remember: node child to: mementoVar.
  1009     compiler add: 'context skipSeparators.'.
   924     codeGen code: 'context skipSeparators.'.
  1010 
   925 
  1011     compiler 
   926     codeGen 
  1012           codeAssignParsedValueOf:[ self visit:node child ]
   927           codeEvaluateAndAssign:[ self visit:node child ]
  1013           to:self retvalVar.
   928           to:self retvalVar.
  1014     
   929     
  1015     compiler add: 'error ifTrue: [ '.
   930     codeGen codeIf: 'error' then: [ 
  1016     compiler indent.
   931         codeGen restore: node child from: mementoVar.
  1017         compiler smartRestore: node child from: mementoVar.
   932         codeGen codeReturn.
  1018         compiler codeReturn.
   933     ] else: [ 
  1019     compiler dedent.
   934         codeGen code: 'context skipSeparators.'.
  1020     compiler add: '] ifFalse: ['	.
   935         codeGen codeReturn.
  1021         compiler indent.
   936     ]
  1022         compiler add: 'context skipSeparators.'.
       
  1023         compiler codeReturn.
       
  1024         compiler dedent.
       
  1025     compiler add: '].'.
       
  1026 !
   937 !
  1027 
   938 
  1028 visitTrimmingTokenCharacterNode: node
   939 visitTrimmingTokenCharacterNode: node
  1029     ^ self visitTrimmingTokenNode: node
   940     ^ self visitTrimmingTokenNode: node
  1030 !
   941 !
  1031 
   942 
  1032 visitTrimmingTokenNode: node
   943 visitTrimmingTokenNode: node
  1033     |  id guard startVar endVar |
   944     |  id guard startVar endVar |
  1034 
   945 
  1035     startVar := compiler allocateTemporaryVariableNamed: 'start'.
   946     startVar := codeGen allocateTemporaryVariableNamed: 'start'.
  1036     endVar := compiler allocateTemporaryVariableNamed:  'end'.
   947     endVar := codeGen allocateTemporaryVariableNamed:  'end'.
  1037     
   948     
  1038     id := compiler idFor: node.
   949     id := codeGen idFor: node.
  1039     compiler profileTokenRead: id.
   950     codeGen profileTokenRead: id.
  1040     
   951     
  1041     self compileTokenWhitespace: node.
   952     self compileTokenWhitespace: node.
  1042 
   953 
  1043     (arguments guards and: [(guard := PPCGuard on: node) makesSense]) ifTrue: [ 
   954     (arguments guards and: [(guard := PPCGuard on: node) makesSense]) ifTrue: [ 
  1044         guard id: id, '_guard'.
   955         guard id: id, '_guard'.
  1045         compiler add: 'context atEnd ifTrue: [ self error ].'.
   956         codeGen code: 'context atEnd ifTrue: [ self error ].'.
  1046         guard compileGuard: compiler.
   957         guard compileGuard: codeGen.
  1047         compiler addOnLine: 'ifFalse: [ self error ].'.
   958         codeGen codeOnLine: 'ifFalse: [ self error ].'.
  1048         compiler add: 'error ifFalse: ['.
   959         codeGen code: 'error ifFalse: ['.
  1049         compiler indent.
   960         codeGen indent.
  1050     ].
   961     ].
  1051 
   962 
  1052     compiler codeAssign: 'context position + 1.' to: startVar.
   963     codeGen codeAssign: 'context position + 1.' to: startVar.
  1053     compiler codeAssignParsedValueOf:[ self visit:node child ] to:#whatever.
   964     codeGen codeEvaluateAndAssign:[ self visit:node child ] to:#whatever.
  1054 
   965 
  1055     (arguments guards and: [(guard := PPCGuard on: node) makesSense]) ifTrue: [ 
   966     (arguments guards and: [(guard := PPCGuard on: node) makesSense]) ifTrue: [ 
  1056         compiler dedent.
   967         codeGen dedent.
  1057         compiler add: '].'.
   968         codeGen code: '].'.
  1058     ].
   969     ].
  1059 
   970 
  1060     compiler add: 'error ifFalse: [ '.
   971     codeGen codeIf: 'error' then: nil else: [
  1061     compiler indent.	
   972         codeGen codeAssign: 'context position.' to: endVar.
  1062     compiler codeAssign: 'context position.' to: endVar.
   973         "	self compileSecondWhitespace: compiler."
  1063     
   974         self compileTokenWhitespace: node.
  1064 "	self compileSecondWhitespace: compiler."
   975 
  1065     self compileTokenWhitespace: node.
   976         codeGen codeReturn: node tokenClass asString, ' on: (context collection) 
  1066 
   977                                                                     start: ', startVar, ' 
  1067     compiler codeReturn: node tokenClass asString, ' on: (context collection) 
   978                                                                     stop: ', endVar, '
  1068                                                                 start: ', startVar, ' 
   979                                                                     value: nil'.
  1069                                                                 stop: ', endVar, '
   980     ]
  1070                                                                 value: nil'.
       
  1071     compiler dedent.																
       
  1072     compiler add: '].'
       
  1073 !
   981 !
  1074 
   982 
  1075 visitUnknownNode: node
   983 visitUnknownNode: node
  1076     | compiledChild compiledParser id |
   984     | compiledChild compiledParser id |
  1077 
   985 
  1078     id := compiler idFor: node.
   986     id := codeGen idFor: node.
  1079     
   987     
  1080     compiledParser := node parser copy.
   988     compiledParser := node parser copy.
  1081     "Compile all the children and call compiled version of them instead of the original one"
   989     "Compile all the children and call compiled version of them instead of the original one"
  1082     compiledParser children do: [ :child | 
   990     compiledParser children do: [ :child | 
  1083         compiledChild := self visit: child.
   991         compiledChild := self visit: child.
  1084         compiledParser replace: child with: compiledChild bridge.
   992         compiledParser replace: child with: compiledChild bridge.
  1085     ].
   993     ].
  1086     
   994     
  1087     compiler addConstant: compiledParser as: id. 
   995     codeGen addConstant: compiledParser as: id. 
  1088     
   996     
  1089     compiler codeClearError.
   997     codeGen codeClearError.
  1090     compiler add: '(', self retvalVar, ' := ', id, ' parseOn: context) isPetitFailure'.
   998     codeGen codeIf: '(', self retvalVar, ' := ', id, ' parseOn: context) isPetitFailure' then: [ 
  1091     compiler indent.
   999         codeGen codeError: 'self error: ', self retvalVar at: self retvalVar, ' position .'.
  1092     compiler add: ' ifTrue: [self error: ', self retvalVar, ' message at: ', self retvalVar, ' position ].'.
  1000     ].
  1093     compiler dedent.
  1001     codeGen code: 'error := ', self retvalVar, ' isPetitFailure.'.
  1094     compiler add: 'error := ', self retvalVar, ' isPetitFailure.'.
  1002     codeGen codeReturn.
  1095     compiler codeReturn.
       
  1096 
  1003 
  1097     "Modified: / 15-06-2015 / 17:59:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1004     "Modified: / 15-06-2015 / 17:59:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
  1098 ! !
  1005 ! !
  1099 
  1006