compiler/PPCCompiler.st
changeset 525 751532c8f3db
parent 523 09afcf28ed60
parent 524 f6f68d32de73
child 526 cc0ce8edda63
equal deleted inserted replaced
523:09afcf28ed60 525:751532c8f3db
     1 "{ Package: 'stx:goodies/petitparser/compiler' }"
       
     2 
       
     3 "{ NameSpace: Smalltalk }"
       
     4 
       
     5 Object subclass:#PPCCompiler
       
     6 	instanceVariableNames:'compilerStack compiledParser cache currentMethod ids constants
       
     7 		compiledParserName compiledParserSuperclass returnVariable
       
     8 		arguments'
       
     9 	classVariableNames:''
       
    10 	poolDictionaries:''
       
    11 	category:'PetitCompiler-Compiler'
       
    12 !
       
    13 
       
    14 
       
    15 !PPCCompiler class methodsFor:'instance creation'!
       
    16 
       
    17 new
       
    18     "return an initialized instance"
       
    19 
       
    20     ^ self on: PPCArguments default
       
    21 !
       
    22 
       
    23 on: aPPCArguments
       
    24     "return an initialized instance"
       
    25 
       
    26     ^ self basicNew
       
    27                 arguments: aPPCArguments;
       
    28                 initializeForCompiledClassName: aPPCArguments parserName
       
    29 ! !
       
    30 
       
    31 !PPCCompiler methodsFor:'accessing'!
       
    32 
       
    33 arguments: args
       
    34     arguments := args
       
    35 !
       
    36 
       
    37 compiledParser
       
    38     ^ compiledParser 
       
    39 !
       
    40 
       
    41 compiledParserSuperclass
       
    42     ^ compiledParserSuperclass ifNil: [ PPCompiledParser ]
       
    43 !
       
    44 
       
    45 currentMethod
       
    46     ^ currentMethod 
       
    47 !
       
    48 
       
    49 currentNonInlineMethod
       
    50     ^ compilerStack 
       
    51         detect:[:m | m isInline not ] 
       
    52         ifNone:[ self error: 'No non-inlined method']
       
    53 
       
    54     "Created: / 23-04-2015 / 17:33:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
    55 !
       
    56 
       
    57 currentReturnVariable
       
    58     ^ currentMethod returnVariable 
       
    59 !
       
    60 
       
    61 ids
       
    62     ^ ids
       
    63 ! !
       
    64 
       
    65 !PPCCompiler methodsFor:'cleaning'!
       
    66 
       
    67 clean: class
       
    68 "	Transcript show: ('Cleaning time: ',
       
    69     [	
       
    70 "		self cleanGeneratedMethods: class.
       
    71         self cleanInstVars: class.
       
    72         self cleanConstants: class.
       
    73 "	] timeToRun asMilliSeconds asString, 'ms'); cr. "
       
    74 !
       
    75 
       
    76 cleanConstants: class
       
    77     class constants removeAll.
       
    78 !
       
    79 
       
    80 cleanGeneratedMethods: class
       
    81     ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
       
    82         class methodsDo: [ :mthd |
       
    83             (mthd category beginsWith: 'generated') ifTrue:[
       
    84                 class removeSelector: mthd selector.
       
    85             ]
       
    86         ]
       
    87     ] ifFalse: [ 
       
    88         (class allProtocolsUpTo: class) do: [ :protocol |
       
    89             (protocol beginsWith: 'generated') ifTrue: [ 
       
    90                 class removeProtocol: protocol.
       
    91             ]
       
    92         ]
       
    93     ]
       
    94 !
       
    95 
       
    96 cleanInstVars: class
       
    97     class class instanceVariableNames: ''.
       
    98 !
       
    99 
       
   100 cleanParsers: class
       
   101     class parsers removeAll.
       
   102 ! !
       
   103 
       
   104 !PPCCompiler methodsFor:'code generation'!
       
   105 
       
   106 add: string
       
   107     currentMethod add: string.
       
   108 !
       
   109 
       
   110 addComment: string
       
   111     currentMethod add: '"', string, '"'.
       
   112 !
       
   113 
       
   114 addConstant: value as: name    
       
   115     (constants includesKey: name) ifTrue:[ 
       
   116         (constants at: name) ~= value ifTrue:[ 
       
   117             self error:'Duplicate constant!!'.
       
   118         ].
       
   119         ^ self.
       
   120     ].
       
   121     constants at: name put: value
       
   122 
       
   123     "Modified: / 29-05-2015 / 07:22:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   124 !
       
   125 
       
   126 addOnLine: string
       
   127     currentMethod addOnLine: string.
       
   128 !
       
   129 
       
   130 addVariable: name
       
   131     ^ self currentNonInlineMethod addVariable: name
       
   132 
       
   133     "Modified: / 23-04-2015 / 17:34:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   134 !
       
   135 
       
   136 call: anotherMethod
       
   137     currentMethod add: anotherMethod call.
       
   138 !
       
   139 
       
   140 callOnLine: anotherMethod
       
   141     currentMethod addOnLine: anotherMethod call.
       
   142 !
       
   143 
       
   144 codeComment: string
       
   145     currentMethod add: '"', string, '"'.
       
   146 !
       
   147 
       
   148 dedent
       
   149     currentMethod dedent
       
   150 !
       
   151 
       
   152 indent
       
   153     currentMethod indent
       
   154 !
       
   155 
       
   156 nl
       
   157     currentMethod nl
       
   158 !
       
   159 
       
   160 smartRemember: parser to: variableName 
       
   161     parser isContextFree ifTrue: [ 
       
   162         self 	codeAssign: 'context lwRemember.' 
       
   163                 to: variableName.
       
   164     ] ifFalse: [ 
       
   165         self  codeAssign: 'context remember.'
       
   166                 to: variableName.
       
   167     ]
       
   168 !
       
   169 
       
   170 smartRestore: parser from: mementoName
       
   171     parser isContextFree ifTrue: [ 
       
   172         self add: 'context lwRestore: ', mementoName, '.'.
       
   173     ] ifFalse: [ 
       
   174         self add: 'context restore: ', mementoName, '.'.
       
   175     ]
       
   176 ! !
       
   177 
       
   178 !PPCCompiler methodsFor:'code generation - coding'!
       
   179 
       
   180 code:aStringOrBlockOrRBParseNode
       
   181     currentMethod code: aStringOrBlockOrRBParseNode
       
   182 
       
   183     "Created: / 01-06-2015 / 23:49:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   184 !
       
   185 
       
   186 codeAssign: code to: variable
       
   187     self assert: variable isNil not.
       
   188     
       
   189     "TODO JK: Hack alert, whatever is magic constant!!"
       
   190     (variable == #whatever) ifFalse: [ 
       
   191         "Do not assign, if somebody does not care!!"
       
   192         self add: variable ,' := ', code.
       
   193     ]
       
   194 !
       
   195 
       
   196 codeAssignParsedValueOf:aBlock to:aString 
       
   197     | tmpVarirable  method |
       
   198 
       
   199     self assert:aBlock isBlock.
       
   200     self assert:aString isNil not.
       
   201     tmpVarirable := returnVariable.
       
   202     returnVariable := aString.
       
   203     method := [
       
   204             aBlock value
       
   205         ] ensure:[ returnVariable := tmpVarirable ].
       
   206     self assert: (method isKindOf: PPCMethod).
       
   207     method isInline ifTrue:[
       
   208         self callOnLine:method
       
   209     ] ifFalse:[
       
   210         self codeEvaluateAndAssign:(method call) to:aString.
       
   211     ]
       
   212 
       
   213     "Created: / 23-04-2015 / 18:21:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   214 !
       
   215 
       
   216 codeBlock: contents
       
   217     currentMethod codeBlock: contents
       
   218 
       
   219     "Created: / 01-06-2015 / 22:35:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   220 !
       
   221 
       
   222 codeClearError
       
   223     self add: 'self clearError.'.
       
   224 !
       
   225 
       
   226 codeDot
       
   227     self addOnLine:'.'.
       
   228 
       
   229     "Created: / 16-06-2015 / 06:09:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   230 !
       
   231 
       
   232 codeError
       
   233     self add: 'self error: ''message notspecified''.'.
       
   234 !
       
   235 
       
   236 codeError: errorMessage
       
   237     self add: 'self error: ''', errorMessage, '''.'
       
   238 !
       
   239 
       
   240 codeError: errorMessage at: position
       
   241     self add: 'self error: ''', errorMessage, ''' at: ', position asString, '.'
       
   242 !
       
   243 
       
   244 codeEvaluate: selector argument: argument on: variable
       
   245     self assert: variable isNil not.
       
   246     
       
   247     "TODO JK: Hack alert, whatever is magic constant!!"
       
   248     (variable == #whatever) ifFalse: [ 
       
   249         "Do not assign, if somebody does not care!!"
       
   250         self add: variable, ' ', selector,' ', argument.
       
   251  				] ifTrue: [ 
       
   252         "In case argument has a side effect"
       
   253  								self add: argument	
       
   254     ]
       
   255 !
       
   256 
       
   257 codeEvaluateAndAssign: argument to: variable
       
   258     self assert: variable isNil not.
       
   259     
       
   260     "TODO JK: Hack alert, whatever is magic constant!!"
       
   261     (variable == #whatever) ifFalse: [ 
       
   262         "Do not assign, if somebody does not care!!"
       
   263         self add: variable ,' := ', argument.
       
   264     ] ifTrue: [ 
       
   265         "In case an argument has a side effect"
       
   266  				self add: argument.	
       
   267     ]
       
   268 !
       
   269 
       
   270 codeHalt
       
   271     self add: 'self halt. '
       
   272 !
       
   273 
       
   274 codeHaltIfShiftPressed
       
   275     arguments debug ifTrue: [
       
   276         ((Smalltalk respondsTo: #isSmalltalkX) and:[Smalltalk isSmalltalkX]) ifFalse:[  
       
   277             self add: 'Halt ifShiftPressed.'
       
   278         ]
       
   279     ]
       
   280 
       
   281     "Modified: / 10-05-2015 / 07:39:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   282 !
       
   283 
       
   284 codeIf: condition then: then 
       
   285     self codeIf: condition then: then else: nil
       
   286 
       
   287     "Created: / 16-06-2015 / 06:07:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   288 !
       
   289 
       
   290 codeIf: condition then: then else: else
       
   291     currentMethod 
       
   292         add: '(';
       
   293         code: condition;
       
   294         addOnLine: ')'.
       
   295     then notNil ifTrue:[ 
       
   296         currentMethod 
       
   297             addOnLine:' ifTrue:';
       
   298             codeBlock: then.
       
   299     ].
       
   300     else notNil ifTrue:[ 
       
   301         currentMethod 
       
   302             addOnLine:' ifFalse:';
       
   303             codeBlock: else.
       
   304     ].
       
   305     self codeDot.
       
   306 
       
   307     "Created: / 01-06-2015 / 22:43:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   308     "Modified: / 16-06-2015 / 06:09:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   309 !
       
   310 
       
   311 codeIfErrorThen: then
       
   312     ^ self codeIf: 'error' then: then else: nil
       
   313 
       
   314     "Created: / 16-06-2015 / 06:06:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   315 !
       
   316 
       
   317 codeIfErrorThen: then else: else
       
   318     ^ self codeIf: 'error' then: then else: else
       
   319 
       
   320     "Created: / 16-06-2015 / 06:05:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   321 !
       
   322 
       
   323 codeNextToken
       
   324     self add: 'self nextToken.'
       
   325 
       
   326     "Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   327     "Modified: / 23-04-2015 / 20:51:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   328 !
       
   329 
       
   330 codeProfileStart
       
   331     self add: 'context methodInvoked: #', currentMethod methodName, '.'
       
   332 
       
   333     "Created: / 01-06-2015 / 21:17:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   334 !
       
   335 
       
   336 codeProfileStop
       
   337     self add: 'context methodFinished: #', currentMethod methodName, '.'
       
   338 
       
   339     "Created: / 01-06-2015 / 21:19:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   340 !
       
   341 
       
   342 codeReturn
       
   343    currentMethod isInline ifTrue: [
       
   344 				"If inlined, the return variable already holds the value"
       
   345 		] ifFalse: [
       
   346 				arguments profile ifTrue:[ 
       
   347 						self codeProfileStop.
       
   348 				]. 
       
   349 				self add: '^ ', currentMethod returnVariable  
       
   350 		].
       
   351 
       
   352 		"Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   353 		"Modified: / 01-06-2015 / 21:49:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   354 !
       
   355 
       
   356 codeReturn: code
       
   357     " - returns whatever is in code OR
       
   358       - assigns whatever is in code into the returnVariable"
       
   359     currentMethod isInline ifTrue:[
       
   360         self codeEvaluateAndAssign: code to: currentMethod returnVariable. 
       
   361     ] ifFalse: [ 
       
   362         arguments profile ifTrue:[ 
       
   363             self codeProfileStop.
       
   364         ].   
       
   365         self add: '^ ', code            
       
   366     ]
       
   367 
       
   368     "Created: / 23-04-2015 / 18:01:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   369     "Modified: / 01-06-2015 / 21:48:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   370 !
       
   371 
       
   372 codeReturnParsedValueOf:aBlock 
       
   373     | tmpVarirable  method |
       
   374 
       
   375     self assert:aBlock isBlock.	
       
   376     tmpVarirable := returnVariable.
       
   377     method := aBlock value. 
       
   378     self assert: returnVariable == tmpVarirable.
       
   379     self assert: (method isKindOf: PPCMethod).
       
   380     method isInline ifTrue:[
       
   381         self callOnLine:method.
       
   382         self codeReturn: returnVariable.
       
   383     ] ifFalse:[
       
   384         self codeReturn: method call.
       
   385         
       
   386     ]
       
   387 
       
   388     "Created: / 23-04-2015 / 18:21:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   389 !
       
   390 
       
   391 codeStoreValueOf: aBlock intoVariable: aString
       
   392     | tmpVarirable method |
       
   393     self assert: aBlock isBlock.
       
   394     self assert: aString isNil not.
       
   395     
       
   396     tmpVarirable := returnVariable.
       
   397     returnVariable := aString.
       
   398     method := [  
       
   399         aBlock value 
       
   400     ] ensure: [ 
       
   401         returnVariable := tmpVarirable 
       
   402     ].
       
   403     
       
   404     method isInline ifTrue: [ 
       
   405         self callOnLine: method 
       
   406     ] ifFalse: [ 
       
   407         self codeEvaluateAndAssign: (method call) to: aString.
       
   408     ]	
       
   409     
       
   410     "Created: / 23-04-2015 / 18:21:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   411 !
       
   412 
       
   413 codeTokenGuard: node ifFalse: codeBlock
       
   414     | guard id |
       
   415     guard := PPCTokenGuard on: node.
       
   416     (guard makesSense) ifTrue: [ 
       
   417         id := self idFor: guard firstToken.
       
   418 
       
   419         self add: 'self ', id asString, ' ifFalse: ['.
       
   420             self indent.
       
   421             codeBlock value.
       
   422             self dedent.
       
   423         self add: '].'.
       
   424     ]
       
   425 !
       
   426 
       
   427 codeTranscriptShow: text
       
   428     (arguments profile) ifTrue: [ 
       
   429         self add: 'Transcript show: ', text storeString, '; cr.'.
       
   430     ]
       
   431 ! !
       
   432 
       
   433 !PPCCompiler methodsFor:'code generation - ids'!
       
   434 
       
   435 asSelector: string
       
   436     "e.g. '234znak 43 ) 2' asLegalSelector = #v234znak432"
       
   437     
       
   438     | toUse |
       
   439 
       
   440     toUse := string select: [:char | char isAlphaNumeric or: [ char = $_ ] ].
       
   441     (toUse isEmpty or: [ toUse first isLetter not ])
       
   442         ifTrue: [ toUse := 'v', toUse ].
       
   443     toUse first isUppercase ifFalse:[
       
   444         toUse := toUse copy.
       
   445         toUse at: 1 put: toUse first asLowercase
       
   446     ].
       
   447     ^toUse
       
   448 
       
   449     "Modified: / 10-05-2015 / 07:29:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   450 !
       
   451 
       
   452 idFor: object
       
   453     self assert: (object isKindOf: PPCNode).
       
   454     ^ self idFor: object prefixed: object prefix suffixed: object suffix effect: #none
       
   455 !
       
   456 
       
   457 idFor: object prefixed: prefix
       
   458     ^ self idFor: object prefixed: prefix effect: #none
       
   459 !
       
   460 
       
   461 idFor: object prefixed: prefix effect: effect
       
   462     ^ self idFor: object prefixed: prefix suffixed: '' effect: effect.
       
   463 !
       
   464 
       
   465 idFor: object prefixed: prefix suffixed: suffix effect: effect
       
   466     | name id |
       
   467     ^ ids at: object ifAbsentPut: [ 
       
   468         ((object isKindOf: PPCNode) and: [object name isNotNil]) ifTrue: [ 
       
   469             "Do not use prefix, if there is a name"
       
   470             name := self asSelector: (object name asString).
       
   471             id := (name, suffix) asSymbol.
       
   472             
       
   473             "Make sure, that the generated ID is uniqe!!"
       
   474             (ids includes: id) ifTrue: [ 
       
   475                 (id, '_', ids size asString) asSymbol 
       
   476             ] ifFalse: [ 
       
   477                 id
       
   478             ]
       
   479         ] ifFalse: [ 
       
   480             (prefix, '_', (ids size asString), suffix) asSymbol
       
   481         ]
       
   482     ]
       
   483 !
       
   484 
       
   485 idFor: object suffixed: suffix
       
   486     self assert: (object isKindOf: PPCNode) description: 'Shold use PPCNode for ids'.
       
   487     ^ self idFor: object prefixed: object prefix suffixed: suffix effect: #none
       
   488 ! !
       
   489 
       
   490 !PPCCompiler methodsFor:'code generation - profiling'!
       
   491 
       
   492 profileTokenRead: tokenName
       
   493     arguments profile ifTrue: [ 
       
   494         self add: 'context tokenRead: ', tokenName storeString, '.'
       
   495     ]
       
   496 ! !
       
   497 
       
   498 !PPCCompiler methodsFor:'code generation - support'!
       
   499 
       
   500 cache: id as: value
       
   501     cache at: id put: value.
       
   502 !
       
   503 
       
   504 cachedValue: id
       
   505     ^ cache at: id ifAbsent: [ nil ]
       
   506 !
       
   507 
       
   508 checkCache: id
       
   509     | method  |
       
   510     "Check if method is hand written"
       
   511     method := compiledParser ifNotNil: [ compiledParser compiledMethodAt: id ifAbsent: [ nil ] ].
       
   512     method ifNotNil: [ ^ PPCCompiledMethod new id: id; yourself ].
       
   513     
       
   514     ^ self cachedValue: id
       
   515 !
       
   516 
       
   517 pop
       
   518     | retval |
       
   519     retval := compilerStack pop.
       
   520     currentMethod := compilerStack isEmpty 
       
   521         ifTrue: [ nil ]
       
   522         ifFalse: [ compilerStack top ].
       
   523     ^ retval
       
   524 
       
   525     "Modified: / 21-11-2014 / 12:27:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   526 !
       
   527 
       
   528 push
       
   529     compilerStack push: currentMethod.
       
   530     (compilerStack size > 500 )ifTrue: [ self error: 'unless it is very complex grammar, there is an error somewhere' ]
       
   531 
       
   532     "Modified: / 21-11-2014 / 12:27:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   533 !
       
   534 
       
   535 startInline: id
       
   536     | indentationLevel |
       
   537     (cache includesKey: id) ifTrue: [ self error: 'OOOUPS!!' ].
       
   538     indentationLevel := currentMethod indentationLevel.
       
   539     
       
   540     currentMethod := PPCInlinedMethod new.
       
   541     currentMethod id: id.   
       
   542     currentMethod returnVariable: returnVariable.
       
   543     currentMethod indentationLevel: indentationLevel.
       
   544     self push.
       
   545 
       
   546     "Modified: / 01-06-2015 / 21:48:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   547 !
       
   548 
       
   549 startMethod: id
       
   550     (cache includesKey: id) ifTrue: [ self error: 'OOOUPS!!' ].
       
   551 
       
   552     currentMethod := PPCMethod new.
       
   553     currentMethod id: id.
       
   554     arguments profile ifTrue:[ 
       
   555         self codeProfileStart.
       
   556     ].
       
   557     self push.      
       
   558                 
       
   559     self cache: id as: currentMethod.
       
   560 
       
   561     "Modified: / 01-06-2015 / 21:19:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   562 !
       
   563 
       
   564 stopInline
       
   565     ^ self pop.
       
   566 
       
   567     "Modified: / 01-06-2015 / 21:37:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   568 !
       
   569 
       
   570 stopMethod
       
   571    self cache: currentMethod methodName as: currentMethod.
       
   572 		
       
   573 		"arguments profile ifTrue: [ Transcript show: currentMethod code; cr. ]."
       
   574 		^ self pop.
       
   575 
       
   576 		"Modified: / 01-06-2015 / 21:38:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   577 !
       
   578 
       
   579 top
       
   580     ^ compilerStack top
       
   581 ! !
       
   582 
       
   583 !PPCCompiler methodsFor:'code generation - variables'!
       
   584 
       
   585 allocateReturnVariable    
       
   586     ^ self allocateReturnVariableNamed: 'retval'
       
   587 
       
   588     "Created: / 23-04-2015 / 18:03:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   589     "Modified: / 15-06-2015 / 17:52:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   590 !
       
   591 
       
   592 allocateReturnVariableNamed: name
       
   593     "Allocate (or return previously allocated one) temporary variable used for
       
   594      storing a parser's return value (the parsed object)"                 
       
   595     ^ currentMethod allocateReturnVariableNamed: name
       
   596 
       
   597     "Created: / 15-06-2015 / 18:04:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   598 !
       
   599 
       
   600 allocateTemporaryVariableNamed: preferredName 
       
   601     "Allocate a new variable with (preferably) given name.
       
   602      Returns a real variable name that should be used."
       
   603     
       
   604     ^ self currentNonInlineMethod allocateTemporaryVariableNamed: preferredName
       
   605 
       
   606     "Created: / 23-04-2015 / 17:33:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   607 ! !
       
   608 
       
   609 !PPCCompiler methodsFor:'compiling'!
       
   610 
       
   611 compileParser
       
   612     self installVariables.
       
   613     self installMethods.
       
   614     self installClassConstants.
       
   615 
       
   616     ^ compiledParser
       
   617 !
       
   618 
       
   619 copy: parser
       
   620     ^ parser transform: [ :p | p copy ].
       
   621 !
       
   622 
       
   623 installClassConstants
       
   624     constants keysAndValuesDo: [ :key :value |
       
   625         compiledParser constants at: key put: value
       
   626     ]
       
   627 !
       
   628 
       
   629 installMethods
       
   630     cache keysAndValuesDo: [ :key :method |
       
   631         compiledParser compileSilently: method source classified: method category.
       
   632     ]
       
   633 
       
   634     "Modified: / 24-07-2015 / 19:45:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   635 !
       
   636 
       
   637 installVariables
       
   638     | varString |
       
   639     varString := constants keys inject: '' into: [:r :e | r, ' ', e  ].
       
   640 
       
   641     (self compiledParserSuperclass) 
       
   642         subclass: compiledParserName  
       
   643         instanceVariableNames: varString 
       
   644         classVariableNames: '' 
       
   645         poolDictionaries: '' 
       
   646         category: 'PetitCompiler-Generated'.
       
   647 
       
   648     compiledParser := Smalltalk at: compiledParserName.
       
   649 ! !
       
   650 
       
   651 !PPCCompiler methodsFor:'initialization'!
       
   652 
       
   653 initializeForCompiledClassName: aString
       
   654     
       
   655     self initialize.
       
   656     compilerStack := Stack new.
       
   657     cache := IdentityDictionary new.
       
   658     constants := Dictionary new.
       
   659     ids := IdentityDictionary new.
       
   660     
       
   661 
       
   662     compiledParserName := aString asSymbol.
       
   663     
       
   664     ((Smalltalk respondsTo:#isSmalltalkX) and:[ Smalltalk isSmalltalkX ]) ifTrue:[
       
   665         | rPackageOrganizer |
       
   666         rPackageOrganizer := Smalltalk at: #RPackageOrganizer.
       
   667         rPackageOrganizer notNil ifTrue:[
       
   668             rPackageOrganizer default registerPackageNamed: 'PetitCompiler-Generated'.
       
   669         ].
       
   670     ] ifFalse: [ 
       
   671         RPackageOrganizer default registerPackageNamed: 'PetitCompiler-Generated'.
       
   672     ].
       
   673 
       
   674     Smalltalk at: compiledParserName ifPresent: [ :class |
       
   675         compiledParser := class.
       
   676         self clean: compiledParser.
       
   677     ].
       
   678 
       
   679 
       
   680     Transcript cr; show: 'intialized for: ', aString; cr.
       
   681 
       
   682     "Modified: / 26-05-2015 / 17:09:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
       
   683 ! !
       
   684 
       
   685 !PPCCompiler class methodsFor:'documentation'!
       
   686 
       
   687 version_HG
       
   688 
       
   689     ^ '$Changeset: <not expanded> $'
       
   690 ! !
       
   691