Planet
navi homePPSaboutscreenshotsdownloaddevelopmentforum

source: downloads/tcl8.5.2/tests/reg.test @ 68

Last change on this file since 68 was 25, checked in by landauf, 16 years ago

added tcl to libs

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