TextView.st
author Claus Gittinger <cg@exept.de>
Wed, 05 Mar 1997 17:32:19 +0100
changeset 1100 2256f369ee96
parent 1055 63810926b20a
child 1109 83d8c0143ef9
permissions -rw-r--r--
checkin from browser

"
 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.
"

ListView subclass:#TextView
	instanceVariableNames:'selectionStartLine selectionStartCol selectionEndLine
		selectionEndCol clickStartLine clickStartCol clickLine clickCol
		clickCount expandingTop wordStartCol wordStartLine wordEndCol
		wordEndLine selectionFgColor selectionBgColor selectStyle
		directoryForFileDialog defaultFileNameForFileDialog
		contentsWasSaved'
	classVariableNames:'DefaultViewBackground DefaultSelectionForegroundColor
		DefaultSelectionBackgroundColor MatchDelayTime
		WordSelectCatchesBlanks'
	poolDictionaries:''
	category:'Views-Text'
!

!TextView 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 readOnly text - this class adds selections to a simple list.
    The text is not editable and there is no cursor.
    Use TextViews for readonly text, EditTextView for editable text.

    Please read the historic notice in the ListView class.

    [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 - remember where select operation started
      clickStartCol           <Number>                temporary
      clickLine               <Number>                temporary
      clickCol                <Number>                temporary
      clickCount              <Number>                temporary
      expandingTop            <Boolean>               temporary - for expandSelection

      selectionFgColor        <Color>                 color used to draw selections
      selectionBgColor        <Color>                 color used to draw selections

      selectStyle             <Symbol>                how words are selected

      directoryForFileDialog  <nil|pathName>          directory where save dialog should start

      contentsWasSaved        <Boolean>               set to true, whenever saved in a file


    [StyleSheet parameters:]

      textViewBackground                 defaults to viewBackground
      textSelectionForegroundColor       defaults to textBackgroundColor
      textSelectionBackgroundColor       defaults to textForegroundColor
      textViewFont                       defaults to textFont


    [author:]
        Claus Gittinger

    [see also:]
        EditTextView CodeView Workspace
"
!

examples
"
    although textViews (and instances of subclasses) are mostly used
    as components (in the fileBrowser, the browser, the launcher etc.),
    they may also be opened as a textEditor;

    open a (readonly) textView on some information text:
                                                        [exBegin]
        TextView 
            openWith:'read this' 
            title:'demonstration'
                                                        [exEnd]

    the same, but open it modal:
                                                        [exBegin]
        TextView 
            openModalWith:'read this first' 
            title:'demonstration'
                                                        [exEnd]


    open it modal (but editable) on some text:
    (must accept before closing)
    This is somewhat kludgy - when closed, the view has already
    nilled its link to the model. Therefore, the accept must be
    done 'manually' below.
    However, usually an applicationModel is installed as the
    editor-topViews application. This would get a closeRequest,
    where it could handle things.
                                                        [exBegin]
        |m textView|

        m := 'read this first' asValue.
        textView := EditTextView openModalOnModel:m.
        textView modified ifTrue:[
            (self confirm:'text was not accepted - do it now ?')
            ifTrue:[
                m value:textView contents
            ]
        ].

        Transcript showCR:m value.
                                                        [exEnd]


    open a textEditor on some file:
                                                        [exBegin]
        EditTextView openOn:'Makefile'
                                                        [exEnd]

"

! !

!TextView class methodsFor:'instance creation'!

on:aModel aspect:aspect change:change menu:menu initialSelection:initial
    "for ST-80 compatibility"

    ^ (self new) 
	on:aModel 
	aspect:aspect
	list:aspect
	change:change 
	menu:menu
	initialSelection:initial
! !

!TextView class methodsFor:'defaults'!

defaultIcon
    "return the icon if started as a topView"

    ^ Image fromFile:'bitmaps/Editor.xbm' resolution:100

    "Created: 1.1.1970 / 14:12:18 / cg"
!

defaultMenuMessage
    "This message is the default yo be sent to the menuHolder to get a menu"

    ^ #editMenu

    "Created: 3.1.1997 / 01:52:21 / stefan"
!

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

    <resource: #style (#textViewBackground
                       #textSelectionForegroundColor #textSelectionBackgroundColor
                       #textViewFont #textWordSelectCatchesBlanks)>

    DefaultViewBackground := StyleSheet colorAt:'textViewBackground' default:White.
    DefaultSelectionForegroundColor := StyleSheet colorAt:'textSelectionForegroundColor'.
    DefaultSelectionBackgroundColor := StyleSheet colorAt:'textSelectionBackgroundColor'.
    DefaultFont := StyleSheet fontAt:'textViewFont'.
    MatchDelayTime := 0.6.
    WordSelectCatchesBlanks := StyleSheet at:'textWordSelectCatchesBlanks' default:false.

    "Modified: 18.3.1996 / 17:32:07 / cg"
! !

!TextView class methodsFor:'startup'!

open
    "start an empty TextView"

    ^ self openWith:nil
!

openModalOnModel:aModel
    "start a textView on a model; return the textView"

    |textView|

    textView := self setupForModel:aModel.
    textView topView openModal.
    ^ textView

    "Created: 14.2.1997 / 15:24:12 / cg"
!

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

    ^ self openModalWith:aString title:nil 

    "
     TextView openModalWith:'some text'
     EditTextView openModalWith:'some text'
    "

    "Created: 14.2.1997 / 15:19:04 / cg"
!

openModalWith:aString title:aTitle
    "start a textView with aString as initial contents. Return the textView."

    |textView|

    textView := self setupWith:aString title:aTitle.
    textView topView openModal.
    ^ textView

    "
     TextView openModalWith:'some text' title:'testing'
     EditTextView openModalWith:'some text' title:'testing'
    "

    "Modified: 9.9.1996 / 19:32:29 / cg"
    "Created: 14.2.1997 / 15:19:18 / cg"
!

openOn:aFileName
    "start a textView on a file; return the textView"

    |textView|

    textView := self setupForFile:aFileName.
    textView topView open.
    ^ textView

    "
     TextView openOn:'../../doc/overview.doc'
     EditTextView openOn:'../../doc/overview.doc'
    "

    "Modified: 14.2.1997 / 15:21:51 / cg"
!

openOnModel:aModel
    "start a textView on a model; return the textView"

    |textView|

    textView := self setupForModel:aModel.
    textView topView open.
    ^ textView

    "Created: 14.2.1997 / 15:23:36 / cg"
!

openWith:aStringOrStringCollection
    "start a textView with aStringOrStringCollection as initial contents"

    ^ self openWith:aStringOrStringCollection title:nil 

    "
     TextView openWith:'some text'
     EditTextView openWith:'some text'
    "

    "Created: 10.12.1995 / 17:41:32 / cg"
    "Modified: 5.3.1997 / 15:37:19 / cg"
!

openWith:aStringOrStringCollection title:aTitle
    "start a textView with aStringOrStringCollection as initial contents. Return the textView."

    |textView|

    textView := self setupWith:aStringOrStringCollection title:aTitle.
    textView topView open.
    ^ textView

    "
     TextView openWith:'some text' title:'testing'
     EditTextView openWith:'some text' title:'testing'
    "

    "Created: 10.12.1995 / 17:40:02 / cg"
    "Modified: 5.3.1997 / 15:37:26 / cg"
!

setupEmpty
    "create a textview in a topview, with horizontal and
     vertical scrollbars - a helper for #startWith: and #startOn:"

    |top frame label|

    label := 'unnamed'.
    top := StandardSystemView label:label icon:self defaultIcon.

    frame := HVScrollableView 
                for:self 
                miniScrollerH:true miniScrollerV:false
                in:top.
    frame origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
    ^ frame scrolledView

    "Modified: 23.5.1965 / 14:12:32 / cg"
!

setupForFile:aFileName
    "setup a textView on a file; return the textView"

    |top textView stream|

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

    ^ textView

    "Created: 14.2.1997 / 15:21:43 / cg"
!

setupForModel:aModel
    "setup a textView on a model; return the textView"

    |top textView|

    textView := self setupEmpty.
    textView model:aModel.
    top := textView topView.
    ^ textView

    "Created: 14.2.1997 / 15:22:42 / cg"
!

setupWith:aStringOrStringCollection title:aTitle
    "setup a textView with aStringOrStringCollection as initial contents in a topView"

    |top textView|

    textView := self setupEmpty.
    top := textView topView.
    aTitle notNil ifTrue:[top label:aTitle].

    aStringOrStringCollection notNil ifTrue:[
        textView contents:aStringOrStringCollection
    ].

    ^ textView

    "Created: 9.9.1996 / 19:31:22 / cg"
    "Modified: 5.3.1997 / 15:37:37 / cg"
! !

!TextView methodsFor:'accessing'!

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

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

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

    ^ contentsWasSaved
!

defaultFileNameForFileDialog:aBaseName
    "define the default fileName to use for the save-box"

    defaultFileNameForFileDialog := aBaseName

    "Created: 13.2.1997 / 18:29:53 / cg"
!

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

    directoryForFileDialog := aDirectory

    "Modified: 13.2.1997 / 18:30:01 / cg"
! !

!TextView methodsFor:'accessing-contents'!

fromFile:aFileName
    "take contents from a named file"

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

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

    self unselect.
    super list:something

    "Modified: 29.4.1996 / 12:13:24 / cg"
!

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

    self unselect.
    super setList:something
!

wordAtLine:selectLine col:selectCol do:aFiveArgBlock
    "find word boundaries, evaluate the block argument with those.
     A helper for nextWord and selectWord functions."

    |beginCol endCol endLine thisCharacter flag|

    flag := #word.
    beginCol := selectCol.
    endCol := selectCol.
    endLine := selectLine.
    thisCharacter := self characterAtLine:selectLine col:beginCol.

    beginCol := self findBeginOfWordAtLine:selectLine col:selectCol.
    endCol := self findEndOfWordAtLine:selectLine col:selectCol.
    endCol == 0 ifTrue:[
        endLine := selectLine + 1
    ].

    "is the initial acharacter within a word ?"
    (wordCheck value:thisCharacter) ifTrue:[
        "
         try to catch a blank ...
        "

        WordSelectCatchesBlanks ifTrue:[
            ((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 := #wordRight
                ]
            ] ifFalse:[
                beginCol := beginCol - 1.
                flag := #wordLeft
            ].
        ].
    ].
    aFiveArgBlock value:selectLine 
                  value:beginCol 
                  value:endLine 
                  value:endCol
                  value:flag

    "Modified: 18.3.1996 / 17:31:04 / cg"
! !

!TextView methodsFor:'accessing-look'!

selectionForegroundColor:color1 backgroundColor:color2
    "set both the selection-foreground and cursor background colors.
     The default is defined by the styleSheet; 
     typically black-on-green for color displays and white-on-black for b&w displays."

    selectionFgColor := color1 on:device.
    selectionBgColor := color2 on:device.
    shown ifTrue:[
        self hasSelection ifTrue:[
            self invalidate
        ]
    ]

    "Modified: 29.5.1996 / 16:22:15 / cg"
! !

!TextView methodsFor:'accessing-mvc'!

on:aModel aspect:aspectSym list:listSym change:changeSym menu:menuSym initialSelection:initial
    "set all of model, aspect, listMessage, changeSymbol, menySymbol
     and selection. Added for ST-80 compatibility"

    aspectSym notNil ifTrue:[aspectMsg := aspectSym. 
                             listMsg isNil ifTrue:[listMsg := aspectSym]].
    changeSym notNil ifTrue:[changeMsg := changeSym].
    listSym notNil ifTrue:[listMsg := listSym].
    menuSym notNil ifTrue:[menuMsg := menuSym].
"/    initial notNil ifTrue:[initialSelectionMsg := initial].
    self model:aModel.

    "Modified: 15.8.1996 / 12:52:54 / stefan"
    "Modified: 2.1.1997 / 16:11:28 / cg"
! !

!TextView methodsFor:'event processing'!

buttonMotion:buttonMask 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].

    "is it the select or 1-button ?"
    (device buttonMotionMask:buttonMask includesButton:#select) ifFalse:[
	(device buttonMotionMask:buttonMask includesButton:1) ifFalse:[
	    ^ self
	].
    ].

    "if moved outside of view, start autoscroll"
    (y < 0) ifTrue:[
	self compressMotionEvents:false.
	self startAutoScrollUp:y.
	^ self
    ].
    (y > height) ifTrue:[
	self compressMotionEvents:false.
	self startAutoScrollDown:(y - height).
	^ self
    ].
    ((x < 0) and:[leftOffset ~~ 0]) ifTrue:[
	self compressMotionEvents:false.
	self startAutoScrollLeft:x.
	^ self
    ].
    (x > width) ifTrue:[
	self compressMotionEvents:false.
	self startAutoScrollRight:(x - width).
	^ 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.
	selectStyle notNil ifTrue:[
	    selectionEndCol := wordEndCol.
	    selectionEndLine := wordEndLine.
	]
    ] ifFalse:[
	"change selectionEnd"
	selectionEndCol := movedCol.
	selectionEndLine := movedLine.
	selectionStartCol := clickStartCol.
	selectionStartLine := clickStartLine.
	selectStyle notNil ifTrue:[
	    selectionStartCol := wordStartCol.
	    selectionStartLine := wordStartLine.
	]
    ].

    selectionStartLine isNil ifTrue:[^ self].

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

    "
     if in word-select, just catch the rest of the word
    "
    (selectStyle notNil and:[selectStyle startsWith:'word']) ifTrue:[
	movedUp ifTrue:[
	    selectionStartCol := self findBeginOfWordAtLine:selectionStartLine col:selectionStartCol
	] ifFalse:[
	    selectionEndCol := self findEndOfWordAtLine:selectionEndLine col:selectionEndCol.
	    selectionEndCol == 0 ifTrue:[
		selectionEndLine := selectionEndLine + 1
	    ]
	].
    ].

    selectStyle == #line ifTrue:[
	movedUp ifTrue:[
	    selectionStartCol := 1.
	] ifFalse:[
	    selectionEndCol := 0.
	    selectionEndLine := selectionEndLine + 1
	]
    ].

    self validateNewSelection.

    (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
!

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

    |sel ch|

    ((button == 1) or:[button == #select]) ifTrue:[
        clickCount notNil ifTrue:[
            clickCount := clickCount + 1.
            (clickCount == 2) ifTrue:[
                self selectWordAtX:x y:y.
                "
                 special - if clicked on a parenthesis, select to matching
                "
                ((sel := self selection) size == 1 
                and:[(sel := sel at:1) size == 1]) ifTrue:[
                    ch := sel at:1.
                    ('()[]{}<>' includes:ch) ifTrue:[
                        self searchForMatchingParenthesisFromLine:selectionStartLine col:selectionStartCol
                              ifFound:[:line :col | 
                                          |prevLine prevCol moveBack pos1|

                                          prevLine := firstLineShown.
                                          prevCol := leftOffset.
                                          self selectFromLine:selectionStartLine col:selectionStartCol
                                                       toLine:line col:col.

                                          self sensor ctrlDown ifFalse:[
                                              "/ undo scroll operation ...
                                              self withCursor:Cursor eye do:[  
                                                  moveBack := false.
                                                  (')]}>' includes:ch) ifTrue:[
                                                       (firstLineShown ~~ prevLine or:[prevCol ~~ leftOffset]) ifTrue:[
                                                           moveBack := true
                                                       ] 
                                                  ] ifFalse:[
                                                       selectionEndLine > (firstLineShown + nFullLinesShown) ifTrue:[
                                                           self makeLineVisible:selectionEndLine.
                                                           moveBack := true
                                                       ]
                                                  ].
                                                  moveBack ifTrue:[
                                                       pos1 := x@y. 
                                                       Delay waitForSeconds:MatchDelayTime. 
                                                        
                                                       [self sensor hasUserEventFor:self] whileFalse:[
                                                            Delay waitForSeconds:MatchDelayTime / 2.
                                                       ].
                                                       self scrollToLine:prevLine; scrollToCol:prevCol.
                                                  ].
                                              ]
                                          ]
                                      ]
                           ifNotFound:[self showNotFound]
                              onError:[self beep].
                        selectStyle := nil
                    ]
                ].

                "
                 remember words position in case of a drag following
                "
                wordStartLine := selectionStartLine.
                wordEndLine := selectionEndLine.
                selectStyle == #wordLeft ifTrue:[
                    wordStartCol := selectionStartCol + 1
                ] ifFalse:[
                    wordStartCol := selectionStartCol.
                ].
                selectStyle == #wordRight ifTrue:[
                    wordEndCol := selectionEndCol - 1
                ] ifFalse:[
                    wordEndCol := selectionEndCol
                ]
            ] ifFalse:[
                (clickCount == 3) ifTrue:[
                    self selectLineAtY:y.
                    selectStyle := #line
                ] ifFalse:[
                    (clickCount == 4) ifTrue:[
                        self selectAll
                    ]
                ]
            ]
        ]
    ] ifFalse:[
        super buttonMultiPress:button x:x y:y
    ]

    "Modified: 1.11.1996 / 17:13:50 / cg"
!

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

    |clickVisibleLine|

    self sensor shiftDown ifTrue:[
        "mouse-click with shift - adding to selection"

        "very simple - just simulate a move"
        ^ self buttonMotion:(device button1MotionMask) x:x y:y
    ].

    ((button == 1) or:[button == #select]) 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
    ]

    "Modified: 1.8.1996 / 17:59:17 / cg"
!

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

    ((button == 1) or:[button == #select]) ifTrue:[
	autoScrollBlock notNil ifTrue:[
	    self stopScrollSelect
	].
    ] ifFalse:[
	super buttonRelease:button x:x y:y
    ]
!

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

    <resource: #keyboard (#Find #Copy #FindNext #FindPrev 
                          #GotoLine #SelectAll #SaveAs #Print
                          #'F*' #'f*' )>

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

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

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

    (key == #SaveAs)    ifTrue:[self save.    ^self].
    (key == #Print)     ifTrue:[self doPrint. ^self].

    "
     shift-Fn defines a key-sequence 
     Fn       pastes that sequence
     cmd-Fn   performs a 'doIt' on the sequence (Workspaces only)

     (see EditTextView>>keyPress:x:y and Workspace>>keyPress:x:y)
    "
    (('[fF][0-9]' match:key)
    or:['[fF][0-9][0-9]' match:key]) ifTrue:[
        self sensor shiftDown ifTrue:[
            (Smalltalk at:#FunctionKeySequences) isNil ifTrue:[
                Smalltalk at:#FunctionKeySequences put:Dictionary new
            ].
            (Smalltalk at:#FunctionKeySequences) at:key put:(self selection)
        ].
        ^ self
    ].

    super keyPress:key x:x y:y

    "Modified: 9.1.1997 / 12:18:14 / cg"
!

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

!TextView methodsFor:'initialize & release'!

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

    super fetchDeviceResources.

    selectionFgColor notNil ifTrue:[selectionFgColor := selectionFgColor on:device].
    selectionBgColor notNil ifTrue:[selectionBgColor := selectionBgColor on:device].

    "Created: 14.1.1997 / 00:14:33 / cg"
!

initStyle
    "setup viewStyle specifics"

    super initStyle.

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

    viewBackground := DefaultViewBackground.
    selectionFgColor := DefaultSelectionForegroundColor.
    selectionFgColor isNil ifTrue:[selectionFgColor := bgColor].
    selectionBgColor := DefaultSelectionBackgroundColor.
    selectionBgColor isNil ifTrue:[
        device hasColors ifTrue:[
            DefaultSelectionForegroundColor isNil ifTrue:[
                selectionFgColor := fgColor
            ].
            selectionBgColor := Color green
        ] ifFalse:[
            device hasGrayscales ifTrue:[
                DefaultSelectionForegroundColor isNil ifTrue:[
                    selectionFgColor := fgColor
                ].
                selectionBgColor := Color grey
            ] ifFalse:[
                selectionBgColor := fgColor
            ]
        ]
    ].

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

initialize
    super initialize.
    contentsWasSaved := false.

    "I handle menus myself"
    menuHolder := menuPerformer := self.

    "Modified: 3.1.1997 / 02:14:01 / stefan"
! !

!TextView methodsFor:'menu actions'!

appendTo:fileName
    "append contents to a file named fileName"

    |aStream msg|

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

changeFont
    "pop up a fontPanel to change font"

    |newFont|

    newFont := FontPanel fontFromUserInitial:font.
    newFont notNil ifTrue:[
        self font:newFont.
    ]

    "Modified: 27.2.1996 / 00:53:51 / cg"
!

copySelection
    "copy contents into smalltalk copybuffer"

    |text|

    text := self selection.
    text notNil ifTrue:[
        self unselect.

	"/ forget any emphasis ...
        text := text collect:[:l | l isNil ifTrue:[l] ifFalse:[l string]].
        self setTextSelection:text.
    ]

    "Modified: 17.5.1996 / 08:57:54 / cg"
!

defaultForGotoLine
    "return a default value to show in the gotoLine box"

    ^ selectionStartLine

    "Modified: 1.3.1996 / 18:44:36 / cg"
!

doPrint
    "print the contents on the printer"

    |printStream|

    list isNil ifTrue:[^ self].

    self withWaitCursorDo:[
        printStream := Printer new.
        printStream notNil ifTrue:[
            Printer writeErrorSignal handle:[:ex |
                self warn:('error while printing:\\' 
                            , ex errorString 
                            , '\\(printing with: ' , (Printer printCommand) , ')') withCRs
            ] do:[
                self fileOutContentsOn:printStream.
            ].
            printStream close
        ]
    ].

    "Created: 6.5.1996 / 16:11:26 / cg"
    "Modified: 5.9.1996 / 19:18:30 / cg"
!

editMenu
    <resource: #keyboard (#Copy #Find #GotoLine #SaveAs #Print)>
    <resource: #menu>

    |labels selectors m|

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

    selectors := #(
                        copySelection
                        nil
                        changeFont
                        nil
                        search
                        gotoLine
                        nil
                        save
                        doPrint
                  ).

    m := PopUpMenu
           labels:(resources array:labels)
           selectors:selectors
           accelerators:#(
                           #Copy
                           nil
                           nil
                           nil
                           #Find
                           #GotoLine
                           nil
                           #SaveAs
                           #Print
                         ).

    self hasSelection ifFalse:[
        m disable:#copySelection.
    ].
    ^ m

    "Modified: 25.2.1997 / 20:12:32 / cg"
!

gotoLine
    "show a box to enter lineNumber for positioning"

    |l lineNumberBox|

    lineNumberBox :=
        EnterBox
           title:(resources string:'line number:')
           okText:(resources string:'goto')
           abortText:(resources string:'cancel')
           action:[:l | |num|
                       num := Integer readFromString:l onError:nil.
                       num notNil ifTrue:[self gotoLine:num]
                  ].

    l := self defaultForGotoLine.
    l notNil ifTrue:[
        l := l printString
    ].
    lineNumberBox initialText:l .
    lineNumberBox showAtPointer

    "Modified: 6.3.1996 / 13:12:27 / cg"
!

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

    |fileBox|

    fileBox := FileSaveBox
                    title:(resources string:'save contents in:')
                    okText:(resources string:'save')
                    abortText:(resources string:'cancel')
                    action:[:fileName | self saveAs:fileName].
    fileBox appendAction:[:fileName | self appendTo:fileName].
    directoryForFileDialog notNil ifTrue:[
        fileBox directory:directoryForFileDialog
    ].
    defaultFileNameForFileDialog notNil ifTrue:[
        fileBox initialText:defaultFileNameForFileDialog asString
    ].
    fileBox showAtPointer.

    directoryForFileDialog := fileBox directory  "/ remember for next time

    "Modified: 13.2.1997 / 18:31:17 / cg"
!

saveAs:fileName
    "save the contents into a file named fileName"
 
    self withCursor:Cursor write do:[
        |aStream msg|

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

    "Modified: 5.1.1997 / 02:14:46 / cg"
! !

!TextView methodsFor:'private'!

fileOutContentsOn:aStream
    "save contents on a stream, replacing leading spaces by tab-characters."

    self fileOutContentsOn:aStream compressTabs:true
!

fileOutContentsOn:aStream compressTabs:compressTabs
    "save contents on a stream. If compressTabs is true,
     leading spaces will be replaced by tab-characters in the output."

    |startNr nLines string|

    aStream isFileStream ifTrue:[
        "on some systems, writing linewise is very slow (via NFS)
         therefore we convert to a string and write it in big chunks.
         To avoid creating huge strings, we do it in blocks of 1000 lines,
         limiting temporary string creation to about 50-80k.
        "
        startNr := 1.
        nLines := list size.
        [startNr <= nLines] whileTrue:[
            string := list asStringWithCRsFrom:startNr 
                                            to:((startNr + 1000) min:nLines)
                                  compressTabs:compressTabs.
            aStream nextPutAll:string.
            startNr := startNr + 1000 + 1.
        ].
    ] ifFalse:[
        list do:[:aLine |
            aLine notNil ifTrue:[
                aStream nextPutAll:aLine.
            ].
            aStream cr
        ]
    ]

    "Modified: 8.6.1996 / 11:50:46 / cg"
!

getFontParameters
    "get some info of the used font. They are cached since we use them often ..
     This is redefined here, to use the fonts maxHeight/maxAscent for
     line separation. This is required, to allow for proper handling of
     national characters, such as A-dieresis ..."

    font := font on:device.
    includesNonStrings == true ifTrue:[
        "/ for now, we do not support variable height entries ...
        fontHeight := list first heightOn:self
    ] ifFalse:[
        fontHeight := font maxHeight.
    ].
    fontHeight := fontHeight + lineSpacing.
    fontAscent := font maxAscent.
    fontWidth := font width.
    fontIsFixedWidth := font isFixedWidth.

    "Modified: 22.5.1996 / 12:02:47 / cg"
    "Created: 22.5.1996 / 12:18:34 / cg"
!

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

    |prevEndLine|

    "just to make certain ..."
    selectionEndLine isNil ifTrue:[^ self].

    self scrollDown.

    "make new selection immediately visible"
    prevEndLine := selectionEndLine.
    selectionEndLine := firstLineShown + nFullLinesShown.
    selectionEndCol := 0.
    prevEndLine to:selectionEndLine do:[:lineNr |
	self redrawLine:lineNr
    ].
    Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
!

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

    |prevStartLine|

    "just to make certain ..."
    selectionStartLine isNil ifTrue:[^ self].
    selectionStartCol isNil ifTrue:[^ self].

    "make new selection immediately visible"
    prevStartLine := selectionStartLine.
    selectionStartCol := selectionStartCol - 1 max:1.
    self scrollLeft.

    Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
!

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

    |prevEndCol|

    "just to make certain ..."
    selectionEndCol isNil ifTrue:[^ self].

    prevEndCol := selectionEndCol.
    selectionEndCol := selectionEndCol + 1.
    self scrollRight.

    Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
!

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

    |prevStartLine|

    "just to make certain ..."
    selectionStartLine isNil ifTrue:[^ self].

    self scrollUp.

    "make new selection immediately visible"
    prevStartLine := selectionStartLine.
    selectionStartLine := firstLineShown.
    selectionStartCol := 1.
    selectionStartLine to:prevStartLine do:[:lineNr |
	self redrawLine:lineNr
    ].
    Processor addTimedBlock:autoScrollBlock afterSeconds:autoScrollDeltaT.
!

stopScrollSelect
    "stop auto scroll; deinstall timed-block"

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

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
! !

!TextView methodsFor:'queries'!

specClass
    self class == TextView ifTrue:[^ TextEditorSpec].
    ^ super specClass


! !

!TextView methodsFor:'redrawing'!

clearMarginOfVisibleLine: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 yOfVisibleLine:visLine)
                      width:leftMargin
                     height:fontHeight
    ]

    "Created: 6.3.1996 / 14:22:55 / cg"
!

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.
	^ self
    ].

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

    (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
    ]
!

redrawMarginOfVisibleLine:visLine
    "draw margin - a helper for selection drawing"


    (leftMargin ~~ 0) ifTrue:[
    ]

    "Created: 6.3.1996 / 14:21:48 / cg"
!

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 clearMarginOfVisibleLine: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).
                    ^ self
                ].

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

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

                self clearMarginOfVisibleLine:visLine with:selectionBgColor.
                self drawVisibleLine:visLine from:1 to:selectionEndCol
                                with:selectionFgColor and:selectionBgColor.
                super redrawVisibleLine:visLine from:(selectionEndCol + 1).
                ^ self
            ].

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

    "Modified: 6.3.1996 / 14:22:19 / cg"
!

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

    |line fg bg|

    line := self visibleLineToAbsoluteLine:visLine.

    "/
    "/ care for selection
    "/
    fg := fgColor.
    bg := bgColor.

    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"
                    fg := selectionFgColor.
                    bg := selectionBgColor.

"/                    self 
"/                        drawVisibleLine:visLine 
"/                        col:col 
"/                        with:selectionFgColor
"/                        and:selectionBgColor.
"/                    ^ self
                ]
            ]
        ]
    ].
    self drawVisibleLine:visLine col:col with:fg and:bg
"/    super redrawVisibleLine:visLine col:col

    "Modified: 12.5.1996 / 17:46:51 / cg"
!

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

    |col line|

    col := startCol.
    col == 0 ifTrue:[
        col := 1.
    ].

    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.
                ^ self
            ].
            "the line is fully within the selection"
            self 
                drawVisibleLine:visLine 
                from:col 
                with:selectionFgColor
                and:selectionBgColor.
            ^ self
        ]
    ].
    super redrawVisibleLine:visLine from:col

    "Modified: 6.3.1996 / 14:19:38 / cg"
!

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.
        ^ self
    ].

    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 clearMarginOfVisibleLine:visLine with:selectionBgColor.
    ].

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

    "Modified: 6.3.1996 / 14:23:26 / cg"
! !

!TextView methodsFor:'searching'!

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

    "
     cache the searchBox
     Q: should we use one global searchBox for all textViews ?
        (we could then preserve the last searchstring between views)
    "
    |searchBox|


"/ "soon to come: search & replace box ...
"/    |box|
"/
"/    box := Dialog new.
"/    (box addTextLabel:(resources at:'searchPattern:')) layout:#left.
"/    box addVerticalSpace.
"/    box addInputFieldOn:'' asValue.
"/    box addVerticalSpace.
"/    (box addTextLabel:(resources at:'replace with:')) layout:#left.
"/    box addVerticalSpace.
"/    box addInputFieldOn:'' asValue.
"/    box addAbortButtonLabelled:(resources at:'cancel');
"/        addButton:(Button label:(resources at:'all'));
"/        addButton:(Button label:(resources at:'prev'));
"/        addOkButtonLabelled:(resources at:'next').
"/    box open.

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

    searchPattern notNil ifTrue:[
        searchBox initialText:searchPattern
    ].
    self hasSelection ifTrue:[
        selectionStartLine == selectionEndLine ifTrue:[
            searchBox initialText:self selection
        ]
    ].
    searchBox showAtPointer

    "Modified: 6.3.1996 / 13:11:46 / cg"
!

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

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

searchBwd:pattern
    "do a backward search"

    self searchBwd:pattern ifAbsent:[self showNotFound].
    searchPattern := pattern

!

searchBwd:pattern ifAbsent:aBlock
    "do a 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 showMatch:pattern atLine:line col:col
    ] ifAbsent:aBlock
!

searchForMatchingParenthesisFromLine:startLine col:startCol
                     ifFound:foundBlock 
                  ifNotFound:notFoundBlock
                     onError:failBlock

    "search for a matching parenthesis, parChar is one of '$( $[ ${ $) $] $}'. 
     Search for the corresponding character is done forward if its an opening,
     backwards if its a closing parenthesis.
     Performs foundBlock with line/col as argument if found, notFoundBlock if not.
     If there is a nesting error, performs failBlock."

    ^ self
        searchForMatchingParenthesisFromLine:startLine col:startCol
                     ifFound:foundBlock 
                  ifNotFound:notFoundBlock
                     onError:failBlock
                    ignoring:#( $' $" '$[' '$]' '${' '$)' )

    "Modified: 18.5.1996 / 11:05:57 / cg"
!

searchForMatchingParenthesisFromLine:startLine col:startCol
                     ifFound:foundBlock 
                  ifNotFound:notFoundBlock
                     onError:failBlock
                    ignoring:ignoreSet
    "search for a matching parenthesis, parChar is one of '$( $[ ${ $) $] $}'. 
     Search for the corresponding character is done forward if its an opening,
     backwards if its a closing parenthesis.
     Performs foundBlock with line/col as argument if found, notFoundBlock if not.
     If there is a nesting error, performs failBlock."

    |i direction lineString 
     parChar charSet  closingChar 
     ignoring 
     line   "{ Class: SmallInteger }"
     col    "{ Class: SmallInteger }"
     delta  "{ Class: SmallInteger }"
     endCol "{ Class: SmallInteger }"
     runCol "{ Class: SmallInteger }"
     cc prevCC nextCC incSet decSet 
     nesting "{ Class: SmallInteger }"
     maxLine "{ Class: SmallInteger }"
     ign skip|

    charSet := #( $( $) $[ $] ${ $} " $< $> " ).

    parChar := self characterAtLine:startLine col:startCol.
    i := charSet indexOf:parChar.
    i == 0 ifTrue:[
        ^ failBlock value   "not a parenthesis"
    ].
    direction := #( fwd bwd fwd bwd fwd bwd fwd bwd) at:i.
    closingChar := #( $) $( $] $[ $} ${ "$> $<") at:i.

    col := startCol.
    line := startLine.
    direction == #fwd ifTrue:[
        delta := 1.
        incSet := #( $( $[ ${ "$<" ).
        decSet := #( $) $] $} "$>" ).
    ] ifFalse:[
        delta := -1.
        incSet := #( $) $] $} "$>" ).
        decSet := #( $( $[ ${ "$<" ).
    ].

    nesting := 1.
    ignoring := false.
    lineString := list at:line.
    maxLine := list size.

    col := col + delta.
    [nesting ~~ 0] whileTrue:[
        lineString notNil ifTrue:[
            direction == #fwd ifTrue:[
                endCol := lineString size.
            ] ifFalse:[
                endCol := 1
            ].

            col to:endCol by:delta do:[:rCol |
                runCol := rCol.

                cc := lineString at:runCol.
                runCol < lineString size ifTrue:[
                    nextCC := lineString at:runCol+1
                ] ifFalse:[
                    nextCC := nil
                ].
                runCol > 1 ifTrue:[
                    prevCC := lineString at:runCol-1
                ] ifFalse:[
                    prevCC := nil
                ].

                ign := skip := false.
                (cc == $"   
                and:[nextCC == $/ or:[prevCC == $$ ]]) ifTrue:[
                    "/ do nothing

                    skip := true.
                ] ifFalse:[
                    ignoreSet do:[:ignore |
                        ignore == cc ifTrue:[
                            ign := true
                        ] ifFalse:[
                            ignore isString ifTrue:[
                                cc == (ignore at:2) ifTrue:[
                                    runCol > 1 ifTrue:[
                                        (lineString at:(runCol-1)) == (ignore at:1) ifTrue:[
                                            skip := true
                                        ]
                                    ]
                                ] ifFalse:[
                                    cc == (ignore at:1) ifTrue:[
                                        runCol < lineString size ifTrue:[
                                            (lineString at:(runCol+1)) == (ignore at:2) ifTrue:[
                                                skip := true
                                            ]
                                        ]
                                    ]
                                ]
                            ]
                        ]
                    ]
                ].

                ign ifTrue:[
                    ignoring := ignoring not
                ].

                ignoring ifFalse:[
                    skip ifFalse:[
                        (incSet includes:cc) ifTrue:[
                            nesting := nesting + 1
                        ] ifFalse:[
                            (decSet includes:cc) ifTrue:[
                                nesting := nesting - 1
                            ]
                        ]
                    ]
                ].

                nesting == 0 ifTrue:[
                    "check if legal"

                    skip ifFalse:[
                        cc == closingChar ifFalse:[
                            ^ failBlock value
                        ].
                        ^ foundBlock value:line value:runCol.
                    ]
                ]
            ].
        ].
        line := line + delta.
        (line < 1 or:[line > maxLine]) ifTrue:[
            ^ failBlock value
        ].
        lineString := list at:line.
        direction == #fwd ifTrue:[
            col := 1
        ] ifFalse:[
            col := lineString size
        ]
    ].
    ^ notFoundBlock value

    "Modified: 15.10.1996 / 12:22:30 / cg"
!

searchFwd
    "search forward for pattern or selection"

    selectStyle == #wordLeft ifTrue:[
	"
	 remove the space from the selection
	"
	selectionStartCol := selectionStartCol + 1.
	super redrawLine:selectionStartLine from:selectionStartCol-1 to:selectionStartCol-1.
	selectStyle := #word.
    ].
    self setSearchPattern.
    searchPattern notNil ifTrue:[
	self searchFwd:searchPattern
    ]
!

searchFwd:pattern
    "do a forward search"

    self searchFwd:pattern ifAbsent:[self showNotFound].
    searchPattern := pattern
!

searchFwd:pattern ifAbsent:aBlock
    "do a 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 showMatch:pattern atLine:line col:col
    ] ifAbsent:aBlock
!

searchPattern
    "return the last search pattern"

    ^ searchPattern
!

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

    |sel|

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

setSearchPattern:aString
    "set the searchpattern for future searches"

    aString isNil ifTrue:[
	searchPattern := aString
    ] ifFalse:[
	searchPattern := aString withoutSeparators
    ]
!

showMatch:pattern atLine:line col:col
    "after a search, highlight the matched pattern.
     The code below needs a rewrite to take care of match-characters
     (for now, it only highlights simple patterns and '*string*' correctly)"

    |realPattern|

    realPattern := pattern.
    (realPattern startsWith:$*) ifTrue:[
	realPattern := realPattern copyFrom:2
    ].
    (realPattern endsWith:$*) ifTrue:[
	realPattern := realPattern copyWithoutLast:1
    ].

    self selectFromLine:line col:col
		 toLine:line col:(col + realPattern size - 1).
    self makeLineVisible:line
!

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|

    savedCursor := cursor.
    [
        self cursor:(Cursor cross).
        self beep.
        Processor activeProcess millisecondDelay:300.
    ] valueNowOrOnUnwindDo:[
        self cursor:savedCursor
    ]

    "Modified: 20.2.1997 / 12:49:27 / cg"
! !

!TextView methodsFor:'selections'!

expandSelectionDown
    |l t|

    selectionStartLine notNil ifTrue:[
        expandingTop ifTrue:[
            l := selectionStartLine.
            selectionStartLine := selectionStartLine + 1.
            (selectionStartLine > clickLine
            or:[selectionStartLine == clickLine and:[selectionStartCol > clickCol]])
            ifTrue:[
                t := selectionStartLine.
                selectionStartLine := selectionEndLine.
                selectionEndLine := t.
                t := selectionStartCol.
                selectionStartCol := selectionEndCol.
                selectionEndCol := t.
                expandingTop := false
            ].
        ] ifFalse:[
            l := selectionEndLine.
            selectionEndLine := selectionEndLine + 1.
        ].
        self redrawLine:l. 
        self redrawLine:l+1.
        self makeSelectionVisible.
    ].

    "Created: 1.3.1996 / 23:35:08 / cg"
    "Modified: 18.3.1996 / 17:18:15 / cg"
!

expandSelectionLeft
    |c l t c1 c2|

    selectionStartLine notNil ifTrue:[
        expandingTop ifTrue:[
            selectionStartCol == 0 ifTrue:[^ self].
            l := selectionStartLine.
            selectionStartCol := (selectionStartCol - 1) max:1.
            c := selectionStartCol.
        ] ifFalse:[
            l := selectionEndLine.
            selectionEndCol := (selectionEndCol - 1) max:0.
            c := selectionEndCol.
            selectionEndLine == selectionStartLine ifTrue:[
                selectionEndCol <= selectionStartCol ifTrue:[
                    t := selectionStartCol. selectionStartCol := selectionEndCol.
                    selectionEndCol := t.
                    expandingTop := true.
                    c := selectionStartCol.
                ]
            ].
        ].
        c1 := c.
        c2 := c1 + 1.
        c1 == 0 ifTrue:[
            c1 := 1
        ].
        self redrawLine:l from:c1 to:c2. 
        self makeSelectionVisible.
    ].

    "Modified: 18.3.1996 / 17:05:46 / cg"
!

expandSelectionRight
    |l c t|

    selectionStartLine notNil ifTrue:[
        expandingTop ifTrue:[
            l := selectionStartLine.
            c := selectionStartCol.
            selectionStartCol := selectionStartCol + 1.
            l == selectionEndLine ifTrue:[
                c >= selectionEndCol ifTrue:[
                    expandingTop := false.
                    t := selectionStartCol. selectionStartCol := selectionEndCol.
                    selectionEndCol := t.
                    c := selectionStartCol.
                ]
            ]
        ] ifFalse:[
            l := selectionEndLine.
            c := selectionEndCol.
            selectionEndCol := selectionEndCol + 1.
        ].

        self redrawLine:l from:c to:c+1.
        self makeSelectionVisible.
    ].

    "Created: 1.3.1996 / 23:33:17 / cg"
    "Modified: 6.3.1996 / 13:54:10 / cg"
!

expandSelectionUp
    |l t|

    selectionStartLine notNil ifTrue:[
        expandingTop ifTrue:[
            selectionStartLine := (selectionStartLine - 1) max:1.
            l := selectionStartLine. 
        ] ifFalse:[
            selectionEndLine := (selectionEndLine - 1) max:0.

            l := selectionEndLine.
            (selectionEndLine < clickLine
            or:[(selectionEndLine == clickLine and:[selectionEndCol < clickCol])])
            ifTrue:[
                t := selectionStartLine.
                selectionStartLine := selectionEndLine.
                selectionEndLine := t.
                t := selectionStartCol.
                selectionStartCol := selectionEndCol.
                selectionEndCol := t.
                l := selectionStartLine.
                expandingTop := true
            ].
        ].
        self redrawLine:l. 
        self redrawLine:l+1. 
        self makeSelectionVisible.
    ].

    "Modified: 6.3.1996 / 14:12:06 / cg"
!

hasSelection
    "return true, if there is a selection"

    ^ selectionStartLine notNil
!

makeSelectionVisible
    "scroll to make the selection visible"

    |line col|

    selectionStartLine notNil ifTrue:[
        expandingTop ~~ false ifTrue:[
            line := selectionStartLine.
            col := selectionStartCol.
        ] ifFalse:[
            line := selectionEndLine.
            col := selectionEndCol.
        ].
        self makeLineVisible:line.
        self makeColVisible:col inLine:line.        
    ]

    "Modified: 6.3.1996 / 13:53:45 / cg"
!

selectAll
    "select the whole text"

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

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
!

selectFromLine:startLine col:startCol toLine:endLine col:endCol
    "select a piece of text and redraw that area"

    self unselect.
    startLine notNil ifTrue:[
        "new:"
        endLine < startLine ifTrue:[
            ^ self selectFromLine:endLine col:endCol toLine:startLine col:startCol
        ].
        (endLine == startLine and:[endCol < startCol]) ifTrue:[
            endCol ~~ 0 ifTrue:[
                self selectFromLine:endLine col:endCol toLine:startLine col:startCol.
            ].
            ^ self
        ].

" old:
        endLine < startLine ifTrue:[^ self].
        (startLine == endLine and:[endCol < startCol]) ifTrue:[^ self].
"
        selectionStartLine := startLine.
        selectionStartCol := startCol.
        selectionEndLine := endLine.
        selectionEndCol := endCol.
        self validateNewSelection.

        (selectionStartLine == selectionEndLine) ifTrue:[
            self redrawLine:selectionStartLine from:selectionStartCol to:selectionEndCol
        ] ifFalse:[
            selectionStartLine to:selectionEndLine do:[:lineNr |
                self redrawLine:lineNr
            ]
        ].
        selectStyle := nil.
    ]

    "
     |v|

     v := TextView extent:300@300.
     v contents:('smalltalk.rc' asFilename contentsOfEntireFile).
     v openAndWait.

     Delay waitForSeconds:1.

     v selectFromLine:2 col:2 toLine:10 col:15
    "

    "Modified: 2.1.1997 / 13:32:25 / cg"
!

selectFromLine:startLine toLine:endLine
    "select a piece of text and redraw that area"

    self selectFromLine:startLine col:1 toLine:endLine+1 col:0

    "
     |v|

     v := TextView extent:300@300.
     v contents:('smalltalk.rc' asFilename contentsOfEntireFile).
     v openAndWait.

     Delay waitForSeconds:1.

     v selectFromLine:2 toLine:10
    "

    "Modified: 29.4.1996 / 12:23:46 / cg"
!

selectLine:selectLine
    "select one line and redraw it"

    self selectFromLine:selectLine col:1 toLine:(selectLine + 1) col:0.
    wordStartCol := selectionStartCol.
    wordEndCol := selectionEndCol.
    wordStartLine := selectionStartLine.
    wordEndLine := selectionEndLine.
    selectStyle := #line
!

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
    ]
!

selectLineWhereCharacterPosition:pos
    "select the line, where characterPosition pos is living.
     The argument pos starts at 1 from the start of the text
     and counts characters (i.e. can be used to convert from 
     character position within a string to line-position in view)."

    self selectLine:(self lineOfCharacterPosition:pos)
!

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

    self wordAtLine:line col:col do:[
        :beginLine :beginCol :endLine :endCol :style |

        self selectFromLine:beginLine col:beginCol toLine:endLine col:endCol.
        selectStyle := style
    ]

    "Modified: 18.3.1996 / 17:30:38 / cg"
!

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

    |selectVisibleLine selectLine selectCol|

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

selection
    "return the selection as a collection of (line-)strings.
     If the selection ends in a full line, the last entry in the returned
     collection will be an empty string."

    |text sz index last
     startLine "{ Class: SmallInteger }"
     endLine   "{ Class: SmallInteger }"|

    selectionStartLine isNil ifTrue:[^ nil].
    startLine := selectionStartLine.
    endLine := selectionEndLine.

    (startLine == endLine) ifTrue:[
	"part of a line"
	^ StringCollection with:(self listAt:startLine
					from:selectionStartCol
					  to:selectionEndCol)
    ].
    sz := endLine - startLine + 1.
    text := StringCollection new:sz.

    "get 1st and last (possibly) partial lines"
    text at:1 put:(self listAt:startLine from:selectionStartCol).
    selectionEndCol == 0 ifTrue:[
	last := ''
    ] ifFalse:[
	last := self listAt:selectionEndLine to:selectionEndCol.
    ].
    text at:sz put:last.

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

selectionEndCol
    ^ selectionEndCol
!

selectionEndLine
    ^ selectionEndLine
!

selectionStartCol
    ^ selectionStartCol
!

selectionStartLine
    ^ selectionStartLine
!

unselect
    "unselect - if there was a selection redraw that area"

    |startLine endLine startVisLine endVisLine|

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

        self unselectWithoutRedraw.

        "/ if the 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

        (startLine == endLine) ifTrue:[
            super redrawVisibleLine:startVisLine from:selectionStartCol to:selectionEndCol
        ] ifFalse:[
            self redrawFromVisibleLine:startVisLine to:endVisLine
        ].
    ].
    selectStyle := nil

    "Modified: 29.5.1996 / 14:54:11 / cg"
!

unselectWithoutRedraw
    "forget selection but do not redraw the selection area
     - can be done when the selected area is redrawn anyway or
     known to be invisible (however, redraw knows about that anyway)."

    selectionStartLine := nil.

    "Modified: 29.4.1996 / 12:33:28 / cg"
!

validateNewSelection
     "make certain that the selection is valid.
      This is a dummy here, but subclasses (like single-line editFields)
      may redefine it to limit the selection to a single line, or whatever."

    ^ self

    "Modified: 29.4.1996 / 12:32:08 / cg"
! !

!TextView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/TextView.st,v 1.87 1997-03-05 16:32:19 cg Exp $'
! !