1# reg.test --
2#
3# This file contains a collection of tests for one or more of the Tcl
4# built-in commands.  Sourcing this file into Tcl runs the tests and
5# generates output for errors.  No output means no errors were found.
6# (Don't panic if you are seeing this as part of the reg distribution
7# and aren't using Tcl -- reg's own regression tester also knows how
8# to read this file, ignoring the Tcl-isms.)
9#
10# Copyright © 1998, 1999 Henry Spencer.  All rights reserved.
11
12if {"::tcltest" ni [namespace children]} {
13    package require tcltest 2.5
14    namespace import -force ::tcltest::*
15}
16
17::tcltest::loadTestedCommands
18catch [list package require -exact tcl::test [info patchlevel]]
19
20# All tests require the testregexp command, return if this
21# command doesn't exist
22
23::tcltest::testConstraint testregexp [llength [info commands testregexp]]
24::tcltest::testConstraint localeRegexp 0
25
26# This file uses some custom procedures, defined below, for regexp regression
27# testing.  The name of the procedure indicates the general nature of the
28# test:
29#	expectError	compile error expected
30#	expectNomatch	match failure expected
31#	expectMatch	successful match
32#	expectIndices	successful match with -indices (used in checking things
33#			like nonparticipating subexpressions)
34#	expectPartial	unsuccessful match with -indices (!!) (used in checking
35#			partial-match reporting)
36# There is also "doing" which sets up title and major test number for each
37# block of tests.
38
39# The first 3 arguments are constant: a minor number (which often gets
40# a letter or two suffixed to it internally), some flags, and the RE
41# itself.  For expectError, the remaining argument is the name of the
42# compile error expected, less the leading "REG_".  For the rest, the
43# next argument is the string to try the match against.  Remaining
44# arguments are the substring expected to be matched, and any
45# substrings expected to be matched by subexpressions.  (For
46# expectNomatch, these arguments are optional, and if present are
47# ignored except that they indicate how many subexpressions should be
48# present in the RE.)  It is an error for the number of subexpression
49# arguments to be wrong.  Cases involving nonparticipating
50# subexpressions, checking where empty substrings are located,
51# etc. should be done using expectIndices and expectPartial.
52
53# The flag characters are complex and a bit eclectic.  Generally speaking,
54# lowercase letters are compile options, uppercase are expected re_info
55# bits, and nonalphabetics are match options, controls for how the test is
56# run, or testing options.  The one small surprise is that AREs are the
57# default, and you must explicitly request lesser flavors of RE.  The flags
58# are as follows.  It is admitted that some are not very mnemonic.
59# There are some others which are purely debugging tools and are not
60# useful in this file.
61#
62#	-	no-op (placeholder)
63#	+	provide fake xy equivalence class and ch collating element
64#	%	force small state-set cache in matcher (to test cache replace)
65#	^	beginning of string is not beginning of line
66#	$	end of string is not end of line
67#	*	test is Unicode-specific, needs big character set
68#
69#	&	test as both ARE and BRE
70#	b	BRE
71#	e	ERE
72#	a	turn advanced-features bit on (error unless ERE already)
73#	q	literal string, no metacharacters at all
74#
75#	i	case-independent matching
76#	o	("opaque") no subexpression capture
77#	p	newlines are half-magic, excluded from . and [^ only
78#	w	newlines are half-magic, significant to ^ and $ only
79#	n	newlines are fully magic, both effects
80#	x	expanded RE syntax
81#	t	incomplete-match reporting
82#
83#	A	backslash-_a_lphanumeric seen
84#	B	ERE/ARE literal-_b_race heuristic used
85#	E	backslash (_e_scape) seen within []
86#	H	looka_h_ead constraint seen
87#	I	_i_mpossible to match
88#	L	_l_ocale-specific construct seen
89#	M	unportable (_m_achine-specific) construct seen
90#	N	RE can match empty (_n_ull) string
91#	P	non-_P_OSIX construct seen
92#	Q	{} _q_uantifier seen
93#	R	back _r_eference seen
94#	S	POSIX-un_s_pecified syntax seen
95#	T	prefers shortest (_t_iny)
96#	U	saw original-POSIX botch:  unmatched right paren in ERE (_u_gh)
97
98# The one area we can't easily test is memory-allocation failures (which
99# are hard to provoke on command).  Embedded NULs also are not tested at
100# the moment, but this is a historical accident which should be fixed.
101
102
103# test procedures and related
104namespace eval RETest {
105    namespace export doing expect* knownBug
106
107    variable regBug 0
108
109    # re_info abbreviation mapping table
110    variable infonames
111    array set infonames {
112	A REG_UBSALNUM
113	B REG_UBRACES
114	E REG_UBBS
115	H REG_ULOOKAHEAD
116	I REG_UIMPOSSIBLE
117	L REG_ULOCALE
118	M REG_UUNPORT
119	N REG_UEMPTYMATCH
120	P REG_UNONPOSIX
121	Q REG_UBOUNDS
122	R REG_UBACKREF
123	S REG_UUNSPEC
124	T REG_USHORTEST
125	U REG_UPBOTCH
126    }
127    variable infonameorder "RHQBAUEPSMLNIT" ;# must match bit order, lsb first
128
129    # build test number (internal)
130    proc TestNum {args} {
131	return reg-[join [concat $args] .]
132    }
133
134    # build description, with possible modifiers (internal)
135    proc TestDesc {args} {
136	variable description
137
138	set testid [concat $args]
139	set d $description
140	if {[llength $testid] > 1} {
141	    set d "$d ([lrange $testid 1 end])"
142	}
143	return $d
144    }
145
146    # build trailing options and flags argument from a flags string (internal)
147    proc TestFlags {fl} {
148	set args [list]
149	set flags ""
150	foreach f [split $fl ""] {
151	    switch -exact -- $f {
152		"i" { lappend args "-nocase" }
153		"x" { lappend args "-expanded" }
154		"n" { lappend args "-line" }
155		"p" { lappend args "-linestop" }
156		"w" { lappend args "-lineanchor" }
157		"-" { }
158		default { append flags $f }
159	    }
160	}
161	if {$flags ne ""} {
162	    lappend args -xflags $flags
163	}
164	return $args
165    }
166
167    # build info-flags list from a flags string (internal)
168    proc TestInfoFlags {fl} {
169	variable infonames
170	variable infonameorder
171
172	set ret [list]
173	foreach f [split $infonameorder ""] {
174	    if {[string match *$f* $fl]} {
175		lappend ret $infonames($f)
176	    }
177	}
178	return $ret
179    }
180
181    # Share the generation of the list of test constraints so it is
182    # done the same on all routes.
183    proc TestConstraints {flags} {
184	set constraints [list testregexp]
185
186	variable regBug
187	if {$regBug} {
188	    # This will trigger registration as a skipped test
189	    lappend constraints knownBug
190	}
191
192	# Tcl locale stuff doesn't do the ch/xy test fakery yet
193	if {[string match *+* $flags]} {
194	    # This will trigger registration as a skipped test
195	    lappend constraints localeRegexp
196	}
197
198	return $constraints
199    }
200
201    # match expected, internal routine that does the work
202    # parameters like the "real" routines except they don't have "opts",
203    #  which is a possibly-empty list of switches for the regexp match attempt
204    # The ! flag is used to indicate expected match failure (for REG_EXPECT,
205    #  which wants argument testing even in the event of failure).
206    proc MatchExpected {opts testid flags re target args} {
207	# if &, test as both BRE and ARE
208	if {[string match *&* $flags]} {
209	    set f [string map {& {}} $flags]
210	    MatchExpected $opts "$testid ARE" ${f}  $re $target {*}$args
211	    MatchExpected $opts "$testid BRE" ${f}b $re $target {*}$args
212	    return
213	}
214
215	set constraints [TestConstraints $flags]
216
217	set f [TestFlags $flags]
218	set infoflags [TestInfoFlags $flags]
219	set ccmd [list testregexp -about        {*}$f $re]
220	set ecmd [list testregexp {*}$opts {*}$f $re $target]
221
222	set nsub [expr {[llength $args] - 1}]
223	set names [list]
224	set refs ""
225	for {set i 0} {$i < [llength $args]} {incr i} {
226	    if {$i == 0} {
227		set name match
228	    } else {
229		set name sub$i
230	    }
231	    lappend names $name
232	    append refs " \$$name"
233	    set $name ""
234	}
235	if {[string match *o* $flags]} {	;# REG_NOSUB kludge
236	    set nsub 0				;# unsigned value cannot be -1
237	}
238	if {[string match *t* $flags]} {	;# REG_EXPECT
239	    incr nsub -1			;# the extra does not count
240	}
241	set erun "list \[[concat $ecmd $names]\] $refs"
242	set result [list [expr {![string match *!* $flags]}] {*}$args]
243	set info [list $nsub $infoflags]
244
245	::tcltest::test [TestNum $testid compile] [TestDesc $testid compile] \
246		-constraints $constraints -body $ccmd -result $info
247	::tcltest::test [TestNum $testid execute] [TestDesc $testid execute] \
248		-constraints $constraints -body $erun -result $result
249    }
250
251    # set major test number and description
252    proc doing {major desc} {
253	variable description "RE engine $desc"
254    }
255
256    # compilation error expected
257    proc expectError {testid flags re err} {
258	# if &, test as both ARE and BRE
259	if {[string match *&* $flags]} {
260	    set f [string map {& {}} $flags]
261	    expectError "$testid ARE" ${f}  $re $err
262	    expectError "$testid BRE" ${f}b $re $err
263	    return
264	}
265
266	set constraints [TestConstraints $flags]
267
268	set cmd [list testregexp -about {*}[TestFlags $flags] $re]
269	::tcltest::test [TestNum $testid error] [TestDesc $testid error] \
270		-constraints $constraints -result [list 1 REG_$err] -body \
271		"list \[catch \{$cmd\}\] \[lindex \$::errorCode 1\]"
272    }
273
274    # match failure expected
275    proc expectNomatch {testid flags re target args} {
276	variable regBug
277	# if &, test as both ARE and BRE
278	if {[string match *&* $flags]} {
279	    set f [string map {& {}} $flags]
280	    expectNomatch "$testid ARE" ${f}  $re $target {*}$args
281	    expectNomatch "$testid BRE" ${f}b $re $target {*}$args
282	    return
283	}
284
285	set constraints [TestConstraints $flags]
286
287	set f [TestFlags $flags]
288	set infoflags [TestInfoFlags $flags]
289	set ccmd [list testregexp -about {*}$f $re]
290	set nsub [expr {[llength $args] - 1}]
291	if {$nsub < 0} {
292	    # didn't tell us number of subexps
293	    set ccmd "lreplace \[$ccmd\] 0 0"
294	    set info [list $infoflags]
295	} else {
296	    set info [list $nsub $infoflags]
297	}
298	set ecmd [list testregexp {*}$f $re $target]
299
300	::tcltest::test [TestNum $testid compile] [TestDesc $testid compile] \
301		-constraints $constraints -body $ccmd -result $info
302	::tcltest::test [TestNum $testid execute] [TestDesc $testid execute] \
303		-constraints $constraints -body $ecmd -result 0
304    }
305
306    # match expected (no missing, empty, or ambiguous submatches)
307    # expectMatch testno flags re target mat submat ...
308    proc expectMatch {args} {
309	MatchExpected {} {*}$args
310    }
311
312    # match expected (full fanciness)
313    # expectIndices testno flags re target mat submat ...
314    proc expectIndices {args} {
315	MatchExpected -indices {*}$args
316    }
317
318    # partial match expected
319    # expectPartial testno flags re target mat "" ...
320    # Quirk:  number of ""s must be one more than number of subREs.
321    proc expectPartial {args} {
322	lset args 1 ![lindex $args 1]	;# add ! flag
323	MatchExpected -indices {*}$args
324    }
325
326    # test is a knownBug
327    proc knownBug {args} {
328	variable regBug 1
329	uplevel \#0 $args
330	set regBug 0
331    }
332}
333namespace import RETest::*
334
335######## the tests themselves ########
336
337# support functions and preliminary misc.
338# This is sensitive to changes in message wording, but we really have to
339# test the code->message expansion at least once.
340::tcltest::test reg-0.1 "regexp error reporting" {
341    list [catch {regexp (*) ign} msg] $msg
342} {1 {couldn't compile regular expression pattern: quantifier operand invalid}}
343
344
345doing 1 "basic sanity checks"
346expectMatch	1.1 &		abc	abc		abc
347expectNomatch	1.2 &		abc	def
348expectMatch	1.3 &		abc	xyabxabce	abc
349
350
351doing 2 "invalid option combinations"
352expectError	2.1 qe		a	INVARG
353expectError	2.2 qa		a	INVARG
354expectError	2.3 qx		a	INVARG
355expectError	2.4 qn		a	INVARG
356expectError	2.5 ba		a	INVARG
357
358
359doing 3 "basic syntax"
360expectIndices	3.1 &NS		""	a	{0 -1}
361expectMatch	3.2 NS		a|	a	a
362expectMatch	3.3 -		a|b	a	a
363expectMatch	3.4 -		a|b	b	b
364expectMatch	3.5 NS		a||b	b	b
365expectMatch	3.6 &		ab	ab	ab
366
367
368doing 4 "parentheses"
369expectMatch	4.1  -		(a)e		ae	ae	a
370expectMatch	4.2  o		(a)e		ae
371expectMatch	4.3  b		{\(a\)b}	ab	ab	a
372expectMatch	4.4  -		a((b)c)		abc	abc	bc	b
373expectMatch	4.5  -		a(b)(c)		abc	abc	b	c
374expectError	4.6  -		a(b		EPAREN
375expectError	4.7  b		{a\(b}		EPAREN
376# sigh, we blew it on the specs here... someday this will be fixed in POSIX,
377#  but meanwhile, it's fixed in AREs
378expectMatch	4.8  eU		a)b		a)b	a)b
379expectError	4.9  -		a)b		EPAREN
380expectError	4.10 b		{a\)b}		EPAREN
381expectMatch	4.11 P		a(?:b)c		abc	abc
382expectError	4.12 e		a(?:b)c		BADRPT
383expectIndices	4.13 S		a()b		ab	{0 1}	{1 0}
384expectMatch	4.14 SP		a(?:)b		ab	ab
385expectIndices	4.15 S		a(|b)c		ac	{0 1}	{1 0}
386expectMatch	4.16 S		a(b|)c		abc	abc	b
387
388
389doing 5 "simple one-char matching"
390# general case of brackets done later
391expectMatch	5.1 &		a.b		axb	axb
392expectNomatch	5.2 &n		"a.b"		"a\nb"
393expectMatch	5.3 &		{a[bc]d}	abd	abd
394expectMatch	5.4 &		{a[bc]d}	acd	acd
395expectNomatch	5.5 &		{a[bc]d}	aed
396expectNomatch	5.6 &		{a[^bc]d}	abd
397expectMatch	5.7 &		{a[^bc]d}	aed	aed
398expectNomatch	5.8 &p		"a\[^bc]d"	"a\nd"
399
400
401doing 6 "context-dependent syntax"
402# plus odds and ends
403expectError	6.1  -		*	BADRPT
404expectMatch	6.2  b		*	*	*
405expectMatch	6.3  b		{\(*\)}	*	*	*
406expectError	6.4  -		(*)	BADRPT
407expectMatch	6.5  b		^*	*	*
408expectError	6.6  -		^*	BADRPT
409expectNomatch	6.7  &		^b	^b
410expectMatch	6.8  b		x^	x^	x^
411expectNomatch	6.9  I		x^	x
412expectMatch	6.10 n		"\n^"	"x\nb"	"\n"
413expectNomatch	6.11 bS		{\(^b\)} ^b
414expectMatch	6.12 -		(^b)	b	b	b
415expectMatch	6.13 &		{x$}	x	x
416expectMatch	6.14 bS		{\(x$\)} x	x	x
417expectMatch	6.15 -		{(x$)}	x	x	x
418expectMatch	6.16 b		{x$y}	"x\$y"	"x\$y"
419expectNomatch	6.17 I		{x$y}	xy
420expectMatch	6.18 n		"x\$\n"	"x\n"	"x\n"
421expectError	6.19 -		+	BADRPT
422expectError	6.20 -		?	BADRPT
423
424
425doing 7 "simple quantifiers"
426expectMatch	7.1  &N		a*	aa	aa
427expectIndices	7.2  &N		a*	b	{0 -1}
428expectMatch	7.3  -		a+	aa	aa
429expectMatch	7.4  -		a?b	ab	ab
430expectMatch	7.5  -		a?b	b	b
431expectError	7.6  -		**	BADRPT
432expectMatch	7.7  bN		**	***	***
433expectError	7.8  &		a**	BADRPT
434expectError	7.9  &		a**b	BADRPT
435expectError	7.10 &		***	BADRPT
436expectError	7.11 -		a++	BADRPT
437expectError	7.12 -		a?+	BADRPT
438expectError	7.13 -		a?*	BADRPT
439expectError	7.14 -		a+*	BADRPT
440expectError	7.15 -		a*+	BADRPT
441
442
443doing 8 "braces"
444expectMatch	8.1  NQ		"a{0,1}"	""	""
445expectMatch	8.2  NQ		"a{0,1}"	ac	a
446expectError	8.3  -		"a{1,0}"	BADBR
447expectError	8.4  -		"a{1,2,3}"	BADBR
448expectError	8.5  -		"a{257}"	BADBR
449expectError	8.6  -		"a{1000}"	BADBR
450expectError	8.7  -		"a{1"		EBRACE
451expectError	8.8  -		"a{1n}"		BADBR
452expectMatch	8.9  BS		"a{b"		"a\{b"	"a\{b"
453expectMatch	8.10 BS		"a{"		"a\{"	"a\{"
454expectMatch	8.11 bQ		"a\\{0,1\\}b"	cb	b
455expectError	8.12 b		"a\\{0,1"	EBRACE
456expectError	8.13 -		"a{0,1\\"	BADBR
457expectMatch	8.14 Q		"a{0}b"		ab	b
458expectMatch	8.15 Q		"a{0,0}b"	ab	b
459expectMatch	8.16 Q		"a{0,1}b"	ab	ab
460expectMatch	8.17 Q		"a{0,2}b"	b	b
461expectMatch	8.18 Q		"a{0,2}b"	aab	aab
462expectMatch	8.19 Q		"a{0,}b"	aab	aab
463expectMatch	8.20 Q		"a{1,1}b"	aab	ab
464expectMatch	8.21 Q		"a{1,3}b"	aaaab	aaab
465expectNomatch	8.22 Q		"a{1,3}b"	b
466expectMatch	8.23 Q		"a{1,}b"	aab	aab
467expectNomatch	8.24 Q		"a{2,3}b"	ab
468expectMatch	8.25 Q		"a{2,3}b"	aaaab	aaab
469expectNomatch	8.26 Q		"a{2,}b"	ab
470expectMatch	8.27 Q		"a{2,}b"	aaaab	aaaab
471
472
473doing 9 "brackets"
474expectMatch	9.1  &		{a[bc]}		ac	ac
475expectMatch	9.2  &		{a[-]}		a-	a-
476expectMatch	9.3  &		{a[[.-.]]}	a-	a-
477expectMatch	9.4  &L		{a[[.zero.]]}	a0	a0
478expectMatch	9.5  &LM	{a[[.zero.]-9]}	a2	a2
479expectMatch	9.6  &M		{a[0-[.9.]]}	a2	a2
480expectMatch	9.7  &+L	{a[[=x=]]}	ax	ax
481expectMatch	9.8  &+L	{a[[=x=]]}	ay	ay
482expectNomatch	9.9  &+L	{a[[=x=]]}	az
483expectError	9.10 &		{a[0-[=x=]]}	ERANGE
484expectMatch	9.11 &L		{a[[:digit:]]}	a0	a0
485expectError	9.12 &		{a[[:woopsie:]]}	ECTYPE
486expectNomatch	9.13 &L		{a[[:digit:]]}	ab
487expectError	9.14 &		{a[0-[:digit:]]}	ERANGE
488expectMatch	9.15 &LP	{[[:<:]]a}	a	a
489expectMatch	9.16 &LP	{a[[:>:]]}	a	a
490expectError	9.17 &		{a[[..]]b}	ECOLLATE
491expectError	9.18 &		{a[[==]]b}	ECOLLATE
492expectError	9.19 &		{a[[::]]b}	ECTYPE
493expectError	9.20 &		{a[[.a}		EBRACK
494expectError	9.21 &		{a[[=a}		EBRACK
495expectError	9.22 &		{a[[:a}		EBRACK
496expectError	9.23 &		{a[}		EBRACK
497expectError	9.24 &		{a[b}		EBRACK
498expectError	9.25 &		{a[b-}		EBRACK
499expectError	9.26 &		{a[b-c}		EBRACK
500expectMatch	9.27 &M		{a[b-c]}	ab	ab
501expectMatch	9.28 &		{a[b-b]}	ab	ab
502expectMatch	9.29 &M		{a[1-2]}	a2	a2
503expectError	9.30 &		{a[c-b]}	ERANGE
504expectError	9.31 &		{a[a-b-c]}	ERANGE
505expectMatch	9.32 &M		{a[--?]b}	a?b	a?b
506expectMatch	9.33 &		{a[---]b}	a-b	a-b
507expectMatch	9.34 &		{a[]b]c}	a]c	a]c
508expectMatch	9.35 EP		{a[\]]b}	a]b	a]b
509expectNomatch	9.36 bE		{a[\]]b}	a]b
510expectMatch	9.37 bE		{a[\]]b}	"a\\]b"	"a\\]b"
511expectMatch	9.38 eE		{a[\]]b}	"a\\]b"	"a\\]b"
512expectMatch	9.39 EP		{a[\\]b}	"a\\b"	"a\\b"
513expectMatch	9.40 eE		{a[\\]b}	"a\\b"	"a\\b"
514expectMatch	9.41 bE		{a[\\]b}	"a\\b"	"a\\b"
515expectError	9.42 -		{a[\Z]b}	EESCAPE
516expectMatch	9.43 &		{a[[b]c}	"a\[c"	"a\[c"
517expectMatch	9.44 EMP*	{a[\xFE-\u0507][\xFF-\u0300]b} \
518	"a\u0102\u02FFb"	"a\u0102\u02FFb"
519
520
521doing 10 "anchors and newlines"
522expectMatch	10.1  &		^a	a	a
523expectNomatch	10.2  &^	^a	a
524expectIndices	10.3  &N	^	a	{0 -1}
525expectIndices	10.4  &		{a$}	aba	{2 2}
526expectNomatch	10.5  {&$}	{a$}	a
527expectIndices	10.6  &N	{$}	ab	{2 1}
528expectMatch	10.7  &n	^a	a	a
529expectMatch	10.8  &n	"^a"	"b\na"	"a"
530expectIndices	10.9  &w	"^a"	"a\na"	{0 0}
531expectIndices	10.10 &n^	"^a"	"a\na"	{2 2}
532expectMatch	10.11 &n	{a$}	a	a
533expectMatch	10.12 &n	"a\$"	"a\nb"	"a"
534expectIndices	10.13 &n	"a\$"	"a\na"	{0 0}
535expectIndices	10.14 N		^^	a	{0 -1}
536expectMatch	10.15 b		^^	^	^
537expectIndices	10.16 N		{$$}	a	{1 0}
538expectMatch	10.17 b		{$$}	"\$"	"\$"
539expectMatch	10.18 &N	{^$}	""	""
540expectNomatch	10.19 &N	{^$}	a
541expectIndices	10.20 &nN	"^\$"	a\n\nb	{2 1}
542expectMatch	10.21 N		{$^}	""	""
543expectMatch	10.22 b		{$^}	"\$^"	"\$^"
544expectMatch	10.23 P		{\Aa}	a	a
545expectMatch	10.24 ^P	{\Aa}	a	a
546expectNomatch	10.25 ^nP	{\Aa}	"b\na"
547expectMatch	10.26 P		{a\Z}	a	a
548expectMatch	10.27 \$P	{a\Z}	a	a
549expectNomatch	10.28 \$nP	{a\Z}	"a\nb"
550expectError	10.29 -		^*	BADRPT
551expectError	10.30 -		{$*}	BADRPT
552expectError	10.31 -		{\A*}	BADRPT
553expectError	10.32 -		{\Z*}	BADRPT
554
555
556doing 11 "boundary constraints"
557expectMatch	11.1  &LP	{[[:<:]]a}	a	a
558expectMatch	11.2  &LP	{[[:<:]]a}	-a	a
559expectNomatch	11.3  &LP	{[[:<:]]a}	ba
560expectMatch	11.4  &LP	{a[[:>:]]}	a	a
561expectMatch	11.5  &LP	{a[[:>:]]}	a-	a
562expectNomatch	11.6  &LP	{a[[:>:]]}	ab
563expectMatch	11.7  bLP	{\<a}		a	a
564expectNomatch	11.8  bLP	{\<a}		ba
565expectMatch	11.9  bLP	{a\>}		a	a
566expectNomatch	11.10 bLP	{a\>}		ab
567expectMatch	11.11 LP	{\ya}		a	a
568expectNomatch	11.12 LP	{\ya}		ba
569expectMatch	11.13 LP	{a\y}		a	a
570expectNomatch	11.14 LP	{a\y}		ab
571expectMatch	11.15 LP	{a\Y}		ab	a
572expectNomatch	11.16 LP	{a\Y}		a-
573expectNomatch	11.17 LP	{a\Y}		a
574expectNomatch	11.18 LP	{-\Y}		-a
575expectMatch	11.19 LP	{-\Y}		-%	-
576expectNomatch	11.20 LP	{\Y-}		a-
577expectError	11.21 -		{[[:<:]]*}	BADRPT
578expectError	11.22 -		{[[:>:]]*}	BADRPT
579expectError	11.23 b		{\<*}		BADRPT
580expectError	11.24 b		{\>*}		BADRPT
581expectError	11.25 -		{\y*}		BADRPT
582expectError	11.26 -		{\Y*}		BADRPT
583expectMatch	11.27 LP	{\ma}		a	a
584expectNomatch	11.28 LP	{\ma}		ba
585expectMatch	11.29 LP	{a\M}		a	a
586expectNomatch	11.30 LP	{a\M}		ab
587expectNomatch	11.31 ILP	{\Ma}		a
588expectNomatch	11.32 ILP	{a\m}		a
589
590
591doing 12 "character classes"
592expectMatch	12.1  LP	{a\db}		a0b	a0b
593expectNomatch	12.2  LP	{a\db}		axb
594expectNomatch	12.3  LP	{a\Db}		a0b
595expectMatch	12.4  LP	{a\Db}		axb	axb
596expectMatch	12.5  LP	"a\\sb"		"a b"	"a b"
597expectMatch	12.6  LP	"a\\sb"		"a\tb"	"a\tb"
598expectMatch	12.7  LP	"a\\sb"		"a\nb"	"a\nb"
599expectNomatch	12.8  LP	{a\sb}		axb
600expectMatch	12.9  LP	{a\Sb}		axb	axb
601expectNomatch	12.10 LP	"a\\Sb"		"a b"
602expectMatch	12.11 LP	{a\wb}		axb	axb
603expectNomatch	12.12 LP	{a\wb}		a-b
604expectNomatch	12.13 LP	{a\Wb}		axb
605expectMatch	12.14 LP	{a\Wb}		a-b	a-b
606expectMatch	12.15 LP	{\y\w+z\y}	adze-guz	guz
607expectMatch	12.16 LPE	{a[\d]b}	a1b	a1b
608expectMatch	12.17 LPE	"a\[\\s]b"	"a b"	"a b"
609expectMatch	12.18 LPE	{a[\w]b}	axb	axb
610
611
612doing 13 "escapes"
613expectError	13.1  &		"a\\"		EESCAPE
614expectMatch	13.2  -		{a\<b}		a<b	a<b
615expectMatch	13.3  e		{a\<b}		a<b	a<b
616expectMatch	13.4  bAS	{a\wb}		awb	awb
617expectMatch	13.5  eAS	{a\wb}		awb	awb
618expectMatch	13.6  PL	"a\\ab"		"a\007b"	"a\007b"
619expectMatch	13.7  P		"a\\bb"		"a\bb"	"a\bb"
620expectMatch	13.8  P		{a\Bb}		"a\\b"	"a\\b"
621expectMatch	13.9  MP	"a\\chb"	"a\bb"	"a\bb"
622expectMatch	13.10 MP	"a\\cHb"	"a\bb"	"a\bb"
623expectMatch	13.11 LMP	"a\\e"		"a\033"	"a\033"
624expectMatch	13.12 P		"a\\fb"		"a\fb"	"a\fb"
625expectMatch	13.13 P		"a\\nb"		"a\nb"	"a\nb"
626expectMatch	13.14 P		"a\\rb"		"a\rb"	"a\rb"
627expectMatch	13.15 P		"a\\tb"		"a\tb"	"a\tb"
628expectMatch	13.16 P		"a\\u0008x"	"a\bx"	"a\bx"
629expectMatch	13.17 P		{a\u008x}	"a\bx"	"a\bx"
630expectError	13.17.1 -	{a\ux}		EESCAPE
631expectMatch	13.18 P		"a\\u00088x"	"a\b8x"	"a\b8x"
632expectMatch	13.19 P		"a\\U00000008x"	"a\bx"	"a\bx"
633expectMatch	13.20 P		{a\U0000008x}	"a\bx"	"a\bx"
634expectMatch	13.21 P		"a\\vb"		"a\vb"	"a\vb"
635expectMatch	13.22 MP	"a\\x08x"	"a\bx"	"a\bx"
636expectError	13.23 -		{a\xq}		EESCAPE
637expectMatch	13.24 MP	"a\\x08x"	"a\bx"	"a\bx"
638expectError	13.25 -		{a\z}		EESCAPE
639expectMatch	13.26 MP	"a\\010b"	"a\bb"	"a\bb"
640expectMatch	13.27 P		"a\\U00001234x"	"a\u1234x"	"a\u1234x"
641expectMatch	13.28 P		{a\U00001234x}	"a\u1234x"	"a\u1234x"
642expectMatch	13.29 P		"a\\U0001234x"	"a\u1234x"	"a\u1234x"
643expectMatch	13.30 P		{a\U0001234x}	"a\u1234x"	"a\u1234x"
644expectMatch	13.31 P		"a\\U000012345x"	"a\u12345x"	"a\u12345x"
645expectMatch	13.32 P		{a\U000012345x}	"a\u12345x"	"a\u12345x"
646expectMatch	13.33 P		"a\\U1000000x"	"a\uFFFD0x"	"a\uFFFD0x"
647expectMatch	13.34 P		{a\U1000000x}	"a\uFFFD0x"	"a\uFFFD0x"
648
649
650doing 14 "back references"
651# ugh
652expectMatch	14.1  RP	{a(b*)c\1}	abbcbb	abbcbb	bb
653expectMatch	14.2  RP	{a(b*)c\1}	ac	ac	""
654expectNomatch	14.3  RP	{a(b*)c\1}	abbcb
655expectMatch	14.4  RP	{a(b*)\1}	abbcbb	abb	b
656expectMatch	14.5  RP	{a(b|bb)\1}	abbcbb	abb	b
657expectMatch	14.6  RP	{a([bc])\1}	abb	abb	b
658expectNomatch	14.7  RP	{a([bc])\1}	abc
659expectMatch	14.8  RP	{a([bc])\1}	abcabb	abb	b
660expectNomatch	14.9  RP	{a([bc])*\1}	abc
661expectNomatch	14.10 RP	{a([bc])\1}	abB
662expectMatch	14.11 iRP	{a([bc])\1}	abB	abB	b
663expectMatch	14.12 RP	{a([bc])\1+}	abbb	abbb	b
664expectMatch	14.13 QRP	"a(\[bc])\\1{3,4}"	abbbb	abbbb	b
665expectNomatch	14.14 QRP	"a(\[bc])\\1{3,4}"	abbb
666expectMatch	14.15 RP	{a([bc])\1*}	abbb	abbb	b
667expectMatch	14.16 RP	{a([bc])\1*}	ab	ab	b
668expectMatch	14.17 RP	{a([bc])(\1*)}	ab	ab	b	""
669expectError	14.18 -		{a((b)\1)}	ESUBREG
670expectError	14.19 -		{a(b)c\2}	ESUBREG
671expectMatch	14.20 bR	{a\(b*\)c\1}	abbcbb	abbcbb	bb
672expectMatch	14.21 RP	{^([bc])\1*$}	bbb	bbb	b
673expectMatch	14.22 RP	{^([bc])\1*$}	ccc	ccc	c
674expectNomatch	14.23 RP	{^([bc])\1*$}	bcb
675expectMatch	14.24 LRP	{^(\w+)( \1)+$}	{abc abc abc} {abc abc abc} abc { abc}
676expectNomatch	14.25 LRP	{^(\w+)( \1)+$}	{abc abd abc}
677expectNomatch	14.26 LRP	{^(\w+)( \1)+$}	{abc abc abd}
678expectMatch	14.27 RP	{^(.+)( \1)+$}	{abc abc abc} {abc abc abc} abc { abc}
679expectNomatch	14.28 RP	{^(.+)( \1)+$}	{abc abd abc}
680expectNomatch	14.29 RP	{^(.+)( \1)+$}	{abc abc abd}
681
682
683doing 15 "octal escapes vs back references"
684# initial zero is always octal
685expectMatch	15.1  MP	"a\\010b"	"a\bb"	"a\bb"
686expectMatch	15.2  MP	"a\\0070b"	"a\0070b"	"a\0070b"
687expectMatch	15.3  MP	"a\\07b"	"a\007b"	"a\007b"
688expectMatch	15.4  MP	"a(b)(b)(b)(b)(b)(b)(b)(b)(b)(b)\\07c" \
689	"abbbbbbbbbb\007c" abbbbbbbbbb\007c b b b b b b b b b b
690# a single digit is always a backref
691expectError	15.5  -		{a\7b}	ESUBREG
692# otherwise it's a backref only if within range (barf!)
693expectMatch	15.6  MP	"a\\10b"	"a\bb"	"a\bb"
694expectMatch	15.7  MP	{a\101b}	aAb	aAb
695expectMatch	15.8  RP	{a(b)(b)(b)(b)(b)(b)(b)(b)(b)(b)\10c} \
696	"abbbbbbbbbbbc" abbbbbbbbbbbc b b b b b b b b b b
697# but we're fussy about border cases -- guys who want octal should use the zero
698expectError	15.9  -	{a((((((((((b\10))))))))))c}	ESUBREG
699# BREs don't have octal, EREs don't have backrefs
700expectMatch	15.10 MP	"a\\12b"	"a\nb"	"a\nb"
701expectError	15.11 b		{a\12b}		ESUBREG
702expectMatch	15.12 eAS	{a\12b}		a12b	a12b
703expectMatch	15.13 MP	{a\701b}	a\u00381b	a\u00381b
704
705
706doing 16 "expanded syntax"
707expectMatch	16.1 xP		"a b c"		"abc"	"abc"
708expectMatch	16.2 xP		"a b #oops\nc\td"	"abcd"	"abcd"
709expectMatch	16.3 x		"a\\ b\\\tc"	"a b\tc"	"a b\tc"
710expectMatch	16.4 xP		"a b\\#c"	"ab#c"	"ab#c"
711expectMatch	16.5 xP		"a b\[c d]e"	"ab e"	"ab e"
712expectMatch	16.6 xP		"a b\[c#d]e"	"ab#e"	"ab#e"
713expectMatch	16.7 xP		"a b\[c#d]e"	"abde"	"abde"
714expectMatch	16.8 xSPB	"ab{ d"		"ab\{d"	"ab\{d"
715expectMatch	16.9 xPQ	"ab{ 1 , 2 }c"	"abc"	"abc"
716
717
718doing 17 "misc syntax"
719expectMatch	17.1 P	a(?#comment)b	ab	ab
720
721
722doing 18 "unmatchable REs"
723expectNomatch	18.1 I	a^b		ab
724
725
726doing 19 "case independence"
727expectMatch	19.1 &i		ab		Ab	Ab
728expectMatch	19.2 &i		{a[bc]}		aC	aC
729expectNomatch	19.3 &i		{a[^bc]}	aB
730expectMatch	19.4 &iM	{a[b-d]}	aC	aC
731expectNomatch	19.5 &iM	{a[^b-d]}	aC
732
733
734doing 20 "directors and embedded options"
735expectError	20.1  &		***?		BADPAT
736expectMatch	20.2  q		***?		***?	***?
737expectMatch	20.3  &P	***=a*b		a*b	a*b
738expectMatch	20.4  q		***=a*b		***=a*b	***=a*b
739expectMatch	20.5  bLP	{***:\w+}	ab	ab
740expectMatch	20.6  eLP	{***:\w+}	ab	ab
741expectError	20.7  &		***:***=a*b	BADRPT
742expectMatch	20.8  &P	***:(?b)a+b	a+b	a+b
743expectMatch	20.9  P		(?b)a+b		a+b	a+b
744expectError	20.10 e		{(?b)\w+}	BADRPT
745expectMatch	20.11 bAS	{(?b)\w+}	(?b)w+	(?b)w+
746expectMatch	20.12 iP	(?c)a		a	a
747expectNomatch	20.13 iP	(?c)a		A
748expectMatch	20.14 APS	{(?e)\W+}	WW	WW
749expectMatch	20.15 P		(?i)a+		Aa	Aa
750expectNomatch	20.16 P		"(?m)a.b"	"a\nb"
751expectMatch	20.17 P		"(?m)^b"	"a\nb"	"b"
752expectNomatch	20.18 P		"(?n)a.b"	"a\nb"
753expectMatch	20.19 P		"(?n)^b"	"a\nb"	"b"
754expectNomatch	20.20 P		"(?p)a.b"	"a\nb"
755expectNomatch	20.21 P		"(?p)^b"	"a\nb"
756expectMatch	20.22 P		(?q)a+b		a+b	a+b
757expectMatch	20.23 nP	"(?s)a.b"	"a\nb"	"a\nb"
758expectMatch	20.24 xP	"(?t)a b"	"a b"	"a b"
759expectMatch	20.25 P		"(?w)a.b"	"a\nb"	"a\nb"
760expectMatch	20.26 P		"(?w)^b"	"a\nb"	"b"
761expectMatch	20.27 P		"(?x)a b"	"ab"	"ab"
762expectError	20.28 -		(?z)ab		BADOPT
763expectMatch	20.29 P		(?ici)a+	Aa	Aa
764expectError	20.30 P		(?i)(?q)a+	BADRPT
765expectMatch	20.31 P		(?q)(?i)a+	(?i)a+	(?i)a+
766expectMatch	20.32 P		(?qe)a+		a	a
767expectMatch	20.33 xP	"(?q)a b"	"a b"	"a b"
768expectMatch	20.34 P		"(?qx)a b"	"a b"	"a b"
769expectMatch	20.35 P		(?qi)ab		Ab	Ab
770
771
772doing 21 "capturing"
773expectMatch	21.1  -		a(b)c		abc	abc	b
774expectMatch	21.2  P		a(?:b)c		xabc	abc
775expectMatch	21.3  -		a((b))c		xabcy	abc	b	b
776expectMatch	21.4  P		a(?:(b))c	abcy	abc	b
777expectMatch	21.5  P		a((?:b))c	abc	abc	b
778expectMatch	21.6  P		a(?:(?:b))c	abc	abc
779expectIndices	21.7  Q		"a(b){0}c"	ac	{0 1}	{-1 -1}
780expectMatch	21.8  -		a(b)c(d)e	abcde	abcde	b	d
781expectMatch	21.9  -		(b)c(d)e	bcde	bcde	b	d
782expectMatch	21.10 -		a(b)(d)e	abde	abde	b	d
783expectMatch	21.11 -		a(b)c(d)	abcd	abcd	b	d
784expectMatch	21.12 -		(ab)(cd)	xabcdy	abcd	ab	cd
785expectMatch	21.13 -		a(b)?c		xabcy	abc	b
786expectIndices	21.14 -		a(b)?c		xacy	{1 2}	{-1 -1}
787expectMatch	21.15 -		a(b)?c(d)?e	xabcdey	abcde	b	d
788expectIndices	21.16 -		a(b)?c(d)?e	xacdey	{1 4}	{-1 -1}	{3 3}
789expectIndices	21.17 -		a(b)?c(d)?e	xabcey	{1 4}	{2 2}	{-1 -1}
790expectIndices	21.18 -		a(b)?c(d)?e	xacey	{1 3}	{-1 -1}	{-1 -1}
791expectMatch	21.19 -		a(b)*c		xabcy	abc	b
792expectIndices	21.20 -		a(b)*c		xabbbcy	{1 5}	{4 4}
793expectIndices	21.21 -		a(b)*c		xacy	{1 2}	{-1 -1}
794expectMatch	21.22 -		a(b*)c		xabbbcy	abbbc	bbb
795expectMatch	21.23 -		a(b*)c		xacy	ac	""
796expectNomatch	21.24 -		a(b)+c		xacy
797expectMatch	21.25 -		a(b)+c		xabcy	abc	b
798expectIndices	21.26 -		a(b)+c		xabbbcy	{1 5}	{4 4}
799expectMatch	21.27 -		a(b+)c		xabbbcy	abbbc	bbb
800expectIndices	21.28 Q		"a(b){2,3}c"	xabbbcy	{1 5}	{4 4}
801expectIndices	21.29 Q		"a(b){2,3}c"	xabbcy	{1 4}	{3 3}
802expectNomatch	21.30 Q		"a(b){2,3}c"	xabcy
803expectMatch	21.31 LP	"\\y(\\w+)\\y"	"-- abc-"	"abc"	"abc"
804expectMatch	21.32 -		a((b|c)d+)+	abacdbd	acdbd	bd	b
805expectMatch	21.33 N		(.*).*		abc	abc	abc
806expectMatch	21.34 N		(a*)*		bc	""	""
807expectMatch	21.35 M		{ TO (([a-z0-9._]+|"([^"]+|"")+")+)}	{asd TO foo}	{ TO foo} foo o {}
808
809
810doing 22 "multicharacter collating elements"
811# again ugh
812expectMatch	22.1  &+L	{a[c]e}		ace	ace
813expectNomatch	22.2  &+IL	{a[c]h}		ach
814expectMatch	22.3  &+L	{a[[.ch.]]}	ach	ach
815expectNomatch	22.4  &+L	{a[[.ch.]]}	ace
816expectMatch	22.5  &+L	{a[c[.ch.]]}	ac	ac
817expectMatch	22.6  &+L	{a[c[.ch.]]}	ace	ac
818expectMatch	22.7  &+L	{a[c[.ch.]]}	ache	ach
819expectNomatch	22.8  &+L	{a[^c]e}	ace
820expectMatch	22.9  &+L	{a[^c]e}	abe	abe
821expectMatch	22.10 &+L	{a[^c]e}	ache	ache
822expectNomatch	22.11 &+L	{a[^[.ch.]]}	ach
823expectMatch	22.12 &+L	{a[^[.ch.]]}	ace	ac
824expectMatch	22.13 &+L	{a[^[.ch.]]}	ac	ac
825expectMatch	22.14 &+L	{a[^[.ch.]]}	abe	ab
826expectNomatch	22.15 &+L	{a[^c[.ch.]]}	ach
827expectNomatch	22.16 &+L	{a[^c[.ch.]]}	ace
828expectNomatch	22.17 &+L	{a[^c[.ch.]]}	ac
829expectMatch	22.18 &+L	{a[^c[.ch.]]}	abe	ab
830expectMatch	22.19 &+L	{a[^b]}		ac	ac
831expectMatch	22.20 &+L	{a[^b]}		ace	ac
832expectMatch	22.21 &+L	{a[^b]}		ach	ach
833expectNomatch	22.22 &+L	{a[^b]}		abe
834
835
836doing 23 "lookahead constraints"
837expectMatch	23.1 HP		a(?=b)b*	ab	ab
838expectNomatch	23.2 HP		a(?=b)b*	a
839expectMatch	23.3 HP		a(?=b)b*(?=c)c*	abc	abc
840expectNomatch	23.4 HP		a(?=b)b*(?=c)c*	ab
841expectNomatch	23.5 HP		a(?!b)b*	ab
842expectMatch	23.6 HP		a(?!b)b*	a	a
843expectMatch	23.7 HP		(?=b)b		b	b
844expectNomatch	23.8 HP		(?=b)b		a
845
846
847doing 24 "non-greedy quantifiers"
848expectMatch	24.1  PT	ab+?		abb	ab
849expectMatch	24.2  PT	ab+?c		abbc	abbc
850expectMatch	24.3  PT	ab*?		abb	a
851expectMatch	24.4  PT	ab*?c		abbc	abbc
852expectMatch	24.5  PT	ab??		ab	a
853expectMatch	24.6  PT	ab??c		abc	abc
854expectMatch	24.7  PQT	"ab{2,4}?"	abbbb	abb
855expectMatch	24.8  PQT	"ab{2,4}?c"	abbbbc	abbbbc
856expectMatch	24.9  -		3z*		123zzzz456	3zzzz
857expectMatch	24.10 PT	3z*?		123zzzz456	3
858expectMatch	24.11 -		z*4		123zzzz456	zzzz4
859expectMatch	24.12 PT	z*?4		123zzzz456	zzzz4
860expectMatch	24.13 PT	{^([^/]+?)(?:/([^/]+?))(?:/([^/]+?))?$}	{foo/bar/baz}	{foo/bar/baz} {foo} {bar} {baz}
861
862
863doing 25 "mixed quantifiers"
864# this is very incomplete as yet
865# should include |
866expectMatch	25.1 PNT	{^(.*?)(a*)$}	"xyza"	xyza	xyz	a
867expectMatch	25.2 PNT	{^(.*?)(a*)$}	"xyzaa"	xyzaa	xyz	aa
868expectMatch	25.3 PNT	{^(.*?)(a*)$}	"xyz"	xyz	xyz	""
869
870
871doing 26 "tricky cases"
872# attempts to trick the matcher into accepting a short match
873expectMatch	26.1 -		(week|wee)(night|knights) \
874	"weeknights" weeknights wee knights
875expectMatch	26.2 RP		{a(bc*).*\1}	abccbccb abccbccb	b
876expectMatch	26.3 -		{a(b.[bc]*)+}	abcbd	abcbd	bd
877
878
879doing 27 "implementation misc."
880# duplicate arcs are suppressed
881expectMatch	27.1 P		a(?:b|b)c	abc	abc
882# make color/subcolor relationship go back and forth
883expectMatch	27.2 &		{[ab][ab][ab]}	aba	aba
884expectMatch	27.3 &		{[ab][ab][ab][ab][ab][ab][ab]} \
885	"abababa" abababa
886
887
888doing 28 "boundary busters etc."
889# color-descriptor allocation changes at 10
890expectMatch	28.1 &		abcdefghijkl	"abcdefghijkl"	abcdefghijkl
891# so does arc allocation
892expectMatch	28.2 P		a(?:b|c|d|e|f|g|h|i|j|k|l|m)n	"agn"	agn
893# subexpression tracking also at 10
894expectMatch	28.3 -		a(((((((((((((b)))))))))))))c \
895	"abc" abc b b b b b b b b b b b b b
896# state-set handling changes slightly at unsigned size (might be 64...)
897# (also stresses arc allocation)
898expectMatch	28.4  Q		"ab{1,100}c"	abbc	abbc
899expectMatch	28.5  Q		"ab{1,100}c" \
900	"abbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbc" \
901	abbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbc
902expectMatch	28.6  Q		"ab{1,100}c" \
903	"abbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbc"\
904	abbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbc
905# force small cache and bust it, several ways
906expectMatch	28.7  LP	{\w+abcdefgh}	xyzabcdefgh	xyzabcdefgh
907expectMatch	28.8  %LP	{\w+abcdefgh}	xyzabcdefgh	xyzabcdefgh
908expectMatch	28.9  %LP	{\w+abcdefghijklmnopqrst} \
909	"xyzabcdefghijklmnopqrst" xyzabcdefghijklmnopqrst
910expectIndices	28.10 %LP	{\w+(abcdefgh)?} xyz	{0 2}	{-1 -1}
911expectIndices	28.11 %LP	{\w+(abcdefgh)?} xyzabcdefg	{0 9}	{-1 -1}
912expectIndices	28.12 %LP	{\w+(abcdefghijklmnopqrst)?} \
913	"xyzabcdefghijklmnopqrs" {0 21} {-1 -1}
914
915
916doing 29 "incomplete matches"
917expectPartial		29.1  t		def	abc	{3 2}	""
918expectPartial		29.2  t		bcd	abc	{1 2}	""
919expectPartial		29.3  t		abc	abab	{0 3}	""
920expectPartial		29.4  t		abc	abdab	{3 4}	""
921expectIndices		29.5  t		abc	abc	{0 2}	{0 2}
922expectIndices		29.6  t		abc	xyabc	{2 4}	{2 4}
923expectPartial		29.7  t		abc+	xyab	{2 3}	""
924expectIndices		29.8  t		abc+	xyabc	{2 4}	{2 4}
925knownBug expectIndices	29.9  t		abc+	xyabcd	{2 4}	{6 5}
926expectIndices		29.10 t		abc+	xyabcdd	{2 4}	{7 6}
927expectPartial		29.11 tPT	abc+?	xyab	{2 3}	""
928# the retain numbers in these two may look wrong, but they aren't
929expectIndices		29.12 tPT	abc+?	xyabc	{2 4}	{5 4}
930expectIndices		29.13 tPT	abc+?	xyabcc	{2 4}	{6 5}
931expectIndices		29.14 tPT	abc+?	xyabcd	{2 4}	{6 5}
932expectIndices		29.15 tPT	abc+?	xyabcdd	{2 4}	{7 6}
933expectIndices		29.16 t		abcd|bc	xyabc	{3 4}	{2 4}
934expectPartial		29.17 tn	.*k	"xx\nyyy"	{3 5}	""
935
936
937doing 30 "misc. oddities and old bugs"
938expectError	30.1 &		***	BADRPT
939expectMatch	30.2 N		a?b*	abb	abb
940expectMatch	30.3 N		a?b*	bb	bb
941expectMatch	30.4 &		a*b	aab	aab
942expectMatch	30.5 &		^a*b	aaaab	aaaab
943expectMatch	30.6 &M		{[0-6][1-2][0-3][0-6][1-6][0-6]} \
944	"010010" 010010
945# temporary REG_BOSONLY kludge
946expectMatch	30.7 s		abc	abcd	abc
947expectNomatch	30.8 s		abc	xabcd
948# back to normal stuff
949expectMatch	30.9 HLP	{(?n)^(?![t#])\S+} \
950	"tk\n\n#\n#\nit0"	it0
951
952
953# Now for tests *not* written by Henry Spencer
954
955namespace import -force ::tcltest::test
956
957# Tests resulting from bugs reported by users
958test reg-31.1 {[[:xdigit:]] behaves correctly when followed by [[:space:]]} {
959    set str {2:::DebugWin32}
960    set re {([[:xdigit:]])([[:space:]]*)}
961    list [regexp $re $str match xdigit spaces] $match $xdigit $spaces
962    # Code used to produce {1 2:::DebugWin32 2 :::DebugWin32} !!!
963} {1 2 2 {}}
964
965test reg-32.1 {canmatch functionality -- at end} testregexp {
966    set pat {blah}
967    set line "asd asd"
968    # can match at the final d, if '%' follows
969    set res [testregexp -xflags -- c $pat $line resvar]
970    lappend res $resvar
971} {0 7}
972test reg-32.2 {canmatch functionality -- at end} testregexp {
973    set pat {s%$}
974    set line "asd asd"
975    # can only match after the end of the string
976    set res [testregexp -xflags -- c $pat $line resvar]
977    lappend res $resvar
978} {0 7}
979test reg-32.3 {canmatch functionality -- not last char} testregexp {
980    set pat {[^d]%$}
981    set line "asd asd"
982    # can only match after the end of the string
983    set res [testregexp -xflags -- c $pat $line resvar]
984    lappend res $resvar
985} {0 7}
986test reg-32.3.1 {canmatch functionality -- no match} testregexp {
987    set pat {\Zx}
988    set line "asd asd"
989    # can match the last char, if followed by x
990    set res [testregexp -xflags -- c $pat $line resvar]
991    lappend res $resvar
992} {0 -1}
993test reg-32.4 {canmatch functionality -- last char} {knownBug testregexp} {
994    set pat {.x}
995    set line "asd asd"
996    # can match the last char, if followed by x
997    set res [testregexp -xflags -- c $pat $line resvar]
998    lappend res $resvar
999} {0 6}
1000test reg-32.4.1 {canmatch functionality -- last char} {knownBug testregexp} {
1001    set pat {.x$}
1002    set line "asd asd"
1003    # can match the last char, if followed by x
1004    set res [testregexp -xflags -- c $pat $line resvar]
1005    lappend res $resvar
1006} {0 6}
1007test reg-32.5 {canmatch functionality -- last char} {knownBug testregexp} {
1008    set pat {.[^d]x$}
1009    set line "asd asd"
1010    # can match the last char, if followed by not-d and x.
1011    set res [testregexp -xflags -- c $pat $line resvar]
1012    lappend res $resvar
1013} {0 6}
1014test reg-32.6 {canmatch functionality -- last char} {knownBug testregexp} {
1015    set pat {[^a]%[^\r\n]*$}
1016    set line "asd asd"
1017    # can match at the final d, if '%' follows
1018    set res [testregexp -xflags -- c $pat $line resvar]
1019    lappend res $resvar
1020} {0 6}
1021test reg-32.7 {canmatch functionality -- last char} {knownBug testregexp} {
1022    set pat {[^a]%$}
1023    set line "asd asd"
1024    # can match at the final d, if '%' follows
1025    set res [testregexp -xflags -- c $pat $line resvar]
1026    lappend res $resvar
1027} {0 6}
1028test reg-32.8 {canmatch functionality -- last char} {knownBug testregexp} {
1029    set pat {[^x]%$}
1030    set line "asd asd"
1031    # can match at the final d, if '%' follows
1032    set res [testregexp -xflags -- c $pat $line resvar]
1033    lappend res $resvar
1034} {0 6}
1035test reg-32.9 {canmatch functionality -- more complex case} {knownBug testregexp} {
1036    set pat {((\B\B|\Bh+line)[ \t]*|[^\B]%[^\r\n]*)$}
1037    set line "asd asd"
1038    # can match at the final d, if '%' follows
1039    set res [testregexp -xflags -- c $pat $line resvar]
1040    lappend res $resvar
1041} {0 6}
1042
1043# Tests reg-33.*: Checks for bug fixes
1044
1045test reg-33.1 {Bug 230589} {
1046    regexp {[ ]*(^|[^%])%V} "*%V2" m s
1047} 1
1048test reg-33.2 {Bug 504785} {
1049    regexp -inline {([^_.]*)([^.]*)\.(..)(.).*} bbcos_001_c01.q1la
1050} {bbcos_001_c01.q1la bbcos _001_c01 q1 l}
1051test reg-33.3 {Bug 505048} {
1052    regexp {\A\s*[^<]*\s*<([^>]+)>} a<a>
1053} 1
1054test reg-33.4 {Bug 505048} {
1055    regexp {\A\s*([^b]*)b} ab
1056} 1
1057test reg-33.5 {Bug 505048} {
1058    regexp {\A\s*[^b]*(b)} ab
1059} 1
1060test reg-33.6 {Bug 505048} {
1061    regexp {\A(\s*)[^b]*(b)} ab
1062} 1
1063test reg-33.7 {Bug 505048} {
1064    regexp {\A\s*[^b]*b} ab
1065} 1
1066test reg-33.8 {Bug 505048} {
1067    regexp -inline {\A\s*[^b]*b} ab
1068} ab
1069test reg-33.9 {Bug 505048} {
1070    regexp -indices -inline {\A\s*[^b]*b} ab
1071} {{0 1}}
1072test reg-33.10 {Bug 840258} -body {
1073    regsub {(^|\n)+\.*b} \n.b {} tmp
1074} -cleanup {
1075    unset tmp
1076} -result 1
1077test reg-33.11 {Bug 840258} -body {
1078    regsub {(^|[\n\r]+)\.*\?<.*?(\n|\r)+} \
1079	    "TQ\r\n.?<5000267>Test already stopped\r\n" {} tmp
1080} -cleanup {
1081    unset tmp
1082} -result 1
1083test reg-33.12 {Bug 1810264 - bad read} {
1084    regexp {\3161573148} {\3161573148}
1085} 0
1086test reg-33.13 {Bug 1810264 - infinite loop} {
1087    regexp {($|^)*} {x}
1088} 1
1089# Some environments have small default stack sizes. [Bug 1905562]
1090test reg-33.14 {Bug 1810264 - super-expensive expression} nonPortable {
1091    regexp {(x{200}){200}$y} {x}
1092} 0
1093
1094test reg-33.15.1 {Bug 3603557 - an "in the wild" RE} {
1095    lindex [regexp -expanded -about {
1096	^TETRA_MODE_CMD				# Message Type
1097	([[:blank:]]+)				# Pad
1098	(ETS_1_1|ETS_1_2|ETS_2_2)		# SystemCode
1099	([[:blank:]]+)				# Pad
1100	(CONTINUOUS|CARRIER|MCCH|TRAFFIC)	# SharingMode
1101	([[:blank:]]+)				# Pad
1102	([[:digit:]]{1,2})			# ColourCode
1103	([[:blank:]]+)				# Pad
1104	(1|2|3|4|6|9|12|18)			# TSReservedFrames
1105	([[:blank:]]+)				# Pad
1106	(PASS|TRUE|FAIL|FALSE)			# UPlaneDTX
1107	([[:blank:]]+)				# Pad
1108	(PASS|TRUE|FAIL|FALSE)			# Frame18Extension
1109	([[:blank:]]+)				# Pad
1110	([[:digit:]]{1,4})			# MCC
1111	([[:blank:]]+)				# Pad
1112	([[:digit:]]{1,5})			# MNC
1113	([[:blank:]]+)				# Pad
1114	(BOTH|BCAST|ENQRY|NONE)			# NbrCellBcast
1115	([[:blank:]]+)				# Pad
1116	(UNKNOWN|LOW|MEDIUM|HIGH)		# CellServiceLevel
1117	([[:blank:]]+)				# Pad
1118	(PASS|TRUE|FAIL|FALSE)			# LateEntryInfo
1119	([[:blank:]]+)				# Pad
1120	(300|400)				# FrequencyBand
1121	([[:blank:]]+)				# Pad
1122	(NORMAL|REVERSE)			# ReverseOperation
1123	([[:blank:]]+)				# Pad
1124	(NONE|\+6\.25|\-6\.25|\+12\.5)		# Offset
1125	([[:blank:]]+)				# Pad
1126	(10)					# DuplexSpacing
1127	([[:blank:]]+)				# Pad
1128	([[:digit:]]{1,4})			# MainCarrierNr
1129	([[:blank:]]+)				# Pad
1130	(0|1|2|3)				# NrCSCCH
1131	([[:blank:]]+)				# Pad
1132	(15|20|25|30|35|40|45)			# MSTxPwrMax
1133	([[:blank:]]+)				# Pad
1134	(\-125|\-120|\-115|\-110|\-105|\-100|\-95|\-90|\-85|\-80|\-75|\-70|\-65|\-60|\-55|\-50)
1135						# RxLevAccessMin
1136	([[:blank:]]+)				# Pad
1137	(\-53|\-51|\-49|\-47|\-45|\-43|\-41|\-39|\-37|\-35|\-33|\-31|\-29|\-27|\-25|\-23)
1138						# AccessParameter
1139	([[:blank:]]+)				# Pad
1140	(DISABLE|[[:digit:]]{3,4})		# RadioDLTimeout
1141	([[:blank:]]+)				# Pad
1142	(\-[[:digit:]]{2,3})			# RSSIThreshold
1143	([[:blank:]]+)				# Pad
1144	([[:digit:]]{1,5})			# CCKIdSCKVerNr
1145	([[:blank:]]+)				# Pad
1146	([[:digit:]]{1,5})			# LocationArea
1147	([[:blank:]]+)				# Pad
1148	([(1|0)]{16})				# SubscriberClass
1149	([[:blank:]]+)				# Pad
1150	([(1|0)]{12})				# BSServiceDetails
1151	([[:blank:]]+)				# Pad
1152	(RANDOMIZE|IMMEDIATE|[[:digit:]]{1,2})	# IMM
1153	([[:blank:]]+)				# Pad
1154	([[:digit:]]{1,2})			# WT
1155	([[:blank:]]+)				# Pad
1156	([[:digit:]]{1,2})			# Nu
1157	([[:blank:]]+)				# Pad
1158	([0-1])					# FrameLngFctr
1159	([[:blank:]]+)				# Pad
1160	([[:digit:]]{1,2})			# TSPtr
1161	([[:blank:]]+)				# Pad
1162	([0-7])					# MinPriority
1163	([[:blank:]]+)				# Pad
1164	(PASS|TRUE|FAIL|FALSE)			# ExtdSrvcsEnabled
1165	([[:blank:]]+)				# Pad
1166	(.*)					# ConditionalFields
1167    }] 0
1168} 68
1169test reg-33.16.1 {Bug [8d2c0da36d]- another "in the wild" RE} {
1170    lindex [regexp -about "^MRK:client1: =1339 14HKelly Talisman 10011000 (\[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]*) \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 8 0 8 0 0 0 77 77 1 1 2 0 11 { 1 3 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 1 13HC6 My Creator 2 3 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 1 31HC7 Slightly offensive name, huh 3 8 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 1 23HE-mail:kelly@hotbox.com 4 9 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 1 17Hcompface must die 5 10 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 0 3HAir 6 12 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 1 14HPGP public key 7 13 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 1 16Hkelly@hotbox.com 8 30 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 0 12H2 text/plain 9 30 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 0 13H2 x-kom/basic 10 33 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 1 1H0 11 14 8 \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* \[0-9\]* 00000000 1 1H3 }\r?"] 0
1171} 1
1172
1173test reg-33.15 {constraint fixes} {
1174    regexp {(^)+^} x
1175} 1
1176test reg-33.16 {constraint fixes} {
1177    regexp {($^)+} x
1178} 0
1179test reg-33.17 {constraint fixes} {
1180    regexp {(^$)*} x
1181} 1
1182test reg-33.18 {constraint fixes} {
1183    regexp {(^(?!aa))+} {aa bb cc}
1184} 0
1185test reg-33.19 {constraint fixes} {
1186    regexp {(^(?!aa)(?!bb)(?!cc))+} {aa x}
1187} 0
1188test reg-33.20 {constraint fixes} {
1189    regexp {(^(?!aa)(?!bb)(?!cc))+} {bb x}
1190} 0
1191test reg-33.21 {constraint fixes} {
1192    regexp {(^(?!aa)(?!bb)(?!cc))+} {cc x}
1193} 0
1194test reg-33.22 {constraint fixes} {
1195    regexp {(^(?!aa)(?!bb)(?!cc))+} {dd x}
1196} 1
1197
1198test reg-33.23 {} {
1199    regexp {abcd(\m)+xyz} x
1200} 0
1201test reg-33.24 {} {
1202    regexp {abcd(\m)+xyz} a
1203} 0
1204test reg-33.25 {} {
1205    regexp {^abcd*(((((^(a c(e?d)a+|)+|)+|)+|)+|a)+|)} x
1206} 0
1207test reg-33.26 {} {
1208    regexp {a^(^)bcd*xy(((((($a+|)+|)+|)+$|)+|)+|)^$} x
1209} 0
1210test reg-33.27 {} {
1211    regexp {xyz(\Y\Y)+} x
1212} 0
1213test reg-33.28 {} {
1214    regexp {x|(?:\M)+} x
1215} 1
1216test reg-33.29 {} {
1217    # This is near the limits of the RE engine
1218    regexp [string repeat x*y*z* 480] x
1219} 1
1220
1221test reg-33.30 {Bug 1080042} {
1222    regexp {(\Y)+} foo
1223} 1
1224test reg-33.31 {Bug 7c64aa5e1a} {
1225    regexp -inline {(?b).\{1,10\}} {abcdef}
1226} abcdef
1227
1228
1229# cleanup
1230::tcltest::cleanupTests
1231return
1232
1233# Local Variables:
1234# mode: tcl
1235# End:
1236