Manual diff again ...<br>
<br>
Best,<br>
Christoph<br>
<br>
<b>==================== Summary ====================</b><br>
<br>
Name: Regex-Core-ct.74<br>
Author: ct<br>
Time: 3 November 2021, 2:56:37.143587 pm<br>
UUID: f1beae70-97a0-9e4f-9e5a-3235c0a6e43a<br>
Ancestors: Regex-Core-mt.61<br>
<br>
Adds support for unicode backslash syntax in pieces and character sets.<br>
<br>
Some examples:<br>
<br>
<font color="#000000">    </font><font color="#800080">'Squeak is the perfect language'</font><font color="#000000"> </font><font color="#000080">allRegexMatches:</font><font color="#000000"> </font><font color="#800080">'\w*\u0061\w*'</font><font color="#000000">.</font><font color="#000000"> </font><font color="#008080">"--> #('Squeak' 'language')"</font><font color="#000000"><br>
    </font><font color="#800080">'Squeak is beautiful'</font><font color="#000000"> </font><font color="#000080">allRegexMatches:</font><font color="#000000"> </font><font color="#800080">'\w*\x75\w*'</font><font color="#000000">.</font><font color="#000000"> </font><font color="#008080">"--> #('Squeak' 'beautiful')"</font><font color="#000000"><br>
    </font><font color="#000000">(</font><font color="#000000">WebUtils</font><font color="#000000"> </font><font color="#000080">jsonDecode:</font><font color="#000000"> </font><font color="#800080">'"$1.00 = \u20AC0.86 = \u00A30.84"'</font><font color="#000000"> </font><font color="#000080">readStream</font><font color="#000000">)</font><font color="#000000"> </font><font color="#000080">allRegexMatches:</font><font color="#000000"> </font><font color="#800080">'\p{Sc}\d+\.[\x31-\u{ar57}]+'</font><font color="#000000">.</font><font color="#000000"> </font><font color="#008080">"--> #('?0.86' '?0.84')"</font><font color="#000000"><br>
    </font><font color="#800080">'Carpe Squeak!'</font><font color="#000000"> </font><font color="#000080">allRegexMatches:</font><font color="#000000"> </font><font color="#800080">'\p{L}+'</font><font color="#000000">.</font><font color="#000000"> </font><font color="#008080">"--> #('Carpe' 'Squeak')"</font><font color="#000000"><br>
    </font><font color="#000000">(</font><font color="#000000">WebUtils</font><font color="#000000"> </font><font color="#000080">jsonDecode:</font><font color="#000000"> </font><font color="#800080">'" get rid of \u2007all these nonsense\nseparators"'</font><font color="#000000"> </font><font color="#000080">readStream</font><font color="#000000">)</font><font color="#000000"> </font><font color="#000080">allRegexMatches:</font><font color="#000000"> </font><font color="#800080">'\P{Z}+'</font><font color="#000000">.</font><font color="#000000"> </font><font color="#008080">"--> #('get' 'rid' 'of' 'all' 'these' 'nonsense<br>
separators')"</font><font color="#000000"><br>
</font><br>
This is a replacement for Regex-Core-ct.68 (which can be moved to the treated inbox) updated with support for the new syntax inside character sets, inspired by Regex-Core-tobe.62 (this is a counterproposal to Regex-Core-tobe.62). See Regex-Tests-Core-ct.28. The following changes have been made since Regex-Core-ct.68:<br>
<br>
- Factored out common parser logic from RxParser and RxCharSetParser into new common superclass RxAbstractParser. Apart from deduplication, this is crucial to use #[uni]codePoint and #unicodeCategory specials in both parsers. (I also considered invoking another RxParser from RxCharSetParser but eventually found this solution more elegant.)<br>
- Split up BackslashSpecials into BackslashPredicates (on RxAbstractParser) and BackslashConditions (only available on RxParser). Escaped uppercase characters (such as '\D') now automatically map to the negation of the lowercase special (see #backslashSpecial:). Deprecated RxsPredicate class >> #forEscapedLetter.<br>
- Cleaned up & deduplicated RxCharSetParser to match the functional style of RxParser. RxCharSetParser is now responsible by itself for handling BackslashConstants.<br>
- Made sure to parse escape characters in the end of a char set range, i.e., allow '[2-\x38]' asRegex and reject '[2-\d]' asRegex (like most other parsers out there do, too).<br>
- Correct maintaining of source position in a RegexSyntaxError that was signaled while parsing a char set. See #testRegexSyntaxErrorPosition.<br>
- Enabled and fixed matching against composed RxCharSets, which can happen now in the case of a pattern like '[\P{L}a]' asRegex.<br>
* Honor case-(in)sensitive matching in nested char sets by appending a #IgnoringCase: argument to #predicate[s|Negation|PartPredicate] on RxsCharSet resp. RxsPredicate.<br>
- Added support for Squeak-style codepoints such as '\x{2r100000}' asRegex matches: ' '.<br>
- Removed superfluos spaces from error messages.<br>
<br>
Reuploaded just another time, superseding Regex-Core-ct.71, to fix a small slip in RxsCharSet >> #predicatePartPredicateIgnoringCase:. Thanks to Tom (tobe) for testing! :-)<br>
<br>
Requires Kernel-ct.1419 (NumberParser >> #defaultBase:) and Multilingual-ct.259 (Unicode class >> #generalTagOf:).<br>
<br>
<b>=============== Diff against Regex-Core-mt.61 ===============</b><br>
<br>
<b>RxAbstractParser</b><br>
<font color="#FF0000">+ Object subclass: #RxAbstractParser<br>
+     instanceVariableNames: 'source lookahead'<br>
+     classVariableNames: 'BackslashConstants BackslashPredicates'<br>
+     poolDictionaries: ''<br>
+     category: 'Regex-Core'<br>
+ <br>
+ RxAbstractParser class <br>
+     instanceVariableNames: ''<br>
+ <br>
+ "I provide general parsing facilities for all kinds of regex parsers.<br>
+ <br>
+ Instance variables:<br>
+     input        <Stream> A stream with the expression being parsed.<br>
+     lookahead    <Character>    The current lookahead character."</font><br>
<br>
<b>RxAbstractParser class>>doShiftingSyntaxExceptionPositions:from: {exception signaling} · ct 10/28/2021 03:18</b><br>
<font color="#FF0000">+ doShiftingSyntaxExceptionPositions: aBlock from: start<br>
+     "When invoking a nested parser, make sure to update the positions of any syntax exception raised by this nested parser."<br>
+     ^ aBlock<br>
+         on: RegexSyntaxError<br>
+         do: [:ex | ex resignalAs: (ex copy<br>
+             position: ex position + start - 1;<br>
+             yourself)]</font><br>
<br>
<b>RxAbstractParser class>>initialize {class initialization} · ct 10/27/2021 23:30</b><br>
<font color="#FF0000">+ initialize<br>
+     "self initialize"<br>
+     self<br>
+         initializeBackslashConstants;<br>
+         initializeBackslashPredicates</font><br>
<br>
<b>RxAbstractParser class>>initializeBackslashConstants {class initialization} · ct 10/27/2021 07:50</b><br>
<font color="#FF0000">+ initializeBackslashConstants<br>
+     "self initializeBackslashConstants"<br>
+ <br>
+     (BackslashConstants := Dictionary new)<br>
+         at: $e put: Character escape;<br>
+         at: $n put: Character lf;<br>
+         at: $r put: Character cr;<br>
+         at: $f put: Character newPage;<br>
+         at: $t put: Character tab</font><br>
<br>
<b>RxAbstractParser class>>initializeBackslashPredicates {class initialization} · ct 10/27/2021 20:57</b><br>
<font color="#FF0000">+ initializeBackslashPredicates<br>
+     "The keys are characters that normally follow a $\, the values are either associations of classes and initialization selectors on their instance side, or evaluables that will be evaluated on the current parser instance."<br>
+     "self initializeBackslashPredicates"<br>
+ <br>
+     (BackslashPredicates := Dictionary new)<br>
+         at: $d put: RxsPredicate -> #beDigit;<br>
+         at: $p put: #unicodeCategory;<br>
+         at: $s put: RxsPredicate -> #beSpace;<br>
+         at: $u put: #unicodePoint;<br>
+         at: $w put: RxsPredicate -> #beWordConstituent;<br>
+         at: $x put: #codePoint.</font><br>
<br>
<b>RxAbstractParser class>>signalSyntaxException: {exception signaling} · avi 11/30/2003 13:25</b><br>
<font color="#FF0000">+ signalSyntaxException: errorString<br>
+     RegexSyntaxError new signal: errorString</font><br>
<br>
<b>RxAbstractParser class>>signalSyntaxException:at: {exception signaling} · CamilloBruni 10/7/2012 22:50</b><br>
<font color="#FF0000">+ signalSyntaxException: errorString at: errorPosition<br>
+     RegexSyntaxError signal: errorString at: errorPosition</font><br>
<br>
<b>RxAbstractParser>>backslashConstant {parsing} · ct 10/27/2021 07:48</b><br>
<font color="#FF0000">+ backslashConstant<br>
+ <br>
+     | character node |<br>
+     character := BackslashConstants at: lookahead ifAbsent: [^ nil].<br>
+     self next.<br>
+     node := RxsCharacter with: character.<br>
+     ^ node</font><br>
<br>
<b>RxAbstractParser>>backslashNode {parsing} · ct 10/28/2021 03:09</b><br>
<font color="#FF0000">+ backslashNode<br>
+ <br>
+     | char |<br>
+     lookahead ifNil: [ self signalParseError: 'bad quotation' ].<br>
+     <br>
+     self basicBackslashNode ifNotNil: [:node | ^node].<br>
+     <br>
+     char := lookahead.<br>
+     self next.<br>
+     ^ RxsCharacter with: char</font><br>
<br>
<b>RxAbstractParser>>backslashPredicate {parsing} · ct 10/27/2021 07:49</b><br>
<font color="#FF0000">+ backslashPredicate<br>
+ <br>
+     ^ self backslashSpecial: BackslashPredicates</font><br>
<br>
<b>RxAbstractParser>>backslashSpecial: {private} · ct 10/28/2021 02:56</b><br>
<font color="#FF0000">+ backslashSpecial: specials<br>
+ <br>
+     | negate specialSelector node |<br>
+     negate := false.<br>
+     specialSelector := specials at: lookahead ifAbsent: [<br>
+         (lookahead isLetter and: [lookahead isUppercase]) ifTrue: [<br>
+             negate := true.<br>
+             specialSelector := specials at: lookahead asLowercase ifAbsent: []].<br>
+         specialSelector ifNil: [^ nil]].<br>
+     self next.<br>
+     <br>
+     node := specialSelector isVariableBinding<br>
+         ifTrue: [specialSelector key new perform: specialSelector value]<br>
+         ifFalse: [specialSelector value: self].<br>
+     negate ifTrue: [node := node negated].<br>
+     ^ node</font><br>
<br>
<b>RxAbstractParser>>basicBackslashNode {parsing} · ct 10/28/2021 03:03</b><br>
<font color="#FF0000">+ basicBackslashNode<br>
+     <br>
+     self backslashConstant ifNotNil: [:node | ^ node].<br>
+     self backslashPredicate ifNotNil: [:node | ^ node].<br>
+     ^ nil</font><br>
<br>
<b>RxAbstractParser>>codePoint {parsing} · ct 10/27/2021 20:48</b><br>
<font color="#FF0000">+ codePoint<br>
+ <br>
+     ^ self codePoint: 2</font><br>
<br>
<b>RxAbstractParser>>codePoint: {parsing} · ct 10/27/2021 22:47</b><br>
<font color="#FF0000">+ codePoint: size<br>
+     "Matches a character that has the given code codepoint with the specified size of hex digits, unless braced.<br>
+     <codePoint> ::= \x ({<hex>} '|' <hex>[size])"<br>
+ <br>
+     | braced codeString codePoint codeStream |<br>
+     braced := self tryMatch: ${.<br>
+     codeString := braced<br>
+         ifFalse: [self<br>
+             input: size<br>
+             errorMessage: 'invalid codepoint']<br>
+         ifTrue: [self<br>
+             inputUpTo: $}<br>
+             errorMessage: 'no terminating "}"'].<br>
+     <br>
+     codeStream := codeString readStream.<br>
+     codePoint := ((ExtendedNumberParser on: codeStream)<br>
+         defaultBase: 16;<br>
+         nextInteger) ifNil: [<br>
+             self signalParseError: 'invalid codepoint'].<br>
+     codeStream atEnd ifFalse: [<br>
+         self signalParseError: 'invalid codepoint'].<br>
+     <br>
+     braced ifTrue: [<br>
+         self match: $}].<br>
+     <br>
+     ^ RxsCharacter with: (Character codePoint: codePoint)</font><br>
<br>
<b>RxAbstractParser>>initialize: {initialize-release} · ct 10/27/2021 07:24</b><br>
<font color="#FF0000">+ initialize: aStream<br>
+ <br>
+     source := aStream.<br>
+     self next.</font><br>
<br>
<b>RxAbstractParser>>input:errorMessage: {private} · ct 10/27/2021 20:52</b><br>
<font color="#FF0000">+ input: anInteger errorMessage: aString<br>
+     "Accumulate input stream with anInteger characters. Raise an error with the specified message if there are not enough characters available, or if the accumulated characters are not included in the characterSet."<br>
+ <br>
+     | accumulator |<br>
+     accumulator := WriteStream on: (String new: 20).<br>
+     anInteger timesRepeat: [<br>
+         lookahead ifNil: [self signalParseError: aString].<br>
+         accumulator nextPut: lookahead.<br>
+         self next].<br>
+     ^ accumulator contents</font><br>
<br>
<b>RxAbstractParser>>inputUpTo:errorMessage: {private} · ul 9/24/2015 08:25</b><br>
<font color="#FF0000">+ inputUpTo: aCharacter errorMessage: aString<br>
+     "Accumulate input stream until <aCharacter> is encountered<br>
+     and answer the accumulated chars as String, not including<br>
+     <aCharacter>. Signal error if end of stream is encountered,<br>
+     passing <aString> as the error description."<br>
+ <br>
+     | accumulator |<br>
+     accumulator := WriteStream on: (String new: 20).<br>
+     [ lookahead == aCharacter or: [lookahead == nil ] ]<br>
+         whileFalse: [<br>
+             accumulator nextPut: lookahead.<br>
+             self next].<br>
+     lookahead ifNil: [ self signalParseError: aString ].<br>
+     ^accumulator contents</font><br>
<br>
<b>RxAbstractParser>>inputUpToAny:errorMessage: {private} · ul 9/24/2015 08:24</b><br>
<font color="#FF0000">+ inputUpToAny: aDelimiterString errorMessage: aString<br>
+     "Accumulate input stream until any character from <aDelimiterString> is encountered<br>
+     and answer the accumulated chars as String, not including the matched characters from the<br>
+     <aDelimiterString>. Signal error if end of stream is encountered,<br>
+     passing <aString> as the error description."<br>
+ <br>
+     | accumulator |<br>
+     accumulator := WriteStream on: (String new: 20).<br>
+     [ lookahead == nil or: [ aDelimiterString includes: lookahead ] ]<br>
+         whileFalse: [<br>
+             accumulator nextPut: lookahead.<br>
+             self next ].<br>
+     lookahead ifNil: [ self signalParseError: aString ].<br>
+     ^accumulator contents</font><br>
<br>
<b>RxAbstractParser>>match: {parsing} · ct 10/27/2021 22:37</b><br>
<font color="#FF0000">+ match: aCharacter<br>
+     "<aCharacter> MUST match the current lookeahead. If this is the case, advance the input. Otherwise, blow up."<br>
+ <br>
+     aCharacter = lookahead ifTrue: [ ^self next ].<br>
+     self signalParseError: (lookahead<br>
+         ifNil: ['unexpected end']<br>
+         ifNotNil: ['unexpected character: ', lookahead asString])</font><br>
<br>
<b>RxAbstractParser>>next {private} · ct 10/27/2021 07:15</b><br>
<font color="#FF0000">+ next<br>
+ <br>
+     ^ lookahead := source next</font><br>
<br>
<b>RxAbstractParser>>signalParseError {private} · ct 10/27/2021 07:16</b><br>
<font color="#FF0000">+ signalParseError<br>
+ <br>
+     self class<br>
+         signalSyntaxException: 'Regex syntax error'<br>
+         at: source position</font><br>
<br>
<b>RxAbstractParser>>signalParseError: {private} · ct 10/27/2021 07:16</b><br>
<font color="#FF0000">+ signalParseError: aString<br>
+ <br>
+     self class signalSyntaxException: aString at: source position</font><br>
<br>
<b>RxAbstractParser>>tryMatch: {private} · ct 8/23/2021 21:01</b><br>
<font color="#FF0000">+ tryMatch: aCharacter<br>
+ <br>
+     ^ lookahead == ${<br>
+         ifTrue: [self next];<br>
+         yourself</font><br>
<br>
<b>RxAbstractParser>>unicodeCategory {parsing} · ct 10/27/2021 22:01</b><br>
<font color="#FF0000">+ unicodeCategory<br>
+     "Matches a character that belongs to the given unicode category.<br>
+     <unicodeCategory> ::= \p '{' <categoryName> '}'"<br>
+ <br>
+     | category |<br>
+     self match: ${.<br>
+     category := self inputUpTo: $} errorMessage: 'no terminating "}"'.<br>
+     self match: $}.<br>
+     ^ RxsPredicate new beUnicodeCategory: category</font><br>
<br>
<b>RxAbstractParser>>unicodePoint {parsing} · ct 10/27/2021 20:49</b><br>
<font color="#FF0000">+ unicodePoint<br>
+ <br>
+     ^ self codePoint: 4</font><br>
<br>
<b>RxCharSetParser (changed)</b><br>
<font color="#0000FF">- Object subclass: #RxCharSetParser<br>
-     instanceVariableNames: 'source lookahead elements'<br>
</font><font color="#FF0000">+ RxAbstractParser subclass: #RxCharSetParser<br>
+     instanceVariableNames: 'elements'<br>
</font>    classVariableNames: ''<br>
    poolDictionaries: ''<br>
    category: 'Regex-Core'<br>
<br>
RxCharSetParser class <br>
    instanceVariableNames: ''<br>
<br>
"-- Regular Expression Matcher v 1.1 (C) 1996, 1999 Vassili Bykov<br>
--<br>
I am a parser created to parse the insides of a character set ([...]) construct. I create and answer a collection of "elements", each being an instance of one of: RxsCharacter, RxsRange, or RxsPredicate.<br>
<br>
Instance Variables:<br>
<br>
<font color="#0000FF">-     source    <Stream>    open on whatever is inside the square brackets we have to parse.<br>
-     lookahead    <Character>    The current lookahead character<br>
</font>    elements    <Collection of: <RxsCharacter|RxsRange|RxsPredicate>> Parsing result"<br>
<br>
<b>RxCharSetParser>>add: {parsing} · ct 10/28/2021 02:24</b><br>
<font color="#FF0000">+ add: nodeOrNodes<br>
+ <br>
+     nodeOrNodes isCollection<br>
+         ifFalse: [elements add: nodeOrNodes]<br>
+         ifTrue: [elements addAll: nodeOrNodes]</font><br>
<br>
<b>RxCharSetParser>>addChar: {parsing} · vb 4/11/09 21:56 (removed)</b><br>
<font color="#0000FF">- addChar: aChar<br>
- <br>
-     elements add: (RxsCharacter with: aChar)</font><br>
<br>
<b>RxCharSetParser>>addRangeFrom:to: {parsing} · CamilloBruni 10/7/2012 22:52 (removed)</b><br>
<font color="#0000FF">- addRangeFrom: firstChar to: lastChar<br>
- <br>
-     firstChar asInteger > lastChar asInteger ifTrue:<br>
-         [RxParser signalSyntaxException: ' bad character range' at: source position].<br>
-     elements add: (RxsRange from: firstChar to: lastChar)</font><br>
<br>
<b>RxCharSetParser>>char {parsing} · ct 10/28/2021 03:06</b><br>
<font color="#FF0000">+ char<br>
+ <br>
+     | char |<br>
+     lookahead == $\ ifTrue:<br>
+         [self match: $\.<br>
+         ^self backslashNode<br>
+             ifNil: [RxsCharacter with: lookahead]].<br>
+     <br>
+     char := RxsCharacter with: lookahead.<br>
+     self next.<br>
+     ^char</font><br>
<br>
<b>RxCharSetParser>>char: {parsing} · ct 10/28/2021 02:20</b><br>
<font color="#FF0000">+ char: aCharacter<br>
+ <br>
+     ^ RxsCharacter with: aCharacter</font><br>
<br>
<b>RxCharSetParser>>charOrRange {parsing} · ct 10/28/2021 02:50</b><br>
<font color="#FF0000">+ charOrRange<br>
+ <br>
+     | firstChar lastChar |<br>
+     firstChar := self char.<br>
+     lookahead == $- ifFalse:<br>
+         [^firstChar].<br>
+     <br>
+     self next ifNil:<br>
+         [^{firstChar. self char: $-}].<br>
+     <br>
+     lastChar := self char.<br>
+     firstChar isRegexCharacter ifFalse:<br>
+         [self signalParseError: 'range must start with a single character'].<br>
+     lastChar isRegexCharacter ifFalse: <br>
+         [self signalParseError: 'range must end with a single character'].<br>
+     ^self rangeFrom: firstChar character to: lastChar character</font><br>
<br>
<b>RxCharSetParser>>element {parsing} · ct 10/28/2021 02:48</b><br>
<font color="#FF0000">+ element<br>
+ <br>
+     (lookahead == $[ and: [source peek == $:]) ifTrue:<br>
+         [^self namedSet].<br>
+     ^self charOrRange</font><br>
<br>
<b>RxCharSetParser>>initialize: {initialize-release} · ct 10/27/2021 07:24 (changed)</b><br>
initialize: aStream<br>
<br>
<font color="#0000FF">-     source := aStream.<br>
-     lookahead := aStream next.<br>
</font><font color="#FF0000">+     super initialize: aStream.<br>
</font>    elements := OrderedCollection new<br>
<br>
<b>RxCharSetParser>>match: {parsing} · ul 5/24/2015 22:01 (removed)</b><br>
<font color="#0000FF">- match: aCharacter<br>
- <br>
-     aCharacter = lookahead ifTrue: [ ^self next ].<br>
-     RxParser <br>
-         signalSyntaxException: 'unexpected character: ', (String with: lookahead)<br>
-         at: source position</font><br>
<br>
<b>RxCharSetParser>>namedSet {parsing} · ct 10/28/2021 02:19</b><br>
<font color="#FF0000">+ namedSet<br>
+ <br>
+     | name |<br>
+     self match: $[; match: $:.<br>
+     name := (String with: lookahead), (source upTo: $:).<br>
+     self next.<br>
+     self match: $].<br>
+     ^ RxsPredicate forNamedClass: name</font><br>
<br>
<b>RxCharSetParser>>next {parsing} · ul 5/24/2015 21:19 (removed)</b><br>
<font color="#0000FF">- next<br>
- <br>
-     ^lookahead := source next</font><br>
<br>
<b>RxCharSetParser>>parse {accessing} · ct 10/28/2021 02:49 (changed)</b><br>
parse<br>
<br>
<font color="#0000FF">-     lookahead == $- ifTrue: [<br>
-         self addChar: $-.<br>
-         self next ].<br>
-     [ lookahead == nil ] whileFalse: [ self parseStep ].<br>
</font><font color="#FF0000">+     [ lookahead == nil ] whileFalse: [ self add: self element ].<br>
</font>    ^elements<br>
<br>
<b>RxCharSetParser>>parseCharOrRange {parsing} · ul 5/24/2015 21:20 (removed)</b><br>
<font color="#0000FF">- parseCharOrRange<br>
- <br>
-     | firstChar |<br>
-     firstChar := lookahead.<br>
-     self next == $- ifFalse: [ ^self addChar: firstChar ].<br>
-     self next ifNil: [ ^self addChar: firstChar; addChar: $- ].<br>
-     self addRangeFrom: firstChar to: lookahead.<br>
-     self next</font><br>
<br>
<b>RxCharSetParser>>parseEscapeChar {parsing} · tobe 8/12/2021 08:56 (removed)</b><br>
<font color="#0000FF">- parseEscapeChar<br>
- <br>
-     | first |<br>
-     self match: $\.<br>
-     first := (RxsPredicate forEscapedLetter: lookahead)<br>
-         ifNil: [ RxsCharacter with: lookahead ].<br>
-     self next == $- ifFalse: [^ elements add: first].<br>
-     self next ifNil: [<br>
-         elements add: first.<br>
-         ^ self addChar: $-].<br>
-     self addRangeFrom: first character to: lookahead.<br>
-     self next</font><br>
<br>
<b>RxCharSetParser>>parseNamedSet {parsing} · ul 5/24/2015 22:00 (removed)</b><br>
<font color="#0000FF">- parseNamedSet<br>
- <br>
-     | name |<br>
-     self match: $[; match: $:.<br>
-     name := (String with: lookahead), (source upTo: $:).<br>
-     self next.<br>
-     self match: $].<br>
-     elements add: (RxsPredicate forNamedClass: name)</font><br>
<br>
<b>RxCharSetParser>>parseStep {parsing} · ul 5/24/2015 21:14 (removed)</b><br>
<font color="#0000FF">- parseStep<br>
- <br>
-     lookahead == $[ ifTrue:<br>
-         [source peek == $:<br>
-             ifTrue: [^self parseNamedSet]<br>
-             ifFalse: [^self parseCharOrRange]].<br>
-     lookahead == $\ ifTrue:<br>
-         [^self parseEscapeChar].<br>
-     lookahead == $- ifTrue:<br>
-         [RxParser signalSyntaxException: 'invalid range' at: source position].<br>
-     self parseCharOrRange</font><br>
<br>
<b>RxCharSetParser>>rangeFrom:to: {parsing} · ct 10/28/2021 02:20</b><br>
<font color="#FF0000">+ rangeFrom: firstChar to: lastChar<br>
+ <br>
+     firstChar asInteger > lastChar asInteger ifTrue:<br>
+         [self signalParseError: 'bad character range'].<br>
+     ^ RxsRange from: firstChar to: lastChar</font><br>
<br>
<b>RxMatchOptimizer>>syntaxCharSet: {double dispatch} · ct 10/27/2021 08:55 (changed)</b><br>
syntaxCharSet: charSetNode <br>
    "All these (or none of these) characters is the prefix."<br>
<br>
    (charSetNode enumerableSetIgnoringCase: ignoreCase) ifNotNil: [ :enumerableSet |<br>
        charSetNode isNegated<br>
            ifTrue: [ self addNonPrefixes: enumerableSet ]<br>
            ifFalse: [ self addPrefixes: enumerableSet ] ].<br>
<br>
<font color="#0000FF">-     charSetNode predicates ifNotNil: [ :charsetPredicates |<br>
</font><font color="#FF0000">+     (charSetNode predicatesIgnoringCase: ignoreCase) ifNotNil: [ :charsetPredicates |<br>
</font>        charSetNode isNegated<br>
            ifTrue: [ <br>
                charsetPredicates do: [ :each | self addNonPredicate: each ] ]<br>
            ifFalse: [ <br>
                charsetPredicates do: [ :each | self addPredicate: each ] ] ]<br>
<br>
<b>RxMatchOptimizer>>syntaxPredicate: {double dispatch} · ct 10/27/2021 08:54 (changed)</b><br>
syntaxPredicate: predicateNode <br>
<br>
<font color="#0000FF">-     self addPredicate: predicateNode predicate<br>
</font><font color="#FF0000">+     self addPredicate: (predicateNode predicateIgnoringCase: ignoreCase)</font><br>
<br>
<b>RxMatcher>>syntaxPredicate: {double dispatch} · ct 10/27/2021 08:54 (changed)</b><br>
syntaxPredicate: predicateNode<br>
    "Double dispatch from the syntax tree. <br>
    A character set is a few characters, and we either match any of them,<br>
    or match any that is not one of them."<br>
<br>
<font color="#0000FF">-     ^RxmPredicate with: predicateNode predicate<br>
</font><font color="#FF0000">+     ^RxmPredicate with: (predicateNode predicateIgnoringCase: ignoreCase)</font><br>
<br>
<b>RxParser (changed)</b><br>
<font color="#0000FF">- Object subclass: #RxParser<br>
-     instanceVariableNames: 'input lookahead'<br>
-     classVariableNames: 'BackslashConstants BackslashSpecials'<br>
</font><font color="#FF0000">+ RxAbstractParser subclass: #RxParser<br>
+     instanceVariableNames: ''<br>
+     classVariableNames: 'BackslashConditions'<br>
</font>    poolDictionaries: ''<br>
    category: 'Regex-Core'<br>
<br>
RxParser class <br>
    instanceVariableNames: ''<br>
<br>
"-- Regular Expression Matcher v 1.1 (C) 1996, 1999 Vassili Bykov<br>
--<br>
<font color="#0000FF">- The regular expression parser. Translates a regular expression read from a stream into a parse tree. ('accessing' protocol). The tree can later be passed to a matcher initialization method. All other classes in this category implement the tree. Refer to their comments for any details.<br>
- <br>
- Instance variables:<br>
-     input        <Stream> A stream with the regular expression being parsed.<br>
-     lookahead    <Character>"<br>
</font><font color="#FF0000">+ The regular expression parser. Translates a regular expression read from a stream into a parse tree. ('accessing' protocol). The tree can later be passed to a matcher initialization method. All other classes in this category implement the tree. Refer to their comments for any details."</font><br>
<br>
<b>RxParser class>>initialize {class initialization} · ct 10/27/2021 07:50 (changed)</b><br>
initialize<br>
    "self initialize"<br>
<font color="#0000FF">-     self<br>
-         initializeBackslashConstants;<br>
-         initializeBackslashSpecials<br>
</font><font color="#FF0000">+     self initializeBackslashConditions</font><br>
<br>
<b>RxParser class>>initializeBackslashConditions {class initialization} · ct 10/27/2021 08:17</b><br>
<font color="#FF0000">+ initializeBackslashConditions<br>
+     "The keys are characters that normally follow a $\, the values are either associations of classes and initialization selectors on their instance side, or evaluables that will be evaluated on the current parser instance."<br>
+     "self initializeBackslashConditions"<br>
+ <br>
+     (BackslashConditions := Dictionary new)<br>
+         at: $b put: RxsContextCondition -> #beWordBoundary;<br>
+         at: $B put: RxsContextCondition -> #beNonWordBoundary;<br>
+         at: $< put: RxsContextCondition -> #beBeginningOfWord;<br>
+         at: $> put: RxsContextCondition -> #beEndOfWord.</font><br>
<br>
<b>RxParser class>>initializeBackslashConstants {class initialization} · lr 11/4/2009 22:14 (removed)</b><br>
<font color="#0000FF">- initializeBackslashConstants<br>
-     "self initializeBackslashConstants"<br>
- <br>
-     (BackslashConstants := Dictionary new)<br>
-         at: $e put: Character escape;<br>
-         at: $n put: Character lf;<br>
-         at: $r put: Character cr;<br>
-         at: $f put: Character newPage;<br>
-         at: $t put: Character tab</font><br>
<br>
<b>RxParser class>>initializeBackslashSpecials {class initialization} · vb 4/11/09 21:56 (removed)</b><br>
<font color="#0000FF">- initializeBackslashSpecials<br>
-     "Keys are characters that normally follow a \, the values are<br>
-     associations of classes and initialization selectors on the instance side<br>
-     of the classes."<br>
-     "self initializeBackslashSpecials"<br>
- <br>
-     (BackslashSpecials := Dictionary new)<br>
-         at: $w put: (Association key: RxsPredicate value: #beWordConstituent);<br>
-         at: $W put: (Association key: RxsPredicate value: #beNotWordConstituent);<br>
-         at: $s put: (Association key: RxsPredicate value: #beSpace);<br>
-         at: $S put: (Association key: RxsPredicate value: #beNotSpace);<br>
-         at: $d put: (Association key: RxsPredicate value: #beDigit);<br>
-         at: $D put: (Association key: RxsPredicate value: #beNotDigit);<br>
-         at: $b put: (Association key: RxsContextCondition value: #beWordBoundary);<br>
-         at: $B put: (Association key: RxsContextCondition value: #beNonWordBoundary);<br>
-         at: $< put: (Association key: RxsContextCondition value: #beBeginningOfWord);<br>
-         at: $> put: (Association key: RxsContextCondition value: #beEndOfWord)</font><br>
<br>
<b>RxParser class>>signalSyntaxException: {exception signaling} · avi 11/30/2003 13:25 (removed)</b><br>
<font color="#0000FF">- signalSyntaxException: errorString<br>
-     RegexSyntaxError new signal: errorString</font><br>
<br>
<b>RxParser class>>signalSyntaxException:at: {exception signaling} · CamilloBruni 10/7/2012 22:50 (removed)</b><br>
<font color="#0000FF">- signalSyntaxException: errorString at: errorPosition<br>
-     RegexSyntaxError signal: errorString at: errorPosition</font><br>
<br>
<b>RxParser>>atom {recursive descent} · ct 10/28/2021 03:03 (changed)</b><br>
atom<br>
    "An atom is one of a lot of possibilities, see below."<br>
<br>
    | atom |<br>
    (lookahead == nil <br>
    or: [ lookahead == $| <br>
    or: [ lookahead == $)<br>
    or: [ lookahead == $*<br>
    or: [ lookahead == $+ <br>
    or: [ lookahead == $? ]]]]])<br>
        ifTrue: [ ^RxsEpsilon new ].<br>
        <br>
    lookahead == $( <br>
        ifTrue: [<br>
            "<atom> ::= '(' <regex> ')' "<br>
            self match: $(.<br>
            atom := self regex.<br>
            self match: $).<br>
            ^atom ].<br>
    <br>
    lookahead == $[<br>
        ifTrue: [<br>
            "<atom> ::= '[' <characterSet> ']' "<br>
            self match: $[.<br>
            atom := self characterSet.<br>
            self match: $].<br>
            ^atom ].<br>
    <br>
    lookahead == $: <br>
        ifTrue: [<br>
            "<atom> ::= ':' <messagePredicate> ':' "<br>
            self match: $:.<br>
            atom := self messagePredicate.<br>
            self match: $:.<br>
            ^atom ].<br>
    <br>
    lookahead == $. <br>
        ifTrue: [<br>
            "any non-whitespace character"<br>
            self next.<br>
            ^RxsContextCondition new beAny].<br>
    <br>
    lookahead == $^ <br>
        ifTrue: [<br>
            "beginning of line condition"<br>
            self next.<br>
            ^RxsContextCondition new beBeginningOfLine].<br>
    <br>
    lookahead == $$ <br>
        ifTrue: [<br>
            "end of line condition"<br>
            self next.<br>
            ^RxsContextCondition new beEndOfLine].<br>
        <br>
    lookahead == $\ <br>
        ifTrue: [<br>
<font color="#0000FF">-             "<atom> ::= '\' <character>"<br>
-             self next ifNil: [ self signalParseError: 'bad quotation' ].<br>
-             (BackslashConstants includesKey: lookahead) ifTrue: [<br>
-                 atom := RxsCharacter with: (BackslashConstants at: lookahead).<br>
-                 self next.<br>
-                 ^atom].<br>
-             self ifSpecial: lookahead<br>
-                 then: [:node | self next. ^node]].<br>
-         <br>
</font><font color="#FF0000">+             "<atom> ::= '\' <node>"<br>
+             self match: $\.<br>
+             ^self backslashNode].<br>
+     <br>
</font>    "If passed through the above, the following is a regular character."<br>
    atom := RxsCharacter with: lookahead.<br>
    self next.<br>
    ^atom<br>
<br>
<b>RxParser>>backslashCondition {recursive descent} · ct 10/27/2021 07:38</b><br>
<font color="#FF0000">+ backslashCondition<br>
+ <br>
+     ^ self backslashSpecial: BackslashConditions</font><br>
<br>
<b>RxParser>>basicBackslashNode {recursive descent} · ct 10/28/2021 03:03</b><br>
<font color="#FF0000">+ basicBackslashNode<br>
+ <br>
+     ^ super basicBackslashNode ifNil: [self backslashCondition]</font><br>
<br>
<b>RxParser>>characterSet {recursive descent} · ct 10/28/2021 03:19 (changed)</b><br>
characterSet<br>
    "Match a range of characters: something between `[' and `]'.<br>
    Opening bracked has already been seen, and closing should<br>
    not be consumed as well. Set spec is as usual for<br>
    sets in regexes."<br>
<br>
<font color="#0000FF">-     | spec errorMessage |<br>
-     errorMessage := ' no terminating "]"'.<br>
</font><font color="#FF0000">+     | start spec errorMessage |<br>
+     errorMessage := 'no terminating "]"'.<br>
+     start := source position.<br>
</font>    spec := self inputUpTo: $] nestedOn: $[ errorMessage: errorMessage.<br>
    (spec isEmpty <br>
    or: [spec = '^']) <br>
        ifTrue: [<br>
            "This ']' was literal." <br>
            self next.<br>
            spec := spec, ']', (self inputUpTo: $] nestedOn: $[ errorMessage: errorMessage)].<br>
<font color="#0000FF">-     ^self characterSetFrom: spec<br>
</font><font color="#FF0000">+     ^self class<br>
+         doShiftingSyntaxExceptionPositions: [self characterSetFrom: spec]<br>
+         from: start</font><br>
<br>
<b>RxParser>>ifSpecial:then: {private} · vb 4/11/09 21:56 (removed)</b><br>
<font color="#0000FF">- ifSpecial: aCharacter then: aBlock<br>
-     "If the character is such that it defines a special node when follows a $\,<br>
-     then create that node and evaluate aBlock with the node as the parameter.<br>
-     Otherwise just return."<br>
- <br>
-     | classAndSelector |<br>
-     classAndSelector := BackslashSpecials at: aCharacter ifAbsent: [^self].<br>
-     ^aBlock value: (classAndSelector key new perform: classAndSelector value)</font><br>
<br>
<b>RxParser>>inputUpTo:errorMessage: {private} · ul 9/24/2015 08:25 (removed)</b><br>
<font color="#0000FF">- inputUpTo: aCharacter errorMessage: aString<br>
-     "Accumulate input stream until <aCharacter> is encountered<br>
-     and answer the accumulated chars as String, not including<br>
-     <aCharacter>. Signal error if end of stream is encountered,<br>
-     passing <aString> as the error description."<br>
- <br>
-     | accumulator |<br>
-     accumulator := WriteStream on: (String new: 20).<br>
-     [ lookahead == aCharacter or: [lookahead == nil ] ]<br>
-         whileFalse: [<br>
-             accumulator nextPut: lookahead.<br>
-             self next].<br>
-     lookahead ifNil: [ self signalParseError: aString ].<br>
-     ^accumulator contents</font><br>
<br>
<b>RxParser>>inputUpTo:nestedOn:errorMessage: {private} · ct 10/27/2021 08:06 (changed)</b><br>
inputUpTo: aCharacter nestedOn: anotherCharacter errorMessage: aString <br>
<font color="#0000FF">-     "Accumulate input stream until <aCharacter> is encountered<br>
-     and answer the accumulated chars as String, not including<br>
-     <aCharacter>. Signal error if end of stream is encountered,<br>
-     passing <aString> as the error description."<br>
</font><font color="#FF0000">+     "Accumulate input stream until <aCharacter> is encountered without escaping and answer the accumulated chars as String, not including <aCharacter>. Signal error if end of stream is encountered, passing <aString> as the error description."<br>
</font><br>
    | accumulator nestLevel |<br>
    accumulator := WriteStream on: (String new: 20).<br>
    nestLevel := 0.<br>
    [ lookahead == aCharacter and: [ nestLevel = 0 ] ] whileFalse: [<br>
        lookahead ifNil: [ self signalParseError: aString ].<br>
        lookahead == $\<br>
            ifTrue: [ <br>
                self next ifNil: [ self signalParseError: aString ].<br>
<font color="#0000FF">-                 BackslashConstants<br>
-                     at: lookahead<br>
-                     ifPresent: [ :unescapedCharacter | accumulator nextPut: unescapedCharacter ]<br>
-                     ifAbsent: [<br>
-                         accumulator<br>
-                             nextPut: $\;<br>
-                             nextPut: lookahead ] ]<br>
</font><font color="#FF0000">+                 accumulator<br>
+                     nextPut: $\;<br>
+                     nextPut: lookahead ]<br>
</font>            ifFalse: [<br>
                accumulator nextPut: lookahead.<br>
                lookahead == anotherCharacter ifTrue: [ nestLevel := nestLevel + 1 ].<br>
                lookahead == aCharacter ifTrue: [ nestLevel := nestLevel - 1 ] ].<br>
        self next ].<br>
    ^accumulator contents<br>
<br>
<b>RxParser>>inputUpToAny:errorMessage: {private} · ul 9/24/2015 08:24 (removed)</b><br>
<font color="#0000FF">- inputUpToAny: aDelimiterString errorMessage: aString<br>
-     "Accumulate input stream until any character from <aDelimiterString> is encountered<br>
-     and answer the accumulated chars as String, not including the matched characters from the<br>
-     <aDelimiterString>. Signal error if end of stream is encountered,<br>
-     passing <aString> as the error description."<br>
- <br>
-     | accumulator |<br>
-     accumulator := WriteStream on: (String new: 20).<br>
-     [ lookahead == nil or: [ aDelimiterString includes: lookahead ] ]<br>
-         whileFalse: [<br>
-             accumulator nextPut: lookahead.<br>
-             self next ].<br>
-     lookahead ifNil: [ self signalParseError: aString ].<br>
-     ^accumulator contents</font><br>
<br>
<b>RxParser>>match: {private} · ul 5/16/2015 01:51 (removed)</b><br>
<font color="#0000FF">- match: aCharacter<br>
-     "<aCharacter> MUST match the current lookeahead.<br>
-     If this is the case, advance the input. Otherwise, blow up."<br>
- <br>
-     aCharacter == lookahead ifFalse: [ ^self signalParseError ]. "does not return"<br>
-     self next</font><br>
<br>
<b>RxParser>>messagePredicate {recursive descent} · ct 10/27/2021 22:01 (changed)</b><br>
messagePredicate<br>
    "Match a message predicate specification: a selector (presumably<br>
    understood by a Character) enclosed in :'s ."<br>
<br>
    | spec negated |<br>
<font color="#0000FF">-     spec := self inputUpTo: $: errorMessage: ' no terminating ":"'.<br>
</font><font color="#FF0000">+     spec := self inputUpTo: $: errorMessage: 'no terminating ":"'.<br>
+     spec ifEmpty: [self signalParseError ].<br>
</font>    negated := false.<br>
    spec first = $^ <br>
        ifTrue: [<br>
            negated := true.<br>
            spec := spec copyFrom: 2 to: spec size].<br>
    ^RxsMessagePredicate new <br>
        initializeSelector: spec asSymbol<br>
        negated: negated<br>
<br>
<b>RxParser>>next {private} · ul 9/25/2015 10:02 (removed)</b><br>
<font color="#0000FF">- next<br>
-     "Advance the input storing the just read character<br>
-     as the lookahead."<br>
- <br>
-     ^lookahead := input next</font><br>
<br>
<b>RxParser>>parseStream: {accessing} · ct 10/27/2021 07:24 (changed)</b><br>
parseStream: aStream<br>
    "Parse an input from a character stream <aStream>.<br>
    On success, answers an RxsRegex -- parse tree root.<br>
    On error, raises `RxParser syntaxErrorSignal' with the current<br>
    input stream position as the parameter."<br>
<br>
    | tree |<br>
<font color="#0000FF">-     input := aStream.<br>
-     self next.<br>
</font><font color="#FF0000">+     self initialize: aStream.<br>
</font>    tree := self regex.<br>
    self match: nil.<br>
    ^tree<br>
<br>
<b>RxParser>>quantifiedAtom: {recursive descent} · ct 10/27/2021 22:01 (changed)</b><br>
quantifiedAtom: atom<br>
    "Parse a quanitifer expression which can have one of the following forms<br>
        {<min>,<max>} match <min> to <max> occurences<br>
        {<minmax>} which is the same as with repeated limits: {<number>,<number>}<br>
        {<min>,} match at least <min> occurences<br>
        {,<max>} match maximally <max> occurences, which is the same as {0,<max>}"<br>
    | min max |<br>
    self next.<br>
    lookahead == $,<br>
        ifTrue: [ min := 0 ]<br>
        ifFalse: [<br>
<font color="#0000FF">-             max := min := (self inputUpToAny: ',}' errorMessage: ' no terminating "}"') asUnsignedInteger ].<br>
</font><font color="#FF0000">+             max := min := (self inputUpToAny: ',}' errorMessage: 'no terminating "}"') asUnsignedInteger ].<br>
</font>    lookahead == $,<br>
        ifTrue: [<br>
            self next.<br>
<font color="#0000FF">-             max := (self inputUpToAny: ',}' errorMessage: ' no terminating "}"') asUnsignedInteger ].    <br>
</font><font color="#FF0000">+             max := (self inputUpToAny: ',}' errorMessage: 'no terminating "}"') asUnsignedInteger ].    <br>
</font>    self match: $}.<br>
    atom isNullable<br>
        ifTrue: [ self signalNullableClosureParserError ].<br>
    (max notNil and: [ max < min ])<br>
        ifTrue: [ self signalParseError: ('wrong quantifier, expected ', min asString, ' <= ', max asString) ].<br>
    ^ RxsPiece new <br>
        initializeAtom: atom<br>
        min: min<br>
        max: max<br>
<br>
<b>RxParser>>signalNullableClosureParserError {private} · ct 10/27/2021 22:00 (changed)</b><br>
signalNullableClosureParserError<br>
<font color="#0000FF">-     self signalParseError: ' nullable closure'.<br>
</font><font color="#FF0000">+     self signalParseError: 'nullable closure'.</font><br>
<br>
<b>RxParser>>signalParseError {private} · CamilloBruni 10/7/2012 22:50 (removed)</b><br>
<font color="#0000FF">- signalParseError<br>
- <br>
-     self class <br>
-         signalSyntaxException: 'Regex syntax error' at: input position</font><br>
<br>
<b>RxParser>>signalParseError: {private} · CamilloBruni 10/7/2012 22:49 (removed)</b><br>
<font color="#0000FF">- signalParseError: aString<br>
- <br>
-     self class signalSyntaxException: aString at: input position</font><br>
<br>
<b>RxsCharSet>>basicMaximumCharacterCodeIgnoringCase: {accessing} · ct 10/27/2021 08:59</b><br>
<font color="#FF0000">+ basicMaximumCharacterCodeIgnoringCase: aBoolean<br>
+ <br>
+     ^ elements inject: -1 into: [ :max :each |<br>
+         (each maximumCharacterCodeIgnoringCase: aBoolean) max: max ]</font><br>
<br>
<b>RxsCharSet>>enumerableSetIgnoringCase: {privileged} · ct 10/27/2021 08:59 (changed)</b><br>
enumerableSetIgnoringCase: aBoolean<br>
    "Answer a collection of characters that make up the portion of me that can be enumerated, or nil if there are no such characters. The case check is only used to determine the type of set to be used. The returned set won't contain characters of both cases, because this way the senders of this method can create more efficient checks."<br>
<br>
    | highestCharacterCode set |<br>
<font color="#0000FF">-     highestCharacterCode := elements inject: -1 into: [ :max :each |<br>
-         (each maximumCharacterCodeIgnoringCase: aBoolean) max: max ].<br>
</font><font color="#FF0000">+     highestCharacterCode := self basicMaximumCharacterCodeIgnoringCase: aBoolean.<br>
</font>    highestCharacterCode = -1 ifTrue: [ ^nil ].<br>
    set := highestCharacterCode <= 255<br>
        ifTrue: [ CharacterSet new ]<br>
        ifFalse: [ WideCharacterSet new ].<br>
    elements do: [ :each | each enumerateTo: set ].<br>
    ^set<br>
<br>
<b>RxsCharSet>>enumerateTo: {accessing} · ct 10/27/2021 08:36</b><br>
<font color="#FF0000">+ enumerateTo: aSet<br>
+ <br>
+     negated ifTrue: [^ self "Not enumerable"].<br>
+     ^ elements do: [:each | each enumerateTo: aSet]</font><br>
<br>
<b>RxsCharSet>>isEnumerable {testing} · ct 10/27/2021 08:50 (changed)</b><br>
isEnumerable<br>
<br>
<font color="#FF0000">+     negated ifTrue: [^ false].<br>
</font>    ^elements anySatisfy: [:some | some isEnumerable ]<br>
<br>
<b>RxsCharSet>>maximumCharacterCodeIgnoringCase: {accessing} · ct 10/27/2021 08:59</b><br>
<font color="#FF0000">+ maximumCharacterCodeIgnoringCase: aBoolean<br>
+     "Return the largest character code among the characters I represent."<br>
+ <br>
+     negated ifTrue: [^ -1 "not enumerable"].<br>
+     ^ self basicMaximumCharacterCodeIgnoringCase: aBoolean</font><br>
<br>
<b>RxsCharSet>>negated {converting} · ct 10/27/2021 08:35</b><br>
<font color="#FF0000">+ negated<br>
+ <br>
+     ^ self class new<br>
+         initializeElements: elements<br>
+         negated: negated not</font><br>
<br>
<b>RxsCharSet>>predicateIgnoringCase: {accessing} · ct 10/27/2021 08:52 (changed)</b><br>
predicateIgnoringCase: aBoolean<br>
<br>
    | enumerable predicate |<br>
    enumerable := self enumerablePartPredicateIgnoringCase: aBoolean.<br>
<font color="#0000FF">-     predicate := self predicatePartPredicate ifNil: [ <br>
</font><font color="#FF0000">+     predicate := (self predicatePartPredicateIgnoringCase: aBoolean) ifNil: [ <br>
</font>        "There are no predicates in this set."<br>
        ^enumerable ifNil: [ <br>
            "This set is empty."<br>
            [ :char | negated ] ] ].<br>
    enumerable ifNil: [ ^predicate ].<br>
    negated ifTrue: [<br>
        "enumerable and predicate already negate the result, that's why #not is not needed here."<br>
        ^[ :char | (enumerable value: char) and: [ predicate value: char ] ] ].<br>
    ^[ :char | (enumerable value: char) or: [ predicate value: char ] ]<br>
<br>
<b>RxsCharSet>>predicatePartPredicate {privileged} · ul 5/16/2015 01:37 (removed)</b><br>
<font color="#0000FF">- predicatePartPredicate<br>
-     "Answer a predicate that tests all of my elements that cannot be enumerated, or nil if such elements don't exist."<br>
- <br>
-     | predicates size |<br>
-     predicates := elements reject: [ :some | some isEnumerable ].<br>
-     (size := predicates size) = 0 ifTrue: [ <br>
-         "We could return a real predicate block - like [ :char | negated ] - here, but it wouldn't be used anyway. This way we signal that this character set has no predicates."<br>
-         ^nil ].<br>
-     size = 1 ifTrue: [<br>
-         negated ifTrue: [ ^predicates first predicateNegation ].<br>
-         ^predicates first predicate ].<br>
-     predicates replace: [ :each | each predicate ].<br>
-     negated ifTrue: [ ^[ [: char | predicates noneSatisfy: [ :some | some value: char ] ] ] ].<br>
-     ^[ :char | predicates anySatisfy: [ :some | some value: char ] ]<br>
-     </font><br>
<br>
<b>RxsCharSet>>predicatePartPredicateIgnoringCase: {privileged} · ct 11/3/2021 14:54</b><br>
<font color="#FF0000">+ predicatePartPredicateIgnoringCase: aBoolean<br>
+     "Answer a predicate that tests all of my elements that cannot be enumerated, or nil if such elements don't exist."<br>
+ <br>
+     | predicates size |<br>
+     predicates := elements reject: [ :some | some isEnumerable ].<br>
+     (size := predicates size) = 0 ifTrue: [ <br>
+         "We could return a real predicate block - like [ :char | negated ] - here, but it wouldn't be used anyway. This way we signal that this character set has no predicates."<br>
+         ^nil ].<br>
+     size = 1 ifTrue: [<br>
+         negated ifTrue: [ ^predicates first predicateNegationIgnoringCase: aBoolean ].<br>
+         ^predicates first predicateIgnoringCase: aBoolean ].<br>
+     predicates replace: [ :each | each predicateIgnoringCase: aBoolean ].<br>
+     negated ifTrue: [ ^[: char | predicates noneSatisfy: [ :some | some value: char ] ] ].<br>
+     ^[ :char | predicates anySatisfy: [ :some | some value: char ] ]</font><br>
<br>
<b>RxsCharSet>>predicates {accessing} · ul 5/16/2015 01:29 (removed)</b><br>
<font color="#0000FF">- predicates<br>
- <br>
-     | predicates |<br>
-     predicates := elements reject: [ :some | some isEnumerable ].<br>
-     predicates isEmpty ifTrue: [ ^nil ].<br>
-     ^predicates replace: [ :each | each predicate ]</font><br>
<br>
<b>RxsCharSet>>predicatesIgnoringCase: {accessing} · ct 10/27/2021 08:55</b><br>
<font color="#FF0000">+ predicatesIgnoringCase: aBoolean<br>
+ <br>
+     | predicates |<br>
+     predicates := elements reject: [ :some | some isEnumerable ].<br>
+     predicates isEmpty ifTrue: [ ^nil ].<br>
+     ^predicates replace: [ :each | each predicateIgnoringCase: aBoolean ]</font><br>
<br>
<b>RxsCharacter>>isRegexCharacter {testing} · ct 10/27/2021 20:38</b><br>
<font color="#FF0000">+ isRegexCharacter<br>
+ <br>
+     ^ true</font><br>
<br>
<b>RxsCharacter>>negated {converting} · ct 10/27/2021 08:32</b><br>
<font color="#FF0000">+ negated<br>
+ <br>
+     ^ RxsCharSet new<br>
+         initializeElements: {self}<br>
+         negated: true</font><br>
<br>
<b>RxsNode>>isRegexCharacter {testing} · ct 10/27/2021 20:38</b><br>
<font color="#FF0000">+ isRegexCharacter<br>
+ <br>
+     ^ false</font><br>
<br>
<b>RxsPredicate (changed)</b><br>
RxsNode subclass: #RxsPredicate<br>
    instanceVariableNames: 'predicate negation'<br>
<font color="#0000FF">-     classVariableNames: 'EscapedLetterSelectors NamedClassSelectors'<br>
</font><font color="#FF0000">+     classVariableNames: 'NamedClassSelectors'<br>
</font>    poolDictionaries: ''<br>
    category: 'Regex-Core'<br>
<br>
RxsPredicate class <br>
    instanceVariableNames: ''<br>
<br>
"-- Regular Expression Matcher v 1.1 (C) 1996, 1999 Vassili Bykov<br>
--<br>
This represents a character that satisfies a certain predicate.<br>
<br>
Instance Variables:<br>
<br>
    predicate    <BlockClosure>    A one-argument block. If it evaluates to the value defined by <negated> when it is passed a character, the predicate is considered to match.<br>
    negation    <BlockClosure>    A one-argument block that is a negation of <predicate>."<br>
<br>
<b>RxsPredicate class>>forEscapedLetter: {instance creation} · ct 10/27/2021 08:16 (changed)</b><br>
forEscapedLetter: aCharacter<br>
    "Return a predicate instance for the given character, or nil if there's no such predicate."<br>
<br>
<font color="#0000FF">-     ^EscapedLetterSelectors<br>
-         at: aCharacter<br>
-         ifPresent: [ :selector | self new perform: selector ]<br>
</font><font color="#FF0000">+     self deprecated.<br>
+     ^ RxParser new<br>
+         initialize: {aCharacter} readStream;<br>
+         backslashPredicate</font><br>
<br>
<b>RxsPredicate class>>initialize {class initialization} · ct 10/27/2021 08:16 (changed)</b><br>
initialize<br>
    "self initialize"<br>
<br>
<font color="#0000FF">-     self<br>
-         initializeNamedClassSelectors;<br>
-         initializeEscapedLetterSelectors<br>
</font><font color="#FF0000">+     self initializeNamedClassSelectors</font><br>
<br>
<b>RxsPredicate class>>initializeEscapedLetterSelectors {class initialization} · ul 9/25/2015 09:25 (removed)</b><br>
<font color="#0000FF">- initializeEscapedLetterSelectors<br>
-     "self initializeEscapedLetterSelectors"<br>
- <br>
-     EscapedLetterSelectors := Dictionary new<br>
-         at: $w put: #beWordConstituent;<br>
-         at: $W put: #beNotWordConstituent;<br>
-         at: $d put: #beDigit;<br>
-         at: $D put: #beNotDigit;<br>
-         at: $s put: #beSpace;<br>
-         at: $S put: #beNotSpace;<br>
-         yourself</font><br>
<br>
<b>RxsPredicate>>beUnicodeCategory: {initialize-release} · ct 8/23/2021 20:50</b><br>
<font color="#FF0000">+ beUnicodeCategory: categoryName<br>
+ <br>
+     self predicate: [:char |<br>
+         (Unicode generalTagOf: char asUnicode) beginsWith: categoryName].</font><br>
<br>
<b>RxsPredicate>>predicate {accessing} · vb 4/11/09 21:56 (removed)</b><br>
<font color="#0000FF">- predicate<br>
- <br>
-     ^predicate</font><br>
<br>
<b>RxsPredicate>>predicate: {initialize-release} · ct 8/23/2021 20:50</b><br>
<font color="#FF0000">+ predicate: aBlock<br>
+ <br>
+     predicate := aBlock.<br>
+     negation := [:char | (predicate value: char) not].</font><br>
<br>
<b>RxsPredicate>>predicateIgnoringCase: {accessing} · ct 10/27/2021 08:53</b><br>
<font color="#FF0000">+ predicateIgnoringCase: aBoolean<br>
+ <br>
+     ^predicate</font><br>
<br>
<b>RxsPredicate>>predicateNegation {accessing} · vb 4/11/09 21:56 (removed)</b><br>
<font color="#0000FF">- predicateNegation<br>
- <br>
-     ^negation</font><br>
<br>
<b>RxsPredicate>>predicateNegationIgnoringCase: {accessing} · ct 10/27/2021 08:53</b><br>
<font color="#FF0000">+ predicateNegationIgnoringCase: aBoolean<br>
+ <br>
+     ^negation</font><br>
<br>
<b>Regex-Core package postscript (changed)</b><br>
<font color="#0000FF">- RxsPredicate initializeEscapedLetterSelectors.<br>
</font><font color="#FF0000">+ RxParser initialize.</font><br>
<br>
<br>
<font color="#808080">---<br>
</font><i><font color="#808080">Sent from </font></i><i><u><a href="https://github.com/hpi-swa-lab/squeak-inbox-talk"><font color="#808080">Squeak Inbox Talk</font></a></u></i><br>
["Regex-Core-ct.74.mcz"]<br>
["Regex-Core-ct.74.mcz"]<br>
["Regex-Core-ct.74.mcz"]