TextView.st
author Claus Gittinger <cg@exept.de>
Tue, 03 Jun 2003 20:08:17 +0200
changeset 2772 4e04a3bf399f
parent 2756 2bdd7ceaf05c
child 2778 223915a2d6a4
permissions -rw-r--r--
check for a valid parenthsisSpec.

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

"{ Package: 'stx:libwidg' }"

ListView subclass:#TextView
	instanceVariableNames:'selectionStartLine selectionStartCol selectionEndLine
		selectionEndCol clickPos clickStartLine clickStartCol clickLine
		clickCol clickCount expandingTop wordStartCol wordStartLine
		wordEndCol wordEndLine selectionFgColor selectionBgColor
		selectStyle directoryForFileDialog defaultFileNameForFileDialog
		externalEncoding contentsWasSaved lastSearchPattern
		lastSearchIgnoredCase lastSearchDirection
		parenthesisSpecification dropSource dragIsActive'
	classVariableNames:'DefaultViewBackground DefaultSelectionForegroundColor
		DefaultSelectionBackgroundColor
		DefaultAlternativeSelectionForegroundColor
		DefaultAlternativeSelectionBackgroundColor MatchDelayTime
		WordSelectCatchesBlanks ST80Selections LastSearchPatterns
		NumRememberedSearchPatterns LastSearchIgnoredCase
		DefaultParenthesisSpecification'
	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

      externalEncoding        <Symbol|nil>            external encoding, used when text is saved to
                                                      a file. Usually something like
                                                      #jis7, #euc, #sjis etc.
                                                      (currently only passed down from the
                                                       fileBrowser)

      dropSource              <DropSource>            drag operation descriptor or nil (dragging disabled)
      dragIsActive            <Boolean>               true, drag operation is activated  


    [class variables:]
        ST80Selections        <Boolean>               enables ST80 style doubleclick behavior
                                                      (right after opening parenthesis, right before
                                                       closing parenthesis, at begin of a line
                                                       at begin of text)

    [StyleSheet parameters:]

      textView.background                       defaults to viewBackground
      textView.ViewFont                         defaults to textFont

      text.st80Selections                       st80 behavior (click on char after parent or quote)

      text.selectionForegroundColor             defaults to textBackgroundColor
      text.selectionBackgroundColor             defaults to textForegroundColor

      text.alternativeSelectionForegroundColor  pasted text (i.e. paste will not replace)
                                                defaults to selectionForegroundColor
      text.alternativeSelectionBackgroundColor  pasted text (i.e. paste will not replace)
                                                defaults to selectionBackgroundColor

    [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:'class initialization'!

initialize
    DefaultParenthesisSpecification isNil ifTrue:[
        DefaultParenthesisSpecification := IdentityDictionary new.       
        DefaultParenthesisSpecification at:#open        put:#( $( $[ ${ "$> $<") .
        DefaultParenthesisSpecification at:#close       put:#( $) $] $} "$> $<").
        DefaultParenthesisSpecification at:#ignore      put:#( $' $" '$[' '$]' '${' '$)' ).
        DefaultParenthesisSpecification at:#eolComment  put:'"/'.     "/ sigh - must be 2 characters
    ].
! !

!TextView class methodsFor:'defaults'!

defaultIcon
    "return the default icon if started as a topView"

    <resource: #style (#ICON #ICON_FILE)>

    |nm i|

    i := self classResources at:'ICON' default:nil.
    i isNil ifTrue:[
        nm := ClassResources at:'ICON_FILE' default:'Editor.xbm'.
        i := Smalltalk imageFromFileNamed:nm forClass:self.
    ].
    i notNil ifTrue:[
        i := i onDevice:Display
    ].
    ^ i

    "Modified: 18.4.1997 / 15:18:06 / 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"
!

defaultSelectionBackgroundColor
    "return the default selection background color"

    ^DefaultSelectionBackgroundColor
!

defaultSelectionForegroundColor
    "return the default selection foreground color"

    ^DefaultSelectionForegroundColor
!

defaultViewBackgroundColor
    "return the default view background"

    ^DefaultViewBackground
!

st80SelectMode
    ^ ST80Selections

    "Modified: / 6.1.1999 / 14:19:26 / cg"
!

st80SelectMode:aBoolean
    ST80Selections := aBoolean

    "Created: / 7.1.1999 / 13:35:24 / cg"
!

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

    <resource: #style (#'textView.background'
                       #'text.selectionForegroundColor' #'text.selectionBackgroundColor'
                       #'text.alternativeSelectionForegroundColor' #'text.alternativeSelectionBackgroundColor'
                       #'textView.font' #'text.wordSelectCatchesBlanks'
                       #'text.st80Selections')>

    DefaultViewBackground := StyleSheet colorAt:'textView.background' default:White.
    DefaultSelectionForegroundColor := StyleSheet colorAt:'text.selectionForegroundColor'.
    DefaultSelectionBackgroundColor := StyleSheet colorAt:'text.selectionBackgroundColor'.
"/    DefaultAlternativeSelectionForegroundColor := StyleSheet colorAt:'text.alternativeSelectionForegroundColor' default:DefaultSelectionForegroundColor.
"/    DefaultAlternativeSelectionBackgroundColor := StyleSheet colorAt:'text.alternativeSelectionBackgroundColor' default:DefaultSelectionBackgroundColor.
    DefaultAlternativeSelectionForegroundColor := DefaultSelectionForegroundColor.
    DefaultAlternativeSelectionBackgroundColor := DefaultSelectionBackgroundColor.
    DefaultFont := StyleSheet fontAt:'textView.font'.
    MatchDelayTime := 0.6.
    WordSelectCatchesBlanks := StyleSheet at:'text.wordSelectCatchesBlanks' default:false.
    ST80Selections := StyleSheet at:'text.st80Selections' default:false.

    "Modified: / 31.10.1997 / 13:17:16 / cg"
! !

!TextView class methodsFor:'interface specs'!

searchDialogSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:TextView andSelector:#searchDialogSpec
    "

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #searchDialogSpec
        #window: 
       #(#WindowSpec
          #label: 'String search'
          #name: 'String search'
          #min: #(#Point 10 10)
          #max: #(#Point 1280 1024)
          #bounds: #(#Rectangle 12 22 311 138)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#HorizontalPanelViewSpec
              #name: 'horizontalPanelView'
              #layout: #(#LayoutFrame 0 0.0 -26 1.0 0 1.0 0 1.0)
              #level: 0
              #horizontalLayout: #fitSpace
              #verticalLayout: #center
              #horizontalSpace: 3
              #verticalSpace: 3
              #ignoreInvisibleComponents: true
              #reverseOrderIfOKAtLeft: true
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#ActionButtonSpec
                    #label: 'Cancel'
                    #name: 'cancelButton'
                    #level: 2
                    #translateLabel: true
                    #tabable: true
                    #model: #cancel
                    #extent: #(#Point 95 21)
                  )
                 #(#ActionButtonSpec
                    #label: 'Prev'
                    #name: 'prevButton'
                    #level: 2
                    #translateLabel: true
                    #tabable: true
                    #model: #prevAction
                    #extent: #(#Point 95 21)
                  )
                 #(#ActionButtonSpec
                    #label: 'Next'
                    #name: 'nextButton'
                    #level: 2
                    #borderWidth: 1
                    #translateLabel: true
                    #tabable: true
                    #model: #nextAction
                    #isDefault: true
                    #extent: #(#Point 95 21)
                  )
                 )
               
              )
            )
           #(#LabelSpec
              #label: 'SearchPattern:'
              #name: 'label'
              #layout: #(#LayoutFrame 1 0.0 3 0 -1 1.0 20 0)
              #level: 0
              #translateLabel: true
              #adjust: #left
            )
           #(#ComboBoxSpec
              #name: 'patternComboBox'
              #layout: #(#LayoutFrame 3 0.0 26 0 -3 1.0 48 0)
              #tabable: true
              #model: #searchPattern
              #immediateAccept: false
              #acceptOnLeave: true
              #acceptOnReturn: true
              #acceptOnTab: true
              #acceptOnLostFocus: true
              #acceptOnPointerLeave: false
              #autoSelectInitialText: true
              #comboList: #patternList
            )
           #(#CheckBoxSpec
              #label: 'Ignore case'
              #name: 'ignoreCaseCheckBox'
              #layout: #(#LayoutFrame 3 0.0 54 0 -3 1.0 77 0)
              #level: 0
              #tabable: true
              #model: #ignoreCase
              #translateLabel: true
            )
           )
         
        )
      )
! !

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

    textView := self setupEmpty.
    top := textView topView.
    aFileName notNil ifTrue:[
	f := aFileName asFilename.
	top label:(f baseName).
	textView contents:(f 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:'Compatibility-ST80'!

displaySelection:aBoolean
    "ST-80 compatibility: ignored here."

!

editText:someText
    "ST-80 compatibility: set the edited text."

    self contents:someText

    "Created: / 5.2.2000 / 17:06:18 / cg"
!

selectAndScroll
    "ST-80 compatibility: ignored here."

!

selectionStartIndex
    "ST-80 compatibility: return the selections start character position."

    ^ self characterPositionOfSelection

    "Created: / 19.6.1998 / 00:21:44 / cg"
!

selectionStopIndex
    "ST-80 compatibility: return the character position of
     the character right after the selection."

    |idx|

    idx := self characterPositionOfSelectionEnd.
    idx == 0 ifTrue:[^ 0].
    ^ idx + 1

    "Created: / 19.6.1998 / 00:22:08 / cg"
! !

!TextView methodsFor:'accessing'!

characterPositionOfSelection
    "return the character index of the first character in the selection.
     Returns 0 if there is no selection."

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

    "Modified: 14.8.1997 / 16:35:37 / cg"
!

characterPositionOfSelectionEnd
    "return the character index of the last character in the selection.
     Returns 0 if there is no selection."

    selectionStartLine isNil ifTrue:[^ 0].
    ^ self characterPositionOfLine:selectionEndLine
                               col:selectionEndCol

    "Created: 14.8.1997 / 16:35:24 / cg"
    "Modified: 14.8.1997 / 16:35:45 / cg"
!

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

externalEncoding:encodingSymOrNil
    "define how the contents should be encoded when saved
     via the 'save / save as' dialog.
     This is (currently) only passed down from the fileBrowser,
     and required when japanese/chines/korean text is edited.
     (encoding is one of #euc, #sjis, #jis7, #gb, #big5 or #ksc)"

    externalEncoding := encodingSymOrNil
!

parenthesisSpecification
    "return the value of the instance variable 'parenthesisSpecification' (automatically generated)"

    ^ parenthesisSpecification
!

parenthesisSpecification:aDictionary
    "set the dictionary which specifies which characters are opening, which are closing
     and which are ignored characters w.r.t. parenthesis matching.
     See the classes initialize method for a useful value."

    parenthesisSpecification := aDictionary
! !

!TextView methodsFor:'accessing-contents'!

fromFile:aFileName
    "take contents from a named file"

    |f|

    f := aFileName asFilename.
    self directoryForFileDialog:(f directoryName).
    self contents:(f 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"
!

setContents:something
    "set the contents (either a string or a Collection of strings)
     dont change the position (i.e. do not scroll) or the selection."

    |selStartLine selStartCol selEndLine selEndCol selStyle|

    selStartLine := selectionStartLine.
    selStartCol := selectionStartCol.
    selEndLine := selectionEndLine.
    selEndCol := selectionEndCol.
    selStyle := selectStyle.

    super setContents:something.

    selStartLine notNil ifTrue:[
	self 
	    selectFromLine:selStartLine col:selStartCol
	    toLine:selEndLine col:selEndCol.
    ].

    selectStyle := selStyle

    "Modified: / 31.3.1998 / 23:33:21 / cg"
!

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

    self unselect.
    super setList:something
!

text
    "for ST80 compatibility"

    ^ self contents

    "Created: / 19.4.1998 / 12:53:10 / cg"
!

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

selectionBackgroundColor
    "return the selection-background color."

    ^ selectionBgColor
!

selectionForegroundColor
    "return the selection-foreground color."

    ^ selectionFgColor
!

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 onDevice:device.
    selectionBgColor := color2 onDevice: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:'drag & drop'!

allowDrag:aBoolean
    "enable/disable dragging support
    "
    aBoolean ifFalse:[
        dropSource := nil.
    ] ifTrue:[
        dropSource ifNil:[
            dropSource := DropSource 
                            receiver:self
                            argument:nil
                            dropObjectSelector:#collectionOfDragObjects
                            displayObjectSelector:nil
        ]
    ].
!

canDrag
    "returns true if dragging is enabled
    "
    dropSource notNil ifTrue:[
        ^ self hasSelection
    ].
    ^ false
!

collectionOfDragObjects
    "returns collection of dragable objects assigned to selection
     Here, by default, a collection of text-dragObjects is generated;
     however, if a dragObjectConverter is defined, that one gets a chance
     to convert as appropriate.
    "
    |selection|

    selection := self selection.

    selection size == 0 ifTrue:[^ nil].
  ^ Array with:(DropObject newText:selection).
!

dropSource
    "returns the dropSource or nil
    "
    ^ dropSource
!

dropSource:aDropSourceOrNil
    "set the dropSource or nil
    "
    dropSource := aDropSourceOrNil.
! !

!TextView methodsFor:'event handling'!

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:[
        dragIsActive := false.
        ^ self
    ].

    dragIsActive ifTrue:[
        clickPos ifNil:[
            dragIsActive := false.
          ^ self
        ].
        (clickPos dist:(x@y)) >= 5.0 ifTrue:[
            dragIsActive := false.

            self hasSelection ifTrue:[
                dropSource startDragIn:self at:(x@y)
            ]
        ].
        ^ self
    ].

    "is it the select or 1-button ?"
    self sensor leftButtonPressed ifFalse:[^ self].
"/    (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:[viewOrigin x ~~ 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:[
        selectionStartLine notNil ifTrue:[
            ^ self
        ].
        (clickPos isNil 
        or:[(clickPos x - x) abs < 3 
            and:[(clickPos y - y) abs < 3]]) ifTrue:[
            ^ self
        ].
        selectionStartLine := clickLine.
        selectionStartCol := clickCol.
        selectionEndLine := selectionStartLine.
        selectionEndCol := selectionStartCol.

        oldStartLine := selectionStartLine.
        oldEndLine := selectionEndLine.
        oldStartCol := selectionStartCol.
        oldEndCol := selectionEndCol-1.
    ] ifFalse:[
        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

    "Modified: / 28.7.1998 / 16:02:18 / cg"
!

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

    ((button == 1) or:[button == #select]) ifTrue:[
	clickCount notNil ifTrue:[
	    clickCount := clickCount + 1.
	    (clickCount == 2) ifTrue:[
		self doubleClickX:x y:y
	    ] ifFalse:[
		(clickCount == 3) ifTrue:[
		    self tripleClickX:x y:y
		] ifFalse:[
		    (clickCount == 4) ifTrue:[
			self quadClickX:x y:y
		    ]
		]
	    ]
	]
    ] ifFalse:[
	super buttonMultiPress:button x:x y:y
    ]

    "Modified: 11.9.1997 / 04:15:35 / cg"
!

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

    |sensor clickVisibleLine|

    dragIsActive := false.
    sensor       := self sensor.

    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.
        clickPos := x @ y.
        clickCol := self colOfX:x inVisibleLine:clickVisibleLine.
        clickLine := self visibleLineToAbsoluteLine:clickVisibleLine.
        clickStartLine := clickLine.
        clickStartCol := clickCol.

        (self canDrag 
        and:[(self isInSelection:clickLine col:clickCol)
        and:[UserPreferences current startTextDragWithControl not
             or:[sensor ctrlDown]]]) ifTrue:[
            dragIsActive := true
        ] ifFalse:[
            self unselect.
        ].
        clickCount := 1
    ] ifFalse:[
        super buttonPress:button x:x y:y
    ]

    "Modified: / 20.5.1999 / 17:02:45 / 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
        ].
        dragIsActive ifTrue:[
            self unselect
        ].
        clickPos := nil.

    ] ifFalse:[
        super buttonRelease:button x:x y:y
    ].
    dragIsActive := false.

    "/ clickPos := clickLine := clickCol := nil.

    "Modified: / 20.5.1999 / 17:14:23 / cg"
!

doubleClickX:x y:y
    "double-click - select word under pointer"

    |sel ch matchCol scanCol fwdScan|

    ST80Selections == true ifTrue:[
        "/ st80 selects:
        "/   if clicked right after a parenthesis -> select to matching parenthesis
        "/   if clicked at beginning of the line  -> select that line
        "/   if clicked at the top of the text    -> select all
        "/
        clickCol == 1 ifTrue:[
            clickLine == 1 ifTrue:[
                self selectAll.
                ^ self.
            ].
            self selectLineAtY:y.
            selectStyle := #line.
            ^ self
        ].

        matchCol := nil.
        "/ see what is to the left of that character ...
        clickCol > 1 ifTrue:[
            ch := self characterAtLine:clickLine col:clickCol-1.
            ('([{<' includes:ch) ifTrue:[
                matchCol := clickCol - 1
            ] ifFalse:[
                ('"' includes:ch) ifTrue:[
                    scanCol := clickCol - 1.
                    fwdScan := true
                ]
            ]
        ].
        clickCol < (self listAt:clickLine) size ifTrue:[
            ch := self characterAtLine:clickLine col:clickCol+1.
            (')]}>' includes:ch) ifTrue:[
                matchCol := clickCol + 1.
            ] ifFalse:[
                ('"' includes:ch) ifTrue:[
                    scanCol := clickCol + 1.
                    fwdScan := false
                ]
            ]
        ].
        matchCol notNil ifTrue:[
            self searchForAndSelectMatchingParenthesisFromLine:clickLine col:matchCol.
            ^ self
        ].
        scanCol notNil ifTrue:[
            "/ if its an EOL comment, do it differently
            ch := self characterAtLine:clickLine col:clickCol.
            ch == $/ ifTrue:[
                self selectFromLine:clickLine col:clickCol+1 toLine:clickLine+1 col:0.
                ^ self
            ].

            self 
                scanFor:$" fromLine:clickLine col:scanCol forward:fwdScan
                ifFound:[:line :col |
                            |selStart selEnd|

                            fwdScan ifTrue:[
                                selStart := scanCol+1.
                                selEnd := col-1.
                            ] ifFalse:[
                                selStart := scanCol-1.
                                selEnd := col+1.
                            ].
                            self selectFromLine:clickLine col:selStart
                                 toLine:line col:selEnd.
                            ^ self
                           ]
                ifNotFound:[self showNotFound].
            ^ self
        ]
    ].

    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 := viewOrigin x.
                              self selectFromLine:selectionStartLine col:selectionStartCol
                                           toLine:line col:col.

                              self sensor ctrlDown ifFalse:[
                                  "/ undo scroll operation ...
                                  self withCursor:Cursor eye do:[
                                      |delayCount|

                                      moveBack := false.
                                      (')]}>' includes:ch) ifTrue:[
                                           (firstLineShown ~~ prevLine or:[prevCol ~~ viewOrigin x]) ifTrue:[
                                               moveBack := true
                                           ] 
                                      ] ifFalse:[
                                           selectionEndLine > (firstLineShown + nFullLinesShown) ifTrue:[
                                               self makeLineVisible:selectionEndLine.
                                               moveBack := true
                                           ]
                                      ].
                                      moveBack ifTrue:[
                                           delayCount  := 0.
                                           pos1 := x@y. 
                                           self invalidateRepairNow:true.
                                           Delay waitForSeconds:MatchDelayTime. 
                                           delayCount := delayCount + MatchDelayTime. 
                                           [self sensor hasUserEventFor:self] whileFalse:[
                                                Delay waitForSeconds:MatchDelayTime / 2.
                                                delayCount := delayCount + (MatchDelayTime / 2). 
                                                delayCount > 2 ifTrue:[
                                                    self cursor:Cursor eyeClosed.
                                                ].
                                                delayCount >= 2.3 ifTrue:[
                                                    self cursor:Cursor eye.
                                                    delayCount := 0.
                                                ]
                                           ].
                                           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
    ]

    "Created: 11.9.1997 / 04:12:55 / cg"
    "Modified: 19.9.1997 / 06:43:10 / cg"
!

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

    <resource: #keyboard (#Find #Copy #FindNext #FindPrev #FindAgain
                          #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 == #FindAgain) ifTrue:[self searchAgainInSameDirection. ^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)
    "
    (key size > 1 and:[(key at:1) asLowercase == $f]) ifTrue:[
        (('[fF][0-9]' match:key)
        or:['[fF][0-9][0-9]' match:key]) ifTrue:[
            self sensor shiftDown ifTrue:[
                UserPreferences current functionKeySequences
                    at:key put:(self selection)
            ].
            ^ self
        ].
    ].

    super keyPress:key x:x y:y

    "Modified: / 18.4.1997 / 12:12:27 / stefan"
    "Modified: / 3.5.1999 / 15:03:16 / cg"
!

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

quadClickX:x y:y
    "quadrupleClick-click - select all"

    self selectAll

    "Created: / 11.9.1997 / 04:15:24 / cg"
    "Modified: / 31.3.1998 / 14:21:13 / cg"
!

tripleClickX:x y:y
    "triple-click - select line under pointer"

    self selectLineAtY:y.
    selectStyle := #line

    "Created: 11.9.1997 / 04:13:37 / cg"
! !

!TextView methodsFor:'initialization & release'!

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

    super fetchDeviceResources.

    selectionFgColor notNil ifTrue:[selectionFgColor := selectionFgColor onDevice:device].
    selectionBgColor notNil ifTrue:[selectionBgColor := selectionBgColor onDevice: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.
    dragIsActive     := false.

    parenthesisSpecification isNil ifTrue:[
        parenthesisSpecification := DefaultParenthesisSpecification.
    ].

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

    "/ on default allow drag
    self allowDrag:true.
! !

!TextView methodsFor:'menu actions'!

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

    |aStream msg filename|

    filename := aFileName asFilename.

    (FileStream userInitiatedFileSaveQuerySignal queryWith:filename) ifFalse:[
        msg := resources string:'Refused to append to file ''%1'' !!' with:filename name.
        self warn:(msg , '\\(ST/X internal permission check)' ) withCRs.
        ^ self
    ].

    [
        aStream := filename appendingWriteStream.
        self fileOutContentsOn:aStream 
             compressTabs:true 
             encoding:externalEncoding.
        aStream close.
        contentsWasSaved := true
    ] on:FileStream openErrorSignal do:[:ex|
        msg := resources string:'cannot append to file %1 !!' with:filename name.
        self warn:(msg , '\\(' , FileStream lastErrorString , ')' ) withCRs
    ]
!

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 description 
                            , '\\(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
    "return my popUpMenu"

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

    |items m|

    items := #(
                        ('Copy'        copySelection  Copy)
                        ('-'           nil            )
                        ('Search...'   search         Find)
                        ('Goto...'     gotoLine       GotoLine)
                        ('-'           nil            )
                        ('Font...'     changeFont     )
                        ('-'           nil            )
                        ('Save As...'  save           SaveAs)
                        ('Print'       doPrint        Print)
                ).

    m := PopUpMenu itemList:items resources:resources.

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

    "Modified: / 12.11.2001 / 13:43:56 / cg"
!

find
    "same as search - for VW compatibility"

    self search

    "Created: 31.7.1997 / 19:13:58 / cg"
!

gotoLine
    "show a box to enter lineNumber for positioning;
     The entered number may be prefixed by a + or -; 
     in this case, the linenumber is taken relative to the current position."

    |l lineNumberBox input lineToGo relative|

    lineNumberBox :=
        EnterBox
           title:(resources string:'Line number (or +/- relativeNr):')
           okText:(resources string:'Goto')
           abortText:(resources string:'Cancel')
           action:[:l | input := l].

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

    input size > 0 ifTrue:[
        input := input withoutSpaces.
        input size > 0 ifTrue:[
            (input startsWith:$+) ifTrue:[
                relative := 1.
            ] ifFalse:[
                (input startsWith:$-) ifTrue:[
                    relative := -1.
                ].
            ].
            relative notNil ifTrue:[
                input := input copyFrom:2.
            ].
            lineToGo := Integer readFromString:input onError:nil.
            lineToGo notNil ifTrue:[
                relative notNil ifTrue:[
                    lineToGo := self currentLine + (lineToGo * relative)
                ].
                self gotoLine:lineToGo
            ]
        ]
    ].

    "Modified: / 17.5.1998 / 20:07:59 / cg"
!

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

    Dialog
        requestSaveFileName:(resources string:'Save contents in:') 
        default:defaultFileNameForFileDialog 
        fromDirectory:directoryForFileDialog 
        action:[:fileName | self saveAs:fileName] 
        appendAction:[:fileName | self appendTo:fileName]

"/    |fileBox fileName|
"/
"/true ifTrue:[
"/    fileName := FileDialog 
"/                    requestFileName:(resources string:'Save contents in:') 
"/                    default:(defaultFileNameForFileDialog ifNotNil:[defaultFileNameForFileDialog asString])
"/                    ok:(resources string:'Save') 
"/                    abort:nil 
"/                    version:nil 
"/                    ifFail:nil 
"/                    pattern:nil 
"/                    fromDirectory:directoryForFileDialog 
"/                    whenBoxCreatedEvaluate:[:dialog | dialog appendButtonVisibleHolder value:true].
"/
"/    fileName size > 0 ifTrue:[
"/self halt.
"/        self saveAs:fileName.    
"/    ].
"/    ^ self.
"/].
"/    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
"/
"/    fileBox destroy.
"/
"/    "Modified: 16.4.1997 / 20:49:26 / cg"
!

saveAs:fileName
    "save the contents into a file named fileName"
 
    ^ self saveAs:fileName doAppend:false
!

saveAs:aFilename doAppend:doAppend
    "save the contents into a file named fileName;
     if doAppend is true, the views contents is appended to the existing
     contents - otherwise, it overwrites any previous file contents."

    |filename|

    filename := aFilename asFilename.

    self withCursor:Cursor write do:[
        |aStream msg|

        (FileStream userInitiatedFileSaveQuerySignal queryWith:filename) ifFalse:[
            msg := resources string:'Refused to write file ''%1'' !!' with:filename name.
            self warn:(msg , '\\(ST/X internal permission check)' ) withCRs.
            ^ self
        ].

        [
            doAppend ifTrue:[
                aStream := filename appendingWriteStream.
            ] ifFalse:[
                aStream := filename newReadWriteStream.
            ].
            self fileOutContentsOn:aStream 
                 compressTabs:true 
                 encoding:externalEncoding.
            aStream close.
            contentsWasSaved := true
        ] on:FileStream openErrorSignal do:[:ex|
            msg := resources string:'cannot write file ''%1'' !!' with:filename name.
            self warn:(msg , '\\(' , FileStream lastErrorString , ')' ) withCRs
        ].
    ]

    "Modified: 22.10.1997 / 12:32:51 / cg"
!

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

    "
     Q: is it a good idea to preserve the last searchstring between views ?
    "

    |searchBox patternHolder caseHolder 
     pattern fwd ign initialString
     bindings bldr searchAction modal|


    modal := (UserPreferences current searchDialogIsModal).   "/ thats experimental

    ign := lastSearchIgnoredCase ? LastSearchIgnoredCase ? false.
    caseHolder := ign asValue.

    patternHolder := '' asValue.

    lastSearchPattern notNil ifTrue:[
        initialString := lastSearchPattern
    ].
    self hasSelectionWithinSingleLine ifTrue:[
        initialString := self selection
    ].
    initialString isNil ifTrue:[
        LastSearchPatterns size > 0 ifTrue:[
            initialString := LastSearchPatterns first
        ]
    ].

    initialString notNil ifTrue:[
        patternHolder value:initialString.
    ].

    fwd := true. 

    searchAction := [:fwd |
        pattern := patternHolder value.
        pattern := pattern string withoutSeparators. "/ is that a good idea ?
        pattern notEmpty ifTrue:[
            self rememberSearchPattern:pattern.

            ign := caseHolder value.
            LastSearchIgnoredCase := ign.

            fwd ifFalse:[
                lastSearchDirection := #backward.
                self searchBwd:pattern ignoreCase:ign.
            ] ifTrue:[
                lastSearchDirection := #forward.
                self searchFwd:pattern ignoreCase:ign.
            ]
        ]
    ].

    bindings := IdentityDictionary new.
    bindings at:#searchPattern put:patternHolder.
    modal ifTrue:[
        bindings at:#nextAction put:[searchBox doAccept.].
        bindings at:#prevAction put:[fwd := false. searchBox doAccept.].
    ] ifFalse:[
        bindings at:#nextAction put:[searchAction value:true.  "searchBox doAccept."].
        bindings at:#prevAction put:[searchAction value:false. "fwd := false. searchBox doAccept."].
    ].
    bindings at:#ignoreCase put:caseHolder.
    bindings at:#patternList put:LastSearchPatterns.

    modal ifTrue:[
        searchBox := SimpleDialog new.
    ] ifFalse:[
        searchBox := ApplicationModel new.
        searchBox createBuilder.
    ].
    searchBox resources:(self resources).

    bldr := searchBox builder.
    bldr addBindings:bindings.
    searchBox allButOpenFrom:(self class searchDialogSpec).

    (bldr componentAt:#nextButton) cursor:(Cursor thumbsUp).
    (bldr componentAt:#prevButton) cursor:(Cursor thumbsUp).
    (bldr componentAt:#cancelButton) cursor:(Cursor thumbsDown).

    modal ifTrue:[
        searchBox openDialog.
        searchBox accepted ifTrue:[ searchAction value:fwd ].
    ] ifFalse:[
        (bldr componentAt:#nextButton) isReturnButton:false.
        (bldr componentAt:#cancelButton) 
                label:(resources string:'Close');
                action:[searchBox closeRequest].
        "/ searchBox masterApplication:self application.
        self topView beMaster.
        searchBox window 
                beSlave;
                openInGroup:(self windowGroup).

        "/ searchBox window open.
        searchBox window assignKeyboardFocusToFirstInputField.
    ]
! !

!TextView methodsFor:'private'!

currentSelectionBgColor
    ^  selectionBgColor
!

currentSelectionFgColor
    ^ selectionFgColor
!

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

    self 
	fileOutContentsOn:aStream 
	compressTabs:compressTabs 
	encoding:nil
!

fileOutContentsOn:aStream compressTabs:compressTabs encoding:encodingSymOrNil
    "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.
            encodingSymOrNil notNil ifTrue:[
                string := string encodeInto:encodingSymOrNil
            ].
            aStream nextPutAll:string.
            startNr := startNr + 1000 + 1.
        ].
    ] ifFalse:[
        list do:[:aLine |
            aLine notNil ifTrue:[
                encodingSymOrNil notNil ifTrue:[
                    aStream nextPutLine:(aLine encodeInto:encodingSymOrNil)
                ] ifFalse:[
                    aStream nextPutLine:aLine.
                ]
            ] ifFalse:[
                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 onDevice: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"
!

rememberSearchPattern:pattern
    |nRemembered patternString|

    patternString := pattern string.

    nRemembered := NumRememberedSearchPatterns ? 15.

    LastSearchPatterns isNil ifTrue:[
        LastSearchPatterns := OrderedCollection new.
    ].
    "/ move to top or addFirst
    (LastSearchPatterns includes:pattern) ifTrue:[
        LastSearchPatterns remove:pattern.
    ] ifFalse:[
        LastSearchPatterns size > nRemembered ifTrue:[
            LastSearchPatterns removeFirst
        ]
    ].
    LastSearchPatterns addFirst:pattern.
!

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

isTextView
    "I am showing text"

    ^ true
!

specClass
    "redefined, since the name of my specClass is nonStandard (i.e. not TextViewSpec)"

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

    "Modified: / 31.10.1997 / 19:48:35 / cg"
! !

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

drawSelectedFromVisibleLine:startVisLineNr to:endVisLineNr
    startVisLineNr to:endVisLineNr do:[:visLine |
        self drawVisibleLineSelected:visLine 
    ]
!

drawVisibleLineSelected:visLineNr 
    self 
        drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
        inVisible:visLineNr 
        with:self currentSelectionFgColor and:self currentSelectionBgColor
!

drawVisibleLineSelected:visLineNr col:col
    self
        drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
        inVisible:visLineNr 
        col:col 
        with:self currentSelectionFgColor and:self currentSelectionBgColor
!

drawVisibleLineSelected:visLineNr from:selectionStartCol
    self 
        drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
        inVisible:visLineNr 
        from:selectionStartCol
        with:self currentSelectionFgColor and:self currentSelectionBgColor.
!

drawVisibleLineSelected:visLineNr from:startCol to:endCol
    self 
        drawLine:(self withoutAnyColorEmphasis:(self visibleAt:visLineNr))
        inVisible:visLineNr 
        from:startCol to:endCol
        with:self currentSelectionFgColor and:self currentSelectionBgColor.
!

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

    selectionEndLine isNil ifTrue:[
        selectionStartLine := nil
    ].

    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 drawSelectedFromVisibleLine:startVisLineNr to:end.
        ^ 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 drawSelectedFromVisibleLine:line1 to:line2.

    (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:visLineNr
    "redraw visible line lineNr"

    |line|

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

                "its the first line of a multi-line selection"
                (selectionStartCol ~~ 1) ifTrue:[
                    self clearMarginOfVisibleLine:visLineNr with:bgColor.
                    super redrawVisibleLine:visLineNr from:1 to:(selectionStartCol - 1)
                ] ifFalse:[
                    viewOrigin x == 0 ifTrue:[
                        self clearMarginOfVisibleLine:visLineNr with:self currentSelectionBgColor.
                    ]
                ].
                self drawVisibleLineSelected:visLineNr from:selectionStartCol.
                ^ self
            ].

            (line == selectionEndLine) ifTrue:[
                "its the last line of a multi-line selection"
                (selectionEndCol == 0) ifTrue:[
                    ^ super redrawVisibleLine:visLineNr
                ].

                self clearMarginOfVisibleLine:visLineNr with:self currentSelectionBgColor.
                self drawVisibleLineSelected:visLineNr from:1 to:selectionEndCol.
                super redrawVisibleLine:visLineNr from:(selectionEndCol + 1).
                ^ self
            ].

            "its a full line in a multi-line selection"
            self clearMarginOfVisibleLine:visLineNr with:self currentSelectionBgColor.
            self drawVisibleLineSelected:visLineNr.
            ^ self
        ]
    ].
    super redrawVisibleLine:visLineNr

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

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

    |line|

    "/
    "/ care for selection
    "/
    selectionStartLine notNil ifTrue:[
        line := self visibleLineToAbsoluteLine:visLine.
        (line between:selectionStartLine and:selectionEndLine) ifTrue:[
            ((line == selectionStartLine)
            and: [col < selectionStartCol]) ifFalse:[
                ((line == selectionEndLine)
                and: [col > selectionEndCol]) ifFalse:[
                    "its in the selection"
                    self drawVisibleLineSelected:visLine col:col.
                    ^ self.
                ]
            ]
        ]
    ].
    self drawVisibleLine:visLine col:col with:fgColor and:bgColor

    "Modified: / 22.4.1998 / 08:53:05 / cg"
!

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

    |col line|

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

    selectionStartLine notNil ifTrue:[
        line := self visibleLineToAbsoluteLine:visLine.
        (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 drawVisibleLineSelected:visLine from:col. 
            ^ 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 drawVisibleLineSelected:visLine from:startCol to:endCol
    ] 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 drawVisibleLineSelected:visLine from:leftCol to:rightCol.

        "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:self currentSelectionBgColor.
    ].

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

scanFor:aCharacter fromLine:startLine col:startCol forward:forward
                     ifFound:foundBlock 
                  ifNotFound:notFoundBlock
    "search for a character in the direction given by forward. 
     Performs foundBlock with line/col as argument if found, notFoundBlock if not."

    |lineString 
     line   "{ Class: SmallInteger }"
     col    "{ Class: SmallInteger }"
     delta  "{ Class: SmallInteger }"
     endCol "{ Class: SmallInteger }"
     cc     
     maxLine "{ Class: SmallInteger }"
      |

    col := startCol.
    line := startLine.
    forward ifTrue:[
        delta := 1.
    ] ifFalse:[
        delta := -1.
    ].

    lineString := list at:line.
    maxLine := list size.

    col := col + delta.
    [true] whileTrue:[
        lineString notNil ifTrue:[
            forward ifTrue:[
                endCol := lineString size.
            ] ifFalse:[
                endCol := 1
            ].

            col to:endCol by:delta do:[:rCol |
                cc := lineString at:rCol.
                cc == aCharacter ifTrue:[
                    ^ foundBlock value:line value:rCol.
                ]
            ].
        ].
        line := line + delta.
        (line < 1 or:[line > maxLine]) ifTrue:[
            ^ notFoundBlock value
        ].
        lineString := list at:line.
        forward ifTrue:[
            col := 1
        ] ifFalse:[
            col := lineString size
        ]
    ].
    "not reached"

    "Modified: 15.10.1996 / 12:22:30 / cg"
    "Created: 11.9.1997 / 04:36:29 / cg"
!

searchAgainInSameDirection
    "search again in the same direction and -if found- position cursor"

    |ign|

    ign := lastSearchIgnoredCase ? false.

    self setSearchPattern.
    lastSearchPattern notNil ifTrue:[
        lastSearchDirection == #backward ifTrue:[
            self 
                searchBwd:lastSearchPattern 
                ignoreCase:ign
        ] ifFalse:[
            self 
                searchFwd:lastSearchPattern 
                ignoreCase:ign
        ]
    ]

    "Modified: / 3.5.1999 / 15:00:28 / cg"
    "Created: / 3.5.1999 / 15:02:16 / cg"
!

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

    |ign|

    ign := lastSearchIgnoredCase ? false.

    self setSearchPattern.
    lastSearchPattern isNil ifTrue:[
        LastSearchPatterns size > 0 ifTrue:[
            lastSearchPattern := LastSearchPatterns first
        ]
    ].

    lastSearchPattern notNil ifTrue:[
        lastSearchDirection := #backward.
        self rememberSearchPattern:lastSearchPattern.
        self 
            searchBwd:lastSearchPattern 
            ignoreCase:ign
    ]

    "Modified: / 3.5.1999 / 15:00:28 / cg"
!

searchBwd:pattern
    "do a backward search"

    self searchBwd:pattern ifAbsent:[self showNotFound].
    lastSearchIgnoredCase := false.
    lastSearchPattern := pattern string

    "Modified: / 6.3.1999 / 23:46:40 / cg"
!

searchBwd:pattern ifAbsent:aBlock
    "do a backward search"

    |pos startLine startCol|

    pos :=  self startPositionForSearchBackward.
    startLine := pos y.
    startCol := pos x.

    self 
        searchBackwardFor:pattern 
        startingAtLine:startLine col:startCol
        ifFound:[:line :col | 
            self showMatch:pattern atLine:line col:col] 
        ifAbsent:aBlock

    "Modified: 13.9.1997 / 01:05:49 / cg"
!

searchBwd:pattern ignoreCase:ign
    "do a backward search"

    self searchBwd:pattern 
         ignoreCase:ign 
         ifAbsent:[
                    self sensor compressKeyPressEventsWithKey:#FindPrev.
                    self showNotFound
                  ].
    lastSearchIgnoredCase := ign.
    lastSearchPattern := pattern string

    "Created: / 13.9.1997 / 06:18:00 / cg"
    "Modified: / 6.3.1999 / 23:46:47 / cg"
!

searchBwd:pattern ignoreCase:ign ifAbsent:aBlock
    "do a backward search"

    |pos startLine startCol|

    pos :=  self startPositionForSearchBackward.
    startLine := pos y.
    startCol := pos x.

    self 
        searchBackwardFor:pattern 
        ignoreCase:ign
        startingAtLine:startLine col:startCol
        ifFound:[:line :col | self showMatch:pattern atLine:line col:col] 
        ifAbsent:aBlock

    "Modified: 13.9.1997 / 01:05:49 / cg"
    "Created: 13.9.1997 / 06:18:41 / cg"
!

searchForAndSelectMatchingParenthesisFromLine:startLine col:startCol
    "select characters enclosed by matching parenthesis if one is under startLine/Col"

    self 
        searchForMatchingParenthesisFromLine:startLine col:startCol
        ifFound:[:line :col | 
                  self selectFromLine:startLine col:startCol
                               toLine:line col:col]
        ifNotFound:[self showNotFound]
        onError:[self beep]

    "Modified: 9.10.1997 / 12:57:34 / cg"
!

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

    "search for a matching parenthesis; start search with character at startLine/startCol.
     Search for the corresponding character is done forward if its an opening,
     backwards if its a closing parenthesis.
     Evaluate foundBlock with line/col as argument if found, notFoundBlock if not.
     If there is a nesting error, evaluate failBlock."

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

    "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; start search with character at startLine/startCol.
     Search for the corresponding character is done forward if its an opening,
     backwards if its a closing parenthesis.
     Evaluate foundBlock with line/col as argument if found, notFoundBlock if not.
     If there is a nesting error, evaluate failBlock."

    ^ self
        searchForMatchingParenthesisFromLine:startLine col:startCol
        ifFound:foundBlock 
        ifNotFound:notFoundBlock
        onError:failBlock
        openingCharacters: (parenthesisSpecification at:#open)  "/ #( $( $[ ${ "$> $<") 
        closingCharacters: (parenthesisSpecification at:#close) "/ #( $) $] $} "$> $<")
        ignoredCharacters: ignoreSet
        specialEOLComment: (parenthesisSpecification at:#eolComment) "/

"/    |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 anySet|
"/
"/    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 := #( $( $[ ${ "$<" ).
"/    ].
"/    anySet := Set new.
"/    anySet addAll:incSet; addAll:decSet; addAll:ignoreSet.
"/    anySet := (anySet select:[:c | c isCharacter]) asString.
"/
"/    nesting := 1.
"/    ignoring := false.
"/    lineString := list at:line.
"/    maxLine := list size.
"/
"/    col := col + delta.
"/    [nesting ~~ 0] whileTrue:[
"/        (lineString notNil
"/        and:[lineString includesAny:anySet]) 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.
"/
"/                "/ check for comments.
"/
"/                ((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"
!

searchForMatchingParenthesisFromLine:startLine col:startCol
                     ifFound:foundBlock 
                  ifNotFound:notFoundBlock
                     onError:failBlock
           openingCharacters:openingCharacters
           closingCharacters:closingCharacters
           ignoredCharacters:ignoreSet
          specialEOLComment:eolCommentSequence

    "search for a matching parenthesis; start search with character at startLine/startCol.
     Search for the corresponding character is done forward if its an opening,
     backwards if its a closing parenthesis.
     Evaluate foundBlock with line/col as argument if found, notFoundBlock if not.
     If there is a nesting error, evaluate 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 anySet
     eol1 eol2|

    self assert:(openingCharacters size == closingCharacters size).

    charSet := openingCharacters , closingCharacters.

    parChar := self characterAtLine:startLine col:startCol.
    i := charSet indexOf:parChar.
    i == 0 ifTrue:[
        ^ failBlock value   "not a parenthesis"
    ].

    direction := ((openingCharacters collect:[:c | #fwd]) , (closingCharacters collect:[:c | #bwd])) at:i.
    closingChar := (closingCharacters , openingCharacters) at:i.

    eol1 := eolCommentSequence at:1 ifAbsent:nil.
    eol2 := eolCommentSequence at:2 ifAbsent:nil.

    col := startCol.
    line := startLine.
    direction == #fwd ifTrue:[
        delta := 1.
        incSet := openingCharacters.
        decSet := closingCharacters.
    ] ifFalse:[
        delta := -1.
        incSet := closingCharacters.
        decSet := openingCharacters.
    ].
    anySet := Set new.
    anySet addAll:incSet; addAll:decSet; addAll:ignoreSet.
    anySet := (anySet select:[:c | c isCharacter]) asString.

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

    col := col + delta.
    [nesting ~~ 0] whileTrue:[
        (lineString notNil
        and:[lineString includesAny:anySet]) 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.

                "/ check for comments.

                ((cc == eol1 and:[nextCC == eol2])
                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"

    |ign|

    ign := lastSearchIgnoredCase ? false.

    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.

    lastSearchPattern isNil ifTrue:[
        LastSearchPatterns size > 0 ifTrue:[
            lastSearchPattern := LastSearchPatterns first
        ]
    ].

    lastSearchPattern notNil ifTrue:[
        self rememberSearchPattern:lastSearchPattern.
        lastSearchDirection := #forward.
        self 
            searchFwd:lastSearchPattern
            ignoreCase:ign
    ]

    "Modified: / 3.5.1999 / 15:00:40 / cg"
!

searchFwd:pattern
    "do a forward search"

    self searchFwd:pattern ifAbsent:[self showNotFound].
    lastSearchIgnoredCase := false.
    lastSearchPattern := pattern string

    "Modified: / 6.3.1999 / 23:46:53 / cg"
!

searchFwd:pattern ifAbsent:aBlock
    "do a forward search"

    |pos startLine startCol|

    pos :=  self startPositionForSearchForward.
    startLine := pos y.
    startCol := pos x.

    self 
        searchForwardFor:pattern startingAtLine:startLine col:startCol
        ifFound:[:line :col | self showMatch:pattern atLine:line col:col]
        ifAbsent:aBlock

    "Modified: 13.9.1997 / 01:05:35 / cg"
!

searchFwd:pattern ignoreCase:ign
    "do a forward search"

    self 
        searchFwd:pattern 
        ignoreCase:ign 
        ifAbsent:[
                    self sensor compressKeyPressEventsWithKey:#FindNext.
                    self showNotFound
                 ].
    lastSearchIgnoredCase := ign.
    lastSearchPattern := pattern string

    "Created: / 13.9.1997 / 06:18:13 / cg"
    "Modified: / 6.3.1999 / 23:46:58 / cg"
!

searchFwd:pattern ignoreCase:ign ifAbsent:aBlock
    "do a forward search"

    |pos startLine startCol|

    pos :=  self startPositionForSearchForward.
    startLine := pos y.
    startCol := pos x.

    self 
        searchForwardFor:pattern 
        ignoreCase:ign
        startingAtLine:startLine col:startCol
        ifFound:[:line :col | self showMatch:pattern atLine:line col:col]
        ifAbsent:aBlock

    "Modified: 13.9.1997 / 01:05:35 / cg"
    "Created: 13.9.1997 / 06:18:27 / cg"
!

searchPattern
    "return the last search pattern"

    ^ lastSearchPattern
!

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

    |sel|

"/    clickPos isNil ifTrue:[^ self].

    sel := self selection.
    sel notNil ifTrue:[
        self setSearchPattern:sel asString withMatchEscapes 
    ]

    "Modified: / 6.3.1999 / 23:48:04 / cg"
!

setSearchPattern:aString
    "set the searchpattern for future searches"

    aString isNil ifTrue:[
        lastSearchPattern := aString 
    ] ifFalse:[
        lastSearchPattern := aString asString withoutSeparators string
    ].

    "Modified: / 6.3.1999 / 23:47:36 / cg"
!

setSearchPattern:aString ignoreCase:aBoolean
    "set the searchpattern and caseIgnore for future searches"

    self setSearchPattern:aString.
    lastSearchIgnoredCase := aBoolean.
!

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.
    ] ensure:[
        self cursor:savedCursor
    ]

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

startPositionForSearchBackward
    |startLine startCol|

    selectionStartLine notNil ifTrue:[
        startLine := selectionStartLine.
        startCol := selectionStartCol
    ] ifFalse:[
        startLine := 1.
        startCol := 1
    ].

    ^ startCol @ startLine
!

startPositionForSearchForward
    |startLine startCol|

    selectionStartLine notNil ifTrue:[
        startLine := selectionStartLine.
        startCol := selectionStartCol
    ] ifFalse:[
        startLine := 1.
        startCol := 1
    ].

    ^ startCol @ startLine
! !

!TextView methodsFor:'selections'!

changeTypeOfSelectionTo:newType
    "ignored here - but redefined in subclasses which
     differentiate between pasted- and user-selections"
!

expandSelectionDown
    |l t|

    selectionStartLine notNil ifTrue:[
        expandingTop == true 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 validateNewSelection.
        self redrawFromLine:l to: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 == true 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 validateNewSelection.
        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 == true 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 validateNewSelection.
        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 == true 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 validateNewSelection.
        "/ self redrawLine:l. 
        "/ self redrawLine:l+1. 
        self redrawFromLine:l to:l+1.
        self makeSelectionVisible.
    ].

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

hasSelection
    "return true, if there is a selection"

    ^ selectionStartLine notNil
!

hasSelectionForCopy
    "return true, if there is a selection which can be copyied
     (the same as #hasSelection, except for editfields in password-mode)"

    ^ self hasSelection
!

hasSelectionWithinSingleLine
    "return true, if there is a selection and it is within a line"

    ^ selectionStartLine notNil
      and:[ selectionStartLine == selectionEndLine ]
!

isInSelection:line col:aColNr
    "returns true, if the line, and column is in the selection
    "
    selectionStartLine ifNil:[^ false].
    selectionEndLine   ifNil:[^ false].

    (line between:selectionStartLine and:selectionEndLine) ifFalse:[
        ^ false
    ].

    line == selectionStartLine ifTrue:[
        aColNr < selectionStartCol ifTrue:[^ false]
    ].

    line == selectionEndLine ifTrue:[
        (selectionEndCol ~~ 0 and:[selectionEndCol < aColNr]) ifTrue:[^ false]
    ].
    ^ true
!

makeSelectionVisible
    "scroll to make the selection visible"

    |line col|

    selectionStartLine notNil ifTrue:[
        expandingTop == true 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"

    |selectLine|

    selectLine := self lineAtY:y. "/ self visibleLineToListLine:(self visibleLineOfY:y).
    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:selectVisibleLine.
	self selectWordAtLine:selectLine col:selectCol
    ]

    "Modified: / 8.9.1998 / 21:22:46 / cg"
!

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

    selectionStartLine isNil ifTrue:[^ nil].
    ^ self textFromLine:selectionStartLine col:selectionStartCol toLine:selectionEndLine col:selectionEndCol

    "Modified: / 22.2.2000 / 23:54:54 / cg"
!

selectionAsString
    "return the selection as a String (i.e. without emphasis)"

    |sel|

    (sel := self selection) isNil ifTrue:[^ nil].
    sel := sel collect:[:each| each isNil ifTrue:[nil] ifFalse:[each string]].
    ^ (sel asStringWithCRsFrom:1 to:(sel size) compressTabs:false withCR:false) string
!

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 := selectionEndLine := nil.
!

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.205 2003-06-03 18:08:17 cg Exp $'
! !

TextView initialize!