|
From: Brenda L. <asp...@us...> - 2003-05-12 05:00:11
|
Update of /cvsroot/squeak/squeak/platforms/Cross/plugins/RePlugin In directory sc8-pr-cvs1:/tmp/cvs-serv13419 Added Files: RePlugin3-Fixes.1.cs RePlugin3-Fixes2.1.cs RePlugin3.3.1.cs Log Message: Ian Piumarta's 3.4.1 release --- NEW FILE: RePlugin3-Fixes.1.cs --- 'From Squeak 3.2 of 11 July 2002 [latest update: #4917] on 17 August 2002 at 6:10:11 pm'! "Change Set: RePlugin3-Fixes Date: 17 August 2002 Author: ti...@su... Some small fixes to RePlugin3 to allow compiling on Acorn"! !RePlugin methodsFor: 're primitives' stamp: 'tpr 8/17/2002 18:00'! primPCREExec "<rcvr primPCREExec: searchObject>, where rcvr is an object with instance variables: 'patternStr compileFlags pcrePtr extraPtr errorStr errorOffset matchFlags' Apply the regular expression (stored in <pcrePtr> and <extratr>, generated from calls to primPCRECompile), to smalltalk String searchObject using <matchOptions>. If there is no match, answer nil. Otherwise answer a ByteArray of offsets representing the results of the match." | searchObject searchBuffer length result matchSpacePtr matchSpaceSize | self export: true. self var:#searchBuffer declareC: 'char *searchBuffer'. self var:#matchSpacePtr declareC: 'int *matchSpacePtr'. self var:#result declareC: 'int result'. "Load Parameters" searchObject _ interpreterProxy stackObjectValue: 0. searchBuffer _ interpreterProxy arrayValueOf: searchObject. length _ interpreterProxy byteSizeOf: searchObject. self loadRcvrFromStackAt: 1. "Load Instance Variables" pcrePtr _ self rcvrPCREBufferPtr. extraPtr _ self rcvrExtraPtr. matchFlags _ self rcvrMatchFlags. matchSpacePtr _ self rcvrMatchSpacePtr. matchSpaceSize _ self rcvrMatchSpaceSize. interpreterProxy failed ifTrue:[^ nil]. result _ self cCode: 'pcre_exec((pcre *)pcrePtr, (pcre_extra *)extraPtr, searchBuffer, length, 0, matchFlags, matchSpacePtr, matchSpaceSize)'. interpreterProxy pop: 2; pushInteger: result. "empty call so compiler doesn't bug me about variables not used" self touch: searchBuffer; touch: matchSpacePtr; touch: matchSpaceSize; touch: length ! ! !RePlugin methodsFor: 're primitives' stamp: 'tpr 8/17/2002 18:00'! primPCREExecfromto "<rcvr primPCREExec: searchObject> from: fromInteger to: toInteger>, where rcvr is an object with instance variables: 'patternStr compileFlags pcrePtr extraPtr errorStr errorOffset matchFlags' Apply the regular expression (stored in <pcrePtr> and <extratr>, generated from calls to primPCRECompile), to smalltalk String searchObject using <matchOptions>, beginning at offset <fromInteger> and continuing until offset <toInteger>. If there is no match, answer nil. Otherwise answer a ByteArray of offsets representing the results of the match." | searchObject searchBuffer length result matchSpacePtr matchSpaceSize fromInteger toInteger | self export: true. self var:#searchBuffer declareC: 'char *searchBuffer'. self var:#fromInteger declareC: 'int fromInteger'. self var:#toInteger declareC: 'int toInteger'. self var:#matchSpacePtr declareC: 'int *matchSpacePtr'. self var:#result declareC: 'int result'. "Load Parameters" toInteger _ interpreterProxy stackIntegerValue: 0. fromInteger _ interpreterProxy stackIntegerValue: 1. searchObject _ interpreterProxy stackObjectValue: 2. searchBuffer _ interpreterProxy arrayValueOf: searchObject. length _ interpreterProxy byteSizeOf: searchObject. self loadRcvrFromStackAt: 3. "Validate parameters" interpreterProxy success: (1 <= fromInteger). interpreterProxy success: (toInteger<=length). fromInteger _ fromInteger - 1. "Smalltalk offsets are 1-based" interpreterProxy success: (fromInteger<=toInteger). "adjust length, searchBuffer" length _ toInteger - fromInteger. searchBuffer _ searchBuffer + fromInteger. "Load Instance Variables" pcrePtr _ self rcvrPCREBufferPtr. extraPtr _ self rcvrExtraPtr. matchFlags _ self rcvrMatchFlags. matchSpacePtr _ self rcvrMatchSpacePtr. matchSpaceSize _ self rcvrMatchSpaceSize. interpreterProxy failed ifTrue:[^ nil]. result _ self cCode: 'pcre_exec((pcre *)pcrePtr, (pcre_extra *)extraPtr, searchBuffer, length, 0, matchFlags, matchSpacePtr, matchSpaceSize)'. interpreterProxy pop: 2; pushInteger: result. "empty call so compiler doesn't bug me about variables not used" self touch: searchBuffer; touch: matchSpacePtr; touch: matchSpaceSize; touch: length ! ! !RePlugin methodsFor: 'rcvr linkage' stamp: 'tpr 8/17/2002 18:01'! allocateStringAndSetRcvrErrorStrFromCStr: aCStrBuffer |length errorStrObj errorStrObjPtr | self var: #aCStrBuffer declareC: 'const char *aCStrBuffer'. self var: #errorStrObjPtr declareC: 'void *errorStrObjPtr'. "Allocate errorStrObj" length _ self cCode: 'strlen(aCStrBuffer)'. errorStrObj _ interpreterProxy instantiateClass: (interpreterProxy classString) indexableSize: length. self loadRcvrFromStackAt: 0. "Assume garbage collection after instantiation" "Copy aCStrBuffer to errorStrObj's buffer" errorStrObjPtr _ interpreterProxy arrayValueOf: errorStrObj. self cCode:'memcpy(errorStrObjPtr,aCStrBuffer,length)'. self touch: errorStrObjPtr; touch: errorStrObj. "Set rcvrErrorStr from errorStrObj and Return" self rcvrErrorStrFrom: errorStrObj. ^errorStrObj.! ! !RePlugin class methodsFor: 'plugin code generation' stamp: 'tpr 8/17/2002 18:02'! declareCVarsIn: cg cg addHeaderFile:'"rePlugin.h"'. "Memory Managament Error Checking" cg var: 'netMemory' declareC: 'int netMemory = 0'. cg var: 'numAllocs' declareC: 'int numAllocs = 0'. cg var: 'numFrees' declareC: 'int numFrees = 0'. cg var: 'lastAlloc' declareC: 'int lastAlloc = 0'. "The receiver Object Pointer" cg var: 'rcvr' declareC: 'int rcvr'. "Instance Variables of Receiver Object" cg var: 'patternStr' declareC: 'int patternStr'. cg var: 'compileFlags' declareC: 'int compileFlags'. cg var: 'pcrePtr' declareC: 'int pcrePtr'. cg var: 'extraPtr' declareC: 'int extraPtr'. cg var: 'errorStr' declareC: 'int errorStr'. cg var: 'errorOffset' declareC: 'int errorOffset'. cg var: 'matchFlags' declareC: 'int matchFlags'. "Support Variables for Access to Receiver Instance Variables" cg var: 'patternStrPtr' declareC: 'const char * patternStrPtr'. cg var: 'errorStrBuffer' declareC: 'const char * errorStrBuffer'.! ! --- NEW FILE: RePlugin3-Fixes2.1.cs --- 'From Squeak3.2gamma of 15 January 2002 [latest update: #4881] on 21 August 2002 at 10:52:51 pm'! "Change Set: RePlugin3-Fixes2 Date: 21 August 2002 Author: ian...@in... Adds a cast to one method in RePlugin to avoid a compiler warning."! !RePlugin methodsFor: 'rcvr linkage' stamp: 'ikp 8/21/2002 22:40'! rcvrExtraPtr |extraObj| self inline: true. extraObj _ interpreterProxy fetchPointer: 3 ofObject: rcvr. (extraObj = (interpreterProxy nilObject)) ifTrue: [^ self cCode: '(int) NULL']. ^self cCoerce:(interpreterProxy arrayValueOf: extraObj) to: 'int'.! ! --- NEW FILE: RePlugin3.3.1.cs --- 'From Squeak3.3alpha of 12 January 2002 [latest update: #4934] on 16 August 2002 at 10:56:49 pm'! "Change Set: RePlugin3.3 Date: 16 August 2002 Author: acg Perl-Style Regular Expressions in Smalltalk by Andrew C. Greenberg Version 3.3beta I. Regular Expressions in General Regular expressions are a language for specifying text to ease the searching and manipulation of text. A complete discussion of regular expressions is beyond the scope of this document. See Jeffrey Friedl, Mastering Regular Expressions, by O'Reilly for a relatively complete. The regular expressions supported by this package are similar to those presently used in Perl 5.05 and Python, and are based upon Philip Hazel's excellent PCRE libraries (incorporated almost without change, subject to a free license described in Re aLicenseComment. Thanks are due to Markus Kohler and Stephen Pair for their assistance in the initial ports of early versions of the Plugin. An explanation of the expressions available in this package are summarized in Re aRegexComment, Re anOptionsComment and Re aGlobalSearchComment. A more detailed description of RePlugin is available downloading the file 'RePluginDoco,' which can be obtained from http://www.gate.net/~werdna/RePlugin.html, into your default directory, and then executing Utilities reconstructTextWindowsFromFileNamed: 'RePluginDoco' II. Overview of the 'Package.' The following new classes are provided: Class Description of Instances ---------------------- ------------------------------------------------------------------- Re A regular expression matching engine ReMatch Result of a search using Re RePattern Deprecated engine class from earlier plugin versions RePlugin The Plugin 'Glue' to the PCRE Library. String Various new messages were added to String, which are the principal means for users to access the package. PluginCodeGenerator has been deleted from the packgage. III. Some Examples. A. Simple Matching and Querying of Matches To search a string for matches in a regular expression, use String reMatch: 'just trying to catch some zzz''s before noon' matchRe: 'z+' which returns true if matched, and false otherwise. If more information from a positive search result is desired, the method reMatch will return a ReMatch object corresponding to the result. 'just trying to catch some zzz''s before noon' reMatch: 'z+' The match object can be queried in various ways. For example, to obtain details when parenthetical phrases of a regular expression are captured: |m| m _ 'Andy was born on 10/02/1957, and not soon enough!!' reMatch: '(\d\d)/(\d\d)/((19|20)?\d\d)'. m matches answers with: ('10' '02' '1957' '19' ) The first message answers a ReMatch m representing the result of a search of the string for matches of re (nil would be returned if no match was found). The third message answered a collection of the parenthetical subgroups matched, each showing the day, month and year as extracted from the string. B. Global Matching and String Substitutions You can perform global searches to repeatedly search a string for non-overlapping occurrences of a pattern by using reMatch:collect: For example, 'this is a test' collectRe: '\w+' can be used to gather a collection of all words in the search string, answering: OrderedCollection ('this' 'is' 'a' 'test' ) For slightly more complex collections, you can use #reMatch:andCollect: Additionally, you can perform global searches with text substitutions using reMatch:sub: For example, 'this is a test' reMatch: '\w+' andReplace: [:m | '<', (m match), '>'] can be used to replace every word in the search string with the word enclosed by matching brackets, answering: '<this> <is> <a> <test>' Further examples and documentation can be found in the references above, and in the comments and definitions set forth in ReMatch, RePattern and String. "! Object subclass: #Re instanceVariableNames: 'pattern compiledPattern isAnchored isCaseSensitive isDollarEndOnly isDotIncludesNewline isExtended isExtra isMultiline isBeginningOfLine isEndOfLine isGreedy ' classVariableNames: '' module: #(Werdna Re)! !Re commentStamp: '<historical>' prior: 0! Perl-Style Regular Expressions in Smalltalk Documentation The documentation category of this method contains substantial documentation on the operation of this Class. Re aGeneralComment Re aGlobalSearchComment Re aRegexComment Re aRegexGoryDetailsComment Re aVersionsComment Re anReComment Re anReOverviewComment à Re aLicenseComment Examples: (Re on: 'a.*y') search: 'Candy is dandy.' 'a.*y' asRe search: 'Candy is dandy.' 'Candy is dandy' reMatch: 'a.*y' (Re on: '\w+') searchAndCollect: 'Candy is dandy.' '\w+' asRe searchAndCollect: 'Candy is dandy.' 'Candy is dandy.' reMatch: '\w+' andCollect: [:m | m match] Structure: pattern String -- the string with the regular expression source code compiledPattern RePlugin representing a compiled pattern isAnchored Boolean -- representing an option setting is ... Booleans -- for the other options below List ofcommon public methods: #opt: sets options using Perl-style string #beAnchored #beNotAnchored #isAnchored #isAnchored: #beBeginningOfLine #beNotBeginningOfLine #isBeginningOfLine #isBeginningOfLine: #beCaseSensitive #beNotCaseSensitive #isCaseSensitive #isCaseSensitive: #beDollarEndOnly #beNotDollarEndOnly #isDollarEndOnly #isDollarEndOnly: #beDotIncludesNewline #beNotDotIncludesNewline #isDotIncludesNewLine #isDotIncludesNewline: #beEndOfLine #beNotEndOfLine #isEndOfLine #isEndOfLine: #beExtended #beNotExtended #isExtended #isExtended: #beExtra #beNotExtra #isExtra #isNotExtra: #beGreedy #beNotGreedy #isGreedy #isGreedy: #beMultiline #beNotMultiline #isMultiline #isMultiline: Getters and setters for options in traditional Smalltalk style search: aTargetString search aTargetString from: startInteger to: endInteger Compiling the pattern, if necessary, search a string (or substring) using the pattern. Answers nil if no match. searchAndCollect: aTargetString search: aTargetString andCollect: aBlock search: aTargetString andCollect: aBlock matchCount: anInteger Compiling the pattern, if necessary, gather all (or, if specified, the first anInteger) non-overlapping matches to me in aTargetString. Answer a collection of the results of applying aBlock to each ReMatch result. search: aTargetString andReplace: aBlock search: aTargetString andReplace: aBlock matchCount: anInteger Compiling the pattern, if necessary, find all (or, if specified, the first anInteger) non-overlapping matches to me in aTargetString. Answer a new string, created by substituting the results of applying aBlock to each ReMatch result for the matched substring. ! ]style[(44 16 109 1 1 18 2 23 2 16 2 27 2 19 2 14 2 22 3 1 19 1 12 280 11 236 30 1 6 40 687 66 8 13 8 13 7 12 5 10 1 118 18 13 9 13 13 6 9 13 13 6 13 9 1 217 8 13 13 6 9 13 13 6 13 9 1 266)bf3,bf1,f1,bf1,f1,f1LRe aGeneralComment;,f1,f1LRe aGlobalSearchComment;,f1,f1LRe aRegexComment;,f1,f1LRe aRegexGoryDetailsComment;,f1,f1LRe aVersionsComment;,f1,f1LRe anReComment;,f1,f1LRe anReOverviewComment;,bf1,f1,f1LRe aLicenseComment;,f1,bf1,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1,f1b,f1! Re class instanceVariableNames: ''! Object subclass: #ReMatch instanceVariableNames: 'matchArray re searchString pos endpos ' classVariableNames: '' module: #(Werdna Re)! !ReMatch commentStamp: '<historical>' prior: 0! ReMatch: Perl-Style Regular Expression Search Results I. Introduction This Class is part of a package of classes providing a Smalltalk wrapper to Philip Hazel's excellent PCRE library. The Plugin interface and Smalltalk wrapper was written by Andrew C. Greenberg. As discussed in RePattern aGeneralComment, the functionality is essentially embodied in this class, Class RePattern and certain new messages in Class String. A summary of the regular expression syntax c an be found in RePattern aRegexComment and a summary of the compile option codes available can be found in RePattern anOptionsComment. A more detailed description of RePlugin is available downloading the file 'RePluginDoco,' which can be obtained from http://www.gate.net/~werdna/RePlugin.html, into your default directory, and then executing Utilities reconstructTextWindowsFromFileNamed: 'RePluginDoco' II. Principal Match Results The substring of searchString matched by re is given by: m match which can be derived from searchString as follows: m searchString copyFrom: (m from) to: (m to) III. Captured Groups (and Collections of Captured Groups) The number of substrings capturable by a parenthetical grouping in an re (regardless of the number actually matched to create m) is given by: m numGroups The string captured by parenthetical grouping i, where 1<=i<=(m numGroups) is given by m matchAt: i and this can be generated as follows: m searchString copyFrom: (m fromAt: i) to: (m toAt: i) And an array of size (m numGroups) can be generated from strings and indices accordingly: m matches m froms m tos ! ]style[(53 2 15 214 25 65 9 103 23 69 26 120 41 53 61 2 27 177 57 488)bf3,f1,bf2,f1,f1LRePattern aGeneralComment;,f1,f1LRePattern Comment;,f1,f1LRePattern aRegexComment;,f1,f1LRePattern anOptionsComment;,f1,f1Rhttp://www.gate.net/~werdna/RePlugin.html;,f1,f1dUtilities reconstructTextWindowsFromFileNamed: 'RePluginDoco';;,f1,bf2,f1,bf2,f1! ReMatch class instanceVariableNames: ''! Object subclass: #RePattern instanceVariableNames: 'pattern compileOptions pcrePointer extraPointer errorString offset matchOptions matchSpace lastMatchResult ' classVariableNames: '' module: #(Werdna Re)! !RePattern commentStamp: '<historical>' prior: 0! RePattern: Compiled Perl-Style Regular Expressions I. Introduction. This Smalltalk implementation of modern Perl-Style regular expressions was compiled by Andrew Greenberg <we...@ga...> and contributors, based upon the excellent PCRE library by Philip Hazel. As discussed in RePattern aGeneralComment, the functionality is essentially embodied in this class, Class ReMatch and certain new messages in Class String. A summary of the regular expression syntax can be found in RePattern aRegexComment and a summary of the compile option codes available can be found in RePattern anOptionsComment. A substantially more detailed description of RePlugin is available downloading the file "RePluginDoco," which can be obtained from http://www.gate.net/~werdna/RePlugin.html, into your default directory, and then executing Utilities reconstructTextWindowsFromFileNamed: 'RePluginDoco' II. To Search a String or Substring For Pattern Matches (Once Only): Examples: 'Squeak or Squawk!!' reMatch: '^Squ(ea|aw)k' 'Squeak or Squawk!!' reMatch: '^Squ(ea|aw)k' opt: 'imsxABEXZ' 'Squeak or Squawk!!' reMatch: '^Squ(ea|aw)k!!' from: 11 more generally, srchStr reMatch: patStr [opt: oStr] [from: start] [to: stop] For a one-time search of a string (or substring) for occurences of a match pattern. The message will be answered with nil (if there is no match) or an instance of ReMatch, which can then be queried for further details about the match. III. Global Searching and Replacing The re package provides rudimentary facilities for global searches and replacements on a string. The following expressions '\w+' reMatch: 'this is a test' collect: [:m | m] (RePattern on: '\w+') search: 'this is a test' collect: [:m | m] return an ordered collection of the results of repeated non-overlapping applications of the pattern to the string, or nil if there are no matches in the string. To produce a list of matched strings, you can for example execute the following: '\w+' reMatch: 'this is a test' collect: [:m| m match] (RePattern on: '\w+') search: 'this is a test' collect: [:m | m match] You can also perform global search and string replacements, where the answer is a string with unmatched text left alone, and matched text replaced by the result of a call to a Block passed the ReMatch object as a single parameter. For example, ('\w+' reMatch: 'this is a test' sub: [:m| '<', (m match), '>'] and (RePattern on: '\w+') search: 'this is a test' sub: [:m| '<', (m match), '>'] return a string with each nonblank word surrounded by angle brackets. For more details, see RePattern aGlobalSearchComment. IV. To Create Compiled Regular Expression Objects (For Repeated Matching): '^Squ(ea|aw)k!!$' asRePattern '^Squ(ea|aw)k!!$' asRePatternOpt: 'imsxAEX' '^Squ(ea|aw)k!!$' asRePatternOpt: 'imsxAEX' onErrorRun: aBlock RePattern on: '^Squ(ea|aw)k!!$' RePattern on: '^Squ(ea|aw)k!!$' opt: 'imsxAEX' RePattern on: '^Squ(ea|aw)k!!$' opt: 'imsxAEX' onErrorRun: [:pat :offset :message | "your code here" ] Each of the preceding expressions returns an instance of RePattern, compiled for efficient matching when the pattern is repeatedly searched against different strings. RePattern ordinarily caches a dozen or so of the most recently compiled patterns, but nevertheless invokes a cost for the table lookup. To avoid compile and lookup costs, use the above messages. To perform a one-time search, see above. V. To Search a Compiled Regexp Against A String or Substring for Matches: searchString reMatch: re [from: from] [to: to] [opt: optStr] or re search: searchString [from: from] [to: to] [opt: optStr] Examples: 'Squeak or Squawk' reMatch: re. re search: 'Squeak or Squawk!!'. re search: 'Squeak or Squawk!!' opt: 'ABZ'. If no match is found, these messages answer nil. Otherwise, they answer with a corresponding instance of ReMatch.! ]style[(50 1 1 17 2 211 25 65 7 103 23 69 26 1 2 131 41 53 61 2 69 499 36 2 1110 30 3 75 749 73 362 7 1)bf3,f3,f1b,bf2,f1b,f1,f1LRePattern aGeneralComment;,f1,f1LReMatch Comment;,f1,f1LRePattern aRegexComment;,f1,f1LRePattern anOptionsComment;,f1,f1b,f1,f1Rhttp://www.gate.net/~werdna/RePlugin.html;,f1,f1dUtilities reconstructTextWindowsFromFileNamed: 'RePluginDoco';;,f1,bf2,f1,bf2,bf1,f1,f1LRePattern aGlobalSearchComment;,f1,f1b,f1,f1b,f1,f1LReMatch Comment;,f1! RePattern class instanceVariableNames: 'Patterns Options CompileObjects Front '! TestInterpreterPlugin subclass: #RePlugin instanceVariableNames: 'netMemory numAllocs numFrees lastAlloc patternStr rcvr compileFlags pcrePtr extraPtr errorStr errorOffset matchFlags patternStrPtr errorStrBuffer ' classVariableNames: '' module: #(Werdna Re)! !RePlugin commentStamp: '<historical>' prior: 0! /* Regular Expression Plugin (This class comment becomes part of rePlugin.c) RePlugin translate: 'RePlugin.c' doInlining: true. See documentation and source code for the PCRE C Library Code. This plugin is designed to serve an object such as RePattern: patternStr A 0-terminated string comprising the pattern to be compiled. compileFlags An Integer representing re compiler options PCREBuffer A ByteArray of regular expression bytecodes extraPtr A ByteArray of match optimization data (or nil) errorString A String Object For Holding an Error Message (when compile failed) errorOffset The index in patternStr (0-based) where the error ocurred (when compile failed) matchFlags An Integer representing re matcher options matchSpaceObj An Integer array for match results and workspace during matching. The instance variables must appear in the preceding order. MatchSpaceObj must be allocated by the calling routine and contain at least 6*(numGroups+1) bytes. */ #include "pcre.h" #include "internal.h" /* Slight machine-specific hack for MacOS Memory Management */ #ifdef TARGET_OS_MAC #define malloc(ptr) NewPtr(ptr) #define free(ptr) DisposePtr(aPointer) #endif /* Adjust malloc and free routines as used by PCRE */ void rePluginFree(void * aPointer); void * rePluginMalloc(size_t anInteger); void *(*pcre_malloc)(size_t) = rePluginMalloc; void (*pcre_free)(void *) = rePluginFree; ! RePlugin class instanceVariableNames: ''! TestCase subclass: #ReTest instanceVariableNames: '' classVariableNames: '' module: #(Werdna Re)! ReTest class instanceVariableNames: ''! !Re met hodsFor: 'documentation' stamp: 'acg 8/3/2002 22:57'! aGeneralComment " Perl-Style Regular Expressions in Smalltalk by Andrew C. Greenberg I. Regular Expressions in General Regular expressions are a language for specifying text to ease the searching and manipulation of text. A complete discussion of regular expressions is beyond the scope of this document. See Jeffrey Friedl, Mastering Regular Expressions, by O'Reilly for a relatively complete. The regular expressions supported by this package are similar to those presently used in Perl 5.05 and Python, and are based upon Philip Hazel's excellent PCRE libraries (incorporated almost without change, subject to a free license described in Re aLicenseComment. Thanks are due to Markus Kohler and Stephen Pair for their assistance in the initial ports of early versions of the Plugin. An explanation of the expressions available in this package are summarized in Re aRegexComment, Re anOptionsComment and Re aGlobalSearchComment. A more detailed description of RePlugin is available downloading the file 'RePluginDoco,' which can be obtained from http://www.gate.net/~werdna/RePlugin.html, into your default directory, and then executing Utilities reconstructTextWindowsFromFileNamed: 'RePluginDoco' II. Overview of the 'Package.' The following new classes are provided: Class Description of Instances ---------------------- ------------------------------------------------------------------- Re A regular expression matching engine ReMatch Result of a search using Re RePattern Deprecated engine class from earlier plugin versions RePlugin The Plugin 'Glue' to the PCRE Library. String Various new messages were added to String, which are the principal means for users to access the package. PluginCodeGenerator has been deleted from the packgage. III. Some Examples. A. Simple Matching and Querying of Matches To search a string for matches in a regular expression, use String reMatch: 'just trying to catch some zzz''s before noon' matchRe: 'z+' which returns true if matched, and false otherwise. If more information from a positive search result is desired, the method reMatch will return a ReMatch object corresponding to the result. 'just trying to catch some zzz''s before noon' reMatch: 'z+' The match object can be queried in various ways. For example, to obtain details when parenthetical phrases of a regular expression are captured: |m| m _ 'Andy was born on 10/02/1957, and not soon enough!!' reMatch: '(\d\d)/(\d\d)/((19|20)?\d\d)'. m matches answers with: ('10' '02' '1957' '19' ) The first message answers a ReMatch m representing the result of a search of the string for matches of re (nil would be returned if no match was found). The third message answered a collection of the parenthetical subgroups matched, each showing the day, month and year as extracted from the string. B. Global Matching and String Substitutions You can perform global searches to repeatedly search a string for non-overlapping occurrences of a pattern by using reMatch:collect: For example, 'this is a test' collectRe: '\w+' can be used to gather a collection of all words in the search string, answering: OrderedCollection ('this' 'is' 'a' 'test' ) For slightly more complex collections, you can use #reMatch:andCollect: Additionally, you can perform global searches with text substitutions using reMatch:sub: For example, 'this is a test' reMatch: '\w+' andReplace: [:m | '<', (m match), '>'] can be used to replace every word in the search string with the word enclosed by matching brackets, answering: '<this> <is> <a> <test>' Further examples and documentation can be found in the references above, and in the comments and definitions set forth in ReMatch, RePattern and String. "! ]style[(19 44 24 34 211 29 289 18 206 16 2 19 5 24 119 41 53 61 2 30 224 7 34 9 59 8 46 6 179 65 291 7 442 7 268 43 832 7 2 9 5 7 2)f1b,bf3,bf2,bf1,f1,f1i,f1,f1LRe aLicenseComment;,f1,f1LRe aRegexComment;,f1,f1LRe anOptionsComment;,f1,f1LRe aGlobalSearchComment;,f1,f1Rhttp://www.gate.net/~werdna/RePlugin.html;,f1,f1dUtilities reconstructTextWindowsFromFileNamed: 'RePluginDoco';;,f1,f1b,f1,f1LReMatch Comment;,f1,f1LRePattern Comment;,f1,f1LRePlugin Comment;,f1,f1LString Comment;,f1,f1b,f1,f1LReMatch Comment;,f1,f1LReMatch Comment;,f1,f1b,f1,f1LReMatch Comment;,f1,f1LRePattern Comment;,f1,f1LString Comment;,f1! ! !Re methodsFor: 'documentation' stamp: 'acg 8/3/2002 23:06'! aGlobalSearchComment " Global Searching Introduction RePattern provides facilities to support global searching and global searching and replacement of search strings with semantics quite similar to that of Perl 5.004. Global searching means that the search string is repeatedly searched for matches, beginning at the beginning of the string, and subsequently beginning the next match immediately after the preceding match terminated. For example, if we wanted to find all words in the subject string, we could execute: 'this is a test' reMatch: '\w+' collect: [:m | m match] which returns OrderedCollection ('this' 'is' 'a' 'test' ). The collect: keyword directs PCRE to repeat the search for '\w+', and to return a collection of the result of applying each ReMatch to the block. (In this case, the block simply returns the string that was matched.) To do global searching and string substitution, we could execute: 'this is a test' reMatch: '\w+' sub: [:m | '<', m match, '>'] which return '<this> <is> <a> <test>' The sub: keyword directs PCRE to repeat the search, and to return the original string, but with each matched substring replaced by the result of applying the block to the corresponding ReMatch object. Global Matching Functions RePattern convenience functions provide the following general global functions: searchString reMatch: pattern [opt: oStr] collect: aBlock [num: anInteger] searchString reMatch: pattern [opt: oStr] sub: aBlock [num: anInteger] Optionally, you may specify search and compile options with oStr, and you may specify a maximum number of searches performed in the global search with anInteger. If anInteger is less than 0, then as many searches as can be performed, will be performed. Special Case of the Empty Match Finally, the definition given above would infinite loop if the pattern matches an empty string. For example: 'abcdef' reMatch: 'x*' sub: [:m| '<', m match, '>'] will actually match the empty string just before and after each letter of the string, even though there is no x there. ('x+' would return nil). Since the string ends where it begins, at the beginning of the string, repeating the search from that point would simply infinite loop. Accordingly, RePattern gives the pattern a one-character 'bump' after matching an empty string, at which point the block is applied. For example, the preceding would answer '<>a<>b<>c<>d<>e<>f<>' In the ca... [truncated message content] |