ETxtView.st
author Claus Gittinger <cg@exept.de>
Mon, 06 Sep 1999 14:57:31 +0200
changeset 2005 9b1ff373a8ad
parent 1993 5ffe0b3943cd
permissions -rw-r--r--
moved opaqueResize setting to userPreferences

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

TextView subclass:#EditTextView
	instanceVariableNames:'cursorLine cursorVisibleLine cursorCol cursorShown
		prevCursorState readOnly modifiedChannel fixedSize exceptionBlock
		cursorFgColor cursorBgColor cursorNoFocusFgColor cursorType
		cursorTypeNoFocus undoAction typeOfSelection lastString
		lastReplacement lastAction replacing showMatchingParenthesis
		hasKeyboardFocus acceptAction lockUpdates tabMeansNextField
		autoIndent insertMode trimBlankLines wordWrap
		replacementWordSelectStyle acceptChannel acceptEnabled st80Mode'
	classVariableNames:'DefaultCursorForegroundColor DefaultCursorBackgroundColor
		DefaultCursorType DefaultCursorNoFocusForegroundColor ST80Mode
		DefaultCursorTypeNoFocus'
	poolDictionaries:''
	category:'Views-Text'
!

!EditTextView 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 editable text - adds editing functionality to TextView
    Also, it adds accept functionality, and defines a new actionBlock: 
    acceptAction to be performed for accept

    If used with a model, this is informed by sending it a changeMsg with
    the current contents as argument.
    (however, it is possible to define both changeMsg and acceptAction)

    Please read the historic notice in the ListView class.

    [Instance variables:]

	cursorLine              <Number>        line where cursor sits (1..)

	cursorVisibleLine       <Number>        visible line where cursor sits (1..nLinesShown)

	cursorCol               <Number>        col where cursor sits (1..)

	cursorShown             <Boolean>       true, if cursor is currently shown

	readOnly                <Boolean>       true, if text may not be edited

	modifiedChannel         <ValueHolder>   holding true, if text has been modified.
						cleared on accept.

	acceptChannel           <ValueHolder>   holding true, if text has been accepted.

	fixedSize               <Boolean>       true, if no lines may be added/removed

	exceptionBlock          <Block>         block to be evaluated when readonly text is about to be modified
						if it returns true, the modification will be done anyway.
						if it returns anything else, the modification is not done.

	cursorFgColor           <Color>         color used for cursor drawing
	cursorBgColor           <Color>         color used for cursor drawing

	cursorType              <Symbol>        how the cursor is drawn; currently implemented
						are #block (solid-block cursor), #ibeam
						(vertical bar at insertion point) 
						and #caret (caret below insertion-point)

	cursorTypeNoFocus       <Symbol>        like above, if view has no focus
						nil means: hide the cursor.

	undoAction              <Block>         block which undoes last cut, paste or replace
						(not yet fully implemented)

	typeOfSelection         <Symbol>        #paste, if selection created by paste, nil otherwise
						this affects the next keyPress: if #paste it does not
						replace; otherwise it replaces the selection.

	lastCut                 <String>        last cut or replaced string

	lastReplacement         <String>        last replacement

	replacing               <Boolean>       true if entered characters replace last selection

	showMatchingParenthesis <Boolean>       if true, shows matching parenthesis
						when entering one; this is the default.

	hasKeyboardFocus        <Boolean>       true if this view has the focus

	acceptAction            <Block>         accept action - evaluated passing the contents as 
						argument 

	tabMeansNextField       <Boolean>       if true, Tab is ignored as input and shifts keyboard
						focus to the next field. For editTextViews, this is false
						by default (i.e. tabs can be entered into the text).
						For some subclasses (inputFields), this may be true.

	trimBlankLines          <Boolean>       if true, trailing blanks are
						removed when editing.
						Default is true.

	wordWrap                <Boolean>       Currently not used.

	lockUpdates             <Boolean>       internal, private

	prevCursorState         <Boolean>       temporary, private


    class variables:
	ST80Mode                <Boolean>       if true, cursor positioning is
						done as in vi or ST80; i.e.
						wysiwyg mode is somewhat relaxed,
						in that the cursor cannot be
						positioned behind a lines end.
						This is not yet completely implemented.
    used globals:

	DeleteHistory           <Text>          last 1000 lines of deleted text
						(but only if this variable exists already)

    [styleSheet parameters:]

	textCursorForegroundColor <Color>       cursor fg color; default: text background
	textCursorBackgroundColor <Color>       cursor bg color; default: text foreground
	textCursorNoFocusForegroundColor 
				  <Color>       cursor fg color if no focus; default: cursor fg color
	textCursorType            <Symbol>      cursor type; default:  #block

    [author:]
	Claus Gittinger

    [see also:]
	CodeView Workspace TextView ListView
	EditField
"
!

examples
"
  non MVC operation:

    basic setup:
									[exBegin]
	|top textView|

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

	textView := EditTextView new.
	textView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
	top addSubView:textView.

	textView contents:('/etc/hosts' asFilename contentsOfEntireFile).

	top open.
									[exEnd]


    with vertical scrollbar:
									[exBegin]
	|top scrollView textView|

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

	scrollView := ScrollableView for:EditTextView.
	textView := scrollView scrolledView.
	scrollView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
	top addSubView:scrollView.

	textView contents:('/etc/hosts' asFilename contentsOfEntireFile).

	top open.
									[exEnd]


    with horizontal & vertical scrollbars:
									[exBegin]
	|top scrollView textView|

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

	scrollView := HVScrollableView for:EditTextView.
	textView := scrollView scrolledView.
	scrollView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
	top addSubView:scrollView.

	textView contents:('/etc/hosts' asFilename contentsOfEntireFile).

	top open.
									[exEnd]


    set the action for accept:
									[exBegin]
	|top textView|

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

	textView := EditTextView new.
	textView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
	top addSubView:textView.

	textView contents:('/etc/hosts' asFilename contentsOfEntireFile).
	textView acceptAction:[:contents |
				Transcript showCR:'will not overwrite the file with:'.
				Transcript showCR:contents asString
			      ].
	top open.
									[exEnd]



    non-string (text) items:
									[exBegin]
	|top textView list|

	list := '/etc/hosts' asFilename contentsOfEntireFile asStringCollection.
	1 to:list size by:2 do:[:nr |
	    list at:nr put:(Text string:(list at:nr)
				 emphasis:(Array with:#bold with:(#color->Color red)))
	].

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

	textView := EditTextView new.
	textView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
	top addSubView:textView.

	textView contents:list.
	top open.
									[exEnd]



  MVC operation:
    (the examples model here is a plug simulating a real model;
     real world applications would not use a plug ..)
									[exBegin]
	|top textView model|

	model := Plug new.
	model respondTo:#accepted:
		   with:[:newContents | 
				Transcript showCR:'will not overwrite the file with:'.
				Transcript showCR:newContents asString
			].
	model respondTo:#getList
		   with:['/etc/hosts' asFilename contentsOfEntireFile].

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

	textView := EditTextView new.
	textView origin:0.0 @ 0.0 corner:1.0 @ 1.0.
	top addSubView:textView.

	textView listMessage:#getList;
		 model:model;
		 changeMessage:#accepted:;
		 aspect:#list.
	top open.
									[exEnd]


    two textViews on the same model:
									[exBegin]
	|top1 textView1 top2 textView2 model currentContents|

	model := Plug new.
	model respondTo:#accepted:
		   with:[:newContents |
				Transcript showCR:'accepted:'.
				Transcript showCR:newContents asString.
				currentContents := newContents.
				model changed:#contents
			].
	model respondTo:#getList
		   with:[Transcript showCR:'query'.
			 currentContents].


	top1 := StandardSystemView new.
	top1 extent:300@200.

	textView1 := EditTextView new.
	textView1 origin:0.0 @ 0.0 corner:1.0 @ 1.0.
	top1 addSubView:textView1.

	textView1 listMessage:#getList;
		  model:model;
		  aspect:#contents;
		  changeMessage:#accepted:.
	top1 open.

	top2 := StandardSystemView new.
	top2 extent:300@200.

	textView2 := EditTextView new.
	textView2 origin:0.0 @ 0.0 corner:1.0 @ 1.0.
	top2 addSubView:textView2.

	textView2 listMessage:#getList;
		  model:model;
		  aspect:#contents;
		  changeMessage:#accepted:.
	top2 open.
									[exEnd]
"
! !

!EditTextView class methodsFor:'defaults'!

st80Mode
    "return true, if the st80 editing mode is turned on.
     This setting affects the behavior of the cursor, when positioned
     behond the end of a line or the end of the text.
     The default is initialized from the viewStyle."

    ^ ST80Mode

   "
    EditTextView st80Mode:true
    EditTextView st80Mode:false
   "

    "Modified: / 16.1.1998 / 22:54:57 / cg"
!

st80Mode:aBoolean
    "turns on/off st80 behavior, where the cursor cannot be positioned
     behond the end of a line or the last line"

    ST80Mode := aBoolean.

   "
    EditTextView st80Mode:true
    EditTextView st80Mode:false
   "

    "Modified: / 16.1.1998 / 22:55:19 / cg"
!

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

    <resource: #style (#'textCursor.foregroundColor' #'textCursor.backgroundColor'
                       #'textCursor.noFocusForegroundColor' 
                       #'textCursor.type' #'textCursor.typeNoFocus'
                       #'editText.st80Mode')>

    DefaultCursorForegroundColor := StyleSheet colorAt:'textCursor.foregroundColor'.
    DefaultCursorBackgroundColor := StyleSheet colorAt:'textCursor.backgroundColor'.
    DefaultCursorNoFocusForegroundColor := StyleSheet colorAt:'textCursor.noFocusForegroundColor'.
    DefaultCursorType := StyleSheet at:'textCursor.type' default:#block.
    DefaultCursorTypeNoFocus := StyleSheet at:'textCursor.typeNoFocus'.

    ST80Mode := StyleSheet at:'editText.st80Mode' default:false.

    "
     self updateStyleCache
    "

    "Modified: / 20.5.1998 / 04:27:41 / cg"
! !

!EditTextView methodsFor:'ST-80 compatibility'!

autoAccept:aBoolean
    "ignored for now"

    "Created: / 5.6.1998 / 15:30:32 / cg"
!

continuousAccept:aBoolean
    "ignored for now"

    "Created: / 19.6.1998 / 00:03:49 / cg"
!

enabled:aBoolean

    self readOnly:aBoolean not

    "Created: / 30.3.1999 / 15:10:23 / stefan"
    "Modified: / 30.3.1999 / 15:10:53 / stefan"
!

textHasChanged
    ^ self modified

    "Created: / 19.6.1998 / 00:09:43 / cg"
! !

!EditTextView methodsFor:'ST-80 compatibility editing'!

cutSelection
    self cut

    "Created: / 31.10.1997 / 03:29:50 / cg"
!

deselect
    "remove the selection"

    ^ self unselect

    "Created: / 19.6.1998 / 02:41:54 / cg"
!

find:pattern
    self searchFwd:pattern ifAbsent:nil

    "Created: / 29.1.1999 / 19:09:42 / cg"
    "Modified: / 29.1.1999 / 19:10:12 / cg"
!

insert:aString at:aCharacterPosition
    "insert a string at aCharacterPosition."

    |line col|

    line := self lineOfCharacterPosition:aCharacterPosition.
    col := aCharacterPosition - (self characterPositionOfLine:line col:1) + 1.
    col < 1 ifTrue:[
        col := 1
    ].
    self insertString:aString atLine:line col:col.

    "
     |top v|

     top := StandardSystemView new.
     top extent:300@300.
     v := EditTextView origin:0.0@0.0 corner:1.0@1.0 in:top.
     top openAndWait.
     v contents:'1234567890\1234567890\1234567890\' withCRs.
     v insert:'<- hello there' at:5.
    "

    "Modified: / 5.4.1998 / 17:20:08 / cg"
!

insertAndSelect:aString at:aCharacterPosition
    "insert a selected string at aCharacterPosition."

    |line col|

    line := self lineOfCharacterPosition:aCharacterPosition.
    col := aCharacterPosition - (self characterPositionOfLine:line col:1) + 1.
    self insertString:aString atLine:line col:col.
    self selectFromLine:line col:col toLine:line col:col + aString size - 1
    "
     |v|

     v := EditTextView new openAndWait.
     v contents:'1234567890\1234567890\1234567890\' withCRs.
     v insertAndSelect:'<- hello there' at:5.
    "
!

pasteSelection
    self paste

    "Created: / 31.10.1997 / 03:28:53 / cg"
!

replaceSelectionWith:aString
    ^ self replaceSelectionBy:aString

    "Created: / 19.6.1998 / 02:42:32 / cg"
!

selectAt:pos
    "move the cursor before cursorPosition."

    self cursorToCharacterPosition:pos

    "Modified: / 19.6.1998 / 02:41:28 / cg"
    "Created: / 19.6.1998 / 02:43:39 / cg"
!

selectFrom:startPos to:endPos
    "change the selection given two aCharacterPositions."

    |line1 col1 line2 col2|

    startPos > endPos ifTrue:[
        ^ self unselect
    ].

    line1 := self lineOfCharacterPosition:startPos.
    col1 := startPos - (self characterPositionOfLine:line1 col:1) + 1.
    col1 < 1 ifTrue:[
        col1 := 1
    ].
    line2 := self lineOfCharacterPosition:endPos.
    col2 := startPos - (self characterPositionOfLine:line2 col:1) + 1.
    col2 < 1 ifTrue:[
        col2 := 1
    ].
    self selectFromLine:line1 col:col1 toLine:line2 col:col2

    "Modified: / 19.6.1998 / 02:41:28 / cg"
! !

!EditTextView methodsFor:'accessing-behavior'!

acceptAction
    "return the action to be performed on accept (or nil)"

    ^ acceptAction
!

acceptAction:aBlock
    "set the action to be performed on accept"

    acceptAction := aBlock
!

acceptEnabled:aBoolean
    "enable/disable accept. This greys the corresponding item in the menu"

    acceptEnabled := aBoolean

    "Created: 7.3.1997 / 11:04:34 / cg"
!

autoIndent:aBoolean
    autoIndent := aBoolean

    "Created: 5.3.1996 / 14:37:50 / cg"
!

exceptionBlock:aBlock
    "define the action to be triggered when user tries to modify
     readonly text"

    exceptionBlock := aBlock
!

insertMode:aBoolean
    insertMode := aBoolean

    "Created: 6.3.1996 / 12:24:05 / cg"
!

tabMeansNextField:aBoolean
    "set/clear tabbing to the next field.
     If true, Tab is ignored and shifts the keyboard focus.
     If false, tabs can be entered into the text.
     The default is true for editTextView, false for single-line
     input fields."

    tabMeansNextField := aBoolean
! !

!EditTextView methodsFor:'accessing-contents'!

acceptChannel
    "return the valueHolder holding true if text was accepted.
     By placing a true into this channel, an accept can also be forced."

    ^ acceptChannel

    "Modified: / 30.1.1998 / 14:17:11 / cg"
!

acceptChannel:aValueHolder
    "set the valueHolder holding true if text was accepted.
     By placing a true into this channel, an accept can also be forced."

    |prev|

    prev := acceptChannel.
    acceptChannel := aValueHolder.
    self setupChannel:aValueHolder for:nil withOld:prev

    "Created: / 30.1.1998 / 14:51:09 / cg"
!

accepted
    "return true if text was accepted"

    ^ acceptChannel value

    "Created: 14.2.1997 / 16:43:46 / cg"
!

accepted:aBoolean
    "set/clear the accepted flag.
     This may force my current contents to be placed into my model."

    acceptChannel value:aBoolean.

    "Created: / 14.2.1997 / 16:44:01 / cg"
    "Modified: / 30.1.1998 / 14:20:15 / cg"
!

at:lineNr basicPut:aLine
    "change a line without change notification"

    (self at:lineNr) = aLine ifFalse:[
        super at:lineNr put:aLine.
    ].
!

at:lineNr put:aLine
    (self at:lineNr) = aLine ifFalse:[
	super at:lineNr put:aLine.
	self textChanged
    ].
!

characterBeforeCursor
    "return the character under the cursor - space if behond line.
     For non-block cursors, this is the character immediately to the right
     of the insertion-bar or caret."

    cursorCol == 1 ifTrue:[^ nil].

    ^ self characterAtLine:cursorLine col:cursorCol-1

    "Created: / 17.6.1998 / 15:16:41 / cg"
!

characterUnderCursor
    "return the character under the cursor - space if behond line.
     For non-block cursors, this is the character immediately to the right
     of the insertion-bar or caret."

    ^ self characterAtLine:cursorLine col:cursorCol
!

contents
    "return the contents as a String"

    list isNil ifTrue:[^ ''].
    self removeTrailingBlankLines.
    ^ list asStringWithCRs
!

cursorCol
    "return the cursors col (1..).
     This is the absolute col; NOT the visible col"

    ^ cursorCol
!

cursorLine
    "return the cursors line (1..). 
     This is the absolute line; NOT the visible line"

    ^ cursorLine
!

fixedSize
    "make the texts size fixed (no lines may be added).
     OBSOLETE: use readOnly"

    self obsoleteMethodWarning:'use #readOnly:'.
    readOnly == true ifFalse:[
        readOnly := true.
        middleButtonMenu notNil ifTrue:[
            middleButtonMenu disableAll:#(cut paste replace indent)
        ]
    ]

    "Modified: 14.2.1997 / 17:35:24 / cg"
!

isReadOnly
    "return true, if the text is readonly."

    ^ readOnly value

    "Modified: 14.2.1997 / 17:35:56 / cg"
!

list:something
    "position cursor home when setting contents"

    super list:something.
    self cursorHome
!

modified
    "return true if text was modified"

    ^ modifiedChannel value
!

modified:aBoolean
    "set/clear the modified flag"

    modifiedChannel value:aBoolean

    "Modified: 14.2.1997 / 16:44:05 / cg"
!

modifiedChannel
    "return the valueHolder holding true if text was modified"

    ^ modifiedChannel
!

modifiedChannel:aValueHolder
    "set the valueHolder holding true if text was modified"

    |prev|

    prev := modifiedChannel.
    modifiedChannel := aValueHolder.
    self setupChannel:aValueHolder for:nil withOld:prev

    "Created: / 30.1.1998 / 14:51:32 / cg"
!

readOnly
    "make the text readonly.
     Somewhat obsolete - use #readOnly:"

    self obsoleteMethodWarning:'use #readOnly:'.
    readOnly := true

    "Modified: 14.2.1997 / 17:35:56 / cg"
!

readOnly:aBoolean
    "make the text readonly (aBoolean == true) or writable (aBoolean == false).
     The argument may also be a valueHolder."

    readOnly := aBoolean

    "Created: 14.2.1997 / 17:35:39 / cg"
!

setContents:something
    |selType|

    selType := typeOfSelection.
    super setContents:something.
    typeOfSelection := selType.

    "Created: / 31.3.1998 / 23:35:06 / cg"
! !

!EditTextView methodsFor:'accessing-look'!

cursorForegroundColor:color1 backgroundColor:color2
    "set both cursor foreground and cursor background colors"

    |wasOn|

    wasOn := self hideCursor.
    cursorFgColor := color1 onDevice:device.
    cursorBgColor := color2 onDevice:device.
    wasOn ifTrue:[self showCursor]
!

cursorType
    "return the style of the text cursor.
     Currently, supported are: #block, #frame, #ibeam, #caret, #solidCaret
                               #bigCaret and #bigSolidCaret"

    ^ cursorType

    "Modified: / 5.5.1999 / 14:52:33 / cg"
!

cursorType:aCursorTypeSymbol
    "set the style of the text cursor.
     Currently, supported are: #block, #frame, #ibeam, #caret, #solidCaret
			       #bigCaret and #bigSolidCaret"

    cursorType := aCursorTypeSymbol.

    "Created: 21.9.1997 / 13:42:23 / cg"
    "Modified: 21.9.1997 / 13:43:35 / cg"
!

cursorTypeNoFocus
    "return the style of the text cursor when the view has no focus.
     If left unspecified, this is the same as the regular cursorType."

    ^ cursorTypeNoFocus

    "Created: / 5.5.1999 / 14:52:46 / cg"
!

cursorTypeNoFocus:aCursorTypeSymbol
    "set the style of the text cursor when the view has no focus.
     If left unspecified, this is the same as the regular cursorType."

    cursorTypeNoFocus := aCursorTypeSymbol
! !

!EditTextView methodsFor:'change & update '!

accept
    "accept the current contents by executing the accept-action and/or
     changeMessage."

    acceptEnabled == false ifTrue:[
        device beep.
        ^ self
    ].

    lockUpdates := true.

    "/
    "/ ST-80 way of doing it
    "/
    model notNil ifTrue:[
        self sendChangeMessageWith:self argForChangeMessage.
    ].

    "/
    "/ ST/X way of doing things
    "/ as a historic (and temporary) leftover,
    "/ the block is called with a stringCollection
    "/ - not with the actual string
    "/
    acceptAction notNil ifTrue:[
        acceptAction value:self list
    ].

    "/ NO - must be manually reset by application
    "/ self modified:false.

    "/ self accepted:true.
    "/ changed to:
    acceptChannel value:true withoutNotifying:self.

    lockUpdates := false.

    "Modified: / 30.1.1998 / 14:19:00 / cg"
!

argForChangeMessage
    "return the argument to be passed with the change notification.
     Defined as separate method for easier subclassability."

    ^ self contents

    "Modified: 29.4.1996 / 12:42:14 / cg"
!

getListFromModel
    "get my contents from the model.
     Redefined to ignore updates resulting from my own changes
     (i.e. if lockUpdates is true)."

    "
     ignore updates from my own change
    "
    lockUpdates ifTrue:[
	lockUpdates := false.
	^ self
    ].
    ^ super getListFromModel

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

update:something with:aParameter from:changedObject
    changedObject == acceptChannel ifTrue:[
        acceptChannel value == true ifTrue:[ 
            self accept.
        ].
        ^ self.
    ].
    super update:something with:aParameter from:changedObject

    "Created: / 30.1.1998 / 14:15:56 / cg"
    "Modified: / 1.2.1998 / 13:15:55 / cg"
! !

!EditTextView methodsFor:'cursor handling'!

cursorBacktab
    "move cursor to prev tabstop"

    self cursorCol:(self prevTabBefore:cursorCol).
!

cursorCol:newCol
    "move cursor to some column in the current line"

    |wasOn|

    wasOn := self hideCursor.
    cursorCol := self validateCursorCol:newCol inLine:cursorLine.
    self makeCursorVisibleAndShowCursor:wasOn.

    "Modified: 22.5.1996 / 14:25:53 / cg"
!

cursorDown
    "move cursor down; scroll if at end of visible text;
     beep if at end of physical text."

    |wasOn|

    self cursorDown:1.

    "/ cursor behond text ?
    cursorLine > list size ifTrue:[
        wasOn := self hideCursor.
        cursorLine := self validateCursorLine:(list size + 1).
        cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
        "/ wasOn ifTrue:[self showCursor].
        self makeCursorVisibleAndShowCursor:wasOn.
        self beep.
    ].

    "Modified: / 10.6.1998 / 17:00:23 / cg"
!

cursorDown:n
    "move cursor down by n lines; scroll if at end of visible text"

    |wasOn nv|

    cursorVisibleLine notNil ifTrue:[
        wasOn := self hideCursor.
        nv := cursorVisibleLine + n - 1.
        (nv >= nFullLinesShown) ifTrue:[
            self scrollDown:(nv - nFullLinesShown + 1)
        ].
        cursorLine := self validateCursorLine:(cursorLine + n).
        cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
        "/ wasOn ifTrue:[self showCursor].
        self makeCursorVisibleAndShowCursor:wasOn.
    ] ifFalse:[
        cursorLine isNil ifTrue:[
            cursorLine := firstLineShown
        ].
        cursorLine := self validateCursorLine:(cursorLine + n).
        cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
        cursorVisibleLine := self listLineToVisibleLine:cursorLine.
        self makeCursorVisible.
    ].

    "Modified: / 10.6.1998 / 16:59:17 / cg"
!

cursorHome
    "scroll to top AND move cursor to first line of text."

    self cursorLine:1 col:1

"/    |wasOn|
"/
"/    wasOn := self hideCursor.
"/    self scrollToTop.
"/    cursorLine := cursorVisibleLine := 1.
"/    cursorCol := self validateCursorCol:1 inLine:cursorLine.
"/    self makeCursorVisibleAndShowCursor:wasOn.

    "Modified: 22.5.1996 / 18:26:42 / cg"
!

cursorLeft
    "move cursor to left"

    (cursorCol ~~ 1) ifTrue:[
        self cursorCol:(cursorCol - 1)
    ] ifFalse:[
"/ no, do not wrap back to previous line
"/        cursorLine ~~ 1 ifTrue:[
"/            ST80Mode == true ifTrue:[
"/                self cursorUp.
"/                self cursorToEndOfLine.
"/           ]
"/        ]
    ]

    "Modified: / 23.1.1998 / 12:37:13 / cg"
!

cursorLine:line col:col
    "this positions onto physical - not visible - line"

    |wasOn newCol|

    wasOn := self hideCursor.
    cursorLine := self validateCursorLine:line.
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
    (col < 1) ifTrue:[
        newCol := 1
    ] ifFalse:[
        newCol := col.
    ].
    st80Mode ifTrue:[
        (cursorLine == list size
        and:[cursorLine ~~ line]) ifTrue:[
            newCol := (self listAt:(list size)) size + 1.
        ]
    ].
    cursorCol := self validateCursorCol:newCol inLine:cursorLine.
    self makeCursorVisibleAndShowCursor:wasOn.

    "Modified: / 20.6.1998 / 18:19:06 / cg"
!

cursorMovementAllowed
    "return true, if the user may move the cursor around
     (via button-click, or cursor-key with selection).
     By default, true is returned, but this may be redefined
     in special subclasses (such as a terminal view), where
     this is not wanted"

    ^ true

    "Created: / 18.6.1998 / 14:11:16 / cg"
!

cursorReturn
    "move cursor to start of next line; scroll if at end of visible text"

    |wasOn|

    self checkForExistingLine:(cursorLine + 1).
    cursorVisibleLine notNil ifTrue:[
	nFullLinesShown notNil ifTrue:[
	    (cursorVisibleLine >= nFullLinesShown) ifTrue:[self scrollDown]
	]
    ].

    wasOn := self hideCursor.
    cursorLine := self validateCursorLine:cursorLine + 1.
    cursorCol := self validateCursorCol:1 inLine:cursorLine.
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
    self makeCursorVisibleAndShowCursor:wasOn.

    "Modified: 22.5.1996 / 18:27:34 / cg"
!

cursorRight
    "move cursor to right"

    |l|

    st80Mode == true ifTrue:[
        l := (self listAt:cursorLine).
        cursorCol >= (l size + 1) ifTrue:[
"/ no, do not wrap to next line
"/            cursorLine < list size ifTrue:[
"/                self cursorReturn.
"/            ].
            ^ self    
        ]
    ].    
    self cursorCol:(cursorCol + 1)

    "Modified: / 20.6.1998 / 18:19:07 / cg"
!

cursorShown:aBoolean
    "change cursor visibility
     return true if cursor was visible before."

    |oldState|

    oldState := cursorShown.

    aBoolean ifTrue:[
        self drawCursor.
    ] ifFalse:[
        (cursorShown and:[shown]) ifTrue: [
            self undrawCursor.
        ].
    ].
    cursorShown := aBoolean.

    ^ oldState

    "Modified: / 30.3.1999 / 15:32:43 / stefan"
    "Created: / 30.3.1999 / 15:59:30 / stefan"
!

cursorTab
    "move cursor to next tabstop"

    self cursorCol:(self nextTabAfter:cursorCol).
!

cursorToBeginOfLine
    "move cursor to start of current line"

    self cursorCol:1
!

cursorToBottom
    "move cursor to last line of text"

    |wasOn newTop|

    wasOn := self hideCursor.

    newTop := list size - nFullLinesShown.
    (newTop < 1) ifTrue:[
	newTop := 1
    ].
    self scrollToLine:newTop.
    cursorLine := self validateCursorLine:list size.
    cursorCol := self validateCursorCol:1 inLine:cursorLine.
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.

    self makeCursorVisibleAndShowCursor:wasOn.

    "Modified: 22.5.1996 / 18:27:45 / cg"
!

cursorToCharacterPosition:pos
    "compute line/col from character position (1..)
     and move the cursor onto that char"

    |line col|

    line := self lineOfCharacterPosition:pos.
    col := pos - (self characterPositionOfLine:line col:1) + 1.
    self cursorLine:line col:col

    "Created: / 15.1.1998 / 21:55:33 / cg"
!

cursorToEnd
    "move cursor down below last line of text"

    |wasOn newTop l line|

    l := list size.

    cursorLine >= l ifTrue:[
	line := self listAt:cursorLine.
	(line isNil or:[line isEmpty]) ifTrue:[
	    ^ self
	]
    ].

    wasOn := self hideCursor.

    l := l + 1.
    newTop :=  l - nFullLinesShown.
    (newTop < 1) ifTrue:[
	newTop := 1
    ].
    self scrollToLine:newTop.
    cursorLine := self validateCursorLine:l.
    cursorCol := self validateCursorCol:1 inLine:1.
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.

    self makeCursorVisibleAndShowCursor:wasOn.

    "Modified: 22.5.1996 / 18:27:53 / cg"
!

cursorToEndOfLine
    "move cursor to end of current line"

    |line|

    line := (self listAt:cursorLine).
    self cursorCol:(line size + 1)

    "Modified: 13.8.1997 / 15:34:02 / cg"
!

cursorToFirstVisibleLine
    "place cursor into the first visible line; do not scroll."

    self cursorLine:(self visibleLineToAbsoluteLine:1) col:1
!

cursorToLastVisibleLine
    "place cursor into the first visible line; do not scroll."

    self cursorLine:(self visibleLineToAbsoluteLine:nFullLinesShown) col:1
!

cursorToNextWord
    "move the cursor to the beginning of the next word"

    |col line searching|

    (cursorLine > list size) ifTrue:[^ self].
    self wordAtLine:cursorLine col:cursorCol do:[
	:beginLine :beginCol :endLine :endCol :style | 

	line := endLine.
	col := endCol + 1.
	searching := true.
	[searching 
	 and:[(self characterAtLine:line col:col) isSeparator]] whileTrue:[
	    self wordAtLine:line col:col do:[
		:beginLine :beginCol :endLine :endCol :style |

		(line > list size) ifTrue:[
		    "break out"
		    searching := false
		] ifFalse:[
		    line := endLine.
		    col := endCol + 1.
		]
	    ]
	].
	self cursorLine:line col:col
    ]
!

cursorToPreviousWord
    "move the cursor to the beginning of this or the previous word"

    |col line searching l|

    (cursorLine > list size) ifTrue:[^ self].

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

	line := beginLine.
	col := beginCol.
	style == #wordLeft ifTrue:[
	    col := col + 1
	].

	(cursorLine == line
	and:[cursorCol == col]) ifTrue:[
	    searching := true.

	    col > 1 ifTrue:[
		col := col - 1.
	    ].

	    [searching] whileTrue:[
		(col == 1) ifTrue:[    
		    line == 1 ifTrue:[
			searching := false
		    ] ifFalse:[
			line := line - 1.
			l := list at:line.
			col := l size + 1.
		    ]
		] ifFalse:[
		    (self characterAtLine:line col:col) isSeparator ifFalse:[
			self wordAtLine:line col:col do:[
			    :beginLine :beginCol :endLine :endCol :style |

			    line := beginLine.
			    col := beginCol.
			    style == #wordLeft ifTrue:[
				col := col + 1
			    ].
			    searching := false.
			]
		    ] ifTrue:[
			col := col - 1
		    ]
		]
	    ]
	].
	self cursorLine:line col:col
    ]

    "Created: 8.3.1996 / 21:52:48 / cg"
    "Modified: 8.3.1996 / 22:12:45 / cg"
!

cursorToTop
    "move cursor to absolute home"

    self cursorLine:1 col:1
!

cursorUp
    "move cursor up; scroll if at start of visible text"

    self cursorUp:1
!

cursorUp:n
    "move cursor up n lines; scroll if at start of visible text"

    |wasOn nv nl|

    cursorLine isNil ifTrue:[
	cursorLine := firstLineShown + nFullLinesShown - 1.
    ].
    nl := cursorLine - n.
    nl < 1 ifTrue:[nl := 1].

    (nl ~~ cursorLine) ifTrue: [
	wasOn := self hideCursor.
	cursorVisibleLine notNil ifTrue:[
	    nv := cursorVisibleLine - n.
	    nv < 1 ifTrue:[
		self scrollUp:(nv negated + 1)
	    ].
	].
	cursorLine := self validateCursorLine:nl.
	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	cursorCol := self validateCursorCol:cursorCol inLine:cursorLine.
	wasOn ifTrue:[self showCursor].
"/
"/ to make cursor visible (even if below visible end):
"/
"/      self makeCursorVisibleAndShowCursor:wasOn.
    ]

    "Modified: 22.5.1996 / 18:28:11 / cg"
!

cursorVisibleLine:visibleLineNr col:colNr
    "put cursor to visibleline/col"

    |wasOn newCol|

    wasOn := self hideCursor.
    cursorLine := self validateCursorLine:(self visibleLineToAbsoluteLine:visibleLineNr).
    cursorVisibleLine := visibleLineNr.
    newCol := colNr.
    (newCol < 1) ifTrue:[
        newCol := 1
    ].
    cursorCol := self validateCursorCol:newCol inLine:cursorLine.
    self makeCursorVisibleAndShowCursor:wasOn.

    "Modified: / 20.6.1998 / 18:40:28 / cg"
!

cursorX:x y:y
    "put cursor to position next to x/y coordinate in view"

    |line col|

    line := self visibleLineOfY:y.
    col := self colOfX:x inVisibleLine:line.
    self cursorVisibleLine:line col:col.
!

drawCursor
    "draw the cursor if shown and cursor is visible.
     (but not, if there is a selection - to avoid confusion)"

    shown ifTrue:[
	cursorVisibleLine notNil ifTrue:[
	    self hasSelection ifFalse:[
		self drawCursorCharacter
	    ]
	]
    ]
!

drawCursor:cursorType with:fgColor and:bgColor
    "draw a cursor; the argument cursorType specifies what type
     of cursor should be drawn.
     Currently, supported are: #block, #frame, #ibeam, #caret, #solidCaret
                               #bigCaret and #bigSolidCaret"

    |x y w char y2 x1 x2 oldPaint oldClip|

    self hasSelection ifTrue:[
        "
         hide cursor, if there is a selection
        "
        ^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
    ].

    cursorType == #none ifTrue:[
        ^ self
    ].

    cursorType == #block ifTrue:[
        super drawVisibleLine:cursorVisibleLine 
                          col:cursorCol 
                         with:fgColor
                          and:bgColor.
        ^ self
    ].
    x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
    y := self yOfVisibleLine:cursorVisibleLine.

    oldPaint := self paint. "/ do not clobber GC
    cursorType == #frame ifTrue:[
        super redrawVisibleLine:cursorVisibleLine col:cursorCol.

        char := self characterUnderCursor asString.
        self paint:bgColor.
        self displayRectangleX:x y:y 
                         width:(font widthOf:char) height:fontHeight.
    ] ifFalse:[
        self paint:bgColor.
        cursorType == #ibeam ifTrue:[
            x1 := x - 1.
            y2 := y + fontHeight - 1.
            self displayLineFromX:x1 y:y toX:x1 y:y2. 
            self displayLineFromX:x y:y toX:x y:y2. 
            ^ self
        ].

        cursorType == #Ibeam ifTrue:[
            x1 := x - 1.
            y2 := y + fontHeight - 1.
            self displayLineFromX:x1 y:y toX:x1 y:y2. 
            self displayLineFromX:x y:y toX:x y:y2. 
            self displayLineFromX:x1-2 y:y toX:x+2 y:y. 
            self displayLineFromX:x1-2 y:y2 toX:x+2 y:y2. 
            ^ self
        ].

        y := y + fontHeight - 3.
        ((cursorType == #bigCaret) or:[cursorType == #bigSolidCaret]) ifTrue:[
            w := (fontWidth * 2 // 3) max:4.
            y2 := y + w + (w//2).
        ] ifFalse:[
            w := (fontWidth // 2) max:4.
            y2 := y + w.
        ].
        x1 := x - w.
        x2 := x + w.

        oldClip := self clippingRectangleOrNil.
        self clippingRectangle:(margin@margin extent:(width-margin) @ (height-margin)).

        cursorType == #caret ifTrue:[
            self lineWidth:2.
            self displayLineFromX:x1 y:y2 toX:x y:y. 
            self displayLineFromX:x y:y toX:x2 y:y2. 
        ] ifFalse:[
            "anything else: solidCaret"

            self fillPolygon:(Array with:(x1 @ y2)
                                    with:(x @ y)
                                    with:(x2 @ y2))
        ].

        self clippingRectangle:oldClip
    ].
    self paint:oldPaint.

    "Modified: 18.2.1997 / 15:19:03 / cg"
!

drawCursorCharacter
    "draw the cursor. 
     (i.e. the cursor if no selection)
     - helper for many cursor methods"

    (hasKeyboardFocus 
    and:[self enabled
    and:[readOnly not]]) ifTrue:[
        self drawFocusCursor
    ] ifFalse:[
        self drawNoFocusCursor
    ]

    "Modified: / 23.3.1999 / 13:52:48 / cg"
!

drawFocusCursor
    "draw the cursor when the focus is in the view."

    self hasSelection ifTrue:[
	^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
    ].
    cursorType == #none ifTrue:[
	^ self undrawCursor
    ].
    self drawCursor:cursorType with:cursorFgColor and:cursorBgColor.

    "Modified: 22.9.1997 / 00:16:38 / cg"
!

drawNoFocusCursor
    "draw the cursor for the case when the view has no keyboard focus" 

    |cType|

    self hasSelection ifTrue:[
	^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
    ].

    cType := cursorTypeNoFocus ? cursorType.
    cType == #none ifTrue:[
	^ self undrawCursor
    ].

    cType == #block ifTrue:[
	^ self drawCursor:#frame with:cursorNoFocusFgColor and:cursorBgColor
    ].

    ^ self drawCursor:cType with:cursorNoFocusFgColor and:cursorNoFocusFgColor.

    "Modified: 22.9.1997 / 00:16:13 / cg"
!

gotoLine:aLineNumber
    "position cursor onto line, aLineNumber.
     Make certain that this line is visible"

    self makeLineVisible:aLineNumber.
    self cursorLine:aLineNumber col:1
!

hideCursor
    "make cursor invisible if currently invisible"

    ^ self cursorShown:false

    "Modified: / 30.3.1999 / 16:02:28 / stefan"
!

makeCursorVisible
    "scroll text to make cursorline visible 
     (i.e. to have cursorLine in visible area)"

    |line col|

    cursorLine notNil ifTrue:[
	line := cursorLine.
	col := cursorCol.
	"
	 if there is a selection, its better to
	 have its start being visible, instead of the end
	"
	(selectionStartLine notNil 
	and:[selectionEndLine notNil]) ifTrue:[
	    expandingTop ~~ false ifTrue:[
		line := selectionStartLine.
		col := selectionStartCol.
	    ] ifFalse:[
		line := selectionEndLine.
		col := selectionEndCol
	    ]
	].
	self makeLineVisible:line.
	self makeColVisible:col inLine:line 
    ]

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

makeCursorVisibleAndShowCursor:flag
    "scroll to make cursorLine visible;
     if flag is true, draw the cursor"

    self makeCursorVisible.
    flag ifTrue:[self showCursor]
!

showCursor
    "make cursor visible if currently invisible"

    ^ self cursorShown:true

    "Modified: / 30.3.1999 / 16:02:34 / stefan"
!

undrawCursor
    "undraw the cursor (i.e. redraw the character(s) under the cursor)"

    |prevCol line oldClip x y|

    cursorVisibleLine notNil ifTrue:[
        prevCol := cursorCol - 1.

        ((cursorType == #caret)
         or:[cursorType == #solidCaret
         or:[cursorType == #bigSolidCaret
         or:[cursorType == #bigCaret
         or:[cursorType == #Ibeam]]]]) ifTrue:[
            "caret-cursor touches 4 characters"
            ((cursorCol > 1) and:[fontIsFixedWidth]) ifTrue:[
                super redrawVisibleLine:cursorVisibleLine from:prevCol to:cursorCol.
                super redrawVisibleLine:cursorVisibleLine+1 from:prevCol to:cursorCol.
            ] ifFalse:[
                "care for left margin"
                super redrawVisibleLine:cursorVisibleLine; redrawVisibleLine:cursorVisibleLine+1.
            ].
            ^ self
        ].

        cursorType == #ibeam ifTrue:[
            "ibeam-cursor touches 2 characters"
            cursorCol > 1 ifTrue:[
                super redrawVisibleLine:cursorVisibleLine from:prevCol to:cursorCol.
            ] ifFalse:[
                "care for left margin"
                super redrawVisibleLine:cursorVisibleLine.
            ].
            ^ self
        ].

        "block cursor is simple - just one character under cursor"

        "/ however, if italic characters are involved, we must care
        "/ for the chars before/after the cursor.
        "/ We redraw the part of the previous character which got
        "/ detroyed by the block cursor.
        "/ (must change the clip, to avoid destroying the prev-prev character) 

        line := self visibleAt:cursorVisibleLine.
        (line notNil and:[line isText]) ifTrue:[
            cursorCol > 1 ifTrue:[
                oldClip := self clippingRectangleOrNil.
                x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
                y := self yOfVisibleLine:cursorVisibleLine.
                self clippingRectangle:(x@y extent:((font width * 2) @ fontHeight)).
                super redrawVisibleLine:cursorVisibleLine from:cursorCol-1 to:cursorCol.
                self clippingRectangle:oldClip.
                ^ self.
            ].
        ].
        super redrawVisibleLine:cursorVisibleLine col:cursorCol
    ]

    "Modified: / 22.4.1998 / 09:13:07 / cg"
!

validateCursorCol:col inLine:line
    "check of col is a valid cursor position; return a new col-nr if not.
     Here, no limits are enforced (and col is returned), 
     but it may be redefined in EditFields or views which dont like the 
     cursor to be positioned behind the end of a textLine (vi/st-80 behavior)"

    |l max|

    "/ in ST80 mode,
    "/ the cursor may not be positioned behond the
    "/ end of a line or behond the last line of the text
    "/
    st80Mode == true ifTrue:[
        l := (self listAt:line).
        max := l size + 1.
        col > max ifTrue:[
            ^ max
        ]
    ].
    ^ col

    "Created: / 22.5.1996 / 14:25:30 / cg"
    "Modified: / 20.6.1998 / 18:19:24 / cg"
!

validateCursorLine:line
    "check of line is a valid cursor line; return a fixed line-nr if not.
     Here, no limits are enforced (and line is returned), but it may be 
     redefined in views which dont like the cursor to be positioned
     behind the end of the text (vi/st-80 behavior), or want to
     skip reserved regions"

    "/
    "/ in st80Mode, the cursor may not be positioned
    "/ behond the last line
    "/
    st80Mode == true ifTrue:[
        ^ (line min:(list size)) max:1
    ].
    ^ line

    "Created: / 22.5.1996 / 18:22:23 / cg"
    "Modified: / 20.6.1998 / 18:19:26 / cg"
!

withCursorOffDo:aBlock
    "evaluate aBlock with cursor off; turn it on afterwards."

    (shown not or:[cursorShown not]) ifTrue:[
	^ aBlock value
    ].
    self hideCursor.
    aBlock valueNowOrOnUnwindDo:[
	self showCursor
    ]
! !

!EditTextView methodsFor:'editing'!

copyAndDeleteSelection
    "copy the selection into the pastBuffer and delete it"

    selectionStartLine notNil ifTrue:[
	self setTextSelection:(self selection).
	self deleteSelection.
    ].

    "Created: 27.1.1996 / 16:23:28 / cg"
!

deleteCharAtCursor
    "delete single character under cursor; does not merge lines"

    |wasOn|

    wasOn := self hideCursor.
    self deleteCharAtLine:cursorLine col:cursorCol.
    wasOn ifTrue:[self showCursor]
!

deleteCharAtLine:lineNr col:colNr
    "delete a single character at colNr in line lineNr"

    self deleteCharsAtLine:lineNr fromCol:colNr toCol:colNr
!

deleteCharBeforeCursor
    "delete single character to the left of cursor and move cursor to left"

    |soCol wasOn lineNrAboveCursor ln|

    wasOn := self hideCursor.

	(autoIndent
    and:[cursorCol  ~~ 1
    and:[cursorLine <= (list size)]]) 
     ifTrue:[
	soCol := (self leftIndentForLine:cursorLine) + 1.

	(cursorCol == soCol and:[soCol > 1]) ifTrue:[
	    ln := list at:cursorLine.
	    (ln notNil and:[(ln indexOfNonSeparatorStartingAt:1) < soCol]) ifTrue:[
		soCol := 1
	    ]
	]
    ] ifFalse:[
	soCol := 1
    ].

    (cursorCol ~~ soCol and:[cursorCol ~~ 1]) ifTrue:[
	"
	 somewhere in the middle of a line
	"
	self cursorLeft.
	self deleteCharAtLine:cursorLine col:cursorCol.
    ] ifFalse:[
	"
	 at begin of line - merge with previous line;
	 except for the very first line.
	"
	(cursorLine == 1) ifFalse:[
	    lineNrAboveCursor := self validateCursorLine:(cursorLine - 1).
	    lineNrAboveCursor < cursorLine ifTrue:[
		self mergeLine:lineNrAboveCursor removeBlanks:false.
	    ]
	]
    ].
    wasOn ifTrue:[ self showCursor ]

    "Modified: / 16.1.1998 / 22:33:04 / cg"
!

deleteCharsAtLine:lineNr fromCol:colNr
    "delete characters from colNr up to the end in line lineNr"

    |line|

    (line := self listAt:lineNr) notNil ifTrue:[
	self deleteCharsAtLine:lineNr fromCol:colNr toCol:(line size)
    ]

!

deleteCharsAtLine:lineNr toCol:colNr
    "delete characters from start up to colNr in line lineNr"

    self deleteCharsAtLine:lineNr fromCol:1 toCol:colNr


!

deleteCursorLine
    "delete the line where the cursor sits"

    self deleteLine:cursorLine
!

deleteLine:lineNr
    "delete line"

    self deleteFromLine:lineNr toLine:lineNr


!

deleteLinesWithoutRedrawFrom:startLine to:endLine
    "delete lines - no redraw;
     return true, if something was really deleted"

    |lastLine|

    self checkModificationsAllowed ifFalse:[ ^ self].

    (list isNil or:[startLine > list size]) ifTrue:[^ false].
    (endLine > list size) ifTrue:[
        lastLine := list size
    ] ifFalse:[
        lastLine := endLine
    ].
    list removeFromIndex:startLine toIndex:lastLine.
    "/ TODO: remember old maxwidth of linerange,
    "/ only clear widthOfWidestLine, if this max
    "/ length was (one of) the longest.
    "/ avoids slow delete with huge texts.
    widthOfWidestLine := nil. "/ i.e. unknown
    self textChanged.
    ^ true

    "Modified: / 10.11.1998 / 23:55:29 / cg"
!

deleteSelection
    "delete the selection"

    |wasOn startLine startCol endLine endCol|

    self checkModificationsAllowed ifFalse:[ ^ self].

    selectionStartLine notNil ifTrue:[
	wasOn := self hideCursor.

	startLine := selectionStartLine.
	startCol := selectionStartCol.
	endLine := selectionEndLine.
	endCol := selectionEndCol.
	self unselectWithoutRedraw.
	self deleteFromLine:startLine col:startCol 
		     toLine:endLine col:endCol.
	cursorCol := startCol.
	cursorLine := startLine.
	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	self makeCursorVisibleAndShowCursor:wasOn
    ]
!

insertCharAtCursor:aCharacter
    "insert a single character at cursor-position - advance cursor."

    |wasOn|

    wasOn := self hideCursor.
    aCharacter == Character tab ifTrue:[
        "/ needs special care to advance cursor correctly
        self insertTabAtCursor
    ] ifFalse:[
        self insert:aCharacter atLine:cursorLine col:cursorCol.
        aCharacter == (Character cr) ifTrue:[
            self cursorReturn
        ] ifFalse:[
            self cursorRight.
        ].
    ].
    self makeCursorVisibleAndShowCursor:wasOn.

    "Modified: / 12.6.1998 / 21:50:20 / cg"
!

insertLine:aString before:lineNr
    "insert the line aString before line lineNr"

    ^ self insertLines:(Array with:aString) from:1 to:1  before:lineNr.

    "Modified: 14.5.1996 / 13:42:54 / cg"
!

insertLines:aStringCollection before:lineNr
    "insert a bunch before line lineNr"

    self insertLines:aStringCollection from:1 to:aStringCollection size before:lineNr

    "Modified: 6.9.1995 / 20:51:03 / claus"
!

insertLines:lines withCR:withCr
    "insert a bunch of lines at cursor position. 
     Cursor is moved behind insertion.
     If withCr is true, append cr after last line"

    |start end nLines wasOn|

    lines notNil ifTrue:[
        nLines := lines size.
        (nLines == 1) ifTrue:[
            self insertStringAtCursor:(lines at:1).
            withCr ifTrue:[
                self insertCharAtCursor:(Character cr)
            ] 
        ] ifFalse:[
            (cursorCol ~~ 1) ifTrue:[
                self insertStringAtCursor:(lines at:1).
                self insertCharAtCursor:(Character cr).
                start := 2
            ] ifFalse:[
                start := 1
            ].
            withCr ifTrue:[
                end := nLines
            ] ifFalse:[
                end := nLines - 1
            ].
            (start < nLines) ifTrue:[
                (end >= start) ifTrue:[
                    wasOn := self hideCursor.
                    self insertLines:lines from:start to:end before:cursorLine.
                    cursorLine := cursorLine + (end - start + 1).
                    cursorVisibleLine := self absoluteLineToVisibleLine:cursorLine.
                    wasOn ifTrue:[self showCursor].
                ]
            ].
            withCr ifFalse:[
                "last line without cr"
                self insertStringAtCursor:(lines at:nLines)
            ]
        ]
    ]

    "Created: / 18.5.1996 / 15:32:06 / cg"
    "Modified: / 12.6.1998 / 21:51:16 / cg"
!

insertLines:lines withCr:withCr
    "insert a bunch of lines at cursor position. Cursor
     is moved behind insertion.
     If withCr is true, append cr after last line"

    self obsoleteMethodWarning:'use #insertLines:withCR:'.
    self insertLines:lines withCR:withCr.

    "Modified: 31.7.1997 / 23:07:22 / cg"
!

insertSelectedStringAtCursor:aString
    "insert the argument, aString at cursor position and select it"

    |startLine startCol|

    startLine := cursorLine.
    startCol := cursorCol.
    self insertStringAtCursor:aString.
    self selectFromLine:startLine col:startCol
		 toLine:cursorLine col:(cursorCol - 1)
!

insertString:aString atCharacterPosition:charPos
    "insert the argument, aString at a character position"

    |line col|

    line := self lineOfCharacterPosition:charPos.
    col := charPos - (self characterPositionOfLine:line col:1) + 1.
    self insertString:aString atLine:line col:col
!

insertString:aString atLine:lineNr col:colNr
    "insert the string, aString at line/col;
     handle cr's correctly"

    |start           "{ Class: SmallInteger }"
     stop            "{ Class: SmallInteger }"
     end             "{ Class: SmallInteger }"
     subString c
     l               "{ Class: SmallInteger }" |

    aString isNil ifTrue:[^ self].
    (aString includes:(Character cr)) ifFalse:[
        ^ self insertStringWithoutCRs:aString atLine:lineNr col:colNr
    ].

    l := lineNr.
    c := colNr.
    start := 1.
    end := aString size.
    [start <= end] whileTrue:[
        stop := aString indexOf:(Character cr) startingAt:start.
        stop == 0 ifTrue:[
            stop := end + 1
        ].
        subString := aString copyFrom:start to:(stop - 1).
        self insertStringWithoutCRs:subString atLine:l col:c.
        (stop <= end) ifTrue:[
            c := c + subString size.
            self insert:(Character cr) atLine:l col:c.
            l := l + 1.
            c := 1
        ].
        start := stop + 1
    ]

    "Modified: / 10.6.1998 / 19:03:59 / cg"
!

insertStringAtCursor:aString
    "insert the argument, aString at cursor position
     handle cr's correctly. A nil argument is interpreted as an empty line."

    aString isNil ifTrue:[
        "new:"
        self insertCharAtCursor:(Character cr).
        ^ self
    ].
    (aString includes:(Character cr)) ifFalse:[
        ^ self insertStringWithoutCRsAtCursor:aString
    ].

    self insertLines:aString asStringCollection withCR:false.

    "Modified: / 10.6.1998 / 19:03:21 / cg"
!

insertStringWithoutCRs:aString atLine:lineNr col:colNr
    "insert aString (which has no crs) at lineNr/colNr"

    self withoutRedrawInsertStringWithoutCRs:aString atLine:lineNr col:colNr.
    shown ifTrue:[self redrawLine:lineNr from:colNr]

    "Modified: / 5.4.1998 / 16:51:14 / cg"
!

insertStringWithoutCRsAtCursor:aString
    "insert a string (which has no crs) at cursor position
     - advance cursor"

    |wasOn oldLen newLen|

    aString notNil ifTrue:[
        wasOn := self hideCursor.
        (aString includes:Character tab) ifTrue:[
            self checkForExistingLine:cursorLine.
            oldLen := (list at:cursorLine) size.
            self insertString:aString atLine:cursorLine col:cursorCol.
            newLen := (list at:cursorLine) size.
            cursorCol := cursorCol + (newLen - oldLen).
        ] ifFalse:[
            self insertString:aString atLine:cursorLine col:cursorCol.
            cursorCol := cursorCol + aString size.
        ].
        wasOn ifTrue:[self showCursor]
    ]

    "Modified: / 10.6.1998 / 20:43:52 / cg"
!

insertTabAtCursor
    "insert spaces to next tab"

    |wasOn nextTab|

    wasOn := self hideCursor.
    nextTab := self nextTabAfter:cursorCol.
    self insertStringAtCursor:(String new:(nextTab - cursorCol)).
    self makeCursorVisibleAndShowCursor:wasOn.
!

removeTrailingBlankLines
    "remove all blank lines at end of text"

    |lastLine "{ Class: SmallInteger }"
     line finished|

    lastLine := list size.
    finished := false.
    [finished] whileFalse:[
	(lastLine <= 1) ifTrue:[
	    finished := true
	] ifFalse:[
	    line := list at:lastLine.
	    line notNil ifTrue:[
		line isBlank ifTrue:[
		    list at:lastLine put:nil.
		    line := nil
		]
	    ].
	    line notNil ifTrue:[
		finished := true
	    ] ifFalse:[
		lastLine := lastLine - 1
	    ]
	]
    ].
    (lastLine ~~ list size) ifTrue:[
	list grow:lastLine.
"/        self textChanged
    ]
!

replaceCharAtCursor:aCharacter
    "replace a single character at cursor-position - advance cursor"

    |wasOn|

    wasOn := self hideCursor.
    aCharacter == (Character cr) ifTrue:[
	self cursorReturn
    ] ifFalse:[
	self replace:aCharacter atLine:cursorLine col:cursorCol.
	self cursorRight.
    ].
    self makeCursorVisibleAndShowCursor:wasOn.

    "Created: 6.3.1996 / 12:27:42 / cg"
!

replaceLines:lines withCR:withCr
    "replace a bunch of lines at cursor position. Cursor
     is moved behind replacement.
     If withCr is true, move to the beginning of the next line
     after the last line"

    |line col nLines wasOn|

    lines notNil ifTrue:[
        wasOn := self hideCursor.
        nLines := lines size.
        line := cursorLine.
        col := cursorCol.
        lines keysAndValuesDo:[:i :l |
            self replaceString:l atLine:line col:col.
            (i ~~ nLines or:[withCr]) ifTrue:[
                line := line + 1.
                col := 1.
            ] ifFalse:[
                col := col + (l size).
            ]
        ].
        self cursorLine:line col:col.
        self makeCursorVisibleAndShowCursor:wasOn.
        "/ wasOn ifTrue:[self showCursor].
    ]

    "Created: / 18.5.1996 / 15:32:06 / cg"
    "Modified: / 12.6.1998 / 22:05:51 / cg"
!

replaceSelectionBy:something
    "delete the selection (if any) and insert something, a character or string;
     leave cursor after insertion"

    self replaceSelectionBy:something keepCursor:false
!

replaceSelectionBy:something keepCursor:keep
    "delete the selection (if any) and insert something, a character or string;
     leave cursor after insertion or leave it, depending on keep"

    |sel l c|

    l := cursorLine.
    c := cursorCol.

    sel := self selection.
    sel notNil ifTrue:[
	lastString := sel.
	self deleteSelection.
	replacing := true.
	lastReplacement := ''
    ].

    (something isMemberOf:Character) ifTrue:[
	lastReplacement notNil ifTrue:[
"/ "XXX - replacing text with spaces ..."
"/            (lastReplacement endsWith:Character space) ifTrue:[
"/                lastReplacement := lastReplacement copyWithoutLast:1 "copyTo:(lastReplacement size - 1)".
"/                lastReplacement := lastReplacement copyWith:something.
"/                lastReplacement := lastReplacement copyWith:Character space
"/            ] ifFalse:[
		lastReplacement := lastReplacement copyWith:something.
"/            ]
	].
	insertMode ifTrue:[
	    self insertCharAtCursor:something
	] ifFalse:[
	    self replaceCharAtCursor:something
	]
    ] ifFalse:[
	lastReplacement := something.
	insertMode ifTrue:[
	    self insertStringAtCursor:something
	] ifFalse:[
	    self replaceStringAtCursor
	]
    ].
    keep ifTrue:[
	self cursorLine:l col:c
    ]

    "Modified: 9.10.1996 / 16:14:35 / cg"
!

replaceStringAtCursor:aString
    "replace multiple characters at cursor-position - advance cursor"

    |wasOn i1 i2|

    wasOn := self hideCursor.
    (aString includes:Character tab) ifTrue:[
        "/ need special care for TAB (to move cursor correctly)
        i1 := 1.
        [i1 ~~ 0] whileTrue:[
            i2 := aString indexOf:Character tab startingAt:i1.
            i2 ~~ 0 ifTrue:[
                i1 ~~ i2 ifTrue:[
                    self replaceString:(aString copyFrom:i1 to:i2-1) atLine:cursorLine col:cursorCol.
                    self cursorCol:(cursorCol + (i2 - i1)).
                ].
                self replaceTABAtCursor.
                i2 := i2 + 1.
            ] ifFalse:[
                self replaceString:(aString copyFrom:i1) atLine:cursorLine col:cursorCol.
                self cursorCol:(cursorCol + (aString size - i1 + 1)).
            ].
            i1 := i2.
        ]
    ] ifFalse:[
        self replaceString:aString atLine:cursorLine col:cursorCol.
        self cursorCol:(cursorCol + aString size).
    ].
    self makeCursorVisibleAndShowCursor:wasOn.

    "Created: / 9.6.1998 / 20:33:20 / cg"
    "Modified: / 20.6.1998 / 19:41:02 / cg"
!

replaceTABAtCursor
    "replace a single character at cursor-position by a TAB character"

    |wasOn nextTab|

    wasOn := self hideCursor.
    nextTab := self nextTabAfter:cursorCol.
    self replaceStringAtCursor:(String new:(nextTab - cursorCol)).
    self makeCursorVisibleAndShowCursor:wasOn.

    "Created: / 12.6.1998 / 21:53:23 / cg"
! !

!EditTextView methodsFor:'editing - basic'!

deleteCharsAtLine:lineNr fromCol:startCol toCol:endCol
    "delete characters from startCol to endCol in line lineNr
    "
    |line lineSize newLine start stop prevWidth newWidth|

    line := self listAt:lineNr.

    (self checkModificationsAllowed and:[line notNil]) ifTrue:[ 
        lineSize := line size.

        startCol == 0     ifFalse:[ start := startCol ]
                           ifTrue:[ start := 1 ]. 

        endCol > lineSize ifFalse:[ stop  := endCol ]
                           ifTrue:[ stop  := lineSize ].

        stop >= start ifTrue:[
            start ~~ 1 ifTrue:[ newLine := line copyFrom:1 to:(start-1) ]
                      ifFalse:[ newLine := '' ].

            stop == lineSize ifFalse:[
                line bitsPerCharacter > newLine bitsPerCharacter ifTrue:[
                    newLine := line string species fromString:newLine.
                ].
                newLine := newLine, (line copyFrom:(stop + 1) to:lineSize)
            ].

            (trimBlankLines and:[newLine isBlank]) ifTrue:[
                newLine := nil
            ].

            prevWidth := self widthOfLine:lineNr.

            list at:lineNr put:newLine.

            (prevWidth = widthOfWidestLine) ifTrue:[
                "/ remember old width of this line,
                "/ only clear widthOfWidestLine, if this lines
                "/ length was (one of) the longest.
                "/ avoids slow delete with huge texts.
                widthOfWidestLine := nil.   "i.e. unknown"

                "/ scroll left if reqiured
                viewOrigin x > 0 ifTrue:[
                    newWidth := self widthOfLine:lineNr.
                    newWidth < (viewOrigin x + width) ifTrue:[
                        self scrollHorizontalTo:(newWidth 
                                                 - width 
                                                 + margin + margin 
                                                 + (font widthOf:'  '))
                    ]
                ].
            ].
            self textChanged.
            self redrawLine:lineNr from:start.

        ]
    ]

    "Modified: / 11.11.1998 / 00:01:09 / cg"
!

deleteFromLine:startLine col:startCol toLine:endLine col:endCol
    "delete all text from startLine/startCol to endLine/endCol -
     joining lines if nescessary"

    |line newLine lineSize nMore|

    self checkModificationsAllowed ifFalse:[ ^ self].
    list isNil ifTrue:[^ self].
    startLine > list size ifTrue:[ ^ self]. "/ deleted space below text

    (startLine == endLine) ifTrue:[
        "/ delete chars within a line
        self deleteCharsAtLine:startLine fromCol:startCol toCol:endCol.
        ^ self
    ].

    ((startCol == 1) and:[endCol == 0]) ifTrue:[
        "/ delete full lines only
        endLine > startLine ifTrue:[
            self deleteFromLine:startLine toLine:(endLine - 1)
        ].
        ^ self
    ].

    "/ delete right rest of 1st line
    self deleteCharsAtLine:startLine fromCol:startCol.

    "/ delete the inner lines ...
    endLine > (startLine + 1) ifTrue:[
        self deleteFromLine:(startLine + 1) toLine:(endLine - 1)
    ].

    (endCol ~~ 0) ifTrue:[
        "/ delete the left rest of the last line

        self deleteCharsAtLine:(startLine + 1) toCol:endCol.

        "/ must add blanks, if startCol lies behond end of startLine

        line := list at:startLine.
        lineSize := line size.
        (startCol > lineSize) ifTrue:[
            newLine := line.
            line isNil ifTrue:[
                newLine := String new:(startCol - 1)
            ] ifFalse:[
                nMore := startCol - 1 - lineSize.
                nMore > 0 ifTrue:[
                    newLine := line , (line species new:nMore)
                ]
            ].
            newLine ~~ line ifTrue:[
                list at:startLine put:newLine.
            ].
            "/ TODO: remember old maxwidth of linerange,
            "/ only clear widthOfWidestLine, if this max
            "/ length was (one of) the longest.
            "/ avoids slow delete with huge texts.
            widthOfWidestLine := nil. "/ i.e. unknown
            self textChanged.
        ]
    ].

    "/ merge the left rest of 1st line with right rest of last line into one
    self mergeLine:startLine removeBlanks:false

    "Modified: / 10.11.1998 / 23:52:59 / cg"
!

deleteFromLine:startLineNr toLine:endLineNr
    "delete some lines"

    |wasOn nLines|

    self checkModificationsAllowed ifFalse:[ ^ self].
    list isNil ifTrue:[^ self].

    wasOn := self hideCursor.

    "/ isnt this the same as:
    "/ self deleteLinesWithoutRedrawFrom:startLineNr to:endLineNr.

    list removeFromIndex:startLineNr toIndex:(endLineNr min:list size).
    "/ TODO: remember old maxwidth of linerange,
    "/ only clear widthOfWidestLine, if this max
    "/ length was (one of) the longest.
    "/ avoids slow delete with huge texts.
    widthOfWidestLine := nil. "/ i.e. unknown
    self textChanged.

    self redrawFromLine:startLineNr.

    nLines := list size.
    (firstLineShown >= nLines) ifTrue:[
        self makeLineVisible:nLines
    ].
    wasOn ifTrue:[self showCursor].

    "Modified: / 10.11.1998 / 23:55:05 / cg"
!

deleteLineWithoutRedraw:lineNr
    "delete line - no redraw;
     return true, if something was really deleted"

    self checkModificationsAllowed ifFalse:[ ^ self].

    (list isNil or:[lineNr > list size]) ifTrue:[^ false].
    list removeIndex:lineNr.
    "/ TODO: remember old maxwidth of linerange,
    "/ only clear widthOfWidestLine, if this max
    "/ length was (one of) the longest.
    "/ avoids slow delete with huge texts.
    widthOfWidestLine := nil. "/ i.e. unknown
    self textChanged.
    ^ true

    "Modified: / 10.11.1998 / 23:53:24 / cg"
!

insert:aCharacter atLine:lineNr col:colNr
    "insert a single character at lineNr/colNr; 
     set emphasis to character at current position"

    |line lineSize newLine drawCharacterOnly attribute oldClip x y|

    self checkModificationsAllowed ifFalse:[ ^ self].

    aCharacter == (Character cr) ifTrue:[
        self splitLine:lineNr before:colNr.
        ^ self
    ].

    drawCharacterOnly := false.
    self checkForExistingLine:lineNr.
    line := list at:lineNr.
    lineSize := line size.

    st80Mode ~~ true ifTrue:[
        (trimBlankLines 
        and:[colNr > lineSize
        and:[aCharacter == Character space]]) ifTrue:[
            ^ self
        ]
    ].

    (lineSize == 0) ifTrue:[
        newLine := aCharacter asString species new:colNr.
        drawCharacterOnly := true
    ] ifFalse: [
        (colNr > lineSize) ifTrue: [
            colNr == (lineSize +1) ifTrue:[
                attribute := line emphasisAt:lineSize
            ].
            newLine := line species new:colNr.
            newLine replaceFrom:1 to:lineSize
                           with:line startingAt:1.
            drawCharacterOnly := true
        ] ifFalse: [
            attribute := line emphasisAt:colNr.
            newLine   := line species new:(lineSize + 1).

            newLine replaceFrom:1 to:(colNr - 1)
                           with:line startingAt:1.
            newLine replaceFrom:(colNr + 1) to:(lineSize + 1)
                           with:line startingAt:colNr
        ]
    ].

    newLine at:colNr put:aCharacter.

    attribute notNil ifTrue:[
        newLine emphasisAt:colNr put:attribute
    ].

    aCharacter == (Character tab) ifTrue:[
        newLine := self withTabsExpanded:newLine.
        drawCharacterOnly := false
    ].

    list at:lineNr put:newLine.
    widthOfWidestLine notNil ifTrue:[
        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
    ].
    self textChanged.
    shown ifTrue:[
        "/ care for italic text - in this case, we must also
        "/ redraw the character before the insertion in order
        "/ to fix the slanted piece of the character.
        "/ (but we must clip, to avoid destoying the character before)
        (newLine notNil and:[newLine isText]) ifTrue:[
            colNr > 1 ifTrue:[
                oldClip := self clippingRectangleOrNil.
                x := (self xOfCol:colNr inVisibleLine:cursorVisibleLine) - leftOffset.
                y := self yOfVisibleLine:cursorVisibleLine.
                drawCharacterOnly ifTrue:[
                    self clippingRectangle:(x@y extent:((font width * 2) @ fontHeight)).
                    self redrawLine:lineNr from:colNr-1 to:colNr
                ] ifFalse:[
                    self clippingRectangle:(x@y extent:((width - x) @ fontHeight)).
                    self redrawLine:lineNr from:colNr-1
                ].
                self clippingRectangle:oldClip.
                ^ self.
            ].
        ].
        drawCharacterOnly ifTrue:[
            self redrawLine:lineNr col:colNr
        ] ifFalse:[
            self redrawLine:lineNr from:colNr
        ]
    ]

    "Modified: / 20.6.1998 / 18:19:22 / cg"
!

insertLines:someText from:start to:end before:lineNr
    "insert a bunch of lines before line lineNr"

    |text indent visLine w nLines "{ Class: SmallInteger }"
     srcY "{ Class: SmallInteger }"
     dstY "{ Class: SmallInteger }" |

    self isReadOnly ifTrue:[
        ^ self
    ].

    autoIndent ifTrue:[
        indent := self leftIndentForLine:lineNr.

        text := someText collect:[:ln||line|
            ln notNil ifTrue:[
                line := ln withoutLeadingSeparators.
                (line isEmpty or:[indent == 0]) ifFalse:[
                    line := (String new:indent), line
                ].
                line
            ] ifFalse:[
                nil
            ]
        ].
    ] ifFalse:[
        text := someText
    ].

    visLine := self listLineToVisibleLine:lineNr.
    (shown not or:[visLine isNil]) ifTrue:[
        self withoutRedrawInsertLines:text
                                 from:start to:end
                               before:lineNr.
    ] ifFalse:[
        nLines := end - start + 1.
        ((visLine + nLines) >= nLinesShown) ifTrue:[
            self withoutRedrawInsertLines:text
                                     from:start to:end
                                   before:lineNr.
            self redrawFromVisibleLine:visLine to:nLinesShown
        ] ifFalse:[
            w := self widthForScrollBetween:(lineNr + nLines)
                                        and:(firstLineShown + nLines + nLinesShown).
            srcY := topMargin + ((visLine - 1) * fontHeight).
            dstY := srcY + (nLines * fontHeight).

            "/
            "/ scroll ...
            "/
            "
             stupid: must catchExpose before inserting new
             stuff - since catchExpose may perform redraws
            "
            self catchExpose.
            self withoutRedrawInsertLines:text
                                     from:start to:end
                                   before:lineNr.
            self 
                copyFrom:self 
                x:textStartLeft y:srcY
                toX:textStartLeft y:dstY
                width:w
                height:(height - dstY)
                async:true.
            self redrawFromVisibleLine:visLine to:(visLine + nLines - 1).
            self waitForExpose
        ].
    ].
    widthOfWidestLine notNil ifTrue:[
        text do:[:line |
            widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
        ]
    ].
    self textChanged.

    "Modified: 29.1.1997 / 13:02:39 / cg"
!

mergeLine:lineNr
    "merge line lineNr with line lineNr+1"

    self mergeLine:lineNr removeBlanks:true

    "Modified: 9.9.1997 / 09:28:03 / cg"
!

mergeLine:lineNr removeBlanks:removeBlanks
    "merge line lineNr with line lineNr+1"

    |leftPart rightPart bothParts nextLineNr i|

    (list notNil and:[(list size) > lineNr]) ifFalse:[
	^ self
    ].
    leftPart := self listAt:lineNr.

    leftPart isNil ifTrue:[
	leftPart := ''.
	autoIndent ifTrue:[
	    (i := self leftIndentForLine:cursorLine) == 0 ifFalse:[
		leftPart := String new:i
	    ]
	]
    ].
    self cursorLine:lineNr col:((leftPart size) + 1).
    nextLineNr := self validateCursorLine:(lineNr + 1).

    nextLineNr > (list size) ifFalse:[
	(rightPart := self listAt:nextLineNr) isNil ifTrue:[
	    rightPart := ''
	] ifFalse:[
	    removeBlanks ifTrue:[
		rightPart := rightPart withoutLeadingSeparators.
	    ]
	].

	bothParts := leftPart , rightPart.
	(trimBlankLines and:[bothParts isBlank]) ifTrue:[bothParts := nil].
	list at:lineNr put:bothParts.
	self redrawLine:lineNr.
	self deleteLine:nextLineNr
    ]

    "Created: 9.9.1997 / 09:27:38 / cg"
    "Modified: 9.9.1997 / 09:28:27 / cg"
!

replace:aCharacter atLine:lineNr col:colNr
    "replace a single character at lineNr/colNr"

    |line lineSize newLine drawCharacterOnly|

    self checkModificationsAllowed ifFalse:[ ^ self].

    aCharacter == (Character cr) ifTrue:[
        ^ self
    ].

    drawCharacterOnly := true.
    self checkForExistingLine:lineNr.
    line := list at:lineNr.
    lineSize := line size.

    (trimBlankLines
    and:[colNr > lineSize
    and:[aCharacter == Character space]]) ifTrue:[
        ^ self
    ].

    (lineSize == 0) ifTrue:[
        newLine := aCharacter asString species new:colNr.
    ] ifFalse: [
        (colNr > lineSize) ifTrue: [
            newLine := line species new:colNr.
            newLine replaceFrom:1 to:lineSize with:line startingAt:1.
        ] ifFalse: [
            newLine := line copy.
        ]
    ].
    newLine at:colNr put:aCharacter.
    aCharacter == (Character tab) ifTrue:[
        newLine := self withTabsExpanded:newLine.
        drawCharacterOnly := false
    ].
    list at:lineNr put:newLine.
    widthOfWidestLine notNil ifTrue:[
        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
    ].
    self textChanged.
    shown ifTrue:[
        drawCharacterOnly ifTrue:[
            self redrawLine:lineNr col:colNr
        ] ifFalse:[
            self redrawLine:lineNr from:colNr
        ]
    ]

    "Created: / 6.3.1996 / 12:29:20 / cg"
    "Modified: / 10.6.1998 / 18:50:18 / cg"
!

replaceString:aString atLine:lineNr col:colNr
    "replace multiple characters starting at lineNr/colNr.
     This is not prepared to encounter special chars (except TAB)
     in the string."

    |line lineSize newLine endCol|

    self checkModificationsAllowed ifFalse:[ ^ self].

    self checkForExistingLine:lineNr.
    line := list at:lineNr.
    lineSize := line size.

    endCol := colNr + aString size - 1.
    (lineSize == 0) ifTrue:[
        newLine := aString species new:endCol.
    ] ifFalse: [
        (endCol > lineSize) ifTrue: [
            aString isText ifTrue:[
                newLine := aString species new:endCol.
            ] ifFalse:[
                newLine := line species new:endCol.
            ].
            newLine replaceFrom:1 to:lineSize with:line startingAt:1.
        ] ifFalse: [
            aString isText ifTrue:[
                newLine := aString species new:line size.
                newLine replaceFrom:1 to:lineSize with:line startingAt:1.
            ] ifFalse:[
                newLine := line copy.
            ]
        ]
    ].
    newLine replaceFrom:colNr with:aString.
    (aString includes:(Character tab)) ifTrue:[
        newLine := self withTabsExpanded:newLine.
    ].
    list at:lineNr put:newLine.
    widthOfWidestLine notNil ifTrue:[
        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
    ].
    self textChanged.
    shown ifTrue:[
        self redrawLine:lineNr from:colNr
    ]

    "Created: / 11.6.1998 / 10:38:32 / cg"
    "Modified: / 20.6.1998 / 20:23:50 / cg"
!

splitLine:lineNr before:colNr
    "split the line linNr before colNr; the right part (from colNr)
     is cut off and inserted after lineNr; the view is redrawn"

    |line lineSize leftRest rightRest visLine w h mustWait    
     srcY    "{ Class: SmallInteger }" |

    list isNil ifFalse:[
	lineNr > (list size) ifFalse:[
	    (colNr == 1) ifTrue:[
		self insertLine:nil before:lineNr.
		^ self
	    ].
	    line := list at:lineNr.
	    line isNil ifFalse:[
		lineSize := line size.
		(colNr <= lineSize) ifTrue:[
		    rightRest := line copyFrom:colNr to:lineSize.
		    (colNr > 1) ifTrue:[
			leftRest := line copyTo:(colNr - 1)
		    ]
		] ifFalse:[
		    leftRest := line
		]
	    ].
	    leftRest notNil ifTrue:[
		(trimBlankLines and:[leftRest isBlank]) ifTrue:[leftRest := nil]
	    ].
	    list at:lineNr put:leftRest.
	    self withoutRedrawInsertLine:rightRest before:(lineNr + 1).

	    visLine := self listLineToVisibleLine:(lineNr).
	    visLine notNil ifTrue:[
		w := self widthForScrollBetween:lineNr
					    and:(firstLineShown + nLinesShown).
		srcY := topMargin + (visLine * fontHeight).
		h := ((nLinesShown - visLine - 1) * fontHeight).
		(mustWait := (w > 0 and:[h > 0])) ifTrue:[
		    self catchExpose.
		    self 
			copyFrom:self 
			x:textStartLeft y:srcY
			toX:textStartLeft y:(srcY + fontHeight)
			width:w
			height:((nLinesShown - visLine - 1) * fontHeight)
			async:true.
		].
		self redrawLine:lineNr.
		self redrawLine:(lineNr + 1).
		mustWait ifTrue:[self waitForExpose]
	    ].
	    widthOfWidestLine := nil. "/ unknown
	    self textChanged.
	]
    ]

    "Modified: 29.1.1997 / 13:03:22 / cg"
!

withoutRedrawInsertLine:aString before:lineNr
    "insert the argument, aString before line lineNr; the string
     becomes line nileNr; everything else is moved down; the view
     is not redrawn"

    |line|

    self checkModificationsAllowed ifFalse:[ ^ self].

    line := aString.
    line notNil ifTrue:[
        line isString ifTrue:[
            line isBlank ifTrue:[
                line := nil
            ] ifFalse:[
                (line includes:(Character tab)) ifTrue:[
                    line := self withTabsExpanded:line
                ]
            ]
        ]
    ].
    list isNil ifTrue: [
        list := StringCollection new:lineNr
    ] ifFalse: [
        list grow:((list size + 1) max:lineNr)
    ].

    "I have changed 'replaceFrom:to:with:startingAt:' to correctly handle 
     overlapping copy - if it didn't, we had to use:"
"
    index := list size.
    [index > lineNr] whileTrue: [
        pIndex := index - 1.
        list at:index put:(list at:pIndex).
        index := pIndex
    ].
"
    list replaceFrom:(lineNr + 1) to:(list size) with:list startingAt:lineNr.
    list at:lineNr put:line.
    self contentsChanged

    "Modified: / 10.6.1998 / 19:00:56 / cg"
!

withoutRedrawInsertLines:lines from:start to:end before:lineNr
    "insert a bunch of lines before line lineNr; the view is not redrawn"

    |newLine newLines nLines|

    self checkModificationsAllowed ifFalse:[ ^ self].

    nLines := end - start + 1.
    newLines := Array new:(lines size).
    start to:end do:[:index |
        newLine := lines at:index.
        newLine notNil ifTrue:[
            newLine isString ifTrue:[
                newLine isBlank ifTrue:[
                    newLine := nil
                ] ifFalse:[
                    (newLine includes:(Character tab)) ifTrue:[
                        newLine := self withTabsExpanded:newLine
                    ]
                ]
            ]
        ].
        newLines at:index put:newLine
    ].
    list isNil ifTrue: [
        list := StringCollection new:(lineNr + nLines + 1)
    ] ifFalse: [
        list grow:((list size + nLines) max:(lineNr + nLines - 1))
    ].

    "I have changed 'replaceFrom:to:with:startingAt:' to correctly handle 
     overlapping copy - if it didn't, we had to use:"
"
    index := list size.
    [index > lineNr] whileTrue: [
        pIndex := index - 1.
        list at:index put:(list at:pIndex).
        index := pIndex
    ].
"
    list replaceFrom:(lineNr + nLines) to:(list size) with:list startingAt:lineNr.
    list replaceFrom:lineNr to:(lineNr + nLines - 1) with:newLines startingAt:start.
    self contentsChanged

    "Modified: / 10.6.1998 / 19:01:16 / cg"
!

withoutRedrawInsertStringWithoutCRs:aString atLine:lineNr col:colNr
    "insert aString (which has no crs) at lineNr/colNr"

    |isText strLen line lineSize newLine stringType sz|

    (aString notNil) ifFalse:[ ^ self].

    strLen := aString size.
    self checkForExistingLine:lineNr.

    stringType := aString string species.
    isText     := aString isText.
    line       := list at:lineNr.

    line notNil ifTrue:[
        lineSize := line size.
        line bitsPerCharacter > aString bitsPerCharacter ifTrue:[
            stringType := line string species
        ].
        line isText ifTrue:[ isText := true ]

    ] ifFalse:[
        lineSize := 0
    ].

    ((colNr == 1) and:[lineSize == 0]) ifTrue: [
        newLine := aString
    ] ifFalse:[
        (lineSize == 0 or:[colNr > lineSize]) ifTrue: [
            sz := colNr + strLen - 1
        ] ifFalse:[
            sz := lineSize + strLen
        ].

        isText ifFalse:[
            newLine := stringType new:sz
        ] ifTrue:[
            newLine := Text string:(stringType new:sz)
        ].

        (lineSize ~~ 0) ifTrue: [
            (colNr > lineSize) ifTrue: [
                newLine replaceFrom:1 to:lineSize
                               with:line startingAt:1
            ] ifFalse: [
                newLine replaceFrom:1 to:(colNr - 1)
                               with:line startingAt:1.
                newLine replaceFrom:(colNr + strLen) to:(lineSize + strLen)
                               with:line startingAt:colNr
            ]
        ].
        newLine replaceFrom:colNr to:(colNr + strLen - 1)
                       with:aString startingAt:1
    ].

    (aString includes:(Character tab)) ifTrue:[
        newLine := self withTabsExpanded:newLine
    ].

    list at:lineNr put:newLine.
    widthOfWidestLine notNil ifTrue:[
        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:newLine).
    ].
    self textChanged.

    "Modified: / 10.6.1998 / 19:01:52 / cg"
! !

!EditTextView methodsFor:'event processing'!

buttonPress:button x:x y:y
    "hide the cursor when button is activated"

    hasKeyboardFocus := true.
    cursorShown ifTrue: [
        self drawCursor
    ].

    ((button == 1) or:[button == #select]) ifTrue:[
        self hideCursor
    ].
    (button == #paste) ifTrue:[
        self pasteOrReplace.
        ^ self
    ].
    super buttonPress:button x:x y:y

    "Modified: / 23.3.1999 / 13:51:40 / cg"
!

buttonRelease:button x:x y:y
    "move the cursor to the click-position of previous button press"

    ((button == 1) or:[button == #select]) ifTrue:[
        typeOfSelection := nil. 
        selectionStartLine isNil ifTrue:[
            clickCol notNil ifTrue:[
                self cursorMovementAllowed ifTrue:[
                    self cursorLine:clickLine col:clickCol
                ]
            ]
        ] ifFalse:[
            lastString := nil. "new selection invalidates remembered string"
        ].
        self showCursor
    ].
    super buttonRelease:button x:x y:y

    "Modified: / 18.6.1998 / 14:14:05 / cg"
!

keyPress:key x:x y:y
    "handle keyboard input"

    <resource: #keyboard (#Paste #Insert #Cut #Again #Replace #Accept
                          #Delete #BasicDelete #BackSpace #BasicBackspace
                          #SelectWord
                          #SearchMatchingParent #SelectMatchingParents 
                          #SelectToEnd #SelectFromBeginning
                          #BeginOfLine #EndOfLine #NextWord #PreviousWord
                          #CursorRight #CursorDown #CursorLeft #CursorUp
                          #Return #Tab #Escape
                          #GotoLine #Delete #BeginOfText #EndOfText
                          #SelectLine #ExpandSelectionByLine #DeleteLine
                          #InsertLine
                          #SelectLineFromBeginning
                          #'F*' #'f*')>

    |sensor n fKeyMacros shifted i|

    sensor := self sensor.
    shifted := (sensor ? device) shiftDown.

    (key isMemberOf:Character) ifTrue:[
        self isReadOnly ifTrue:[
            self flash
        ] ifFalse:[
            typeOfSelection == #paste ifTrue:[
                "pasted selection will NOT be replaced by keystroke"
                self unselect
            ].

            "replace selection by what is typed in -
             if word was selected with a space, keep it"

            (selectStyle == #wordLeft) ifTrue:[
                self replaceSelectionBy:(' ' copyWith:key)
            ] ifFalse:[
                (selectStyle == #wordRight) ifTrue:[
                    self replaceSelectionBy:(key asString , ' ').
                    self cursorLeft
                ] ifFalse:[
                    self replaceSelectionBy:key
                ]
            ].
            selectStyle := nil.

            showMatchingParenthesis ifTrue:[
                "emacs style parenthesis shower"

                "claus: only do it for closing parenthesis -
                        otherwise its too anoying.
                "
"
                (#( $( $) $[ $] ${ $} ) includes:key) ifTrue:[
"
                (#( $) $] $} ) includes:key) ifTrue:[
                self searchForMatchingParenthesisFromLine:cursorLine col:(cursorCol - 1)
                                   ifFound:[:line :col |
                                                |savLine savCol|

                                                self withCursor:Cursor eye do:[
                                                    savLine := cursorLine.
                                                    savCol := cursorCol.
                                                    self cursorLine:line col:col.
                                                    device flush.
                                                    "/ want to wait 200ms, but not if another keyPress
                                                    "/ arrives in the meantime ...
                                                    "/
                                                    5 timesRepeat:[
                                                        (sensor notNil and:[sensor hasKeyPressEventFor:self]) ifFalse:[
                                                            Processor activeProcess millisecondDelay:40.
                                                        ]
                                                    ].
                                                    self cursorLine:savLine col:savCol
                                                ]
                                           ]
                                ifNotFound:[self showNotFound]
                                   onError:[self beep]
                ].
            ].
        ].
        ^ self
    ].                         

    replacing := false.

    "
     Fn      pastes a key-sequence (but only if not overlayed with
             another function in the keyboard map)

     see TextView>>:x:y
    "
    (key at:1) asLowercase == $f ifTrue:[
        (('[fF][0-9]' match:key)
        or:['[fF][0-9][0-9]' match:key]) ifTrue:[
            shifted ifFalse:[
                fKeyMacros := UserPreferences current functionKeySequences.
                fKeyMacros notNil ifTrue:[
                    (fKeyMacros includesKey:key) ifTrue:[
                        self pasteOrReplace:(fKeyMacros at:key) asStringCollection.
                        ^ self
                    ]
                ]
            ]
        ].
    ].

    (key == #Accept)  ifTrue:[^ self accept].

    ((key == #Paste) or:[key == #Insert]) ifTrue:[self pasteOrReplace. ^self].
    (key == #Cut) ifTrue:[self cut. ^self].
    (key == #Again) ifTrue:[self again. ^self].

    (key == #Replace) ifTrue:[self replace. ^self].
    (key == #SelectWord) ifTrue:[
        self makeCursorVisible.
        ^ self selectWordUnderCursor. 
    ].

    (key == #SearchMatchingParent) ifTrue:[^ self searchForMatchingParenthesis.].
    (key == #SelectMatchingParents) ifTrue:[^ self searchForAndSelectMatchingParenthesis.].
    (key == #SelectToEnd) ifTrue:[^ self selectUpToEnd.].
    (key == #SelectFromBeginning) ifTrue:[^ self selectFromBeginning.].

" disabled - nobody liked it ...
  and if you like it, its better done in the keymap.

    (key == #Ctrlb) ifTrue:[self unselect. self cursorLeft. ^ self].
    (key == #Ctrlf) ifTrue:[self unselect. self cursorRight. ^ self].
    (key == #Ctrln) ifTrue:[self unselect. self cursorDown. ^ self].
    (key == #Ctrlp) ifTrue:[self unselect. self cursorUp. ^ self].
"

    (key == #BeginOfLine) ifTrue:[
        self unselect.
        shifted ifTrue:[
            self cursorHome
        ] ifFalse:[
            self cursorToBeginOfLine. 
        ].
        ^ self
    ].
    (key == #EndOfLine) ifTrue:[
        self unselect.
        shifted ifTrue:[
            self cursorToBottom
        ] ifFalse:[
            self cursorToEndOfLine. 
        ].
        ^ self
    ].
    (key == #NextWord) ifTrue:[self cursorToNextWord. ^self].
    (key == #PreviousWord) ifTrue:[self cursorToPreviousWord. ^self].
    (key == #GotoLine) ifTrue:[self gotoLine. ^self].

    (key == #CursorRight) ifTrue:[
        (shifted and:[selectionStartLine isNil]) ifTrue:[
            selectionStartLine := selectionEndLine := clickStartLine := cursorLine.
            selectionStartCol := selectionEndCol := clickStartCol := cursorCol.
            expandingTop := false.
            ^ self redrawLine:selectionStartLine. 
        ].

        selectionStartLine notNil ifTrue:[
            self cursorMovementAllowed ifTrue:[
                "/
                "/ treat the whole selection as cursor
                "/
                cursorLine := selectionEndLine.
                cursorVisibleLine := self listLineToVisibleLine:cursorLine.
                selectionEndCol == 0 ifTrue:[
                    selectionEndCol := 1.
                ].
                cursorCol := selectionEndCol.
                shifted ifTrue:[
                    self expandSelectionRight.
                    ^ self
                ].
                self unselect; makeCursorVisible.
                cursorCol == 1 ifTrue:[^ self].
            ].
        ].
        self cursorRight. ^self
    ].
    (key == #CursorDown) ifTrue:[
        (shifted and:[selectionStartLine isNil]) ifTrue:[
            selectionStartLine := clickStartLine := cursorLine. selectionEndLine := cursorLine + 1.
            selectionStartCol := clickStartCol := selectionEndCol := cursorCol.
            self redrawLine:selectionStartLine. 
            expandingTop := false.
            ^ self redrawLine:selectionEndLine. 
        ].

        selectionStartLine notNil ifTrue:[
            self cursorMovementAllowed ifTrue:[
                "/
                "/ treat the whole selection as cursor
                "/
                cursorLine := selectionEndLine.
                cursorVisibleLine := self listLineToVisibleLine:cursorLine.
                cursorCol := selectionStartCol.
                cursorCol == 0 ifTrue:[
                    cursorCol := 1.
                    cursorLine := cursorLine - 1.
                    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
                ].
                self makeCursorVisible.

                shifted ifTrue:[
                    clickLine := cursorLine.
                    clickCol := cursorCol.
                    self expandSelectionDown.
                    ^ self
                ].
                self unselect. 
            ].
        ].

        sensor isNil ifTrue:[
            n := 1
        ] ifFalse:[
            n := 1 + (sensor compressKeyPressEventsWithKey:#CursorDown).
        ].
        self cursorDown:n. 
        "/
        "/ flush keyboard to avoid runaway cursor
        "/
        sensor notNil ifTrue:[self sensor flushKeyboardFor:self].
        ^ self
    ].
    (key == #CursorLeft or:[key == #CursorUp]) ifTrue:[
        (shifted and:[selectionStartLine isNil]) ifTrue:[
            expandingTop := true.
            key == #CursorLeft ifTrue:[
                cursorCol > 1 ifTrue:[
                    selectionStartLine := selectionEndLine := clickStartLine := cursorLine.
                    selectionEndCol := clickStartCol := cursorCol-1.
                    selectionStartCol := cursorCol-1.
                    ^ self redrawLine:selectionStartLine. 
                ]
            ] ifFalse:[
                cursorLine > 1 ifTrue:[
                    selectionEndLine := clickStartLine := cursorLine.
                    selectionEndCol := selectionStartCol := clickStartCol := cursorCol.
                    selectionStartLine := cursorLine - 1.
                    ^ self redrawFromLine:selectionStartLine to:cursorLine. 
                ]
            ]
        ].

        selectionStartLine notNil ifTrue:[
            self cursorMovementAllowed ifTrue:[
                "/
                "/ treat the whole selection as cursor
                "/
                cursorLine := selectionStartLine.
                cursorVisibleLine := self listLineToVisibleLine:cursorLine.
                cursorCol := selectionStartCol.
                (key == #CursorLeft) ifTrue:[    
                    cursorCol := cursorCol+1.  "/ compensate for followup crsr-left
                ].
                self makeCursorVisible.

                shifted ifTrue:[
                    (key == #CursorUp) ifTrue:[
                        clickLine := cursorLine.
                        ^ self expandSelectionUp.
                    ].
                    ^ self expandSelectionLeft.
                ].
                self unselect. 
            ].
        ].
        (key == #CursorLeft) ifTrue:[
            self cursorLeft. ^self
        ].
        (key == #CursorUp)        ifTrue:[
            sensor isNil ifTrue:[
                n := 1
            ] ifFalse:[
                n := 1 + (sensor compressKeyPressEventsWithKey:#CursorUp).
            ].
            self cursorUp:n. 
            "/
            "/ flush keyboard to avoid runaway cursor
            "/
            sensor notNil ifTrue:[sensor flushKeyboardFor:self].
            ^ self
        ].
    ].

    (key == #Return)    ifTrue:[
        shifted ifTrue:[
            self unselect. self cursorReturn. ^self
        ].
        self isReadOnly ifTrue:[
            self unselect; makeCursorVisible.
            self cursorReturn
        ] ifFalse:[
            insertMode ifFalse:[
                self cursorReturn.
                autoIndent == true ifTrue:[
                    i := self leftIndentForLine:(cursorLine + 1).
                    self cursorCol:(i+1 max:1)
                ]
            ] ifTrue:[
                "/ old version just unselected ...
                "/ self unselect; makeCursorVisible.

                "/ new version deletes ...
                typeOfSelection == #paste ifTrue:[
                    self unselect; makeCursorVisible.
                ] ifFalse:[
                    self copyAndDeleteSelection.            
                ].
                self insertCharAtCursor:(Character cr). 
                autoIndent == true ifTrue:[
                    i := self leftIndentForLine:cursorLine.
                    self indentFromLine:cursorLine toLine:cursorLine.
                    self cursorCol:(i+1 max:1)
                ].
            ].
        ].
        ^self
    ].

    (key == #Tab) ifTrue:[
        self tabMeansNextField ifTrue:[^ super keyPress:key x:x y:y].

        shifted ifTrue:[
            "
             the old version used shift-tab as backtab,
             however, backtab was seldom used.
             An alternative is to make it a non-inserting tab ...
            "
            "/ self unselect. self cursorBacktab.
            self unselect. self cursorTab. 
            ^self
        ].

        "
         uncomment line below, if you like RAND/INed/MAXed editor behavior
         (where tab-key is only cursor positioning)
         this was the original behavior of the TAB key, but many people
         complained ....
        "
        insertMode ifFalse:[
            self unselect. self cursorTab. ^self
        ].
        self unselect. self insertTabAtCursor. 
        ^self
    ].

    (key == #BackSpace
     or:[key == #BasicBackspace]) ifTrue:[
        selectionStartLine notNil ifTrue:[
            (key == #BasicBackspace) ifTrue:[
                ^ self deleteSelection.
            ] ifFalse:[
                ^ self copyAndDeleteSelection.
            ].
        ].

        self makeCursorVisible.
        self deleteCharBeforeCursor. ^self
    ].

    (key == #Delete
     or:[key == #BasicDelete]) ifTrue:[
        selectionStartLine notNil ifTrue:[
            (key == #BasicDelete) ifTrue:[
                ^ self deleteSelection.
            ] ifFalse:[
                ^ self copyAndDeleteSelection.
            ].
        ].
        self makeCursorVisible.
        self deleteCharAtCursor. ^self
    ].

    (key == #BeginOfText) ifTrue:[     "i.e. HOME"
        self unselect. 
        cursorVisibleLine == 1 ifTrue:[
            self cursorHome.
        ] ifFalse:[
            self cursorToFirstVisibleLine
        ].
        ^ self
    ].
    (key == #EndOfText) ifTrue:[       "i.e. END"
        self unselect.
        cursorVisibleLine == nFullLinesShown ifTrue:[
            self cursorToBottom.
        ] ifFalse:[
            self cursorToLastVisibleLine
        ].
        ^self
    ].
    ((key == #Escape)
    or:[key == #SelectLineFromBeginning])    ifTrue:[
        self makeCursorVisible.
        self unselect. self selectCursorLineFromBeginning. ^ self
    ].
    (key == #SelectLine)    ifTrue:[
        self makeCursorVisible.
        self unselect. self selectCursorLine. ^ self
    ].
    (key == #ExpandSelectionByLine)    ifTrue:[
"/        self makeCursorVisible.
        self selectExpandCursorLine. ^ self
    ].
    (key == #DeleteLine)    ifTrue:[
        self makeCursorVisible.
        self unselect. self deleteCursorLine. ^self
    ].
    (key == #InsertLine)    ifTrue:[
        self makeCursorVisible.
        self unselect. self insertLine:nil before:cursorLine. ^self
    ].
    super keyPress:key x:x y:y

    "Modified: / 6.2.1998 / 11:59:59 / stefan"
    "Modified: / 20.9.1998 / 17:55:11 / cg"
!

mapped
    "view was made visible"

    super mapped.
"/    self makeCursorVisible.
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.

    "Modified: 20.12.1996 / 14:15:56 / cg"
!

pointerEnter:state x:x y:y
    "mouse pointer entered - request the keyboard focus (sometimes)"

    self wantsFocusWithPointerEnter ifTrue:[
        self requestFocus.
    ].
!

sizeChanged:how
    "make certain, cursor is visible after the sizechange"

    |cv|

    cv := cursorVisibleLine.
    super sizeChanged:how.
    cv notNil ifTrue:[
	self makeLineVisible:cursorLine
    ]
! !

!EditTextView methodsFor:'focus handling'!

hasKeyboardFocus:aBoolean
    "sent by the windowGroup, a delegate or myself to make me show a block cursor
     (otherwise, I would not know about this)"

    hasKeyboardFocus := aBoolean.
    (cursorShown 
    and:[self enabled 
    and:[readOnly not]]) ifTrue:[
        self drawCursor
    ].

    "Modified: / 23.3.1999 / 13:49:35 / cg"
!

showFocus:explicit
    "in addition to however my superclass thinks how a focusView is to be
     displayed, show the cursor when I got the focus"

    self showCursor.
    self hasKeyboardFocus:true.
    super showFocus:explicit

    "Modified: 11.12.1996 / 16:56:54 / cg"
!

wantsFocusWithPointerEnter
    "return true, if I want the focus when
     the mouse pointer enters"

    |pref|

    pref := UserPreferences current focusFollowsMouse.
    (pref ~~ false
    and:[(styleSheet at:#'editText.requestFocusOnPointerEnter' default:true)
    and:[self enabled 
    and:[readOnly not]]]) ifTrue:[
        ^ true
    ].

    ^ false



! !

!EditTextView methodsFor:'formatting'!

indent
    "indent selected line-range"

    |start end|

    selectionStartLine isNil ifTrue:[^ self].
    start := selectionStartLine.
    end := selectionEndLine.
    (selectionEndCol == 0) ifTrue:[
	end := end - 1
    ].
    self unselect.
    self indentFromLine:start toLine:end
!

indentFromLine:start toLine:end
    "indent a line-range - this is don by searching for the 
     last non-empty line before start, and change the indent
     of the line based on that indent."

    |leftStart delta d line spaces|

    leftStart := self leftIndentForLine:start.
    (leftStart == 0) ifTrue:[^ self].

    delta := leftStart - (self leftIndentOfLine:start).
    (delta == 0) ifTrue:[^ self].
    (delta > 0) ifTrue:[
	spaces := String new:delta
    ].
    start to:end do:[:lineNr |
	line := self listAt:lineNr.
	line notNil ifTrue:[
	    line isBlank ifTrue:[
		list at:lineNr put:nil
	    ] ifFalse:[
		(delta > 0) ifTrue:[
		    line := spaces , line.
		    widthOfWidestLine notNil ifTrue:[
			widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
		    ]
		] ifFalse:[
		    "check if deletion is ok"
		    d := delta negated + 1.

		    line size > d ifTrue:[
			(line copyTo:(d - 1)) withoutSeparators isEmpty ifTrue:[
			    line := line copyFrom:d
			]
		    ].
		    widthOfWidestLine := nil
		].
		list at:lineNr put:line.
		self textChanged.
	    ]
	]
    ].
    self redrawFromLine:start to:end

    "Modified: 5.3.1996 / 14:59:18 / cg"
!

leftIndentForLine:lineNr
    "find an appropriate indent for a line.
     this is done by searching for the last non-empty line before it
     and returning its indent."

    "SHOULD GO TO ListView"

    |line lnr indent|

    lnr := lineNr.

    [lnr ~~ 1] whileTrue:[
	lnr  := lnr - 1.
	line := self listAt:lnr.

	line notNil ifTrue:[
	    indent := line indexOfNonSeparatorStartingAt:1.
	    indent ~~ 0 ifTrue:[
		^ indent - 1
	    ]
	]
    ].
    ^ 0

    "Created: 5.3.1996 / 14:58:53 / cg"
! !

!EditTextView methodsFor:'initialization'!

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

    super fetchDeviceResources.

    cursorFgColor notNil ifTrue:[cursorFgColor := cursorFgColor onDevice:device].
    cursorBgColor notNil ifTrue:[cursorBgColor := cursorBgColor onDevice:device].
    cursorNoFocusFgColor notNil ifTrue:[cursorNoFocusFgColor := cursorNoFocusFgColor onDevice:device].

    "Created: 14.1.1997 / 00:15:24 / cg"
    "Modified: 18.2.1997 / 15:02:46 / cg"
!

initEvents
    "enable enter/leave events in addition"

    super initEvents.
    self enableEnterLeaveEvents
!

initStyle
    "initialize style specific stuff"

    super initStyle.
    lockUpdates := false.

    cursorFgColor := DefaultCursorForegroundColor.
    cursorFgColor isNil ifTrue:[cursorFgColor := bgColor].
    cursorBgColor := DefaultCursorBackgroundColor.
    cursorBgColor isNil ifTrue:[cursorBgColor := fgColor].
    cursorType := cursorTypeNoFocus := DefaultCursorType.
    DefaultCursorTypeNoFocus notNil ifTrue:[
        cursorTypeNoFocus := DefaultCursorTypeNoFocus.
    ].
    cursorNoFocusFgColor := DefaultCursorNoFocusForegroundColor.
    cursorNoFocusFgColor isNil ifTrue:[
        cursorType ~~ #block ifTrue:[
            cursorNoFocusFgColor := cursorBgColor
        ] ifFalse:[
            cursorNoFocusFgColor := cursorFgColor
        ]
    ].

    "Modified: / 20.5.1998 / 04:26:31 / cg"
!

initialize
    "initialize a new EditTextView;
     setup some instance variables"

    super initialize.

    self level:-1.
    readOnly := false.
    fixedSize := false.
    exceptionBlock := [:errorText | ].
    cursorShown := prevCursorState := true.
    cursorLine := 1.
    cursorVisibleLine := 1.
    cursorCol := 1.
    modifiedChannel := ValueHolder newBoolean.
    acceptChannel := ValueHolder newBoolean.
    acceptChannel addDependent:self.
    showMatchingParenthesis := false.
    hasKeyboardFocus := false. "/ true.
    tabMeansNextField := false.
    autoIndent := false.
    insertMode := true.
    st80Mode := ST80Mode.
    trimBlankLines := st80Mode not. "true."

    "Modified: / 20.6.1998 / 18:19:17 / cg"
! !

!EditTextView methodsFor:'menu actions'!

cut
    "cut selection into copybuffer"

    |line col history sel s|

    (self checkModificationsAllowed) ifFalse:[
        self flash.
        ^ self
    ].

    sel := self selection.
    sel notNil ifTrue:[
        lastString := s := sel asStringWithCRs.
        line := selectionStartLine.
        col := selectionStartCol.
        undoAction := [ self cursorLine:line col:col.
                        self insertLines:(Array with:s) withCR:false.
                      ].

        "
         remember in CopyBuffer
        "
        self setTextSelection:lastString.

        "
         append to DeleteHistory (if there is one)
        "
        history := Smalltalk at:#DeleteHistory.
        history notNil ifTrue:[
            history addAll:(lastString asStringCollection).
            history size > 1000 ifTrue:[
                history := history copyFrom:(history size - 1000)
            ].
        ].

        "
         now, delete it
        "
        self deleteSelection.
        lastReplacement := nil
    ] ifFalse:[
        "
         a cut without selection will search&cut again
        "
        self again
    ]

    "Modified: / 5.4.1998 / 16:51:53 / cg"
!

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

    cursorLine notNil ifTrue:[
	^ cursorLine
    ].
    ^ super defaultForGotoLine
!

editMenu
    "return the views middleButtonMenu"

    <resource: #keyboard (#Again #Copy #Cut #Paste #Accept #Find #GotoLine #SaveAs #Print)>
    <resource: #programMenu>

    |items m sub sensor|

    ((sensor := self sensor) notNil and:[sensor ctrlDown]) ifTrue:[
        items := #(
                        ('again (for all)'      multipleAgain)  
                  ).
    ] ifFalse:[
        items := #(
"/                        ('undo'     undo                   )
                        ('again'   again            Again  )
                        ('-'                               )
                        ('copy'    copySelection    Copy   )
                        ('cut'     cut              Cut    )
                        ('paste'   pasteOrReplace   Paste  )
                        ('-'                               )
                        ('accept'  accept           Accept )
                        ('='                               )
                        ('others'  others                  )
                  ).
    ].

    m := PopUpMenu itemList:items resources:resources.

    items := #(
                    ('search ...'    search         Find         )
                    ('goto ...'      gotoLine       GotoLine     )
                    ('-'                                         )
                    ('font ...'      changeFont                  )
                    ('-'                                         )
                    ('indent'        indent                      )
                    ('autoIndent \c' autoIndent:                 )
                    ('insertMode \c' insertMode:                 )
                    ('-'                                         )
                    ('save as ...'   save           SaveAs       )
                    ('print'         doPrint        Print        )
              ).

    sub := PopUpMenu itemList:items resources:resources performer:model.

    m subMenuAt:#others put:sub.
    sub checkToggleAt:#autoIndent: put:autoIndent.
    sub checkToggleAt:#insertMode: put:insertMode.

    self isReadOnly ifTrue:[
        m disableAll:#(paste pasteOrReplace cut indent autoIndent: insertMode:)
    ].
    self hasSelection not ifTrue:[
        m disable:#copySelection.
    ].
    (self hasSelection not or:[self isReadOnly]) ifTrue:[
        m disable:#cut.
    ].
    (undoAction isNil) ifTrue:[
        m disable:#undo.
    ].
    acceptEnabled == false ifTrue:[
        m disable:#accept
    ].
    ^ m.

    "Modified: / 21.5.1998 / 15:52:38 / cg"
!

paste
    "paste the copybuffer; if there is a selection, unselect first.
     Then paste at cursor position."

    |sel|

    self checkModificationsAllowed ifFalse:[
        self flash.
        ^ self
    ].

    sel := self getTextSelection.
    self unselect.  
    sel notNil ifTrue:[
        self paste:sel.
    ]

    "Modified: / 5.4.1998 / 16:55:02 / cg"
!

paste:someText
    "paste someText at cursor"

    |s nLines startLine startCol l1 l2 c1 c2|

    self checkModificationsAllowed ifFalse:[^ self].

    someText notNil ifTrue:[
        s := someText.
        s isString ifTrue:[
            s := s asStringCollection
        ] ifFalse:[
            (s isStringCollection) ifFalse:[
                self warn:'selection (' , s class name , ') is not convertable to Text'.
                ^ self
            ]
        ].
        (nLines := s size) == 0 ifTrue:[^ self].
        (nLines == 1 and:[(s at:1) size == 0]) ifTrue:[^ self].

        startLine := l1 := cursorLine.
        startCol := c1 := cursorCol.
        self insertLines:(s withTabsExpanded) withCR:false.
        l2 := cursorLine.
        c2 := (cursorCol - 1).
        self selectFromLine:l1 col:c1 toLine:l2 col:c2.
        typeOfSelection := #paste.
        undoAction := [ self unselect.
                        self deleteFromLine:l1 col:c1 toLine:l2 col:c2.
                        self cursorLine:l1 col:c1.
                      ].
    ]

    "Modified: / 14.2.1996 / 11:14:14 / stefan"
    "Modified: / 12.6.1998 / 22:12:00 / cg"
!

pasteOrReplace
    "paste the copybuffer; if there is a selection, replace it.
     otherwise paste at cursor position. Replace is not done
     for originating by a paste, to allow multiple
     paste."

    |sel|

    self checkModificationsAllowed ifFalse:[
        self flash.
        ^ self
    ].

    sel := self getTextSelection.
    self pasteOrReplace:sel.

    "Modified: / 5.4.1998 / 16:55:16 / cg"
!

pasteOrReplace:someText
    "paste someText; if there is a selection, replace it.
     otherwise paste at cursor position. Replace is not done
     for originating by a paste, to allow multiple
     paste."

    self checkModificationsAllowed ifFalse:[^ self].

    ((self hasSelection == true) and:[typeOfSelection ~~ #paste]) ifTrue:[
        ^ self replace:someText
    ].
    self paste:someText.

    "Modified: / 5.4.1998 / 16:55:21 / cg"
!

replace
    "replace the selection by the contents of the copybuffer"

    |sel|

    self checkModificationsAllowed ifFalse:[^ self].

    sel := self getTextSelection.
    sel notNil ifTrue:[
        self replace:sel
    ]

    "Modified: / 5.4.1998 / 16:55:24 / cg"
!

replace:someText
    "replace the selection by someText"

    |selected selectedString| 

    self checkModificationsAllowed ifFalse:[^ self].

    selected := self selection.
    selected isNil ifTrue:[
        ^ self paste:someText
    ].
    self deleteSelection.

    "take care, if we replace a selection without space by a word selected
     with one - in this case we usually do not want the space.
     But, if we replace a word-selected selection by something without a
     space, we DO want the space added."

    selected size == 1 ifTrue:[
        selectedString := selected at:1.
    ].

    someText size == 1 ifTrue:[
        |cutOffSpace addSpace replacement replacementString|

        cutOffSpace := false.
        addSpace := false.
        replacement := someText copy.

        selectedString notNil ifTrue:[
            ((selectedString startsWith:' ') or:[selectedString endsWith:' ']) ifFalse:[
               "selection has no space"

                ((selectStyle == #wordleft) or:[selectStyle == #wordRight]) ifTrue:[
                    cutOffSpace := true
                ]
            ] ifTrue:[
                addSpace := true
            ]
        ].
        replacementString := replacement at:1.
        cutOffSpace ifTrue:[
            (replacementString startsWith:' ') ifTrue:[
                replacementString := replacementString withoutSpaces
            ].
        ] ifFalse:[
            selectStyle == #wordLeft ifTrue:[
                "want a space at left"
                (replacementString startsWith:' ') ifFalse:[
                    replacementString := replacementString withoutSpaces.
                    replacementString := ' ' , replacementString
                ]
            ].
            selectStyle == #wordRight ifTrue:[
                "want a space at right"

                (replacementString endsWith:' ') ifFalse:[
                    replacementString := replacementString withoutSpaces.
                    replacementString := replacementString , ' '
                ]
            ].
        ].
        replacement at:1 put: replacementString.
        self paste:replacement.
    ] ifFalse:[
        self paste:someText
    ].
    lastString := selectedString.
    lastReplacement := someText

    "Modified: / 14.2.1996 / 10:37:02 / stefan"
    "Modified: / 5.4.1998 / 16:55:28 / cg"
!

showDeleted
    "open a readonly editor on all deleted text"

    |v|

    v := EditTextView openWith:(Smalltalk at:#DeleteHistory).
    v readOnly:true.
    v topView label:'deleted text'.
! !

!EditTextView methodsFor:'private'!

checkModificationsAllowed
    "check if the text can be modified (i.e. is not readOnly).
     evaluate the exceptionBlock if not.
     This block should be provided by the application or user of the textView,
     and may show a warnBox or whatever."

    self isReadOnly ifTrue: [
        exceptionBlock isNil ifTrue:[
            ^ false
        ].

        (exceptionBlock value:'Text may not be modified') ~~ true ifTrue:[
            ^ false
        ]
    ].
    ^ true

    "Modified: / 17.6.1998 / 15:51:10 / cg"
!

textChanged
    "my text was modified (internally).
     Sent whenever text has been edited (not to confuse with
     contentsChanged, which is triggered when the size has changed, and
     is used to notify scrollers, other views etc.)"

    self contentsChanged.
    self modified:true.
    contentsWasSaved := false

    "Modified: 14.2.1997 / 16:58:38 / cg"
! !

!EditTextView methodsFor:'queries'!

currentLine
    "the current line (for relative gotos)"

    ^ cursorLine

    "Created: / 17.5.1998 / 20:07:52 / cg"
!

isKeyboardConsumer
    "return true, if the receiver is a keyboard consumer;
     Return true here, redefined from SimpleView."

    ^ true

!

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

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

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

tabMeansNextField
    "return true, if a Tab character should shift focus."

    "if not readOnly, I want my tab keys ..."

    ^ self isReadOnly or:[tabMeansNextField]

    "Created: 7.2.1996 / 19:15:31 / cg"
!

widthOfContents
    "return the width of the contents in pixels
     Redefined to add the size of a space (for the cursor).
     this enables us to scroll one position further than the longest
     line (and possibly see the cursor behind the line)"

    |w dev|

    w := super widthOfContents.
    (dev := device) isNil ifTrue:[
	"/ really dont know ...
	dev := Screen current
    ].
    ^ w + (font widthOn:dev)

    "Modified: 28.5.1996 / 19:32:25 / cg"
! !

!EditTextView methodsFor:'realization'!

realize
    "make the view visible - scroll to make the cursor visible."

    super realize.

    self makeCursorVisible.
    cursorFgColor := cursorFgColor onDevice:device.
    cursorBgColor := cursorBgColor onDevice:device.

    "Modified: 20.12.1996 / 14:16:05 / cg"
    "Created: 24.7.1997 / 18:24:12 / cg"
! !

!EditTextView methodsFor:'redrawing'!

redrawCursorIfBetweenVisibleLine:startVisLine and:endVisLine
    "redraw the cursor, if it sits in a line range"

    cursorShown ifTrue:[
	cursorVisibleLine notNil ifTrue:[
	    (cursorVisibleLine between:startVisLine and:endVisLine) ifTrue:[
		self drawCursorCharacter
	    ]
	]
    ]
!

redrawCursorIfInVisibleLine:visLine
    "redraw the cursor, if it sits in visible line"

    cursorShown ifTrue:[
	(visLine == cursorVisibleLine) ifTrue:[
	    self drawCursorCharacter
	]
    ]
!

redrawFromVisibleLine:startVisLine to:endVisLine
    "redraw a visible line range"

    super redrawFromVisibleLine:startVisLine to:endVisLine.
    self redrawCursorIfBetweenVisibleLine:startVisLine and:endVisLine
!

redrawVisibleLine:visLine
    "redraw a visible line"

    super redrawVisibleLine:visLine.
    self redrawCursorIfInVisibleLine:visLine
!

redrawVisibleLine:visLine col:colNr
    "redraw the single character in visibleline at colNr"

    cursorShown ifTrue:[
	(visLine == cursorVisibleLine) ifTrue:[
	    (colNr == cursorCol) ifTrue:[
		self drawCursorCharacter.
		^ self
	    ]
	]
    ].
    super redrawVisibleLine:visLine col:colNr
!

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

    super redrawVisibleLine:visLine from:startCol.
    self redrawCursorIfInVisibleLine:visLine
!

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

    super redrawVisibleLine:visLine from:startCol to:endCol.
    self redrawCursorIfInVisibleLine:visLine
! !

!EditTextView methodsFor:'scrolling'!

halfPageDown
    "half a page down - to keep cursor on same visible line, it has to be moved
     within the real text  "

    |prevCursorLine|

    prevCursorLine := cursorVisibleLine.
    super halfPageDown.
    self cursorVisibleLine:prevCursorLine col:cursorCol
!

halfPageUp
    "half a page up - to keep cursor on same visible line, it has to be moved
     within the real text  "

    |prevCursorLine|

    prevCursorLine := cursorVisibleLine.
    super halfPageUp.
    self cursorVisibleLine:prevCursorLine col:cursorCol
!

originChanged:delta
    "sent after scrolling - have to show the cursor if it was on before"

    super originChanged:delta.
    "
     should we move the cursor with the scroll - or leave it ?
    "
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
    prevCursorState ifTrue:[
        self showCursor
    ]

    "Modified: / 17.6.1998 / 16:13:24 / cg"
!

originWillChange
    "sent before scrolling - have to hide the cursor"

    prevCursorState := cursorShown.
    "/ cursorShown := false.
    cursorShown ifTrue:[
        self hideCursor
    ]

    "Modified: / 6.7.1998 / 13:07:23 / cg"
!

pageDown
    "page down - to keep cursor on same visible line, it has to be moved
     within the real text  "

    |prevCursorLine|

    prevCursorLine := cursorVisibleLine.
    super pageDown.
    self cursorVisibleLine:prevCursorLine col:cursorCol
!

pageUp
    "page up - to keep cursor on same visible line, it has to be moved
     within the real text  "

    |prevCursorLine|

    prevCursorLine := cursorVisibleLine.
    super pageUp.
    self cursorVisibleLine:prevCursorLine col:cursorCol
! !

!EditTextView methodsFor:'searching'!

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

    |startLine startCol|

    cursorLine isNil ifTrue:[^ self].
    selectionStartLine notNil ifTrue:[
	startLine := selectionStartLine.
	startCol := selectionStartCol
    ] ifFalse:[
	startLine := cursorLine min:list size.
	startCol := cursorCol
    ].
    self 
	searchBackwardFor:pattern 
	startingAtLine:startLine col:startCol
	ifFound:[:line :col |
	    self cursorLine:line col:col.
	    self showMatch:pattern atLine:line col:col.
"/            self makeLineVisible:cursorLine
	    typeOfSelection := #search] 
	ifAbsent:aBlock

    "Modified: 9.10.1997 / 13:02:04 / cg"
!

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

    |startLine startCol|

    cursorLine isNil ifTrue:[^ self].
    selectionStartLine notNil ifTrue:[
	startLine := selectionStartLine.
	startCol := selectionStartCol
    ] ifFalse:[
	startLine := cursorLine min:list size.
	startCol := cursorCol
    ].
    self 
	searchBackwardFor:pattern
	ignoreCase:ign
	startingAtLine:startLine col:startCol
	ifFound:[:line :col |
	    self cursorLine:line col:col.
	    self showMatch:pattern atLine:line col:col.
"/            self makeLineVisible:cursorLine
	    typeOfSelection := #search] 
	ifAbsent:aBlock

    "Modified: 9.10.1997 / 13:02:13 / cg"
!

searchForAndSelectMatchingParenthesis
    "select characters enclosed by matching parenthesis if one is under cusor"

    self 
	searchForMatchingParenthesisFromLine:cursorLine col:cursorCol
	ifFound:[:line :col | 
		  self selectFromLine:cursorLine col:cursorCol
			       toLine:line col:col]
	ifNotFound:[self showNotFound]
	onError:[self beep]

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

searchForMatchingParenthesis
    "search for a matching parenthesis starting at cursor position. 
     Search for the corresponding character is done forward if its an opening, 
     backwards if its a closing parenthesis.
     Positions the cursor if found, peeps if not"

     self 
	searchForMatchingParenthesisFromLine:cursorLine col:cursorCol
	ifFound:[:line :col | self cursorLine:line col:col]
	ifNotFound:[self showNotFound]
	onError:[self beep]

    "Modified: 9.10.1997 / 12:56:30 / cg"
!

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

    |startCol|

    "/ if there is no selection and the cursor is at the origin, 
    "/ assume its the first search and do not skip the very first match
    startCol := cursorCol.
    self hasSelection ifFalse:[
	(cursorLine == 1 and:[cursorCol == 1]) ifTrue:[
	    startCol := 0
	]
    ].

    self 
	searchFwd:pattern 
	startingAtLine:cursorLine col:startCol 
	ifAbsent:aBlock

    "Modified: 9.10.1997 / 12:58:59 / cg"
!

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

    |startCol|

    "/ if there is no selection and the cursor is at the origin, 
    "/ assume its the first search and do not skip the very first match
    startCol := cursorCol.
    self hasSelection ifFalse:[
	(cursorLine == 1 and:[cursorCol == 1]) ifTrue:[
	    startCol := 0
	]
    ].

    self 
	searchFwd:pattern
	ignoreCase:ign
	startingAtLine:cursorLine col:startCol 
	ifAbsent:aBlock

    "Modified: 9.10.1997 / 12:58:59 / cg"
    "Created: 9.10.1997 / 13:04:10 / cg"
!

searchFwd:pattern ignoreCase:ign startingAtLine:startLine col:startCol ifAbsent:aBlock
    "do a forward search"

    cursorLine isNil ifTrue:[^ self].
    self 
	searchForwardFor:pattern 
	ignoreCase:ign
	startingAtLine:startLine col:startCol
	ifFound:[:line :col |
	    self cursorLine:line col:col.
	    self showMatch:pattern atLine:line col:col.
"/            self makeLineVisible:cursorLine
	    typeOfSelection := #search]
	ifAbsent:aBlock

    "Modified: 9.10.1997 / 12:57:47 / cg"
    "Created: 9.10.1997 / 13:01:12 / cg"
!

searchFwd:pattern startingAtLine:startLine col:startCol ifAbsent:aBlock
    "do a forward search"

    self 
	searchForwardFor:pattern 
	startingAtLine:startLine col:startCol
	ifFound:[:line :col |
	    self cursorLine:line col:col.
	    self showMatch:pattern atLine:line col:col.
	    typeOfSelection := #search]
	ifAbsent:aBlock

    "Modified: 9.10.1997 / 13:07:52 / cg"
!

setSearchPattern
    "set the searchpattern from the selection if there is one, and position
     cursor to start of pattern"

    |sel|

    "/
    "/ if the last operation was a replcae, set pattern to last
    "/ original string (for search after again)
    "/
    (lastString notNil 
     and:[lastReplacement notNil
     and:[typeOfSelection ~~ #search]]) ifTrue:[
	lastSearchPattern := lastString asString withoutSeparators.
	^ self
    ].

    "/
    "/ if there is a selection:
    "/    if there was no previous search, take it as search pattern.
    "/    if there was a previous search, only take the selection if
    "/    it did not result from a paste.
    "/    (to allow search-paste to be repeated)
    "/
    sel := self selection.
    sel notNil ifTrue:[
	(lastSearchPattern isNil
	or:[typeOfSelection ~~ #paste]) ifTrue:[
	    self cursorLine:selectionStartLine col:selectionStartCol.
	    lastSearchPattern := sel asString withoutSeparators
	]
    ]

    "Modified: 20.4.1996 / 12:50:13 / cg"
! !

!EditTextView methodsFor:'selections'!

autoMoveCursorToEndOfSelection
    "return true, if the cursor should be automatically moved to the
     end of a selection.
     Redefined to return false in terminaViews, where the cursor should
     not be affected by selecting"

    ^ true
!

selectAll
    "select the whole text.
     redefined to send super selectFrom... since we dont want the
     cursor to be moved in this case."

    list isNil ifTrue:[
	self unselect
    ] ifFalse:[
	super selectFromLine:1 col:1 toLine:(list size + 1) col:0.
	typeOfSelection := nil
    ]

    "Modified: 28.2.1997 / 19:14:54 / cg"
!

selectCursorLine
    "select cursorline"

    self selectFromLine:cursorLine col:1 toLine:cursorLine+1 col:0 
!

selectCursorLineFromBeginning
    "select cursorline up to cursor position"

    cursorCol > 1 ifTrue:[
	self selectFromLine:cursorLine col:1
		     toLine:cursorLine col:(cursorCol-1)
    ]

    "Modified: 16.8.1996 / 19:14:14 / cg"
!

selectExpandCursorLine
    "expand selection by one line or select cursorline"

    selectionStartLine isNil ifTrue:[
	self selectCursorLine
    ] ifFalse:[
	self selectFromLine:selectionStartLine col:selectionStartCol
		     toLine:cursorLine+1 col:0.
	self makeLineVisible:selectionEndLine
    ]
!

selectFromBeginning
    "select the text from the beginning to the current cursor position."

    |col|

    list isNil ifTrue:[
	self unselect
    ] ifFalse:[
	cursorCol == 0 ifTrue:[
	    col := 0
	] ifFalse:[
	    col := cursorCol - 1
	].
	super selectFromLine:1 col:1 toLine:cursorLine col:col.
	typeOfSelection := nil
    ]
!

selectFromLine:startLine col:startCol toLine:endLine col:endCol
    "when a range is selected, position the cursor behind the selection
     for easier editing. Also typeOfSelection is nilled here."

    super selectFromLine:startLine col:startCol toLine:endLine col:endCol.
    (selectionEndLine notNil and:[self autoMoveCursorToEndOfSelection]) ifTrue:[
        self cursorLine:selectionEndLine col:(selectionEndCol + 1).
    ].
    typeOfSelection := nil
!

selectUpToEnd
    "select the text from the current cursor position to the end."

    list isNil ifTrue:[
	self unselect
    ] ifFalse:[
	super selectFromLine:cursorLine col:cursorCol toLine:(list size + 1) col:0.
	typeOfSelection := nil
    ]
!

selectWordUnderCursor
    "select the word under the cursor"

    self selectWordAtLine:cursorLine col:cursorCol
!

unselect
    "forget and unhilight selection - must take care of cursor here"

    |wasOn|

    wasOn := self hideCursor.
    super unselect.
    wasOn ifTrue:[self showCursor]
! !

!EditTextView methodsFor:'undo & again'!

again
    "repeat the last action (which was a cut or replace).
     If current selection is not last string, search forward to
     next occurence of it before repeating the last operation."

    |s l c sel savedSelectStyle|

    lastString notNil ifTrue:[
	s := lastString asString.

	"remove final cr"
	s := s copyWithoutLast:1.
"/        s := s withoutSpaces.        "XXX - replacing text with spaces ..."
	savedSelectStyle := selectStyle.
	selectStyle := nil.

	sel := self selection.

	"if we are already there (after a find), ommit search"

	(sel notNil and:[sel asString withoutSeparators = s]) ifTrue:[
	    undoAction := [self insertLines:lastString atLine:cursorLine col:cursorCol].
	    l := selectionStartLine "cursorLine". 
	    c := selectionStartCol "cursorCol".
	    self deleteSelection.
	    lastReplacement notNil ifTrue:[
		self insertLines:lastReplacement asStringCollection withCR:false.
		self selectFromLine:l col:c toLine:cursorLine col:(cursorCol - 1).
	    ].
	    selectStyle := savedSelectStyle.
	    ^ true
	].

	self searchForwardFor:s startingAtLine:cursorLine col:cursorCol 
	    ifFound:
		[
		    :line :col |

		    |repl|

		    self selectFromLine:line col:col
				 toLine:line col:(col + s size - 1).
		    self makeLineVisible:line.
		    undoAction := [self insertLines:lastString atLine:line col:col].

		    self deleteSelection.
		    lastReplacement notNil ifTrue:[
			lastReplacement isString ifFalse:[
			    repl := lastReplacement asString withoutSpaces
			] ifTrue:[
			    repl := lastReplacement withoutSpaces.
			].
			self insertLines:repl asStringCollection withCR:false.
			self selectFromLine:line col:col toLine:cursorLine col:(cursorCol - 1).
		    ].
		    selectStyle := savedSelectStyle.
		    ^ true
		] 
	   ifAbsent:
		[
		    self showNotFound.
		    selectStyle := savedSelectStyle.
		    ^ false
		]
    ]

    "Modified: 9.10.1996 / 16:14:11 / cg"
!

multipleAgain
    "repeat the last action (which was a cut or replace) until search fails"

    [self again] whileTrue:[]
!

undo
    "currently not implemented"

    undoAction notNil ifTrue:[
        undoAction value.
        undoAction := nil.
    ]
! !

!EditTextView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/Attic/ETxtView.st,v 1.212 1999-08-18 15:06:16 cg Exp $'
! !