#QUALITY by exept
authorClaus Gittinger <cg@exept.de>
Sun, 17 Nov 2019 15:32:55 +0100
changeset 2409 83ccbaa621f8
parent 2408 888711f2dca0
child 2410 c1c8182c5e59
#QUALITY by exept class: RegressionTests::RxTests added:182 methods comment/format in: #compileRegex:into: #runRegexTestsForMatcher: #runTestsForMatcher: #test001 changed:143 methods
RegressionTests__RxTests.st
--- a/RegressionTests__RxTests.st	Fri Nov 08 09:37:26 2019 +0100
+++ b/RegressionTests__RxTests.st	Sun Nov 17 15:32:55 2019 +0100
@@ -21,6 +21,16 @@
 
 !RxTests methodsFor:'helper'!
 
+compileRegex: aString
+
+        "Compile the regex and answer the matcher, or answer nil if compilation fails."
+
+        | syntaxTree |
+
+        syntaxTree := Regex::RxParser safelyParse: aString.
+        ^ syntaxTree ifNotNil: [ self matcherClass for: syntaxTree ]
+!
+
 compileRegex: regexSource into: matcherClass
         "Compile the regex and answer the matcher, or answer nil if compilation fails."
 
@@ -28,13 +38,40 @@
 
         "/ ^ Regex::RxMatcher2 forString: regexSource.
 
-        syntaxTree := Regex::RxParser safelyParse: regexSource.
+        syntaxTree := Regex::RxParser "self matcherClass" safelyParse: regexSource.
         syntaxTree == nil ifTrue: [^nil].
         ^matcherClass for: syntaxTree
 
     "Modified: / 31-07-2019 / 11:48:08 / Stefan Reise"
 !
 
+matcherClass
+    ^ Regex::RxMatcher
+!
+
+runMatcher: aMatcher with: aString expect: aBoolean withSubexpressions: anArray
+        | copy got sub subExpect subGot |
+        copy := aMatcher
+                copy: aString
+                translatingMatchesUsing: [ :each | each ].
+        self 
+                assert: copy = aString
+                description: 'Copying: expected ' , aString printString , ', but got ' , copy printString.
+        got := aMatcher search: aString.
+        self
+                assert: got = aBoolean 
+                description: 'Searching: expected ' , aBoolean printString , ', but got ' , got printString.
+        (anArray isNil or: [ aMatcher supportsSubexpressions not ])
+                ifTrue: [ ^ self ].
+        1 to: anArray size by: 2 do: [ :index |
+                sub := anArray at: index.
+                subExpect := anArray at: index + 1.
+                subGot := aMatcher subexpression: sub.
+                self
+                        assert: subExpect = subGot
+                        description: 'Subexpression ' , sub printString , ': expected ' , subExpect printString , ', but got ' , subGot storeString ]
+!
+
 runProtocolTestsForMatcher: matcherClass
 
 	| matcher |
@@ -53,68 +90,94 @@
 	Transcript show: 'OK'; cr
 !
 
+runRegex: anArray
+
+        "Run a clause anArray against a set of tests. Each clause is an array with a regex source string followed by sequence of 3-tuples. Each three-element group is one test to try against the regex, and includes: 1) test string; 2) expected result; 3) expected subexpression as an array of (index, substring), or nil."
+
+        | source matcher |
+
+        source := anArray first.
+        matcher := self compileRegex: source.
+        matcher
+                ifNil: [ ( anArray at: 2 )
+                                ifNotNil: [ self signalFailure: 'Compilation failed, should have succeeded: ' , source printString ]
+                        ]
+                ifNotNil: [ ( anArray at: 2 )
+                                ifNil: [ self signalFailure: 'Compilation succeeded, should have failed: ' , source printString ]
+                                ifNotNil: [ 2 to: anArray size by: 3 do: [ :index | 
+                                                self
+                                                        runMatcher: matcher
+                                                        with: ( anArray at: index )
+                                                        expect: ( anArray at: index + 1 )
+                                                        withSubexpressions: ( anArray at: index + 2 )
+                                                ]
+                                        ]
+                        ]
+!
+
 runRegexTestsForMatcher: matcherClass
-	"Run the whole suite of tests for the given matcher class. May blow up
-	if anything goes wrong with the matcher or parser. Since this is a
-	developer's tool, who cares?"
-	"self runRegexTestsForMatcher: Regex::RxMatcher"
-
-	| failures |
-	failures := 0.
-	Transcript cr.
-	self xtestSuite do: [:clause |
-		| rxSource matcher isOK |
-		rxSource := clause first.
-		Transcript show: 'Testing regex: '; show: rxSource printString; cr.
-		matcher := self compileRegex: rxSource into: matcherClass.
-		matcher == nil
-			ifTrue:
-				[(clause at: 2) isNil
-					ifTrue:
-						[Transcript tab; show: 'Compilation error as expected (ok)'; cr]
-					ifFalse:
-						[Transcript tab;
-							show: 'Compilation error, UNEXPECTED -- FAILED'; cr.
-						failures := failures + 1]]
-			ifFalse:
-				[(clause at: 2) == nil
-					ifTrue:
-						[Transcript tab;
-							show: 'Compilation succeeded, should have failed -- FAILED!!';
-							cr.
-						failures := failures + 1]
-					ifFalse:
-						[2 to: clause size by: 3 do:
-							[:i |
-							isOK := self
-								xtest: matcher
-								with: (clause at: i)
-								expect: (clause at: i + 1)
-								withSubexpressions: (clause at: i + 2).
-							isOK ifFalse: [failures := failures + 1].
-							Transcript
-								show: (isOK ifTrue: [' (ok).'] ifFalse: [' -- FAILED!!']);
-								cr]]]].
-	failures = 0
-		ifTrue: [Transcript show: 'PASSED ALL TESTS.'; cr]
-		ifFalse: [Transcript show: failures printString, ' TESTS FAILED!!'; cr]
+        "Run the whole suite of tests for the given matcher class. May blow up
+        if anything goes wrong with the matcher or parser. Since this is a
+        developer's tool, who cares?"
+        "self new runRegexTestsForMatcher: Regex::RxMatcher"
+
+        | failures |
+        failures := 0.
+        Transcript cr.
+        self xtestSuite do: [:clause |
+                | rxSource matcher isOK |
+                rxSource := clause first.
+                Transcript show: 'Testing regex: '; show: rxSource printString; cr.
+                matcher := self compileRegex: rxSource into: matcherClass.
+                matcher == nil
+                        ifTrue:
+                                [(clause at: 2) isNil
+                                        ifTrue:
+                                                [Transcript tab; show: 'Compilation error as expected (ok)'; cr]
+                                        ifFalse:
+                                                [Transcript tab;
+                                                        show: 'Compilation error, UNEXPECTED -- FAILED'; cr.
+                                                failures := failures + 1]]
+                        ifFalse:
+                                [(clause at: 2) == nil
+                                        ifTrue:
+                                                [Transcript tab;
+                                                        show: 'Compilation succeeded, should have failed -- FAILED!!';
+                                                        cr.
+                                                failures := failures + 1]
+                                        ifFalse:
+                                                [2 to: clause size by: 3 do:
+                                                        [:i |
+                                                        isOK := self
+                                                                xtest: matcher
+                                                                with: (clause at: i)
+                                                                expect: (clause at: i + 1)
+                                                                withSubexpressions: (clause at: i + 2).
+                                                        isOK ifFalse: [failures := failures + 1].
+                                                        Transcript
+                                                                show: (isOK ifTrue: [' (ok).'] ifFalse: [' -- FAILED!!']);
+                                                                cr]]]].
+        failures = 0
+                ifTrue: [Transcript show: 'PASSED ALL TESTS.'; cr]
+                ifFalse: [Transcript show: failures printString, ' TESTS FAILED!!'; cr]
 !
 
 runTestsForMatcher: matcherClass
-	"Run the whole suite of tests for the given matcher class. May blow up
-	if something goes wrong with the matcher or the parser. Since this is a
-	developer's tool, who cares?"
-	"self runTestsForMatcher: Regex::RxMatcher"
-
-	self
-		runRegexTestsForMatcher: matcherClass;
-		runProtocolTestsForMatcher: matcherClass
+        "Run the whole suite of tests for the given matcher class. May blow up
+        if something goes wrong with the matcher or the parser. Since this is a
+        developer's tool, who cares?"
+        "self new runTestsForMatcher: Regex::RxMatcher"
+
+        self
+                runRegexTestsForMatcher: matcherClass;
+                runProtocolTestsForMatcher: matcherClass
 ! !
 
 !RxTests methodsFor:'profiling'!
 
 bigHonkingStream
-    ^ '~/Downloads/smalltalk/Pharo6.1-64.app/Contents/MacOS/PharoV60.sources' asFilename readStream "36Mb"
+    ^ '~/Documents/Pharo/images/Pharo 8.0 - 64bit (development version, latest)/Pharo8.0-32bit-3a0b722.sources' asFilename readStream "38Mb"
+"/    ^ '~/Downloads/smalltalk/Pharo6.1-64.app/Contents/MacOS/PharoV60.sources' asFilename readStream "36Mb"
 "/    ^'/home/vassili/VisualWorks/image/visualnc.sou' asFilename readStream "7 Megs"
 
     "Modified: / 04-06-2019 / 10:52:51 / Claus Gittinger"
@@ -173,6 +236,551 @@
 	^count
 ! !
 
+!RxTests methodsFor:'test suite - henry'!
+
+testHenry001
+        self runRegex: #('abc'
+                'abc' true (1 'abc')
+                'xbc' false nil
+                'axc' false nil
+                'abx' false nil
+                'xabcy' true (1 'abc')
+                'ababc' true (1 'abc'))
+!
+
+testHenry002
+        self runRegex: #('ab*c'
+                'abc' true (1 'abc'))
+!
+
+testHenry003
+        self runRegex: #('ab*bc'
+                'abc' true (1 'abc')
+                'abbc' true (1 'abbc')
+                'abbbbc' true (1 'abbbbc'))
+!
+
+testHenry004
+        self runRegex: #('ab+bc'        
+                'abbc' true (1 'abbc')
+                'abc' false nil
+                'abq' false nil
+                'abbbbc' true (1 'abbbbc'))
+!
+
+testHenry005
+        self runRegex: #('ab?bc'
+                'abbc' true (1 'abbc')
+                'abc' true (1 'abc')
+                'abbbbc' false nil
+                'abc' true (1 'abc'))
+!
+
+testHenry006
+        self runRegex: #('^abc$'
+                'abc' true (1 'abc')
+                'abcc' false nil
+                'aabc' false nil)
+!
+
+testHenry007
+        self runRegex: #('^abc'
+                'abcc' true (1 'abc'))
+!
+
+testHenry008
+        self runRegex: #('abc$'
+                'aabc' true (1 'abc'))
+!
+
+testHenry009
+        self runRegex: #('^'
+                'abc' true nil)
+!
+
+testHenry010
+        self runRegex: #('$'
+                'abc' true nil)
+!
+
+testHenry011
+        self runRegex: #('a.c'
+                'abc' true (1 'abc')
+                'axc' true (1 'axc'))
+!
+
+testHenry012
+        "Need to get creative to include the null character..."
+        self runRegex: 
+            #('a.*c' 
+                'axyzd' false nil
+                'axyzc' true (1 'axyzc')
+                'axy zc' true (1 'axy zc') "testing that a dot matches a space"
+            ).
+
+        self runRegex: 
+            {'a.*c' . 
+                'axy',(String with: 0 asCharacter),'zc' . false . nil} "testing that a dot does not match a null"
+!
+
+testHenry014
+        self runRegex: #('a\w+c'
+                ' abbbbc ' true (1 'abbbbc')
+                'abb bc' false nil)
+!
+
+testHenry015
+        self runRegex: #('\w+'
+                '       foobar  quux' true (1 'foobar')
+                '       ~!!@#$%^&*()-+=\|/?.>,<' false nil)
+!
+
+testHenry016
+        self runRegex: #('a\W+c'
+                'a   c' true (1 'a   c')
+                'a bc' false nil)
+!
+
+testHenry017
+        self runRegex: #('\W+'
+                'foo!!@#$bar' true (1 '!!@#$')
+                'foobar' false nil)
+!
+
+testHenry018
+        self runRegex: #('a\s*c'
+                'a   c' true (1 'a   c')
+                'a bc' false nil)
+!
+
+testHenry019
+        self runRegex: #('\s+'
+                'abc3457 sd' true (1 ' ')
+                '1234$^*^&asdfb' false nil)
+!
+
+testHenry020
+        self runRegex: #('a\S*c'
+                'aqwertyc' true (1 'aqwertyc')
+                'ab c' false nil)
+!
+
+testHenry021
+        self runRegex: #('\S+'
+                '       asdf            ' true (1 'asdf')
+                '       
+                        ' false nil)
+!
+
+testHenry022
+        self runRegex: #('a\d+c'
+                'a0123456789c' true (1 'a0123456789c')
+                'a12b34c' false nil)
+!
+
+testHenry023
+        self runRegex: #('\d+'
+                'foo@#$%123ASD #$$%^&' true (1 '123')
+                'foo!!@#$asdfl;' false nil)
+!
+
+testHenry024
+        self runRegex: #('a\D+c'
+                'aqwertyc' true (1 'aqwertyc')
+                'aqw6ertc' false nil)
+!
+
+testHenry025
+        self runRegex: #('\D+'
+                '1234 abc 456' true (1 ' abc ')
+                '1234567890' false nil)
+!
+
+testHenry026
+        self runRegex: #('(f|o)+\b'
+                'foo' true (1 'foo')
+                ' foo ' true (1 'foo'))
+!
+
+testHenry027
+        self runRegex: #('\ba\w+' "a word beginning with an A"
+                'land ancient' true (1 'ancient')
+                'antique vase' true (1 'antique')
+                'goofy foobar' false nil)
+!
+
+testHenry028
+        self runRegex: #('(f|o)+\B'
+                'quuxfoobar' true (1 'foo')
+                'quuxfoo ' true (1 'fo'))
+!
+
+testHenry029
+        self runRegex: #('\Ba\w+' "a word with an A in the middle, match at A and further"
+                'land ancient' true (1 'and')
+                'antique vase' true (1 'ase')
+                'smalltalk shall overcome' true (1 'alltalk')
+                'foonix is better' false nil)
+!
+
+testHenry030
+        self runRegex: #('fooa\>.*'
+                'fooa ' true nil
+                'fooa123' false nil
+                'fooa bar' true nil
+                'fooa' true nil
+                'fooargh' false nil)
+!
+
+testHenry031
+        self runRegex: #('\>.+abc'
+                ' abcde fg' false nil
+                'foo abcde' true (1 ' abc')
+                'abcde' false nil)
+!
+
+testHenry032
+        self runRegex: #('\<foo.*'
+                'foo' true nil
+                'foobar' true nil
+                'qfoobarq foonix' true (1 'foonix')
+                ' foo' true nil
+                ' 12foo' false nil
+                'barfoo' false nil)
+!
+
+testHenry033
+        self runRegex: #('.+\<foo'
+                'foo' false nil
+                'ab foo' true (1 'ab foo')
+                'abfoo' false nil)
+!
+
+testHenry034
+        self runRegex: #('a[bc]d'
+                'abc' false nil
+                'abd' true (1 'abd'))
+!
+
+testHenry035
+        self runRegex: #('a[b-d]e'
+                'abd' false nil
+                'ace' true (1 'ace'))
+!
+
+testHenry036
+        self runRegex: #('a[b-d]'
+                'aac' true (1 'ac'))
+!
+
+testHenry037
+        self runRegex: #('a[-b]'
+                'a-' true (1 'a-'))
+!
+
+testHenry038
+        self runRegex: #('a[b-]'
+                'a-' true (1 'a-'))
+!
+
+testHenry039
+        self runRegex: #('a[a-b-c]' nil)
+!
+
+testHenry040
+        self runRegex: #('[k]'
+                'ab' false nil)
+!
+
+testHenry041
+        self runRegex: #('a[b-a]' nil)
+!
+
+testHenry042
+        self runRegex: #('a[]b' nil)
+!
+
+testHenry043
+        self runRegex: #('a[' nil)
+!
+
+testHenry044
+        self runRegex: #('a]' 
+                'a]' true (1 'a]'))
+!
+
+testHenry045
+        self runRegex: #('a[]]b'
+                'a]b' true (1 'a]b'))
+!
+
+testHenry046
+        self runRegex: #('a[^bc]d'
+                'aed' true (1 'aed')
+                'abd' false nil)
+!
+
+testHenry047
+        self runRegex: #('a[^-b]c'
+                'adc' true (1 'adc')
+                'a-c' false nil)
+!
+
+testHenry048
+        self runRegex: #('a[^]b]c'
+                'a]c' false nil
+                'adc' true (1 'adc'))
+!
+
+testHenry049
+        self runRegex: #('[\de]+'
+                '01234' true (1 '01234')
+                '0123e456' true (1 '0123e456')
+                '0123e45g78' true (1 '0123e45'))
+!
+
+testHenry050
+        self runRegex: #('[e\d]+' "reversal of the above, should be the same"
+                '01234' true (1 '01234')
+                '0123e456' true (1 '0123e456')
+                '0123e45g78' true (1 '0123e45'))
+!
+
+testHenry051
+        self runRegex: #('[\D]+'
+                '123abc45def78' true (1 'abc'))
+!
+
+testHenry052
+        self runRegex: #('[[:digit:]e]+'
+                '01234' true (1 '01234')
+                '0123e456' true (1 '0123e456')
+                '0123e45g78' true (1 '0123e45'))
+!
+
+testHenry053
+        self runRegex: #('[\s]+'
+                '2  spaces' true (1 '  '))
+!
+
+testHenry054
+        self runRegex: #('[\S]+'
+                '  word12!!@#$  ' true (1 'word12!!@#$'))
+!
+
+testHenry055
+        self runRegex: #('[\w]+'
+                '       foo123bar       45' true (1 'foo123bar'))
+!
+
+testHenry056
+        self runRegex: #('[\W]+'
+                'fii234!!@#$34f' true (1 '!!@#$'))
+!
+
+testHenry057
+        self runRegex: #('[^[:alnum:]]+'
+                'fii234!!@#$34f' true (1 '!!@#$'))
+!
+
+testHenry058
+        self runRegex: #('[%&[:alnum:]]+'
+                'foo%3' true (1 'foo%3')
+                'foo34&rt4$57a' true (1 'foo34&rt4')
+                '!!@#$' false nil)
+!
+
+testHenry060
+        self runRegex: #('[[:cntrl:]]+'
+                ' a 1234asdf' false nil)
+!
+
+testHenry061
+        self runRegex: #('[[:lower:]]+'
+                'UPPERlower1234' true (1 'lower')
+                'lowerUPPER' true (1 'lower'))
+!
+
+testHenry062
+        self runRegex: #('[[:upper:]]+'
+                'UPPERlower1234' true (1 'UPPER')
+                'lowerUPPER ' true (1 'UPPER'))
+!
+
+testHenry063
+        self runRegex: #('[[:space:]]+'
+                '2  spaces' true (1 '  '))
+!
+
+testHenry064
+        self runRegex: #('[^[:space:]]+'
+                '  word12!!@#$  ' true (1 'word12!!@#$'))
+!
+
+testHenry065
+        self runRegex: #('[[:graph:]]+'
+                'abc' true (1 'abc'))
+!
+
+testHenry066
+        self runRegex: #('[[:print:]]+'
+                'abc' true (1 'abc'))
+!
+
+testHenry067
+        self runRegex: #('[^[:punct:]]+'
+                '!!hello,world!!' true (1 'hello'))
+!
+
+testHenry068
+        self runRegex: #('[[:xdigit:]]+'
+                '  x10FCD  ' true (1 '10FCD')
+                ' hgfedcba0123456789ABCDEFGH '
+                        true (1 'fedcba0123456789ABCDEF'))
+!
+
+testHenry069
+        self runRegex: #('ab|cd'
+                'abc' true (1 'ab')
+                'abcd' true (1 'ab'))
+!
+
+testHenry070
+        self runRegex: #('()ef'
+                'def' true (1 'ef' 2 ''))
+!
+
+testHenry071
+        self runRegex: #('()*' nil)
+!
+
+testHenry072
+        self runRegex: #('*a' nil)
+!
+
+testHenry073
+        self runRegex: #('^*' nil)
+!
+
+testHenry074
+        self runRegex: #('$*' nil)
+!
+
+testHenry075
+        self runRegex: #('(*)b' nil)
+!
+
+testHenry076
+        self runRegex: #('$b'   'b' false nil)
+!
+
+testHenry077
+        self runRegex: #('a\' nil)
+!
+
+testHenry078
+        self runRegex: #('a\(b'
+                'a(b' true (1 'a(b'))
+!
+
+testHenry079
+        self runRegex: #('a\(*b'
+                'ab' true (1 'ab')
+                'a((b' true (1 'a((b'))
+!
+
+testHenry080
+        self runRegex: #('a\\b'
+                'a\b' true (1 'a\b'))
+!
+
+testHenry081
+        self runRegex: #('abc)' nil)
+!
+
+testHenry082
+        self runRegex: #('(abc' nil)
+!
+
+testHenry083
+        self runRegex: #('((a))'
+                'abc' true (1 'a' 2 'a' 3 'a'))
+!
+
+testHenry084
+        self runRegex: #('(a)b(c)'
+                'abc' true (1 'abc' 2 'a' 3 'c'))
+!
+
+testHenry085
+        self runRegex: #('a+b+c'
+                'aabbabc' true (1 'abc'))
+!
+
+testHenry086
+        self runRegex: #('a**' nil)
+!
+
+testHenry087
+        self runRegex: #('a*?' nil)
+!
+
+testHenry088
+        self runRegex: #('(a*)*' nil)
+!
+
+testHenry089
+        self runRegex: #('(a*)+' nil)
+!
+
+testHenry090
+        self runRegex: #('(a|)*' nil)
+!
+
+testHenry091
+        self runRegex: #('(a*|b)*' nil)
+!
+
+testHenry092
+        self runRegex: #('(a+|b)*'
+                'ab' true (1 'ab' 2 'b'))
+!
+
+testHenry093
+        self runRegex: #('(a+|b)+'
+                'ab' true (1 'ab' 2 'b'))
+!
+
+testHenry094
+        self runRegex: #('(a+|b)?'
+                'ab' true (1 'a' 2 'a'))
+!
+
+testHenry095
+        self runRegex: #('[^ab]*'
+                'cde' true (1 'cde'))
+!
+
+testHenry096
+        self runRegex: #('(^)*' nil)
+!
+
+testHenry097
+        self runRegex: #('(ab|)*' nil)
+!
+
+testHenry098
+        self runRegex: #(')(' nil)
+!
+
+testHenry099
+        self runRegex: #('' 'abc' true (1 ''))
+!
+
+testHenry100
+        self runRegex: #('abc' '' false nil)
+! !
+
 !RxTests methodsFor:'test suite - new'!
 
 test001
@@ -188,7 +796,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'abc' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'abc' into:Regex::RxMatcher) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
     self should:[ (matcher search:'xbc') = false ].
@@ -212,7 +820,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'ab*c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'ab*c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
 
@@ -231,7 +839,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'ab*bc' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'ab*bc' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
     self should:[ (matcher search:'abbc') = true ].
@@ -255,7 +863,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'ab+bc' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'ab+bc' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abbc') = true ].
     self should:[ (matcher subexpression:1) = 'abbc' ].
     self should:[ (matcher search:'abc') = false ].
@@ -278,7 +886,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'ab?bc' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'ab?bc' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abbc') = true ].
     self should:[ (matcher subexpression:1) = 'abbc' ].
     self should:[ (matcher search:'abc') = true ].
@@ -298,7 +906,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'ab?c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'ab?c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
 
@@ -317,7 +925,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'^abc$' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'^abc$' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
     self should:[ (matcher search:'abcc') = false ].
@@ -336,7 +944,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'^abc' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'^abc' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abcc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
 
@@ -353,7 +961,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'abc$' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'abc$' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'aabc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
 
@@ -369,7 +977,7 @@
 
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'^' into:Regex::RxMatcher) ~= nil ].
+    self should:[ (matcher := self compileRegex:'^' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
 
     "
@@ -384,7 +992,7 @@
 
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'$' into:Regex::RxMatcher) ~= nil ].
+    self should:[ (matcher := self compileRegex:'$' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
 
     "
@@ -396,7 +1004,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a.c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a.c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
     self should:[ (matcher search:'axc') = true ].
@@ -407,17 +1015,17 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a.*c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a.*c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'axyzc') = true ].
     self should:[ (matcher subexpression:1) = 'axyzc' ].
     self should:[ (matcher search:'axy zc') = true ].
     self should:[ (matcher subexpression:1) = 'axy zc' ].
     self
-	should:[
-	    (matcher search:'axy
-						 zc')
-		= false
-	].
+        should:[
+            (matcher search:'axy
+                                                 zc')
+                = false
+        ].
     self should:[ (matcher search:'axyzd') = false ].
 !
 
@@ -425,7 +1033,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'.a.*' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'.a.*' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'1234abc') = true ].
     self should:[ (matcher subexpression:1) = '4abc' ].
     self should:[ (matcher search:'abcd') = false ].
@@ -435,7 +1043,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a\w+c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a\w+c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:' abbbbc ') = true ].
     self should:[ (matcher subexpression:1) = 'abbbbc' ].
     self should:[ (matcher search:'abb bc') = false ].
@@ -445,7 +1053,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\w+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\w+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'       foobar  quux') = true ].
     self should:[ (matcher subexpression:1) = 'foobar' ].
     self should:[ (matcher search:'       ~!!@#$%^&*()-+=\|/?.>,<') = false ].
@@ -455,7 +1063,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a\W+c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a\W+c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a   c') = true ].
     self should:[ (matcher subexpression:1) = 'a   c' ].
     self should:[ (matcher search:'a bc') = false ].
@@ -465,7 +1073,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\W+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\W+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'foo!!@#$bar') = true ].
     self should:[ (matcher subexpression:1) = '!!@#$' ].
     self should:[ (matcher search:'foobar') = false ].
@@ -475,7 +1083,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a\s*c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a\s*c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a   c') = true ].
     self should:[ (matcher subexpression:1) = 'a   c' ].
     self should:[ (matcher search:'a bc') = false ].
@@ -485,7 +1093,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\s+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\s+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc3457 sd') = true ].
     self should:[ (matcher subexpression:1) = ' ' ].
     self should:[ (matcher search:'1234$^*^&asdfb') = false ].
@@ -495,7 +1103,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a\S*c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a\S*c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'aqwertyc') = true ].
     self should:[ (matcher subexpression:1) = 'aqwertyc' ].
     self should:[ (matcher search:'ab c') = false ].
@@ -505,19 +1113,19 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\S+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\S+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'       asdf            ') = true ].
     self should:[ (matcher subexpression:1) = 'asdf' ].
     self
-	should:[ (matcher search:'
-				') = false ].
+        should:[ (matcher search:'
+                                ') = false ].
 !
 
 test022
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a\d+c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a\d+c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a0123456789c') = true ].
     self should:[ (matcher subexpression:1) = 'a0123456789c' ].
     self should:[ (matcher search:'a12b34c') = false ].
@@ -527,7 +1135,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\d+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\d+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'foo@#$%123ASD #$$%^&') = true ].
     self should:[ (matcher subexpression:1) = '123' ].
     self should:[ (matcher search:'foo!!@#$asdfl;') = false ].
@@ -537,7 +1145,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a\D+c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a\D+c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'aqwertyc') = true ].
     self should:[ (matcher subexpression:1) = 'aqwertyc' ].
     self should:[ (matcher search:'aqw6ertc') = false ].
@@ -547,7 +1155,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\D+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\D+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'1234 abc 456') = true ].
     self should:[ (matcher subexpression:1) = ' abc ' ].
     self should:[ (matcher search:'1234567890') = false ].
@@ -557,7 +1165,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(f|o)+\b' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'(f|o)+\b' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'foo') = true ].
     self should:[ (matcher subexpression:1) = 'foo' ].
     self should:[ (matcher search:' foo ') = true ].
@@ -568,7 +1176,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\ba\w+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\ba\w+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'land ancient') = true ].
     self should:[ (matcher subexpression:1) = 'ancient' ].
     self should:[ (matcher search:'antique vase') = true ].
@@ -580,7 +1188,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(f|o)+\B' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'(f|o)+\B' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'quuxfoobar') = true ].
     self should:[ (matcher subexpression:1) = 'foo' ].
     self should:[ (matcher search:'quuxfoo ') = true ].
@@ -591,7 +1199,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\Ba\w+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\Ba\w+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'land ancient') = true ].
     self should:[ (matcher subexpression:1) = 'and' ].
     self should:[ (matcher search:'antique vase') = true ].
@@ -605,7 +1213,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'fooa\>.*' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'fooa\>.*' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'fooa ') = true ].
     self should:[ (matcher search:'fooa123') = false ].
     self should:[ (matcher search:'fooa bar') = true ].
@@ -617,7 +1225,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\>.+abc' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\>.+abc' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:' abcde fg') = false ].
     self should:[ (matcher search:'foo abcde') = true ].
     self should:[ (matcher subexpression:1) = ' abc' ].
@@ -628,7 +1236,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'\<foo.*' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'\<foo.*' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'foo') = true ].
     self should:[ (matcher search:'foobar') = true ].
     self should:[ (matcher search:'qfoobarq foonix') = true ].
@@ -642,7 +1250,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'.+\<foo' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'.+\<foo' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'foo') = false ].
     self should:[ (matcher search:'ab foo') = true ].
     self should:[ (matcher subexpression:1) = 'ab foo' ].
@@ -653,7 +1261,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[bc]d' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a[bc]d' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = false ].
     self should:[ (matcher search:'abd') = true ].
     self should:[ (matcher subexpression:1) = 'abd' ].
@@ -663,7 +1271,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[b-d]e' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a[b-d]e' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abd') = false ].
     self should:[ (matcher search:'ace') = true ].
     self should:[ (matcher subexpression:1) = 'ace' ].
@@ -673,7 +1281,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[b-d]' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a[b-d]' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'aac') = true ].
     self should:[ (matcher subexpression:1) = 'ac' ].
 !
@@ -682,7 +1290,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[-b]' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a[-b]' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a-') = true ].
     self should:[ (matcher subexpression:1) = 'a-' ].
 !
@@ -691,7 +1299,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[b-]' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a[b-]' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a-') = true ].
     self should:[ (matcher subexpression:1) = 'a-' ].
 !
@@ -700,14 +1308,14 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[a-b-c]' into:Regex::RxMatcher) = nil ].
+        should:[ (matcher := self compileRegex:'a[a-b-c]' into:self matcherClass) = nil ].
 !
 
 test040
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[k]' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'[k]' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'ab') = false ].
 !
 
@@ -715,26 +1323,26 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[b-a]' into:Regex::RxMatcher) = nil ].
+        should:[ (matcher := self compileRegex:'a[b-a]' into:self matcherClass) = nil ].
 !
 
 test042
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[]b' into:Regex::RxMatcher) = nil ].
+        should:[ (matcher := self compileRegex:'a[]b' into:self matcherClass) = nil ].
 !
 
 test043
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'a[' into:Regex::RxMatcher) = nil ].
+    self should:[ (matcher := self compileRegex:'a[' into:self matcherClass) = nil ].
 !
 
 test044
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'a]' into:Regex::RxMatcher) ~= nil ].
+    self should:[ (matcher := self compileRegex:'a]' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a]') = true ].
     self should:[ (matcher subexpression:1) = 'a]' ].
 !
@@ -743,7 +1351,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[]]b' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a[]]b' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a]b') = true ].
     self should:[ (matcher subexpression:1) = 'a]b' ].
 !
@@ -752,7 +1360,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[^bc]d' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a[^bc]d' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'aed') = true ].
     self should:[ (matcher subexpression:1) = 'aed' ].
     self should:[ (matcher search:'abd') = false ].
@@ -762,7 +1370,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[^-b]c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a[^-b]c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'adc') = true ].
     self should:[ (matcher subexpression:1) = 'adc' ].
     self should:[ (matcher search:'a-c') = false ].
@@ -772,7 +1380,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a[^]b]c' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'a[^]b]c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a]c') = false ].
     self should:[ (matcher search:'adc') = true ].
     self should:[ (matcher subexpression:1) = 'adc' ].
@@ -782,7 +1390,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[\de]+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'[\de]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'01234') = true ].
     self should:[ (matcher subexpression:1) = '01234' ].
     self should:[ (matcher search:'0123e456') = true ].
@@ -795,7 +1403,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[e\d]+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'[e\d]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'01234') = true ].
     self should:[ (matcher subexpression:1) = '01234' ].
     self should:[ (matcher search:'0123e456') = true ].
@@ -808,7 +1416,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[\D]+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'[\D]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'123abc45def78') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
 !
@@ -817,7 +1425,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[[:digit:]e]+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'[[:digit:]e]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'01234') = true ].
     self should:[ (matcher subexpression:1) = '01234' ].
     self should:[ (matcher search:'0123e456') = true ].
@@ -830,7 +1438,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[\s]+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'[\s]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'2  spaces') = true ].
     self should:[ (matcher subexpression:1) = '  ' ].
 !
@@ -839,7 +1447,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[\S]+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'[\S]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'  word12!!@#$  ') = true ].
     self should:[ (matcher subexpression:1) = 'word12!!@#$' ].
 !
@@ -848,7 +1456,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[\w]+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'[\w]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'       foo123bar       45') = true ].
     self should:[ (matcher subexpression:1) = 'foo123bar' ].
 !
@@ -857,7 +1465,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[\W]+' into:Regex::RxMatcher) ~= nil ].
+        should:[ (matcher := self compileRegex:'[\W]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'fii234!!@#$34f') = true ].
     self should:[ (matcher subexpression:1) = '!!@#$' ].
 !
@@ -866,7 +1474,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[^[:alnum:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[^[:alnum:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'fii234!!@#$34f') = true ].
     self should:[ (matcher subexpression:1) = '!!@#$' ].
 !
@@ -876,7 +1484,7 @@
 
     self
 	should:[
-	    (matcher := self compileRegex:'[%&[:alnum:]]+' into:Regex::RxMatcher) ~= nil
+	    (matcher := self compileRegex:'[%&[:alnum:]]+' into:self matcherClass) ~= nil
 	].
     self should:[ (matcher search:'foo%3') = true ].
     self should:[ (matcher subexpression:1) = 'foo%3' ].
@@ -889,7 +1497,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[[:alpha:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[[:alpha:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:' 123foo3 ') = true ].
     self should:[ (matcher subexpression:1) = 'foo' ].
     self should:[ (matcher search:'123foo') = true ].
@@ -902,7 +1510,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[[:cntrl:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[[:cntrl:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:' a 1234asdf') = false ].
 !
 
@@ -910,7 +1518,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[[:lower:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[[:lower:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'UPPERlower1234') = true ].
     self should:[ (matcher subexpression:1) = 'lower' ].
     self should:[ (matcher search:'lowerUPPER') = true ].
@@ -921,7 +1529,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[[:upper:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[[:upper:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'UPPERlower1234') = true ].
     self should:[ (matcher subexpression:1) = 'UPPER' ].
     self should:[ (matcher search:'lowerUPPER ') = true ].
@@ -932,7 +1540,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[[:space:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[[:space:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'2  spaces') = true ].
     self should:[ (matcher subexpression:1) = '  ' ].
 !
@@ -941,7 +1549,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[^[:space:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[^[:space:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'  word12!!@#$  ') = true ].
     self should:[ (matcher subexpression:1) = 'word12!!@#$' ].
 !
@@ -950,7 +1558,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[[:graph:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[[:graph:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
 !
@@ -959,7 +1567,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[[:print:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[[:print:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
 !
@@ -968,7 +1576,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[^[:punct:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[^[:punct:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'!!hello,world!!') = true ].
     self should:[ (matcher subexpression:1) = 'hello' ].
 !
@@ -977,7 +1585,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[[:xdigit:]]+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[[:xdigit:]]+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'  x10FCD  ') = true ].
     self should:[ (matcher subexpression:1) = '10FCD' ].
     self should:[ (matcher search:' hgfedcba0123456789ABCDEFGH ') = true ].
@@ -988,7 +1596,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'ab|cd' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'ab|cd' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'ab' ].
     self should:[ (matcher search:'abcd') = true ].
@@ -999,7 +1607,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'()ef' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'()ef' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'def') = true ].
     self should:[ (matcher subexpression:1) = 'ef' ].
     self should:[ (matcher subexpression:2) = '' ].
@@ -1008,52 +1616,52 @@
 test071
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'()*' into:Regex::RxMatcher) = nil ].
+    self should:[ (matcher := self compileRegex:'()*' into:self matcherClass) = nil ].
 !
 
 test072
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'*a' into:Regex::RxMatcher) = nil ].
+    self should:[ (matcher := self compileRegex:'*a' into:self matcherClass) = nil ].
 !
 
 test073
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'^*' into:Regex::RxMatcher) = nil ].
+    self should:[ (matcher := self compileRegex:'^*' into:self matcherClass) = nil ].
 !
 
 test074
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'$*' into:Regex::RxMatcher) = nil ].
+    self should:[ (matcher := self compileRegex:'$*' into:self matcherClass) = nil ].
 !
 
 test075
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(*)b' into:Regex::RxMatcher) = nil ].
+	should:[ (matcher := self compileRegex:'(*)b' into:self matcherClass) = nil ].
 !
 
 test076
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'$b' into:Regex::RxMatcher) ~= nil ].
+    self should:[ (matcher := self compileRegex:'$b' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'b') = false ].
 !
 
 test077
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'a\' into:Regex::RxMatcher) = nil ].
+    self should:[ (matcher := self compileRegex:'a\' into:self matcherClass) = nil ].
 !
 
 test078
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a\(b' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'a\(b' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a(b') = true ].
     self should:[ (matcher subexpression:1) = 'a(b' ].
 !
@@ -1062,7 +1670,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a\(*b' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'a\(*b' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'ab') = true ].
     self should:[ (matcher subexpression:1) = 'ab' ].
     self should:[ (matcher search:'a((b') = true ].
@@ -1073,7 +1681,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a\\b' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'a\\b' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'a\b') = true ].
     self should:[ (matcher subexpression:1) = 'a\b' ].
 !
@@ -1082,21 +1690,21 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'abc)' into:Regex::RxMatcher) = nil ].
+	should:[ (matcher := self compileRegex:'abc)' into:self matcherClass) = nil ].
 !
 
 test082
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(abc' into:Regex::RxMatcher) = nil ].
+	should:[ (matcher := self compileRegex:'(abc' into:self matcherClass) = nil ].
 !
 
 test083
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'((a))' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'((a))' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'a' ].
     self should:[ (matcher subexpression:2) = 'a' ].
@@ -1107,7 +1715,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(a)b(c)' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'(a)b(c)' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
     self should:[ (matcher subexpression:2) = 'a' ].
@@ -1118,7 +1726,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a+b+c' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'a+b+c' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'aabbabc') = true ].
     self should:[ (matcher subexpression:1) = 'abc' ].
 !
@@ -1126,48 +1734,48 @@
 test086
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'a**' into:Regex::RxMatcher) = nil ].
+    self should:[ (matcher := self compileRegex:'a**' into:self matcherClass) = nil ].
 !
 
 test087
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'a*?' into:Regex::RxMatcher) = nil ].
+    self should:[ (matcher := self compileRegex:'a*?' into:self matcherClass) = nil ].
 !
 
 test088
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(a*)*' into:Regex::RxMatcher) = nil ].
+	should:[ (matcher := self compileRegex:'(a*)*' into:self matcherClass) = nil ].
 !
 
 test089
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(a*)+' into:Regex::RxMatcher) = nil ].
+	should:[ (matcher := self compileRegex:'(a*)+' into:self matcherClass) = nil ].
 !
 
 test090
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(a|)*' into:Regex::RxMatcher) = nil ].
+	should:[ (matcher := self compileRegex:'(a|)*' into:self matcherClass) = nil ].
 !
 
 test091
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(a*|b)*' into:Regex::RxMatcher) = nil ].
+	should:[ (matcher := self compileRegex:'(a*|b)*' into:self matcherClass) = nil ].
 !
 
 test092
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(a+|b)*' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'(a+|b)*' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'ab') = true ].
     self should:[ (matcher subexpression:1) = 'ab' ].
     self should:[ (matcher subexpression:2) = 'b' ].
@@ -1177,7 +1785,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(a+|b)+' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'(a+|b)+' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'ab') = true ].
     self should:[ (matcher subexpression:1) = 'ab' ].
     self should:[ (matcher subexpression:2) = 'b' ].
@@ -1187,7 +1795,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(a+|b)?' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'(a+|b)?' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'ab') = true ].
     self should:[ (matcher subexpression:1) = 'a' ].
     self should:[ (matcher subexpression:2) = 'a' ].
@@ -1197,7 +1805,7 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'[^ab]*' into:Regex::RxMatcher) ~= nil ].
+	should:[ (matcher := self compileRegex:'[^ab]*' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'cde') = true ].
     self should:[ (matcher subexpression:1) = 'cde' ].
 !
@@ -1206,26 +1814,26 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(^)*' into:Regex::RxMatcher) = nil ].
+	should:[ (matcher := self compileRegex:'(^)*' into:self matcherClass) = nil ].
 !
 
 test097
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'(ab|)*' into:Regex::RxMatcher) = nil ].
+	should:[ (matcher := self compileRegex:'(ab|)*' into:self matcherClass) = nil ].
 !
 
 test098
     |matcher|
 
-    self should:[ (matcher := self compileRegex:')(' into:Regex::RxMatcher) = nil ].
+    self should:[ (matcher := self compileRegex:')(' into:self matcherClass) = nil ].
 !
 
 test099
     |matcher|
 
-    self should:[ (matcher := self compileRegex:'' into:Regex::RxMatcher) ~= nil ].
+    self should:[ (matcher := self compileRegex:'' into:self matcherClass) ~= nil ].
     self should:[ (matcher search:'abc') = true ].
     self should:[ (matcher subexpression:1) = '' ].
 !
@@ -1233,7 +1841,7 @@
 test100
     | matcher |
 
-    self should: [ (matcher := self compileRegex: 'abc' into:Regex::RxMatcher) ~= nil ].
+    self should: [ (matcher := self compileRegex: 'abc' into:self matcherClass) ~= nil ].
     self should: [ (matcher search: '') = false ].
 
     "
@@ -1244,7 +1852,7 @@
 test101
     | matcher |
 
-    self should: [ (matcher := self compileRegex: 'a*' into:Regex::RxMatcher) ~= nil ].
+    self should: [ (matcher := self compileRegex: 'a*' into:self matcherClass) ~= nil ].
     self should: [ (matcher search: '') = true ].
 
     "
@@ -1255,7 +1863,7 @@
 test102
     | matcher |
 
-    self should: [ (matcher := self compileRegex: 'abcd' into:Regex::RxMatcher) ~= nil ].
+    self should: [ (matcher := self compileRegex: 'abcd' into:self matcherClass) ~= nil ].
     self should: [ (matcher search: 'abcd') = true ].
     self should: [ (matcher subexpression: 1) = 'abcd' ].
 
@@ -1267,7 +1875,7 @@
 test103
     | matcher |
 
-    self should: [ (matcher := self compileRegex: 'a(bc)d' into:Regex::RxMatcher) ~= nil ].
+    self should: [ (matcher := self compileRegex: 'a(bc)d' into:self matcherClass) ~= nil ].
     self should: [ (matcher search: 'abcd') = true ].
     self should: [ (matcher subexpression: 1) = 'abcd' ].
     self should: [ (matcher subexpression: 2) = 'bc' ].
@@ -1281,7 +1889,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '([abc])*d' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '([abc])*d' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abbbcd') = true ].
 	self should: [ (matcher subexpression: 1) = 'abbbcd' ].
 	self should: [ (matcher subexpression: 2) = 'c' ].
@@ -1291,7 +1899,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '([abc])*bcd' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '([abc])*bcd' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcd') = true ].
 	self should: [ (matcher subexpression: 1) = 'abcd' ].
 	self should: [ (matcher subexpression: 2) = 'a' ].
@@ -1301,7 +1909,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: 'a|b|c|d|e' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: 'a|b|c|d|e' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'e') = true ].
 	self should: [ (matcher subexpression: 1) = 'e' ].
 !
@@ -1310,7 +1918,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '(a|b|c|d|e)f' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '(a|b|c|d|e)f' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'ef') = true ].
 	self should: [ (matcher subexpression: 1) = 'ef' ].
 	self should: [ (matcher subexpression: 2) = 'e' ].
@@ -1320,7 +1928,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: 'abcd*efg' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: 'abcd*efg' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcdefg') = true ].
 	self should: [ (matcher subexpression: 1) = 'abcdefg' ].
 !
@@ -1329,7 +1937,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: 'ab*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: 'ab*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'xabyabbbz') = true ].
 	self should: [ (matcher subexpression: 1) = 'ab' ].
 	self should: [ (matcher search: 'xayabbbz') = true ].
@@ -1340,7 +1948,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '(ab|cd)e' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '(ab|cd)e' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcde') = true ].
 	self should: [ (matcher subexpression: 1) = 'cde' ].
 	self should: [ (matcher subexpression: 2) = 'cd' ].
@@ -1350,7 +1958,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '[abhgefdc]ij' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '[abhgefdc]ij' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'hij') = true ].
 	self should: [ (matcher subexpression: 1) = 'hij' ].
 !
@@ -1359,7 +1967,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '^(ab|cd)e' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '^(ab|cd)e' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcde') = false ].
 !
 
@@ -1367,7 +1975,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '(abc|)def' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '(abc|)def' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcdef') = true ].
 !
 
@@ -1375,7 +1983,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '(a|b)c*d' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '(a|b)c*d' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcd') = true ].
 	self should: [ (matcher subexpression: 1) = 'bcd' ].
 	self should: [ (matcher subexpression: 2) = 'b' ].
@@ -1385,7 +1993,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '(ab|ab*)bc' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '(ab|ab*)bc' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 	self should: [ (matcher subexpression: 2) = 'a' ].
@@ -1395,7 +2003,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: 'a([bc]*)c*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: 'a([bc]*)c*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 	self should: [ (matcher subexpression: 2) = 'bc' ].
@@ -1405,7 +2013,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: 'a([bc]*)(c*d)' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: 'a([bc]*)(c*d)' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcd') = true ].
 	self should: [ (matcher subexpression: 1) = 'abcd' ].
 	self should: [ (matcher subexpression: 2) = 'bc' ].
@@ -1416,7 +2024,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: 'a([bc]+)(c*d)' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: 'a([bc]+)(c*d)' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcd') = true ].
 	self should: [ (matcher subexpression: 1) = 'abcd' ].
 	self should: [ (matcher subexpression: 2) = 'bc' ].
@@ -1427,7 +2035,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: 'a([bc]*)(c+d)' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: 'a([bc]*)(c+d)' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcd') = true ].
 	self should: [ (matcher subexpression: 1) = 'abcd' ].
 	self should: [ (matcher subexpression: 2) = 'b' ].
@@ -1438,7 +2046,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: 'a[bcd]*dcdcde' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: 'a[bcd]*dcdcde' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'adcdcde') = true ].
 	self should: [ (matcher subexpression: 1) = 'adcdcde' ].
 !
@@ -1447,7 +2055,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: 'a[bcd]+dcdcde' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: 'a[bcd]+dcdcde' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'adcdcde') = false ].
 !
 
@@ -1455,7 +2063,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '(ab|a)b*c' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '(ab|a)b*c' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 !
@@ -1464,7 +2072,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '((a)(b)c)(d)' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '((a)(b)c)(d)' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abcd') = true ].
 	self should: [ (matcher subexpression: 1) = 'abcd' ].
 	self should: [ (matcher subexpression: 3) = 'a' ].
@@ -1476,7 +2084,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '[ -~]*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '[ -~]*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 !
@@ -1485,7 +2093,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '[ -~ -~]*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '[ -~ -~]*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 !
@@ -1494,7 +2102,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '[ -~ -~ -~]*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '[ -~ -~ -~]*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 !
@@ -1503,7 +2111,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~]*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~]*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 !
@@ -1512,7 +2120,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~ -~]*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~ -~]*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 !
@@ -1521,7 +2129,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~ -~ -~]*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~ -~ -~]*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 !
@@ -1530,7 +2138,7 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~ -~ -~ -~]*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~ -~ -~ -~]*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'abc') = true ].
 	self should: [ (matcher subexpression: 1) = 'abc' ].
 !
@@ -1539,74 +2147,74 @@
 	| matcher |
 
 
-	self should: [ (matcher := self compileRegex: '[a-zA-Z_][a-zA-Z0-9_]*' into:Regex::RxMatcher) ~= nil ].
+	self should: [ (matcher := self compileRegex: '[a-zA-Z_][a-zA-Z0-9_]*' into:self matcherClass) ~= nil ].
 	self should: [ (matcher search: 'alpha') = true ].
 	self should: [ (matcher subexpression: 1) = 'alpha' ].
 !
 
 test132
-	| matcher |
-
-	self should: [ (matcher := self compileRegex: '^a(bc+|b[eh])g|.h$' into:Regex::RxMatcher) ~= nil ].
-	self should: [ (matcher search: 'abh') = true ].
-	self should: [ (matcher subexpression: 1) = 'bh' ].
-	self should: [ (matcher subexpression: 2) = '' ].
+        | matcher |
+
+        self should: [ (matcher := self compileRegex: '^a(bc+|b[eh])g|.h$' into:self matcherClass) ~= nil ].
+        self should: [ (matcher search: 'abh') = true ].
+        self should: [ (matcher subexpression: 1) = 'bh' ].
+        self should: [ (matcher subexpression: 2) = '' ].
 !
 
 test133
-	| matcher |
-
-	self should: [ (matcher := self compileRegex: '(bc+d$|ef*g.|h?i(j|k))' into:Regex::RxMatcher) ~= nil ].
-	self should: [ (matcher search: 'effgz') = true ].
-	self should: [ (matcher subexpression: 1) = 'effgz' ].
-	self should: [ (matcher subexpression: 2) = 'effgz' ].
-	self should: [ (matcher subexpression: 3) = '' ].
-	self should: [ (matcher search: 'ij') = true ].
-	self should: [ (matcher subexpression: 1) = 'ij' ].
-	self should: [ (matcher subexpression: 2) = 'ij' ].
-	self should: [ (matcher subexpression: 3) = 'j' ].
-	self should: [ (matcher search: 'effg') = false ].
-	self should: [ (matcher search: 'bcdd') = false ].
-	self should: [ (matcher search: 'reffgz') = true ].
-	self should: [ (matcher subexpression: 1) = 'effgz' ].
-	self should: [ (matcher subexpression: 2) = 'effgz' ].
-	self should: [ (matcher subexpression: 3) = '' ].
+        | matcher |
+
+        self should: [ (matcher := self compileRegex: '(bc+d$|ef*g.|h?i(j|k))' into:self matcherClass) ~= nil ].
+        self should: [ (matcher search: 'effgz') = true ].
+        self should: [ (matcher subexpression: 1) = 'effgz' ].
+        self should: [ (matcher subexpression: 2) = 'effgz' ].
+        self should: [ (matcher subexpression: 3) = '' ].
+        self should: [ (matcher search: 'ij') = true ].
+        self should: [ (matcher subexpression: 1) = 'ij' ].
+        self should: [ (matcher subexpression: 2) = 'ij' ].
+        self should: [ (matcher subexpression: 3) = 'j' ].
+        self should: [ (matcher search: 'effg') = false ].
+        self should: [ (matcher search: 'bcdd') = false ].
+        self should: [ (matcher search: 'reffgz') = true ].
+        self should: [ (matcher subexpression: 1) = 'effgz' ].
+        self should: [ (matcher subexpression: 2) = 'effgz' ].
+        self should: [ (matcher subexpression: 3) = '' ].
 !
 
 test134
-	| matcher |
-
-	self should: [ (matcher := self compileRegex: '(((((((((a)))))))))' into:Regex::RxMatcher) ~= nil ].
-	self should: [ (matcher search: 'a') = true ].
-	self should: [ (matcher subexpression: 1) = 'a' ].
+        | matcher |
+
+        self should: [ (matcher := self compileRegex: '(((((((((a)))))))))' into:self matcherClass) ~= nil ].
+        self should: [ (matcher search: 'a') = true ].
+        self should: [ (matcher subexpression: 1) = 'a' ].
 !
 
 test135
-	| matcher |
-
-	self should: [ (matcher := self compileRegex: 'multiple words of text' into:Regex::RxMatcher) ~= nil ].
-	self should: [ (matcher search: 'uh-uh') = false ].
-	self should: [ (matcher search: 'multiple words of text, yeah') = true ].
-	self should: [ (matcher subexpression: 1) = 'multiple words of text' ].
+        | matcher |
+
+        self should: [ (matcher := self compileRegex: 'multiple words of text' into:self matcherClass) ~= nil ].
+        self should: [ (matcher search: 'uh-uh') = false ].
+        self should: [ (matcher search: 'multiple words of text, yeah') = true ].
+        self should: [ (matcher subexpression: 1) = 'multiple words of text' ].
 !
 
 test136
-	| matcher |
-
-	self should: [ (matcher := self compileRegex: '(.*)c(.*)' into:Regex::RxMatcher) ~= nil ].
-	self should: [ (matcher search: 'abcde') = true ].
-	self should: [ (matcher subexpression: 1) = 'abcde' ].
-	self should: [ (matcher subexpression: 2) = 'ab' ].
-	self should: [ (matcher subexpression: 3) = 'de' ].
+        | matcher |
+
+        self should: [ (matcher := self compileRegex: '(.*)c(.*)' into:self matcherClass) ~= nil ].
+        self should: [ (matcher search: 'abcde') = true ].
+        self should: [ (matcher subexpression: 1) = 'abcde' ].
+        self should: [ (matcher subexpression: 2) = 'ab' ].
+        self should: [ (matcher subexpression: 3) = 'de' ].
 !
 
 test137
-	| matcher |
-
-	self should: [ (matcher := self compileRegex: '\((.*), (.*)\)' into:Regex::RxMatcher) ~= nil ].
-	self should: [ (matcher search: '(a, b)') = true ].
-	self should: [ (matcher subexpression: 2) = 'a' ].
-	self should: [ (matcher subexpression: 3) = 'b' ].
+        | matcher |
+
+        self should: [ (matcher := self compileRegex: '\((.*), (.*)\)' into:self matcherClass) ~= nil ].
+        self should: [ (matcher search: '(a, b)') = true ].
+        self should: [ (matcher subexpression: 2) = 'a' ].
+        self should: [ (matcher subexpression: 3) = 'b' ].
 !
 
 test138
@@ -1626,47 +2234,47 @@
     |matcher|
 
     self
-	should:[ (matcher := self compileRegex:'a{}b' into:Regex::RxMatcher) = nil ].
+        should:[ (matcher := self compileRegex:'a{}b' into:self matcherClass) = nil ].
 !
 
 test200
-	| matcher |
-
-	self should: [ (matcher := self compileRegex: '\d{2,5}' into:Regex::RxMatcher) ~= nil ].
-	self should: [ (matcher search: '1') = false ].
-	self should: [ (matcher search: '12') = true ].
-	self should: [ (matcher search: '123') = true ].
-	self should: [ (matcher search: '1234') = true ].
-	self should: [ (matcher search: '12356') = true ].
-	self should: [ (matcher search: '123456') = true ].
-	self should: [ (matcher subexpression: 1) = '12345' ].
+        | matcher |
+
+        self should: [ (matcher := self compileRegex: '\d{2,5}' into:self matcherClass) ~= nil ].
+        self should: [ (matcher search: '1') = false ].
+        self should: [ (matcher search: '12') = true ].
+        self should: [ (matcher search: '123') = true ].
+        self should: [ (matcher search: '1234') = true ].
+        self should: [ (matcher search: '12356') = true ].
+        self should: [ (matcher search: '123456') = true ].
+        self should: [ (matcher subexpression: 1) = '12345' ].
 !
 
 test201
-	| matcher |
-
-	self should: [ (matcher := self compileRegex: '[0-9]{2,5}' into:Regex::RxMatcher) ~= nil ].
-	self should: [ (matcher search: '1') = false ].
-	self should: [ (matcher search: '12') = true ].
-	self should: [ (matcher search: '123') = true ].
-	self should: [ (matcher search: '1234') = true ].
-	self should: [ (matcher search: '12356') = true ].
-	self should: [ (matcher search: '123456') = true ].
-	self should: [ (matcher subexpression: 1) = '12345' ].
+        | matcher |
+
+        self should: [ (matcher := self compileRegex: '[0-9]{2,5}' into:self matcherClass) ~= nil ].
+        self should: [ (matcher search: '1') = false ].
+        self should: [ (matcher search: '12') = true ].
+        self should: [ (matcher search: '123') = true ].
+        self should: [ (matcher search: '1234') = true ].
+        self should: [ (matcher search: '12356') = true ].
+        self should: [ (matcher search: '123456') = true ].
+        self should: [ (matcher subexpression: 1) = '12345' ].
 !
 
 test202
-	| matcher |
-
-	self assert: ( (matcher := self compileRegex: '([0-9]{2,4}\s){2}' into:Regex::RxMatcher) ~= nil ).
-	self deny:   ( matcher matches: '1 1 ').
-	self assert: ( matcher matches: '12 12 ' ).
-	self assert: ( matcher matches: '12 123 ' ).
-	self assert: ( matcher matches: '123 12 ' ).
-	self assert: ( matcher matches: '123 123 ' ).
-	self assert: ( matcher matches: '1234 12 ' ).
-	self deny:   ( matcher matches: '123456 12 ' ).
-	self deny:   ( matcher matches: '12356 12 ' ).
+        | matcher |
+
+        self assert: ( (matcher := self compileRegex: '([0-9]{2,4}\s){2}' into:self matcherClass) ~= nil ).
+        self deny:   ( matcher matches: '1 1 ').
+        self assert: ( matcher matches: '12 12 ' ).
+        self assert: ( matcher matches: '12 123 ' ).
+        self assert: ( matcher matches: '123 12 ' ).
+        self assert: ( matcher matches: '123 123 ' ).
+        self assert: ( matcher matches: '1234 12 ' ).
+        self deny:   ( matcher matches: '123456 12 ' ).
+        self deny:   ( matcher matches: '12356 12 ' ).
 !
 
 testProtocol
@@ -1683,11 +2291,21 @@
                                 replacingMatchesWith: 'foo') = 'foo1bbb foo' ].
 !
 
+testSubExpression001
+     |matcher|
+
+     matcher := Regex::RxMatcher new
+                    initializeFromString:'(Jan|Feb|Mar|Apr|May|Jun|Jul|Aug|Sep|Oct|Nov|Dec)[ ]+(:isDigit::isDigit:?)[ ]*,[ ]*19(:isDigit::isDigit:)'
+                    ignoreCase:false.
+     self assert:(matcher matches:'Aug 6, 1996').
+     self assert:(matcher subexpression:2) = 'Aug'
+!
+
 testTermination001
     self assert:(('' allRegexMatches:'\S*') asArray = #('')).
-    self assert:(('t' allRegexMatches:'\S*') asArray = #('t')).
-    self assert:(('the' allRegexMatches:'\S*') asArray = #('the')).
-    self assert:(('the time' allRegexMatches:'\S*') asArray = #('the' 'time')).
+    self assert:(('t' allRegexMatches:'\S*') asArray = #('t' '')).
+    self assert:(('the' allRegexMatches:'\S*') asArray = #('the' '')).
+    self assert:(('the time' allRegexMatches:'\S*') asArray = #('the' 'time' '')).
 
     self assert:(('the   time' allRegexMatches:'\S*') size >= 2).
 
@@ -1711,6 +2329,25 @@
     self assert: ( 'caddar' matchesRegex: 'c(a|d)+r').
 !
 
+testCaseInsensitive
+        | matcher |
+        matcher := self matcherClass forString: 'the quick brown fox' ignoreCase: true.
+        self 
+                assert: (matcher search: 'the quick brown fox');
+                assert: (matcher search: 'The quick brown FOX');
+                assert: (matcher search: 'What do you know about the quick brown fox?');
+                assert: (matcher search: 'What do you know about THE QUICK BROWN FOX?')
+!
+
+testCaseSensitive
+        | matcher |
+        matcher := self matcherClass forString: 'the quick brown fox' ignoreCase: false.
+        self assert: (matcher search: 'the quick brown fox').
+        self deny: (matcher search: 'The quick brown FOX').
+        self assert: (matcher search: 'What do you know about the quick brown fox?').
+        self deny: (matcher search: 'What do you know about THE QUICK BROWN FOX?')
+!
+
 testCharacterSet
     "self debug: #testCharacterSet"
 
@@ -1769,6 +2406,81 @@
     self assert: ('01442128629839374565' matchesRegex: '[0-9]+').
 !
 
+testCopyReplacingMatches
+        "See that the match context is preserved while copying stuff between matches:"
+        
+        | matcher |
+        matcher := self matcherClass forString: '\<\d\D+'.
+        self 
+                assert: (matcher copy: '9aaa1bbb 8ccc' replacingMatchesWith: 'foo') equals: 'foo1bbb foo'
+!
+
+testCopyTranslatingMatches
+        | matcher |
+        matcher := self matcherClass forString: '\w+'.
+        self assert: (matcher copy: 'now is  the   time    ' translatingMatchesUsing: [ :each | each reversed ]) equals: 'won si  eht   emit    '
+!
+
+testEmptyStringAtBeginningOfLine
+        | matcher result |
+
+        matcher := self matcherClass forString: '^'.
+        result := (matcher copy: 'foo1 bar1' , String cr , 'foo2 bar2' replacingMatchesWith: '*').
+        self
+                assert: result = ('*foo1 bar1' , String cr , '*foo2 bar2')
+                description: 'An empty string at the beginning of a line'
+!
+
+testEmptyStringAtBeginningOfWord
+        | matcher result |
+
+        matcher := self matcherClass forString: '\<'.
+        result := (matcher copy: 'foo bar' replacingMatchesWith: '*').
+        self
+                assert: result = '*foo *bar'
+                description: 'An empty string at the beginning of a word'
+!
+
+testEmptyStringAtEndOfLine
+        | matcher |
+
+        matcher := self matcherClass forString: '$'.
+        self
+                assert: (matcher copy: 'foo1 bar1' , String cr , 'foo2 bar2' replacingMatchesWith: '*')
+                        = ('foo1 bar1*', String cr , 'foo2 bar2*')
+                description: 'An empty string at the end of a line'
+!
+
+testEmptyStringAtEndOfWord
+        | matcher |
+
+        matcher := self matcherClass forString: '\>'.
+        self
+                assert: (matcher copy: 'foo bar' replacingMatchesWith: '*')
+                        = 'foo* bar*'
+                description: 'An empty string at the end of a word'
+!
+
+testEmptyStringAtWordBoundary
+        | matcher result |
+
+        matcher := self matcherClass forString: '\b'.
+        result := (matcher copy: 'foo bar' replacingMatchesWith: '*').
+        self
+                assert: result = '*foo* *bar*'
+                description: 'An empty string at a word boundary'
+!
+
+testEmptyStringNotAtWordBoundary
+        | matcher |
+
+        matcher := self matcherClass forString: '\B'.
+        self
+                assert: (matcher copy: 'foo bar' replacingMatchesWith: '*')
+                        = 'f*o*o b*a*r'
+                description: 'An empty string not at a word boundary'
+!
+
 testMatchesInwW
     "self debug: #testMatchesInwW"
 
@@ -1873,6 +2585,16 @@
     self assert: ('^' matchesRegex: '[^01]').
 !
 
+testSplitJoinBoundaryCases
+        "Empty splitter, joiner or sequence."
+        self assert: ('' join: ('.' asRegex split: '')) equals: ''. "NB: Doesn't work with empty regex"
+!
+
+testSplitStringOnRegex
+        self assert: ('foobar' splitOn: '[aeiou]+' asRegex)
+                equals: #('f' 'b' 'r') asOrderedCollection
+!
+
 testStarPlusQuestionMark
     "self debug: #testStarPlusQuestionMark"
 
@@ -2383,6 +3105,404 @@
 										' ].'; cr ]]]]]
 ! !
 
+!RxTests methodsFor:'testing'!
+
+testRegex001
+	self runRegex: #('^.*$' 
+		'' true (1 '')
+		'a' true (1 'a')
+		'abc' true (1 'abc'))
+!
+
+testRegex002
+	self runRegex: #('a\w+c'
+		' abb_bbc ' true (1 'abb_bbc')
+		'abb-bc' false nil)
+!
+
+testRegex003
+	self runRegex: #('a\W+c'
+		' abb_bbc ' false nil
+		'abb-bc' false nil
+		'a.,:;-&!!"#%/()={[]}+?\~*''c' true (1 'a.,:;-&!!"#%/()={[]}+?\~*''c'))
+!
+
+testRegex004
+	self runRegex: #(':isVowel:'
+		'aei' true nil
+		'xyz' false nil)
+! !
+
+!RxTests methodsFor:'testing-extensions'!
+
+testStringAllRangesOfRegexMatches
+	| result |
+	result := 'aabbcc' allRangesOfRegexMatches: 'b+'.
+	self 
+		assert: result size equals: 1;
+		assert: result first first equals: 3;
+		assert: result first last equals: 4
+	
+!
+
+testStringAllRegexMatches
+	| result |
+	result := 'aabbcc' allRegexMatches: 'b+'.
+	self 
+		assert: result size equals: 1;
+		assert: result first equals: 'bb'
+!
+
+testStringAsRegex
+        
+        self assert: 'b+' asRegex class equals: Regex::RxParser preferredMatcherClass
+!
+
+testStringAsRegexIgnoringCase
+
+        self assert: 'b+' asRegexIgnoringCase class equals: Regex::RxParser preferredMatcherClass
+!
+
+testStringCopyWithRegexMatchesReplacedWith
+
+	self assert: ('aabbcc' copyWithRegex: 'b+' matchesReplacedWith: 'X') equals: 'aaXcc'
+!
+
+testStringCopyWithRegexMatchesTranslatedUsing
+	self assert: ('aabbcc' 
+		copyWithRegex: 'b+' 
+		matchesTranslatedUsing: [ :each | 
+			self assert: each equals: 'bb'.
+			'X' ]) equals: 'aaXcc'
+!
+
+testStringMatchesRegex
+	self deny: ('aabbcc' matchesRegex: 'a+').
+	self deny: ('aabbcc' matchesRegex: 'b+c+').
+	self assert: ('aabbcc' matchesRegex: 'a+b+c+')
+!
+
+testStringMatchesRegexIgnoringCase
+	self deny: ('AABBCC' matchesRegexIgnoringCase: 'a+').
+	self deny: ('AABBCC' matchesRegexIgnoringCase: 'b+c+').
+	self assert: ('AABBCC' matchesRegexIgnoringCase: 'a+b+c+')
+!
+
+testStringPrefixMatchesRegex
+	self assert: ('aabbcc' prefixMatchesRegex: 'a+').
+	self deny: ('aabbcc' prefixMatchesRegex: 'b+')
+!
+
+testStringPrefixMatchesRegexIgnoringCase
+	self assert: ('AABBCC' prefixMatchesRegexIgnoringCase: 'a+').
+	self deny: ('AABBCC' prefixMatchesRegexIgnoringCase: 'b+')
+!
+
+testStringRegexMatchesCollect
+	| result |
+	result := 'aabbcc' regex: 'b+' matchesCollect: [ :each | each asUppercase ].
+	self 
+		assert: result size equals: 1;
+		assert: result first equals: 'BB'
+!
+
+testStringRegexMatchesDo
+	| result |
+	result := OrderedCollection new.
+	'aabbcc' regex: 'b+' matchesDo: [ :each | result add: each ].
+	self 
+		assert: result size equals: 1;
+		assert: result first equals: 'bb'
+! !
+
+!RxTests methodsFor:'testing-henry'!
+
+henryReadme
+	self error: 'The tests in this category are based on the ones in Henry Spencer''s regexp.c package.'
+!
+
+testHenry013
+	self runRegex: #('.a.*'
+		'1234abc' true (1 '4abc')
+		'abcd' false nil)
+!
+
+testHenry059
+	self runRegex: #('[[:alpha:]]+'
+		' 123foo3 ' true (1 'foo')
+		'123foo' true (1 'foo')
+		'foo1b' true (1 'foo'))
+!
+
+testHenry101
+	self runRegex: #('a*'
+		'' true '')
+!
+
+testHenry102
+	self runRegex: #('abcd'
+		'abcd' true (1 'abcd'))
+!
+
+testHenry103
+	self runRegex: #('a(bc)d'
+		'abcd' true (1 'abcd' 2 'bc'))
+!
+
+testHenry104
+	self runRegex: #('([abc])*d'
+		'abbbcd' true (1 'abbbcd' 2 'c'))
+!
+
+testHenry105
+	self runRegex: #('([abc])*bcd'
+		'abcd' true (1 'abcd' 2 'a'))
+!
+
+testHenry106
+	self runRegex: #('a|b|c|d|e' 'e' true (1 'e'))
+!
+
+testHenry107
+	self runRegex: #('(a|b|c|d|e)f'
+		'ef' true (1 'ef' 2 'e'))
+	"	((a*|b))*	-	c	-	-"
+!
+
+testHenry108
+	self runRegex: #('abcd*efg' 
+		'abcdefg' true (1 'abcdefg'))
+!
+
+testHenry109
+	self runRegex: #('ab*' 
+		'xabyabbbz' true (1 'ab')
+		'xayabbbz' true (1 'a'))
+!
+
+testHenry110
+	self runRegex: #('(ab|cd)e' 'abcde' true (1 'cde' 2 'cd'))
+!
+
+testHenry111
+	self runRegex: #('[abhgefdc]ij' 'hij' true (1 'hij'))
+!
+
+testHenry112
+	self runRegex: #('^(ab|cd)e' 'abcde' false nil)
+	
+!
+
+testHenry113
+	self runRegex: #('(abc|)def' 'abcdef' true nil)
+	
+!
+
+testHenry114
+	self runRegex: #('(a|b)c*d' 'abcd' true (1 'bcd' 2 'b'))
+	
+!
+
+testHenry115
+	self runRegex: #('(ab|ab*)bc' 'abc' true (1 'abc' 2 'a'))
+	
+!
+
+testHenry116
+	self runRegex: #('a([bc]*)c*' 'abc' true (1 'abc' 2 'bc'))
+	
+!
+
+testHenry117
+	self runRegex: #('a([bc]*)(c*d)' 'abcd' true (1 'abcd' 2 'bc' 3 'd'))
+	
+!
+
+testHenry118
+	self runRegex: #('a([bc]+)(c*d)' 'abcd' true (1 'abcd' 2 'bc' 3 'd'))
+	
+!
+
+testHenry119
+	self runRegex: #('a([bc]*)(c+d)' 'abcd' true (1 'abcd' 2 'b' 3 'cd'))
+	
+!
+
+testHenry120
+	self runRegex: #('a[bcd]*dcdcde' 'adcdcde' true (1 'adcdcde'))
+	
+!
+
+testHenry121
+	self runRegex: #('a[bcd]+dcdcde' 'adcdcde' false nil)
+	
+!
+
+testHenry122
+	self runRegex: #('(ab|a)b*c' 'abc' true (1 'abc'))
+	
+!
+
+testHenry123
+	self runRegex: #('((a)(b)c)(d)' 'abcd' true (1 'abcd' 3 'a' 4 'b' 5 'd'))
+	
+!
+
+testHenry124
+	self runRegex: #('[ -~]*' 'abc' true (1 'abc'))
+	
+!
+
+testHenry125
+	self runRegex: #('[ -~ -~]*' 'abc' true (1 'abc'))
+	
+!
+
+testHenry126
+	self runRegex: #('[ -~ -~ -~]*' 'abc' true (1 'abc'))
+	
+!
+
+testHenry127
+	self runRegex: #('[ -~ -~ -~ -~]*' 'abc' true (1 'abc'))
+	
+!
+
+testHenry128
+	self runRegex: #('[ -~ -~ -~ -~ -~]*' 'abc' true (1 'abc'))
+	
+!
+
+testHenry129
+	self runRegex: #('[ -~ -~ -~ -~ -~ -~]*' 'abc' true (1 'abc'))
+	
+!
+
+testHenry130
+	self runRegex: #('[ -~ -~ -~ -~ -~ -~ -~]*' 'abc' true (1 'abc'))
+	
+!
+
+testHenry131
+	self runRegex: #('[a-zA-Z_][a-zA-Z0-9_]*' 'alpha' true (1 'alpha'))
+	
+!
+
+testHenry132
+	self runRegex: #('^a(bc+|b[eh])g|.h$' 'abh' true (1 'bh' 2 nil))
+	
+!
+
+testHenry133
+	self runRegex: #('(bc+d$|ef*g.|h?i(j|k))' 
+		'effgz' true (1 'effgz' 2 'effgz' 3 nil)
+		'ij' true (1 'ij' 2 'ij' 3 'j')
+		'effg' false nil
+		'bcdd' false nil
+		'reffgz' true (1 'effgz' 2 'effgz' 3 nil))
+!
+
+testHenry134
+	self runRegex: #('(((((((((a)))))))))' 'a' true (1 'a'))
+!
+
+testHenry135
+	self runRegex: #('multiple words of text' 
+		'uh-uh' false nil
+		'multiple words of text, yeah' true (1 'multiple words of text'))
+!
+
+testHenry136
+	self runRegex: #('(.*)c(.*)' 'abcde' true (1 'abcde' 2 'ab' 3 'de'))
+!
+
+testHenry137
+	self runRegex: #('\((.*), (.*)\)' '(a, b)' true (2 'a' 3 'b'))
+! !
+
+!RxTests methodsFor:'testing-protocol'!
+
+testMatches
+	| matcher |
+	matcher := self matcherClass forString: '\w+'.
+	self assert: (matcher matches: 'now').
+	self deny: (matcher matches: 'now is')
+!
+
+testMatchesIn
+	| matcher |
+	matcher := self matcherClass forString: '\w+'.
+	self assert: (matcher matchesIn: 'now is the time') asArray 
+		= #('now' 'is' 'the' 'time')
+!
+
+testMatchesInCollect
+	| matcher |
+	matcher := self matcherClass forString: '\w+'.
+	self assert: (matcher
+		matchesIn: 'now is the time'
+		collect: [ :each | each reversed ]) asArray
+			= #('won' 'si' 'eht' 'emit')
+!
+
+testMatchesInDo
+	| matcher expected |
+	matcher := self matcherClass forString: '\w+'.
+	expected := #('now' 'is' 'the' 'time') asOrderedCollection.
+	matcher matchesIn: 'now is the time' do: [ :each | self assert: each = expected removeFirst ].
+	self assertEmpty: expected
+!
+
+testMatchesOnStream
+	| matcher |
+	matcher := self matcherClass forString: '\w+'.
+	self assert: (matcher matchesOnStream: 'now is the time' readStream) asArray 
+		= #('now' 'is' 'the' 'time')
+!
+
+testMatchesOnStreamCollect
+	| matcher |
+	matcher := self matcherClass forString: '\w+'.
+	self assert: (matcher 
+		matchesOnStream: 'now is the time' readStream 
+		collect: [ :each | each reversed ]) asArray
+			= #('won' 'si' 'eht' 'emit')
+!
+
+testMatchesOnStreamDo
+	| matcher expected |
+	matcher := self matcherClass forString: '\w+'.
+	expected := #('now' 'is' 'the' 'time') asOrderedCollection.
+	matcher matchesOnStream: 'now is the time' readStream do: [ :each | self assert: each = expected removeFirst ].
+	self assertEmpty: expected
+!
+
+testMatchesStream
+	| matcher |
+	matcher := self matcherClass forString: '\w+'.
+	self assert: (matcher matchesStream: 'now' readStream).
+	self deny: (matcher matchesStream: 'now is' readStream)
+!
+
+testMatchingRangesIn
+	| matcher expected |
+	matcher := self matcherClass forString: '\w+'.
+	expected := #(1 3 5 6 8 10 12 15) asOrderedCollection.
+	(matcher matchingRangesIn: 'now is the time')
+		do: [ :range | 
+			self assert: range first = expected removeFirst.
+			self assert: range last = expected removeFirst ].
+	self assertEmpty: expected
+!
+
+testSubexpressionCount
+	| matcher |
+	#(('a' 1) ('a(b)' 2) ('a(b(c))' 3) ('(a)(b)' 3) ('(a(b))*' 3)) do: [ :pair |
+		matcher := self matcherClass forString: pair first.
+		matcher supportsSubexpressions 
+			ifTrue: [ self assert: matcher subexpressionCount equals: pair last ] ]
+! !
+
 !RxTests class methodsFor:'documentation'!
 
 version