Changed TokenPatternParser to parse from string rather from literal array.
authorJan Vrany <jan.vrany@fit.cvut.cz>
Fri, 09 May 2014 17:16:42 +0100
changeset 203 c70b7351eda6
parent 202 5c8610dad14c
child 204 190357b490fd
Changed TokenPatternParser to parse from string rather from literal array. The literal array syntax was ambiguous and no way easier to read.
Make.proto
Make.spec
SmallSense__TokenPatternMatcher.st
SmallSense__TokenPatternMatcherTests.st
SmallSense__TokenPatternNode.st
SmallSense__TokenPatternParser.st
SmallSense__TokenPatternToken.st
SmallSense__TokenPatternTokenSet.st
abbrev.stc
bc.mak
jv_smallsense.st
libInit.cc
smallsense.rc
--- a/Make.proto	Fri May 09 15:22:12 2014 +0100
+++ b/Make.proto	Fri May 09 17:16:42 2014 +0100
@@ -192,8 +192,9 @@
 $(OUTDIR)SmallSense__SmalltalkSyntaxHighlighter.$(O) SmallSense__SmalltalkSyntaxHighlighter.$(H): SmallSense__SmalltalkSyntaxHighlighter.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libcomp/AbstractSyntaxHighlighter.$(H) $(INCLUDE_TOP)/stx/libcomp/Parser.$(H) $(INCLUDE_TOP)/stx/libcomp/Scanner.$(H) $(INCLUDE_TOP)/stx/libcomp/SyntaxHighlighter.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__SmalltalkUnacceptedMethodEnvironment.$(O) SmallSense__SmalltalkUnacceptedMethodEnvironment.$(H): SmallSense__SmalltalkUnacceptedMethodEnvironment.st $(INCLUDE_TOP)/stx/goodies/refactoryBrowser/helpers/BrowserEnvironment.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__TokenPatternMatcher.$(O) SmallSense__TokenPatternMatcher.$(H): SmallSense__TokenPatternMatcher.st $(INCLUDE_TOP)/stx/goodies/regex/RxMatcher.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)SmallSense__TokenPatternNode.$(O) SmallSense__TokenPatternNode.$(H): SmallSense__TokenPatternNode.st $(INCLUDE_TOP)/stx/goodies/regex/RxsNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)SmallSense__TokenPatternParser.$(O) SmallSense__TokenPatternParser.$(H): SmallSense__TokenPatternParser.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__TokenPatternParser.$(O) SmallSense__TokenPatternParser.$(H): SmallSense__TokenPatternParser.st $(INCLUDE_TOP)/stx/goodies/regex/RxCharSetParser.$(H) $(INCLUDE_TOP)/stx/goodies/regex/RxParser.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__TokenPatternToken.$(O) SmallSense__TokenPatternToken.$(H): SmallSense__TokenPatternToken.st $(INCLUDE_TOP)/stx/goodies/regex/RxsNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__TokenPatternTokenSet.$(O) SmallSense__TokenPatternTokenSet.$(H): SmallSense__TokenPatternTokenSet.st $(INCLUDE_TOP)/stx/goodies/regex/RxsCharSet.$(H) $(INCLUDE_TOP)/stx/goodies/regex/RxsNode.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__TokenStream.$(O) SmallSense__TokenStream.$(H): SmallSense__TokenStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__Type.$(O) SmallSense__Type.$(H): SmallSense__Type.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__TypeHolder.$(O) SmallSense__TypeHolder.$(H): SmallSense__TypeHolder.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/Make.spec	Fri May 09 15:22:12 2014 +0100
+++ b/Make.spec	Fri May 09 17:16:42 2014 +0100
@@ -79,8 +79,9 @@
 	SmallSense::SmalltalkSyntaxHighlighter \
 	SmallSense::SmalltalkUnacceptedMethodEnvironment \
 	SmallSense::TokenPatternMatcher \
-	SmallSense::TokenPatternNode \
 	SmallSense::TokenPatternParser \
+	SmallSense::TokenPatternToken \
+	SmallSense::TokenPatternTokenSet \
 	SmallSense::TokenStream \
 	SmallSense::Type \
 	SmallSense::TypeHolder \
@@ -140,8 +141,9 @@
     $(OUTDIR_SLASH)SmallSense__SmalltalkSyntaxHighlighter.$(O) \
     $(OUTDIR_SLASH)SmallSense__SmalltalkUnacceptedMethodEnvironment.$(O) \
     $(OUTDIR_SLASH)SmallSense__TokenPatternMatcher.$(O) \
-    $(OUTDIR_SLASH)SmallSense__TokenPatternNode.$(O) \
     $(OUTDIR_SLASH)SmallSense__TokenPatternParser.$(O) \
+    $(OUTDIR_SLASH)SmallSense__TokenPatternToken.$(O) \
+    $(OUTDIR_SLASH)SmallSense__TokenPatternTokenSet.$(O) \
     $(OUTDIR_SLASH)SmallSense__TokenStream.$(O) \
     $(OUTDIR_SLASH)SmallSense__Type.$(O) \
     $(OUTDIR_SLASH)SmallSense__TypeHolder.$(O) \
--- a/SmallSense__TokenPatternMatcher.st	Fri May 09 15:22:12 2014 +0100
+++ b/SmallSense__TokenPatternMatcher.st	Fri May 09 17:16:42 2014 +0100
@@ -82,6 +82,34 @@
 
     "Created: / 06-05-2014 / 14:38:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 06-05-2014 / 15:59:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+syntaxTokenSet: tokenSetNode
+    | tokens|
+
+    tokens := tokenSetNode tokens.
+
+    ^ Regex::RxmPredicate new predicate:
+        [:token |
+            | matches |
+            matches := tokens anySatisfy:[:tokenNode |
+                | type value |
+
+                type := tokenNode type.
+                value := tokenNode value.
+                (token isSymbol or:[token isCharacter]) ifTrue:[ 
+                    (type = token) and:[ value isNil or:[value == token ] ]
+                ] ifFalse:[ 
+                    (type = token type) and:[ value isNil or:[value = token value]  ]
+                ].
+            ].
+            tokenSetNode negated ifTrue:[ 
+                matches := matches not.
+            ].
+            matches.
+        ].
+
+    "Created: / 09-05-2014 / 16:22:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !TokenPatternMatcher methodsFor:'initialize-release'!
--- a/SmallSense__TokenPatternMatcherTests.st	Fri May 09 15:22:12 2014 +0100
+++ b/SmallSense__TokenPatternMatcherTests.st	Fri May 09 17:16:42 2014 +0100
@@ -13,24 +13,24 @@
 
 test_01
 
-    | tex matcher |
+    | pattern matcher |
 
-    tex := (SmallSense::TokenPatternParser parse: #( $] Keyword -> 'do:' )).
-    matcher := SmallSense::TokenPatternMatcher for: tex.
+    pattern := SmallSense::TokenPatternParser parse: '][[:Keyword=do\::]]'.
+    matcher := SmallSense::TokenPatternMatcher for: pattern.
 
     self assert: (matcher searchStream: (SmallSense::TokenStream on: (Scanner for: '] do:'))).
     self deny:   (matcher searchStream: (SmallSense::TokenStream on: (Scanner for: 'self matches do:'))).
 
     "Created: / 06-05-2014 / 16:29:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 09-05-2014 / 15:17:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 09-05-2014 / 16:36:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 test_02
 
-    | tex matcher |
+    | pattern matcher |
 
-    tex := (SmallSense::TokenPatternParser parse: #( $[ ( ( $: Identifier ) $* $| ) $? )).
-    matcher := SmallSense::TokenPatternMatcher for: tex.
+    pattern := SmallSense::TokenPatternParser parse: '\[(\:[[:Identifier:]]+\|)?'.
+    matcher := SmallSense::TokenPatternMatcher for: pattern.
 
     self assert: (matcher searchStream: (SmallSense::TokenStream on: (Scanner for: '[ '))).
     self assert: (matcher searchStream: (SmallSense::TokenStream on: (Scanner for: '[ :arg1 |'))).
@@ -38,5 +38,6 @@
 
     "Created: / 06-05-2014 / 17:04:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 09-05-2014 / 15:18:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 09-05-2014 / 17:07:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- a/SmallSense__TokenPatternNode.st	Fri May 09 15:22:12 2014 +0100
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,49 +0,0 @@
-"{ Package: 'jv:smallsense' }"
-
-"{ NameSpace: SmallSense }"
-
-Regex::RxsNode subclass:#TokenPatternNode
-	instanceVariableNames:'type value'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'SmallSense-Utils-Matcher'
-!
-
-!TokenPatternNode methodsFor:'accessing'!
-
-type
-    ^ type
-!
-
-type:something
-    type := something.
-!
-
-value
-    ^ value
-!
-
-value:something
-    value := something.
-! !
-
-!TokenPatternNode methodsFor:'double dispatch'!
-
-dispatchTo: matcher
-     "Inform the matcher of the kind of the node, and it
-      will do whatever it has to."
-
-     ^matcher syntaxToken: self
-
-    "Created: / 06-05-2014 / 14:32:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!TokenPatternNode methodsFor:'initialization'!
-
-initializeTyoe: t value: v
-    type := t.
-    value := v
-
-    "Created: / 02-05-2014 / 21:21:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
--- a/SmallSense__TokenPatternParser.st	Fri May 09 15:22:12 2014 +0100
+++ b/SmallSense__TokenPatternParser.st	Fri May 09 17:16:42 2014 +0100
@@ -2,13 +2,20 @@
 
 "{ NameSpace: SmallSense }"
 
-Object subclass:#TokenPatternParser
-	instanceVariableNames:'source stream'
+Regex::RxParser subclass:#TokenPatternParser
+	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
 	category:'SmallSense-Utils-Matcher'
 !
 
+Regex::RxCharSetParser subclass:#TokenSpecParser
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:TokenPatternParser
+!
+
 !TokenPatternParser class methodsFor:'documentation'!
 
 documentation
@@ -35,121 +42,80 @@
     "Created: / 02-05-2014 / 18:56:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!TokenPatternParser methodsFor:'parsing'!
+!TokenPatternParser methodsFor:'private'!
+
+characterSetFrom: setSpec
+        "<setSpec> is what goes between the brackets in a charset regex
+        (a String). Make a string containing all characters the spec specifies.
+        Spec is never empty."
 
-parse: anArrayOrStream
-    source := anArrayOrStream readStream.
-    ^ self parse.
+        | negated spec |
+        spec := ReadStream on: setSpec.
+        spec peek = $^
+                ifTrue:         [negated := true.
+                                spec next]
+                ifFalse:        [negated := false].
+        ^ TokenPatternTokenSet new
+                initializeElements: (TokenSpecParser on: spec) parse
+                negated: negated
 
-    "Created: / 02-05-2014 / 18:56:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 02-05-2014 / 21:27:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 09-05-2014 / 15:48:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
-!TokenPatternParser methodsFor:'parsing-private'!
+!TokenPatternParser methodsFor:'recursive descent'!
 
-expect: token
-    source peek ~~ token ifTrue:[ 
-        self error:'Expeciting ', token printString, ' got ' , source peek printString
+atom
+    | atom |
+
+    atom := super atom.
+    (atom isKindOf:Regex::RxsCharacter) ifTrue:[
+        atom := TokenPatternToken new type:atom character.
     ].
+    ^ atom
 
-    "Created: / 02-05-2014 / 19:05:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
+    "Created: / 09-05-2014 / 15:56:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
 
-parse
-    ^ self parseRegex
+!TokenPatternParser::TokenSpecParser methodsFor:'parsing'!
+
+parseNamedSet
+    | type value done out |
 
-    "Created: / 02-05-2014 / 18:56:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-parseAtom
-    | peek type value |
-
-    peek := source peek.
-    peek isSymbol ifTrue:[ 
-        type := source next.
-        source peek == #'->' ifTrue:[ 
-            source next.
-            source peek isString ifFalse:[ 
-                self error: 'Expecting token value'.
-            ] ifTrue:[ 
-                value := source next.
+    self
+        match:$[;
+        match:$:.
+    done := false.
+    out := '' writeStream.
+    [ done ] whileFalse:[ 
+        lookahead == $\ ifTrue:[ 
+            "/ Escape sequence
+            lookahead := source next.
+            out nextPut: lookahead.
+        ] ifFalse:[ 
+            lookahead == $: ifTrue:[ 
+                done := true.
+            ] ifFalse:[ 
+                lookahead == $= ifTrue:[ 
+                    type := out contents.
+                    out reset.
+                ] ifFalse:[ 
+                    out nextPut: lookahead.
+                ].
             ].
         ].
-        ^ TokenPatternNode new initializeTyoe: type value: value.
-    ].
-    peek isCharacter ifTrue:[ 
-        type := source next.
-        ^ TokenPatternNode new initializeTyoe: type value: nil.                                
+        lookahead := source next.
     ].
-    peek isArray ifTrue:[ 
-        | savedSource newSource subRegex |
-
-        newSource := source next readStream.
-        savedSource := source.
-        source := newSource.
-        [ 
-            subRegex := self parseRegex.
-        ] ensure:[ 
-            source := savedSource
-        ].
-        ^ subRegex
+    type isNil ifTrue:[ 
+        type := out contents.
+    ] ifFalse:[
+        value := out contents.
     ].
-    self error:'Unknown atom type'.
-
-    "Created: / 02-05-2014 / 21:17:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 09-05-2014 / 15:16:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-parseBranch
-
-    | piece branch |
-
-    piece := self parsePiece.
-    branch := (source peek isNil or:[ source peek == #'||' ]) 
-        ifTrue:[ nil ]
-        ifFalse:[ self parseBranch ].
-    ^ Regex::RxsBranch new 
-        initializePiece: piece 
-        branch: branch
+    self match:$].
 
-    "Created: / 02-05-2014 / 19:06:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 02-05-2014 / 21:11:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-parsePiece
-    | atom peek |
+    elements add:((TokenPatternToken new)
+                type:type;
+                value:value)
 
-    atom := self parseAtom.
-    peek := source peek.
-    peek == $* ifTrue:[ 
-        source next.
-        ^ Regex::RxsPiece new initializeStarAtom: atom.  
-    ].
-    peek == $+ ifTrue:[ 
-        source next.
-        ^ Regex::RxsPiece new initializePlusAtom: atom.  
-    ].
-    peek == $? ifTrue:[ 
-        source next.
-        ^ Regex::RxsPiece new initializeOptionalAtom: atom.  
-    ].
-     ^Regex::RxsPiece new initializeAtom: atom
-
-    "Created: / 02-05-2014 / 21:11:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-parseRegex
-    | regex branch |
-
-    branch := self parseBranch.
-    source atEnd ifTrue:[ 
-        regex := nil.
-    ] ifFalse:[
-        self expect: $|.
-        regex := self parseRegex.
-    ].
-    ^ Regex::RxsRegex new initializeBranch: branch regex: regex
-
-    "Created: / 02-05-2014 / 18:59:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 09-05-2014 / 16:35:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/SmallSense__TokenPatternToken.st	Fri May 09 17:16:42 2014 +0100
@@ -0,0 +1,57 @@
+"{ Package: 'jv:smallsense' }"
+
+"{ NameSpace: SmallSense }"
+
+Regex::RxsNode subclass:#TokenPatternToken
+	instanceVariableNames:'type value'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SmallSense-Utils-Matcher'
+!
+
+!TokenPatternToken methodsFor:'accessing'!
+
+type
+    ^ type
+!
+
+type:something
+    type := something.
+!
+
+value
+    ^ value
+!
+
+value:something
+    value := something.
+! !
+
+!TokenPatternToken methodsFor:'double dispatch'!
+
+dispatchTo: matcher
+     "Inform the matcher of the kind of the node, and it
+      will do whatever it has to."
+
+     ^matcher syntaxToken: self
+
+    "Created: / 06-05-2014 / 14:32:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!TokenPatternToken methodsFor:'initialization'!
+
+initializeTyoe: t value: v
+    type := t.
+    value := v
+
+    "Created: / 02-05-2014 / 21:21:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!TokenPatternToken methodsFor:'testing'!
+
+isEnumerable
+    ^ false
+
+    "Created: / 09-05-2014 / 16:10:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/SmallSense__TokenPatternTokenSet.st	Fri May 09 17:16:42 2014 +0100
@@ -0,0 +1,28 @@
+"{ Package: 'jv:smallsense' }"
+
+"{ NameSpace: SmallSense }"
+
+Regex::RxsCharSet subclass:#TokenPatternTokenSet
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SmallSense-Utils-Matcher'
+!
+
+!TokenPatternTokenSet methodsFor:'accessing'!
+
+dispatchTo: aMatcher
+        "Inform the matcher of the kind of the node, and it
+        will do whatever it has to."
+
+        ^aMatcher syntaxTokenSet: self
+
+    "Created: / 09-05-2014 / 16:18:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+tokens
+    ^ elements
+
+    "Created: / 09-05-2014 / 16:20:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- a/abbrev.stc	Fri May 09 15:22:12 2014 +0100
+++ b/abbrev.stc	Fri May 09 17:16:42 2014 +0100
@@ -1,6 +1,7 @@
 # automagically generated by the project definition
 # this file is needed for stc to be able to compile modules independently.
 # it provides information about a classes filename, category and especially namespace.
+SmallSense::BaseTestClass SmallSense__BaseTestClass jv:smallsense 'SmallSense-Tests' 1
 SmallSense::CodeHighlightingService SmallSense__CodeHighlightingService jv:smallsense 'SmallSense-Core-Services' 0
 SmallSense::CodeNavigationService SmallSense__CodeNavigationService jv:smallsense 'SmallSense-Core-Services' 0
 SmallSense::CompletionContext SmallSense__CompletionContext jv:smallsense 'SmallSense-Core' 0
@@ -29,9 +30,12 @@
 SmallSense::SmalltalkQuickFixer SmallSense__SmalltalkQuickFixer jv:smallsense 'SmallSense-Smalltalk-Lint' 0
 SmallSense::SmalltalkSyntaxHighlighter SmallSense__SmalltalkSyntaxHighlighter jv:smallsense 'SmallSense-Smalltalk' 3
 SmallSense::SmalltalkUnacceptedMethodEnvironment SmallSense__SmalltalkUnacceptedMethodEnvironment jv:smallsense 'SmallSense-Smalltalk-Lint' 0
+SmallSense::TestCase SmallSense__TestCase jv:smallsense 'SmallSense-Tests' 1
 SmallSense::TokenPatternMatcher SmallSense__TokenPatternMatcher jv:smallsense 'SmallSense-Utils-Matcher' 0
-SmallSense::TokenPatternNode SmallSense__TokenPatternNode jv:smallsense 'SmallSense-Utils-Matcher' 0
+SmallSense::TokenPatternMatcherTests SmallSense__TokenPatternMatcherTests jv:smallsense 'SmallSense-Tests' 1
 SmallSense::TokenPatternParser SmallSense__TokenPatternParser jv:smallsense 'SmallSense-Utils-Matcher' 0
+SmallSense::TokenPatternToken SmallSense__TokenPatternToken jv:smallsense 'SmallSense-Utils-Matcher' 0
+SmallSense::TokenPatternTokenSet SmallSense__TokenPatternTokenSet jv:smallsense 'SmallSense-Utils-Matcher' 0
 SmallSense::TokenStream SmallSense__TokenStream jv:smallsense 'SmallSense-Utils-Matcher' 0
 SmallSense::Type SmallSense__Type jv:smallsense 'SmallSense-Smalltalk-Types' 0
 SmallSense::TypeHolder SmallSense__TypeHolder jv:smallsense 'SmallSense-Smalltalk-Types' 0
@@ -40,16 +44,19 @@
 SmallSense::ClassPO SmallSense__ClassPO jv:smallsense 'SmallSense-Core-Interface-PO' 0
 SmallSense::ClassType SmallSense__ClassType jv:smallsense 'SmallSense-Smalltalk-Types' 0
 SmallSense::ConstantPO SmallSense__ConstantPO jv:smallsense 'SmallSense-Core-Interface-PO' 0
+SmallSense::FinderTests SmallSense__FinderTests jv:smallsense 'SmallSense-Tests' 1
 SmallSense::GenericEditSupport SmallSense__GenericEditSupport jv:smallsense 'SmallSense-Core-Services' 0
 SmallSense::JavaCompletionEngineSimple SmallSense__JavaCompletionEngineSimple jv:smallsense 'SmallSense-Java' 0
 SmallSense::JavaEditSupport SmallSense__JavaEditSupport jv:smallsense 'SmallSense-Java' 0
 SmallSense::JavaImportPO SmallSense__JavaImportPO jv:smallsense 'SmallSense-Java-Interface-PO' 0
 SmallSense::MethodInfo SmallSense__MethodInfo jv:smallsense 'SmallSense-Smalltalk-Types-Info' 0
 SmallSense::MethodPO SmallSense__MethodPO jv:smallsense 'SmallSense-Core-Interface-PO' 0
+SmallSense::RecognizerTests SmallSense__RecognizerTests jv:smallsense 'SmallSense-Tests' 1
 SmallSense::SmalltalkCompletionEngine SmallSense__SmalltalkCompletionEngine jv:smallsense 'SmallSense-Smalltalk' 0
 SmallSense::SmalltalkEditSupport SmallSense__SmalltalkEditSupport jv:smallsense 'SmallSense-Smalltalk' 0
 SmallSense::SmalltalkInferencer SmallSense__SmalltalkInferencer jv:smallsense 'SmallSense-Smalltalk-Types-Inference' 0
 SmallSense::SmalltalkParseNodeFinder SmallSense__SmalltalkParseNodeFinder jv:smallsense 'SmallSense-Smalltalk' 0
+SmallSense::SmalltalkParserTests SmallSense__SmalltalkParserTests jv:smallsense 'SmallSense-Tests' 1
 SmallSense::SnippetPO SmallSense__SnippetPO jv:smallsense 'SmallSense-Core-Interface-PO' 0
 SmallSense::UnionType SmallSense__UnionType jv:smallsense 'SmallSense-Smalltalk-Types' 0
 SmallSense::UnknownType SmallSense__UnknownType jv:smallsense 'SmallSense-Smalltalk-Types' 1
@@ -57,9 +64,3 @@
 SmallSense::GroovyCompletionEngineSimple SmallSense__GroovyCompletionEngineSimple jv:smallsense 'SmallSense-Groovy' 0
 SmallSense::GroovyEditSupport SmallSense__GroovyEditSupport jv:smallsense 'SmallSense-Groovy' 0
 SmallSense::MethodKeywordRestPO SmallSense__MethodKeywordRestPO jv:smallsense 'SmallSense-Core-Interface-PO' 0
-SmallSense::TokenPatternMatcherTests SmallSense__TokenPatternMatcherTests jv:smallsense 'SmallSense-Tests' 1
-SmallSense::BaseTestClass SmallSense__BaseTestClass jv:smallsense 'SmallSense-Tests' 1
-SmallSense::FinderTests SmallSense__FinderTests jv:smallsense 'SmallSense-Tests' 1
-SmallSense::RecognizerTests SmallSense__RecognizerTests jv:smallsense 'SmallSense-Tests' 1
-SmallSense::SmalltalkParserTests SmallSense__SmalltalkParserTests jv:smallsense 'SmallSense-Tests' 1
-SmallSense::TestCase SmallSense__TestCase jv:smallsense 'SmallSense-Tests' 1
--- a/bc.mak	Fri May 09 15:22:12 2014 +0100
+++ b/bc.mak	Fri May 09 17:16:42 2014 +0100
@@ -116,8 +116,9 @@
 $(OUTDIR)SmallSense__SmalltalkSyntaxHighlighter.$(O) SmallSense__SmalltalkSyntaxHighlighter.$(H): SmallSense__SmalltalkSyntaxHighlighter.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libcomp\AbstractSyntaxHighlighter.$(H) $(INCLUDE_TOP)\stx\libcomp\Parser.$(H) $(INCLUDE_TOP)\stx\libcomp\Scanner.$(H) $(INCLUDE_TOP)\stx\libcomp\SyntaxHighlighter.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__SmalltalkUnacceptedMethodEnvironment.$(O) SmallSense__SmalltalkUnacceptedMethodEnvironment.$(H): SmallSense__SmalltalkUnacceptedMethodEnvironment.st $(INCLUDE_TOP)\stx\goodies\refactoryBrowser\helpers\BrowserEnvironment.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__TokenPatternMatcher.$(O) SmallSense__TokenPatternMatcher.$(H): SmallSense__TokenPatternMatcher.st $(INCLUDE_TOP)\stx\goodies\regex\RxMatcher.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)SmallSense__TokenPatternNode.$(O) SmallSense__TokenPatternNode.$(H): SmallSense__TokenPatternNode.st $(INCLUDE_TOP)\stx\goodies\regex\RxsNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)SmallSense__TokenPatternParser.$(O) SmallSense__TokenPatternParser.$(H): SmallSense__TokenPatternParser.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__TokenPatternParser.$(O) SmallSense__TokenPatternParser.$(H): SmallSense__TokenPatternParser.st $(INCLUDE_TOP)\stx\goodies\regex\RxCharSetParser.$(H) $(INCLUDE_TOP)\stx\goodies\regex\RxParser.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__TokenPatternToken.$(O) SmallSense__TokenPatternToken.$(H): SmallSense__TokenPatternToken.st $(INCLUDE_TOP)\stx\goodies\regex\RxsNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)SmallSense__TokenPatternTokenSet.$(O) SmallSense__TokenPatternTokenSet.$(H): SmallSense__TokenPatternTokenSet.st $(INCLUDE_TOP)\stx\goodies\regex\RxsCharSet.$(H) $(INCLUDE_TOP)\stx\goodies\regex\RxsNode.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__TokenStream.$(O) SmallSense__TokenStream.$(H): SmallSense__TokenStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__Type.$(O) SmallSense__Type.$(H): SmallSense__Type.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmallSense__TypeHolder.$(O) SmallSense__TypeHolder.$(H): SmallSense__TypeHolder.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/jv_smallsense.st	Fri May 09 15:22:12 2014 +0100
+++ b/jv_smallsense.st	Fri May 09 17:16:42 2014 +0100
@@ -46,9 +46,9 @@
     ^ #(
         #'stx:goodies/refactoryBrowser/helpers'    "BrowserEnvironment - superclass of SmallSense::SmalltalkUnacceptedMethodEnvironment "
         #'stx:goodies/refactoryBrowser/lint'    "RBLintRule - extended "
-        #'stx:goodies/regex'    "Regex::RxMatcher - superclass of SmallSense::TokenExpressionMatcher "
-        #'stx:goodies/sunit'    "TestAsserter - superclass of SmallSense::TokenExpressionMatcherTests "
-        #'stx:libbasic'    "Autoload - superclass of SmallSense::BaseTestClass "
+        #'stx:goodies/regex'    "Regex::RxCharSetParser - superclass of SmallSense::TokenPatternParser::TokenSpecParser "
+        #'stx:goodies/sunit'    "TestAsserter - superclass of SmallSense::BaseTestClass "
+        #'stx:libbasic'    "Collection - extended "
         #'stx:libcomp'    "AbstractSyntaxHighlighter - superclass of SmallSense::SmalltalkParser "
         #'stx:libhtml'    "HTMLDocumentFrame - extended "
         #'stx:libtool'    "AbstractSettingsApplication - superclass of SmallSense::SettingsAppl "
@@ -162,6 +162,7 @@
 
     ^ #(
         "<className> or (<className> attributes...) in load order"
+        (#'SmallSense::BaseTestClass' autoload)
         #'SmallSense::CodeHighlightingService'
         #'SmallSense::CodeNavigationService'
         #'SmallSense::CompletionContext'
@@ -190,9 +191,12 @@
         #'SmallSense::SmalltalkQuickFixer'
         #'SmallSense::SmalltalkSyntaxHighlighter'
         #'SmallSense::SmalltalkUnacceptedMethodEnvironment'
+        (#'SmallSense::TestCase' autoload)
         #'SmallSense::TokenPatternMatcher'
-        #'SmallSense::TokenPatternNode'
+        (#'SmallSense::TokenPatternMatcherTests' autoload)
         #'SmallSense::TokenPatternParser'
+        #'SmallSense::TokenPatternToken'
+        #'SmallSense::TokenPatternTokenSet'
         #'SmallSense::TokenStream'
         #'SmallSense::Type'
         #'SmallSense::TypeHolder'
@@ -201,16 +205,19 @@
         #'SmallSense::ClassPO'
         #'SmallSense::ClassType'
         #'SmallSense::ConstantPO'
+        (#'SmallSense::FinderTests' autoload)
         #'SmallSense::GenericEditSupport'
         #'SmallSense::JavaCompletionEngineSimple'
         #'SmallSense::JavaEditSupport'
         #'SmallSense::JavaImportPO'
         #'SmallSense::MethodInfo'
         #'SmallSense::MethodPO'
+        (#'SmallSense::RecognizerTests' autoload)
         #'SmallSense::SmalltalkCompletionEngine'
         #'SmallSense::SmalltalkEditSupport'
         #'SmallSense::SmalltalkInferencer'
         #'SmallSense::SmalltalkParseNodeFinder'
+        (#'SmallSense::SmalltalkParserTests' autoload)
         #'SmallSense::SnippetPO'
         #'SmallSense::UnionType'
         #'SmallSense::UnknownType'
@@ -218,15 +225,7 @@
         #'SmallSense::GroovyCompletionEngineSimple'
         #'SmallSense::GroovyEditSupport'
         #'SmallSense::MethodKeywordRestPO'
-        (#'SmallSense::TokenPatternMatcherTests' autoload)
-        (#'SmallSense::BaseTestClass' autoload)
-        (#'SmallSense::FinderTests' autoload)
-        (#'SmallSense::RecognizerTests' autoload)
-        (#'SmallSense::SmalltalkParserTests' autoload)
-        (#'SmallSense::TestCase' autoload)
     )
-
-    "Modified: / 09-05-2014 / 15:20:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 extensionMethodNames
--- a/libInit.cc	Fri May 09 15:22:12 2014 +0100
+++ b/libInit.cc	Fri May 09 17:16:42 2014 +0100
@@ -56,8 +56,9 @@
 _SmallSense__SmalltalkSyntaxHighlighter_Init(pass,__pRT__,snd);
 _SmallSense__SmalltalkUnacceptedMethodEnvironment_Init(pass,__pRT__,snd);
 _SmallSense__TokenPatternMatcher_Init(pass,__pRT__,snd);
-_SmallSense__TokenPatternNode_Init(pass,__pRT__,snd);
 _SmallSense__TokenPatternParser_Init(pass,__pRT__,snd);
+_SmallSense__TokenPatternToken_Init(pass,__pRT__,snd);
+_SmallSense__TokenPatternTokenSet_Init(pass,__pRT__,snd);
 _SmallSense__TokenStream_Init(pass,__pRT__,snd);
 _SmallSense__Type_Init(pass,__pRT__,snd);
 _SmallSense__TypeHolder_Init(pass,__pRT__,snd);
--- a/smallsense.rc	Fri May 09 15:22:12 2014 +0100
+++ b/smallsense.rc	Fri May 09 17:16:42 2014 +0100
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2011\nCopyright eXept Software AG 1998-2011\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.3.0\0"
-      VALUE "ProductDate", "Fri, 09 May 2014 14:21:23 GMT\0"
+      VALUE "ProductDate", "Fri, 09 May 2014 16:14:40 GMT\0"
     END
 
   END