compiler/PEGFsaState.st
changeset 516 3b81c9e53352
parent 504 0fb1f0799fc1
parent 515 b5316ef15274
child 518 a6d8b93441b0
equal deleted inserted replaced
514:46dd1237b20a 516:3b81c9e53352
     1 "{ Package: 'stx:goodies/petitparser/compiler' }"
     1 "{ Package: 'stx:goodies/petitparser/compiler' }"
     2 
     2 
     3 "{ NameSpace: Smalltalk }"
     3 "{ NameSpace: Smalltalk }"
     4 
     4 
     5 Object subclass:#PEGFsaState
     5 Object subclass:#PEGFsaState
     6 	instanceVariableNames:'name retval priority transitions final multivalue'
     6 	instanceVariableNames:'name infos transitions'
     7 	classVariableNames:''
     7 	classVariableNames:''
     8 	poolDictionaries:''
     8 	poolDictionaries:''
     9 	category:'PetitCompiler-FSA'
     9 	category:'PetitCompiler-FSA'
    10 !
    10 !
    11 
    11 
    15     "return an initialized instance"
    15     "return an initialized instance"
    16 
    16 
    17     ^ self basicNew initialize.
    17     ^ self basicNew initialize.
    18 ! !
    18 ! !
    19 
    19 
       
    20 !PEGFsaState class methodsFor:'as yet unclassified'!
       
    21 
       
    22 named: aName
       
    23     ^ self new
       
    24         name: aName;
       
    25         yourself
       
    26 ! !
       
    27 
    20 !PEGFsaState methodsFor:'accessing'!
    28 !PEGFsaState methodsFor:'accessing'!
    21 
    29 
    22 destination
    30 destination
    23     self assert: transitions size = 1.
    31     self assert: transitions size = 1.
    24     ^ transitions anyOne destination
    32     ^ transitions anyOne destination
    26 
    34 
    27 destinations
    35 destinations
    28     ^ (transitions collect: #destination) asIdentitySet
    36     ^ (transitions collect: #destination) asIdentitySet
    29 !
    37 !
    30 
    38 
       
    39 failure: boolean
       
    40     self info failure: boolean
       
    41 !
       
    42 
    31 final
    43 final
    32     ^ final
    44     ^ self info final
    33 !
    45 !
    34 
    46 
    35 final: anObject
    47 final: boolean
    36     final := anObject
    48     self info final: boolean
       
    49 !
       
    50 
       
    51 infoFor: retval
       
    52     ^ infos at: retval
       
    53 !
       
    54 
       
    55 infoFor: retval ifAbsent: block
       
    56     ^ infos at: retval ifAbsent: block
       
    57 !
       
    58 
       
    59 isFsaFailure
       
    60     ^ self isFinal and: [ self info isFsaFailure ]
    37 !
    61 !
    38 
    62 
    39 multivalue
    63 multivalue
    40     ^ multivalue
    64     <resource: #obsolete>
       
    65     ^ self isMultivalue
       
    66 
       
    67     "Modified: / 17-08-2015 / 12:03:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    41 !
    68 !
    42 
    69 
    43 multivalue: anObject
    70 multivalue: anObject
    44     multivalue := anObject
    71     self flag: 'JK: Obsolete?'.
       
    72     "multivalue := anObject"
       
    73 
       
    74     "Modified: / 17-08-2015 / 12:03:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    45 !
    75 !
    46 
    76 
    47 name
    77 name
    48     ^ name
    78     ^ name
    49 !
    79 !
    50 
    80 
    51 name: anObject
    81 name: anObject
    52     name := anObject asString
    82     name := anObject asString
    53 !
    83 !
    54 
    84 
    55 prefix
       
    56     ^ 'state'
       
    57 !
       
    58 
       
    59 priority
    85 priority
    60     ^ priority
    86     ^ self info priority
    61 !
    87 !
    62 
    88 
    63 priority: anObject
    89 priority: anObject
    64     priority := anObject
    90     self info priority: anObject
       
    91 !
       
    92 
       
    93 priorityFor: retval
       
    94     ^ (self infoFor: retval) priority
    65 !
    95 !
    66 
    96 
    67 priorityIfNone: value
    97 priorityIfNone: value
    68     ^ self hasPriority ifTrue: [ self priority ] ifFalse: [ value ]
    98     ^ self hasPriority ifTrue: [ self priority ] ifFalse: [ value ]
    69 !
    99 !
    70 
   100 
    71 retval
   101 retval
    72     ^ retval
   102     self assert: self isMultivalue not.
       
   103     ^ infos keys anyOne
    73 !
   104 !
    74 
   105 
    75 retval: anObject
   106 retval: anObject
    76     retval := anObject
   107     | info |
       
   108     info := self info.
       
   109     infos removeAll.
       
   110     infos at: anObject put: info.
    77 !
   111 !
    78 
   112 
    79 retvalAsCollection
   113 retvalAsCollection
    80     ^ self isMultivalue ifTrue: [ 
   114     ^ infos keys
    81         self retval
   115 !
    82     ] ifFalse: [ 
   116 
    83         Array with: self retval
   117 retvals
    84     ]
   118     ^ infos keys
    85 !
   119 !
    86 
   120 
    87 suffix
   121 retvalsAndInfosDo: twoArgBlock
    88     ^ ''
   122  	infos keysAndValuesDo: twoArgBlock
       
   123 !
       
   124 
       
   125 stateInfos
       
   126     ^ infos values
    89 !
   127 !
    90 
   128 
    91 transitions
   129 transitions
    92     ^ transitions
   130     ^ transitions
    93 ! !
   131 ! !
    94 
   132 
    95 !PEGFsaState methodsFor:'analysis'!
   133 !PEGFsaState methodsFor:'analysis'!
       
   134 
       
   135 collectNonEpsilonTransitionsOf: state to: collection
       
   136     state transitions do: [ :t | 
       
   137         t isEpsilon ifTrue: [ 
       
   138             self collectNonEpsilonTransitionsOf: t destination to: collection
       
   139         ] ifFalse: [ 
       
   140             collection add: t
       
   141         ]
       
   142     ].
       
   143     ^ collection
       
   144 !
       
   145 
       
   146 nonEpsilonTransitionPairs
       
   147     | size pairs collection |
       
   148     pairs := OrderedCollection new.
       
   149     
       
   150     collection := OrderedCollection new.
       
   151     self collectNonEpsilonTransitionsOf: self to: collection.
       
   152     size := collection size.
       
   153 
       
   154     1 to: (size - 1) do: [ :index1 |
       
   155         (index1 + 1 to: size) do: [ :index2 | 
       
   156             pairs add: (PEGFsaPair 
       
   157                 with: (collection at: index1)
       
   158                 with: (collection at: index2)).
       
   159         ]
       
   160     ].
       
   161     ^ pairs
       
   162 !
    96 
   163 
    97 reachableStates
   164 reachableStates
    98     | openSet |
   165     | openSet |
    99     openSet := IdentitySet new.
   166     openSet := IdentitySet new.
   100     self reachableStatesOpenSet: openSet.
   167     self reachableStatesOpenSet: openSet.
   115 !
   182 !
   116 
   183 
   117 transitionPairs
   184 transitionPairs
   118     | size pairs collection |
   185     | size pairs collection |
   119     size := transitions size.
   186     size := transitions size.
   120     pairs := OrderedCollection new: (size - 1) * size / 2.
   187     pairs := OrderedCollection new.
   121     
   188     
   122     collection := transitions asOrderedCollection.
   189     collection := transitions asOrderedCollection.
   123 
   190 
   124     1 to: (size - 1) do: [ :index1 |
   191     1 to: (size - 1) do: [ :index1 |
   125         (index1 + 1 to: size) do: [ :index2 | 
   192         (index1 + 1 to: size) do: [ :index2 | 
   126             pairs add: (PEGFsaPair new 
   193             pairs add: (PEGFsaPair 
   127                 first: (collection at: index1);
   194                 with: (collection at: index1)
   128                 second: (collection at: index2);
   195                 with: (collection at: index2)).
   129                 yourself).
       
   130         ]
   196         ]
   131     ].
   197     ].
   132     ^ pairs
   198     ^ pairs
   133 ! !
   199 ! !
   134 
   200 
   135 !PEGFsaState methodsFor:'comparing'!
   201 !PEGFsaState methodsFor:'comparing'!
   136 
   202 
   137 = anotherState
   203 = anotherState
   138     (self == anotherState) ifTrue: [ ^ true ].
   204     (self == anotherState) ifTrue: [ ^ true ].
   139     (self class == anotherState class) ifFalse: [ ^ true ].
   205     (self class == anotherState class) ifFalse: [ ^ false ].
   140     
   206     
   141     (name == anotherState name) ifFalse: [ ^ false ].
   207     (name == anotherState name) ifFalse: [ ^ false ].
   142     (priority == anotherState priority) ifFalse: [ ^ false ].
   208 
   143     (multivalue == anotherState multivalue) ifFalse: [ ^ false ].
   209     (self stateInfos size == anotherState stateInfos size) ifFalse: [ ^ false ].
   144     (retval = anotherState retval) ifFalse: [ ^ false ].
   210     self retvals do: [:retval |
   145     (final = anotherState final) ifFalse: [ ^ false ].
   211         ((self infoFor: retval) = (anotherState infoFor: retval  ifAbsent: [ ^ false ])) ifFalse: [ ^ false ]
       
   212     ].
   146 
   213 
   147     (transitions size = anotherState transitions size) ifFalse: [ ^ false ].
   214     (transitions size = anotherState transitions size) ifFalse: [ ^ false ].
   148     transitions do: [:t |
   215     transitions do: [:t |
   149         (anotherState transitions contains: [:at | at = t]) ifFalse: [ ^ false ].
   216         (anotherState transitions contains: [:at | at = t]) ifFalse: [ ^ false ].
   150     ].
   217     ].
   152     ^ true
   219     ^ true
   153 !
   220 !
   154 
   221 
   155 canBeIsomorphicTo: anotherState
   222 canBeIsomorphicTo: anotherState
   156     (name == anotherState name) ifFalse: [ ^ false ].
   223     (name == anotherState name) ifFalse: [ ^ false ].
   157     (priority == anotherState priority) ifFalse: [ ^ false ].
       
   158     (multivalue == anotherState multivalue) ifFalse: [ ^ false ].
       
   159     (final == anotherState final) ifFalse: [ ^ false ].
       
   160     (transitions size == anotherState transitions size) ifFalse: [ ^ false ].
   224     (transitions size == anotherState transitions size) ifFalse: [ ^ false ].
   161     (retval = anotherState retval) ifFalse: [ ^ false ].
   225 
       
   226     (self stateInfos size == anotherState stateInfos size) ifFalse: [ ^ false ].
       
   227     self retvals do: [:retval |
       
   228         ((self infoFor: retval) = (anotherState infoFor: retval ifAbsent: [ ^ false ])) ifFalse: [ ^ false ]
       
   229     ].
   162     
   230     
   163     ^ true
   231     ^ true
   164 !
   232 !
   165 
   233 
   166 equals: anotherState
   234 equals: anotherState
       
   235     self error: 'deprecated'.
       
   236     "
       
   237         JK: there is a bit mess between equals, isomorphic and =
       
   238         
       
   239         JK: I should clean it, but the idea behind is:
       
   240             - for minimization, I use equals 
       
   241             - for comparing, I use canBeIsomorphicTo: (because it can handle nested structures)
       
   242             - I have no idea, why I override =     O:)
       
   243     "
       
   244 
   167     (self == anotherState) ifTrue: [ ^ true ].
   245     (self == anotherState) ifTrue: [ ^ true ].
   168     (anotherState class == PEGFsaState) ifFalse: [ ^ false ].
   246     (self class == anotherState class) ifFalse: [ ^ false ].
   169     
   247     
   170     (retval = anotherState retval) ifFalse: [ ^ false ].
       
   171     (multivalue = anotherState multivalue) ifFalse: [ ^ false ].
       
   172     (self isFinal = anotherState isFinal) ifFalse: [ ^ false ].
   248     (self isFinal = anotherState isFinal) ifFalse: [ ^ false ].
   173 
   249 
   174     (self hasPriority and: [anotherState hasPriority]) ifTrue: [ 	
   250     (self stateInfos size == anotherState stateInfos size) ifFalse: [ ^ false ].
   175         (priority == anotherState priority) ifFalse: [ ^ false ].
   251     self retvals do: [:retval |
       
   252         ((self infoFor: retval) equals: (anotherState infoFor: retval ifAbsent: [ ^ false ])) ifFalse: [ ^ false ]
   176     ].
   253     ].
   177 
   254 
   178     (transitions size == anotherState transitions size) ifFalse: [ ^ false ].
   255     (transitions size == anotherState transitions size) ifFalse: [ ^ false ].
   179     anotherState transitions do: [ :t | 
   256     anotherState transitions do: [ :t | 
   180         (transitions contains: [ :e | e equals: t]) ifFalse: [ ^ false ]
   257         (transitions contains: [ :e | e equals: t]) ifFalse: [ ^ false ]
   182     
   259     
   183     ^ true
   260     ^ true
   184 !
   261 !
   185 
   262 
   186 hash
   263 hash
   187     ^ retval hash bitXor: (
   264     "JK: Size is not the best option here, but it one gets infinite loops otherwise"
   188         priority hash bitXor: (
   265     ^ infos hash bitXor: transitions size hash
   189         multivalue hash bitXor:
       
   190         "JK: Size is not the best option here, but it one gets infinite loops otherwise"
       
   191         transitions size hash)).
       
   192 !
   266 !
   193 
   267 
   194 isIsomorphicTo: anotherState resolvedSet: set
   268 isIsomorphicTo: anotherState resolvedSet: set
       
   269     self error: 'depracated?'.
   195     (self == anotherState) ifTrue: [ ^ true ].
   270     (self == anotherState) ifTrue: [ ^ true ].
   196     
   271     
   197     (name == anotherState name) ifFalse: [ ^ false ].
   272 "	(name == anotherState name) ifFalse: [ ^ false ].
   198     (priority == anotherState priority) ifFalse: [ ^ false ].
   273     (priority == anotherState priority) ifFalse: [ ^ false ].
   199     (multivalue == anotherState multivalue) ifFalse: [ ^ false ].
   274     (multivalue == anotherState isMultivalue) ifFalse: [ ^ false ].
   200     (retval = anotherState retval) ifFalse: [ ^ false ].
   275     (retval = anotherState retval) ifFalse: [ ^ false ].
   201     (final = anotherState final) ifFalse: [ ^ false ].
   276     (final = anotherState final) ifFalse: [ ^ false ].
   202 
   277 "
   203     (transitions size = anotherState transitions size) ifFalse: [ ^ false ].
   278     (transitions size = anotherState transitions size) ifFalse: [ ^ false ].
   204     transitions do: [:t |
   279     transitions do: [:t |
   205         (anotherState transitions contains: [:at | t isIsomorphicto: at]) ifFalse: [ ^ false ].
   280         (anotherState transitions contains: [:at | t isIsomorphicto: at]) ifFalse: [ ^ false ].
   206     ].
   281     ].
   207     
   282     
   209 ! !
   284 ! !
   210 
   285 
   211 !PEGFsaState methodsFor:'copying'!
   286 !PEGFsaState methodsFor:'copying'!
   212 
   287 
   213 postCopy
   288 postCopy
       
   289     | newInfos |
   214     super postCopy.
   290     super postCopy.
   215     transitions := (transitions collect: [ :t | t copy ]).
   291     transitions := (transitions collect: [ :t | t copy ]).
   216     retval := retval copy.
   292     
       
   293     newInfos := IdentityDictionary new.
       
   294     infos keysAndValuesDo: [ :key :value | 
       
   295         newInfos at: key put: value copy
       
   296     ].
       
   297 
       
   298     infos := newInfos.
   217 ! !
   299 ! !
   218 
   300 
   219 !PEGFsaState methodsFor:'gt'!
   301 !PEGFsaState methodsFor:'gt'!
   220 
   302 
   221 gtName
   303 gtName
   222     | gtName |
   304     |  gtStream |
   223     gtName := name.
   305     gtStream := '' writeStream.
   224 
   306     self printNameOn: gtStream.
       
   307     
   225     self hasPriority ifTrue: [ 
   308     self hasPriority ifTrue: [ 
   226         gtName := gtName asString, ',', self priority asString.
   309         self retvalsAndInfosDo: [ :retval :info | 
   227     ].
   310             gtStream nextPut: (Character codePoint: 13). 
   228 
   311             gtStream nextPutAll: retval asString.
   229     ^ gtName
   312             gtStream nextPutAll: '->'.
       
   313             info printOn: gtStream. 
       
   314         ].
       
   315     ].
       
   316 
       
   317     ^ gtStream contents trim
       
   318 ! !
       
   319 
       
   320 !PEGFsaState methodsFor:'ids'!
       
   321 
       
   322 defaultName
       
   323     ^ #state
       
   324 !
       
   325 
       
   326 hasName
       
   327     ^ name isNil not
       
   328 !
       
   329 
       
   330 prefix
       
   331     ^ nil
       
   332 !
       
   333 
       
   334 suffix
       
   335     ^ nil
       
   336 ! !
       
   337 
       
   338 !PEGFsaState methodsFor:'infos'!
       
   339 
       
   340 info
       
   341     self assert: infos size = 1.
       
   342     ^ infos anyOne
   230 ! !
   343 ! !
   231 
   344 
   232 !PEGFsaState methodsFor:'initialization'!
   345 !PEGFsaState methodsFor:'initialization'!
   233 
   346 
   234 initialize
   347 initialize
   235     super initialize.
   348     super initialize.
   236     
   349     
   237     transitions := OrderedCollection new.
   350     transitions := OrderedCollection new.
   238     multivalue := false.
   351 
       
   352     infos := IdentityDictionary new.
       
   353     infos at: nil put: PEGFsaStateInfo new.
   239 ! !
   354 ! !
   240 
   355 
   241 !PEGFsaState methodsFor:'modifications'!
   356 !PEGFsaState methodsFor:'modifications'!
       
   357 
       
   358 addInfo: info for: retval
       
   359     infos removeKey: nil ifAbsent: [ "not a big deal" ].
       
   360     infos at: retval put: info
       
   361 !
   242 
   362 
   243 addTransition: t
   363 addTransition: t
   244     self assert: (transitions identityIncludes: t) not.
   364     self assert: (transitions identityIncludes: t) not.
   245     transitions add: t
   365     transitions add: t
   246 !
   366 !
   247 
   367 
   248 decreasePriority
   368 decreasePriority
       
   369     self decreasePriorityBy: 1.
       
   370 !
       
   371 
       
   372 decreasePriorityBy: value
   249     (self isFinal and: [ self hasPriority not ]) ifTrue: [ 
   373     (self isFinal and: [ self hasPriority not ]) ifTrue: [ 
   250         priority := 0.
   374         self error: 'Final States Should have priority!!'
   251     ].
   375     ].
   252     priority isNil ifFalse: [ 
   376 
   253         priority := priority - 1
   377     self priority isNil ifFalse: [ 
       
   378         self priority: self priority - value
       
   379     ]
       
   380 !
       
   381 
       
   382 join: state
       
   383     ^ self join: state joinDictionary: Dictionary new
       
   384 !
       
   385 
       
   386 mergeInfo: state into: newState
       
   387     self info merge: state info into: newState info.
       
   388 !
       
   389 
       
   390 mergeTransitions
       
   391     | toRemove |
       
   392     toRemove := OrderedCollection new.
       
   393     self transitionPairs do:[ :pair | 
       
   394         (pair first destination = pair second destination) ifTrue: [ 
       
   395             (pair first isPredicateTransition not and: [pair second isPredicateTransition not]) ifTrue: [ 
       
   396                 pair first mergeWith: pair second.
       
   397                 toRemove add: pair second.
       
   398             ]
       
   399         ]
       
   400     ].
       
   401 
       
   402     toRemove do: [ :t |
       
   403         self removeTransition: t
   254     ]
   404     ]
   255 !
   405 !
   256 
   406 
   257 removeTransition: t
   407 removeTransition: t
   258     self assert: (transitions includes: t).
   408     self assert: (transitions includes: t).
   259     transitions remove: t
   409     transitions remove: t
       
   410 ! !
       
   411 
       
   412 !PEGFsaState methodsFor:'modifications - determinization'!
       
   413 
       
   414 determinize
       
   415     ^ PEGFsaAbstractDeterminizator new determinizeState: self
       
   416 !
       
   417 
       
   418 join: state joinDictionary: dictionary
       
   419     | pair newState |
       
   420     self error: 'deprecated'.
       
   421     pair := PEGFsaPair with: self with: state.
       
   422     (dictionary includesKey: pair) ifTrue: [ ^ dictionary at: pair ].
       
   423     
       
   424     newState := PEGFsaState new.
       
   425     
       
   426     dictionary at: pair put: newState.
       
   427 
       
   428     self joinRetval: state into: newState.
       
   429     self joinName: state into: newState.
       
   430     self joinTransitions: state into: newState.	
       
   431 
       
   432     newState determinize: dictionary.
       
   433     
       
   434     ^ dictionary at: pair put: newState
       
   435 !
       
   436 
       
   437 joinInfo: state into: newState
       
   438     self info join: state info into: newState info.
       
   439 !
       
   440 
       
   441 joinName: state into: newState
       
   442     newState name: self name asString, '_', state name asString.
       
   443 !
       
   444 
       
   445 joinRetval: state into: newState
       
   446     "Different retvals cannot merge their info"
       
   447     (self hasDifferentRetvalThan: state) ifTrue: [  
       
   448         newState addInfo: self info for: self retval.
       
   449         newState addInfo: state info for: state retval.
       
   450         ^ self
       
   451     ].
       
   452 
       
   453 
       
   454     (self hasHigherPriorityThan: state) ifTrue: [ 
       
   455         newState retval: self retval	
       
   456     ].
       
   457 
       
   458     (state hasHigherPriorityThan: self) ifTrue: [ 
       
   459         newState retval: state retval	
       
   460     ].
       
   461 
       
   462     (state priority == self priority) ifTrue: [ 
       
   463         self hasRetval ifTrue: [newState retval: self retval].
       
   464         state hasRetval ifTrue: [newState retval: state retval].
       
   465     ].
       
   466 
       
   467     self joinInfo: state into: newState.
       
   468 !
       
   469 
       
   470 joinTransitions: state into: newState
       
   471     newState isMultivalue ifTrue: [ 
       
   472         newState transitions addAll: (self transitions collect: #copy).
       
   473         newState transitions addAll: (state transitions collect: #copy).
       
   474         ^ self
       
   475     ].
       
   476     
       
   477     newState hasPriority ifFalse: [ 
       
   478         newState transitions addAll: (self transitions collect: #copy).
       
   479         newState transitions addAll: (state transitions collect: #copy).
       
   480         ^ self
       
   481     ].
       
   482 
       
   483     
       
   484     self assert: newState hasPriority.
       
   485     
       
   486     "This is a part when low priority branches are cut"
       
   487     (self priority == newState priority) ifTrue: [ 
       
   488         newState transitions addAll: (self transitions collect: #copy).
       
   489     ] ifFalse: [
       
   490         newState transitions addAll: (self transitions select: [ :t | t priority > newState priority ] thenCollect: #copy)
       
   491     ].
       
   492 
       
   493     (state priority == newState priority) ifTrue: [ 
       
   494         newState transitions addAll: (state transitions collect: #copy).
       
   495     ] ifFalse: [
       
   496         newState transitions addAll: (state transitions select: [ :t | t priority > newState priority ] thenCollect: #copy)
       
   497     ].
   260 ! !
   498 ! !
   261 
   499 
   262 !PEGFsaState methodsFor:'printing'!
   500 !PEGFsaState methodsFor:'printing'!
   263 
   501 
   264 printNameOn: aStream
   502 printNameOn: aStream
   271     super printOn: aStream.
   509     super printOn: aStream.
   272     aStream nextPut: $(.
   510     aStream nextPut: $(.
   273     self printNameOn: aStream.
   511     self printNameOn: aStream.
   274     aStream nextPut: Character space.
   512     aStream nextPut: Character space.
   275     aStream nextPutAll: self identityHash asString.
   513     aStream nextPutAll: self identityHash asString.
   276     self isFinal ifTrue: [ 
   514 
   277         aStream nextPutAll: ' FINAL'.
   515     self retvalsAndInfosDo: [ :retval :info | 
   278     ].
   516         retval printOn: aStream.
   279     aStream nextPut: (Character codePoint: 32).
   517         aStream nextPutAll: '->'.
   280     aStream nextPutAll: priority asString.
   518         info printOn: aStream.
       
   519         aStream nextPutAll: ';'.
       
   520     ].
       
   521 
   281     aStream nextPut: $)
   522     aStream nextPut: $)
   282 ! !
   523 ! !
   283 
   524 
   284 !PEGFsaState methodsFor:'testing'!
   525 !PEGFsaState methodsFor:'testing'!
   285 
   526 
   286 canHavePPCId
   527 canHavePPCId
   287     ^ true
   528     ^ true
   288 !
   529 !
   289 
   530 
       
   531 hasDifferentRetvalThan: anotherState
       
   532     "returns true only if both hav retval and both retvals are different"
       
   533     self hasRetval ifFalse: [ ^ false ].	
       
   534     anotherState hasRetval ifFalse: [ ^ false ].
       
   535 
       
   536     "`retval value` is called in order to obtain retval from FsaFailure (if any)"
       
   537     ^ (self retval value == anotherState retval value) not
       
   538 !
       
   539 
   290 hasEqualPriorityTo: state
   540 hasEqualPriorityTo: state
   291     "nil - nil"
   541     ^ self info hasEqualPriorityTo: state info
   292     (self hasPriority not and: [state hasPriority not]) ifTrue: [ ^ true ].
       
   293     
       
   294     "nil - priority"
       
   295     (self hasPriority) ifFalse: [ ^ false ].
       
   296     
       
   297     "priority - nil"
       
   298     state hasPriority ifFalse: [ ^ false ].
       
   299     
       
   300     "priority - priority"
       
   301     ^ self priority = state priority 
       
   302 !
   542 !
   303 
   543 
   304 hasHigherPriorityThan: state
   544 hasHigherPriorityThan: state
   305     "nil - nil"
   545     ^ self info hasHigherPriorityThan: state info
   306     (self hasPriority not and: [state hasPriority not]) ifTrue: [ ^ true ].
       
   307     
       
   308     "nil - priority"
       
   309     (self hasPriority) ifFalse: [ ^ false ].
       
   310     
       
   311     "priority - nil"
       
   312     state hasPriority ifFalse: [ ^ true ].
       
   313     
       
   314     "priority - priority"
       
   315     ^ self priority > state priority 
       
   316 !
   546 !
   317 
   547 
   318 hasPriority
   548 hasPriority
   319     ^ priority isNil not
   549     ^ self stateInfos anySatisfy: [ :info | info hasPriority ]
       
   550 !
       
   551 
       
   552 hasRetval
       
   553     ^ self retval isNil not
       
   554 !
       
   555 
       
   556 hasZeroPriorityOnly
       
   557     ^ self stateInfos allSatisfy: [ :si | si hasPriority not or: [ si priority == 0 ] ].
   320 !
   558 !
   321 
   559 
   322 isFailure
   560 isFailure
       
   561     self error: 'Obsolete?'.
       
   562     "
   323     ^ self isFinal and: [ retval class == PEGFsaFailure ]
   563     ^ self isFinal and: [ retval class == PEGFsaFailure ]
       
   564     "
       
   565 
       
   566     "Modified: / 17-08-2015 / 12:01:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
   324 !
   567 !
   325 
   568 
   326 isFinal
   569 isFinal
   327     final isNil ifTrue: [ ^ false ].
   570     ^ self stateInfos anySatisfy: [ :info | info isFinal ].
   328     
   571 !
   329     final ifTrue: [
   572 
   330 "		self assert: self hasPriority. "
   573 isMultivalue
   331         ^ true
   574     ^ infos size > 1
   332     ].
   575 !
   333 
   576 
       
   577 isStub
   334     ^ false
   578     ^ false
   335 !
       
   336 
       
   337 isMultivalue
       
   338     ^ multivalue
       
   339 ! !
   579 ! !
   340 
   580 
   341 !PEGFsaState methodsFor:'transformation'!
   581 !PEGFsaState methodsFor:'transformation'!
   342 
       
   343 determinize
       
   344     ^ self determinize: Dictionary new.
       
   345 !
       
   346 
       
   347 determinize: dictionary
       
   348     self transitionPairs do: [ :pair |
       
   349         self assert: (pair first destination = pair second destination) not.
       
   350         (pair first overlapsWith: pair second) ifTrue: [ 
       
   351             self determinizeOverlap: pair first second: pair second joinDictionary: dictionary
       
   352         ]
       
   353     ].
       
   354 !
       
   355 
       
   356 determinizeOverlap: t1 second: t2 joinDictionary: dictionary
       
   357     | pair t1Prime t2Prime tIntersection |
       
   358     pair := PEGFsaPair with: t1 with: t2.
       
   359 
       
   360     (dictionary includes: pair) ifTrue: [ self error: 'should not happen'.].
       
   361     dictionary at: pair put: nil.
       
   362     
       
   363     tIntersection := t1 join: t2 joinDictionary: dictionary.
       
   364     t1Prime := PEGFsaTransition new
       
   365                     destination: t1 destination;
       
   366                     characterSet: (t1 complement: t2);
       
   367                     yourself.
       
   368     t2Prime := PEGFsaTransition new
       
   369                     destination: t2 destination;
       
   370                     characterSet: (t2 complement: t1);
       
   371                     yourself.					
       
   372                                     
       
   373                                 
       
   374     self removeTransition: t1.
       
   375     self removeTransition: t2.
       
   376     
       
   377     tIntersection isEpsilon ifFalse: [ self addTransition: tIntersection  ].
       
   378     t1Prime isEpsilon ifFalse: [ self addTransition: t1Prime ].
       
   379     t2Prime isEpsilon ifFalse: [ self addTransition: t2Prime ].
       
   380     
       
   381     dictionary at: pair put: (Array 
       
   382                                         with: tIntersection 
       
   383                                         with: t1Prime
       
   384                                         with: t2Prime
       
   385                                     )
       
   386 !
       
   387 
       
   388 join: state
       
   389     ^ self join: state joinDictionary: Dictionary new
       
   390 !
       
   391 
       
   392 join: state joinDictionary: dictionary
       
   393     | pair newState |
       
   394     pair := PEGFsaPair with: self with: state.
       
   395     (dictionary includesKey: pair) ifTrue: [ ^ dictionary at: pair ].
       
   396     
       
   397     newState := PEGFsaState new.
       
   398     
       
   399     dictionary at: pair put: newState.
       
   400     
       
   401     self joinFinal: state newState: newState.
       
   402     self joinPriority: state newState: newState.
       
   403     self joinRetval: state newState: newState.
       
   404     self joinName: state newState: newState.
       
   405     
       
   406     newState transitions addAll: (self transitions collect: #copy).
       
   407     newState transitions addAll: (state transitions collect: #copy).
       
   408     newState determinize: dictionary.
       
   409     
       
   410     ^ dictionary at: pair put: newState
       
   411 !
       
   412 
   582 
   413 joinFinal: state newState: newState
   583 joinFinal: state newState: newState
   414     (self hasEqualPriorityTo: state) ifTrue: [ 
   584     (self hasEqualPriorityTo: state) ifTrue: [ 
   415         ^ newState final: (self isFinal or: [ state isFinal ]).
   585         ^ newState final: (self isFinal or: [ state isFinal ]).
   416     ].
   586     ].