TextView.st
author claus
Wed, 13 Oct 1993 02:04:14 +0100
changeset 3 9d7eefb5e69f
parent 0 e6a541c1c0eb
child 5 7b4fb1b170e5
permissions -rw-r--r--
(none)

"
 COPYRIGHT (c) 1989-93 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.
"

ListView subclass:#TextView
       instanceVariableNames:'selectionStartLine selectionStartCol
                              selectionEndLine selectionEndCol
                              clickStartLine clickStartCol
                              clickLine clickCol clickCount
                              selectionFgColor selectionBgColor
                              fileBox searchBox lineNumberBox
                              wordSelectStyle
                              directoryForFileDialog
                              contentsWasSaved'
       classVariableNames:'fontPanel'
       poolDictionaries:''
       category:'Views-Text'
!

TextView comment:'

COPYRIGHT (c) 1989-93 by Claus Gittinger
             All Rights Reserved

$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.2 1993-10-13 01:03:50 claus Exp $

written jun-89 by claus
autoscroll added spring 92 by claus
'!

!TextView class methodsFor:'documentation'!

documantation
"
a view for text - this class adds selections to a simple List

Instance variables:

selectionStartLine      <Number>                the line of the selection start (or nil)
selectionStartCol       <Number>                the col of the selection start
selectionEndLine        <Number>                the line of the selection end
selectionEndCol         <Number>                the col of the selection end
clickStartLine          <Number>                temporary
clickStartCol           <Number>                temporary
clickLine               <Number>                temporary
clickCol                <Number>                temporary
clickCount              <Number>                temporary
selectionFgColor        <Color>                 color used to draw selections
selectionBgColor        <Color>                 color used to draw selections
fileBox                 <FileSelectionBox>      box for save
searchBox               <EnterBox2>             box to enter searchpattern
lineNumberBox           <EnterBox>              box to enter linenumber
wordSelectStyle         <Symbol>                how words are selected
"
! !

!TextView class methodsFor:'startup'!

setupEmpty
    "create a textview - a helper for startWith: and startOn:"

    |top frame label|

    label := 'unnamed'.
    top := StandardSystemView label:label
                               icon:(Form fromFile:'Editor.xbm' resolution:100).

    frame := ScrollableView for:self in:top.
    frame origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
    ^ frame scrolledView
!

start
    "start an empty TextView"

    ^ self startWith:nil
!

startWith:aString
    "start a textView with aString as initial contents"

    |top textView|

    textView := self setupEmpty.
    top := textView topView.
    aString notNil ifTrue:[
        textView contents:aString
    ].

    top realize.
    ^ textView

    "TextView startWith:'some text'"
    "EditTextView startWith:'some text'"
!

startOn:aFileName
    "start a textView on a file"

    |top textView|

    textView := self setupEmpty.
    top := textView topView.
    aFileName notNil ifTrue:[
        top label:(OperatingSystem baseNameOf:aFileName).
        textView contents:(aFileName asFilename readStream contents)
    ].

    top realize.
    ^ textView

    "TextView startOn:'../doc/info.doc'"
    "EditTextView startOn:'../doc/info.doc'"
! !

!TextView methodsFor:'initialize & release'!

initialize
    super initialize.
    contentsWasSaved := false
!

initStyle
    super initStyle.

    viewBackground := White.

    "if running on a color display, we hilight by drawing black on green
     (looks like a text-marker) otherwise, we draw reverse"
    device hasColors ifTrue:[
        selectionFgColor := fgColor.
        selectionBgColor := Color red:0 green:100 blue:0
    ] ifFalse:[
        device hasGreyscales ifTrue:[
            selectionFgColor := fgColor.
            selectionBgColor := Color lightGrey 
        ] ifFalse:[
            selectionFgColor := bgColor.
            selectionBgColor := fgColor
        ]
    ]
!

initEvents
    super initEvents.
    self enableButtonEvents.
    self enableButtonMotionEvents
!

realize
    super realize.
    selectionFgColor := selectionFgColor on:device.
    selectionBgColor := selectionBgColor on:device.
!

initializeMiddleButtonMenu
    |labels|

    labels := resources array:#(
                                       'copy'
                                       '-'
                                       'font'
                                       '-'
                                       'search'
                                       'goto'
                                       '-'
                                       'save'
                                       'print').

    self middleButtonMenu:(PopUpMenu
                                labels:labels
                             selectors:#(copySelection
                                         nil
                                         changeFont
                                         nil
                                         search
                                         gotoLine
                                         nil
                                         save
                                         print)
                                receiver:self
                                     for:self).

    self enableOrDisableSelectionMenuEntries
!

destroy
    fileBox notNil ifTrue:[
        fileBox destroy.
        fileBox := nil
    ].
    searchBox notNil ifTrue:[
        searchBox destroy.
        searchBox := nil
    ].
    lineNumberBox notNil ifTrue:[
        lineNumberBox destroy.
        lineNumberBox := nil
    ].
    super destroy
! !

!TextView methodsFor:'accessing'!

selectionForegroundColor:color1 backgroundColor:color2
    "set both selection-foreground and cursor background colors"

    selectionFgColor := color1 on:device.
    selectionBgColor := color2 on:device.
    shown ifTrue:[
        self redraw
    ]
!

setList:something
    "set the displayed contents (a collection of strings)
     without redraw.
     Redefined since changing contents implies deselect"

    self unselect.
    super setList:something
!

list:something
    "set the displayed contents (a collection of strings)
     with redraw.
     Redefined since changing contents implies deselect"

    self unselect.
    super list:something
!

characterAtLine:lineNr col:colNr
    "return the character at physical line/col -
     return space if nothing is there"

    |line|

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

characterPositionOfSelection
    "return the character index of the first character in the selection"

    selectionStartLine isNil ifTrue:[^ 1].
    ^ self characterPositionOfLine:selectionStartLine
                               col:selectionStartCol
!

directoryForFileDialog:aDirectory
    "define the directory to use for save-box"

    directoryForFileDialog := aDirectory
!

contentsWasSaved
    "return true, if the contents was saved (by a save action),
     false if not (or was modified again after the last save)."

    ^ contentsWasSaved
!

fromFile:aFileName
    "take contents from a named file"

    self directoryForFileDialog:(OperatingSystem directoryNameOf:aFileName).
    self contents:(FileStream oldFileNamed:aFileName) contents
! !

!TextView methodsFor:'private'!

fileOutContentsOn:aStream
    "save contents on a stream"

    list do:[:aLine |
        aLine notNil ifTrue:[
            aStream nextPutAll:aLine
        ].
        aStream cr
    ]
!

widthForScrollBetween:firstLine and:lastLine
    "return the width in pixels for a scroll between firstLine and lastLine"

    selectionStartLine notNil ifTrue:[
        (lastLine < selectionStartLine) ifFalse:[
            (firstLine > selectionEndLine) ifFalse:[
                ^ width
            ]
        ]
    ].
    ^ super widthForScrollBetween:firstLine and:lastLine
!

scrollSelectUp
    "auto scroll action; scroll and reinstall timed-block"

    device addTimedBlock:autoScrollBlock after:autoScrollDeltaT.
    self scrollUp
!

scrollSelectDown
    "auto scroll action; scroll and reinstall timed-block"

    device addTimedBlock:autoScrollBlock after:autoScrollDeltaT.
    self scrollDown
!

stopScrollSelect
    "stop auto scroll; deinstall timed-block"

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

!TextView methodsFor:'menu actions'!

print
    "print the contents on the printer"

    |printStream|

    list isNil ifTrue:[^ self].
    printStream := Printer new.
    printStream notNil ifTrue:[
        self fileOutContentsOn:printStream.
        printStream close
    ]
!

saveAs:fileName
    "save contents into a file named fileName"
 
    |aStream msg|

    aStream := FileStream newFileNamed:fileName.
    aStream isNil ifTrue:[
	msg := resources string:'cannot write file %1 !!' with:fileName.
	self warn:(msg , '\\(' , OperatingSystem lastErrorString , ')' ) withCRs
    ] ifFalse:[
        self fileOutContentsOn:aStream.
        aStream close.
        contentsWasSaved := true
    ]
!

save
    "save contents into a file 
     - ask user for filename using a fileSelectionBox."

    fileBox isNil ifTrue:[
        fileBox := FileSelectionBox
                        title:(resources string:'save contents in:')
                        okText:(resources string:'save')
                        abortText:(resources string:'cancel')
                        action:[:fileName | self saveAs:fileName]
    ].
    directoryForFileDialog notNil ifTrue:[
        fileBox directory:directoryForFileDialog
    ].
    fileBox showAtPointer
!

copySelection
    "copy contents into smalltalk copybuffer"

    |text|

    text := self selection.
    text notNil ifTrue:[
        Smalltalk at:#CopyBuffer put:text.
        self unselect
    ]
!

changeFont
    "pop up a fontPanel to change font"

    fontPanel isNil ifTrue:[
        fontPanel := FontPanel new
    ].
    fontPanel action:[:family :face :style :size |
        self font:(Font family:family
                          face:face
                         style:style
                          size:size)
    ].
    fontPanel initialFont:font.
    fontPanel showAtPointer
!

gotoLine
    "show a box to enter lineNumber for positioning"

    lineNumberBox isNil ifTrue:[
        lineNumberBox :=
            EnterBox
               title:(resources string:'line number:')
              okText:(resources string:'goto')
           abortText:(resources string:'cancel')
              action:[:l | self gotoLine:(Number readFromString:l)]
    ].
    lineNumberBox showAtPointer
! !

!TextView methodsFor:'selections'!

enableOrDisableSelectionMenuEntries
    "sent internally, whenever selection status changes to
     update menu entries"

    selectionStartLine isNil ifTrue:[
        self disableSelectionMenuEntries
    ] ifFalse:[
        self enableSelectionMenuEntries
    ]
!

disableSelectionMenuEntries
    "disable relevant menu entries when no selection is
     available - redefined in subclasses to disable more,
     but do NOT forget a super disableSelectionMenuEntries there."

    middleButtonMenu notNil ifTrue:[
        middleButtonMenu disable:#copySelection
    ]
!

enableSelectionMenuEntries
    "disable relevant menu entries when a selection is
     available - redefined in subclasses to enable more,
     but do NOT forget a super enableSelectionMenuEntries there."

    middleButtonMenu notNil ifTrue:[
        middleButtonMenu enable:#copySelection
    ]
!

unselectWithoutRedraw
    "forget selection but do not redraw the selection area
     - can be done when selected area is redrawn anyway or
     known to be invisible."

    selectionStartLine := nil.
    self disableSelectionMenuEntries
!

unselect
    "unselect - if there was a selection redraw"

    |startLine endLine startVisLine endVisLine|

    selectionStartLine notNil ifTrue:[
        startLine := selectionStartLine.
        endLine := selectionEndLine.
        selectionStartLine := nil.

        "if selection is not visible, we are done"
        startLine >= (firstLineShown + nLinesShown) ifTrue:[^ self].
        endLine < firstLineShown ifTrue:[^ self].

        startLine < firstLineShown ifTrue:[
            startVisLine := 1
        ] ifFalse:[
            startVisLine := self listLineToVisibleLine:startLine
        ].
        endLine >= (firstLineShown + nLinesShown) ifTrue:[
            endVisLine := nLinesShown
        ] ifFalse:[
            endVisLine := self listLineToVisibleLine:endLine
        ].
        "if its only part of a line, just redraw what has to be"
        (startVisLine == endVisLine) ifTrue:[
            super redrawVisibleLine:startVisLine from:selectionStartCol to:selectionEndCol
        ] ifFalse:[
            super redrawFromVisibleLine:startVisLine to:endVisLine
        ].
        self unselectWithoutRedraw
    ].
    wordSelectStyle := nil
!

selectFromLine:startLine col:startCol toLine:endLine col:endCol
    "select a piece of text"

    self unselect.
    startLine notNil ifTrue:[
        selectionStartLine := startLine.
        selectionStartCol := startCol.
        selectionEndLine := endLine.
        selectionEndCol := endCol.
        (startLine == endLine) ifTrue:[
            self redrawLine:startLine from:startCol to:endCol
        ] ifFalse:[
            startLine to:endLine do:[:lineNr |
                self redrawLine:lineNr
            ]
        ].
        wordSelectStyle := nil.
        self enableSelectionMenuEntries
    ]
!

selectLine:selectLine
    "select one line"

    self selectFromLine:selectLine col:1 toLine:(selectLine + 1) col:0
!

selectLineWhereCharacterPosition:pos
    "select the line, where characterPosition pos is living.
     The argument pos starts at 1 from the start of the text."

    self selectLine:(self lineOfCharacterPosition:pos)
!

selectFromCharacterPosition:pos1 to:pos2
    "compute line/col from character positions and select the text"

    |line1 col1 line2 col2|

    line1 := self lineOfCharacterPosition:pos1.
    col1 := pos1 - (self characterPositionOfLine:line1 col:1) + 1.
    line2 := self lineOfCharacterPosition:pos2.
    col2 := pos2 - (self characterPositionOfLine:line2 col:1) + 1.
    self selectFromLine:line1 col:col1 toLine:line2 col:col2
!

selectWordAtLine:selectLine col:selectCol
    "select the word at given line/col"

    |beginCol endCol thisCharacter flag|

    flag := nil.
    beginCol := selectCol.
    endCol := selectCol.
    thisCharacter := self characterAtLine:selectLine col:beginCol.
    thisCharacter isAlphaNumeric ifTrue:[
        [thisCharacter isAlphaNumeric] whileTrue:[
            beginCol := beginCol - 1.
            beginCol < 1 ifTrue:[
                thisCharacter := Character space
            ] ifFalse:[
                thisCharacter := self characterAtLine:selectLine col:beginCol
            ]
        ].
        beginCol := beginCol + 1.
        thisCharacter := self characterAtLine:selectLine col:endCol.
        [thisCharacter isAlphaNumeric] whileTrue:[
            endCol := endCol + 1.
            thisCharacter := self characterAtLine:selectLine col:endCol
        ].
        endCol := endCol - 1.

        "now, we have the word at beginCol..endCol try to catch a blank ..."
        ((beginCol == 1)
        or:[(self characterAtLine:selectLine col:(beginCol - 1))
             ~~ Character space]) ifTrue:[
            ((self characterAtLine:selectLine col:(endCol + 1))
              == Character space) ifTrue:[
                endCol := endCol + 1.
                flag := #right
            ]
        ] ifFalse:[
            beginCol := beginCol - 1.
            flag := #left
        ]
    ].
    self selectFromLine:selectLine col:beginCol toLine:selectLine col:endCol.
    wordSelectStyle := flag
!

selectWordAtX:x y:y
    "select the word at given x/y-(view-)coordinate"

    |selectVisibleLine selectLine selectCol|

    wordSelectStyle := nil.
    selectVisibleLine := self visibleLineOfY:y.
    selectLine := self visibleLineToListLine:selectVisibleLine.
    selectLine notNil ifTrue:[
        selectCol := self colOfX:x inVisibleLine:selectLine.
        self selectWordAtLine:selectLine col:selectCol
    ]
!

selectLineAtY:y
    "select the line at given y-(view-)coordinate"

    |selectVisibleLine selectLine|

    selectVisibleLine := self visibleLineOfY:y.
    selectLine := self visibleLineToListLine:selectVisibleLine.
    selectLine notNil ifTrue:[
        self selectLine:selectLine
    ]
!

selectAll
    "select the whole text"

    self selectFromLine:1 col:1 toLine:(list size + 1) col:0
!

selection
    "return the selection as a Text-Collection"

    |text sz index|

    selectionStartLine isNil ifTrue:[^ nil].
    (selectionStartLine == selectionEndLine) ifTrue:[
        "part of a line"
        ^ Text with:(self listAt:selectionStartLine
                            from:selectionStartCol
                              to:selectionEndCol)
    ].
    sz := selectionEndLine - selectionStartLine + 1.
    text := Text new:sz.

    "get 1st and last (possibly) partial lines"
    text at:1 put:(self listAt:selectionStartLine from:selectionStartCol).
    text at:sz put:(self listAt:selectionEndLine to:selectionEndCol).

    "get bulk of text"
    index := 2.
    (selectionStartLine + 1) to:(selectionEndLine - 1) do:[:lineNr |
        text at:index put:(self listAt:lineNr).
        index := index + 1
    ].
    ^ text
!

makeSelectionVisible
    "scroll to make selection visible"

    selectionStartLine notNil ifTrue:[
        self makeLineVisible:selectionStartLine
    ]
! !

!TextView methodsFor:'searching'!

search
    "show a box to enter searchpattern 
     - currently no regular expressions are handled."

    searchBox isNil ifTrue:[
        searchBox :=
            EnterBox2
               title:(resources at:'searchPattern:')
             okText1:(resources at:'prev')
             okText2:(resources at:'next')
           abortText:(resources at:'cancel')
             action1:[:pattern | self searchBwd:(pattern withoutSeparators)]
             action2:[:pattern | self searchFwd:(pattern withoutSeparators)]
    ].
    searchPattern notNil ifTrue:[
        searchBox initialText:searchPattern
    ].
    searchBox showAtPointer
!

setSearchPattern
    "set the searchpattern from the selection if there is one"

    |sel|

    sel := self selection.
    sel notNil ifTrue:[
        searchPattern := sel asString withoutSeparators
    ]
!

showNotFound
    "search not found - tell user by beeping and changing
     cursor for a while (sometimes I work with a headset :-)
     (used to be: tell user by changing cursor for a while)"

    |savedCursor|

    device beep.
"
    uncomment if you want a CROSS cursor to be shown for a while ..
"

" "
    savedCursor := cursor.
    self cursor:(Cursor cross).
    OperatingSystem millisecondDelay:300.
    self cursor:savedCursor
" "
!

searchFwd
    "search forward for pattern or selection"

    self setSearchPattern.
    searchPattern notNil ifTrue:[
        self searchFwd:searchPattern
    ]
!

searchBwd
    "search backward and -if found- position cursor"

    self setSearchPattern.
    searchPattern notNil ifTrue:[
        self searchBwd:searchPattern
    ]
!

searchFwd:pattern
    "do the forward search"

    |startLine startCol|

    selectionStartLine notNil ifTrue:[
        startLine := selectionStartLine.
        startCol := selectionStartCol
    ] ifFalse:[
        startLine := 1.
        startCol := 1
    ].
    self searchForwardFor:pattern startingAtLine:startLine col:startCol
    ifFound:[:line :col |
        self selectFromLine:line col:col
                     toLine:line col:(col + pattern size - 1).
        self makeLineVisible:line
    ] else:[
        self showNotFound
    ]
!

searchBwd:pattern
    "do the backward search"

    |startLine startCol|

    selectionStartLine notNil ifTrue:[
        startLine := selectionStartLine.
        startCol := selectionStartCol
    ] ifFalse:[
        startLine := 1.
        startCol := 1
    ].
    self searchBackwardFor:pattern startingAtLine:startLine col:startCol
    ifFound:[:line :col |
        self selectFromLine:line col:col
                     toLine:line col:(col + pattern size - 1).
        self makeLineVisible:line
    ] else:[
        self showNotFound
    ]
! !

!TextView methodsFor:'redrawing'!

clearMarginOfVisible:visLine with:color
    "if there is a margin, clear it - a helper for selection drawing"

    (leftMargin ~~ 0) ifTrue:[
        self paint:color.
        self fillRectangleX:margin
                          y:(self yOfLine:visLine)
                      width:leftMargin
                     height:fontHeight
    ]
!

redrawVisibleLine:visLine col:col
    "redraw single character at col in visible line lineNr"

    |line|

    line := self visibleLineToAbsoluteLine:visLine.
    selectionStartLine notNil ifTrue:[
        (line between:selectionStartLine and:selectionEndLine) ifTrue:[
            ((line == selectionStartLine)
            and: [col < selectionStartCol]) ifFalse:[
                ((line == selectionEndLine)
                and: [col > selectionEndCol]) ifFalse:[
                    "its in the selection"
                    self drawVisibleLine:visLine col:col with:selectionFgColor
                                                          and:selectionBgColor.
                    ^ self
                ]
            ]
        ]
    ].
    super redrawVisibleLine:visLine col:col
!

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

    |startLine endLine specialCare end selVisStart line1 line2|

    shown ifFalse:[^ self].

    end := endVisLineNr.
    (end > nLinesShown) ifTrue:[
        end := nLinesShown
    ].

    selectionStartLine isNil ifTrue:[
        specialCare := false
    ] ifFalse:[
        startLine := self visibleLineToAbsoluteLine:startVisLineNr.
        (startLine > selectionEndLine) ifTrue:[
            specialCare := false
        ] ifFalse:[
            endLine := self visibleLineToAbsoluteLine:end.
            (endLine < selectionStartLine) ifTrue:[
                specialCare := false
            ] ifFalse:[
                specialCare := true
            ]
        ]
    ].

    "easy: nothing is selected"
    specialCare ifFalse:[
      ^ super redrawFromVisibleLine:startVisLineNr to:end
    ].

    "easy: all is selected"
    ((selectionStartLine < startLine) and:[selectionEndLine > endLine]) ifTrue:[
        ^ self drawFromVisibleLine:startVisLineNr to:end with:selectionFgColor
                                                          and:selectionBgColor
    ].

    (selectionStartLine >= firstLineShown) ifTrue:[
        "draw unselected top part"

        selVisStart := self listLineToVisibleLine:selectionStartLine.
        super redrawFromVisibleLine:startVisLineNr to:(selVisStart - 1).

        "and first partial selected line"
        self redrawVisibleLine:selVisStart.

        "rest starts after this one"
        line1 := selVisStart + 1
    ] ifFalse:[
        line1 := 1
    ].

    (line1 > end) ifTrue:[^ self].
    (line1 < startVisLineNr) ifTrue:[
        line1 := startVisLineNr
    ].

    "draw middle part of selection"

    (selectionEndLine >= (firstLineShown + nLinesShown)) ifTrue:[
        line2 := nLinesShown
    ] ifFalse:[
        line2 := (self listLineToVisibleLine:selectionEndLine) - 1
    ].
    (line2 > end) ifTrue:[
        line2 := end
    ].

    self drawFromVisibleLine:line1 to:line2 with:selectionFgColor
                                             and:selectionBgColor.

    (line2 >= end) ifTrue:[^ self].

    "last line of selection"
    self redrawVisibleLine:(line2 + 1).

    ((line2 + 2) <= end) ifTrue:[
        super redrawFromVisibleLine:(line2 + 2) to:end
    ]
!

redrawVisibleLine:visLine
    "redraw visible line lineNr"

    |len line l|

    selectionStartLine notNil ifTrue:[
        line := self visibleLineToAbsoluteLine:visLine.
        (line between:selectionStartLine and:selectionEndLine) ifTrue:[
            (line == selectionStartLine) ifTrue:[
                (line == selectionEndLine) ifTrue:[
                    "its part-of-single-line selection"
                    self clearMarginOfVisible:visLine with:bgColor.
                    (selectionStartCol > 1) ifTrue:[
                        super redrawVisibleLine:visLine
                                           from:1
                                             to:(selectionStartCol - 1)
                    ].
                    self drawVisibleLine:visLine from:selectionStartCol
                                                   to:selectionEndCol
                                                 with:selectionFgColor
                                                  and:selectionBgColor.
                    ^ super redrawVisibleLine:visLine
                                         from:(selectionEndCol + 1)
                ].

                "its the first line of a multi-line selection"
                (selectionStartCol ~~ 1) ifTrue:[
                    self clearMarginOfVisible:visLine with:bgColor.
                    super redrawVisibleLine:visLine
                                       from:1
                                         to:(selectionStartCol - 1)
                ].
                ^ self drawVisibleLine:visLine from:selectionStartCol
                                  with:selectionFgColor and:selectionBgColor
            ].

            (line == selectionEndLine) ifTrue:[
                "its the last line of a multi-line selection"
                (selectionEndCol == 0) ifTrue:[
                    ^ super redrawVisibleLine:visLine
                ].
                l := self visibleAt:selectionEndLine.
                l isNil ifTrue:[
                    len := 0
                ] ifFalse:[
                    len := l size
                ].

                self clearMarginOfVisible:visLine with:selectionBgColor.
                self drawVisibleLine:visLine from:1 to:selectionEndCol
                                with:selectionFgColor and:selectionBgColor.
                (selectionEndCol ~~ len) ifTrue:[
                    super redrawVisibleLine:visLine
                                       from:(selectionEndCol + 1)
                ].
                ^ self
            ].

            "its a full line in a multi-line selection"
            self clearMarginOfVisible:visLine with:selectionBgColor.
            ^ self drawVisibleLine:visLine with:selectionFgColor
                                            and:selectionBgColor
        ]
    ].
    ^ super redrawVisibleLine:visLine
!

redrawVisibleLine:visLine from:startCol
    "redraw visible line lineNr from startCol to end of line"

    |line|

    line := self visibleLineToAbsoluteLine:visLine.
    selectionStartLine notNil ifTrue:[
        (line between:selectionStartLine and:selectionEndLine) ifTrue:[
            ((line == selectionStartLine) 
             or:[line == selectionEndLine]) ifTrue:[
                "since I'm lazy, redraw full line"
                ^ self redrawVisibleLine:visLine
            ].
            "the line is fully within the selection"
            ^ self drawVisibleLine:visLine from:startCol with:selectionFgColor
                                                          and:selectionBgColor
        ]
    ].
    super redrawVisibleLine:visLine from:startCol
!

redrawVisibleLine:visLine from:startCol to:endCol
    "redraw visible line lineNr from startCol to endCol"

    |line allOut allIn leftCol rightCol|

    line := self visibleLineToAbsoluteLine:visLine.

    allIn := false.
    allOut := false.
    selectionStartLine isNil ifTrue:[
        allOut := true
    ] ifFalse:[
        (line between:selectionStartLine and:selectionEndLine) ifFalse:[
            allOut := true
        ] ifTrue:[
            (selectionStartLine == selectionEndLine) ifTrue:[
                ((endCol < selectionStartCol) 
                or:[startCol > selectionEndCol]) ifTrue:[
                    allOut := true
                ] ifFalse:[
                    ((startCol >= selectionStartCol) 
                    and:[endCol <= selectionEndCol]) ifTrue:[
                        allIn := true
                    ]
                ]
            ] ifFalse:[
                (line == selectionStartLine) ifTrue:[
                    (endCol < selectionStartCol) ifTrue:[
                        allOut := true
                    ] ifFalse:[
                        (startCol >= selectionStartCol) ifTrue:[
                            allIn := true
                        ]
                    ]
                ] ifFalse:[
                    (line == selectionEndLine) ifTrue:[
                        (startCol > selectionEndCol) ifTrue:[
                            allOut := true
                        ] ifFalse:[
                            (endCol <= selectionEndCol) ifTrue:[
                                allIn := true
                            ]
                        ]
                    ] ifFalse:[
                        allIn := true
                    ]
                ]
            ]
        ]
    ].
    allOut ifTrue:[
        ^ super redrawVisibleLine:visLine from:startCol to:endCol
    ].

    allIn ifTrue:[
        self drawVisibleLine:visLine from:startCol to:endCol
                        with:selectionFgColor and:selectionBgColor
    ] ifFalse:[
        "redraw part before selection"
        ((line == selectionStartLine)
         and:[startCol <= selectionStartCol]) ifTrue:[
            super redrawVisibleLine:visLine from:startCol
                                              to:(selectionStartCol - 1).
            leftCol := selectionStartCol
        ] ifFalse:[
            leftCol := startCol
        ].
        "redraw selected part"
        (selectionEndLine > line) ifTrue:[
            rightCol := endCol
        ] ifFalse:[
            rightCol := selectionEndCol min:endCol
        ].
        self drawVisibleLine:visLine from:leftCol to:rightCol
                        with:selectionFgColor and:selectionBgColor.

        "redraw part after selection"
        (rightCol < endCol) ifTrue:[
            super redrawVisibleLine:visLine from:(rightCol + 1) to:endCol
        ]
    ].

    "special care for first and last line of selection:
     must handle margin also"

    ((line == selectionEndLine)
    and:[(startCol == 1)
    and:[selectionStartLine < selectionEndLine]])
    ifTrue:[
        self clearMarginOfVisible:visLine with:selectionBgColor.
    ].

    ((line == selectionStartLine)
    and:[(startCol == 1)
    and:[selectionStartLine < selectionEndLine]])
    ifTrue:[
        self clearMarginOfVisible:visLine with:bgColor.
    ]
! !

!TextView methodsFor:'event processing'!

keyPress:key x:x y:y
    "handle some keyboard input (there is not much to be done here)"

    (key == #Find) ifTrue:[self search. ^self].
    (key == #Copy) ifTrue:[self copySelection. ^self].

    (key == #FindNext) ifTrue:[self searchFwd. ^self].
    (key == #FindPrev) ifTrue:[self searchBwd. ^self].

    (key == #SelectAll) ifTrue:[self selectAll. ^self].

    super keyPress:key x:x y:y
!

buttonPress:button x:x y:y
    "mouse-click - prepare for selection change"

    |clickVisibleLine|

    (button == 1) ifTrue:[
        clickVisibleLine := self visibleLineOfY:y.
        clickCol := self colOfX:x inVisibleLine:clickVisibleLine.
        clickLine := self visibleLineToAbsoluteLine:clickVisibleLine.
        clickStartLine := clickLine.
        clickStartCol := clickCol.
        self unselect.
        clickCount := 1
    ] ifFalse:[
        super buttonPress:button x:x y:y
    ]
!

buttonShiftPress:button x:x y:y
    "mouse-click with shift - adding to selection"

    "very simple - just simulate a move"
    ^ self buttonMotion:button x:x y:y
!

buttonMultiPress:button x:x y:y
    "multi-mouse-click - select word under pointer"

    (button == 1) ifTrue:[
        clickCount notNil ifTrue:[
            clickCount := clickCount + 1.
            (clickCount == 2) ifTrue:[
                self selectWordAtX:x y:y
            ] ifFalse:[
                (clickCount == 3) ifTrue:[
                    self selectLineAtY:y
                ] ifFalse:[
                    (clickCount == 4) ifTrue:[
                        self selectAll
                    ]
                ]
            ]
        ]
    ] ifFalse:[
        super buttonMultiPress:button x:x y:y
    ]
!

buttonMotion:button x:x y:y
    "mouse-move while button was pressed - handle selection changes"

    |movedVisibleLine movedLine movedCol 
     movedUp 
     oldStartLine oldEndLine oldStartCol oldEndCol|

    clickLine isNil ifTrue:[^ self].

    "if moved outside of view, start autoscroll"
    (y < 0) ifTrue:[
        device compressMotionEvents:false.
        self startScrollUp:y.
        ^ self
    ].
    (y > height) ifTrue:[
        device compressMotionEvents:false.
        self startScrollDown:(y - height).
        ^ self
    ].

    "move inside - stop autoscroll if any"
    autoScrollBlock notNil ifTrue:[
        self stopScrollSelect
    ].

    movedVisibleLine := self visibleLineOfY:y.
    movedLine := self visibleLineToAbsoluteLine:movedVisibleLine.
    (x < leftMargin) ifTrue:[
        movedCol := 0
    ] ifFalse:[
        movedCol := self colOfX:x inVisibleLine:movedVisibleLine
    ].
    ((movedLine == clickLine) and:[movedCol == clickCol]) ifTrue:[^ self].

    selectionStartLine isNil ifTrue:[
        selectionStartLine := clickLine.
        selectionStartCol := clickCol.
        selectionEndLine := selectionStartLine.
        selectionEndCol := selectionStartCol
    ].
    oldStartLine := selectionStartLine.
    oldEndLine := selectionEndLine.
    oldStartCol := selectionStartCol.
    oldEndCol := selectionEndCol.


    "find out if we are before or after initial click"
    movedUp := false.
    (movedLine < clickStartLine) ifTrue:[
        movedUp := true
    ] ifFalse:[
        (movedLine == clickStartLine) ifTrue:[
            (movedCol < clickStartCol) ifTrue:[
                movedUp := true
            ]
        ]
    ].

    movedUp ifTrue:[
        "change selectionStart"
        selectionStartCol := movedCol.
        selectionStartLine := movedLine.
        selectionEndCol := clickStartCol.
        selectionEndLine := clickStartLine
    ] ifFalse:[
        "change selectionEnd"
        selectionEndCol := movedCol.
        selectionEndLine := movedLine.
        selectionStartCol := clickStartCol.
        selectionStartLine := clickStartLine
    ].

    (selectionStartCol == 0) ifTrue:[
        selectionStartCol := 1
    ].

    (oldStartLine == selectionStartLine) ifTrue:[
        (oldStartCol ~~ selectionStartCol) ifTrue:[
            self redrawLine:oldStartLine 
                       from:((selectionStartCol min:oldStartCol) max:1)
                         to:((selectionStartCol max:oldStartCol) max:1)
        ]
    ] ifFalse:[
        self redrawFromLine:(oldStartLine min:selectionStartLine)
                         to:(oldStartLine max:selectionStartLine)
    ].

    (oldEndLine == selectionEndLine) ifTrue:[
        (oldEndCol ~~ selectionEndCol) ifTrue:[
            self redrawLine:oldEndLine 
                       from:((selectionEndCol min:oldEndCol) max:1)
                         to:((selectionEndCol max:oldEndCol) max:1)
        ]
    ] ifFalse:[
        self redrawFromLine:(oldEndLine min:selectionEndLine)
                         to:(oldEndLine max:selectionEndLine)
    ].
    clickLine := movedLine.
    clickCol := movedCol
!

buttonRelease:button x:x y:y
    "mouse- button release - turn off autoScroll if any"

    (button == 1) ifTrue:[
        autoScrollBlock notNil ifTrue:[
            self stopScrollSelect
        ].
        selectionStartLine notNil ifTrue:[
            middleButtonMenu enable:#cut.
            middleButtonMenu enable:#copySelection.
            middleButtonMenu enable:#replace.
            middleButtonMenu enable:#indent.
            middleButtonMenu enable:#explain.
            middleButtonMenu enable:#doIt.
            middleButtonMenu enable:#printIt.
            middleButtonMenu enable:#inspectIt
        ]
    ] ifFalse:[
        super buttonRelease:button x:x y:y
    ]
! !