#FEATURE by cg
authorClaus Gittinger <cg@exept.de>
Thu, 13 Sep 2018 10:26:57 +0200
changeset 6429 5bc480285a06
parent 6428 ee9bb5de3bbc
child 6430 27333e3928e5
#FEATURE by cg class: ListView feature: search at end of line only changed: #searchBackwardUsingSpec:startingAtLine:col:ifFound:ifAbsent: #searchForwardUsingSpec:startingAtLine:col:ifFound:ifAbsent: class: ListView::SearchSpec class definition added: #atEndOfLineOnly #atEndOfLineOnly: #pattern:ignoreCase:match:variable:fullWord:forward:atBeginOfLineOnly:atEndOfLineOnly: class: ListView::SearchSpec class added: #documentation
ListView.st
--- a/ListView.st	Thu Sep 13 10:26:31 2018 +0200
+++ b/ListView.st	Thu Sep 13 10:26:57 2018 +0200
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -40,7 +42,8 @@
 
 Object subclass:#SearchSpec
 	instanceVariableNames:'pattern match ignoreCase variable fullWord forward
-		atBeginOfLineOnly ignoreDiacritics regexMatch wrapAtEndOfText'
+		atBeginOfLineOnly atEndOfLineOnly ignoreDiacritics regexMatch
+		wrapAtEndOfText'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:ListView
@@ -4872,7 +4875,7 @@
      Also, wraps are not done when searching backward."
 
     |lineString
-     pattern ignCase match fullWord atBeginOfLineOnly
+     pattern ignCase match fullWord atBeginOfLineOnly atEndOfLineOnly
      found firstChar1 firstChar2 c pc col1
      col         "{ Class: SmallInteger }"
      cc          "{ Class: SmallInteger }"
@@ -4886,88 +4889,91 @@
     match ifTrue:[ Transcript showCR:'backward matchsearch is (still) not implemented' ].
     fullWord := searchSpec fullWord.
     atBeginOfLineOnly := searchSpec atBeginOfLineOnly.
+    atEndOfLineOnly := searchSpec atEndOfLineOnly.
 
     patternSize := pattern size.
     (list notNil
     and:[startLine > 0
     and:[patternSize ~~ 0]])
     ifTrue:[
-	self withCursor:Cursor questionMark do:[
-	    col := startCol - 1.
-	    firstChar1 := pattern at:1.
-	    ignCase ifTrue:[
-		firstChar1 := firstChar1 asLowercase.
-		firstChar2 := firstChar1 asUppercase.
-	    ] ifFalse:[
-		firstChar2 := firstChar1
-	    ].
-
-	    line1 := startLine.
-	    line1 > list size ifTrue:[
-		line1 := list size.
-		col := -999
-	    ] ifFalse:[
-		col > (list at:line1) size ifTrue:[
-		    col := -999
-		]
-	    ].
-	    line1 to:1 by:-1 do:[:lnr |
-		lineString := list at:lnr.
-		lineString notNil ifTrue:[
-		    lineString := lineString asString.
-		    lineString isString ifTrue:[
-			"/ quick check if pattern is present
-			col1 := lineString
-				findString:pattern startingAt:1
-				ifAbsent:0 caseSensitive: ignCase not.
-			col1 ~~ 0 ifTrue:[
-			    lineSize := lineString size.
-			    col == -999 ifTrue:[col := lineSize - patternSize + 1].
-			    [(col > 0)
-			     and:[(c := lineString at:col) ~= firstChar1
-			     and:[c ~= firstChar2]]] whileTrue:[
-				col := col - 1
-			    ].
-			    [col > 0] whileTrue:[
-				cc := col.
-				found := true.
-				1 to:patternSize do:[:cnr |
-				    cc > lineSize ifTrue:[
-					found := false
-				    ] ifFalse:[
-					pc := pattern at:cnr.
-					c := lineString at:cc.
-					pc ~= c ifTrue:[
-					    (ignCase not or:[pc asLowercase ~= c asLowercase]) ifTrue:[
-						found := false
-					    ]
-					]
-				    ].
-				    cc := cc + 1
-				].
-				found ifTrue:[
-				    (fullWord not
-					or:[ (self findBeginOfWordAtLine:lnr col:col) == col
-					      and:[ (self findEndOfWordAtLine:lnr col:col) == (col + patternSize - 1) ]]
-				    ) ifTrue:[
-					(atBeginOfLineOnly not or:[col == 1]) ifTrue:[
-					    ^ block1 value:lnr value:col optionalArgument:nil.
-					]
-				    ]
-				].
-				col := col - 1.
-				[(col > 0)
-				and:[(c := lineString at:col) ~= firstChar1
-				and:[c ~= firstChar2]]] whileTrue:[
-				    col := col - 1
-				]
-			    ]
-			]
-		    ].
-		].
-		col := -999.
-	    ]
-	]
+        self withCursor:Cursor questionMark do:[
+            col := startCol - 1.
+            firstChar1 := pattern at:1.
+            ignCase ifTrue:[
+                firstChar1 := firstChar1 asLowercase.
+                firstChar2 := firstChar1 asUppercase.
+            ] ifFalse:[
+                firstChar2 := firstChar1
+            ].
+
+            line1 := startLine.
+            line1 > list size ifTrue:[
+                line1 := list size.
+                col := -999
+            ] ifFalse:[
+                col > (list at:line1) size ifTrue:[
+                    col := -999
+                ]
+            ].
+            line1 to:1 by:-1 do:[:lnr |
+                lineString := list at:lnr.
+                lineString notNil ifTrue:[
+                    lineString := lineString asString.
+                    lineString isString ifTrue:[
+                        "/ quick check if pattern is present
+                        col1 := lineString
+                                findString:pattern startingAt:1
+                                ifAbsent:0 caseSensitive: ignCase not.
+                        col1 ~~ 0 ifTrue:[
+                            lineSize := lineString size.
+                            col == -999 ifTrue:[col := lineSize - patternSize + 1].
+                            [(col > 0)
+                             and:[(c := lineString at:col) ~= firstChar1
+                             and:[c ~= firstChar2]]] whileTrue:[
+                                col := col - 1
+                            ].
+                            [col > 0] whileTrue:[
+                                cc := col.
+                                found := true.
+                                1 to:patternSize do:[:cnr |
+                                    cc > lineSize ifTrue:[
+                                        found := false
+                                    ] ifFalse:[
+                                        pc := pattern at:cnr.
+                                        c := lineString at:cc.
+                                        pc ~= c ifTrue:[
+                                            (ignCase not or:[pc asLowercase ~= c asLowercase]) ifTrue:[
+                                                found := false
+                                            ]
+                                        ]
+                                    ].
+                                    cc := cc + 1
+                                ].
+                                found ifTrue:[
+                                    (fullWord not
+                                        or:[ (self findBeginOfWordAtLine:lnr col:col) == col
+                                              and:[ (self findEndOfWordAtLine:lnr col:col) == (col + patternSize - 1) ]]
+                                    ) ifTrue:[
+                                        (atBeginOfLineOnly not or:[col == 1]) ifTrue:[
+                                            (atEndOfLineOnly not or:[(col + patternSize - 1) >= lineSize]) ifTrue:[
+                                                ^ block1 value:lnr value:col optionalArgument:nil.
+                                            ]
+                                        ]
+                                    ]
+                                ].
+                                col := col - 1.
+                                [(col > 0)
+                                and:[(c := lineString at:col) ~= firstChar1
+                                and:[c ~= firstChar2]]] whileTrue:[
+                                    col := col - 1
+                                ]
+                            ]
+                        ]
+                    ].
+                ].
+                col := -999.
+            ]
+        ]
     ].
     "not found"
 
@@ -4975,6 +4981,7 @@
 
     "Created: / 13-09-1997 / 01:06:19 / cg"
     "Modified: / 05-08-2012 / 12:16:31 / cg"
+    "Modified: / 13-09-2018 / 10:07:29 / Claus Gittinger"
 !
 
 searchForwardFor:pattern ignoreCase:ignCase match:match startingAtLine:startLine col:startCol ifFound:block1 ifAbsent:block2
@@ -5016,7 +5023,7 @@
      if not found evaluate block2.
      If the block is a three-arg block, it gets the end-col (or nil, if not known)"
 
-    |lineString col pattern match regexMatch ignCase fullWord atBeginOfLineOnly
+    |lineString col pattern match regexMatch ignCase fullWord atBeginOfLineOnly atEndOfLineOnly
      wrapAtEndOfText patternSize matcher lnr   "{Class: SmallInteger}"
      line1 "{Class: SmallInteger}"
      line2 "{Class: SmallInteger}"
@@ -5032,6 +5039,7 @@
     ignCase := searchSpec ignoreCase.
     fullWord := searchSpec fullWord.
     atBeginOfLineOnly := searchSpec atBeginOfLineOnly.
+    atEndOfLineOnly := searchSpec atEndOfLineOnly.
     wrapAtEndOfText := searchSpec wrapAtEndOfText.
 
     patternSize := pattern size.
@@ -5088,7 +5096,9 @@
                             (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.
+                                    (atEndOfLineOnly not or:[endCol >= lineString size]) ifTrue:[
+                                        ^ block1 value:lnr value:foundCol optionalArgument:endCol.
+                                    ]
                                 ]
                             ]
                         ]
@@ -5112,8 +5122,9 @@
                                         caseSensitive:ignCase not ifAbsent:0.
                                 foundCol ~~ 0 ifTrue:[
                                     (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
-                                        ^ block1 value:lnr value:foundCol optionalArgument:nil.
-                                    ]]]
+                                        (atEndOfLineOnly not or:[(foundCol+p size) >= lineString size]) ifTrue:[
+                                            ^ block1 value:lnr value:foundCol optionalArgument:nil.
+                                    ]]]]
                             ].
                 ] ifFalse:[
                     "perform a findString (no matching)"
@@ -5131,7 +5142,13 @@
                                           and:[ (self findEndOfWordAtLine:lnr col:foundCol) == (foundCol + patternSize - 1) ]]
                                 ) ifTrue:[
                                     (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
-                                        ^ block1 value:lnr value:foundCol optionalArgument:nil.
+                                        atEndOfLineOnly ifTrue:[
+                                            (lineString endsWith:p caseSensitive:ignCase not) ifTrue:[
+                                                ^ block1 value:lnr value:(lineString size - p size + 1) optionalArgument:nil.
+                                            ].    
+                                        ] ifFalse:[ 
+                                            ^ block1 value:lnr value:foundCol optionalArgument:nil.
+                                        ]
                                     ]
                                 ]
                             ]
@@ -5147,7 +5164,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"
-    "Modified: / 20-08-2018 / 21:02:27 / Claus Gittinger"
+    "Modified: / 13-09-2018 / 10:20:55 / Claus Gittinger"
 !
 
 standardWordCheck:char
@@ -5427,6 +5444,24 @@
     fgColor := something.
 ! !
 
+!ListView::SearchSpec class methodsFor:'documentation'!
+
+documentation
+"
+    documentation to be added.
+
+    [author:]
+        Claus Gittinger
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+
+"
+! !
+
 !ListView::SearchSpec methodsFor:'accessing'!
 
 atBeginOfLineOnly
@@ -5437,6 +5472,18 @@
     atBeginOfLineOnly := aBoolean.
 !
 
+atEndOfLineOnly
+    ^ atEndOfLineOnly ? false
+
+    "Created: / 13-09-2018 / 10:04:11 / Claus Gittinger"
+!
+
+atEndOfLineOnly:aBoolean
+    atEndOfLineOnly := aBoolean.
+
+    "Created: / 13-09-2018 / 10:04:16 / Claus Gittinger"
+!
+
 forward
     ^ forward ? true
 !
@@ -5548,6 +5595,22 @@
     atBeginOfLineOnly := atBeginOfLineOnlyArg
 !
 
+pattern:patternString ignoreCase:ignoredCaseBoolean match:matchBoolean variable:variableBoolen
+                      fullWord:fullWordBoolen forward:forwardBoolean
+                      atBeginOfLineOnly:atBeginOfLineOnlyArg
+                      atEndOfLineOnly:atEndOfLineOnlyArg
+    pattern := patternString.
+    ignoreCase := ignoredCaseBoolean.
+    match := matchBoolean.
+    variable := variableBoolen.
+    fullWord := fullWordBoolen.
+    forward := forwardBoolean.
+    atBeginOfLineOnly := atBeginOfLineOnlyArg.
+    atEndOfLineOnly := atEndOfLineOnlyArg.
+
+    "Created: / 13-09-2018 / 10:04:35 / Claus Gittinger"
+!
+
 regexMatch
     ^ regexMatch ? false
 !