ListView.st
author Claus Gittinger <cg@exept.de>
Tue, 24 Feb 1998 16:34:14 +0100
changeset 1451 3598c65cd89d
parent 1450 4ae9757ed852
child 1452 d4c481299b88
permissions -rw-r--r--
search max height, if non-strings are present (dont just take the first non-strings height)

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

View subclass:#ListView
	instanceVariableNames:'list firstLineShown leftOffset nFullLinesShown nLinesShown
		fgColor bgColor partialLines leftMargin topMargin textStartLeft
		textStartTop innerWidth tabPositions lineSpacing fontHeight
		fontAscent fontIsFixedWidth fontWidth autoScroll autoScrollBlock
		autoScrollDeltaT lastSearchPattern lastSearchIgnoredCase
		wordCheck includesNonStrings widthOfWidestLine listMsg viewOrigin
		listChannel'
	classVariableNames:'DefaultForegroundColor DefaultBackgroundColor DefaultTabPositions'
	poolDictionaries:''
	category:'Views-Text'
!

!ListView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    a View for (string-)lists.

    This class can only passively display collections of strings-
    selections, editing, cursors etc. must be done in subclasses.
    see SelectionInListView, TextView etc.

    This code currently handles only fixed-height fonts correctly -
    should be rewritten in some places ...

    It can only scroll by full lines vertically (i.e. setting firstLineShown to ~~ 1)
    which should be changed to have this behavior optionally for smooth scroll.

    The text is internally kept in the list instance variable, and is supposed to consist
    of a collection (Ordered- or StringCollection) of line entries.
    Typically, individual entries are either strings or nil (for empty lines).
    However, any object which supports the displayOn: and widthIn: protocol can be
    used - see MultipleColumnListEntry as an example.
    Therefore, ListView (and all subclasses) are prepared to handle non-string entries
    (especially: attributed Text).

    The internal version of the text has tabulators expanded to blanks - when text is exchanged
    with an external medium (i.e. reading/writing files), these are expanded/compressed assuming
    a tab-setting of 8. This is done independent of the users tab setting, which is used
    while the text is edited. Thus, even if the tab setting is multiple of 4's, tabs are
    written in multiples of 8 when the text is saved. Since this is the default on all ascii
    terminals and printers, this assures that the text looks correctly indented when finally printed.

    Notice:

    ListView is one of the oldest widget classes in the current system and
    definitely requires some rewrite:

    Due to historic reasons (ListView implemented scrolling before the general
    scrolling code in View was added), this one does scrolling different from all other
    views. The general scrolling code (in View) uses the transformation for transparent scrolling.
    Here, the transformation is not used, instead it is done again, by keeping the firstLineShown
    (i.e. vertical offset) and leftOffset (horizontal offset).
    The most annoying consequence of this is, that scrolling is done by lines here, 
    while its done in pixels in the View class. Thus, be careful, when changing things
    (better: dont touch it ;-)

    Also, all controller functionality is completely performed by the listView
    (and subclasses) itself. It is still possible, to define and set a specialized
    controller, though. I.e. if you like to change the input behavior, define
    a corresponding controller class and intersect the keyXXX/buttonXXX messages
    there.

    This will be totally rewritten ... so dont depend on the internals; especially the scrolling
    code will be totally removed here and the inherited functionality be used in the next version.


    [Instance variables:]

      list                <aCollection>           the text strings, a collection of lines.
						  Nils may be used for empty lines.

      firstLineShown      <Number>                the index of the 1st visible line (1 ..)
      leftOffset          <Number>                left offset for horizontal scroll

      nFullLinesShown     <Number>                the number of unclipped lines in visible area
                                                  (internal; updated on size changes)
      nLinesShown         <Number>                the number of lines in visible area, incl. partial
                                                  (internal; updated on size changes)

      fgColor             <Color>                 color to draw characters
      bgColor             <Color>                 the background

      partialLines        <Boolean>               allow last line to be partial displayed
      leftMargin          <Number>                margin at left in pixels
      topMargin           <Number>                margin at top in pixels
      textStartLeft       <Number>                margin + leftMargin (internal)
      textStartTop        <Number>                margin + topMargin (internal)
      innerWidth          <Number>                width - margins (internal)
      tabPositions        <aCollection>           tab stops (cols)
      fontHeight          <Number>                font height in pixels (internal)
      fontAscent          <Number>                font ascent in pixels (internal)
      fontIsFixed         <Boolean>               true if its a fixed font (internal)
      fontWidth           <Number>                width of space (internal)
      lineSpacing         <Number>                pixels between lines
      lastSearchPattern   <String>                last pattern for searching 
						  (kept to provide a default for next search)
      lastSearchIgnoredCase   <Boolean>           last search ignored case
						  (kept to provide a default for next search)
      wordCheck           <Block>                 rule used for check for word boundaries in word select
                                                  The default rule is to return true for alphaNumeric characters.
                                                  (can be changed to allow for underscore and other
                                                   characters to be treated as alphaCharacters)

      autoScrollBlock     <Block>                 block installed as timeoutBlock when doing an
                                                  autoScroll (internal)
      autoScrollDeltaT                            computed scroll time delta in seconds (internal)

      includesNonStrings                          cached flag if any non-strings are in list
      widthOfWidestLine                           cached width of widest line
      listMsg                                     if view has a model and listMsg is non-nil,
                                                  this is sent to the model to aquired a new contents
                                                  whenever a change of the aspect  (aspectMsg) occurs.

      viewOrigin                                  the current origin 


    [StyleSheet parameters:]

      textForegroundColor                         defaults to Black
      textBackgroundColor                         defaults to White
      textFont                                    defaults to defaultFont
      textTabPositions                            defaults to #(1 9 17 25 ...)

    [author:]
        Claus Gittinger

    [see also:]
        TextView EditTextView
        
"
!

examples 
"
    ListViews alone are rarely used - its mostly an abstract superclass
    for TextView, EditTextView and SelectionInListView.

    anyway, here are a few examples:

     basic simple setup:
									[exBegin]
	|top l|

	top := StandardSystemView new.
	top extent:100@200.

	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
	l list:#('one' 'two' 'three').

	top open
									[exEnd]



      specifying textMargins (these have NOTHING to do with the viewInset):
									[exBegin]
	|top l|

	top := StandardSystemView new.
	top extent:100@200.

	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
	l list:#('one' 'two' 'three').
	l topMargin:10.
	l leftMargin:20.

	top open
									[exEnd]



      globally set the fg/bg colors:
									[exBegin]
	|top l|

	top := StandardSystemView new.
	top extent:100@200.

	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
	l list:#('one' 'two' 'three').
	l foregroundColor:(Color white).
	l backgroundColor:(Color blue).

	top open
									[exEnd]



      non-string (text) entries:
									[exBegin]
	|top list l|

	top := StandardSystemView new.
	top extent:100@200.

	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
	list := #('all' 'of' 'your' 'preferred' 'colors') 
		with:#(red green blue 'orange' cyan)
		collect:[:s :clr | 
			    Text string:s 
				 emphasis:(Array with:#bold
						 with:(#color->(Color name:clr))) ].
	l list:list.

	top open
									[exEnd]



      generic non-string entries:
      (notice: ColoredListEntry is obsoleted by Text)
									[exBegin]
	|top list l|

	top := StandardSystemView new.
	top extent:100@200.

	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
	list := #('all' 'of' 'your' 'preferred' 'colors') 
		with:#(red green blue 'orange' cyan)
		collect:[:s :clr | ColoredListEntry string:s color:(Color name:clr) ].
	l list:list.

	top open
									[exEnd]



      using a model (default listMessage is aspectMessage):
									[exBegin]
	|top model l theModelsText|

	model := Plug new.
	model respondTo:#modelsAspect
		   with:[ theModelsText ].

	top := StandardSystemView new.
	top extent:100@200.

	l := ListView origin:0.0 @ 0.0 corner:1.0 @ 1.0 in:top.
	l model:model.
	l aspect:#modelsAspect.

	top open.

	Delay waitForSeconds:3.
	theModelsText := #('foo' 'bar' 'baz').
	model changed:#modelsAspect.
									[exEnd]



      using a model with different aspects
      for two listViews:
									[exBegin]
	|top model l1 l2 plainText|

	plainText := #('').

	model := Plug new.
	model respondTo:#modelsUppercaseText
		   with:[ plainText asStringCollection 
			      collect:[:l | l asUppercase]].
	model respondTo:#modelsLowercaseText
		   with:[ plainText asStringCollection 
			      collect:[:l | l asLowercase]].

	top := StandardSystemView extent:200@200.

	l1 := ListView origin:0.0 @ 0.0 corner:1.0 @ 0.5 in:top.
	l1 model:model.
	l1 aspect:#modelsAspect.
	l1 listMessage:#modelsUppercaseText.

	l2 := ListView origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:top.
	l2 model:model.
	l2 aspect:#modelsAspect.
	l2 listMessage:#modelsLowercaseText.

	top open.

	Delay waitForSeconds:3.
	plainText := #('foo' 'bar' 'baz').
	model changed:#modelsAspect.
									[exEnd]

"
! !

!ListView class methodsFor:'defaults'!

defaultTabPositions
    ^ self tab8Positions
!

tab4Positions
    ^ #(1 5 9 13 17 21 25 29 33 37 41 45 49 53 57 61 65 69 73 77 81 
	85 89 93 97 101 105 109 113 114 121 125 129 133 137 141 145)
!

tab8Positions
    ^ #(1 9 17 25 33 41 49 57 65 73 81 89 97 105 113 121 129 137 145)
!

updateStyleCache
    "extract values from the styleSheet and cache them in class variables"

    <resource: #style (#'text.foregroundColor' #'text.backgroundColor'
                       #'text.tabPositions'
                       #'text.font')>

    DefaultForegroundColor := StyleSheet colorAt:'text.foregroundColor' default:Black.
    DefaultBackgroundColor := StyleSheet colorAt:'text.backgroundColor' default:White.
    DefaultFont := StyleSheet fontAt:'text.font'.
    DefaultTabPositions := StyleSheet at:'text.tabPositions'.
    DefaultTabPositions isNil ifTrue:[DefaultTabPositions := self defaultTabPositions].

    "Modified: 20.10.1997 / 15:05:30 / cg"
! !

!ListView methodsFor:'accessing'!

backgroundColor
    "return the background color"

    ^ bgColor
!

backgroundColor:aColor
    "set the background color of the contents"

    bgColor ~~ aColor ifTrue:[
        bgColor := aColor.
        self viewBackground:bgColor.
        shown ifTrue:[
            self invalidate "/ clear; redraw
        ]
    ]

    "Modified: 3.5.1997 / 10:27:40 / cg"
!

font:aFont
    "set the font for all shown text.
     Redraws everything.
     CAVEAT: with the addition of Text objects,
             this method is going to be obsoleted by a textStyle
             method, which allows specific control over
             normalFont/boldFont/italicFont parameters."

    aFont isNil ifTrue:[
        ^ self error:'nil font'
    ].
    font ~~ aFont ifTrue:[
        super font:(aFont on:device).
        preferredExtent := nil.
        widthOfWidestLine := nil. "/ i.e. unknown
        self getFontParameters.
        realized ifTrue:[
            (font graphicsDevice == device) ifTrue:[
                self getFontParameters.
                self computeNumberOfLinesShown.
                shown ifTrue:[
                    self redrawFromVisibleLine:1 to:nLinesShown
                ]
            ].
            self contentsChanged
        ]
    ]

    "Modified: 5.7.1996 / 17:55:34 / cg"
!

fontHeight:pixels
    "set the lines height - thats the number of pixels,
     by which lines are vertically separated."

    fontHeight ~~ pixels ifTrue:[
        fontHeight := pixels.
    ]

    "Created: 17.4.1997 / 01:41:33 / cg"
!

foregroundColor
    "return the foreground color"

    ^ fgColor
!

foregroundColor:aColor
    "set the foreground color"

    fgColor ~~ aColor ifTrue:[
	fgColor := aColor.
	shown ifTrue:[
	    self invalidate 
	]
    ]

    "Modified: 29.5.1996 / 16:19:02 / cg"
!

foregroundColor:color1 backgroundColor:color2
    "set both foreground and background colors"

    ((fgColor ~~ color1) or:[bgColor ~~ color2]) ifTrue:[
	fgColor := color1.
	bgColor := color2.
	shown ifTrue:[
	    self invalidate 
	]
    ]

    "Modified: 29.5.1996 / 16:19:05 / cg"
!

innerHeight
    "return the number of pixels visible of the contents
     - redefined since ListView adds another margin to start the text
     somewhat to indented from the 3D border."

    ^ height - (2 * margin) - topMargin
!

innerHorizontalMargin
    "return the margin between the left border and the 1st col"

    ^ leftMargin

    "Created: 16.1.1996 / 19:28:23 / cg"
!

innerVerticalMargin
    "return the margin between the top border and the 1st line"

    ^ topMargin

    "Created: 16.1.1996 / 19:28:00 / cg"
!

leftMargin
    "return the margin to left of 1st col"

    ^ leftMargin
!

leftMargin:aNumber
    "set the margin between the left border and the 1st col"

    leftMargin := aNumber.
    textStartLeft := aNumber + margin.
    innerWidth := width - aNumber - margin

    "Modified: 28.2.1996 / 19:32:55 / cg"
!

level:aNumber
    "set the 3D level - caught here to update text-position variables
     (which avoids many computations later)"

    |newMargin|

    aNumber ~~ level ifTrue:[
        newMargin := aNumber abs.
        textStartLeft := leftMargin + newMargin.
        textStartTop := topMargin + newMargin.
        innerWidth := width - textStartLeft - newMargin.

        super level:aNumber.
    ]

    "Modified: 11.8.1997 / 02:59:15 / cg"
!

lineSpacing:pixels
    "set the lineSpacing - thats an additional number of pixels,
     by which lines are vertically separated."

    lineSpacing ~~ pixels ifTrue:[
	lineSpacing := pixels.
	self getFontParameters.
    ]

    "Modified: 22.5.1996 / 12:22:29 / cg"
!

partialLines:aBoolean
    "allow/disallow display of a last partial line"

    partialLines := aBoolean.
    self computeNumberOfLinesShown
!

topMargin:aNumber
    "set the margin between the top border and the 1st line"

    topMargin := aNumber.
    textStartTop := topMargin + margin.
!

wordCheckBlock:aBlock
    "set the word-check block - this block is called with a character argument,
     when the end/beginning of a word is searched.
     It should return true, if the character belongs to the word.
     The default block is set in #initialize, and returns true for alphanumeric
     (national) characters.
     Applications may change it to include underlines, dollars or other characters. 
     (a C/C++ editor would include underlines ...)"

    wordCheck := aBlock.

    "Modified: 22.5.1996 / 12:26:55 / cg"
! !

!ListView methodsFor:'accessing-contents'!

add:aString
    "add a line and redisplay"

    list add:aString.
    includesNonStrings ifFalse:[
        includesNonStrings := (aString notNil and:[aString isString not]).
"/        includesNonStrings ifTrue:[self getFontParameters].
    ].
    shown ifTrue:[
        self redrawLine:(self size).
        self contentsChanged.             "recompute scrollbars"
    ]

    "Modified: 22.10.1996 / 23:18:47 / cg"
!

add:aString beforeIndex:index
    "add a line and redisplay"

    list isNil ifTrue:[list := OrderedCollection new].
    list add:aString beforeIndex:index.
    includesNonStrings ifFalse:[
        includesNonStrings := (aString notNil and:[aString isString not]).
"/        includesNonStrings ifTrue:[self getFontParameters].
    ].
    shown ifTrue:[
        self redrawFromLine:index.
        self contentsChanged.             "recompute scrollbars"
    ]

    "Modified: 22.10.1996 / 23:18:53 / cg"
!

at:lineNr
    "retrieve a line; return nil if beyond end-of-text.
     this allows textViews to be used like collections in some places."

    list isNil ifTrue:[^ nil].
    (lineNr between:1 and:self size) ifFalse:[^ nil].
    ^ list at:lineNr
!

at:index put:aString
    "change a line and redisplay"

    |visibleLine y|

    self withoutRedrawAt:index put:aString.
    shown ifTrue:[
        "/ synchronous:
        self redrawLine:index

        "/ asynchronous:
"/        visibleLine := self listLineToVisibleLine:index.
"/        visibleLine notNil ifTrue:[
"/            y := self yOfVisibleLine:visibleLine.
"/            self invalidate:((margin @ y) extent:(width@fontHeight))
"/        ].
    ]

    "Modified: 18.4.1997 / 14:52:28 / cg"
!

characterAtLine:lineNr col:colNr
    "return the character at physical line/col. 
     The lineNr and colNr arguments start at 1, for the top-left cgaracter.
     Return a space character if nothing is there
     (i.e. behond the end of the line or below the last line)"

    |line|

    list notNil ifTrue:[
	line := self listAt:lineNr.
	line notNil ifTrue:[
	    (line size >= colNr) ifTrue:[
		^ line at:colNr
	    ]
	]
    ].
    ^ Character space

    "Created: 29.4.1996 / 12:11:00 / cg"
    "Modified: 29.4.1996 / 12:12:41 / cg"
!

contents
    "return the contents as a string"

    list isNil ifTrue:[^ ''].
    ^ list asStringCollection asString
!

contents:something
    "set the contents (either a String or a Collection of strings)
     also scroll to top. See #setContents:, which does not scroll.
     If the argument is a string, it is converted
     to a collection of line-strings here."

    |l|

    l := something.
    l notNil ifTrue:[
        l isString ifTrue:[
            l := l asStringCollection
        ]
    ].
    self list:l

    "Modified: 5.6.1997 / 11:11:54 / cg"
!

from:from to:to do:aBlock
    "evaluate aBlock on some of my lines"

    ^ list from:from to:to do:aBlock.

    "Modified: 18.5.1996 / 14:02:14 / cg"
!

grow:n
    "grow our list"

    ^ list grow:n.
!

list
    "return the contents as a collection of strings.
     This returns the views internal list - modifying it may confuse
     the listView."

    ^ list

    "Modified: 5.6.1997 / 11:10:54 / cg"
!

list:aCollection
    "set the contents (a collection of strings or list entries) 
     and scroll to top-left.
     See also #setList:, which does not scroll.
     Tabs are expanded (to spaces).
     The passed list is scanned for nonStrings 
     (remembered to optimize later redraws)."

    self list:aCollection expandTabs:true

    "Modified: 5.6.1997 / 11:10:45 / cg"
!

list:aCollection expandTabs:expand
    "set the contents (a collection of strings) and scroll to top-left.
     If expand is true, tabs are expanded (to spaces).
     The passed list is scanned for nonStrings (remembered to optimize
     later redraws)."

    self list:aCollection expandTabs:expand scanForNonStrings:true

    "Modified: 5.6.1997 / 11:09:44 / cg"
!

list:aCollection expandTabs:expand scanForNonStrings:scan
    "set the contents (a collection of strings) and scroll to top-left.
     If expand is true, tabs are expanded (to spaces).
     If scan is true, scan the passed list for nonStrings; otherwise,
     assume that it does contain non-strings
     (remembered to optimize later redraws)."

    self
        list:aCollection expandTabs:expand scanForNonStrings:scan includesNonStrings:true

    "Modified: 5.6.1997 / 12:40:35 / cg"
!

list:aCollection expandTabs:expand scanForNonStrings:scan includesNonStrings:nonStrings
    "set the contents (a collection of strings) and scroll to top-left.
     If expand is true, tabs are expanded (to spaces).
     If scan is true, scan the passed list for nonStrings; 
     otherwise, take the information from the nonStrings arg.
     (the nonStrings information is remembered to optimize later redraws & height computations)."

    |oldFirst oldLeft nonStringsBefore|

    (aCollection isNil and:[list isNil]) ifTrue:[
        "no change"
        self scrollToTop.
        self scrollToLeft.
        ^ self
    ].
    list := aCollection.

    nonStringsBefore := includesNonStrings.
    includesNonStrings := false.

    list notNil ifTrue:[
        expand ifTrue:[
            self expandTabs
        ] ifFalse:[
            scan ifTrue:[
                includesNonStrings := (list findFirst:[:e | e isString not]) ~~ 0.
            ] ifFalse:[
                includesNonStrings := nonStrings
            ]
        ].
    ].
    (includesNonStrings ~~ nonStringsBefore) ifTrue:[self getFontParameters].

    widthOfWidestLine := nil.   "/ i.e. unknown
    oldFirst := firstLineShown.
    oldLeft := leftOffset.
    firstLineShown := 1.
    leftOffset := 0.

    realized ifTrue:[
        self computeNumberOfLinesShown.
        self contentsChanged.
        "
         dont use scroll here to avoid the redraw
        "
        oldFirst ~~ firstLineShown ifTrue:[
            self originChanged:0 @ ((oldFirst - 1) * fontHeight negated).
        ].
        shown ifTrue:[
            self redrawFromVisibleLine:1 to:nLinesShown
        ]
    ]

    "Modified: 30.8.1995 / 19:07:13 / claus"
    "Modified: 5.6.1997 / 11:09:56 / cg"
    "Created: 5.6.1997 / 12:40:06 / cg"
!

removeIndex:lineNr
    "delete a line, redraw the view"

    |visLine w x
     srcY "{ Class: SmallInteger }" |

    (self removeIndexWithoutRedraw:lineNr) ifFalse:[^ self].

    "
     is there a need to redraw ?
    "
    shown ifFalse:[^ self].
    visLine := self listLineToVisibleLine:lineNr.
    visLine notNil ifTrue:[
        w := self widthForScrollBetween:lineNr and:(firstLineShown + nLinesShown).
"/        x := textStartLeft.
"/ CLAUS fixes leftOver selection pixels
        w := w + leftMargin.
        x := margin.

        srcY := topMargin + (visLine * fontHeight).
        self catchExpose.
        self 
            copyFrom:self 
            x:x y:srcY
            toX:x y:(srcY - fontHeight)
            width:w height:((nLinesShown - visLine) * fontHeight)
            async:true.
        self redrawVisibleLine:nFullLinesShown.
        "
         redraw last partial line - if any
        "
        (nFullLinesShown ~~ nLinesShown) ifTrue:[
            self redrawVisibleLine:nLinesShown
        ].
        self waitForExpose
    ]

    "Modified: 29.1.1997 / 13:05:50 / cg"
!

removeIndexWithoutRedraw:lineNr
    "delete a line, given its lineNr - no redraw;
     return true, if something was really deleted (so sender knows,
     if a redraw is needed)"

    (list isNil or:[lineNr > self size]) ifTrue:[^ false].
    list removeIndex:lineNr.

    lineNr < firstLineShown ifTrue:[
	firstLineShown := firstLineShown - 1
    ].
    self contentsChanged.
    ^ true
!

setContents:something
    "set the contents (either a string or a Collection of strings)
     dont change position (i.e. do not scroll).
     This can be used to update a self-changing list 
     (for example: a file list being shown, without disturbing user too much).
     Compare with #contents:, which scrolls to top."

    |l oldSize|

    oldSize := self size.
    l := something.
    l notNil ifTrue:[
	l isString ifTrue:[
	    l := l asStringCollection
	]
    ].
    self setList:l.

    "Modified: 18.12.1995 / 22:20:43 / stefan"
!

setList:aCollection
    "set the contents (a collection of strings);
     do not change position (i.e. do not scroll).
     This can be used to update a self-changing list 
     (for example: a file list being shown, without disturbing user too much)"

    ^ self setList:aCollection expandTabs:true
!

setList:aCollection expandTabs:expandTabs
    "set the contents (a collection of strings);
     do not change position (i.e. do not scroll).
     This can be used to update a self-changing list 
     (for example: a file list being shown, without disturbing the user too much)"

    |oldFirst nonStringsBefore linesShownBefore|

    (aCollection isNil and:[list isNil]) ifTrue:[
        "no change"
        ^ self
    ].

"/    list isNil ifTrue:[
"/        linesShownBefore := (1 to:nLinesShown) collect:[:i | ''].
"/    ] ifFalse:[
"/        linesShownBefore := (firstLineShown to:(firstLineShown+nLinesShown-1))
"/                            collect:[:i | (self at:i) ? ''].
"/    ].

    list := aCollection.

    nonStringsBefore := includesNonStrings.
    includesNonStrings := false.

    list notNil ifTrue:[
        expandTabs ifTrue:[
            self expandTabs
        ] ifFalse:[
            includesNonStrings := (list findFirst:[:e | e isString not]) ~~ 0.
        ].
    ].
    (includesNonStrings ~~ nonStringsBefore) ifTrue:[self getFontParameters].

"/ new - reposition horizontally if too big
    widthOfWidestLine := nil.   "/ i.e. unknown
    innerWidth >= self widthOfContents ifTrue:[
        leftOffset := 0.
    ].
    self contentsChanged.

"/ new - reposition vertically if too big
    (firstLineShown + nFullLinesShown) > self size ifTrue:[
        oldFirst := firstLineShown.
        firstLineShown := self size - nFullLinesShown + 1.
        firstLineShown < 1 ifTrue:[firstLineShown := 1].
        self originChanged:0 @ ((oldFirst - 1) negated * fontHeight).
        linesShownBefore := nil.
        shown ifTrue:[
            self clear.
        ]
    ].
"/ end new
    shown ifTrue:[
          self redrawFromVisibleLine:1 to:nLinesShown

"/        linesShownBefore isNil ifTrue:[
"/            self redrawFromVisibleLine:1 to:nLinesShown
"/        ] ifFalse:[
"/            1 to:nLinesShown do:[:l |
"/                |oldLine newLine|
"/
"/                newLine := self visibleAt:l.
"/                newLine size == 0 ifTrue:[
"/                    newLine := ''
"/                ].
"/                oldLine := linesShownBefore at:l ifAbsent:nil.
"/                oldLine size == 0 ifTrue:[
"/                    oldLine := ''
"/                ].
"/                oldLine ~= newLine ifTrue:[
"/                    self redrawVisibleLine:l
"/                ]
"/            ]
"/        ]
    ]

    "Modified: 18.12.1995 / 23:27:54 / stefan"
    "Modified: 6.3.1997 / 15:23:37 / cg"
!

size
    "return the size (i.e. number of lines)
     this allows textViews to be used like collections in some places."

    ^ list size.
!

stringAtLine:lineNr from:col1 to:col2
    "return the substring starting at physical line/col1, up-to and
     including col2. 
     The lineNr and colNr arguments start at 1, for the top-left character.
     Fills the string with space characters at the right.
     (i.e. behond the end of the line or below the last line)"

    |line len s|

    len := col2 - col1 + 1.
    list notNil ifTrue:[
        line := self listAt:lineNr.
        line notNil ifTrue:[
            (line size >= col1) ifTrue:[
                s := line copyFrom:col1.
                s size < len ifTrue:[
                    ^ s paddedTo:len
                ].
                ^ s copyTo:len
            ]
        ]
    ].
    ^ String new:len withAll:Character space

    "Created: 7.1.1997 / 19:58:43 / cg"
!

withoutRedrawAt:index put:aString
    "change a line without redisplay"

    |w|

    self checkForExistingLine:index.
    list at:index put:aString.
    includesNonStrings ifFalse:[
        includesNonStrings := (aString notNil and:[aString isString not]).
    ] ifTrue:[
        (aString isNil or:[aString isString]) ifTrue:[
            includesNonStrings := (list findFirst:[:l | l notNil and:[l isString not]]) ~~ 0.
        ]
    ].

    widthOfWidestLine notNil ifTrue:[
        aString isString ifTrue:[
            w := font widthOf:aString
        ] ifFalse:[
            w := aString widthOn:self
        ].
        w > widthOfWidestLine ifTrue:[
            widthOfWidestLine := w
        ] ifFalse:[
            widthOfWidestLine := nil "/ means: unknown
        ].
    ]

    "Modified: 22.10.1996 / 23:19:29 / cg"
! !

!ListView methodsFor:'accessing-mvc'!

addModelInterfaceTo:aDictionary
    "see comment in View>>modelInterface"

    super addModelInterfaceTo:aDictionary.
    aDictionary at:#listMessage put:listMsg
!

listMessage 
    "return the listMsg selector; 
     if non-nil, this is the message sent to the model (if any) to aquire
     a new text upon change of the aspect.
     This defaults to the aspect-selector."

    ^ listMsg
!

listMessage:aSymbol 
    "ST-80 compatibility: set the listMsg selector; 
     if non-nil, this will be sent to the model (if any) to aquire a 
     new text upon change of the aspect.
     This defaults to the aspect-selector."

    listMsg := aSymbol.
!

model:aModel
    "define the receivers model, from which the text is
     to be aquired via list- or aspect-messages, whenever its aspect
     changes."

    super model:aModel.
    self getListFromModel

    "Created: 31.12.1996 / 14:56:43 / stefan"
!

on:aModel aspect:aspectSymbol
    "ST-80 compatibility"

    ^ self on:aModel aspect:aspectSymbol change:nil list:aspectSymbol menu:nil 
!

on:aModel aspect:aspectSymbol change:changeSymbol 
    "ST-80 compatibility"

    ^self on:aModel aspect:aspectSymbol change:changeSymbol list:aspectSymbol menu:nil 
!

on:aModel aspect:aspectSymbol change:changeSymbol list:listSymbol menu:menuSymbol 
    "ST-80 compatibility"

    aspectSymbol notNil ifTrue:[aspectMsg := aspectSymbol. 
                             listMsg isNil ifTrue:[listMsg := aspectSymbol]].
    listSymbol notNil ifTrue:[listMsg := listSymbol].
    changeSymbol notNil ifTrue:[changeMsg := changeSymbol].
    menuMsg := menuSymbol.
    self model:aModel.

    "Modified: 2.1.1997 / 16:11:16 / cg"
!

on:aModel aspect:aspectSymbol change:changeSymbol menu:menuSymbol
    "ST-80 compatibility"

    ^ self on:aModel aspect:aspectSymbol change:changeSymbol list:nil menu:menuSymbol
!

on:aModel aspect:aspectSymbol list:listSymbol menu:menuSymbol 
    "ST-80 compatibility"

    ^ self on:aModel aspect:aspectSymbol change:nil list:listSymbol menu:menuSymbol 
!

on:aModel aspect:aspectSymbol menu:menuSymbol 
    "ST-80 compatibility"

    ^self on:aModel aspect:aspectSymbol change:nil list:aspectSymbol menu:menuSymbol 
! !

!ListView methodsFor:'change and update '!

update:something with:aParameter from:changedObject
    changedObject == model ifTrue:[
        (aspectMsg notNil
        and:[something == aspectMsg]) ifTrue:[
            ^ self getListFromModel.
        ].

        something == #size ifTrue:[
            ^ self getListFromModelScroll:false.
        ]
    ].
    ^ super update:something with:aParameter from:changedObject

    "Modified: 5.3.1997 / 16:14:01 / cg"
! !

!ListView methodsFor:'drawing'!

drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fg and:bg
    "draw a visible line range in fg/bg"

    |y         "{ Class: SmallInteger }"
     x         "{ Class: SmallInteger }"
     startLine "{ Class: SmallInteger }"
     endLine   "{ Class: SmallInteger }"
     listSize e sH|

    y := self yOfVisibleLine:startVisLineNr.
    sH := lineSpacing // 2.

    self paint:bg.
    self fillRectangleX:margin 
		      y:y-sH
		  width:(width - (margin * 2))
		 height:(endVisLineNr - startVisLineNr + 1) * fontHeight + (lineSpacing - sH).
    list isNil ifTrue:[^ self].

    y := y + fontAscent.
    listSize := self size.

    startLine := startVisLineNr + firstLineShown - 1.
    endLine := endVisLineNr + firstLineShown - 1.
    (startLine == 0) ifTrue:[
	y := y + fontHeight.
	startLine := startLine + 1
    ].

    (endLine > listSize) ifTrue:[
	e := listSize
    ] ifFalse:[
	e := endLine
    ].

    (startLine <= e) ifTrue:[
	x := textStartLeft - leftOffset.
	self paint:fg on:bg.
	self from:startLine to:e do:[:line |
	    line notNil ifTrue:[
		self displayOpaqueString:line x:x y:y
	    ].
	    y := y + fontHeight
	]
    ]

    "Modified: 24.2.1996 / 16:41:48 / cg"
!

drawLine:line atX:x inVisible:visLineNr with:fg and:bg
    "draw a given string at visible lines position with
     given x position in fg/bg. Clears the whole line before drawing the string.
     Low level entry; not meant for public use."

    |y|

    y := self yOfVisibleLine:visLineNr.
    self paint:bg.
    self fillRectangleX:margin y:y - (lineSpacing//2)
		  width:(width - (2 * margin)) 
		 height:fontHeight.
    line notNil ifTrue:[
	self paint:fg on:bg.
	self displayOpaqueString:line x:x y:(y + fontAscent)
    ]

    "Modified: 28.2.1996 / 14:46:07 / cg"
!

drawLine:line fromX:x inVisible:visLineNr with:fg and:bg
    "draw a given string at visible lines position with
     given x position in fg/bg. Clears partial line before drawing the string.
     Low level entry; not meant for public use."

    |y|

    y := self yOfVisibleLine:visLineNr.
"/    self paint:bg.
"/    self fillRectangleX:x "margin" y:y - (lineSpacing//2)
"/                  width:(width - margin - x) 
"/                 height:fontHeight.
    line notNil ifTrue:[
	self paint:fg on:bg.
	self displayOpaqueString:line x:x y:(y + fontAscent)
    ]

    "Modified: 28.2.1996 / 18:36:33 / cg"
!

drawLine:line inVisible:visLineNr with:fg and:bg
    "draw a given string at visible lines position in fg/bg"

    self drawLine:line atX:(textStartLeft - leftOffset) inVisible:visLineNr with:fg and:bg
!

drawVisibleLine:visLineNr col:col with:fg and:bg
    "draw single character at col index of visible line in fg/bg"

    |y yf x lineString characterString|

    lineString := self visibleAt:visLineNr.
    x := (self xOfCol:col inVisibleLine:visLineNr) - leftOffset.
    y := self yOfVisibleLine:visLineNr.

    self paint:bg.

    (lineString notNil and:[lineString isString not])
    ifTrue:[
	self drawVisibleLine:visLineNr with:fg and:bg
    ] ifFalse:[
	yf := y - (lineSpacing//2).
	col > lineString size ifTrue:[
	    self fillRectangleX:x y:yf width:(font width) height:fontHeight.
	    self paint:fg
	] ifFalse:[
	    characterString := lineString copyFrom:col to:col.
	    self fillRectangleX:x y:yf 
			  width:(font widthOf:characterString)
			 height:fontHeight.
	    self paint:fg.
	    self displayString:characterString x:x y:(y + fontAscent)
	]
    ]

    "Modified: 12.5.1996 / 12:47:07 / cg"
!

drawVisibleLine:visLineNr from:startCol to:endCol with:fg and:bg
    "draw part of a visible line in fg/bg"

    |y yf x lineString len characterString w|

    (endCol >= startCol) ifTrue:[
	lineString := self visibleAt:visLineNr.

	(lineString notNil and:[lineString isString not])
	ifTrue:[
	    self drawVisibleLine:visLineNr with:fg and:bg.
	] ifFalse:[
	    x := (self xOfCol:startCol inVisibleLine:visLineNr) - leftOffset.
	    y := (self yOfVisibleLine:visLineNr).
	    yf := y - (lineSpacing // 2).
	    len := lineString size.
	    (startCol > len) ifTrue:[
		len := endCol - startCol + 1.
		self paint:bg.
		self fillRectangleX:x y:yf 
			      width:(fontWidth * len) 
			     height:fontHeight
	    ] ifFalse:[
		(endCol > len) ifTrue:[
		    characterString := lineString species new:endCol.
		    characterString replaceFrom:1 to:len with:lineString startingAt:1.
		    lineString := characterString
		].
		self paint:bg.
		fontIsFixedWidth ifTrue:[
		    w := (endCol - startCol + 1) * fontWidth
		] ifFalse:[
		    (lineString isMemberOf:String) ifTrue:[
			w := font widthOf:lineString from:startCol to:endCol
		    ] ifFalse:[
			w := (lineString copyFrom:startCol to:endCol) widthOn:self
		    ]
		].
		self fillRectangleX:x y:yf 
			      width:w
			      height:fontHeight.
		self paint:fg on:bg.
		self displayOpaqueString:lineString from:startCol to:endCol x:x y:(y + fontAscent)
	    ]
	]
    ]

    "Modified: 22.5.1996 / 15:52:35 / cg"
!

drawVisibleLine:visLineNr from:startCol with:fg and:bg
    "draw right part of a visible line from startCol to end of line in fg/bg"

    |y x lineString index1 index2|

    (startCol < 1) ifTrue:[
	index1 := 1
    ] ifFalse:[
	index1 := startCol
    ].
    y := self yOfVisibleLine:visLineNr.
    x := (self xOfCol:index1 inVisibleLine:visLineNr) - leftOffset.
    self paint:bg.
    self fillRectangleX:x y:y - (lineSpacing // 2)
		  width:(width + leftOffset - x)
		 height:fontHeight.

    lineString := self visibleAt:visLineNr.
    lineString notNil ifTrue:[
	lineString isString ifFalse:[
	    self drawVisibleLine:visLineNr with:fg and:bg.
	] ifTrue:[
	    index2 := lineString size.
	    (index2 < index1) ifTrue:[^ self].
	    (index1 <= index2) ifTrue:[
		self paint:fg on:bg.
		self displayOpaqueString:lineString from:index1 to:index2 x:x y:(y + fontAscent)
	    ]
	]
    ]

    "Modified: 12.5.1996 / 12:47:49 / cg"
!

drawVisibleLine:visLineNr with:fg and:bg
    "draw a visible line in fg/bg"

    self 
	drawLine:(self visibleAt:visLineNr) 
	atX:(textStartLeft - leftOffset) 
	inVisible:visLineNr 
	with:fg 
	and:bg

    "Modified: 28.2.1996 / 19:30:23 / cg"
! !

!ListView methodsFor:'event processing'!

contentsChanged
    "contents changed - move origin up if possible"

    |listSize newOrigin|

    shown ifTrue:[
        list notNil ifTrue:[
            listSize := self numberOfLines.

            listSize == 0 ifTrue:[
                widthOfWidestLine := 0.
            ].
        
            "
             if we are beyond the end, scroll up a bit
            "
            ((firstLineShown + nFullLinesShown) > listSize) ifTrue:[
                newOrigin := listSize - nFullLinesShown + 1.
                newOrigin < 1 ifTrue:[
                    newOrigin := 1
                ].
                self scrollToLine: newOrigin.
            ].
        ].
    ].

    ^ super contentsChanged

    "Modified: 18.11.1996 / 19:50:07 / stefan"
    "Modified: 5.3.1997 / 15:50:46 / cg"
!

keyPress:key x:x y:y
    "a key was pressed - handle page-keys here"

    <resource: #keyboard (#PreviousPage #NextPage #HalfPageUp #HalfPageDown
			  #BeginOfText #EndOfText
			  #ScrollUp #ScrollDown )>
    |sensor n|

    (key == #PreviousPage) ifTrue: [^ self pageUp].
    (key == #NextPage)     ifTrue: [^ self pageDown].
    (key == #HalfPageUp)   ifTrue: [^ self halfPageUp].
    (key == #HalfPageDown) ifTrue: [^ self halfPageDown].

    (key == #BeginOfText) ifTrue:[^ self scrollToTop].
    (key == #EndOfText) ifTrue:[^ self scrollToBottom].

    sensor := self sensor.
    (key == #ScrollUp) ifTrue:[
	sensor isNil ifTrue:[
	    n := 1
	] ifFalse:[
	    n := 1 + (sensor compressKeyPressEventsWithKey:#ScrollUp).
	].
	^ self scrollUp:n
    ].
    (key == #ScrollDown) ifTrue:[
	sensor isNil ifTrue:[
	    n := 1
	] ifFalse:[
	    n := 1 + (sensor compressKeyPressEventsWithKey:#ScrollDown).
	].
	^ self scrollDown:n
    ].

    super keyPress:key x:x y:y
!

redrawX:x y:y width:w height:h
    "a region must be redrawn"

    |startLine stopLine startCol endCol line|

    shown ifFalse:[^ self].

    startLine := self visibleLineOfY:y.
    stopLine := self visibleLineOfY:(y + h).

    "if text-margin is affected"
    x < textStartLeft ifTrue:[
        self paint:bgColor.
        self fillRectangleX:margin y:margin width:(textStartLeft - margin)
                                           height:(height - margin - margin)
    ].
    y < textStartTop ifTrue:[
        self paint:bgColor.
        self fillRectangleX:margin y:margin width:(width - margin - margin)
                                           height:(textStartTop - margin)
    ].
    (w > (width // 4 * 3)) ifTrue:[
        "if area is big enough redraw whole lines"
        self redrawFromVisibleLine:startLine to:stopLine
    ] ifFalse:[
        includesNonStrings ifTrue:[
            startLine to:stopLine do:[:i |
                self redrawVisibleLine:i
            ]
        ] ifFalse:[
            line := self visibleAt:startLine.

            (fontIsFixedWidth 
            and:[line notNil
            and:[line isMemberOf:String]]) ifFalse:[
                "start/end col has to be computed for each line"

                startLine to:stopLine do:[:i |
                    startCol := self colOfX:x inVisibleLine:i.
                    endCol := self colOfX:(x + w) inVisibleLine:i.
                    startCol > 0 ifTrue:[
                        endCol > 0 ifTrue:[
                            self redrawVisibleLine:i from:startCol to:endCol
                        ]
                    ]
                ]
            ] ifTrue:[
                "start/end col is the same for all lines"
                startCol := self colOfX:x inVisibleLine:startLine.
                endCol := self colOfX:(x + w) inVisibleLine:startLine.
                startCol > 0 ifTrue:[
                    endCol > 0 ifTrue:[
                        startLine to:stopLine do:[:i |
                            line := self visibleAt:i.
                            (line isMemberOf:String) ifTrue:[
                                self redrawVisibleLine:i from:startCol to:endCol
                            ] ifFalse:[
                                self redrawVisibleLine:i
                            ]
                        ]
                    ]
                ]
            ]
        ]
    ]
!

sizeChanged:how
    "size changed - move origin up if possible"

    |listSize newOrigin|

    super sizeChanged:how.

    self computeNumberOfLinesShown.

    innerWidth := width - textStartLeft - margin.
    shown ifFalse:[^ self].
    list isNil ifTrue:[^ self].

"/    how ~~ #smaller ifTrue:[
"/        self invalidate 
"/    ].

    listSize := self numberOfLines.
    "
     if we are beyond the end, scroll up a bit
    "
    ((firstLineShown + nFullLinesShown) > listSize) ifTrue:[
        newOrigin := listSize - nFullLinesShown + 1.
        newOrigin < 1 ifTrue:[
            newOrigin := 1
        ].
        self scrollToLine: newOrigin.
        ^ self
    ].

    "Modified: / 18.11.1996 / 19:37:02 / stefan"
    "Modified: / 27.1.1998 / 14:10:04 / cg"
! !

!ListView methodsFor:'initialization'!

create
    super create.

    "I cache font parameters here - they are used so often ..."
    self getFontParameters.
    self computeNumberOfLinesShown.
    fgColor := fgColor on:device.
    bgColor := bgColor on:device
!

defaultControllerClass
    self class == ListView ifTrue:[^ ListViewController].
    ^ super defaultControllerClass
!

fetchDeviceResources
    "fetch device colors, to avoid reallocation at redraw time"

    super fetchDeviceResources.

    fgColor notNil ifTrue:[fgColor := fgColor on:device].
    bgColor notNil ifTrue:[bgColor := bgColor on:device].

    "Created: 14.1.1997 / 00:12:12 / cg"
!

initStyle
    "setup viewStyle specifics"

    super initStyle.

"/    DefaultFont notNil ifTrue:[font := DefaultFont on:device]

    self topMargin:(self verticalPixelPerMillimeter:0.5) rounded.
    self leftMargin:(self horizontalPixelPerMillimeter:0.5) rounded.

    lineSpacing := 0.
    fgColor := DefaultForegroundColor.
    bgColor := DefaultBackgroundColor.

    "Modified: 22.1.1997 / 11:57:21 / cg"
!

initialize
    super initialize.

    viewOrigin := 0@0.

    textStartTop := topMargin + margin.

    bitGravity := #NorthWest.
    list := nil.
    firstLineShown := 1.
    nFullLinesShown := 1. "just any value ..."
    nLinesShown := 1.     "just any value"
    leftOffset := 0.
    partialLines := true.
    tabPositions := DefaultTabPositions.
    includesNonStrings := false.
    self getFontParameters.
    wordCheck := [:char | char isNationalAlphaNumeric].

    autoScroll := true.

    "Modified: 4.11.1996 / 23:28:17 / cg"
!

realize
    |sz|

    extentChanged ifTrue:[
        self computeNumberOfLinesShown.
    ].

    firstLineShown ~~ 1 ifTrue:[
        sz := self size.
        firstLineShown + nLinesShown > sz ifTrue:[
            self scrollToLine:sz - nLinesShown.
        ]
    ].

    super realize.

"/ old: fetch models value on realize;
"/ new: fetch value when model is assigned.
"/
"/    model notNil ifTrue:[
"/        self getListFromModel.
"/    ]

    "Modified: 15.8.1996 / 13:08:56 / stefan"
    "Modified: 28.2.1997 / 19:44:19 / cg"
!

recreate
    "recreate after a snapin"

    super recreate.

    "
     recompute margins and font parameters
     - display may have different resolution/font sizes.
    "
    topMargin := (self verticalPixelPerMillimeter:0.5) rounded.
    self leftMargin:(self horizontalPixelPerMillimeter:0.5) rounded.
    self getFontParameters
! !

!ListView methodsFor:'private'!

absoluteLineToVisibleLine:absLineNr
    "given an absolute line (1..) return visible linenr or nil"

    absLineNr isNil ifTrue:[^ nil].
    (absLineNr < firstLineShown) ifTrue:[^ nil].
    (absLineNr >= (firstLineShown + nLinesShown)) ifTrue:[^ nil].
    ^ absLineNr - firstLineShown + 1
!

characterPositionOfLine:lineNr col:col
    "given a line/col position, return the character index within the contents-string,
     - used with Compilers error-positioning"

    |lineString pos|

    self checkForExistingLine:lineNr.
    pos := 1.
    1 to:(lineNr - 1) do:[:lnr |
	lineString := self at:lnr.
	lineString notNil ifTrue:[
	    pos := pos + lineString size
	].
	pos := pos + 1   "the return-character"
    ].
    ^ pos + col - 1

!

checkForExistingLine:lineNr
    "check if a line for lineNr exists; if not, expand text"

    list isNil ifTrue: [
	list := StringCollection new:lineNr.
	self contentsChanged
    ] ifFalse: [
	lineNr > (list size) ifTrue:[
	    self grow:lineNr.
	    self contentsChanged
	]
    ]
!

colOfX:x inVisibleLine:visLineNr
    "given a visible lineNr and x-coordinate, return colNr"

    |lineString linePixelWidth xRel runCol posLeft posRight done
     hasEmphasis oPosRight oPosLeft|

    xRel := x - textStartLeft + leftOffset.
    (xRel <= 0) ifTrue:[^ 1].

    "
     for fix fonts, this is easy ...
    "
    fontIsFixedWidth ifTrue:[
        ^ (xRel // fontWidth) + 1
    ].

    "
     for variable fonts, more work is required ...
    "
    lineString := self visibleAt:visLineNr.
    lineString notNil ifTrue:[
        lineString := lineString asString.
        (hasEmphasis := lineString hasChangeOfEmphasis) ifTrue:[
            linePixelWidth := lineString widthOn:self
        ] ifFalse:[
            linePixelWidth := font widthOf:lineString
        ]
    ] ifFalse:[
        linePixelWidth := 0
    ].

    (linePixelWidth <= xRel) ifTrue:[
        fontWidth == 0 ifTrue:[
            "
             although this 'cannot happen',
             it seems that X reports this width for some strange fonts ...
            "
            ^ lineString size   
        ].
        ^ lineString size + ((xRel - linePixelWidth) // fontWidth) + 1
    ].

    "/ cannot simply count individual characters,
    "/ since kerning or other non-linear effects may be involved ...

    runCol := lineString size // 2.
    (runCol == 0) ifTrue:[runCol := 1].

    hasEmphasis ifTrue:[
        posLeft := (lineString copyFrom:1 to:(runCol - 1)) widthOn:self.
        posRight := (lineString copyFrom:1 to:runCol) widthOn:self.
    ] ifFalse:[    
        posLeft := font widthOf:lineString from:1 to:(runCol - 1).
        posRight := font widthOf:lineString from:1 to:runCol.
    ].

    done := (posLeft <= xRel) and:[posRight > xRel].

    [done] whileFalse:[
        oPosRight := posRight.
        oPosLeft := posLeft.

        (posRight <= xRel) ifTrue:[
            runCol := runCol + 1.
            posLeft := posRight.
            hasEmphasis ifTrue:[
                posRight := (lineString copyFrom:1 to:runCol) widthOn:self.
            ] ifFalse:[
                posRight := font widthOf:lineString from:1 to:runCol
            ]
        ] ifFalse:[
            (posLeft > xRel) ifTrue:[
                runCol := runCol - 1.
                (runCol == 0) ifTrue:[^ 0].
                posRight := posLeft.
                hasEmphasis ifTrue:[
                    posLeft := (lineString copyFrom:1 to:(runCol - 1)) widthOn:self.
                ] ifFalse:[
                    posLeft := font widthOf:lineString from:1 to:(runCol - 1)
                ]
            ]
        ].
        done := (posLeft <= xRel) and:[posRight > xRel].

        ((oPosRight == posRight) and:[oPosLeft == posLeft]) ifTrue:[
            "/ paranoia: just in case there are unprintable characters
            "/ (avoid endless loop if the binary search does not make progress)
            done := true.
         ]
    ].

    ^ runCol

    "Modified: 2.7.1997 / 14:54:12 / cg"
!

computeNumberOfLinesShown
    "recompute the number of visible lines"

    |innerHeight|

    innerHeight := self innerHeight.
    nFullLinesShown := (innerHeight + lineSpacing) // fontHeight.
    nLinesShown := nFullLinesShown.

    partialLines ifTrue:[
	((nLinesShown * fontHeight) < innerHeight) ifTrue:[
	    nLinesShown := nLinesShown + 1
	]
    ]

    "Modified: 29.5.1996 / 14:48:43 / cg"
!

convertRTF:aList
    "this is a q&d RTF to poor-text converter which removes any rich stuff.
     - a first shot 'til  DocumentView is finished ..."

    |newList newLine charIndex inEscape char special|

    self obsoleteMethodWarning.

    newList := StringCollection new:200.
    newList grow:0.

    newLine := ''.
    aList do:[:line |
	((line size == 0) or:[line isBlank]) ifTrue:[
	    newList add:newLine.
	    newLine := ''
	] ifFalse:[
	    special := ((line at:1) == ${) or:[(line includes:$\)].
	    special := special or:[(line at:1) == $}].
	    special ifFalse:[
		newList add:(newLine , line)
	    ] ifTrue:[
		charIndex := 1.
		[charIndex <= line size] whileTrue:[
		    char := line at:charIndex.
		    ((char == ${ ) or:[char == $} ]) ifTrue:[
			"left-brace: ignore rest of line"
			charIndex := line size + 1
		    ] ifFalse:[
			(char == $\) ifTrue:[
			    inEscape := true
			] ifFalse:[
			    inEscape ifTrue:[
				(char == Character space) ifTrue:[
				    inEscape := false
				]
			    ] ifFalse:[
				newLine := newLine copyWith:char
			    ]
			].
			charIndex := charIndex + 1
		    ]
		]
	    ]
	]
    ].
    ^ newList

    "Modified: 18.5.1996 / 14:03:16 / cg"
!

getFontParameters
    "get some info of the used font. They are cached since we use them often ..
     The code below uses the fonts average height parameters - these
     are not OK for some oversized national characters (such as A-dieresis).
     Therefore, this method should be redefined in views which will be used
     with national characters (i.e. editTextViews)."

    |hMax|

    font := font on:device.
    hMax := font height.

    includesNonStrings == true ifTrue:[
        "/
        "/ find maximum height of lines
        "/
        hMax := list inject:hMax into:[:maxSoFar :thisLine | 
                                        thisLine isNil ifTrue:[
                                            maxSoFar
                                        ] ifFalse:[
                                            (thisLine isMemberOf:String) ifTrue:[
                                                maxSoFar
                                            ] ifFalse:[   
                                                maxSoFar max:(thisLine heightOn:self)
                                            ]
                                        ]
                              ].

    ].
    fontHeight := hMax + lineSpacing.
    fontAscent := font ascent. "/ maxAscent.
    fontWidth := font width.
    fontIsFixedWidth := font isFixedWidth.

    "Modified: 3.7.1997 / 12:24:25 / cg"
!

getListFromModel
    "ask my model (if any) for the text via the listMsg.
     If there is no listMessage, try aspect for backward compatibility."

    |text msg|

    model notNil ifTrue:[
        msg := listMsg.
        msg isNil ifTrue:[
            msg := aspectMsg
        ].


        msg notNil ifTrue:[
            text := model perform:msg.
            text notNil ifTrue:[
                text := text asStringCollection.
            ].
"/ SV: this does not work, if model uses (i.e. updates) the same stringCollection
"/ as the view!!
"/            text ~= list ifTrue:[
                self list:text
"/            ].
        ].
    ].

    "Modified: 26.4.1996 / 14:09:42 / cg"
    "Modified: 19.2.1997 / 12:08:50 / stefan"
!

getListFromModelScroll:aBoolean
    "ask my model (if any) for the text via the listMsg.
     If there is no listMessage, try aspect for backward compatibility."

    |text msg|

    model notNil ifTrue:[
        msg := listMsg.
        msg isNil ifTrue:[
            msg := aspectMsg
        ].

        msg notNil ifTrue:[
            text := model perform:msg.
            text notNil ifTrue:[
                text := text asStringCollection.
            ].
"/ SV: this does not work, if model uses (i.e. updates) the same stringCollection
"/ as the view!!
"/            text ~= list ifTrue:[
                aBoolean ifTrue:[
                    self list:text
                ] ifFalse:[
                    self setList:text
                ]
"/            ].
        ].
    ].

    "Modified: 19.2.1997 / 12:08:50 / stefan"
    "Created: 5.3.1997 / 16:10:22 / cg"
    "Modified: 5.3.1997 / 16:14:44 / cg"
!

lineOfCharacterPosition:charPos
    "given a character index within the contents-string,
     return the lineNumber where the character is
     - used to find line to hilight from Compilers error-position"

    |lineNr sum lastLine|

    lineNr := 1.
    sum := 0.
    lastLine := self size.
    [sum < charPos] whileTrue:[
	(lineNr > lastLine) ifTrue:[^ lineNr - 1].
	sum := sum + (self at:lineNr) size + 1.
	lineNr := lineNr + 1
    ].
    ^ lineNr - 1
!

listAt:lineNr
    "given a lineNumber, return the corresponding string
     This is used for accessing; i.e. for non-string entries, this
     returns the corresponding string."

    |l|

    list isNil ifTrue:[^ nil].
    (lineNr between:1 and:self size) ifFalse:[^ nil].
    l := self at:lineNr.
    l isNil ifTrue:[^ l].
    ^ l asString

    "Modified: 7.9.1995 / 15:54:59 / claus"
!

listAt:lineNr from:startCol
    "return right substring from startCol to end of a line"

    |line|

    line := self listAt:lineNr.
    line isNil ifTrue:[^ nil].
    (startCol > line size) ifTrue:[^ nil].
    ^ line copyFrom:startCol
!

listAt:lineNr from:startCol to:endCol
    "return substring from startCol to endCol of a line"

    |line stop lineLen|

    line := self listAt:lineNr.
    line isNil ifTrue:[^ nil].
    lineLen := line size.
    (startCol > lineLen) ifTrue:[^ nil].
    stop := endCol.
    (stop > lineLen) ifTrue:[stop := lineLen].
    ^ line copyFrom:startCol to:stop
!

listAt:lineNr to:endCol
    "return left substring from start to endCol of a line"

    |line stop|

    line := self listAt:lineNr.
    line isNil ifTrue:[^ nil].
    stop := endCol.
    (stop > line size) ifTrue:[stop := line size].
    ^ line copyTo:stop
!

listLineToVisibleLine:listLineNr
    "given a list line (1..) return visible linenr or nil"

    |visibleLineNr "{ Class: SmallInteger }"|

    shown ifFalse:[^ nil].
    listLineNr isNil ifTrue:[^ nil].
    visibleLineNr := listLineNr + 1 - firstLineShown.
    (visibleLineNr between:1 and:nLinesShown) ifFalse:[^ nil].
    ^ visibleLineNr
!

visibleAt:visibleLineNr
    "return what is visible at line (numbers start at 1).
     This is used for redrawing; i.e. for non-string entries, this
     returns the original."

    |listLineNr listsize|

    listLineNr := visibleLineNr + firstLineShown - 1.
    (listLineNr == 0) ifTrue:[^ nil].
    (list notNil) ifTrue:[
	listsize := self size
    ] ifFalse:[
	listsize := 0
    ].
    (listLineNr <= listsize) ifTrue:[^ self at:listLineNr].
    ^ ''
!

visibleLineOfY:y
    "given a y-coordinate, return lineNr
     - works for fix-height fonts only"

    ^ (((y - textStartTop) // fontHeight) + 1) max:1

    "Modified: / 13.2.1998 / 20:57:26 / stefan"
!

visibleLineToAbsoluteLine:visibleLineNr
    "given a visible line (1..) return absolut linenr"

    visibleLineNr isNil ifTrue:[^ nil].
    ^ visibleLineNr + firstLineShown - 1
!

visibleLineToListLine:visibleLineNr
    "given a visible line (1..) return linenr in list or nil
     (this one returns nil if the given visibleLineNr is one of the
     separators)"

    |listLineNr  "{ Class: SmallInteger }"
     listsize    "{ Class: SmallInteger }" |

    visibleLineNr isNil ifTrue:[^ nil].
    listLineNr := visibleLineNr + firstLineShown - 1.
    (listLineNr == 0) ifTrue:[^nil].
    listsize := self size.
    (listLineNr <= listsize) ifTrue:[^ listLineNr].
    ^ nil
!

widthForScrollBetween:firstLine and:lastLine
    "return the width in pixels for a scroll between firstLine and lastLine.
     - used to optimize scrolling, by limiting the scrolled area.
     Subclasses with selections or other additional visible stuff should redefine
     this method."

    |w|

    ^ innerWidth

"/    "for small width, its not worth searching for
"/     longest line ...
"/    "
"/    (width < 300) ifTrue:[^ innerWidth].
"/
"/    "for large lists, search may take longer than scrolling full
"/    "
"/    self size > 2000 ifTrue:[^ innerWidth].
"/
"/    "
"/     if there is a pattern-background, we have to scroll everything
"/    "
"/    (viewBackground isColor not
"/     or:[viewBackground isDithered]) ifTrue:[
"/        ^ width
"/    ].
"/
"/    w := self widthOfWidestLineBetween:firstLine and:lastLine.
"/    (w > innerWidth) ifTrue:[^ innerWidth].
"/    ^ w

    "Modified: 17.1.1997 / 17:44:12 / cg"
!

widthOfLineString:entry
    "return the width of an entry"

    entry isNil ifTrue:[^ 0].
    entry isString ifTrue:[
	^ font widthOf:entry
    ].
    ^ entry widthOn:self

    "Modified: 12.5.1996 / 20:09:53 / cg"
!

widthOfWidestLineBetween:firstLine and:lastLine
    "return the width in pixels of the widest line in a range
     - used to optimize scrolling, by limiting the scrolled area"

    |max      "{ Class: SmallInteger }"
     first    "{ Class: SmallInteger }"
     last     "{ Class: SmallInteger }"
     thisLen  "{ Class: SmallInteger }"
     listSize "{ Class: SmallInteger }" |

    includesNonStrings ifTrue:[
	^ width
    ].

    fontIsFixedWidth ifTrue:[
	^ (self lengthOfLongestLineBetween:firstLine and:lastLine) * fontWidth
    ].
    listSize := self size.
    max := 0.
    first := firstLine.
    last := lastLine.

    (first > listSize) ifTrue:[^ max].
    (last > listSize) ifTrue:[
	last := listSize
    ].

    self from:first to:last do:[:line |
	line notNil ifTrue:[
	    thisLen := font widthOf:line.
	    (thisLen > max) ifTrue:[
		max := thisLen
	    ]
	]
    ].
    ^ max
!

xOfCol:col inVisibleLine:visLineNr
    "given a visible line- and colNr, return x-coordinate in view"

    |line lineSize tcol|

    tcol := col - 1.
    fontIsFixedWidth ifTrue:[
	^ (tcol * fontWidth) + textStartLeft
    ].
    line := self visibleAt:visLineNr.
    line notNil ifTrue:[
	lineSize := line size
    ] ifFalse:[
	lineSize := 0
    ].
    (lineSize == 0) ifTrue:[
	^ (tcol * fontWidth) + textStartLeft
    ].

    (lineSize < col) ifTrue:[
	^ (line widthOn:self) 
	  + (fontWidth * (tcol - lineSize)) 
	  + textStartLeft
    ].
    (line isMemberOf:String) ifTrue:[
	^ (font widthOf:line from:1 to:tcol) + textStartLeft
    ].
    ^ ((line copyTo:tcol) widthOn:self) + textStartLeft

    "Modified: 19.7.1996 / 20:38:54 / cg"
!

yOfVisibleLine:visLineNr
    "given a visible lineNr, return y-coordinate in view
     - works for fix-height fonts only"

    ^ ((visLineNr - 1) * fontHeight) + textStartTop
! !

!ListView methodsFor:'queries'!

firstLineShown
    "return the index of the first (possibly partial) visible line"

    ^ firstLineShown
!

heightForLines:numberOfLines
    "return the height of the receiver, if numberOfLines are to be displayed"

    "need a device font for query"
    font := font on:device.
    ^ numberOfLines * fontHeight + topMargin + font descent + (lineSpacing) + (margin * 2)

    "Created: 27.1.1996 / 16:55:39 / cg"
!

heightOfContents
    "return the height of the contents in pixels
     - used for scrollbar interface"

    | numLines |

    numLines := self numberOfLines.
    numLines == 0 ifTrue:[^ 0].

    "/
    "/ kludge for last partial line
    "/
"/    nFullLinesShown ~~ nLinesShown ifTrue:[
"/        numLines := numLines + 1
"/    ].
    "
     need device-font for query
    "
    font := font on:device.
    ^ numLines * fontHeight 
"/                            + textStartTop
			    - (lineSpacing // 2)
"/                            + (font descent)       
"/                            + (font descent * 2) "makes it look better"
				.

"/    "it used to be that code - which is wrong"
"/    (nLinesShown == nFullLinesShown) ifTrue:[
"/        ^ numLines * fontHeight
"/    ].
"/    "add one - otherwise we cannot make last line
"/     fully visible since scrolling is done by full lines only"
"/
"/    ^ (numLines + 1) * fontHeight
!

lastLineShown
    "return the index of the last (possibly partial) visible line"

    ^ firstLineShown + nLinesShown
!

leftIndentOfLine:lineNr
    "return the number of spaces at the left in line, lineNr.
     returns 0 for empty lines."

    |lineString indent|

    lineString := self listAt:lineNr.
    lineString notNil ifTrue:[
	indent := lineString leftIndent.
	indent == lineString size ifTrue:[^ 0].
	^ indent.
    ].
    ^ 0

    "Modified: 20.4.1996 / 19:30:38 / cg"
!

lengthOfLongestLine
    "return the length (in characters) of the longest line"

    ^ self lengthOfLongestLineBetween:1 and:self size
!

lengthOfLongestLineBetween:firstLine and:lastLine
    "return the length (in characters) of the longest line in a line-range"

    |max      "{ Class: SmallInteger }"
     thisLen  "{ Class: SmallInteger }"
     listSize "{ Class: SmallInteger }"
     first    "{ Class: SmallInteger }"
     last     "{ Class: SmallInteger }" |

    list isNil ifTrue:[^ 0].

    listSize := self size.
    max := 0.
    first := firstLine.
    last := lastLine.

    (first > listSize) ifTrue:[^ max].
    (last > listSize) ifTrue:[
	last := listSize
    ].
    self from:first to:last do:[:lineString |
	lineString notNil ifTrue:[
	    thisLen := lineString size.
	    (thisLen > max) ifTrue:[
		max := thisLen
	    ]
	]
    ].
    ^ max

!

lineIsFullyVisible:line
    "is line fully visible?"

    (line >= firstLineShown
     and:[ line < (firstLineShown + nFullLinesShown) ]) ifTrue:[ ^ true ].
    ^ false.

    "Created: 26.4.1996 / 14:36:45 / cg"
!

lineIsVisible:line
    "is line visible?"

    (line >= firstLineShown and:[ line < (firstLineShown + nLinesShown) ]) ifTrue:[ ^ true ].
    ^ false.
!

numberOfLines
    "return the number of lines the text has"

    ^ self size
!

preferredExtentForLines:numLines cols:numCols
    ^ (((font widthOf:'x') * numCols + margin + margin) 
      @ 
      (fontHeight * numLines + margin + margin + font descent + lineSpacing + topMargin)).

    "Modified: 26.5.1996 / 12:26:41 / cg"
!

widthOfContents
    "return the width of the contents in pixels
     - used for scrollbar interface"

    |max f|

    list isNil ifTrue:[^ 0].
    widthOfWidestLine notNil ifTrue:[^ widthOfWidestLine + (leftMargin * 2)].

    device isNil ifTrue:[
	"/ mhmh - really dont know yet
	f := font on:Screen current
    ] ifFalse:[
	f := font := font on:device.
    ].

    includesNonStrings ifTrue:[
	max := list 
		   inject:0 
		   into:[:maxSoFar :entry |
			     (
				 entry isNil ifTrue:[
				     0
				 ] ifFalse:[
				    entry isString ifTrue:[
					f widthOf:entry
				    ] ifFalse:[
					entry widthOn:self
				    ]
				 ]
			     ) max:maxSoFar.
			]
    ] ifFalse:[
	fontIsFixedWidth ifTrue:[
	    max := self lengthOfLongestLine * fontWidth
	] ifFalse:[
	    max := 0.
	    list notNil ifTrue:[
		list do:[:line |
		    line notNil ifTrue:[
			max := max max:(line widthOn:self)
		    ]
		].
"/                max := max max:(f widthOf:list)
	    ].
	].
    ].
    widthOfWidestLine := max.
    ^ max + (leftMargin * 2)

    "Modified: 5.7.1996 / 13:54:01 / cg"
!

xOriginOfContents
    "return the horizontal origin of the contents in pixels
     - used for scrollbar interface"

    ^ leftOffset 
!

yOriginOfContents
    "return the vertical origin of the contents in pixels
     - used for scrollbar interface"

    ^ (firstLineShown - 1) * fontHeight
! !

!ListView methodsFor:'redrawing'!

flash
    "show contents in reverse colors for a moment - to wakeup the user :-)"

    self redrawInverted.
    Delay waitForSeconds:0.1.
    self redraw

    "
     Transcript flash
     Transcript redrawInverted
     Transcript redraw
    "
!

redraw
    "redraw complete view"

    shown ifTrue:[
	self redrawFromVisibleLine:1 to:nLinesShown
    ]
!

redrawFromLine:lineNr
    "redraw starting at linrNr"

    |visibleLine first|

    shown ifTrue:[
	"if first line to redraw is above 1st visible line,
	 start redraw at 1st visible line"
	(lineNr < firstLineShown) ifTrue:[
	    first := firstLineShown
	] ifFalse:[
	    first := lineNr
	].
	visibleLine := self listLineToVisibleLine:first.
	visibleLine notNil ifTrue:[
	    self redrawFromVisibleLine:visibleLine to:nLinesShown
	]
    ]
!

redrawFromLine:start to:end
    "redraw lines from start to end"

    |visibleFirst visibleLast first last lastLineShown|

    shown ifTrue:[
	lastLineShown := firstLineShown + nLinesShown - 1.
	(start <= lastLineShown) ifTrue:[
	    (end >= firstLineShown) ifTrue:[

		"if first line to redraw is above 1st visible line,
		 start redraw at 1st visible line"

		(start < firstLineShown) ifTrue:[
		    first := firstLineShown
		] ifFalse:[
		    first := start
		].
		(end > lastLineShown) ifTrue:[
		    last := lastLineShown
		] ifFalse:[
		    last := end
		].
		visibleFirst := self listLineToVisibleLine:first.
		visibleLast := self listLineToVisibleLine:last.
		self redrawFromVisibleLine:visibleFirst to:visibleLast
	    ]
	]
    ]
!

redrawFromVisibleLine:startVisLineNr to:endVisLineNr
    "redraw a visible line range"

    shown ifTrue:[
	self drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fgColor and:bgColor
    ]
!

redrawInverted
    "show contents in reverse colors"

    |savFg savBg|

    savFg := fgColor.
    savBg := bgColor.
    fgColor := savBg.
    bgColor := savFg.
    self redraw.
    fgColor := savFg.
    bgColor := savBg.
!

redrawLine:lineNr
    "redraw a list line"

    |visibleLine|

    visibleLine := self listLineToVisibleLine:lineNr.
    visibleLine notNil ifTrue:[
	self redrawVisibleLine:visibleLine
    ]
!

redrawLine:lineNr col:col
    "redraw a single character"

    |visibleLine|

    visibleLine := self listLineToVisibleLine:lineNr.
    visibleLine notNil ifTrue:[
	self redrawVisibleLine:visibleLine col:col
    ]
!

redrawLine:lineNr from:startCol
    "redraw a list line from startCol to end of line"

    |visibleLine|

    visibleLine := self listLineToVisibleLine:lineNr.
    visibleLine notNil ifTrue:[
	self redrawVisibleLine:visibleLine from:startCol
    ]
!

redrawLine:lineNr from:startCol to:endCol
    "redraw a list line from startCol to endCol"

    |visibleLine|

    visibleLine := self listLineToVisibleLine:lineNr.
    visibleLine notNil ifTrue:[
	self redrawVisibleLine:visibleLine from:startCol to:endCol
    ]
!

redrawVisibleLine:visLineNr
    "redraw a visible line"

    shown ifTrue:[
	self drawVisibleLine:visLineNr with:fgColor and:bgColor
    ]
!

redrawVisibleLine:visLineNr col:col
    "redraw single character at col index of visible line"

    shown ifTrue:[
	self drawVisibleLine:visLineNr col:col with:fgColor and:bgColor
    ]
!

redrawVisibleLine:visLineNr from:startCol
    "redraw right part of a visible line from startCol to end of line"

    shown ifTrue:[
	self drawVisibleLine:visLineNr from:startCol with:fgColor and:bgColor
    ]
!

redrawVisibleLine:visLineNr from:startCol to:endCol
    "redraw part of a visible line"

    shown ifTrue:[
	self drawVisibleLine:visLineNr from:startCol to:endCol with:fgColor and:bgColor
    ]
! !

!ListView methodsFor:'scrolling'!

gotoLine:aLineNumber
    "position to line aLineNumber; this may be redefined
     in subclasses (for example to move the cursor also)"

    ^ self scrollToLine:aLineNumber
!

halfPageDown
    "scroll down half a page"

    self scrollDown:(nFullLinesShown // 2)
!

halfPageUp
    "scroll up half a page"

    self scrollUp:(nFullLinesShown // 2)
!

makeColVisible:aCol inLine:aLineNr
    "if column aCol is not visible, scroll horizontal to make it visible"

    |xWant xVis visLnr|

    (aCol isNil or:[shown not]) ifTrue:[^ self].

    visLnr := self absoluteLineToVisibleLine:aLineNr.
    visLnr isNil ifTrue:[^ self].

    xWant := self xOfCol:aCol inVisibleLine:visLnr.
    xVis := xWant - leftOffset.

    "
     dont scroll, if already visible
     (but scroll, if not in inner 20%..80% of visible area)
    "
"/    ((xVis >= (width // 5)) and:[xVis <= (width * 4 // 5)]) ifTrue:[
"/        ^ self
"/    ].

    "
     no, the above does not look good, if you click / select at the
     far right - makes selecting so difficult ...
    "
    (xVis >= 0 and:[xVis < (width - font width)]) ifTrue:[^ self].

    self scrollHorizontalTo:(xWant - (width // 2)).
!

makeLineVisible:aListLineNr
    "if aListLineNr is not visible, scroll to make it visible.
     Numbering starts with 1 for the very first line of the text."

    |bott|

    (aListLineNr isNil "or:[shown not]") ifTrue:[^ self].

"/  Old code follows. It is no longer used, because:
"/      1. we must maintain our viewOrigin (not maintained in this code!!)
"/      2. we must inform our dependents about originChanges.
"/
"/    shown ifFalse:[
"/        firstLineShown := (aListLineNr - 1) max:1.
"/        firstLineShown > (list size - nFullLinesShown) ifTrue:[
"/            firstLineShown := list size - nFullLinesShown
"/        ].
"/        list size <= nFullLinesShown ifTrue:[
"/            firstLineShown := 1
"/        ].
"/        ^ self
"/    ].

    (aListLineNr >= firstLineShown) ifTrue:[
        (aListLineNr < (firstLineShown + nFullLinesShown)) ifTrue:[
            ^ self
        ]
    ].
    (aListLineNr < nFullLinesShown) ifTrue:[
        ^ self scrollToLine:1
    ].
    (nFullLinesShown < 3) ifTrue:[
        ^ self scrollToLine:aListLineNr
    ].
    bott := self numberOfLines - (nFullLinesShown - 1).
    (aListLineNr > bott) ifTrue:[
        ^ self scrollToLine:bott
    ].
    self scrollToLine:(aListLineNr - (nFullLinesShown // 2) + 1)

    "Modified: 26.5.1996 / 16:00:32 / cg"
    "Modified: 18.12.1996 / 17:48:22 / stefan"
!

makeVisible:someString
    "if nescessary, scroll to make the (first)
     line containing someString visible."

    |line index list|

    (list := self list) notNil ifTrue:[
        index := list indexOf:someString.
        index ~~ 0 ifTrue:[
            self makeLineVisible:index
        ]
    ]

    "Modified: 9.9.1997 / 10:10:13 / cg"
!

pageDown
    "change origin to display next page"

    |nLines|

    nLines := nFullLinesShown.
    (firstLineShown + nLines + nFullLinesShown > self size) ifTrue:[
        nLines := self size - firstLineShown - nFullLinesShown + 1
    ].
    nLines <= 0 ifTrue:[^ self].

    self originWillChange.
    firstLineShown := firstLineShown + nLines.
    self originChanged:0 @ (nLines * fontHeight).
    "/ self redrawFromVisibleLine:1 to:nLinesShown
    self invalidate

    "Modified: 17.4.1997 / 01:46:34 / cg"
!

pageUp
    "change origin to display previous page"

    |oldOrg|

    (firstLineShown == 1) ifFalse:[
        self originWillChange.
        oldOrg := firstLineShown.
        firstLineShown := firstLineShown - nFullLinesShown.
        (firstLineShown < 1) ifTrue:[
            firstLineShown := 1
        ].
        self originChanged:0 @ (firstLineShown - oldOrg * fontHeight).
        "/ self redrawFromVisibleLine:1 to:nLinesShown
        self invalidate
    ]

    "Modified: 17.4.1997 / 01:46:57 / cg"
!

scrollDown
    "change origin to scroll down one line (towards the bottom of the text)"

    self scrollDown:1

    "Modified: 24.2.1996 / 16:17:32 / cg"
!

scrollDown:nLines
    "change origin to scroll down some lines (towards the bottom of the text)"

    |w     "{ Class:SmallInteger }"
     h     "{ Class:SmallInteger }"
     n     "{ Class:SmallInteger }"
     m2    "{ Class:SmallInteger }"
     count "{ Class:SmallInteger }"
     y0    "{ Class:SmallInteger }"
     y1    "{ Class:SmallInteger }"
     nPixel sz sH partialCopy|

    count := nLines.
    sz := self size.
    (firstLineShown + nLines + nFullLinesShown > sz) ifTrue:[
        count := sz - firstLineShown - nFullLinesShown + 1
    ].
    count <= 0 ifTrue:[^ self].

    self originWillChange.
    nPixel := fontHeight * count.

    shown ifFalse:[
        firstLineShown := firstLineShown + count.
        viewOrigin := viewOrigin x @ (viewOrigin y + nPixel).
    ] ifTrue:[
        (count >= nLinesShown) ifTrue:[
            firstLineShown := firstLineShown + count.
            viewOrigin := viewOrigin x @ (viewOrigin y + nPixel).
            "/ self redrawFromVisibleLine:1 to:nLinesShown.
            self invalidate
        ] ifFalse:[
            m2 := margin * 2.
            w := self widthForScrollBetween:firstLineShown 
                                        and:(firstLineShown + nLinesShown).
            w := w + leftMargin.

            sH := lineSpacing // 2.    
            y0 := textStartTop - sH.
            h := nPixel + y0.
            n := height - h + (lineSpacing " //2 ").   

            y1 := h + n - 1.
            y1 >= (height - margin) ifTrue:[
                partialCopy := true.
                y1 := height - margin - 1
            ].

            self catchExpose.
            self 
                copyFrom:self x:margin y:h
                toX:margin y:y0
                width:w height:(y1 - h + 1)
                async:true.

            firstLineShown := firstLineShown + count.
            viewOrigin := viewOrigin x @ (viewOrigin y + nPixel).

            (partialCopy == true and:[lineSpacing ~~ 0]) ifTrue:[
                self paint:bgColor.
                self fillRectangleX:margin y:(y0 + (y1 - h + 1))
                              width:w height:sH.
            ].
            self redrawFromVisibleLine:(nFullLinesShown - count + 1) to:nLinesShown.
            self waitForExpose.
        ].
    ].
    self originChanged:(0 @ nPixel).

    "Modified: 17.4.1997 / 01:47:46 / cg"
!

scrollDownPixels:pix
    "change origin to scroll down some pixels 
     (towards the bottom of the text)
     THIS WILL VANISH!!"

    |w     "{ Class:SmallInteger }"
     h     "{ Class:SmallInteger }"
     n     "{ Class:SmallInteger }"
     m2    "{ Class:SmallInteger }"
     count "{ Class:SmallInteger }"
     y0    "{ Class:SmallInteger }"
     y1    "{ Class:SmallInteger }"
     nLines nPixel sz sH partialCopy|

    nLines := pix / fontHeight.
    count := nLines.
    sz := self size.
    (firstLineShown + nLines + nFullLinesShown > sz) ifTrue:[
        count := sz - firstLineShown - nFullLinesShown + 1
    ].
    count <= 0 ifTrue:[^ self].

    self originWillChange.
    nPixel := fontHeight * count.

    shown ifFalse:[
        firstLineShown := firstLineShown + count.
        viewOrigin := viewOrigin x @ (viewOrigin y + nPixel).
    ] ifTrue:[
        (count >= nLinesShown) ifTrue:[
            firstLineShown := firstLineShown + count.
            viewOrigin := viewOrigin x @ (viewOrigin y + nPixel).
            self redrawFromVisibleLine:1 to:nLinesShown.
        ] ifFalse:[
            m2 := margin * 2.
            w := self widthForScrollBetween:firstLineShown 
                                        and:(firstLineShown + nLinesShown).
            w := w + leftMargin.

            sH := lineSpacing // 2.    
            y0 := textStartTop - sH.
            h := nPixel + y0.
            n := height - h + (lineSpacing " //2 ").   

            y1 := h + n - 1.
            y1 >= (height - margin) ifTrue:[
                partialCopy := true.
                y1 := height - margin - 1
            ].

            self catchExpose.
            self 
                copyFrom:self 
                x:margin y:h
                toX:margin y:y0
                width:w height:(y1 - h + 1)
                async:true.

            firstLineShown := firstLineShown + count.
            viewOrigin := viewOrigin x @ (viewOrigin y + nPixel).

            (partialCopy == true and:[lineSpacing ~~ 0]) ifTrue:[
                self paint:bgColor.
                self fillRectangleX:margin y:(y0 + (y1 - h + 1))
                              width:w height:sH.
            ].
            self redrawFromVisibleLine:(nFullLinesShown - count + 1) to:nLinesShown.
            self waitForExpose.
        ].
    ].
    self originChanged:(0 @ nPixel).

    "Modified: 29.1.1997 / 13:06:15 / cg"
!

scrollHorizontalTo:aPixelOffset
    "change origin to make aPixelOffset be the left col"

    |orgX|

    orgX := leftOffset.

    (aPixelOffset < orgX) ifTrue:[
	self scrollLeft:(orgX - aPixelOffset)
    ] ifFalse:[
	(aPixelOffset > orgX) ifTrue:[
	    self scrollRight:(aPixelOffset - orgX)
	]
    ]
!

scrollLeft
    "scroll left by one character
      - question is how much is a good for variable fonts"

    self scrollLeft:font width
!

scrollLeft:nPixel
    "change origin to scroll left some cols"

    |newLeftOffset delta|

    nPixel <= 0 ifTrue:[^ self].

    newLeftOffset := leftOffset - nPixel.
    newLeftOffset <= 0 ifTrue:[
        leftOffset == 0 ifTrue:[^ self].
        newLeftOffset := 0
    ].

    self originWillChange.
    delta := newLeftOffset - leftOffset.
    leftOffset := newLeftOffset.
    viewOrigin := newLeftOffset @ viewOrigin y.
    "/ self redrawFromVisibleLine:1 to:nLinesShown.
    self invalidate.
    self originChanged:(delta @ 0)

    "Modified: 17.4.1997 / 01:48:34 / cg"
!

scrollRight
    "scroll right by one character
      - question is how much is a good for variable fonts"

    self scrollRight:font width
!

scrollRight:nPixel
    "change origin to scroll right some cols"

    |wMax cnt|


    cnt := nPixel.

"
 commenting out the block below allows scrolling to the right of
 the widest line
"
" "
    "
     the 10 below allows scrolling somewhat behind the end of the line
    "
    wMax := self widthOfContents + 10.
    (leftOffset + nPixel + width > wMax) ifTrue:[
        cnt := wMax - leftOffset - width
    ].
" "
    cnt <= 0 ifTrue:[^ self].
    self originWillChange.
    leftOffset := leftOffset + cnt.
    viewOrigin := leftOffset @ viewOrigin y.
    "/ self redrawFromVisibleLine:1 to:nLinesShown.
    self invalidate.
    self originChanged:(cnt @ 0)

    "Modified: 17.4.1997 / 01:48:27 / cg"
!

scrollSelectDown
    "just a template - I do not know anything about selections"

    ^ self subclassResponsibility
!

scrollSelectUp
    "just a template - I do not know anything about selections"

    ^ self subclassResponsibility
!

scrollTo:newOrigin 
    "change origin to have newOrigin be visible at the top-left.
     The argument defines the integer device coordinates of the new top-left 
     point."

    "due to historic reasons, the work is actually done by scrollUp/Down
     scrollLeft/Right (those where implemented first).
     This will be changed to do all work here, and call it from
     the other scrolling methods."

    |dX   "{ Class:SmallInteger }"
     dY   "{ Class:SmallInteger }"
     m2   "{ Class:SmallInteger }" |

    dX := newOrigin x - viewOrigin x.
    dY := newOrigin y - viewOrigin y.
    dX = 0 ifTrue:[
        dY < 0 ifTrue:[
            ^ self scrollUpPixels:(dY negated).
        ].
        dY > 0 ifTrue:[
            ^ self scrollDownPixels:dY.
        ].
        ^ self
    ].
    dY = 0 ifTrue:[
        dX < 0 ifTrue:[
            ^ self scrollLeft:dX negated
        ].
        dX > 0 ifTrue:[
            ^ self scrollRight:dX
        ].
    ].

    self originWillChange.
    self setViewOrigin:newOrigin.
    shown ifTrue:[
        m2 := margin * 2. "top & bottom margins"
        self redrawDeviceX:margin y:margin
                     width:(width - m2)
                    height:(height - m2).
    ].
    self originChanged:(dX negated @ dY negated).

    "Modified: 22.5.1996 / 11:18:30 / cg"
    "Created: 7.8.1996 / 17:51:34 / stefan"
    "Modified: 16.12.1996 / 14:07:32 / stefan"
!

scrollToBottom
    "change origin to show end of text"

    "scrolling to the end is not really correct (i.e. should scroll to list size - nFullLinesShown), 
     but scrollDown: will adjust it ..."

    self scrollToLine:(self size)
!

scrollToCol:aColNr
    "change origin to make aColNr be the left col"

    |pxlOffset|

    aColNr == 1 ifTrue:[
	leftOffset ~~ 0 ifTrue:[
	    self scrollLeft:leftOffset.
	].
	^ self
    ].

    pxlOffset := font width * (aColNr - 1).

    pxlOffset < leftOffset ifTrue:[
	self scrollLeft:(leftOffset - pxlOffset)
    ] ifFalse:[
	pxlOffset > leftOffset ifTrue:[
	    self scrollRight:(pxlOffset - leftOffset)
	]
    ]
!

scrollToLeft
    "change origin to start (left) of text"

    leftOffset ~~ 0 ifTrue:[
	self scrollToCol:1
    ]
!

scrollToLine:aLineNr
    "change origin to make aLineNr be the top line"

    aLineNr < firstLineShown ifTrue:[
	self scrollUp:(firstLineShown - aLineNr)
    ] ifFalse:[
	aLineNr > firstLineShown ifTrue:[
	    self scrollDown:(aLineNr - firstLineShown)
	]
    ]
!

scrollToPercent:percentOrigin
    "scroll to a position given in percent of total"

    "kludge - ListView thinks in lines"

    self scrollHorizontalToPercent:percentOrigin x.
    self scrollVerticalToPercent:percentOrigin y.
!

scrollToTop
    "change origin to start of text"

    self scrollToLine:1
!

scrollUp
    "change origin to scroll up one line (towards the top of the text)"

    self scrollUp:1

    "Modified: 24.2.1996 / 16:17:38 / cg"
!

scrollUp:nLines
    "change origin to scroll up some lines (towards the top of the text)"

    |w      "{ Class:SmallInteger }"
     h      "{ Class:SmallInteger }"
     count  "{ Class:SmallInteger }"
     nPixel|

    count := nLines.
    count >= firstLineShown ifTrue:[
        count := firstLineShown - 1
    ].
    (count == 0) ifTrue:[^ self].

    self originWillChange.
    nPixel := fontHeight * count.
    shown ifFalse:[
        firstLineShown := firstLineShown - count.
        viewOrigin := viewOrigin x @ (viewOrigin y - nPixel).
    ] ifTrue:[
        (count >= nLinesShown) ifTrue:[
            firstLineShown := firstLineShown - count.
            viewOrigin := viewOrigin x @ (viewOrigin y - nPixel).
            "/ self redrawFromVisibleLine:1 to:nLinesShown.
            self invalidate.
        ] ifFalse:[
            w := self widthForScrollBetween:firstLineShown
                                        and:(firstLineShown + nLinesShown).
            w := w + leftMargin.
            h := nPixel + margin.
            self catchExpose.
            self 
                copyFrom:self 
                x:margin y:margin 
                toX:margin y:h
                width:w height:(height - h)
                async:true.
            firstLineShown := firstLineShown - count.
            viewOrigin := viewOrigin x @ (viewOrigin y - nPixel).
            self redrawFromVisibleLine:1 to:count.
            self waitForExpose.
        ].
    ].
    self originChanged:(0 @ (nPixel negated)).

    "Modified: 17.4.1997 / 01:48:50 / cg"
!

scrollUpPixels:pix
    "change origin to scroll up some pixels 
     (towards the top of the text)
    THIS WILL VANISH!!"

    |w      "{ Class:SmallInteger }"
     h      "{ Class:SmallInteger }"
     count  "{ Class:SmallInteger }"
     nLines nPixel|

    nLines := pix / fontHeight.

    count := nLines.
    count >= firstLineShown ifTrue:[
        count := firstLineShown - 1
    ].
    (count == 0) ifTrue:[^ self].

    self originWillChange.
    nPixel := fontHeight * count.
    shown ifFalse:[
        firstLineShown := firstLineShown - count.
        viewOrigin := viewOrigin x @ (viewOrigin y - nPixel).
    ] ifTrue:[
        (count >= nLinesShown) ifTrue:[
            firstLineShown := firstLineShown - count.
            viewOrigin := viewOrigin x @ (viewOrigin y - nPixel).
            self redrawFromVisibleLine:1 to:nLinesShown.
        ] ifFalse:[
            w := self widthForScrollBetween:firstLineShown
                                        and:(firstLineShown + nLinesShown).
            w := w + leftMargin.
            h := nPixel + margin.
            self catchExpose.
            self 
                copyFrom:self x:margin y:margin 
                toX:margin y:h
                width:w height:(height - h)
                async:true.
            firstLineShown := firstLineShown - count.
            viewOrigin := viewOrigin x @ (viewOrigin y - nPixel).
            self redrawFromVisibleLine:1 to:count.
            self waitForExpose.
        ].
    ].
    self originChanged:(0 @ (nPixel negated)).

    "Modified: 29.1.1997 / 13:06:46 / cg"
!

scrollVerticalToPercent:percent
    "scroll to a position given in percent of total"

    |nL lineNr|

    nL := self numberOfLines.
    "/
    "/ kludge for last partial line
    "/
    nFullLinesShown ~~ nLinesShown ifTrue:[
	nL := nL + 1
    ].
    lineNr := (((nL * percent) asFloat / 100.0) + 0.5) asInteger + 1.
    self scrollToLine:lineNr
!

startAutoScrollDown:yDistance
    "setup for auto-scroll down (when button-press-moving below view)
     - timeDelta for scroll is computed from distance"

    |deltaT mm|

    autoScroll ifFalse:[^ self].

    mm := yDistance // self verticalIntegerPixelPerMillimeter + 1.
    deltaT := 0.5 / mm.

    (deltaT = autoScrollDeltaT) ifFalse:[
	autoScrollDeltaT := deltaT.
	autoScrollBlock isNil ifTrue:[
	    autoScrollBlock := [self scrollSelectDown].
	    Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
	]
    ]
!

startAutoScrollLeft:xDistance
    "setup for auto-scroll up (when button-press-moving to the left of the view)
     - timeDelta for scroll is computed from distance"

    |deltaT mm|

    autoScroll ifFalse:[^ self].

    mm := xDistance negated // self horizontalIntegerPixelPerMillimeter + 1.
    deltaT := 0.5 / mm.

    (deltaT = autoScrollDeltaT) ifFalse:[
	autoScrollDeltaT := deltaT.
	autoScrollBlock isNil ifTrue:[
	    autoScrollBlock := [self scrollSelectLeft].
	    Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
	]
    ]
!

startAutoScrollRight:xDistance
    "setup for auto-scroll down (when button-press-moving to the right of the view)
     - timeDelta for scroll is computed from distance"

    |deltaT mm|

    autoScroll ifFalse:[^ self].

    mm := xDistance // self horizontalIntegerPixelPerMillimeter + 1.
    deltaT := 0.5 / mm.

    (deltaT = autoScrollDeltaT) ifFalse:[
	autoScrollDeltaT := deltaT.
	autoScrollBlock isNil ifTrue:[
	    autoScrollBlock := [self scrollSelectRight].
	    Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
	]
    ]
!

startAutoScrollUp:yDistance
    "setup for auto-scroll up (when button-press-moving below view)
     - timeDelta for scroll is computed from distance"

    |deltaT mm|

    autoScroll ifFalse:[^ self].

    mm := yDistance negated // self verticalIntegerPixelPerMillimeter + 1.
    deltaT := 0.5 / mm.

    (deltaT = autoScrollDeltaT) ifFalse:[
	autoScrollDeltaT := deltaT.
	autoScrollBlock isNil ifTrue:[
	    autoScrollBlock := [self scrollSelectUp].
	    Processor addTimedBlock:autoScrollBlock afterSeconds:deltaT
	]
    ]
!

stopAutoScroll
    "stop any auto-scroll"

    autoScrollBlock notNil ifTrue:[
	self compressMotionEvents:true.
	Processor removeTimedBlock:autoScrollBlock.
	autoScrollBlock := nil.
	autoScrollDeltaT := nil
    ].
!

viewOrigin
    "return the viewOrigin; thats the coordinate of the contents 
     which is shown topLeft in the view 
     (i.e. the origin of the visible part of the contents)."

    ^ viewOrigin
! !

!ListView methodsFor:'searching'!

findBeginOfWordAtLine:selectLine col:selectCol
    "return the col of first character of the word at given line/col.
     If the character under the initial col is a space character, return
     the first col of the blank-block."

    |beginCol thisCharacter|

    beginCol := selectCol.
    thisCharacter := self characterAtLine:selectLine col:beginCol.

    "is this acharacter within a word ?"
    (wordCheck value:thisCharacter) ifTrue:[
	[wordCheck value:thisCharacter] whileTrue:[
	    beginCol := beginCol - 1.
	    beginCol < 1 ifTrue:[
		thisCharacter := Character space
	    ] ifFalse:[
		thisCharacter := self characterAtLine:selectLine col:beginCol
	    ]
	].
	beginCol := beginCol + 1.
    ] ifFalse:[
	"nope - maybe its a space"
	thisCharacter == Character space ifTrue:[
	    [beginCol > 1 and:[thisCharacter == Character space]] whileTrue:[
		beginCol := beginCol - 1.
		thisCharacter := self characterAtLine:selectLine col:beginCol
	    ].
	    thisCharacter ~~ Character space ifTrue:[
		beginCol := beginCol + 1.
	    ].
	] ifFalse:[
	    "select single character"
	]
    ].
    ^ beginCol
!

findEndOfWordAtLine:selectLine col:selectCol
    "return the col of last character of the word at given line/col.
     If the character under the initial col is a space character, return
     the last col of the blank-block.
     Return 0 if we should wrap to next line (for spaces)"

    |endCol "{ Class: SmallInteger }"
     len    "{ Class: SmallInteger }"
     thisCharacter|

    endCol := selectCol.
    endCol == 0 ifTrue:[endCol := 1].
    thisCharacter := self characterAtLine:selectLine col:endCol.

    "is this acharacter within a word ?"
    (wordCheck value:thisCharacter) ifTrue:[
	thisCharacter := self characterAtLine:selectLine col:endCol.
	[wordCheck value:thisCharacter] whileTrue:[
	    endCol := endCol + 1.
	    thisCharacter := self characterAtLine:selectLine col:endCol
	].
	endCol := endCol - 1.
    ] ifFalse:[
	"nope - maybe its a space"
	thisCharacter == Character space ifTrue:[
	    len := (self listAt:selectLine) size.
	    endCol > len ifTrue:[
		"select rest to end"
		endCol := 0
	    ] ifFalse:[
		thisCharacter := self characterAtLine:selectLine col:endCol.
		[endCol <= len and:[thisCharacter == Character space]] whileTrue:[
		    endCol := endCol + 1.
		    thisCharacter := self characterAtLine:selectLine col:endCol
		].
		endCol := endCol - 1.
	    ]
	] ifFalse:[
	    "select single character"
	]
    ].
    ^ endCol.
!

searchBackwardFor:pattern ignoreCase:ignCase startingAtLine:startLine col:startCol ifFound:block1 ifAbsent:block2
    "search for a pattern, if found evaluate block1 with row/col as arguments, if not
     found evaluate block2.
     Sorry, but pattern is no regular expression pattern (yet)"

    |lineString 
     found firstChar1 firstChar2 c pc
     col         "{ Class: SmallInteger }"
     cc          "{ Class: SmallInteger }"
     patternSize "{ Class: SmallInteger }"
     line1       "{ Class: SmallInteger }"
     lineSize    "{ Class: SmallInteger }" |

    patternSize := pattern size.
    (list notNil 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
            ].
            col > (list at:startLine) size ifTrue:[
                col := -999
            ].
            line1 := startLine.
            line1 to:1 by:-1 do:[:lnr |
                lineString := list at:lnr.
                lineString notNil 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:[
                            ^ block1 value:lnr value:col.
                        ].
                        col := col - 1.
                        [(col > 0) 
                        and:[(c := lineString at:col) ~= firstChar1
                        and:[c ~= firstChar2]]] whileTrue:[
                            col := col - 1
                        ]
                    ]
                ].
                col := -999.
            ]
        ]
    ].
    "not found"

    ^ block2 value

    "Created: 13.9.1997 / 01:06:19 / cg"
    "Modified: 5.10.1997 / 01:53:18 / cg"
!

searchBackwardFor:pattern startingAtLine:startLine col:startCol ifFound:block1 ifAbsent:block2
    "search for a pattern, if found evaluate block1 with row/col as arguments, if not
     found evaluate block2.
     Sorry, but pattern is no regular expression pattern (yet)"

    ^ self
        searchBackwardFor:pattern 
        ignoreCase:false 
        startingAtLine:startLine col:startCol 
        ifFound:block1 
        ifAbsent:block2

    "Modified: 13.9.1997 / 01:07:36 / cg"
!

searchForwardFor:pattern ignoreCase:ignCase startingAtLine:startLine col:startCol ifFound:block1 ifAbsent:block2
    "search for a pattern, if found evaluate block1 with row/col as arguments, if not
     found evaluate block2."

    |lineString col patternSize 
     line1 "{Class: SmallInteger}"
     line2 "{Class: SmallInteger}"
     p realPattern|

    patternSize := pattern size.
    (list notNil and:[patternSize ~~ 0]) ifTrue:[
        self withCursor:Cursor questionMark do:[

            col := startCol + 1.
            line1 := startLine.
            line2 := list size.

            pattern includesUnescapedMatchCharacters ifTrue:[
                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
                ].
                line1 to:line2 do:[:lnr |
                    lineString := list at:lnr.
                    lineString notNil ifTrue:[
                        "/ first a crude check ...
                        (p match:lineString ignoreCase:ignCase) ifTrue:[
                            "/ ok, there it is; look at which position
                            col := lineString 
                                        findMatchString:realPattern 
                                        startingAt:col 
                                        ignoreCase:ignCase 
                                        ifAbsent:0.
                            col ~~ 0 ifTrue:[
                                ^ block1 value:lnr value:col.
                            ]
                        ].
                    ].
                    col := 1
                ]
            ] ifFalse:[
                p := pattern withoutMatchEscapes.
                line1 to:line2 do:[:lnr |
                    lineString := list at:lnr.
                    lineString isString ifTrue:[
                        ignCase ifTrue:[
                            col := lineString 
                                        findMatchString:p 
                                        startingAt:col 
                                        ignoreCase:ignCase 
                                        ifAbsent:0.
                        ] ifFalse:[
                            col := lineString 
                                        findString:p 
                                        startingAt:col 
                                        ifAbsent:0.
                        ].
                        col ~~ 0 ifTrue:[
                            ^ block1 value:lnr value:col.
                        ]
                    ].
                    col := 1
                ]
            ].
        ]
    ].
    "not found"

    ^ block2 value

    "Created: 13.9.1997 / 01:06:31 / cg"
    "Modified: 13.9.1997 / 01:11:28 / cg"
!

searchForwardFor:pattern startingAtLine:startLine col:startCol ifFound:block1 ifAbsent:block2
    "search for a pattern, if found evaluate block1 with row/col as arguments, if not
     found evaluate block2."

    ^ self
        searchForwardFor:pattern 
        ignoreCase:false 
        startingAtLine:startLine col:startCol 
        ifFound:block1 
        ifAbsent:block2

    "Modified: 13.9.1997 / 01:07:11 / cg"
! !

!ListView methodsFor:'tabulators'!

expandTabs
    "go through whole text expanding tabs into spaces.
     This is meant to be called for text being imported from a file. 
     Therefore, 8-col tabs are assumed - independent of any private tab setting."

    |line newLine nLines "{ Class: SmallInteger }"|

    includesNonStrings := false.
    list notNil ifTrue:[
	nLines := self size.
	1 to:nLines do:[:index |
	    line := self at:index.
	    line notNil ifTrue:[
		line isString ifTrue:[
		    newLine := line withTabsExpanded.
		    newLine ~~ line ifTrue:[
			self withoutRedrawAt:index put:newLine
		    ].
		] ifFalse:[
		    includesNonStrings := true.
		]
	    ]
	]
    ]

    "Modified: 30.8.1995 / 19:06:37 / claus"
    "Modified: 12.5.1996 / 12:48:03 / cg"
!

nextTabAfter:colNr
    "return the next tab position after col"

    ^ self nextTabAfter:colNr in:tabPositions
!

nextTabAfter:colNr in:tabPositions
    "return the next tab position after col.
     The second arg, tabPositions is a collection of tabStops."

    |col      "{ Class: SmallInteger }"
     tabIndex "{ Class: SmallInteger }"
     thisTab  "{ Class: SmallInteger }"
     nTabs    "{ Class: SmallInteger }" |

    tabIndex := 1.
    col := colNr.
    thisTab := tabPositions at:tabIndex.
    nTabs := tabPositions size.
    [thisTab <= col] whileTrue:[
	(tabIndex == nTabs) ifTrue:[^ thisTab].
	tabIndex := tabIndex + 1.
	thisTab := tabPositions at:tabIndex
    ].
    ^ thisTab
!

prevTabBefore:colNr
    "return the prev tab position before col"

    |col      "{ Class: SmallInteger }"
     tabIndex "{ Class: SmallInteger }"
     thisTab  "{ Class: SmallInteger }"
     nTabs    "{ Class: SmallInteger }" |

    tabIndex := 1.
    col := colNr.
    thisTab := tabPositions at:tabIndex.
    nTabs := tabPositions size.
    [thisTab < col] whileTrue:[
	(tabIndex == nTabs) ifTrue:[^ thisTab].
	tabIndex := tabIndex + 1.
	thisTab := tabPositions at:tabIndex
    ].
    (tabIndex == 1) ifTrue:[
	^ 1
    ].
    ^ tabPositions at:(tabIndex - 1)
!

setTab4
    "set 4-character tab stops"

    tabPositions := self class tab4Positions.
!

setTab8
    "set 8-character tab stops"

    tabPositions := self class tab8Positions.
!

withTabs:line
    "Assuming an 8-character tab,
     compress multiple leading spaces to tabs, return a new line string
     or the original line, if no tabs where created.
     good idea, to make this one a primitive, since its called
     many times when a big text is saved to a file."

    |newLine eightSpaces nTabs|

    "
     the code below is a hack, producing many garbage strings for lines
     which compress multiple tabs ... needs rewrite: saving big files
     stresses the garbage collector a bit ...
    "
    line isNil ifTrue:[^ line].
    eightSpaces := '        '.
    (line startsWith:eightSpaces) ifFalse:[^ line].

    nTabs := 1.
    newLine := line copyFrom:9.
    [newLine startsWith:eightSpaces] whileTrue:[
	newLine := newLine copyFrom:9.
	nTabs := nTabs + 1.
    ].
    ^ (line species new:nTabs withAll:Character tab) asString , newLine.

    "Modified: 23.2.1996 / 19:10:36 / cg"
!

withTabs:tabulatorTable expand:line
    "expand tabs into spaces, return a new line string,
     or original line, if no tabs are included.
     good idea, to make this one a primitive, since it is called
     many times if a big text is read from a file."

    |tmpString nString nTabs
     currentMax "{ Class: SmallInteger }"
     dstIndex   "{ Class: SmallInteger }"
     nextTab    "{ Class: SmallInteger }" |

    "
     the code below tries to avoid creating too much garbage;
     therefore, the string is scanned first for the number of
     tabs to get a rough idea of the final strings size.
     (it could be done better, by computing the exact size
      required here ...)
    "
    line isNil ifTrue:[^ line].
    nTabs := line occurrencesOf:(Character tab).
    nTabs == 0 ifTrue:[^ line].

    currentMax := line size + (nTabs * 7).
    tmpString := line species new:currentMax.
    dstIndex := 1.
    line do:[:character |
	(character == (Character tab)) ifTrue:[
	    nextTab := self nextTabAfter:dstIndex in:tabulatorTable.
	    [dstIndex < nextTab] whileTrue:[
		tmpString at:dstIndex put:(Character space).
		dstIndex := dstIndex + 1
	    ]
	] ifFalse:[
	    tmpString at:dstIndex put:character.
	    dstIndex := dstIndex + 1
	].
	(dstIndex > currentMax) ifTrue:[
	    "
	     this cannot happen with <= 8 tabs
	    "
	    currentMax := currentMax + currentMax.
	    nString := line species new:currentMax.
	    nString replaceFrom:1 to:(dstIndex - 1) 
			   with:tmpString startingAt:1.
	    tmpString := nString.
	    nString := nil
	].

	"make stc-optimizer happy
	 - no need to return value of ifTrue:/ifFalse above"
	0
    ].
    dstIndex := dstIndex - 1.
    dstIndex == currentMax ifTrue:[
	^ tmpString
    ].
    ^ tmpString copyTo:dstIndex

    "Modified: 23.2.1996 / 19:11:01 / cg"
!

withTabsExpanded:line
    "expand tabs into spaces, return a new line string,
     or original line, if no tabs are included.
     good idea, to make this one a primitive"

    ^ self withTabs:tabPositions expand:line
! !

!ListView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/ListView.st,v 1.150 1998-02-24 15:34:14 cg Exp $'
! !