compiler/PEGFsaTransition.st
changeset 502 1e45d3c96ec5
child 504 0fb1f0799fc1
child 515 b5316ef15274
equal deleted inserted replaced
464:f6d77fee9811 502:1e45d3c96ec5
       
     1 "{ Package: 'stx:goodies/petitparser/compiler' }"
       
     2 
       
     3 "{ NameSpace: Smalltalk }"
       
     4 
       
     5 Object subclass:#PEGFsaTransition
       
     6 	instanceVariableNames:'characterSet destination priority'
       
     7 	classVariableNames:''
       
     8 	poolDictionaries:''
       
     9 	category:'PetitCompiler-FSA'
       
    10 !
       
    11 
       
    12 !PEGFsaTransition methodsFor:'accessing'!
       
    13 
       
    14 characterSet
       
    15     ^ characterSet
       
    16 !
       
    17 
       
    18 characterSet: anObject
       
    19     characterSet := anObject
       
    20 !
       
    21 
       
    22 destination
       
    23     ^ destination
       
    24 !
       
    25 
       
    26 destination: anObject
       
    27     destination := anObject
       
    28 !
       
    29 
       
    30 priority
       
    31     ^ priority
       
    32 !
       
    33 
       
    34 priority: anObject
       
    35     priority := anObject
       
    36 ! !
       
    37 
       
    38 !PEGFsaTransition methodsFor:'comparing'!
       
    39 
       
    40 = anotherTransition
       
    41     "
       
    42     Please note the identity comparison on destination
       
    43     If you use equality instead of identy, you will get infinite loop.
       
    44 
       
    45     So much for comparison by now :)	
       
    46     "
       
    47     (self == anotherTransition) ifTrue: [ ^ true ].
       
    48     (self class == anotherTransition class) ifFalse: [ ^ false ].
       
    49 
       
    50     (destination == anotherTransition destination) ifFalse: [ ^ false ].
       
    51     (priority == anotherTransition priority) ifFalse: [ ^ false ].
       
    52     (characterSet = anotherTransition characterSet) ifFalse: [ ^ false ].
       
    53     
       
    54     ^ true
       
    55 !
       
    56 
       
    57 canBeIsomorphicTo: anotherTransition
       
    58     (priority == anotherTransition priority) ifFalse: [ ^ false ].
       
    59     (characterSet = anotherTransition characterSet) ifFalse: [ ^ false ].
       
    60     
       
    61     ^ true
       
    62 !
       
    63 
       
    64 equals: anotherTransition
       
    65     "this method is used for minimization of the FSA"
       
    66     
       
    67     (self == anotherTransition) ifTrue: [ ^ true ].
       
    68 
       
    69     (destination == anotherTransition destination) ifFalse: [ ^ false ].
       
    70     (characterSet = anotherTransition characterSet) ifFalse: [ ^ false ].
       
    71 
       
    72     "JK: If character set and destination are the same, priority does not really matter"
       
    73     ^ true
       
    74 !
       
    75 
       
    76 hash
       
    77     ^ destination hash bitXor: (priority hash bitXor: characterSet hash)
       
    78 !
       
    79 
       
    80 isIsomorphicTo: object resolvedSet: set
       
    81     (set includes: (PEGFsaPair with: self with: object)) ifTrue: [ 
       
    82         ^ true
       
    83     ].
       
    84     set add: (PEGFsaPair with: self with: object).
       
    85 
       
    86     (self == object) ifTrue: [ ^ true ].
       
    87     (self class == object class) ifFalse: [ ^ false ].
       
    88 
       
    89     (priority == object priority) ifFalse: [ ^ false ].
       
    90     (characterSet = object characterSet) ifFalse: [ ^ false ].
       
    91     (destination isIsomorphicTo: object destination resolvedSet: set) ifFalse: [ ^ false ].
       
    92     
       
    93     ^ true
       
    94 ! !
       
    95 
       
    96 !PEGFsaTransition methodsFor:'copying'!
       
    97 
       
    98 postCopy
       
    99     super postCopy.
       
   100     characterSet := characterSet copy.
       
   101 ! !
       
   102 
       
   103 !PEGFsaTransition methodsFor:'gt'!
       
   104 
       
   105 gtName
       
   106     | gtName |
       
   107     gtName := self characterSetAsString.
       
   108     priority < 0 ifTrue: [ gtName := gtName, ',', priority asString ].
       
   109     ^ gtName
       
   110 ! !
       
   111 
       
   112 !PEGFsaTransition methodsFor:'initialization'!
       
   113 
       
   114 initialize
       
   115     super initialize.
       
   116     characterSet := Array new: 255 withAll: false.
       
   117     priority := 0.
       
   118 ! !
       
   119 
       
   120 !PEGFsaTransition methodsFor:'modifications'!
       
   121 
       
   122 addCharacter: character
       
   123     characterSet at: character codePoint put: true
       
   124 !
       
   125 
       
   126 decreasePriority
       
   127     priority := priority - 1
       
   128 ! !
       
   129 
       
   130 !PEGFsaTransition methodsFor:'printing'!
       
   131 
       
   132 characterSetAsString
       
   133     | stream |
       
   134     stream := WriteStream on: ''.
       
   135     self printCharacterSetOn: stream.
       
   136     ^ stream contents
       
   137 !
       
   138 
       
   139 printCharacterSetOn: stream
       
   140     self isEpsilon ifTrue: [ 
       
   141         stream nextPutAll: '<epsilon>'.
       
   142         ^ self
       
   143     ].
       
   144 
       
   145     stream nextPut: $[.
       
   146     32 to: 127 do: [ :index |
       
   147         (characterSet at: index) ifTrue: [ 
       
   148             stream nextPut: (Character codePoint: index)
       
   149         ]
       
   150     ].
       
   151     stream nextPut: $].
       
   152 !
       
   153 
       
   154 printOn: stream
       
   155     self printCharacterSetOn: stream.
       
   156     stream nextPutAll: ' ('.
       
   157     priority printOn: stream.
       
   158     stream nextPutAll: ')'.		
       
   159     stream nextPutAll: '-->'.
       
   160     destination printOn: stream.
       
   161     stream nextPutAll: '(ID: '.
       
   162     stream nextPutAll: self identityHash asString.
       
   163     stream nextPutAll: ')'.
       
   164 ! !
       
   165 
       
   166 !PEGFsaTransition methodsFor:'set operations'!
       
   167 
       
   168 complement: transition
       
   169     | complement |
       
   170     complement := Array new: 255.
       
   171     
       
   172     1 to: 255 do: [ :index |
       
   173         complement
       
   174             at: index 
       
   175             put: ((self characterSet at: index) and: [(transition characterSet at: index) not])
       
   176     ].
       
   177 
       
   178     ^ complement
       
   179 !
       
   180 
       
   181 disjunction: transition
       
   182     | disjunction |
       
   183     disjunction := Array new: 255.
       
   184     
       
   185     1 to: 255 do: [ :index |
       
   186         disjunction
       
   187             at: index 
       
   188             put: ((self characterSet at: index) xor: [transition characterSet at: index])
       
   189     ].
       
   190 
       
   191     ^ disjunction
       
   192 !
       
   193 
       
   194 intersection: transition
       
   195     | intersection |
       
   196     intersection := Array new: 255.
       
   197     
       
   198     1 to: 255 do: [ :index |
       
   199         intersection
       
   200             at: index 
       
   201             put: ((self characterSet at: index) and: [transition characterSet at: index])
       
   202     ].
       
   203 
       
   204     ^ intersection
       
   205 !
       
   206 
       
   207 union: transition
       
   208     | union |
       
   209     union := Array new: 255.
       
   210     
       
   211     1 to: 255 do: [ :index |
       
   212         union
       
   213             at: index 
       
   214             put: ((self characterSet at: index) or: [transition characterSet at: index])
       
   215     ].
       
   216 
       
   217     ^ union
       
   218 ! !
       
   219 
       
   220 !PEGFsaTransition methodsFor:'testing'!
       
   221 
       
   222 accepts: character
       
   223     ^ characterSet at: character codePoint
       
   224 !
       
   225 
       
   226 isEpsilon
       
   227     ^ characterSet allSatisfy: [ :e | e not ]
       
   228 !
       
   229 
       
   230 overlapsWith: transition
       
   231     ^ (self intersection: transition) anySatisfy: [ :bool | bool ]
       
   232 ! !
       
   233 
       
   234 !PEGFsaTransition methodsFor:'transformation'!
       
   235 
       
   236 join: transition
       
   237     ^ self join: transition joinDictionary: Dictionary new.
       
   238 !
       
   239 
       
   240 join: transition joinDictionary: dictionary
       
   241     | newDestination newTransition |
       
   242 "	pair := PEGFsaPair with: self with: transition.
       
   243     (dictionary includesKey: pair) ifTrue: [ ^ dictionary at: pair ].
       
   244     dictionary at: pair put: nil.
       
   245 "	
       
   246     newDestination := self destination join: transition destination joinDictionary: dictionary.
       
   247     newDestination isNil ifTrue: [ self error: 'What a cycle!! I wonder, how does this happened!!' ].
       
   248     
       
   249     newTransition := PEGFsaTransition new.
       
   250     newTransition destination: newDestination.
       
   251     newTransition characterSet: (self intersection: transition).
       
   252     newTransition priority: (self priority min: transition priority).
       
   253     
       
   254 "	^ dictionary at: pair put: newTransition"
       
   255     ^ newTransition 
       
   256 !
       
   257 
       
   258 mergeWith: transition
       
   259     | union |
       
   260     self assert: destination = transition destination.
       
   261     
       
   262     union := self union: transition.
       
   263     self characterSet: union
       
   264 ! !
       
   265