RegressionTests__RxTests.st
author Claus Gittinger <cg@exept.de>
Tue, 25 Feb 2020 17:19:49 +0100
changeset 2586 7dc7be5a6f3d
parent 2409 83ccbaa621f8
permissions -rw-r--r--
#OTHER by cg s

"{ Encoding: utf8 }"

"{ Package: 'stx:goodies/regression' }"

"{ NameSpace: RegressionTests }"

TestCase subclass:#RxTests
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'tests-Regression-Collections-Utilities'
!

!RxTests class methodsFor:'documentation'!

documentation
"
    regex tests.
"
! !

!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."

        | syntaxTree |

        "/ ^ Regex::RxMatcher2 forString: 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 |
	Transcript show: 'Testing matcher protocol...'.
	matcher := matcherClass forString: '\w+'.
	(matcher matchesIn: 'now is the time') asArray = #('now' 'is' 'the' 'time')
		ifFalse: [self error: 'matchesIn: test failed'].
	(matcher copy: 'now is  the   time    ' translatingMatchesUsing: [:s | s reverse])
		= 'won si  eht   emit    '
		ifFalse: [self error: 'copy:translatingMatchesWith: test failed'].
	"See that the match context is preserved while copying stuff between matches:"
	((matcherClass forString: '\<\d\D+')
		copy: '9aaa1bbb 8ccc'
		replacingMatchesWith: 'foo') = 'foo1bbb foo'
			ifFalse: [self error: 'test failed'].
	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 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 new runTestsForMatcher: Regex::RxMatcher"

        self
                runRegexTestsForMatcher: matcherClass;
                runProtocolTestsForMatcher: matcherClass
! !

!RxTests methodsFor:'profiling'!

bigHonkingStream
    ^ '~/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"
!

frequentMatchProfile
	"
	TimeProfiler profile: [self frequentMatchProfile]
	Time millisecondsToRun: [self frequentMatchProfile]
	"

	| stream matcher count |
	stream := self bigHonkingStream.
	count := 0.
	matcher := '\<\w+' asRegex.
	[
		[matcher searchStream: stream] whileTrue: [count := count + 1].
	]
	valueNowOrOnUnwindDo: [stream close].
	^count
!

rareMatchProfile
        "                          o:Regex::RxMatcher
        TimeProfiler profile: [self new rareMatchProfile]
        Time millisecondsToRun: [self new rareMatchProfile] -> 22760         
        "

        | stream matcher count |
        stream := self bigHonkingStream.
        count := 0.
        matcher := 'foo' asRegex.
        [
                [matcher searchStream: stream] whileTrue: [count := count + 1].
        ]
        valueNowOrOnUnwindDo: [stream close].
        ^count

    "Modified (comment): / 04-06-2019 / 10:54:16 / Claus Gittinger"
!

singleCharPrefixMatchProfile
	"
	TimeProfiler profile: [self singleCharPrefixMatchProfile]
	Time millisecondsToRun: [self singleCharPrefixMatchProfile]
	"

	| stream matcher count |
	stream := self bigHonkingStream.
	count := 0.
	matcher := 'm(e|a)th' asRegex.
	[
		[matcher searchStream: stream] whileTrue: [count := count + 1].
	]
	valueNowOrOnUnwindDo: [stream close].
	^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
    "patt.   input   match-expected  matched-expression
     abc     abc     y              &       abc
     abc     xbc     n              -       -
     abc     axc     n              -       -
     abc     abx     n              -       -
     abc     xabcy   y              &       abc
     abc     ababc   y              &       abc
    "

    |matcher|

    self
        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 ].
    self should:[ (matcher search:'axc') = false ].
    self should:[ (matcher search:'abx') = false ].
    self should:[ (matcher search:'xabcy') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].
    self should:[ (matcher search:'ababc') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].

    "
     self new test01
    "
!

test002
    "patt.   input   match-expected  matched-expression
     ab*c    abc     y                  &       abc
    "

    |matcher|

    self
        should:[ (matcher := self compileRegex:'ab*c' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'abc') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].

    "
     self new test02
    "
!

test003
    "patt.   input   match-expected  matched-expression
     ab*bc   abc     y              &       abc
     ab*bc   abbc    y              &       abbc
     ab*bc   abbbbc  y              &       abbbbc
    "

    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = 'abbc' ].
    self should:[ (matcher search:'abbbbc') = true ].
    self should:[ (matcher subexpression:1) = 'abbbbc' ].

    "
     self new test02
    "
!

test004
    "patt.   input   match-expected  matched-expression
     ab+bc   abbc    y              &       abbc
     ab+bc   abc     n              -       -
     ab+bc   abq     n              -       -
     ab+bc   abbbbc  y              &       abbbbc
    "

    |matcher|

    self
        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 ].
    self should:[ (matcher search:'abq') = false ].
    self should:[ (matcher search:'abbbbc') = true ].
    self should:[ (matcher subexpression:1) = 'abbbbc' ].

    "
     self new test04
    "
!

test005
    "patt.   input   match-expected  matched-expression
     ab?bc   abbc    y              &       abbc
     ab?bc   abc     y              &       abc
     ab?bc   abbbbc  n              -       -
    "

    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = 'abc' ].
    self should:[ (matcher search:'abbbbc') = false ].

    "
     self new test05
    "
!

test005b
    "patt.   input   match-expected  matched-expression
     ab?c    abc     y              &       abc
    "

    |matcher|

    self
        should:[ (matcher := self compileRegex:'ab?c' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'abc') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].

    "
     self new test05b
    "
!

test006
    "patt.   input   match-expected  matched-expression
     ^abc$   abc     y       &       abc
     ^abc$   abcc    n       -       -
     ^abc$   aabc    n       -       -
    "

    |matcher|

    self
        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 ].
    self should:[ (matcher search:'aabc') = false ].

    "
     self new test06
    "
!

test007
    "patt.   input   match-expected  matched-expression
     ^abc    abcc    y       &       abc
    "

    |matcher|

    self
        should:[ (matcher := self compileRegex:'^abc' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'abcc') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].

    "
     self new test07
    "
!

test008
    "patt.   input   match-expected  matched-expression
    abc$    aabc    y       &       abc
    "

    |matcher|

    self
        should:[ (matcher := self compileRegex:'abc$' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'aabc') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].

    "
     self new test08
    "
!

test009
    "patt.   input   match-expected  matched-expression
     ^       abc     y       &
    "

    |matcher|

    self should:[ (matcher := self compileRegex:'^' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'abc') = true ].

    "
     self new test09
    "
!

test010
    "patt.   input   match-expected  matched-expression
     $       abc     y       &
    "

    |matcher|

    self should:[ (matcher := self compileRegex:'$' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'abc') = true ].

    "
     self new test10
    "
!

test011
    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = 'axc' ].
!

test012
    |matcher|

    self
        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
        ].
    self should:[ (matcher search:'axyzd') = false ].
!

test013
    |matcher|

    self
        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 ].
!

test014
    |matcher|

    self
        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 ].
!

test015
    |matcher|

    self
        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 ].
!

test016
    |matcher|

    self
        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 ].
!

test017
    |matcher|

    self
        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 ].
!

test018
    |matcher|

    self
        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 ].
!

test019
    |matcher|

    self
        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 ].
!

test020
    |matcher|

    self
        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 ].
!

test021
    |matcher|

    self
        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 ].
!

test022
    |matcher|

    self
        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 ].
!

test023
    |matcher|

    self
        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 ].
!

test024
    |matcher|

    self
        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 ].
!

test025
    |matcher|

    self
        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 ].
!

test026
    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = 'foo' ].
!

test027
    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = 'antique' ].
    self should:[ (matcher search:'goofy foobar') = false ].
!

test028
    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = 'fo' ].
!

test029
    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = 'ase' ].
    self should:[ (matcher search:'smalltalk shall overcome') = true ].
    self should:[ (matcher subexpression:1) = 'alltalk' ].
    self should:[ (matcher search:'foonix is better') = false ].
!

test030
    |matcher|

    self
        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 ].
    self should:[ (matcher search:'fooa') = true ].
    self should:[ (matcher search:'fooargh') = false ].
!

test031
    |matcher|

    self
        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' ].
    self should:[ (matcher search:'abcde') = false ].
!

test032
    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = 'foonix' ].
    self should:[ (matcher search:' foo') = true ].
    self should:[ (matcher search:' 12foo') = false ].
    self should:[ (matcher search:'barfoo') = false ].
!

test033
    |matcher|

    self
        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' ].
    self should:[ (matcher search:'abfoo') = false ].
!

test034
    |matcher|

    self
        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' ].
!

test035
    |matcher|

    self
        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' ].
!

test036
    |matcher|

    self
        should:[ (matcher := self compileRegex:'a[b-d]' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'aac') = true ].
    self should:[ (matcher subexpression:1) = 'ac' ].
!

test037
    |matcher|

    self
        should:[ (matcher := self compileRegex:'a[-b]' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'a-') = true ].
    self should:[ (matcher subexpression:1) = 'a-' ].
!

test038
    |matcher|

    self
        should:[ (matcher := self compileRegex:'a[b-]' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'a-') = true ].
    self should:[ (matcher subexpression:1) = 'a-' ].
!

test039
    |matcher|

    self
        should:[ (matcher := self compileRegex:'a[a-b-c]' into:self matcherClass) = nil ].
!

test040
    |matcher|

    self
        should:[ (matcher := self compileRegex:'[k]' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'ab') = false ].
!

test041
    |matcher|

    self
        should:[ (matcher := self compileRegex:'a[b-a]' into:self matcherClass) = nil ].
!

test042
    |matcher|

    self
        should:[ (matcher := self compileRegex:'a[]b' into:self matcherClass) = nil ].
!

test043
    |matcher|

    self should:[ (matcher := self compileRegex:'a[' into:self matcherClass) = nil ].
!

test044
    |matcher|

    self should:[ (matcher := self compileRegex:'a]' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'a]') = true ].
    self should:[ (matcher subexpression:1) = 'a]' ].
!

test045
    |matcher|

    self
        should:[ (matcher := self compileRegex:'a[]]b' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'a]b') = true ].
    self should:[ (matcher subexpression:1) = 'a]b' ].
!

test046
    |matcher|

    self
        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 ].
!

test047
    |matcher|

    self
        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 ].
!

test048
    |matcher|

    self
        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' ].
!

test049
    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = '0123e456' ].
    self should:[ (matcher search:'0123e45g78') = true ].
    self should:[ (matcher subexpression:1) = '0123e45' ].
!

test050
    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = '0123e456' ].
    self should:[ (matcher search:'0123e45g78') = true ].
    self should:[ (matcher subexpression:1) = '0123e45' ].
!

test051
    |matcher|

    self
        should:[ (matcher := self compileRegex:'[\D]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'123abc45def78') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].
!

test052
    |matcher|

    self
        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 ].
    self should:[ (matcher subexpression:1) = '0123e456' ].
    self should:[ (matcher search:'0123e45g78') = true ].
    self should:[ (matcher subexpression:1) = '0123e45' ].
!

test053
    |matcher|

    self
        should:[ (matcher := self compileRegex:'[\s]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'2  spaces') = true ].
    self should:[ (matcher subexpression:1) = '  ' ].
!

test054
    |matcher|

    self
        should:[ (matcher := self compileRegex:'[\S]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'  word12!!@#$  ') = true ].
    self should:[ (matcher subexpression:1) = 'word12!!@#$' ].
!

test055
    |matcher|

    self
        should:[ (matcher := self compileRegex:'[\w]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'       foo123bar       45') = true ].
    self should:[ (matcher subexpression:1) = 'foo123bar' ].
!

test056
    |matcher|

    self
        should:[ (matcher := self compileRegex:'[\W]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'fii234!!@#$34f') = true ].
    self should:[ (matcher subexpression:1) = '!!@#$' ].
!

test057
    |matcher|

    self
	should:[ (matcher := self compileRegex:'[^[:alnum:]]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'fii234!!@#$34f') = true ].
    self should:[ (matcher subexpression:1) = '!!@#$' ].
!

test058
    |matcher|

    self
	should:[
	    (matcher := self compileRegex:'[%&[:alnum:]]+' into:self matcherClass) ~= nil
	].
    self should:[ (matcher search:'foo%3') = true ].
    self should:[ (matcher subexpression:1) = 'foo%3' ].
    self should:[ (matcher search:'foo34&rt4$57a') = true ].
    self should:[ (matcher subexpression:1) = 'foo34&rt4' ].
    self should:[ (matcher search:'!!@#$') = false ].
!

test059
    |matcher|

    self
	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 ].
    self should:[ (matcher subexpression:1) = 'foo' ].
    self should:[ (matcher search:'foo1b') = true ].
    self should:[ (matcher subexpression:1) = 'foo' ].
!

test060
    |matcher|

    self
	should:[ (matcher := self compileRegex:'[[:cntrl:]]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:' a 1234asdf') = false ].
!

test061
    |matcher|

    self
	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 ].
    self should:[ (matcher subexpression:1) = 'lower' ].
!

test062
    |matcher|

    self
	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 ].
    self should:[ (matcher subexpression:1) = 'UPPER' ].
!

test063
    |matcher|

    self
	should:[ (matcher := self compileRegex:'[[:space:]]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'2  spaces') = true ].
    self should:[ (matcher subexpression:1) = '  ' ].
!

test064
    |matcher|

    self
	should:[ (matcher := self compileRegex:'[^[:space:]]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'  word12!!@#$  ') = true ].
    self should:[ (matcher subexpression:1) = 'word12!!@#$' ].
!

test065
    |matcher|

    self
	should:[ (matcher := self compileRegex:'[[:graph:]]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'abc') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].
!

test066
    |matcher|

    self
	should:[ (matcher := self compileRegex:'[[:print:]]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'abc') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].
!

test067
    |matcher|

    self
	should:[ (matcher := self compileRegex:'[^[:punct:]]+' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'!!hello,world!!') = true ].
    self should:[ (matcher subexpression:1) = 'hello' ].
!

test068
    |matcher|

    self
	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 ].
    self should:[ (matcher subexpression:1) = 'fedcba0123456789ABCDEF' ].
!

test069
    |matcher|

    self
	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 ].
    self should:[ (matcher subexpression:1) = 'ab' ].
!

test070
    |matcher|

    self
	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) = '' ].
!

test071
    |matcher|

    self should:[ (matcher := self compileRegex:'()*' into:self matcherClass) = nil ].
!

test072
    |matcher|

    self should:[ (matcher := self compileRegex:'*a' into:self matcherClass) = nil ].
!

test073
    |matcher|

    self should:[ (matcher := self compileRegex:'^*' into:self matcherClass) = nil ].
!

test074
    |matcher|

    self should:[ (matcher := self compileRegex:'$*' into:self matcherClass) = nil ].
!

test075
    |matcher|

    self
	should:[ (matcher := self compileRegex:'(*)b' into:self matcherClass) = nil ].
!

test076
    |matcher|

    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:self matcherClass) = nil ].
!

test078
    |matcher|

    self
	should:[ (matcher := self compileRegex:'a\(b' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'a(b') = true ].
    self should:[ (matcher subexpression:1) = 'a(b' ].
!

test079
    |matcher|

    self
	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 ].
    self should:[ (matcher subexpression:1) = 'a((b' ].
!

test080
    |matcher|

    self
	should:[ (matcher := self compileRegex:'a\\b' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'a\b') = true ].
    self should:[ (matcher subexpression:1) = 'a\b' ].
!

test081
    |matcher|

    self
	should:[ (matcher := self compileRegex:'abc)' into:self matcherClass) = nil ].
!

test082
    |matcher|

    self
	should:[ (matcher := self compileRegex:'(abc' into:self matcherClass) = nil ].
!

test083
    |matcher|

    self
	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' ].
    self should:[ (matcher subexpression:3) = 'a' ].
!

test084
    |matcher|

    self
	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' ].
    self should:[ (matcher subexpression:3) = 'c' ].
!

test085
    |matcher|

    self
	should:[ (matcher := self compileRegex:'a+b+c' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'aabbabc') = true ].
    self should:[ (matcher subexpression:1) = 'abc' ].
!

test086
    |matcher|

    self should:[ (matcher := self compileRegex:'a**' into:self matcherClass) = nil ].
!

test087
    |matcher|

    self should:[ (matcher := self compileRegex:'a*?' into:self matcherClass) = nil ].
!

test088
    |matcher|

    self
	should:[ (matcher := self compileRegex:'(a*)*' into:self matcherClass) = nil ].
!

test089
    |matcher|

    self
	should:[ (matcher := self compileRegex:'(a*)+' into:self matcherClass) = nil ].
!

test090
    |matcher|

    self
	should:[ (matcher := self compileRegex:'(a|)*' into:self matcherClass) = nil ].
!

test091
    |matcher|

    self
	should:[ (matcher := self compileRegex:'(a*|b)*' into:self matcherClass) = nil ].
!

test092
    |matcher|

    self
	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' ].
!

test093
    |matcher|

    self
	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' ].
!

test094
    |matcher|

    self
	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' ].
!

test095
    |matcher|

    self
	should:[ (matcher := self compileRegex:'[^ab]*' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'cde') = true ].
    self should:[ (matcher subexpression:1) = 'cde' ].
!

test096
    |matcher|

    self
	should:[ (matcher := self compileRegex:'(^)*' into:self matcherClass) = nil ].
!

test097
    |matcher|

    self
	should:[ (matcher := self compileRegex:'(ab|)*' into:self matcherClass) = nil ].
!

test098
    |matcher|

    self should:[ (matcher := self compileRegex:')(' into:self matcherClass) = nil ].
!

test099
    |matcher|

    self should:[ (matcher := self compileRegex:'' into:self matcherClass) ~= nil ].
    self should:[ (matcher search:'abc') = true ].
    self should:[ (matcher subexpression:1) = '' ].
!

test100
    | matcher |

    self should: [ (matcher := self compileRegex: 'abc' into:self matcherClass) ~= nil ].
    self should: [ (matcher search: '') = false ].

    "
     self new test100
    "
!

test101
    | matcher |

    self should: [ (matcher := self compileRegex: 'a*' into:self matcherClass) ~= nil ].
    self should: [ (matcher search: '') = true ].

    "
     self new test101
    "
!

test102
    | matcher |

    self should: [ (matcher := self compileRegex: 'abcd' into:self matcherClass) ~= nil ].
    self should: [ (matcher search: 'abcd') = true ].
    self should: [ (matcher subexpression: 1) = 'abcd' ].

    "
     self new test102
    "
!

test103
    | matcher |

    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' ].

    "
     self new test103
    "
!

test104
	| matcher |


	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' ].
!

test105
	| matcher |


	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' ].
!

test106
	| matcher |


	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' ].
!

test107
	| matcher |


	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' ].
!

test108
	| matcher |


	self should: [ (matcher := self compileRegex: 'abcd*efg' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abcdefg') = true ].
	self should: [ (matcher subexpression: 1) = 'abcdefg' ].
!

test109
	| matcher |


	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 ].
	self should: [ (matcher subexpression: 1) = 'a' ].
!

test110
	| matcher |


	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' ].
!

test111
	| matcher |


	self should: [ (matcher := self compileRegex: '[abhgefdc]ij' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'hij') = true ].
	self should: [ (matcher subexpression: 1) = 'hij' ].
!

test112
	| matcher |


	self should: [ (matcher := self compileRegex: '^(ab|cd)e' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abcde') = false ].
!

test113
	| matcher |


	self should: [ (matcher := self compileRegex: '(abc|)def' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abcdef') = true ].
!

test114
	| matcher |


	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' ].
!

test115
	| matcher |


	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' ].
!

test116
	| matcher |


	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' ].
!

test117
	| matcher |


	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' ].
	self should: [ (matcher subexpression: 3) = 'd' ].
!

test118
	| matcher |


	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' ].
	self should: [ (matcher subexpression: 3) = 'd' ].
!

test119
	| matcher |


	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' ].
	self should: [ (matcher subexpression: 3) = 'cd' ].
!

test120
	| matcher |


	self should: [ (matcher := self compileRegex: 'a[bcd]*dcdcde' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'adcdcde') = true ].
	self should: [ (matcher subexpression: 1) = 'adcdcde' ].
!

test121
	| matcher |


	self should: [ (matcher := self compileRegex: 'a[bcd]+dcdcde' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'adcdcde') = false ].
!

test122
	| matcher |


	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' ].
!

test123
	| matcher |


	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' ].
	self should: [ (matcher subexpression: 4) = 'b' ].
	self should: [ (matcher subexpression: 5) = 'd' ].
!

test124
	| matcher |


	self should: [ (matcher := self compileRegex: '[ -~]*' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abc') = true ].
	self should: [ (matcher subexpression: 1) = 'abc' ].
!

test125
	| matcher |


	self should: [ (matcher := self compileRegex: '[ -~ -~]*' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abc') = true ].
	self should: [ (matcher subexpression: 1) = 'abc' ].
!

test126
	| matcher |


	self should: [ (matcher := self compileRegex: '[ -~ -~ -~]*' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abc') = true ].
	self should: [ (matcher subexpression: 1) = 'abc' ].
!

test127
	| matcher |


	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~]*' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abc') = true ].
	self should: [ (matcher subexpression: 1) = 'abc' ].
!

test128
	| matcher |


	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~ -~]*' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abc') = true ].
	self should: [ (matcher subexpression: 1) = 'abc' ].
!

test129
	| matcher |


	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~ -~ -~]*' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abc') = true ].
	self should: [ (matcher subexpression: 1) = 'abc' ].
!

test130
	| matcher |


	self should: [ (matcher := self compileRegex: '[ -~ -~ -~ -~ -~ -~ -~]*' into:self matcherClass) ~= nil ].
	self should: [ (matcher search: 'abc') = true ].
	self should: [ (matcher subexpression: 1) = 'abc' ].
!

test131
	| matcher |


	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: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: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: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: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: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:self matcherClass) ~= nil ].
        self should: [ (matcher search: '(a, b)') = true ].
        self should: [ (matcher subexpression: 2) = 'a' ].
        self should: [ (matcher subexpression: 3) = 'b' ].
!

test138
        | matcher |

        matcher := 'aa*' asRegex.
        self assert:(matcher matches:'a').
        self assert:(matcher matches:'aa').
        self assert:(matcher matches:'aaa').
        self deny:(matcher matches:'ab').
        self deny:(matcher matches:'b').

    "Created: / 15-06-2019 / 09:44:56 / Claus Gittinger"
!

test199
    |matcher|

    self
        should:[ (matcher := self compileRegex:'a{}b' into:self matcherClass) = nil ].
!

test200
        | 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: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: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
        | matcher |

        self should: [ (matcher := Regex::RxMatcher forString: '\w+') ~= nil ].
        self should: [ (matcher matchesIn: 'now is the time') asArray = #('now' 'is' 'the' 'time') ].
        self should: [ (matcher copy: 'now is  the   time    ' translatingMatchesUsing: [:s | s reverse]) = 'won si  eht   emit    ' ].

        "See that the match context is preserved while copying stuff between matches:"

        self should: [ ((Regex::RxMatcher forString: '\<\d\D+')
                                copy: '9aaa1bbb 8ccc'
                                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:(('the   time' allRegexMatches:'\S*') size >= 2).

    "Created: / 04-05-2017 / 19:45:04 / mawalch"
    "Modified (format): / 07-06-2017 / 10:06:59 / mawalch"
! !

!RxTests methodsFor:'test suite - old'!

testCadrMatching
    "self debug: #testCadrMatching"

    "A bit more complex example is the following expression, matching the
name of any of the Lisp-style `car', `cdr', `caar', `cadr',
... functions:"

    self assert: ( 'car' matchesRegex: 'c(a|d)+r').
    self assert: ( 'cdr' matchesRegex: 'c(a|d)+r').
    self assert: ( 'caar' matchesRegex: 'c(a|d)+r').
    self assert: ( 'cadr' matchesRegex: 'c(a|d)+r').
    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"

    "So far, we have used only characters as the 'smallest' components of
regular expressions. There are other, more `interesting', components.
A character set is a string of characters enclosed in square
brackets. It matches any single character if it appears between the
brackets. For example, `[01]' matches either `0' or `1':"

    self assert: ('0' matchesRegex: '[01]').
    self deny: ('3' matchesRegex: '[01]').
    self deny: ('11' matchesRegex: '[01]'). "-- false: a set matches only one character"
    self assert: ('[01]' asRegex hasMatchesIn:'11' ). "-- true"
    self deny: ('01' matchesRegex: '[01]').
!

testCharacterSetBinaryNumber
    "self debug: #testCharacterSetBinaryNumber"

    "Using plus operator, we can build the following binary number
recognizer:"
    self assert: ('10010100' matchesRegex: '[01]+').
    self deny: ('10001210' matchesRegex: '[01]+')
!

testCharacterSetInversion
    "self debug: #testCharacterSetInversion"

    "If the first character after the opening bracket is `^', the set is
inverted: it matches any single character *not* appearing between the
brackets:"

    self deny: ('0' matchesRegex: '[^01]').
    "0 appears in 01 so there is no match"

    self assert: ('3' matchesRegex: '[^01]').
    "3 is not in 01 so it matches"


    self deny: ('30' matchesRegex: '[^01]').
    self deny: ('33333333333333333333333330' matchesRegex: '[^01]').
    "there is one zero so it does not match"
!

testCharacterSetRange
    "self debug: #testCharacterSetRange"

    "For convenience, a set may include ranges: pairs of characters
separated with `-'. This is equivalent to listing all characters
between them: `[0-9]' is the same as `[0123456789]'. "

    self assert: ('0' matchesRegex: '[0-9]').
    self assert: ('9' matchesRegex: '[0-9]').
    self deny: ('a' matchesRegex: '[0-9]').
    self deny: ('01' matchesRegex: '[0-9]').
    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"

    "1. Backslash escapes similar to those in Perl are allowed in patterns:
    \w  any word constituent character (equivalent to [a-zA-Z0-9_])
    \W  any character but a word constituent (equivalent to [^a-xA-Z0-9_]"

    self assert: ('\w+' asRegex matchesIn: 'now is the time') asArray = #('now' 'is' 'the' 'time').
    self assert: ('\W+' asRegex matchesIn: 'now is the time') asArray = #(' ' ' ' ' ').


    "/ self halt.
    "why do we get that"
    self assert: ('\w' asRegex matchesIn: 'now') asArray = #('n' 'o' 'w').
!

testOrOperator
    "self debug: #testOrOperator"

    "The last operator is `|' meaning `or'. It is placed between two
regular expressions, and the resulting expression matches if one of
the expressions matches. It has the lowest possible precedence (lower
than sequencing). For example, `ab*|ba*' means `a followed by any
number of b's, or b followed by any number of a's':"

    self assert: ('abb' matchesRegex: 'ab*|ba*').
    self assert: ('baa' matchesRegex: 'ab*|ba*').
    self deny: ('baab' matchesRegex: 'ab*|ba*').


    "It is possible to write an expression matching an empty string, for
example: `a|'.  However, it is an error to apply `*', `+', or `?' to
such expression: `(a|)*' is an invalid expression."

    self should: ['(a|)*' asRegex] raise: Error.
!

testQuotingOperators
    "self debug: #testQuotingOperators"

    "As we have seen, characters `*', `+', `?', `(', and `)' have special
meaning in regular expressions. If one of them is to be used
literally, it should be quoted: preceded with a backslash. (Thus,
backslash is also special character, and needs to be quoted for a
literal match--as well as any other special character described
further)."

    self deny: ('ab*' matchesRegex: 'ab*'). "   -- false: star in the right string is special"
    self assert: ('ab*' matchesRegex: 'ab\*').
    self assert: ('a\c' matchesRegex: 'a\\c').
!

testSimpleMatchesRegex
    "self debug: #testSimpleMatchesRegex"

    "The simplest regular expression is a single character.  It matches
exactly that character. A sequence of characters matches a string with
exactly the same sequence of characters:"

    self assert: ('a' matchesRegex: 'a').
    self assert: ('foobar' matchesRegex: 'foobar')  .
    self deny: ('blorple' matchesRegex: 'foobar')
!

testSimpleMatchesRegexWithStar
    "self debug: #testSimpleMatchesRegexWithStar"

    "The above paragraph in testSimpleMatchesRegex introduced a primitive regular expression (a
character), and an operator (sequencing). Operators are applied to
regular expressions to produce more complex regular expressions.
Sequencing (placing expressions one after another) as an operator is,
in a certain sense, `invisible'--yet it is arguably the most common.
A more `visible' operator is Kleene closure, more often simply
referred to as `a star'.  A regular expression followed by an asterisk
matches any number (including 0) of matches of the original
expression. For example:"

    self assert: ('ab' matchesRegex: 'a*b').
    self assert: ('aaaaab' matchesRegex: 'a*b').
    self assert: ('b' matchesRegex: 'a*b').
    self deny: ('aac' matchesRegex: 'a*b').
!

testSpecialCharacterInSetRange
    "self debug: #testSpecialCharacterInSetRange"

    "Special characters within a set are `^', `-', and `]' that closes the
set. Below are the examples of how to literally use them in a set:
    [01^]       -- put the caret anywhere except the beginning
    [01-]       -- put the dash as the last character
    []01]       -- put the closing bracket as the first character
    [^]01]          (thus, empty and universal sets cannot be specified)"

    self assert: ('0' matchesRegex: '[01^]').
    self assert: ('1' matchesRegex: '[01^]').
    self assert: ('^' matchesRegex: '[01^]').

    self deny: ('0' matchesRegex: '[^01]').
    self deny: ('1' matchesRegex: '[^01]').

    "[^abc] means that everything except abc is matche"
    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"

    "Two other operators similar to `*' are `+' and `?'. `+' (positive
closure, or simply `plus') matches one or more occurrences of the
original expression. `?' (`optional') matches zero or one, but never
more, occurrences."

    self assert: ('ac' matchesRegex: 'ab*c').
    self deny: ('ac' matchesRegex: 'ab+c').         "-- false: need at least one b"
    self assert: ('abbc' matchesRegex: 'ab+c').
    self assert: ('abbbbbbc' matchesRegex: 'ab+c').
    self deny: ('abbc' matchesRegex: 'ab?c')        "-- false: too many b's"
!

testStarPrecedence
    "self debug: #testStarPrecedence"

    "A star's precedence is higher than that of sequencing. A star applies
to the shortest possible subexpression that precedes it. For example,
'ab*' means `a followed by zero or more occurrences of b', not `zero
or more occurrences of ab':"

    self assert: ('abbb' matchesRegex: 'ab*').
    self deny: ('abab' matchesRegex: 'ab*').

    "To actually make a regex matching `zero or more occurrences of ab',
`ab' is enclosed in parentheses:"
    self assert: ('abab' matchesRegex: '(ab)*').
    self deny: ('abcab' matchesRegex: '(ab)*')
!

testTranslatingMatchesUsing
    "self debug: #testTranslatingMatchesUsing"


    self assert: ('\<t\w+' asRegexIgnoringCase
	copy: 'now is the Time'
	translatingMatchesUsing: [:match | match asUppercase]) = 'now is THE TIME'.

    "the regular expression matches words beginning with either an uppercase or a lowercase T"
!

xtest1
	self runTestsForMatcher: Regex::RxMatcher
!

xtest: aMatcher with: testString expect: expected withSubexpressions: subexpr

	| got |
	Transcript tab;
		show: 'Matching: ';
		show: testString printString;
		show: ' expected: ';
		show: expected printString;
		show: ' got: '.
	got := aMatcher search: testString.
	Transcript show: got printString.
	got ~= expected
		ifTrue: [^false].
	(subexpr notNil and: [aMatcher supportsSubexpressions])
		ifFalse:
			[^true]
		ifTrue:
			[ | isOK |
			isOK := true.
			1 to: subexpr size by: 2 do: [: i |
				| sub subExpect subGot |
				sub := subexpr at: i.
				subExpect := subexpr at: i + 1.
				subGot := aMatcher subexpression: sub.
				Transcript cr; tab; tab;
					show: 'Subexpression: ', sub printString;
					show: ' expected: ';
					show: subExpect printString;
					show: ' got: ';
					show: subGot printString.
				subExpect ~= subGot
					ifTrue:
					[Transcript show: ' -- MISMATCH'.
					isOK := false]].
			^isOK]
!

xtestSuite
    "Answer an array of test clauses. 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.
     The test suite is based on the one in Henry Spencer's regexp.c package."

	^#(
		('abc'
			'abc' true (1 'abc')
			'xbc' false nil
			'axc' false nil
			'abx' false nil
			'xabcy' true (1 'abc')
			'ababc' true (1 'abc'))
		('ab*c'
			'abc' true (1 'abc'))
		('ab*bc'
			'abc' true (1 'abc')
			'abbc' true (1 'abbc')
			'abbbbc' true (1 'abbbbc'))
		('ab+bc'
			'abbc' true (1 'abbc')
			'abc' false nil
			'abq' false nil
			'abbbbc' true (1 'abbbbc'))
		('ab?bc'
			'abbc' true (1 'abbc')
			'abc' true (1 'abc')
			'abbbbc' false nil
			'abc' true (1 'abc'))
		('ab?c'                         "added 08-Jan-2004 by cg "
			'abc' true (1 'abc'))
		('^abc$'
			'abc' true (1 'abc')
			'abcc' false nil
			'aabc' false nil)
		('^abc'
			'abcc' true (1 'abc'))
		('abc$'
			'aabc' true (1 'abc'))
		('^'
			'abc' true nil)
		('$'
			'abc' true nil)
		('a.c'
			'abc' true (1 'abc')
			'axc' true (1 'axc'))
		('a.*c'
			'axyzc' true (1 'axyzc')
			'axy zc' true (1 'axy zc') "testing that a dot matches a space"
			'axy
						 zc' false nil "testing that a dot does not match a newline"
			'axyzd' false nil)
		('.a.*'
			'1234abc' true (1 '4abc')
			'abcd' false nil)
		('a\w+c'
			' abbbbc ' true (1 'abbbbc')
			'abb bc' false nil)
		('\w+'
			'       foobar  quux' true (1 'foobar')
			'       ~!!@#$%^&*()-+=\|/?.>,<' false nil)
		('a\W+c'
			'a   c' true (1 'a   c')
			'a bc' false nil)
		('\W+'
			'foo!!@#$bar' true (1 '!!@#$')
			'foobar' false nil)
		('a\s*c'
			'a   c' true (1 'a   c')
			'a bc' false nil)
		('\s+'
			'abc3457 sd' true (1 ' ')
			'1234$^*^&asdfb' false nil)
		('a\S*c'
			'aqwertyc' true (1 'aqwertyc')
			'ab c' false nil)
		('\S+'
			'       asdf            ' true (1 'asdf')
			'
				' false nil)
		('a\d+c'
			'a0123456789c' true (1 'a0123456789c')
			'a12b34c' false nil)
		('\d+'
			'foo@#$%123ASD #$$%^&' true (1 '123')
			'foo!!@#$asdfl;' false nil)
		('a\D+c'
			'aqwertyc' true (1 'aqwertyc')
			'aqw6ertc' false nil)
		('\D+'
			'1234 abc 456' true (1 ' abc ')
			'1234567890' false nil)
		('(f|o)+\b'
			'foo' true (1 'foo')
			' foo ' true (1 'foo'))
		('\ba\w+' "a word beginning with an A"
			'land ancient' true (1 'ancient')
			'antique vase' true (1 'antique')
			'goofy foobar' false nil)
		('(f|o)+\B'
			'quuxfoobar' true (1 'foo')
			'quuxfoo ' true (1 'fo'))
		('\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)
		('fooa\>.*'
			'fooa ' true nil
			'fooa123' false nil
			'fooa bar' true nil
			'fooa' true nil
			'fooargh' false nil)
		('\>.+abc'
			' abcde fg' false nil
			'foo abcde' true (1 ' abc')
			'abcde' false nil)
		('\<foo.*'
			'foo' true nil
			'foobar' true nil
			'qfoobarq foonix' true (1 'foonix')
			' foo' true nil
			' 12foo' false nil
			'barfoo' false nil)
		('.+\<foo'
			'foo' false nil
			'ab foo' true (1 'ab foo')
			'abfoo' false nil)
		('a[bc]d'
			'abc' false nil
			'abd' true (1 'abd'))
		('a[b-d]e'
			'abd' false nil
			'ace' true (1 'ace'))
		('a[b-d]'
			'aac' true (1 'ac'))
		('a[-b]'
			'a-' true (1 'a-'))
		('a[b-]'
			'a-' true (1 'a-'))
		('a[a-b-c]' nil)
		('[k]'
			'ab' false nil)
		('a[b-a]' nil)
		('a[]b' nil)
		('a[' nil)
		('a]'
			'a]' true (1 'a]'))
		('a[]]b'
			'a]b' true (1 'a]b'))
		('a[^bc]d'
			'aed' true (1 'aed')
			'abd' false nil)
		('a[^-b]c'
			'adc' true (1 'adc')
			'a-c' false nil)
		('a[^]b]c'
			'a]c' false nil
			'adc' true (1 'adc'))
		('[\de]+'
			'01234' true (1 '01234')
			'0123e456' true (1 '0123e456')
			'0123e45g78' true (1 '0123e45'))
		('[e\d]+' "reversal of the above, should be the same"
			'01234' true (1 '01234')
			'0123e456' true (1 '0123e456')
			'0123e45g78' true (1 '0123e45'))
		('[\D]+'
			'123abc45def78' true (1 'abc'))
		('[[:digit:]e]+'
			'01234' true (1 '01234')
			'0123e456' true (1 '0123e456')
			'0123e45g78' true (1 '0123e45'))
		('[\s]+'
			'2  spaces' true (1 '  '))
		('[\S]+'
			'  word12!!@#$  ' true (1 'word12!!@#$'))
		('[\w]+'
			'       foo123bar       45' true (1 'foo123bar'))
		('[\W]+'
			'fii234!!@#$34f' true (1 '!!@#$'))
		('[^[:alnum:]]+'
			'fii234!!@#$34f' true (1 '!!@#$'))
		('[%&[:alnum:]]+'
			'foo%3' true (1 'foo%3')
			'foo34&rt4$57a' true (1 'foo34&rt4')
			'!!@#$' false nil)
		('[[:alpha:]]+'
			' 123foo3 ' true (1 'foo')
			'123foo' true (1 'foo')
			'foo1b' true (1 'foo'))
		('[[:blank:]]+'
			'2  blanks' true (1 '  '))
		('[^[:blank:]]+'
			'  word12!!@#$  ' true (1 'word12!!@#$'))
		('[[:cntrl:]]+'
			' a 1234asdf' false nil)
		('[[:lower:]]+'
			'UPPERlower1234' true (1 'lower')
			'lowerUPPER' true (1 'lower'))
		('[[:upper:]]+'
			'UPPERlower1234' true (1 'UPPER')
			'lowerUPPER ' true (1 'UPPER'))
		('[[:space:]]+'
			'2  spaces' true (1 '  '))
		('[^[:space:]]+'
			'  word12!!@#$  ' true (1 'word12!!@#$'))
		('[[:graph:]]+'
			'abc' true (1 'abc'))
		('[[:print:]]+'
			'abc' true (1 'abc'))
		('[^[:punct:]]+'
			'!!hello,world!!' true (1 'hello'))
		('[[:xdigit:]]+'
			'  x10FCD  ' true (1 '10FCD')
			' hgfedcba0123456789ABCDEFGH '
				true (1 'fedcba0123456789ABCDEF'))
		('ab|cd'
			'abc' true (1 'ab')
			'abcd' true (1 'ab'))
		('()ef'
			'def' true (1 'ef' 2 ''))
		('()*' nil)
		('*a' nil)
		('^*' nil)
		('$*' nil)
		('(*)b' nil)
		('$b'   'b' false nil)
		('a\' nil)
		('a\(b'
			'a(b' true (1 'a(b'))
		('a\(*b'
			'ab' true (1 'ab')
			'a((b' true (1 'a((b'))
		('a\\b'
			'a\b' true (1 'a\b'))
		('abc)' nil)
		('(abc' nil)
		('((a))'
			'abc' true (1 'a' 2 'a' 3 'a'))
		('(a)b(c)'
			'abc' true (1 'abc' 2 'a' 3 'c'))
		('a+b+c'
			'aabbabc' true (1 'abc'))
		('a**' nil)
		('a*?' nil)
		('(a*)*' nil)
		('(a*)+' nil)
		('(a|)*' nil)
		('(a*|b)*' nil)
		('(a+|b)*'
			'ab' true (1 'ab' 2 'b'))
		('(a+|b)+'
			'ab' true (1 'ab' 2 'b'))
		('(a+|b)?'
			'ab' true (1 'a' 2 'a'))
		('[^ab]*'
			'cde' true (1 'cde'))

		('(^)*' nil)
		('(ab|)*' nil)
		(')(' nil)
		('' 'abc' true (1 ''))
		('abc' '' false nil)
		('a*'
			'' true '')
		('abcd'
			'abcd' true (1 'abcd'))
		('a(bc)d'
			'abcd' true (1 'abcd' 2 'bc'))
		('([abc])*d'
			'abbbcd' true (1 'abbbcd' 2 'c'))
		('([abc])*bcd'
			'abcd' true (1 'abcd' 2 'a'))
		('a|b|c|d|e' 'e' true (1 'e'))
		('(a|b|c|d|e)f' 'ef' true (1 'ef' 2 'e'))
			"       ((a*|b))*       -       c       -       -"
		('abcd*efg' 'abcdefg' true (1 'abcdefg'))
		('ab*'
			'xabyabbbz' true (1 'ab')
			'xayabbbz' true (1 'a'))
		('(ab|cd)e' 'abcde' true (1 'cde' 2 'cd'))
		('[abhgefdc]ij' 'hij' true (1 'hij'))
		('^(ab|cd)e' 'abcde' false nil)
		('(abc|)def' 'abcdef' true nil)
		('(a|b)c*d' 'abcd' true (1 'bcd' 2 'b'))
		('(ab|ab*)bc' 'abc' true (1 'abc' 2 'a'))
		('a([bc]*)c*' 'abc' true (1 'abc' 2 'bc'))
		('a([bc]*)(c*d)' 'abcd' true (1 'abcd' 2 'bc' 3 'd'))
		('a([bc]+)(c*d)' 'abcd' true (1 'abcd' 2 'bc' 3 'd'))
		('a([bc]*)(c+d)' 'abcd' true (1 'abcd' 2 'b' 3 'cd'))
		('a[bcd]*dcdcde' 'adcdcde' true (1 'adcdcde'))
		('a[bcd]+dcdcde' 'adcdcde' false nil)
		('(ab|a)b*c' 'abc' true (1 'abc'))
		('((a)(b)c)(d)' 'abcd' true (1 'abcd' 3 'a' 4 'b' 5 'd'))
		('[ -~]*' 'abc' true (1 'abc'))
		('[ -~ -~]*' 'abc' true (1 'abc'))
		('[ -~ -~ -~]*' 'abc' true (1 'abc'))
		('[ -~ -~ -~ -~]*' 'abc' true (1 'abc'))
		('[ -~ -~ -~ -~ -~]*' 'abc' true (1 'abc'))
		('[ -~ -~ -~ -~ -~ -~]*' 'abc' true (1 'abc'))
		('[ -~ -~ -~ -~ -~ -~ -~]*' 'abc' true (1 'abc'))
		('[a-zA-Z_][a-zA-Z0-9_]*' 'alpha' true (1 'alpha'))
		('^a(bc+|b[eh])g|.h$' 'abh' true (1 'bh' 2 ''))
		('(bc+d$|ef*g.|h?i(j|k))'
			'effgz' true (1 'effgz' 2 'effgz' 3 '')
			'ij' true (1 'ij' 2 'ij' 3 'j')
			'effg' false nil
			'bcdd' false nil
			'reffgz' true (1 'effgz' 2 'effgz' 3 ''))
		('(((((((((a)))))))))' 'a' true (1 'a'))
		('multiple words of text'
			'uh-uh' false nil
			'multiple words of text, yeah' true (1 'multiple words of text'))
		('(.*)c(.*)' 'abcde' true (1 'abcde' 2 'ab' 3 'de'))
		('\((.*), (.*)\)' '(a, b)' true (2 'a' 3 'b'))

	    )
! !

!RxTests methodsFor:'test suite - string interface'!

testS001
    self assert:( 'abc' matchesRegex:'abc' ).
    self assert:( 'abc' matchesRegex:'ab.' ).
    self assert:( 'abc' matchesRegex:'ab.*' ).
    self assert:( 'abc' matchesRegex:'a.*' ).
    self assert:( 'abc' matchesRegex:'.*' ).
    self assert:( 'abc' matchesRegex:'[ab].*' ).
    self assert:( 'bca' matchesRegex:'[ab].*' ).
    self assert:( 'cab' matchesRegex:'[ab].*' ) not.

    "
     self new testS001
    "
!

testS002
    self assert:( 'abc' matchesRegexIgnoringCase:'abc' ).
    self assert:( 'ABC' matchesRegexIgnoringCase:'abc' ).
    self assert:( 'ABC' matchesRegex:'abc' ) not.
    self assert:( 'aBc' matchesRegexIgnoringCase:'abc' ).
    self assert:( 'aBc' matchesRegex:'abc' ) not.

    self assert:( 'abc' matchesRegexIgnoringCase:'ab.' ).
    self assert:( 'ABC' matchesRegexIgnoringCase:'ab.' ).
    self assert:( 'ABC' matchesRegex:'ab.' ) not.
    self assert:( 'aBc' matchesRegexIgnoringCase:'ab.' ).
    self assert:( 'aBc' matchesRegex:'ab.' ) not.

    self assert:( 'abc' matchesRegexIgnoringCase:'ab.*' ).
    self assert:( 'ABC' matchesRegexIgnoringCase:'ab.*' ).
    self assert:( 'ABC' matchesRegex:'ab.*' ) not.
    self assert:( 'aBc' matchesRegexIgnoringCase:'ab.*' ).
    self assert:( 'aBc' matchesRegex:'ab.*' ) not.

    self assert:( 'abc' matchesRegexIgnoringCase:'a.*' ).
    self assert:( 'ABC' matchesRegexIgnoringCase:'a.*' ).
    self assert:( 'ABC' matchesRegex:'a.*' ) not.
    self assert:( 'aBc' matchesRegexIgnoringCase:'a.*' ).
    self assert:( 'aBc' matchesRegex:'a.*' ).

    self assert:( 'abc' matchesRegexIgnoringCase:'.*' ).
    self assert:( 'ABC' matchesRegexIgnoringCase:'.*' ).
    self assert:( 'ABC' matchesRegex:'.*' ).
    self assert:( 'aBc' matchesRegexIgnoringCase:'.*' ).
    self assert:( 'aBc' matchesRegex:'.*' ).

    self assert:( 'abc' matchesRegexIgnoringCase:'[ab].*' ).
    self assert:( 'ABC' matchesRegexIgnoringCase:'[ab].*' ).
    self assert:( 'ABC' matchesRegex:'[ab].*' ) not.
    self assert:( 'aBc' matchesRegexIgnoringCase:'[ab].*' ).
    self assert:( 'aBc' matchesRegex:'[ab].*' ).

    self assert:( 'bca' matchesRegexIgnoringCase:'[ab].*' ).
    self assert:( 'BCA' matchesRegexIgnoringCase:'[ab].*' ).
    self assert:( 'BCA' matchesRegex:'[ab].*' ) not.
    self assert:( 'Bca' matchesRegexIgnoringCase:'[ab].*' ).
    self assert:( 'Bca' matchesRegex:'[ab].*' ) not.

    self assert:( 'cab' matchesRegexIgnoringCase:'[ab].*' ) not.
    self assert:( 'CAB' matchesRegexIgnoringCase:'[ab].*' ) not.
    self assert:( 'CAB' matchesRegex:'[ab].*' ) not.
    self assert:( 'caB' matchesRegexIgnoringCase:'[ab].*' ) not.
    self assert:( 'caB' matchesRegex:'[ab].*' ) not.

    "
     self new testS002
    "
! !

!RxTests methodsFor:'test suite conversion'!

writeAllTests
	"Build individual tests from the test suite."

	| aTest matcherClass rxSource matcher isOK subexpr |

	matcherClass := Regex::RxMatcher.

	1 to: self xtestSuite size do: [ :n |
		aTest := self xtestSuite at: n.
		Transcript
			show: 'test', n printString; cr;
			tab; show: '| matcher |'; cr; cr;
			tab; show: 'self should: [ (matcher := Regex::RxParser compileRegex: ''', aTest first, ''' into:Regex::RxMatcher)'.
		(aTest at: 2) isNil
			ifTrue: [ Transcript show: ' = nil ].'; cr ]
			ifFalse: [
				Transcript show: ' ~= nil ].'; cr.
				2 to: aTest size by: 3 do:
					[:i  |
					Transcript tab; show: 'self should: [ (matcher search: ', (aTest at: i) printString, ') = ',
								(aTest at: i+1) printString, ' ].'; cr.
					(aTest at: i+1) ~= nil ifTrue: [
						subexpr := aTest at: i+2.
						1 to: subexpr size by: 2 do: [ :j |
							Transcript tab; show: 'self should: [ (matcher subexpression: ',
										(subexpr at: j) printString, ') = ', (subexpr at: j+1) printString,
										' ].'; 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
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !