ListView.st
branchjv
changeset 5552 58ac0bd34b7b
parent 5482 816a9de03d66
parent 5546 89bcf7a74c6e
child 5596 c5f3ebcef742
equal deleted inserted replaced
5551:692afe1918ed 5552:58ac0bd34b7b
     1 "{ Encoding: utf8 }"
       
     2 
       
     3 "
     1 "
     4  COPYRIGHT (c) 1989 by Claus Gittinger
     2  COPYRIGHT (c) 1989 by Claus Gittinger
     5 	      All Rights Reserved
     3 	      All Rights Reserved
     6 
     4 
     7  This software is furnished under a license and may be used
     5  This software is furnished under a license and may be used
    39 	privateIn:ListView
    37 	privateIn:ListView
    40 !
    38 !
    41 
    39 
    42 Object subclass:#SearchSpec
    40 Object subclass:#SearchSpec
    43 	instanceVariableNames:'pattern match ignoreCase variable fullWord forward
    41 	instanceVariableNames:'pattern match ignoreCase variable fullWord forward
    44 		atBeginOfLineOnly ignoreDiacritics'
    42 		atBeginOfLineOnly ignoreDiacritics regexMatch wrapAtEndOfText'
    45 	classVariableNames:''
    43 	classVariableNames:''
    46 	poolDictionaries:''
    44 	poolDictionaries:''
    47 	privateIn:ListView
    45 	privateIn:ListView
    48 !
    46 !
    49 
    47 
  4702 !
  4700 !
  4703 
  4701 
  4704 searchBackwardUsingSpec:searchSpec startingAtLine:startLine col:startCol ifFound:block1 ifAbsent:block2
  4702 searchBackwardUsingSpec:searchSpec startingAtLine:startLine col:startCol ifFound:block1 ifAbsent:block2
  4705     "search for a pattern, if found evaluate block1 with row/col as arguments, if not
  4703     "search for a pattern, if found evaluate block1 with row/col as arguments, if not
  4706      found evaluate block2.
  4704      found evaluate block2.
  4707      Sorry, but pattern is no regular expression pattern (yet)"
  4705      Sorry, but pattern is no regular expression pattern (yet).
       
  4706      Also, wraps are not done when searching backward."
  4708 
  4707 
  4709     |lineString
  4708     |lineString
  4710      pattern ignCase match fullWord atBeginOfLineOnly
  4709      pattern ignCase match fullWord atBeginOfLineOnly
  4711      found firstChar1 firstChar2 c pc col1
  4710      found firstChar1 firstChar2 c pc col1
  4712      col         "{ Class: SmallInteger }"
  4711      col         "{ Class: SmallInteger }"
  4751                 lineString notNil ifTrue:[
  4750                 lineString notNil ifTrue:[
  4752                     lineString := lineString asString.
  4751                     lineString := lineString asString.
  4753                     lineString isString ifTrue:[
  4752                     lineString isString ifTrue:[
  4754                         "/ quick check if pattern is present
  4753                         "/ quick check if pattern is present
  4755                         col1 := lineString
  4754                         col1 := lineString
  4756                                 findString:pattern
  4755                                 findString:pattern startingAt:1
  4757                                 startingAt:1
  4756                                 ifAbsent:0 caseSensitive: ignCase not.
  4758                                 ifAbsent:0
       
  4759                                 caseSensitive: ignCase not.
       
  4760                         col1 ~~ 0 ifTrue:[
  4757                         col1 ~~ 0 ifTrue:[
  4761                             lineSize := lineString size.
  4758                             lineSize := lineString size.
  4762                             col == -999 ifTrue:[col := lineSize - patternSize + 1].
  4759                             col == -999 ifTrue:[col := lineSize - patternSize + 1].
  4763                             [(col > 0)
  4760                             [(col > 0)
  4764                              and:[(c := lineString at:col) ~= firstChar1
  4761                              and:[(c := lineString at:col) ~= firstChar1
  4847 
  4844 
  4848     "Modified: 13.9.1997 / 01:07:11 / cg"
  4845     "Modified: 13.9.1997 / 01:07:11 / cg"
  4849 !
  4846 !
  4850 
  4847 
  4851 searchForwardUsingSpec:searchSpec startingAtLine:startLine col:startCol ifFound:block1 ifAbsent:block2
  4848 searchForwardUsingSpec:searchSpec startingAtLine:startLine col:startCol ifFound:block1 ifAbsent:block2
  4852     "search for a pattern, if found evaluate block1 with row/col as arguments, if not
  4849     "search for a pattern, if found evaluate block1 with row/col as arguments, 
  4853      found evaluate block2."
  4850      if not found evaluate block2. 
  4854 
  4851      If the block is a three-arg block, it gets the end-col (or nil, if not found)"
  4855     |lineString col pattern match ignCase fullWord atBeginOfLineOnly
  4852 
  4856      patternSize
  4853     |lineString col pattern match regexMatch ignCase fullWord atBeginOfLineOnly
       
  4854      wrapAtEndOfText patternSize matcher lnr   "{Class: SmallInteger}"  
  4857      line1 "{Class: SmallInteger}"
  4855      line1 "{Class: SmallInteger}"
  4858      line2 "{Class: SmallInteger}"
  4856      line2 "{Class: SmallInteger}"
  4859      p realPattern|
  4857      p realPattern runner foundCol endCol|
  4860 
  4858 
  4861     pattern := searchSpec pattern.
  4859     pattern := searchSpec pattern.
  4862     match := searchSpec match.
  4860     match := searchSpec match.
       
  4861     regexMatch := searchSpec regexMatch.
  4863     ignCase := searchSpec ignoreCase.
  4862     ignCase := searchSpec ignoreCase.
  4864     fullWord := searchSpec fullWord.
  4863     fullWord := searchSpec fullWord.
  4865     atBeginOfLineOnly := searchSpec atBeginOfLineOnly.
  4864     atBeginOfLineOnly := searchSpec atBeginOfLineOnly.
       
  4865     wrapAtEndOfText := searchSpec wrapAtEndOfText.
  4866 
  4866 
  4867     patternSize := pattern size.
  4867     patternSize := pattern size.
  4868     (list notNil and:[patternSize ~~ 0]) ifTrue:[
  4868     (list notNil and:[patternSize ~~ 0]) ifTrue:[
  4869         self withCursor:Cursor questionMark do:[
  4869         self withCursor:Cursor questionMark do:[
  4870 
  4870 
  4871             col := startCol + 1.
  4871             col := startCol + 1.
  4872             line1 := startLine.
  4872             line1 := startLine.
  4873             line2 := list size.
  4873             line2 := list size.
  4874 
  4874 
  4875             (match and:[pattern includesUnescapedMatchCharacters]) ifTrue:[
  4875             "/ call searchBlock with lnr, col, and line. Cares for wrap
  4876                 "perform a findMatchString (matching)"
  4876             runner := 
  4877                 p := pattern species new:0.
  4877                 [:searchBlock |
  4878                 (pattern startsWith:$*) ifFalse:[
  4878                     |didWrap|
  4879                     p := p , '*'
  4879                     
       
  4880                     lnr := line1.
       
  4881                     didWrap := false.
       
  4882                     [lnr <= line2] whileTrue:[
       
  4883                         lineString := list at:lnr.
       
  4884                         lineString notNil ifTrue:[
       
  4885                             lineString := lineString asString string.
       
  4886                             lineString isString ifTrue:[
       
  4887                                 searchBlock value:lnr value:col value:lineString
       
  4888                             ]
       
  4889                         ].
       
  4890                         col := 1.
       
  4891                         lnr := lnr + 1.
       
  4892                         lnr > line2 ifTrue:[
       
  4893                             (wrapAtEndOfText and:[didWrap not]) ifTrue:[
       
  4894                                 didWrap := true.
       
  4895                                 lnr := 1.
       
  4896                                 line2 := line1-1.
       
  4897                             ].   
       
  4898                         ].    
       
  4899                    ].
       
  4900                     
  4880                 ].
  4901                 ].
  4881                 p := p , pattern.
  4902                 
  4882                 (pattern endsWith:$*) ifFalse:[
  4903             (match and:[regexMatch]) ifTrue:[
  4883                     p := p , '*'
  4904                 "perform a findMatchString (regex matching)"
  4884                 ].
  4905                 matcher := ignCase ifTrue:[pattern asRegexIgnoringCase] ifFalse:[pattern asRegex]. 
  4885                 realPattern := pattern.
  4906                 runner 
  4886                 (realPattern startsWith:$*) ifTrue:[
  4907                     value:[:lnr :col :lineString |
  4887                     realPattern := realPattern copyFrom:2
  4908                         "/ first a crude check ...
  4888                 ].
  4909                         (matcher hasMatchesIn:lineString) ifTrue:[
  4889                 line1 to:line2 do:[:lnr |
  4910                             "/ find which match to show
  4890                     lineString := list at:lnr.
  4911                             1 to:matcher subexpressionCount do:[:i | 
  4891                     lineString notNil ifTrue:[
  4912                                 foundCol := matcher subBeginning:i.
  4892                         lineString := lineString asString string.
  4913                                 endCol := matcher subEnd:i.
  4893                         lineString isString ifTrue:[
  4914                                 (foundCol notNil and: [endCol notNil]) ifTrue: [
  4894                             "/ first a crude check ...
  4915                                     foundCol := foundCol + 1. "/ regex uses 0-based indexes (sigh)
       
  4916                                     foundCol >= col ifTrue:[
       
  4917                                         (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
       
  4918                                             ^ block1 value:lnr value:foundCol optionalArgument:endCol.
       
  4919                                         ]]]]]].
       
  4920             ] ifFalse:[    
       
  4921                 (match and:[regexMatch or:[pattern includesUnescapedMatchCharacters]]) ifTrue:[
       
  4922                     "perform a findMatchString (glob matching)"
       
  4923                     p := pattern species new:0.
       
  4924                     (pattern startsWith:$*) ifFalse:[p := p , '*'].
       
  4925                     p := p , pattern.
       
  4926                     (pattern endsWith:$*) ifFalse:[p := p , '*'].
       
  4927                     realPattern := pattern.
       
  4928                     (realPattern startsWith:$*) ifTrue:[
       
  4929                         realPattern := realPattern copyFrom:2
       
  4930                     ].
       
  4931                     runner 
       
  4932                         value:[:lnr :col :lineString |
  4895                             (p match:lineString caseSensitive:ignCase not) ifTrue:[
  4933                             (p match:lineString caseSensitive:ignCase not) ifTrue:[
  4896                                 "/ ok, there it is; look at which position
  4934                                 "/ ok, there it is; look at which position
  4897                                 col := lineString
  4935                                 foundCol := lineString
  4898                                         findMatchString:realPattern
  4936                                         findMatchString:realPattern startingAt:col
  4899                                         startingAt:col
  4937                                         caseSensitive:ignCase not ifAbsent:0.
  4900                                         caseSensitive:ignCase not
  4938                                 foundCol ~~ 0 ifTrue:[
  4901                                         ifAbsent:0.
  4939                                     (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
  4902                                 col ~~ 0 ifTrue:[
  4940                                         ^ block1 value:lnr value:foundCol optionalArgument:nil.
  4903                                     (atBeginOfLineOnly not or:[col == 1]) ifTrue:[
  4941                                     ]]]].
  4904                                         ^ block1 value:lnr value:col.
  4942                 ] ifFalse:[
       
  4943                     "perform a findString (no matching)"
       
  4944                     p := pattern.
       
  4945                     runner 
       
  4946                         value:[:lnr :col :lineString |
       
  4947                             foundCol := lineString
       
  4948                                     findString:p startingAt:col ifAbsent:0 caseSensitive: ignCase not.
       
  4949                             foundCol ~~ 0 ifTrue:[
       
  4950                                 (fullWord not
       
  4951                                     or:[ (self findBeginOfWordAtLine:lnr col:foundCol) == foundCol
       
  4952                                           and:[ (self findEndOfWordAtLine:lnr col:foundCol) == (foundCol + patternSize - 1) ]]
       
  4953                                 ) ifTrue:[
       
  4954                                     (atBeginOfLineOnly not or:[foundCol == 1]) ifTrue:[
       
  4955                                         ^ block1 value:lnr value:foundCol optionalArgument:nil.
  4905                                     ]
  4956                                     ]
  4906                                 ]
  4957                                 ]
  4907                             ]
  4958                             ]
  4908                         ].
  4959                         ].
  4909                     ].
  4960                 ].
  4910                     col := 1
       
  4911                 ]
       
  4912             ] ifFalse:[
       
  4913                 "perform a findString (no matching)"
       
  4914                 p := pattern "withoutMatchEscapes".
       
  4915                 line1 to:line2 do:[:lnr |
       
  4916                     lineString := list at:lnr.
       
  4917                     lineString notNil ifTrue:[
       
  4918                         lineString := lineString asString string.
       
  4919                         lineString isString ifTrue:[
       
  4920                             col := lineString
       
  4921                                     findString:p
       
  4922                                     startingAt:col
       
  4923                                     ifAbsent:0
       
  4924                                     caseSensitive: ignCase not.
       
  4925                             col ~~ 0 ifTrue:[
       
  4926 "/Transcript showCR:'---'.
       
  4927 "/Transcript showCR:lineString.
       
  4928 "/Transcript showCR:col.
       
  4929 "/Transcript showCR:(self findBeginOfWordAtLine:lnr col:col).
       
  4930 "/Transcript showCR:(self findEndOfWordAtLine:lnr col:col).
       
  4931 "/Transcript showCR:(lineString copyFrom:(self findBeginOfWordAtLine:lnr col:col) to:(self findEndOfWordAtLine:lnr col:col)).
       
  4932                                 (fullWord not
       
  4933                                     or:[ (self findBeginOfWordAtLine:lnr col:col) == col
       
  4934                                           and:[ (self findEndOfWordAtLine:lnr col:col) == (col + patternSize - 1) ]]
       
  4935                                 ) ifTrue:[
       
  4936                                     (atBeginOfLineOnly not or:[col == 1]) ifTrue:[
       
  4937                                         ^ block1 value:lnr value:col.
       
  4938                                     ]
       
  4939                                 ]
       
  4940                             ]
       
  4941                         ]
       
  4942                     ].
       
  4943                     col := 1
       
  4944                 ]
       
  4945             ].
  4961             ].
  4946         ]
  4962         ]
  4947     ].
  4963     ].
  4948     "not found"
  4964     "not found"
  4949 
  4965 
  5286     ignoreCase := ignoredCaseBoolean.
  5302     ignoreCase := ignoredCaseBoolean.
  5287     match := matchBoolean.
  5303     match := matchBoolean.
  5288     forward := forwardBoolean
  5304     forward := forwardBoolean
  5289 !
  5305 !
  5290 
  5306 
       
  5307 pattern:patternString ignoreCase:ignoredCaseBoolean 
       
  5308           match:matchBoolean regexMatch:regexMatchBoolean
       
  5309           variable:variableBoolen 
       
  5310           fullWord:fullWordBoolen forward:forwardBoolean
       
  5311           atBeginOfLineOnly:atBeginOfLineOnlyArg
       
  5312     pattern := patternString.
       
  5313     ignoreCase := ignoredCaseBoolean.
       
  5314     match := matchBoolean.
       
  5315     regexMatch := regexMatchBoolean.
       
  5316     variable := variableBoolen.
       
  5317     fullWord := fullWordBoolen.
       
  5318     forward := forwardBoolean.
       
  5319     atBeginOfLineOnly := atBeginOfLineOnlyArg
       
  5320 !
       
  5321 
       
  5322 pattern:patternString ignoreCase:ignoredCaseBoolean 
       
  5323           match:matchBoolean regexMatch:regexMatchBoolean
       
  5324           variable:variableBoolen 
       
  5325           fullWord:fullWordBoolen forward:forwardBoolean
       
  5326           atBeginOfLineOnly:atBeginOfLineOnlyArg
       
  5327           wrapAtEnd:wrapAtEndOfTextArg
       
  5328     pattern := patternString.
       
  5329     ignoreCase := ignoredCaseBoolean.
       
  5330     match := matchBoolean.
       
  5331     regexMatch := regexMatchBoolean.
       
  5332     variable := variableBoolen.
       
  5333     fullWord := fullWordBoolen.
       
  5334     forward := forwardBoolean.
       
  5335     atBeginOfLineOnly := atBeginOfLineOnlyArg.
       
  5336     wrapAtEndOfText := wrapAtEndOfTextArg.
       
  5337 !
       
  5338 
  5291 pattern:patternString ignoreCase:ignoredCaseBoolean match:matchBoolean variable:variableBoolen forward:forwardBoolean
  5339 pattern:patternString ignoreCase:ignoredCaseBoolean match:matchBoolean variable:variableBoolen forward:forwardBoolean
  5292     pattern := patternString.
  5340     pattern := patternString.
  5293     ignoreCase := ignoredCaseBoolean.
  5341     ignoreCase := ignoredCaseBoolean.
  5294     match := matchBoolean.
  5342     match := matchBoolean.
  5295     variable := variableBoolen.
  5343     variable := variableBoolen.
  5315     fullWord := fullWordBoolen.
  5363     fullWord := fullWordBoolen.
  5316     forward := forwardBoolean.
  5364     forward := forwardBoolean.
  5317     atBeginOfLineOnly := atBeginOfLineOnlyArg
  5365     atBeginOfLineOnly := atBeginOfLineOnlyArg
  5318 !
  5366 !
  5319 
  5367 
       
  5368 regexMatch
       
  5369     ^ regexMatch
       
  5370 !
       
  5371 
       
  5372 regexMatch:something
       
  5373     regexMatch := something.
       
  5374 !
       
  5375 
  5320 variable
  5376 variable
  5321     ^ variable
  5377     ^ variable
  5322 !
  5378 !
  5323 
  5379 
  5324 variable:variableBoolean
  5380 variable:variableBoolean
  5325     variable := variableBoolean
  5381     variable := variableBoolean
       
  5382 !
       
  5383 
       
  5384 wrapAtEndOfText
       
  5385     ^ wrapAtEndOfText
       
  5386 !
       
  5387 
       
  5388 wrapAtEndOfText:aBoolean
       
  5389     wrapAtEndOfText := aBoolean.
  5326 ! !
  5390 ! !
  5327 
  5391 
  5328 !ListView class methodsFor:'documentation'!
  5392 !ListView class methodsFor:'documentation'!
  5329 
  5393 
  5330 version
  5394 version