compiler/PEGFsa.st
changeset 516 3b81c9e53352
parent 504 0fb1f0799fc1
parent 515 b5316ef15274
child 525 751532c8f3db
equal deleted inserted replaced
514:46dd1237b20a 516:3b81c9e53352
    33     backTransitions := self backTransitions.
    33     backTransitions := self backTransitions.
    34     ^ self allTransitions reject: [ :t | backTransitions includes: t ]
    34     ^ self allTransitions reject: [ :t | backTransitions includes: t ]
    35 !
    35 !
    36 
    36 
    37 minPriority
    37 minPriority
    38     "this is the worst estimate"
    38     | priority |
    39     ^ (self states size) negated
    39 "	defaultPriority := self states size negated.
       
    40     self finalStates isEmpty ifTrue: [ ^ defaultPriority ].
       
    41     
       
    42     ^ (self finalStates collect: [ :e | e priorityIfNone: defaultPriority  ]) min
       
    43 "
       
    44     priority := -1.
       
    45     self allTransitions do: [ :t | t isEpsilon ifTrue: [ priority := priority + t priority ] ].
       
    46     ^ priority
    40 !
    47 !
    41 
    48 
    42 name
    49 name
    43     ^ name 
    50     ^ name 
    44 !
    51 !
    46 name: anObject
    53 name: anObject
    47     
    54     
    48     name := anObject
    55     name := anObject
    49 !
    56 !
    50 
    57 
    51 prefix
    58 retvals
    52     ^ 'fsa_'
    59     ^ (self finalStates flatCollect: [ :e | e retvals collect: #value ]) asIdentitySet
    53 !
    60 !
    54 
    61 
    55 startState
    62 startState
       
    63     self assert: (states includes: startState).
    56     ^ startState
    64     ^ startState
    57 !
    65 !
    58 
    66 
    59 stateNamed: name
    67 stateNamed: name
    60     ^ states detect: [ :e | e name = name ]
    68     ^ states detect: [ :e | e name = name ]
    62 
    70 
    63 states
    71 states
    64     ^ states
    72     ^ states
    65 !
    73 !
    66 
    74 
    67 suffix
    75 states: whatever
    68     ^ ''
    76     states := whatever
    69 !
    77 !
    70 
    78 
    71 transitionFrom: from to: to
    79 transitionFrom: from to: to
    72     ^ from transitions detect: [ :t | t destination = to ]
    80     ^ from transitions detect: [ :t | t destination = to ]
    73 !
    81 !
   170     ]
   178     ]
   171     
   179     
   172 !
   180 !
   173 
   181 
   174 finalStates
   182 finalStates
   175     ^ self reachableStates select: [ :s | s isFinal ]
   183     ^ self states select: [ :s | s isFinal ]
       
   184 !
       
   185 
       
   186 hasDistinctRetvals
       
   187     | finalStates retvals |
       
   188     finalStates := self finalStates.
       
   189 
       
   190     (finalStates anySatisfy: [ :s | s isMultivalue  ]) ifTrue: [ ^ false ].
       
   191     retvals := finalStates collect: [:s | s retval].
       
   192 
       
   193         
       
   194     (finalStates size == 1) ifTrue: [ ^ true ].
       
   195 
       
   196 
       
   197     (retvals asSet size == 1) ifTrue: [ ^ true ].
       
   198     "final states leads only to final states with the same retval"
       
   199     (finalStates allSatisfy: [ :s | 
       
   200         (self statesReachableFrom: s) allSatisfy: [ :rs | rs retval value isNil or: [ rs retval value == s retval value ] ]
       
   201     ]) ifTrue: [ ^ true ].
       
   202     
       
   203     ^ false
   176 !
   204 !
   177 
   205 
   178 is: state furtherThan: anotherState
   206 is: state furtherThan: anotherState
   179 
   207 
   180     ^ (distances at: state) >= (distances at: anotherState)
   208     ^ (distances at: state) >= (distances at: anotherState)
   181 !
   209 !
   182 
   210 
   183 isBackTransition: t
   211 isBackTransition: t
   184     ^ self backTransitions includes: t
   212     ^ self backTransitions includes: t
       
   213 !
       
   214 
       
   215 isWithoutPriorities
       
   216     ^ self states allSatisfy: [ :s | 
       
   217         s hasPriority not or: [ 
       
   218             s stateInfos allSatisfy: [ :i | i priority == 0 ]
       
   219         ] 
       
   220     ].
   185 !
   221 !
   186 
   222 
   187 joinPoints
   223 joinPoints
   188     ^ self joinTransitions collect: [ :t | t destination ]
   224     ^ self joinTransitions collect: [ :t | t destination ]
   189 !
   225 !
   220 !
   256 !
   221 
   257 
   222 statePairs
   258 statePairs
   223     |  pairs ordered |
   259     |  pairs ordered |
   224     pairs := OrderedCollection new.
   260     pairs := OrderedCollection new.
   225     ordered := self topologicalOrder.
   261     ordered := self states asOrderedCollection.
   226     1 to: (ordered size - 1) do: [ :index1 |
   262     1 to: (ordered size - 1) do: [ :index1 |
   227         (index1 + 1) to: ordered size do: [ :index2 |
   263         (index1 + 1) to: ordered size do: [ :index2 |
   228             pairs add: (PEGFsaPair with: (ordered at: index1) with: (ordered at: index2))
   264             pairs add: (PEGFsaPair with: (ordered at: index1) with: (ordered at: index2))
   229  		]
   265  		]
   230     ].
   266     ].
   264 
   300 
   265 !PEGFsa methodsFor:'comparing'!
   301 !PEGFsa methodsFor:'comparing'!
   266 
   302 
   267 = anotherFsa
   303 = anotherFsa
   268     "
   304     "
   269         Please note what the compare does. IMO nothing useful for no.
   305         Please note what the compare does. IMO nothing useful for now.
   270         
   306         
   271         For comparing if two FSA's are equivalent, use isIsomorphicTo:
   307         For comparing if two FSA's are equivalent, use isIsomorphicTo:
   272     "
   308     "
   273 
   309 
   274     (self == anotherFsa)  ifTrue: [ ^ true ].
   310     (self == anotherFsa)  ifTrue: [ ^ true ].
   334 ! !
   370 ! !
   335 
   371 
   336 !PEGFsa methodsFor:'gt'!
   372 !PEGFsa methodsFor:'gt'!
   337 
   373 
   338 gtGraphViewIn: composite
   374 gtGraphViewIn: composite
   339     <gtInspectorPresentationOrder: 41>
   375     <gtInspectorPresentationOrder: 0>
   340     composite roassal2
   376     composite roassal2
   341         title: 'Graph'; 
   377         title: 'Graph'; 
   342         initializeView: [ RTMondrian new ];
   378         initializeView: [ RTMondrian new ];
   343         painting: [ :view |
   379         painting: [ :view |
   344             self viewGraphOn: view.	
   380             self viewGraphOn: view.	
   384     b layout layout horizontalGap: 30.
   420     b layout layout horizontalGap: 30.
   385 
   421 
   386     ^ b
   422     ^ b
   387 ! !
   423 ! !
   388 
   424 
       
   425 !PEGFsa methodsFor:'ids'!
       
   426 
       
   427 defaultName
       
   428     ^ #fsa
       
   429 !
       
   430 
       
   431 hasName
       
   432     ^ name isNil not
       
   433 !
       
   434 
       
   435 prefix
       
   436     ^ nil
       
   437 !
       
   438 
       
   439 suffix
       
   440     ^ nil
       
   441 ! !
       
   442 
   389 !PEGFsa methodsFor:'initialization'!
   443 !PEGFsa methodsFor:'initialization'!
   390 
   444 
   391 initialize
   445 initialize
   392     states := IdentitySet new.
   446     states := IdentitySet new.
   393 ! !
   447 ! !
   398     self assert: (states includes: state) not.
   452     self assert: (states includes: state) not.
   399     states add: state
   453     states add: state
   400 !
   454 !
   401 
   455 
   402 addTransitionFrom: fromState to: toState 
   456 addTransitionFrom: fromState to: toState 
   403     ^ self addTransitionFrom: fromState to: toState priority: 0 
   457     | transition |
       
   458     self assert: (states includes: fromState).
       
   459     self assert: (states includes: toState).
       
   460     
       
   461     transition := PEGFsaEpsilonTransition new 
       
   462         destination: toState;
       
   463         priority: 0;
       
   464         yourself.
       
   465         
       
   466     fromState addTransition: transition.
   404 !
   467 !
   405 
   468 
   406 addTransitionFrom: fromState to: toState on: character
   469 addTransitionFrom: fromState to: toState on: character
   407     self addTransitionFrom: fromState to: toState on: character priority: 0
   470     self addTransitionFrom: fromState to: toState on: character priority: 0
   408 !
   471 !
   409 
   472 
   410 addTransitionFrom: fromState to: toState on: character priority: priority
   473 addTransitionFrom: fromState to: toState on: character priority: priority
   411     | transition |
   474     | transition |
   412     transition := PEGFsaTransition new 
   475     transition := PEGFsaCharacterTransition new 
   413         addCharacter: character;
   476         addCharacter: character;
   414         destination: toState;
   477         destination: toState;
   415         priority: priority;
   478         priority: priority;
   416         yourself.
   479         yourself.
   417         
   480         
   422     self addTransitionFrom: fromState to: toState onCharacterSet: characterSet priority: 0
   485     self addTransitionFrom: fromState to: toState onCharacterSet: characterSet priority: 0
   423 !
   486 !
   424 
   487 
   425 addTransitionFrom: fromState to: toState onCharacterSet: characterSet priority: priority
   488 addTransitionFrom: fromState to: toState onCharacterSet: characterSet priority: priority
   426     | transition |
   489     | transition |
   427     transition := PEGFsaTransition new 
   490     transition := PEGFsaCharacterTransition new 
   428         characterSet: characterSet;
   491         characterSet: characterSet;
   429         destination: toState;
   492         destination: toState;
   430         priority: priority;
   493         priority: priority;
   431         yourself.
   494         yourself.
   432 
   495 
   433     fromState addTransition: transition
   496     fromState addTransition: transition
   434 !
   497 !
   435 
   498 
       
   499 addTransitionFrom: fromState to: toState onPredicate: block
       
   500     self addTransitionFrom: fromState to: toState onPredicate: block priority: 0
       
   501 !
       
   502 
       
   503 addTransitionFrom: fromState to: toState onPredicate: block priority: priority
       
   504     | transition |
       
   505     transition := PEGFsaPredicateTransition new 
       
   506         predicate: block;
       
   507         destination: toState;
       
   508         priority: priority;
       
   509         yourself.
       
   510         
       
   511     fromState addTransition: transition
       
   512 !
       
   513 
   436 addTransitionFrom: fromState to: toState priority: priority
   514 addTransitionFrom: fromState to: toState priority: priority
   437     | transition |
   515     | transition |
       
   516     "should not use minus priority epsilons any more"
       
   517     self assert: (priority == 0).	
   438     self assert: (states includes: fromState).
   518     self assert: (states includes: fromState).
   439     self assert: (states includes: toState).
   519     self assert: (states includes: toState).
   440     
   520     
   441     transition := PEGFsaTransition new 
   521     transition := PEGFsaEpsilonTransition new 
   442         destination: toState;
   522         destination: toState;
   443         priority: priority;
   523         priority: priority;
   444         yourself.
   524         yourself.
   445         
   525         
   446     fromState addTransition: transition.
   526     fromState addTransition: transition.
   448 
   528 
   449 adopt: fsa
   529 adopt: fsa
   450     states addAll: fsa reachableStates.
   530     states addAll: fsa reachableStates.
   451 !
   531 !
   452 
   532 
       
   533 decreasePriority
       
   534     ^ self decreasePriorityBy: 1
       
   535 !
       
   536 
       
   537 decreasePriorityBy: value
       
   538     self states select: [ :s | s hasPriority ] thenDo: [ :s |
       
   539         s decreasePriorityBy: value.
       
   540     ].
       
   541 
       
   542     self allTransitions do: [ :t |
       
   543         t decreasePriorityBy: value
       
   544     ]
       
   545 !
       
   546 
   453 finalState: state
   547 finalState: state
   454     self assert: state isFinal not.
   548     self assert: state isFinal not.
   455     state final: true.
   549     state final: true.
       
   550     state priority: 0.
   456 !
   551 !
   457 
   552 
   458 fixFinalStatePriorities
   553 fixFinalStatePriorities
   459     self finalStates do: [ :s |
   554     self finalStates do: [ :s |
   460         s hasPriority ifFalse: [ s priority: 0 ]
   555         s hasPriority ifFalse: [ s priority: 0 ]
   461     ]
   556     ]
   462 !
   557 !
   463 
   558 
       
   559 minimize
       
   560     ^ PEGFsaMinimizator new minimize: self
       
   561 !
       
   562 
       
   563 removePriorities
       
   564     self states select: [ :s| s hasPriority ] thenDo: [ :s |
       
   565         s priority: 0
       
   566     ].
       
   567 
       
   568     self allTransitions do: [ :t |
       
   569         t priority: 0
       
   570     ]
       
   571 !
       
   572 
   464 removeState: state
   573 removeState: state
   465     self assert: (states includes: state).
   574     self assert: (states includes: state).
   466     states remove: state.
   575     states remove: state.
   467 !
   576 !
   468 
   577 
   469 replace: state with: anotherState
   578 replace: state with: anotherState
   470     | transitions  |
   579     | transitions  |
   471     self assert: (state class == PEGFsaState).
   580     self assert: (state isKindOf: PEGFsaState).
   472     self assert: (anotherState class == PEGFsaState).
   581     self assert: (anotherState isKindOf: PEGFsaState).
   473     
   582     
   474     transitions := self allTransitions.
   583     transitions := self allTransitions.
   475 
   584 
   476     transitions do: [ :t |
   585     transitions do: [ :t |
   477         (t destination == state) ifTrue: [ 
   586         (t destination == state) ifTrue: [ 
   478             t destination: anotherState.
   587             t destination: anotherState.
   479         ]
   588         ]
   480     ].
   589     ].
   481     states := startState reachableStates.	
   590 
       
   591     state == startState ifTrue: [ startState := anotherState ].
       
   592     states remove: state.
       
   593     states add: anotherState.
       
   594 !
       
   595 
       
   596 retval: returnValue
       
   597     self finalStates do: [ :s |
       
   598         self assert: s retval isNil.
       
   599         s retval: returnValue
       
   600     ]
   482 !
   601 !
   483 
   602 
   484 startState: state
   603 startState: state
   485     self assert: (states includes: state).
   604     self assert: (states includes: state).
   486     
   605     
   487     startState := state
   606     startState := state
       
   607 ! !
       
   608 
       
   609 !PEGFsa methodsFor:'modifications - determinization'!
       
   610 
       
   611 determinize
       
   612     ^ PEGFsaSequenceDeterminizator new determinize: self.
       
   613 !
       
   614 
       
   615 determinize: joinDictionary
       
   616     self error: 'deprecated'.
       
   617     
       
   618     self removeEpsilons.
       
   619     self removeUnreachableStates.
       
   620     self removeLowPriorityTransitions.
       
   621     self mergeTransitions.
       
   622     
       
   623     
       
   624     states := self topologicalOrder asOrderedCollection.
       
   625     
       
   626     states do: [ :state |
       
   627         state determinize: joinDictionary.
       
   628     ].
       
   629     
       
   630     states	 := startState reachableStates.
       
   631 
       
   632     self removeUnreachableStates.
       
   633     self removeLowPriorityTransitions.
       
   634     self mergeTransitions.
       
   635     
       
   636 !
       
   637 
       
   638 determinizeChoice
       
   639     ^ PEGFsaChoiceDeterminizator new determinize: self.
       
   640 !
       
   641 
       
   642 determinizeStandard
       
   643     ^ PEGFsaDeterminizator new determinize: self.
       
   644 ! !
       
   645 
       
   646 !PEGFsa methodsFor:'modifications - epsilons'!
       
   647 
       
   648 removeEpsilonTransition: transition source: state
       
   649     ^ self removeEpsilonTransition: transition source: state openSet: IdentitySet new
       
   650 !
       
   651 
       
   652 removeEpsilonTransition: transition source: source openSet: openSet
       
   653     | destination |
       
   654     (openSet includes: transition) ifTrue: [ self error: 'loop in epsilons?!!' ].
       
   655     openSet add: transition.
       
   656     
       
   657     destination := transition destination.
       
   658     
       
   659     "First Remove Recursively"
       
   660     ((self transitionsFor: destination ) select: [ :t | t isEpsilon  ]) do: [ :t |
       
   661         self removeEpsilonTransition: t source: destination openSet: openSet
       
   662     ].
       
   663 
       
   664     self assert: transition isEpsilon.
       
   665     self assert: transition priority = 0.
       
   666     
       
   667     (destination transitions) do: [ :t |
       
   668         source addTransition: (t copy)
       
   669     ].
       
   670 
       
   671     source mergeInfo: destination into: source.
       
   672 
       
   673     destination isFinal ifTrue: [ 
       
   674         source final: true.
       
   675         source retval: destination retval.
       
   676     ].
       
   677 
       
   678     source removeTransition: transition.
       
   679 !
       
   680 
       
   681 removeEpsilons
       
   682     "First, remove the negative values from epsilons"
       
   683     self removeNegativeEpsilons.
       
   684     
       
   685     states do: [ :state |
       
   686         self removeEpsilonsFor: state
       
   687     ]
       
   688 !
       
   689 
       
   690 removeEpsilonsFor: state
       
   691     (self transitionsFor: state) copy do: [ :t |
       
   692         (t isEpsilon and: [ t destination isStub not ]) ifTrue: [ 
       
   693             self removeEpsilonTransition: t source: state
       
   694         ]
       
   695     ]
       
   696 !
       
   697 
       
   698 removeNegativeEpsilonTransition: transition source: state
       
   699     ^ self removeNegativeEpsilonTransition: transition source: state openSet: IdentitySet new
       
   700 !
       
   701 
       
   702 removeNegativeEpsilonTransition: transition source: source openSet: openSet
       
   703     | destination |
       
   704     (openSet includes: transition) ifTrue: [ self error: 'loop in epsilons?!!' ].
       
   705     openSet add: transition.
       
   706     
       
   707     destination := transition destination.
       
   708     
       
   709     "First Remove Recursively"
       
   710     ((self transitionsFor: destination ) select: [ :t | t isEpsilon  ]) do: [ :t |
       
   711         self removeNegativeEpsilonTransition: t source: destination openSet: openSet
       
   712     ].
       
   713     
       
   714     "JK: Problem alert: if two different epsilons point to the same state,
       
   715         it will decreas the state priority two times!! I don't know how to handle
       
   716         this situation properly and I make sure during FSA generation that there
       
   717         are no two paths to one state (except for loops).
       
   718     "
       
   719     (self statesReachableFrom: destination) do: [ :s |
       
   720         s decreasePriorityBy: transition priority abs.
       
   721         s transitions do: [ :t | t decreasePriorityBy: transition priority abs  ]
       
   722     ].
       
   723 
       
   724     transition priority: 0.
       
   725 !
       
   726 
       
   727 removeNegativeEpsilons
       
   728     "
       
   729         This will remove only negative values from epsilons, the epsilons itself will not
       
   730         be removed!!
       
   731     "
       
   732     states do: [ :state |
       
   733         self removeNegativeEpsilonsFor: state
       
   734     ]
       
   735 !
       
   736 
       
   737 removeNegativeEpsilonsFor: state
       
   738     (self transitionsFor: state) copy do: [ :t |
       
   739         t isEpsilon ifTrue: [ 
       
   740             self removeNegativeEpsilonTransition: t source: state
       
   741         ]
       
   742     ]
   488 ! !
   743 ! !
   489 
   744 
   490 !PEGFsa methodsFor:'printing'!
   745 !PEGFsa methodsFor:'printing'!
   491 
   746 
   492 asString
   747 asString
   531 !
   786 !
   532 
   787 
   533 checkSanity
   788 checkSanity
   534     self checkConsistency.
   789     self checkConsistency.
   535     self checkTransitionsIdentity.
   790     self checkTransitionsIdentity.
       
   791     self checkTransitionsPriority.
   536     self checkFinalStatesPriorities.
   792     self checkFinalStatesPriorities.
   537 !
   793 !
   538 
   794 
   539 checkTransitionsIdentity
   795 checkTransitionsIdentity
   540     | bag set |
   796     | bag set |
   544     set := self allTransitions: set.	
   800     set := self allTransitions: set.	
   545     
   801     
   546     self assert: bag size == set size.
   802     self assert: bag size == set size.
   547 !
   803 !
   548 
   804 
       
   805 checkTransitionsPriority
       
   806     self finalStates do: [ :fs |
       
   807         fs isMultivalue ifFalse: [ 
       
   808             fs transitions allSatisfy: [ :t | fs priority >= t priority ]
       
   809         ]
       
   810     ]
       
   811 !
       
   812 
   549 isDeterministic
   813 isDeterministic
   550     self reachableStates do: [ :state |
   814     self reachableStates do: [ :state |
   551         state transitionPairs do: [ :pair | 
   815         state transitionPairs do: [ :pair | 
   552             ((pair first intersection: pair second) includes: true) ifTrue: [ 					
   816             ((pair first intersection: pair second) includes: true) ifTrue: [ 					
   553                 ^ false
   817                 ^ false
   575 ! !
   839 ! !
   576 
   840 
   577 !PEGFsa methodsFor:'transformations'!
   841 !PEGFsa methodsFor:'transformations'!
   578 
   842 
   579 compact
   843 compact
   580     self fixFinalStatePriorities.
   844     self error: 'deprecated?'
   581     self determinize.
       
   582     self minimize.
       
   583     
       
   584     self checkSanity.
       
   585 !
       
   586 
       
   587 determinize
       
   588     | joinDictionary |
       
   589     self removeEpsilons.
       
   590 
       
   591     self removeUnreachableStates.
       
   592     self removeLowPriorityTransitions.
       
   593     self mergeTransitions.
       
   594     
       
   595     joinDictionary := Dictionary new.
       
   596     self topologicalOrder do: [:state | state determinize: joinDictionary ].
       
   597     
       
   598     states	 := startState reachableStates.
       
   599 
       
   600     self removeUnreachableStates.
       
   601     self removeLowPriorityTransitions.
       
   602     self mergeTransitions.
       
   603     
       
   604 !
   845 !
   605 
   846 
   606 mergeTransitions
   847 mergeTransitions
   607     | toRemove |
   848     |  |
   608     self reachableStates do: [ :state |
   849     self reachableStates do: [ :state |
   609         toRemove := OrderedCollection new.
   850         state mergeTransitions.
   610         state transitionPairs do:[ :pair | 
       
   611             (pair first destination = pair second destination) ifTrue: [ 
       
   612                 pair first mergeWith: pair second.
       
   613                 toRemove add: pair second.
       
   614             ]
       
   615         ].
       
   616         toRemove do: [ :t |
       
   617             state removeTransition: t
       
   618         ]
       
   619     ]
       
   620 !
       
   621 
       
   622 minimize
       
   623     | pair |
       
   624     pair := self statePairs detect:  [ :p | p first equals: p second ] ifNone: [ nil ].
       
   625     [ pair isNil not ] whileTrue: [ 
       
   626         "Join priorities, because equivalency of priorities does not imply from the equeality of states"
       
   627         pair first joinPriority: pair second newState: pair first.
       
   628         pair first joinName: pair second newState: pair first.
       
   629         self replace: pair second with: pair first.
       
   630         self mergeTransitions.
       
   631         pair := self statePairs detect:  [ :p | p first equals: p second ] ifNone: [ nil ].
       
   632  	].
       
   633 !
       
   634 
       
   635 removeEpsilonTransition: transition source: state
       
   636     ^ self removeEpsilonTransition: transition source: state openSet: IdentitySet new
       
   637 !
       
   638 
       
   639 removeEpsilonTransition: transition source: source openSet: openSet
       
   640     | destination |
       
   641     (openSet includes: transition) ifTrue: [ self error: 'loop in epsilons?!!' ].
       
   642     openSet add: transition.
       
   643     
       
   644     destination := transition destination.
       
   645     
       
   646     "First Remove Recursively"
       
   647     ((self transitionsFor: destination ) select: [ :t | t isEpsilon  ]) do: [ :t |
       
   648         self removeEpsilonTransition: t source: destination openSet: openSet
       
   649     ].
       
   650     
       
   651     (transition priority abs) timesRepeat: [ 
       
   652         (self statesReachableFrom: destination) do: [ :s |
       
   653             s decreasePriority.
       
   654             s transitions do: [ :t | t decreasePriority  ]
       
   655         ]
       
   656     ].
       
   657 
       
   658     (destination transitions) do: [ :t |
       
   659         source addTransition: (t copy)
       
   660     ].
       
   661 
       
   662     destination hasPriority ifTrue: [ 
       
   663         source hasPriority ifTrue: [ 
       
   664             "self assert: source priority == destination priority"
       
   665             self flag: 'I am not 100% sure about this case'
       
   666         ].
       
   667         source priority: destination priority
       
   668     ].
       
   669 
       
   670     destination isFinal ifTrue: [ 
       
   671         source final: true.
       
   672         source retval: destination retval.
       
   673     ].
       
   674 
       
   675     source removeTransition: transition.
       
   676 !
       
   677 
       
   678 removeEpsilons
       
   679     states do: [ :state |
       
   680         self removeEpsilonsFor: state
       
   681     ]
       
   682 !
       
   683 
       
   684 removeEpsilonsFor: state
       
   685     (self transitionsFor: state) copy do: [ :t |
       
   686         t isEpsilon ifTrue: [ 
       
   687             self removeEpsilonTransition: t source: state
       
   688         ]
       
   689     ]
   851     ]
   690 !
   852 !
   691 
   853 
   692 removeLowPriorityTransitions
   854 removeLowPriorityTransitions
   693     states do: [ :state |
   855     states do: [ :state |
   694         self removeLowPriorityTransitionsFor: state
   856         self removeLowPriorityTransitionsFor: state
   695     ]
   857     ]
   696 !
   858 !
   697 
   859 
   698 removeLowPriorityTransitionsFor: state
   860 removeLowPriorityTransitionsFor: state
       
   861     | transitions |
   699     state hasPriority ifFalse: [ ^ self ].
   862     state hasPriority ifFalse: [ ^ self ].
   700     state isFinal ifFalse: [ ^ self ].
   863     state isFinal ifFalse: [ ^ self ].
   701     
   864     "TODO JK: I can probably cut some transitions from multivalu as well"
   702     state transitions do: [ :t |
   865     state isMultivalue ifTrue: [ ^ self ].
       
   866 
       
   867     transitions := state transitions copy.
       
   868     transitions do: [ :t |
   703         (t priority < state priority) ifTrue: [ 
   869         (t priority < state priority) ifTrue: [ 
   704             state removeTransition: t
   870             state removeTransition: t
   705         ]
   871         ]
   706     ]
   872     ]
   707 !
   873 !