compiler/PEGFsaTransition.st
changeset 515 b5316ef15274
parent 502 1e45d3c96ec5
child 516 3b81c9e53352
child 524 f6f68d32de73
--- a/compiler/PEGFsaTransition.st	Fri Jul 24 15:06:54 2015 +0100
+++ b/compiler/PEGFsaTransition.st	Mon Aug 17 12:13:16 2015 +0100
@@ -3,12 +3,20 @@
 "{ NameSpace: Smalltalk }"
 
 Object subclass:#PEGFsaTransition
-	instanceVariableNames:'characterSet destination priority'
+	instanceVariableNames:'destination priority characterSet'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'PetitCompiler-FSA'
 !
 
+!PEGFsaTransition class methodsFor:'instance creation'!
+
+new
+    "return an initialized instance"
+
+    ^ self basicNew initialize.
+! !
+
 !PEGFsaTransition methodsFor:'accessing'!
 
 characterSet
@@ -49,14 +57,13 @@
 
     (destination == anotherTransition destination) ifFalse: [ ^ false ].
     (priority == anotherTransition priority) ifFalse: [ ^ false ].
-    (characterSet = anotherTransition characterSet) ifFalse: [ ^ false ].
     
     ^ true
 !
 
 canBeIsomorphicTo: anotherTransition
+    (self class == anotherTransition class) ifFalse: [ ^ false ].
     (priority == anotherTransition priority) ifFalse: [ ^ false ].
-    (characterSet = anotherTransition characterSet) ifFalse: [ ^ false ].
     
     ^ true
 !
@@ -65,32 +72,16 @@
     "this method is used for minimization of the FSA"
     
     (self == anotherTransition) ifTrue: [ ^ true ].
+    (self class == anotherTransition class) ifFalse: [ ^ false ].
 
     (destination == anotherTransition destination) ifFalse: [ ^ false ].
-    (characterSet = anotherTransition characterSet) ifFalse: [ ^ false ].
 
     "JK: If character set and destination are the same, priority does not really matter"
     ^ true
 !
 
 hash
-    ^ destination hash bitXor: (priority hash bitXor: characterSet hash)
-!
-
-isIsomorphicTo: object resolvedSet: set
-    (set includes: (PEGFsaPair with: self with: object)) ifTrue: [ 
-        ^ true
-    ].
-    set add: (PEGFsaPair with: self with: object).
-
-    (self == object) ifTrue: [ ^ true ].
-    (self class == object class) ifFalse: [ ^ false ].
-
-    (priority == object priority) ifFalse: [ ^ false ].
-    (characterSet = object characterSet) ifFalse: [ ^ false ].
-    (destination isIsomorphicTo: object destination resolvedSet: set) ifFalse: [ ^ false ].
-    
-    ^ true
+    ^ destination hash bitXor: priority hash
 ! !
 
 !PEGFsaTransition methodsFor:'copying'!
@@ -113,7 +104,6 @@
 
 initialize
     super initialize.
-    characterSet := Array new: 255 withAll: false.
     priority := 0.
 ! !
 
@@ -124,43 +114,11 @@
 !
 
 decreasePriority
-    priority := priority - 1
-! !
-
-!PEGFsaTransition methodsFor:'printing'!
-
-characterSetAsString
-    | stream |
-    stream := WriteStream on: ''.
-    self printCharacterSetOn: stream.
-    ^ stream contents
+    self decreasePriorityBy: 1
 !
 
-printCharacterSetOn: stream
-    self isEpsilon ifTrue: [ 
-        stream nextPutAll: '<epsilon>'.
-        ^ self
-    ].
-
-    stream nextPut: $[.
-    32 to: 127 do: [ :index |
-        (characterSet at: index) ifTrue: [ 
-            stream nextPut: (Character codePoint: index)
-        ]
-    ].
-    stream nextPut: $].
-!
-
-printOn: stream
-    self printCharacterSetOn: stream.
-    stream nextPutAll: ' ('.
-    priority printOn: stream.
-    stream nextPutAll: ')'.		
-    stream nextPutAll: '-->'.
-    destination printOn: stream.
-    stream nextPutAll: '(ID: '.
-    stream nextPutAll: self identityHash asString.
-    stream nextPutAll: ')'.
+decreasePriorityBy: value
+    priority := priority - value
 ! !
 
 !PEGFsaTransition methodsFor:'set operations'!
@@ -223,8 +181,20 @@
     ^ characterSet at: character codePoint
 !
 
+isCharacterTransition
+    ^ false
+!
+
 isEpsilon
-    ^ characterSet allSatisfy: [ :e | e not ]
+    ^ self isEpsilonTransition
+!
+
+isEpsilonTransition
+    ^ false
+!
+
+isPredicateTransition
+    ^ false
 !
 
 overlapsWith: transition