compiler/PPCScannerCodeGenerator.st
changeset 515 b5316ef15274
parent 502 1e45d3c96ec5
child 516 3b81c9e53352
child 524 f6f68d32de73
equal deleted inserted replaced
502:1e45d3c96ec5 515:b5316ef15274
     2 
     2 
     3 "{ NameSpace: Smalltalk }"
     3 "{ NameSpace: Smalltalk }"
     4 
     4 
     5 Object subclass:#PPCScannerCodeGenerator
     5 Object subclass:#PPCScannerCodeGenerator
     6 	instanceVariableNames:'codeGen fsa backlinkStates backlinkTransitions arguments openSet
     6 	instanceVariableNames:'codeGen fsa backlinkStates backlinkTransitions arguments openSet
     7 		joinPoints incommingTransitions methodCache id'
     7 		incommingTransitions methodCache id resultStrategy fsaCache'
     8 	classVariableNames:''
     8 	classVariableNames:''
     9 	poolDictionaries:''
     9 	poolDictionaries:''
    10 	category:'PetitCompiler-Scanner'
    10 	category:'PetitCompiler-Scanner'
    11 !
    11 !
    12 
    12 
    16     ^ arguments 
    16     ^ arguments 
    17 !
    17 !
    18 
    18 
    19 arguments: anObject
    19 arguments: anObject
    20     arguments := anObject
    20     arguments := anObject
       
    21 !
       
    22 
       
    23 codeGen
       
    24     ^ codeGen 
       
    25 !
       
    26 
       
    27 compiler
       
    28     ^ self codeGen 
    21 ! !
    29 ! !
    22 
    30 
    23 !PPCScannerCodeGenerator methodsFor:'analysis'!
    31 !PPCScannerCodeGenerator methodsFor:'analysis'!
    24 
    32 
    25 analyzeBacklinks
    33 analyzeBacklinks
    29     backlinkTransitions do: [ :t |
    37     backlinkTransitions do: [ :t |
    30         (self backlinksTo: (t destination)) add: t.
    38         (self backlinksTo: (t destination)) add: t.
    31     ].
    39     ].
    32 !
    40 !
    33 
    41 
    34 analyzeJoinPoints
    42 analyzeDistinctRetvals
    35     | joinTransitions |
    43     (fsa hasDistinctRetvals) ifTrue: [
    36     joinTransitions := fsa joinTransitions.
    44         resultStrategy := PPCDistinctResultStrategy new
    37     joinTransitions := joinTransitions reject: [ :t | self isBacklinkDestination: t destination ].
    45             codeGen: codeGen;
    38     joinPoints := IdentityDictionary new.
    46             yourself
    39     
    47     ] ifFalse: [ 
    40     joinTransitions do: [ :t |
    48         resultStrategy := PPCUniversalResultStrategy new
    41         (joinPoints at: t destination ifAbsentPut: [ IdentitySet new ]) add: t.
    49             codeGen: codeGen;
    42     ]
    50             tokens: fsa retvals asArray;
    43     
    51             yourself
       
    52     ]
    44 !
    53 !
    45 
    54 
    46 analyzeTransitions
    55 analyzeTransitions
    47     | transitions |
    56     | transitions |
    48     transitions := fsa allTransitions.
    57     transitions := fsa allTransitions.
    56 
    65 
    57 backlinksTo: state
    66 backlinksTo: state
    58     ^ backlinkStates at: state ifAbsentPut: [ OrderedCollection new ] 
    67     ^ backlinkStates at: state ifAbsentPut: [ OrderedCollection new ] 
    59 !
    68 !
    60 
    69 
    61 closedJoinPoints
       
    62     | closed |
       
    63     closed := IdentitySet new.
       
    64     
       
    65     joinPoints keysAndValuesDo: [ :key :value | 
       
    66         value isEmpty ifTrue: [ closed add: key ].
       
    67     ].
       
    68 
       
    69     ^ closed
       
    70 !
       
    71 
       
    72 containsBacklink: state
    70 containsBacklink: state
    73     state transitions do: [ :t |
    71     state transitions do: [ :t |
    74         (self isBacklink:  t) ifTrue: [ ^ true ]
    72         (self isBacklink:  t) ifTrue: [ ^ true ]
    75     ].
    73     ].
    76 
    74 
    91 
    89 
    92 isBacklinkDestination: state
    90 isBacklinkDestination: state
    93     ^ (self backlinksTo: state)  isEmpty not
    91     ^ (self backlinksTo: state)  isEmpty not
    94 !
    92 !
    95 
    93 
    96 isJoinPoint: state
    94 startsSimpleLoop: state
    97     "Please note that joinPoints are removed as the compilaction proceeds"
    95     |   |
    98     ^ joinPoints keys includes: state
    96 
    99 !
    97     "
   100 
    98         This accepts more or less something like $a star
   101 joinTransitionsTo: joinPoint "state"
    99         for now.. might extend later
   102     ^ joinPoints at: joinPoint ifAbsent: [ #() ]
   100     "
       
   101     ((self incommingTransitionsFor: state) size == 2) ifFalse: [ ^ false ].
       
   102     ^ (state transitions select: [ :t | t destination == state ]) size == 1
       
   103     
       
   104 ! !
       
   105 
       
   106 !PPCScannerCodeGenerator methodsFor:'caching'!
       
   107 
       
   108 cache: anFsa method: method
       
   109     fsaCache at: anFsa put: method
       
   110 !
       
   111 
       
   112 cachedValueForIsomorphicFsa: anFsa
       
   113     | key |
       
   114     key := fsaCache keys detect: [ :e | e isIsomorphicTo: anFsa ].
       
   115     ^ fsaCache at: key
       
   116 !
       
   117 
       
   118 isomorphicIsCached: anFsa
       
   119     ^ fsaCache keys anySatisfy: [ :e | e isIsomorphicTo: anFsa ]
   103 ! !
   120 ! !
   104 
   121 
   105 !PPCScannerCodeGenerator methodsFor:'code generation'!
   122 !PPCScannerCodeGenerator methodsFor:'code generation'!
   106 
   123 
   107 generate
   124 generate
       
   125     | method |
   108     self assert: fsa isDeterministic.
   126     self assert: fsa isDeterministic.
   109     self assert: fsa isWithoutEpsilons.
   127     self assert: fsa isWithoutEpsilons.
   110     self assert: fsa checkConsistency.
   128     self assert: fsa checkConsistency.
   111 
   129 
       
   130     (self isomorphicIsCached: fsa) ifTrue: [ 
       
   131         ^ self cachedValueForIsomorphicFsa: fsa 
       
   132     ].
   112 
   133 
   113     self analyzeBacklinks.
   134     self analyzeBacklinks.
   114     self analyzeJoinPoints.
       
   115     self analyzeTransitions.
   135     self analyzeTransitions.
       
   136     self analyzeDistinctRetvals.
   116     
   137     
   117     openSet := IdentitySet new.
   138     openSet := IdentitySet new.
   118     
       
   119     codeGen startMethod: (codeGen idFor: fsa).
   139     codeGen startMethod: (codeGen idFor: fsa).
   120     codeGen codeComment: (Character codePoint: 13) asString, fsa asString.
   140     codeGen codeComment: (Character codePoint: 13) asString, fsa asString.
       
   141     resultStrategy reset.
   121 
   142 
   122     self generateFor: fsa startState.
   143     self generateFor: fsa startState.
   123 
   144 
   124     codeGen stopMethod.	
   145     method := codeGen stopMethod.	
   125         
   146     self cache: fsa method: method.
   126     ^ self compileScannerClass new
   147     
       
   148     ^ method.
       
   149 
   127 
   150 
   128 
   151 
   129 !
   152 !
   130 
   153 
   131 generate: aPEGFsa
   154 generate: aPEGFsa
   132     fsa := aPEGFsa.
   155     fsa := aPEGFsa.
   133 
   156 
   134     fsa compact.
   157     self assert: fsa isDeterministic.
       
   158     self assert: fsa isWithoutPriorities.
       
   159     
       
   160     fsa minimize.
   135     fsa checkSanity.
   161     fsa checkSanity.
   136     
   162     
   137     ^ self generate
   163     ^ self generate
   138 !
   164 !
   139 
   165 
       
   166 generateAndCompile
       
   167     self generate.
       
   168     ^ self compile
       
   169 !
       
   170 
       
   171 generateAndCompile: aPEGFsa
       
   172     fsa := aPEGFsa.
       
   173 
       
   174     fsa minimize.
       
   175     fsa checkSanity.
       
   176     
       
   177     ^ self generateAndCompile
       
   178 !
       
   179 
   140 generateFinalFor: state
   180 generateFinalFor: state
   141     state isFinal ifFalse: [  ^ self ].
   181     ^ self generateFinalFor: state offset: 0
   142 
   182 !
   143     codeGen codeRecordMatch: state retval priority: state priority.
   183 
       
   184 generateFinalFor: state offset: offset
       
   185     state retvalsAndInfosDo: [:retval :info |
       
   186         info isFinal ifTrue: [ 
       
   187             info isFsaFailure ifTrue: [ 
       
   188                 resultStrategy recordFailure: retval offset: offset
       
   189             ] ifFalse: [ 
       
   190                 resultStrategy recordMatch: retval offset: offset
       
   191             ]
       
   192         ].
       
   193     ]
   144 !
   194 !
   145 
   195 
   146 generateFor: state
   196 generateFor: state
   147 "	(self isJoinPoint: state) ifTrue: [ 
       
   148         ^ codeGen codeComment: 'join point generation postponed...'
       
   149     ].
       
   150 "
       
   151     codeGen cachedValue: (codeGen idFor: state) ifPresent: [ :method | 
   197     codeGen cachedValue: (codeGen idFor: state) ifPresent: [ :method | 
   152         "if state is already cached, it has multiple incomming links.
   198         "if state is already cached, it has multiple incomming links.
   153      	 In such a case, it is compiled as a method, thus return immediatelly"
   199      	 In such a case, it is compiled as a method, thus return immediatelly"
   154         ^ codeGen codeAbsoluteReturn:  method call
   200         ^ codeGen codeAbsoluteReturn:  method call
   155     ].
   201     ].
   156 
   202 
   157     self generateStartMethod: state.
   203     (self startsSimpleLoop: state) ifTrue: [ 
   158 "	(self isBacklinkDestination: state) ifTrue: [ 
   204         ^ self generateSimpleLoopFor: state
   159         codeGen codeStartBlock.
   205     ].
   160     ].
   206     
   161 "
   207     ^ self generateStandardFor: state
   162     self generateFinalFor: state.
       
   163     self generateNextFor: state.
       
   164     self generateTransitionsFor: state.
       
   165 
       
   166 "	(self isBacklinkDestination: state) ifTrue: [ 
       
   167         codeGen codeEndBlockWhileTrue.
       
   168     ].
       
   169 "
       
   170     self generateStopMethod: state.
       
   171 !
   208 !
   172 
   209 
   173 generateForSingleTransition: t from: state.
   210 generateForSingleTransition: t from: state.
   174     
   211     
   175     (self isJoinPoint: t destination) ifTrue: [ self removeJoinTransition: t ].
   212     (self isJoinPoint: t destination) ifTrue: [ self removeJoinTransition: t ].
   176     
   213     
   177     codeGen codeAssertPeek: (t characterSet) orReturn: state priority.
   214     codeGen codeAssertPeek: t ifFalse: [ 
       
   215         resultStrategy returnResult: state 
       
   216     ].
   178 "	(self isBacklink: t) ifTrue: [ 
   217 "	(self isBacklink: t) ifTrue: [ 
   179         codeGen add: 'true'
   218         codeGen add: 'true'
   180     ] ifFalse: [ 
   219     ] ifFalse: [ 
   181         self generateFor: t destination.
   220         self generateFor: t destination.
   182     ]
   221     ]
   183 "
   222 "
   184     self generateFor: t destination
   223     self generateFor: t destination
   185 !
   224 !
   186 
   225 
   187 generateForTransition: t from: state	
   226 generateForTransition: t from: state		
   188     (self isJoinPoint: t destination) ifTrue: [ self removeJoinTransition: t   ].
       
   189     
       
   190 "	(self isBacklink: t) ifTrue: [ 
   227 "	(self isBacklink: t) ifTrue: [ 
   191         codeGen codeAssertPeek: (t characterSet) ifTrue: [ 
   228         codeGen codeAssertPeek: (t characterSet) ifTrue: [ 
   192             codeGen add: 'true'
   229             codeGen add: 'true'
   193         ]
   230         ]
   194     ] ifFalse: [ 
   231     ] ifFalse: [ 
   195         codeGen codeAssertPeek: (t characterSet) ifTrue: [.
   232         codeGen codeAssertPeek: (t characterSet) ifTrue: [.
   196             self generateFor: t destination.
   233             self generateFor: t destination.
   197         ].
   234         ].
   198     ].
   235     ].
   199 "
   236 "
   200     codeGen codeAssertPeek: (t characterSet) ifTrue: [.
   237     codeGen codeAssertPeek: t ifTrue: [.
   201         self generateFor: t destination.
   238         self generateFor: t destination.
   202     ].
   239     ].
   203     codeGen codeIfFalse.
   240     codeGen codeIfFalse.
   204 !
   241 !
   205 
   242 
   207     state transitions isEmpty ifTrue: [  ^ self ].
   244     state transitions isEmpty ifTrue: [  ^ self ].
   208     codeGen codeNextChar.
   245     codeGen codeNextChar.
   209 !
   246 !
   210 
   247 
   211 generateReturnFor: state
   248 generateReturnFor: state
   212     codeGen codeNlReturnResult: state priority.
   249     codeGen codeNl.
       
   250     resultStrategy returnResult: state.
       
   251 !
       
   252 
       
   253 generateSimpleLoopFor: state
       
   254     | selfTransition |
       
   255     selfTransition := state transitions detect: [ :t | t destination == state ].
       
   256     
       
   257     codeGen codeStartBlock.
       
   258     codeGen codeNextChar.
       
   259     codeGen codeNl.
       
   260     codeGen codeAssertPeek: selfTransition.
       
   261     codeGen codeEndBlockWhileTrue.
       
   262 
       
   263     "Last transition did not passed the loop, therefore, we have to record succes with offset -1"
       
   264     self generateFinalFor: state offset: 1.
       
   265     self generateTransitions: (state transitions reject: [ :t | t == selfTransition  ]) for: state.
       
   266     
       
   267 !
       
   268 
       
   269 generateStandardFor: state
       
   270     self generateStartMethod: state.
       
   271     self generateFinalFor: state.
       
   272     self generateNextFor: state.
       
   273     self generateTransitionsFor: state.
       
   274 
       
   275     self generateStopMethod: state.
   213 !
   276 !
   214 
   277 
   215 generateStartMethod: state.
   278 generateStartMethod: state.
   216     id := codeGen idFor: state.
   279     id := codeGen idFor: state.
   217 
   280 
   232         codeGen code: codeGen stopInline call.
   295         codeGen code: codeGen stopInline call.
   233     ].
   296     ].
   234     codeGen codeComment: 'STOP - Generated from state: ', state asString.
   297     codeGen codeComment: 'STOP - Generated from state: ', state asString.
   235 !
   298 !
   236 
   299 
   237 generateTransitionsFor: state
   300 generateTransitions: transitions for: state
   238     (state transitions size = 0) ifTrue: [  
   301     (transitions size = 0) ifTrue: [  
   239         self generateReturnFor: state.
   302         self generateReturnFor: state.
   240         ^ self	
   303         ^ self	
   241     ].
   304     ].
   242 
   305 
   243     (state transitions size = 1) ifTrue: [  
   306 "	(state transitions size = 1) ifTrue: [  
   244         self generateForSingleTransition: state transitions anyOne from: state.
   307         self generateForSingleTransition: state transitions anyOne from: state.
   245         ^ self
   308         ^ self
   246     ].
   309     ]."
   247 
       
   248 
   310 
   249     codeGen codeNl.
   311     codeGen codeNl.
   250     state transitions do: [ :t |
   312     transitions do: [ :t |
   251         self generateForTransition: t from: state
   313         self generateForTransition: t from: state
   252     ].
   314     ].
   253 
   315 
   254     codeGen indent.
   316     codeGen indent.
   255     self generateReturnFor: state.
   317     self generateReturnFor: state.
   256     codeGen dedent.
   318     codeGen dedent.
   257     codeGen codeNl.
   319     codeGen codeNl.
   258     state transitions size timesRepeat: [ codeGen addOnLine: ']' ].
   320     transitions size timesRepeat: [ codeGen addOnLine: ']' ].
   259     codeGen addOnLine: '.'.
   321     codeGen addOnLine: '.'.
   260     
   322     
   261 
   323 
   262 "	self closedJoinPoints isEmpty ifFalse: [ 
   324 "	self closedJoinPoints isEmpty ifFalse: [ 
   263         | jp |
   325         | jp |
   266         jp := self closedJoinPoints anyOne.
   328         jp := self closedJoinPoints anyOne.
   267         self removeJoinPoint: jp.
   329         self removeJoinPoint: jp.
   268         self generateFor: jp.
   330         self generateFor: jp.
   269     ]
   331     ]
   270 "
   332 "
       
   333 !
       
   334 
       
   335 generateTransitionsFor: state
       
   336     ^ self generateTransitions: state transitions for: state
       
   337 !
       
   338 
       
   339 setMaxNumericId
       
   340     codeGen addConstant: codeGen idGen numericIds size as: #MaxSymbolNumber 
       
   341 !
       
   342 
       
   343 setTokens
       
   344     | tokens |
       
   345     tokens := Array new: codeGen idGen numericIdCache size.
       
   346     
       
   347     codeGen idGen numericIdCache keysAndValuesDo: [ :key :value |
       
   348         tokens at: value put: key
       
   349     ].
       
   350 
       
   351     codeGen addConstant: tokens as: #Tokens 
   271 ! !
   352 ! !
   272 
   353 
   273 !PPCScannerCodeGenerator methodsFor:'compiling'!
   354 !PPCScannerCodeGenerator methodsFor:'compiling'!
       
   355 
       
   356 compile
       
   357     ^ self compileScannerClass new
       
   358 !
   274 
   359 
   275 compileScannerClass
   360 compileScannerClass
   276     | builder |
   361     | builder |
       
   362     self setMaxNumericId.
       
   363     self setTokens.
       
   364     
   277     builder := PPCClassBuilder new.
   365     builder := PPCClassBuilder new.
   278     
   366     
   279     builder compiledClassName: arguments scannerName.
   367     builder compiledClassName: arguments scannerName.
   280     builder compiledSuperclass: PPCScanner.
   368     builder compiledSuperclass: PPCScanner.
   281     builder methodDictionary: codeGen methodDictionary.
   369     builder methodDictionary: codeGen methodDictionary.
   289 initialize
   377 initialize
   290     super initialize.
   378     super initialize.
   291     
   379     
   292     codeGen := PPCFSACodeGen new.
   380     codeGen := PPCFSACodeGen new.
   293     arguments := PPCArguments default.
   381     arguments := PPCArguments default.
   294 ! !
   382     fsaCache := IdentityDictionary new.
   295 
   383 ! !
   296 !PPCScannerCodeGenerator methodsFor:'support'!
   384 
   297 
       
   298 removeJoinPoint: state
       
   299     self assert: (joinPoints at: state) size = 0.
       
   300     joinPoints removeKey: state
       
   301 !
       
   302 
       
   303 removeJoinTransition: t
       
   304     (self joinTransitionsTo: t destination) remove: t ifAbsent: [ self error: 'this should not happen' ].
       
   305 ! !
       
   306