#BUGFIX by stefan
authorStefan Vogel <sv@exept.de>
Thu, 12 Oct 2017 18:36:45 +0200
changeset 6214 631877afef09
parent 6213 19e9bfd31785
child 6216 d3bf0f1dec62
#BUGFIX by stefan class: ListView changed: #searchForwardUsingSpec:startingAtLine:col:ifFound:ifAbsent: Fix regex searching: https://expeccoalm.exept.de/D222108
ListView.st
--- a/ListView.st	Thu Oct 12 13:19:05 2017 +0200
+++ b/ListView.st	Thu Oct 12 18:36:45 2017 +0200
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -4967,8 +4969,8 @@
     match := searchSpec match.
     regexMatch := searchSpec regexMatch.
     (match and:[regexMatch not]) ifTrue:[
-	pattern := pattern globPatternAsRegexPattern.
-	regexMatch := true.
+        pattern := pattern globPatternAsRegexPattern.
+        regexMatch := true.
     ].
     ignCase := searchSpec ignoreCase.
     fullWord := searchSpec fullWord.
@@ -4977,106 +4979,108 @@
 
     patternSize := pattern size.
     (list notNil and:[patternSize ~~ 0]) ifTrue:[
-	self withCursor:Cursor questionMark do:[
-
-	    col := startCol + 1.
-	    line1 := startLine.
-	    line2 := list size.
-
-	    "/ call searchBlock with lnr, col, and line. Cares for wrap
-	    runner :=
-		[:searchBlock |
-		    |didWrap|
-
-		    lnr := line1.
-		    didWrap := false.
-		    [lnr <= line2] whileTrue:[
-			lineString := list at:lnr.
-			lineString notNil ifTrue:[
-			    lineString := lineString asString string.
-			    lineString isString ifTrue:[
-				searchBlock value:lnr value:col value:lineString
-			    ]
-			].
-			col := 1.
-			lnr := lnr + 1.
-			lnr > line2 ifTrue:[
-			    (wrapAtEndOfText and:[didWrap not]) ifTrue:[
-				didWrap := true.
-				lnr := 1.
-				line2 := line1-1.
-			    ].
-			].
-		   ].
-
-		].
-
-	    (match and:[regexMatch]) ifTrue:[
-		"perform a findMatchString (regex matching)"
-		Regex::RxParser isNil ifTrue:[
-		    Smalltalk loadPackage:'stx:goodies/regex'
-		].
-		matcher := ignCase ifTrue:[pattern asRegexIgnoringCase] ifFalse:[pattern asRegex].
-		runner
-		    value:[:lnr :col :lineString |
-			"/ first a crude check ...
-			(matcher hasMatchesIn:lineString) ifTrue:[
-			    "/ find which match to show
-			    1 to:matcher subexpressionCount do:[:i |
-				foundCol := matcher subBeginning:i.
-				endCol := matcher subEnd:i.
-				(foundCol notNil and: [endCol notNil]) ifTrue: [
-				    foundCol := foundCol + 1. "/ regex uses 0-based indexes (sigh)
-				    foundCol >= col ifTrue:[
-					(atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
-					    ^ block1 value:lnr value:foundCol optionalArgument:endCol.
-					]]]]]].
-	    ] ifFalse:[
-		(match and:[pattern includesUnescapedMatchCharacters]) ifTrue:[
-		    "perform a findMatchString (glob matching)"
-		    p := pattern species new:0.
-		    (pattern startsWith:$*) ifFalse:[p := p , '*'].
-		    p := p , pattern.
-		    (pattern endsWith:$*) ifFalse:[p := p , '*'].
-		    realPattern := pattern.
-		    (realPattern startsWith:$*) ifTrue:[
-			realPattern := realPattern copyFrom:2
-		    ].
-		    runner
-			value:[:lnr :col :lineString |
-			    (p match:lineString caseSensitive:ignCase not) ifTrue:[
-				"/ ok, there it is; look at which position
-				foundCol := lineString
-					findMatchString:realPattern startingAt:col
-					caseSensitive:ignCase not ifAbsent:0.
-				foundCol ~~ 0 ifTrue:[
-				    (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
-					^ block1 value:lnr value:foundCol optionalArgument:nil.
-				    ]]]].
-		] ifFalse:[
-		    "perform a findString (no matching)"
-		    p := pattern.
-		    (match and:[pattern includesMatchCharacters]) ifTrue:[
-			p := pattern withoutMatchEscapes
-		    ].
-		    runner
-			value:[:lnr :col :lineString |
-			    foundCol := lineString
-				    findString:p startingAt:col ifAbsent:0 caseSensitive: ignCase not.
-			    foundCol ~~ 0 ifTrue:[
-				(fullWord not
-				    or:[ (self findBeginOfWordAtLine:lnr col:foundCol) == foundCol
-					  and:[ (self findEndOfWordAtLine:lnr col:foundCol) == (foundCol + patternSize - 1) ]]
-				) ifTrue:[
-				    (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
-					^ block1 value:lnr value:foundCol optionalArgument:nil.
-				    ]
-				]
-			    ]
-			].
-		].
-	    ].
-	]
+        self withCursor:Cursor questionMark do:[
+
+            col := startCol + 1.
+            line1 := startLine.
+            line2 := list size.
+
+            "/ call searchBlock with lnr, col, and line. Cares for wrap
+            runner :=
+                [:searchBlock |
+                    |didWrap|
+
+                    lnr := line1.
+                    didWrap := false.
+                    [lnr <= line2] whileTrue:[
+                        lineString := list at:lnr.
+                        lineString notNil ifTrue:[
+                            lineString := lineString asString string.
+                            lineString isString ifTrue:[
+                                searchBlock value:lnr value:col value:lineString
+                            ]
+                        ].
+                        col := 1.
+                        lnr := lnr + 1.
+                        lnr > line2 ifTrue:[
+                            (wrapAtEndOfText and:[didWrap not]) ifTrue:[
+                                didWrap := true.
+                                lnr := 1.
+                                line2 := line1-1.
+                            ].
+                        ].
+                   ].
+
+                ].
+
+            (match and:[regexMatch]) ifTrue:[
+                "perform a findMatchString (regex matching)"
+                Regex::RxParser isNil ifTrue:[
+                    Smalltalk loadPackage:'stx:goodies/regex'
+                ].
+                matcher := ignCase ifTrue:[pattern asRegexIgnoringCase] ifFalse:[pattern asRegex].
+                runner value:[:lnr :col :lineString |
+                        |lineStream|
+
+                        lineStream := lineString readStream position:col-1; yourself.
+                        "/ find which match to show
+                        (matcher searchStream:lineStream) ifTrue:[
+                            foundCol := matcher subBeginning:1.
+                            endCol := matcher subEnd:1.
+                            (foundCol notNil and: [endCol notNil]) ifTrue: [
+                                foundCol := foundCol + 1. "/ regex uses 0-based indexes (sigh)
+                                (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
+                                    ^ block1 value:lnr value:foundCol optionalArgument:endCol.
+                                ]
+                            ]
+                        ]
+                    ].
+            ] ifFalse:[
+                (match and:[pattern includesUnescapedMatchCharacters]) ifTrue:[
+                    "perform a findMatchString (glob matching)"
+                    p := pattern species new:0.
+                    (pattern startsWith:$*) ifFalse:[p := p , '*'].
+                    p := p , pattern.
+                    (pattern endsWith:$*) ifFalse:[p := p , '*'].
+                    realPattern := pattern.
+                    (realPattern startsWith:$*) ifTrue:[
+                        realPattern := realPattern copyFrom:2
+                    ].
+                    runner value:[:lnr :col :lineString |
+                            (p match:lineString caseSensitive:ignCase not) ifTrue:[
+                                "/ ok, there it is; look at which position
+                                foundCol := lineString
+                                        findMatchString:realPattern startingAt:col
+                                        caseSensitive:ignCase not ifAbsent:0.
+                                foundCol ~~ 0 ifTrue:[
+                                    (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
+                                        ^ block1 value:lnr value:foundCol optionalArgument:nil.
+                                    ]]]
+                            ].
+                ] ifFalse:[
+                    "perform a findString (no matching)"
+                    p := pattern.
+                    (match and:[pattern includesMatchCharacters]) ifTrue:[
+                        p := pattern withoutMatchEscapes
+                    ].
+                    runner
+                        value:[:lnr :col :lineString |
+                            foundCol := lineString
+                                    findString:p startingAt:col ifAbsent:0 caseSensitive: ignCase not.
+                            foundCol ~~ 0 ifTrue:[
+                                (fullWord not
+                                    or:[ (self findBeginOfWordAtLine:lnr col:foundCol) == foundCol
+                                          and:[ (self findEndOfWordAtLine:lnr col:foundCol) == (foundCol + patternSize - 1) ]]
+                                ) ifTrue:[
+                                    (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
+                                        ^ block1 value:lnr value:foundCol optionalArgument:nil.
+                                    ]
+                                ]
+                            ]
+                        ].
+                ].
+            ].
+        ]
     ].
     "not found"
 
@@ -5084,6 +5088,7 @@
 
     "Created: / 13-09-1997 / 01:06:31 / cg"
     "Modified: / 05-08-2012 / 12:22:42 / cg"
+    "Modified (format): / 12-10-2017 / 18:35:55 / stefan"
 !
 
 standardWordCheck:char