ETxtView.st
author claus
Thu, 17 Nov 1994 15:34:12 +0100
changeset 62 7cc1e330da47
parent 60 f3c738c24ce6
child 70 14443a9ea4ec
permissions -rw-r--r--
*** empty log message ***

"
 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 modified fixedSize
			      exceptionBlock
			      errorMessage
			      cursorFgColor cursorBgColor cursorType
			      undoAction  
			      typeOfSelection 
			      lastString lastReplacement lastAction 
			      replacing showMatchingParenthesis
			      hasKeyboardFocus'
       classVariableNames:'DefaultCursorForegroundColor DefaultCursorBackgroundColor
			   DefaultCursorType'
       poolDictionaries:''
       category:'Views-Text'
!

EditTextView comment:'
COPYRIGHT (c) 1989 by Claus Gittinger
	    All Rights Reserved

$Header: /cvs/stx/stx/libwidg/Attic/ETxtView.st,v 1.17 1994-11-17 14:33:59 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libwidg/Attic/ETxtView.st,v 1.17 1994-11-17 14:33:59 claus Exp $
"
!

documentation
"
    a view for editable text - adds editing functionality to TextView

    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
    prevCursorState         <Boolean>       temporary
    readOnly                <Boolean>       true, if text may not be edited
    modified                <Boolean>       true, if text has been modified
    fixedSize               <Boolean>       true, if no lines may be added/removed
    exceptionBlock          <Block>         block to be evaluated when readonly text is about to be modified
    errorMessage            <String>        message text 
    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)
    undoAction              <Block>         block which undoes last cut, paste or replace
    typeOfSelection         <Symbol>        #paste, if selection created by paste, nil otherwise
    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

    used globals:

    CopyBuffer              <Text>          text of last copy or cut
    DeleteHistory           <Text>          last 1000 lines of deleted text
"
! !

!EditTextView class methodsFor:'defaults'!

updateStyleCache
    DefaultCursorForegroundColor := StyleSheet colorAt:'textCursorForegroundColor'.
    DefaultCursorBackgroundColor := StyleSheet colorAt:'textCursorBackgroundColor'.
    DefaultCursorType := StyleSheet at:'textCursorType' default:#block.
! !

!EditTextView methodsFor:'initialization'!

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

    super initialize.

    self level:-1.
    errorMessage := 'Text may not me changed'.
    readOnly := false.
    fixedSize := false.
    exceptionBlock := [:errorText | ].
    cursorShown := prevCursorState := true.
    cursorLine := 1.
    cursorVisibleLine := 1.
    cursorCol := 1.
    modified := false.
    showMatchingParenthesis := false.
    "
     this will change - focusIn/Out seems to not work always
    "
    hasKeyboardFocus := true.
!

initStyle
    "initialize style specific stuff"

    super initStyle.
    cursorFgColor := DefaultCursorForegroundColor.
    cursorFgColor isNil ifTrue:[cursorFgColor := bgColor].
    cursorBgColor := DefaultCursorBackgroundColor.
    cursorBgColor isNil ifTrue:[cursorBgColor := fgColor].
    cursorType := DefaultCursorType.
!

initEvents
    "enable enter/leave events in addition"

    super initEvents.
    self enableEnterLeaveEvents
!

initializeMiddleButtonMenu
    "initialize the views middleButtonMenu"

    |labels|
 
    labels := resources array:#(
"/                               'undo'
			       'again'
			       '-'
			       'copy'
			       'cut'
			       'paste'
			       '-'
			       'accept'
			       '='
			       'others'
			       ).

    self middleButtonMenu:(PopUpMenu
				labels:labels
			     selectors:#(
"/                                         undo
					 again
					 nil
					 copySelection
					 cut
					 paste
					 nil
					 accept
					 nil
					 others
					)
				receiver:self
				     for:self).

    middleButtonMenu subMenuAt:#others put:(PopUpMenu
				labels:(resources array:#(
					 'search ...'
					 'goto ...'
					 '-'
					 'font ...'
					 '-'
					 'indent'
					 '-'
					 'save as ...'
					 'print'
					))
			      selectors:#(
					  search
					  gotoLine
					  nil
					  changeFont
					  nil
					  indent
					  nil
					  save
					  print
					 )
				receiver:self
				     for:self).

    self enableOrDisableSelectionMenuEntries
!

realize
    "make the view visible"

    super realize.
    cursorFgColor := cursorFgColor on:device.
    cursorBgColor := cursorBgColor on:device.
! !

!EditTextView methodsFor:'accessing'!

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

    self hideCursor.
    cursorFgColor := color1 on:device.
    cursorBgColor := color2 on:device.
    self showCursor
!

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

    ^ cursorLine
!

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

    ^ cursorCol
!

contents
    "answer the contents as a String"

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

list:something
    "position cursor home when setting contents"

    super list:something.
    self cursorHome
!

readOnly
    "make the text readonly"

    readOnly ifFalse:[
	readOnly := true.
	self enableOrDisableSelectionMenuEntries
    ]
!

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

    readOnly ifFalse:[
	readOnly := true.
	middleButtonMenu disable:#cut.
	middleButtonMenu disable:#paste.
	middleButtonMenu disable:#replace.
	middleButtonMenu disable:#indent
    ]
!

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

    exceptionBlock := aBlock
!

fromFile:aFileName
    "take contents from a named file"

    self contents:(aFileName asFilename readStream contents)
!

modified:aBoolean
    "set the modified flag"

    modified := aBoolean
!

modified
    "return true if text was modified"

    ^ modified
!

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

!EditTextView methodsFor:'private'!

contentsChanged
    "triggered whenever text is changed"

    super contentsChanged.
    modified := true.
    contentsWasSaved := false
! !

!EditTextView methodsFor:'editing'!

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

    |leftPart rightPart bothParts nextLineNr|

    list isNil ifFalse:[
	nextLineNr := lineNr + 1.
	(nextLineNr > list size) ifFalse:[
	    (list at:lineNr) isNil ifTrue:[
		leftPart := ''
	    ] ifFalse:[
		leftPart := list at:lineNr
	    ].
	    (list at:nextLineNr) isNil ifTrue:[
		rightPart := ''
	    ] ifFalse:[
		rightPart := list at:nextLineNr
	    ].
	    bothParts := leftPart , rightPart.
	    bothParts isBlank ifTrue:[bothParts := nil].
	    list at:lineNr put:bothParts.
	    self redrawLine:lineNr.
	    self deleteLine:nextLineNr
	]
    ]
!

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      
     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:[
		leftRest isBlank ifTrue:[leftRest := nil]
	    ].
	    list at:lineNr put:leftRest.
	    modified := true.
	    contentsWasSaved := false.
	    self withoutRedrawInsertLine:rightRest before:(lineNr + 1).

	    visLine := self listLineToVisibleLine:(lineNr).
	    visLine notNil ifTrue:[
		w := self widthForScrollBetween:lineNr
					    and:(firstLineShown + nLinesShown).
		srcY := topMargin + (visLine * fontHeight).
		self catchExpose.
		self copyFrom:self x:textStartLeft y:srcY
				 toX:textStartLeft y:(srcY + fontHeight)
			       width:w
			      height:((nLinesShown - visLine - 1) * fontHeight).
		self redrawLine:lineNr.
		self redrawLine:(lineNr + 1).
		self waitForExpose
	    ]
	]
    ]
!

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|

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    line := aString.
    line notNil ifTrue:[
	line isBlank ifTrue:[
	    line := nil
	] ifFalse:[
	    (line occurrencesOf:(Character tab)) == 0 ifFalse:[
		line := self withTabsExpanded:line
	    ]
	]
    ].
    list isNil ifTrue: [
	list := Text 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
!

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

    |visLine w 
     dstY "{ Class: SmallInteger }" |

    self withoutRedrawInsertLine:aString before:lineNr.
    visLine := self listLineToVisibleLine:lineNr.
    visLine notNil ifTrue:[
	w := self widthForScrollBetween:lineNr
				    and:(firstLineShown + nLinesShown).
	dstY := topMargin + ((visLine ) * fontHeight).
	self catchExpose.
	self copyFrom:self x:textStartLeft y:(dstY - fontHeight)
			 toX:textStartLeft y:dstY
		       width:w
		      height:((nLinesShown - visLine "- 1") * fontHeight).
	self redrawVisibleLine:visLine.
	self waitForExpose
    ]
!

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

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

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    self withoutRedrawInsertLines:someText
			     from:start to:end
			   before:lineNr.
    visLine := self listLineToVisibleLine:lineNr.
    visLine notNil ifTrue:[
	nLines := end - start + 1.
	((visLine + nLines) >= nLinesShown) ifTrue:[
	    self redrawFromVisibleLine:visLine to:nLinesShown
	] ifFalse:[
	    w := self widthForScrollBetween:(lineNr + nLines)
					and:(firstLineShown + nLines + nLinesShown).
	    srcY := topMargin + ((visLine - 1) * fontHeight).
	    dstY := srcY + (nLines * fontHeight).
	    self catchExpose.
	    self copyFrom:self x:textStartLeft y:srcY
			     toX:textStartLeft y:dstY
			   width:w
			  height:(height - dstY).
	    self redrawFromVisibleLine:visLine to:(visLine + nLines - 1).
	    self waitForExpose
	]
    ]
!

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

    |line lineSize newLine drawCharacterOnly|

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    aCharacter == (Character cr) ifTrue:[
	self splitLine:lineNr before:colNr.
	^ self
    ].
    drawCharacterOnly := false.
    self checkForExistingLine:lineNr.
    line := list at:lineNr.
    lineSize := line size.
    (aCharacter == Character space) ifTrue:[
	(colNr > lineSize)  ifTrue:[
	    ^ self
	]
    ].
    (lineSize == 0) ifTrue: [
	newLine := String new:colNr.
	drawCharacterOnly := true
    ] ifFalse: [
	(colNr > lineSize) ifTrue: [
	    newLine := String new:colNr.
	    newLine replaceFrom:1 to:lineSize
			   with:line startingAt:1.
	    drawCharacterOnly := true
	] ifFalse: [
	    newLine := String 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.
    aCharacter == (Character tab) ifTrue:[
	newLine := self withTabsExpanded:newLine.
	drawCharacterOnly := false
    ].
    list at:lineNr put:newLine.
    modified := true.
    contentsWasSaved := false.
    drawCharacterOnly ifTrue:[
	self redrawLine:lineNr col:colNr
    ] ifFalse:[
	self redrawLine:lineNr from:colNr
    ]
!

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

    |newLine newLines nLines|

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].

    nLines := end - start + 1.
    newLines := Array new:(lines size).
    start to:end do:[:index |
	newLine := lines at:index.
	newLine notNil ifTrue:[
	    newLine isBlank ifTrue:[
		newLine := nil
	    ] ifFalse:[
		(newLine occurrencesOf:(Character tab)) == 0 ifFalse:[
		    newLine := self withTabsExpanded:newLine
		]
	    ]
	].
	newLines at:index put:newLine
    ].
    list isNil ifTrue: [
	list := Text 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
!

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

    |strLen line lineSize newLine|

    aString isNil ifTrue:[^ self].
    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    strLen := aString size.
    self checkForExistingLine:lineNr.
    line := list at:lineNr.
    line notNil ifTrue:[
	lineSize := line size
    ] ifFalse:[
	lineSize := 0
    ].
    ((colNr == 1) and:[lineSize == 0]) ifTrue: [
	newLine := aString
    ] ifFalse:[
	(lineSize == 0) ifTrue: [
	    newLine := String new:(colNr + strLen - 1)
	] ifFalse: [
	    (colNr > lineSize) ifTrue: [
		newLine := String new:(colNr + strLen - 1).
		newLine replaceFrom:1 to:lineSize
			       with:line startingAt:1
	    ] ifFalse: [
		newLine := String new:(lineSize + strLen).
		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 occurrencesOf:(Character tab)) == 0 ifFalse:[
	newLine := self withTabsExpanded:newLine
    ].

    list at:lineNr put:newLine.
    modified := true.
    contentsWasSaved := false.
!

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

    self withoutRedrawInsertStringWithoutCRs:aString atLine:lineNr col:colNr.
    self redrawLine:lineNr from:colNr
!

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

    aString notNil ifTrue:[
	self withCursorOffDo:[
	    self insertString:aString atLine:cursorLine col:cursorCol.
	    cursorCol := cursorCol + aString size
	]
    ]
!

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

    self withCursorOffDo:[
	self insert:aCharacter atLine:cursorLine col:cursorCol.
	aCharacter == (Character cr) ifTrue:[
	    self cursorReturn
	] ifFalse:[
	    cursorCol := cursorCol + 1
	].
	self makeCursorVisible
    ]
!

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 occurrencesOf:(Character cr)) == 0) ifTrue:[
	^ 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
    ]
!

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

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

    aString isNil ifTrue:[
	"new:"
	self insertCharAtCursor:(Character cr).
	^ self
    ].
    ((aString occurrencesOf:(Character cr)) == 0) ifTrue:[
	^ self insertStringWithoutCRsAtCursor:aString
    ].

    self insertLines:aString asText withCr:false.

"/    start := 1.
"/    end := aString size.
"/    "insert the 1st line"
"/    (cursorCol ~~ 1) ifTrue:[
"/        stop := aString indexOf:(Character cr) startingAt:start.
"/        stop == 0 ifTrue:[
"/            stop := end + 1
"/        ].
"/        subString := aString copyFrom:start to:(stop - 1).
"/        self insertStringWithoutCRsAtCursor:subString.
"/        self insertCharAtCursor:(Character cr).
"/        start := stop + 1
"/    ].
"/    "insert the block of full lines"
"/
"/    [start <= end] whileTrue:[
"/        stop := aString indexOf:(Character cr) startingAt:start.
"/        stop == 0 ifTrue:[
"/            stop := end + 1
"/        ].
"/        subString := aString copyFrom:start to:(stop - 1).
"/        self insertStringWithoutCRsAtCursor:subString.
"/        (stop < end) ifTrue:[
"/            self insertCharAtCursor:(Character cr)
"/        ].
"/        start := stop + 1
"/    ]
!

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

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|

    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:[
		    self withCursorOffDo:[
			self insertLines:lines 
				    from:start to:end
				  before:cursorLine.
			cursorLine := cursorLine + (end - start + 1).
			cursorVisibleLine := self absoluteLineToVisibleLine:
								     cursorLine
		    ]
		]
	    ].
	    withCr ifFalse:[
		"last line without cr"
		self insertStringAtCursor:(lines at:nLines)
	    ]
	]
    ]
!

insertTabAtCursor
    "insert spaces to next tab"

    |nextTab|

    self withCursorOffDo:[
	nextTab := self nextTabAfter:cursorCol.
	self insertStringAtCursor:(String new:(nextTab - cursorCol)).
    ].
    self makeCursorVisible.
!

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

    |line lineSize|

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    list isNil ifTrue:[^ self].

    (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 startCal lies behond end of startLine"
	line := list at:startLine.
	lineSize := line size.
	(startCol > lineSize) ifTrue:[
	    line isNil ifTrue:[
		line := String new:(startCol - 1)
	    ] ifFalse:[
		line := line , (String new:(startCol - 1 - lineSize))
	    ].
	    list at:startLine put:line.
	    modified := true.
	    contentsWasSaved := false.
	]
    ].

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

deleteFromLine:startLineNr toLine:endLineNr
    "delete some lines"

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    list isNil ifTrue:[^ self].
    list removeFromIndex:startLineNr toIndex:endLineNr.
    self contentsChanged.
    self redrawFromLine:startLineNr.
    (firstLineShown >= list size) ifTrue:[
	self makeLineVisible:(list size)
    ]
!

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

    readOnly ifTrue:[
	exceptionBlock value:errorMessage.
	^ false
    ].
    (list isNil or:[lineNr > list size]) ifTrue:[^ false].
    list removeIndex:lineNr.
    self contentsChanged.
    ^ true
!

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

    |lastLine|

    readOnly ifTrue:[
	exceptionBlock value:errorMessage.
	^ false
    ].
    (list isNil or:[startLine > list size]) ifTrue:[^ false].
    (endLine > list size) ifTrue:[
	lastLine := list size
    ] ifFalse:[
	lastLine := endLine
    ].
    list removeFromIndex:startLine toIndex:lastLine.
    self contentsChanged.
    ^ true
!

deleteLine:lineNr
    "delete line"

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

    w := self widthForScrollBetween:lineNr
				and:(firstLineShown + nLinesShown).
    (self deleteLineWithoutRedraw:lineNr) ifFalse:[^ self].
    visLine := self listLineToVisibleLine:lineNr.
    visLine notNil ifTrue:[
	srcY :=  margin + topMargin + (visLine * fontHeight).
	self catchExpose.
	self copyFrom:self x:textStartLeft y:srcY
			 toX:textStartLeft y:(srcY - fontHeight)
		       width:w height:((nLinesShown - visLine) * fontHeight).
	self redrawVisibleLine:nFullLinesShown.
	(nFullLinesShown ~~ nLinesShown) ifTrue:[
	    self redrawVisibleLine:nLinesShown
	].
	self waitForExpose
    ]
!

deleteCursorLine
    "delete the line where the cursor sits"

    self withCursorOffDo:[
	 self deleteLine:cursorLine
    ]
!

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

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

    |line lineSize newLine|

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    list isNil ifTrue: [^self].
    (list size < lineNr) ifTrue: [^ self].
    line := list at:lineNr.
    line isNil ifTrue: [^self].
    lineSize := line size.
    (colNr >= lineSize) ifTrue:[
	newLine := nil
    ] ifFalse:[
	newLine := line copyFrom:(colNr + 1) to:lineSize.
	newLine isBlank ifTrue:[
	    newLine := nil
	]
    ].
    list at:lineNr put:newLine.
    modified := true.
    contentsWasSaved := false.
    self redrawLine:lineNr
!

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

    |line newLine|

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    list isNil ifTrue: [^self].
    (list size < lineNr) ifTrue: [^ self].
    line := list at:lineNr.
    line isNil ifTrue: [^self].
    (colNr > line size) ifTrue: [^ self].
    newLine := line copyTo:(colNr - 1).
    newLine isBlank ifTrue:[
	newLine := nil
    ].
    list at:lineNr put:newLine.
    modified := true.
    contentsWasSaved := false.
    self redrawLine:lineNr
!

deleteCharsAtLine:lineNr fromCol:startCol toCol:endCol
    "delete characters from startCol to endCol in line lineNr"

    |line lineSize newLine|

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    list isNil ifTrue: [^self].
    (list size < lineNr) ifTrue: [^ self].

    line := list at:lineNr.
    line isNil ifTrue: [^self].
    lineSize := line size.
    (startCol > lineSize) ifTrue: [^ self].
    (endCol == 0) ifTrue:[^ self].
    (endCol < startCol) ifTrue:[^ self].
    (startCol == endCol) ifTrue:[
	self deleteCharAtLine:lineNr col:startCol.
	^ self
    ].
    (endCol >= lineSize) ifTrue:[
	self deleteCharsAtLine:lineNr fromCol:startCol.
	^ self
    ].
    (startCol <= 1) ifTrue:[
	self deleteCharsAtLine:lineNr toCol:endCol.
	^ self
    ].
    newLine := (line copyTo:(startCol - 1)) 
	       , (line copyFrom:(endCol + 1) to:lineSize).

    newLine isBlank ifTrue:[
	newLine := nil
    ].
    list at:lineNr put:newLine.
    modified := true.
    contentsWasSaved := false.
    self redrawLine:lineNr
!

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

    |line lineSize newLine drawCharacterOnly|

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    list isNil ifTrue: [^self].
    (list size < lineNr) ifTrue: [^ self].

    line := list at:lineNr.
    line isNil ifTrue: [^self].
    lineSize := line size.
    (colNr > lineSize) ifTrue: [^ self].

    drawCharacterOnly := false.
    (colNr == lineSize) ifTrue:[
	newLine := line copyTo:(lineSize - 1).
	fontIsFixedWidth ifTrue:[
	    drawCharacterOnly := true
	]
    ] ifFalse:[
	newLine := String new:(lineSize - 1).
	newLine replaceFrom:1 to:(colNr - 1)
		       with:line startingAt:1.
	newLine replaceFrom:colNr to:(lineSize - 1)
		       with:line startingAt:(colNr + 1)
    ].

    newLine isBlank ifTrue:[
	newLine := nil
    ].
    list at:lineNr put:newLine.
    modified := true.
    contentsWasSaved := false.
    drawCharacterOnly ifTrue:[
	self redrawLine:lineNr col:colNr
    ] ifFalse:[
	self redrawLine:lineNr from:colNr
    ]
!

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

    |oldSize lineNrAboveCursor|

    (cursorCol == 1) ifFalse:[
	 self withCursorOffDo:[
	     cursorCol := cursorCol - 1.
	     self deleteCharAtLine:cursorLine col:cursorCol
	 ]
    ] ifTrue:[
	 (cursorLine == 1) ifFalse:[
	     oldSize := 0.
	     lineNrAboveCursor := cursorLine - 1.
	     list notNil ifTrue:[
		(list size >= lineNrAboveCursor) ifTrue:[
		    (list at:lineNrAboveCursor) notNil ifTrue:[
			oldSize := (list at:lineNrAboveCursor) size
		    ]
		]
	     ].
	     self mergeLine:lineNrAboveCursor.
	     self withCursorOffDo:[
		 cursorLine := lineNrAboveCursor.
		 cursorCol := oldSize + 1.
		 cursorVisibleLine := self listLineToVisibleLine:cursorLine
	     ].
	     self makeCursorVisible
	 ]
    ]
!

deleteCharAtCursor
    "delete single character under cursor"

    self withCursorOffDo:[
	self deleteCharAtLine:cursorLine col:cursorCol
    ]
!

deleteSelection
    "delete the selection"

    |startLine startCol endLine endCol|

    readOnly ifTrue: [
	exceptionBlock value:errorMessage.
	^ self
    ].
    selectionStartLine notNil ifTrue:[
	startLine := selectionStartLine.
	startCol := selectionStartCol.
	endLine := selectionEndLine.
	endCol := selectionEndCol.
	self withCursorOffDo:[
	    self unselectWithoutRedraw.
	    self deleteFromLine:startLine col:startCol 
			 toLine:endLine col:endCol.
	    cursorCol := startCol.
	    cursorLine := startLine.
	    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
"/            self makeLineVisible:cursorLine
	    self makeCursorVisible
	]
    ]
!

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:[
	    (lastReplacement endsWith:Character space) ifTrue:[
		lastReplacement := lastReplacement copyTo:(lastReplacement size - 1).
		lastReplacement := lastReplacement copyWith:something.
		lastReplacement := lastReplacement copyWith:Character space
	    ] ifFalse:[
		lastReplacement := lastReplacement copyWith:something.
	    ]
	].
	self insertCharAtCursor:something
    ] ifFalse:[
	lastReplacement := something.
	self insertStringAtCursor:something
    ].
    keep ifTrue:[
	self cursorLine:l col:c
    ]
!

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

    self replaceSelectionBy:something keepCursor:false
! !

!EditTextView methodsFor:'formatting'!

indent
    "indent selected line-range"

    |start end|

    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 lnr delta d line spaces|

    "find a line to base indent on..."
    leftStart := 0.
    lnr := start.
    [(leftStart == 0) and:[lnr ~~ 1]] whileTrue:[
	lnr := lnr - 1.
	leftStart := self leftIndentOfLine:lnr
    ].

    (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
		] 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
			]
		    ]
		].
		list at:lineNr put:line.
		modified := true.
		contentsWasSaved := false.
	    ]
	]
    ].
    self redrawFromLine:start to:end
! !

!EditTextView methodsFor:'cursor handling'!

makeCursorVisible
    "scroll to make cursor visible"

    |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:[

"/ that was wrong
"/      ((line == selectionEndLine)
"/      and:[selectionEndCol notNil
"/      and:[col == (selectionEndCol+1)]]) ifTrue:[

	    line := selectionStartLine.
	    col := selectionStartCol.
	].
	self makeLineVisible:line.
	self makeColVisible:col inLine:line 
    ]
!

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

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

    hasKeyboardFocus ifTrue:[
	self drawFocusCursor
    ] ifFalse:[
	self drawNoFocusCursor
    ]
!

drawCursor:cursorType with:fgColor and:bgColor
    "draw the normal cursor."

    |x y w char|

    self hasSelection ifTrue:[
	"
	 hide cursor, if there is a selection
	"
	^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
    ].
    cursorType == #block ifTrue:[
	super drawVisibleLine:cursorVisibleLine 
			  col:cursorCol 
			 with:fgColor
			  and:bgColor.
	^ self
    ].
    cursorType == #frame ifTrue:[
	super redrawVisibleLine:cursorVisibleLine col:cursorCol.

	x := self xOfCol:cursorCol inVisibleLine:cursorVisibleLine.
	y := self yOfVisibleLine:cursorVisibleLine.
	char := self characterUnderCursor asString.
	self paint:bgColor.
	self displayRectangleX:x y:y width:(font widthOf:char)
				    height:fontHeight.
	^ self
    ].
    cursorType == #ibeam ifTrue:[
	x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
	y := self yOfVisibleLine:cursorVisibleLine.

	self paint:bgColor.
	self displayLineFromX:x-1 y:y toX:x-1 y:(y + fontHeight - 1). 
	self displayLineFromX:x y:y toX:x y:(y + fontHeight - 1). 
	^ self
    ].
    cursorType == #caret ifTrue:[
	x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
	y := (self yOfVisibleLine:cursorVisibleLine) + fontHeight - 3.
	w := fontWidth // 2.
	self paint:bgColor.
	self lineWidth:2.
	self displayLineFromX:x-w y:y+w toX:x y:y. 
	self displayLineFromX:x y:y toX:x+w y:y+w. 
    ].
    cursorType == #solidCaret ifTrue:[
	x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
	y := (self yOfVisibleLine:cursorVisibleLine) + fontHeight - 3.
	w := fontWidth // 2.
	self paint:bgColor.
	self fillPolygon:(Array with:(x-w) @ (y+w)
				with:(x @ y)
				with:(x+w) @ (y+w))
    ].
!


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

    self hasSelection ifTrue:[
	^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
    ].
    self drawCursor:cursorType with:cursorFgColor and:cursorBgColor.
!

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

    self hasSelection ifTrue:[
	^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
    ].
    cursorType ~~ #block ifTrue:[
	"these dont show unfocussed"
	^ self drawFocusCursor
    ].
    self drawCursor:#frame with:cursorFgColor and:cursorBgColor
!

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

    cursorVisibleLine notNil ifTrue:[
	((cursorType == #caret) or:[cursorType == #solidCaret]) ifTrue:[
	    "caret-cursor touches 4 characters"
	    cursorCol > 1 ifTrue:[
		super redrawVisibleLine:cursorVisibleLine from:cursorCol-1 to:cursorCol.
		super redrawVisibleLine:cursorVisibleLine+1 from:cursorCol-1 to:cursorCol.
	    ] ifFalse:[
		"care for left margin"
		super redrawVisibleLine:cursorVisibleLine.
		super redrawVisibleLine:cursorVisibleLine+1.
	    ].
	    ^ self
	].
	cursorType == #ibeam ifTrue:[
	    "ibeam-cursor touches 2 characters"
	    cursorCol > 1 ifTrue:[
		super redrawVisibleLine:cursorVisibleLine from:cursorCol-1 to:cursorCol.
	    ] ifFalse:[
		"care for left margin"
		super redrawVisibleLine:cursorVisibleLine.
	    ].
	    ^ self
	].
	"block is simple - just one character under cursor"
	super redrawVisibleLine:cursorVisibleLine col:cursorCol
    ]
!

hideCursor
    "make cursor invisible if currently visible; return true if cursor
     was visible"

    cursorShown ifTrue: [
	self undrawCursor.
	cursorShown := false.
	^ true
    ].
    ^ false
!

showCursor
    "make cursor visible if currently invisible"

    cursorShown ifFalse: [
	self drawCursor.
	cursorShown := true
    ]
!

withCursorOffDo:aBlock
    "evaluate aBlock with cursor off"

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

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

    self withCursorOffDo:[
	self scrollToTop.
	cursorCol := 1.
	cursorVisibleLine := 1.
	cursorLine := self visibleLineToAbsoluteLine:1.
	self makeCursorVisible.
    ]
!

cursorToBottom
    "move cursor to last line of text"

    |newTop|

    self withCursorOffDo:[
	newTop := list size - nFullLinesShown.
	(newTop < 1) ifTrue:[
	    newTop := 1
	].
	self scrollToLine:newTop.
	cursorCol := 1.
	cursorLine := list size.
	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	self makeCursorVisible.
    ]
!

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

    (cursorLine == 1) ifFalse: [
	cursorLine isNil ifTrue:[
	    cursorLine := firstLineShown + nFullLinesShown - 1.
	].
"/        cursorVisibleLine notNil ifTrue:[
	    self withCursorOffDo:[
		(cursorVisibleLine == 1) ifTrue:[self scrollUp].
		cursorLine := cursorLine - 1.
		cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	    ].
"/        ] ifFalse:[
"/            self makeCursorVisible.
"/        ]
    ]
!

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

    cursorVisibleLine notNil ifTrue:[
	self withCursorOffDo:[
	    (cursorVisibleLine >= nFullLinesShown) ifTrue:[self scrollDown].
	    cursorLine := cursorLine + 1.
	    cursorVisibleLine := self listLineToVisibleLine:cursorLine
	]
    ] ifFalse:[
	cursorLine isNil ifTrue:[
	    cursorLine := firstLineShown
	].
	cursorLine := cursorLine + 1.
	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	self makeCursorVisible.
    ].
!

cursorLeft
    "move cursor to left"

    (cursorCol == 1) ifFalse: [
	self withCursorOffDo:[cursorCol := cursorCol - 1]
    ].
    self makeCursorVisible.
!

cursorRight
    "move cursor to right"

    self withCursorOffDo:[cursorCol := cursorCol + 1].
    self makeCursorVisible.
!

cursorToBeginOfLine
    "move cursor to start of current line"

    self withCursorOffDo:[
	cursorCol := 1
    ].
    self makeCursorVisible.
!

cursorToEndOfLine
    "move cursor to end of current line"

    |line|

    self withCursorOffDo:[
	line := list at:cursorLine.
	cursorCol := line size + 1
    ].
    self makeCursorVisible.
!

cursorTab
    "move cursor to next tabstop"

    self withCursorOffDo:[
	cursorCol := self nextTabAfter:cursorCol
    ].
    self makeCursorVisible.
!

cursorBacktab
    "move cursor to prev tabstop"

    self withCursorOffDo:[
	cursorCol := self prevTabBefore:cursorCol
    ].
    self makeCursorVisible.
!

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

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

    self checkForExistingLine:(cursorLine + 1).
    cursorVisibleLine notNil ifTrue:[
	nFullLinesShown notNil ifTrue:[
	    (cursorVisibleLine >= nFullLinesShown) ifTrue:[self scrollDown]
	]
    ].
    self withCursorOffDo:[
	cursorCol := 1.
	cursorLine := cursorLine + 1.
	cursorVisibleLine := self listLineToVisibleLine:cursorLine
    ].
    self makeCursorVisible.
!

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

    self withCursorOffDo:[
	cursorLine := self visibleLineToAbsoluteLine:visibleLineNr.
	cursorVisibleLine := visibleLineNr.
	cursorCol := colNr.
	(cursorCol < 1) ifTrue:[
	    cursorCol := 1
	]
    ].
    self makeCursorVisible.
!

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

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

    self withCursorOffDo:[
	cursorLine := line.
	cursorVisibleLine := self listLineToVisibleLine:line.
	cursorCol := col.
	(cursorCol < 1) ifTrue:[
	    cursorCol := 1
	]
    ].
    self makeCursorVisible.
!

cursorToTop
    "move cursor to absolute home"

    self cursorLine:1 col:1
!

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

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

!EditTextView methodsFor:'undo & again'!

undo
    "currently not implemented"

    undoAction notNil ifTrue:[
	undoAction value
    ]
!

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|

    lastString notNil ifTrue:[
	s := lastString asString.
	"remove final cr"
	s := s copyTo:(s size - 1).

	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 asText withCr:false.
		self selectFromLine:l col:c toLine:cursorLine col:(cursorCol - 1).
	    ].
	    ^ true
	].

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

		    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:[
			self insertLines:lastReplacement asText withCr:false.
			self selectFromLine:line col:col toLine:cursorLine col:(cursorCol - 1).
		    ].
		    ^ true
		] 
	   ifAbsent:
		[
		    self showNotFound.
		    ^ false
		]
    ]
!

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

    [self again] whileTrue:[]
! !

!EditTextView methodsFor:'menu actions'!

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

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

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

    (self hasSelection notNil and:[typeOfSelection ~~ #paste]) ifTrue:[
	^ self replace
    ].
    self paste:(Smalltalk at:#CopyBuffer).
!

replace
    "replace selection by copybuffer"

    self replace:(Smalltalk at:#CopyBuffer)
!

cut
    "cut selection into copybuffer"

    |line col history sel|

    sel := self selection.
    sel notNil ifTrue:[
	lastString := sel.
	line := selectionStartLine.
	col := selectionStartCol.
	undoAction := [self insertLines:lastString atLine:line col:col].

	"
	 remember in CopyBuffer
	"
	Smalltalk at:#CopyBuffer put:lastString.

	"
	 append to DeleteHistory (if there is one)
	"
	history := Smalltalk at:#DeleteHistory.
	history notNil ifTrue:[
	    history addAll:(lastString asText).
	    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
    ]
!

paste:someText
    "paste someText at cursor"

    |startLine startCol|

    someText notNil ifTrue:[
	startLine := cursorLine.
	startCol := cursorCol.
	self insertLines:someText asText withCr:false.
	self selectFromLine:startLine col:startCol
		     toLine:cursorLine col:(cursorCol - 1).
	typeOfSelection := #paste.
	undoAction := [self cut].
    ]
!

replace:someText
    "replace selection by someText"

    |selected selectedString replacement replacementString 
     cutOffSpace addSpace|

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

    cutOffSpace := false.
    addSpace := false.

    replacement := someText copy.

    selected size == 1 ifTrue:[
	selectedString := selected at:1.
    ].
    selectedString notNil ifTrue:[
	((selectedString startsWith:' ') or:[selectedString endsWith:' ']) ifFalse:[
	   "selection has no space"

	    ((selectStyle == #wordleft) or:[selectStyle == #wordRight]) ifTrue:[
		cutOffSpace := true
	    ]
	] ifTrue:[
	    addSpace := true
	]
    ].

    replacement size == 1 ifTrue:[
	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
!

showDeleted
    "open a readonly editor on all deleted text"

    |v|

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

!EditTextView methodsFor:'selections'!

disableSelectionMenuEntries
    "disable relevant menu entries for a selection"

    middleButtonMenu notNil ifTrue:[
	super disableSelectionMenuEntries.
	middleButtonMenu disable:#cut.
	middleButtonMenu disable:#replace.
	middleButtonMenu disable:#indent
    ]
!

enableSelectionMenuEntries
    "enable relevant menu entries for a selection"

    middleButtonMenu notNil ifTrue:[
	"if readonly, never enable destructive functions"
	readOnly ifTrue:[
	    super enableSelectionMenuEntries.
	    middleButtonMenu disable:#cut.
	    middleButtonMenu disable:#replace.
	    middleButtonMenu disable:#indent.
	    middleButtonMenu disable:#paste.
	] ifFalse:[
	    super enableSelectionMenuEntries.
	    middleButtonMenu enable:#cut.
	    middleButtonMenu enable:#replace.
	    middleButtonMenu enable:#indent.
	]
    ]
! 

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

    self withCursorOffDo:[
	super unselect
    ]
!

selectCursorLine
    "select cursorline up to cursor position"

    self selectFromLine:cursorLine col:1
		 toLine:cursorLine col:cursorCol
!

selectWordUnderCursor
    "select the word under the cursor"

    self selectWordAtLine:cursorLine col:cursorCol
!

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.
    self cursorLine:selectionEndLine col:(selectionEndCol + 1).
    typeOfSelection := nil
!

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

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

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

!EditTextView methodsFor:'scrolling'!

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

    prevCursorState := cursorShown.
    cursorShown ifTrue:[
	self hideCursor
    ]
!

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

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
!

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

!EditTextView methodsFor:'searching'!

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

    |sel|

    "if last operation was a replcae, set pattern to last
     original string (for search after again)"

    (lastString notNil and:[lastReplacement notNil]) ifTrue:[
	searchPattern := lastString asString withoutSeparators.
	^ self
    ].

    sel := self selection.
    sel notNil ifTrue:[
	self cursorLine:selectionStartLine col:selectionStartCol.
	searchPattern := sel asString withoutSeparators
    ]
!

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

    cursorLine isNil ifTrue:[^ self].
    self searchForwardFor:pattern startingAtLine:cursorLine col:cursorCol
    ifFound:[:line :col |
	self cursorLine:line col:col.
	self selectFromLine:line col:col
		     toLine:line col:(col + pattern size - 1).
	self makeLineVisible:cursorLine
    ] ifAbsent:aBlock
!

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 selectFromLine:line col:col
		     toLine:line col:(col + pattern size - 1).
	self makeLineVisible:cursorLine
    ] ifAbsent:aBlock
!

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

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

    |i direction lineString line col parChar charSet ignoreSet closingChar 
     ignoring delta endCol cc incSet decSet nesting maxLine|

    charSet := #( $( $) $[ $] ${ $} ).
    ignoreSet := #( $' $" ).

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

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

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

    col := col + delta.
    [nesting ~~ 0] whileTrue:[
	lineString notNil ifTrue:[
	    direction == #fwd ifTrue:[
		endCol := lineString size.
	    ] ifFalse:[
		endCol := 1
	    ].
	    col to:endCol by:delta do:[:runCol |
		cc := lineString at:runCol.

		(ignoreSet includes:cc) ifTrue:[
		    ignoring := ignoring not
		].
		ignoring ifFalse:[
		    (incSet includes:cc) ifTrue:[
			nesting := nesting + 1
		    ] ifFalse:[
			(decSet includes:cc) ifTrue:[
			    nesting := nesting - 1
			]
		    ]
		].
		nesting == 0 ifTrue:[
		    "check if legal"

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

    ^ notFoundBlock value
!

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:[device beep]
!

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:[device beep]
! !

!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 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
    "redraw a visible line"

    super redrawVisibleLine:visLine.
    self redrawCursorIfInVisibleLine:visLine
!

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:'event processing'!

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

    |cv|

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

pointerEnter:state x:x y:y
    hasKeyboardFocus := true.
    self drawCursor.
    super pointerEnter:state x:x y:y
!

pointerLeave:state
    hasKeyboardFocus := false.
    self drawCursor.
    super pointerLeave:state
!


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

    (key isMemberOf:Character) ifTrue:[
	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|

					    savLine := cursorLine.
					    savCol := cursorCol.
					    self cursorLine:line col:col.
					    device synchronizeOutput.
					    OperatingSystem millisecondDelay:200.
					    self cursorLine:savLine col:savCol
				       ]
			    ifNotFound:[self showNotFound]
			       onError:[device beep]
	    ].
	].
	^ self
    ].                         

    replacing := false.

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

     see TextView>>keyPress:x:y
    "
    (#(F1 F2 F3 F4 F5 F6 F7 F8 F9) includes:key) ifTrue:[
	device shiftDown ifFalse:[
	    (Smalltalk at:#FunctionKeySequences) notNil ifTrue:[
		self paste:((Smalltalk at:#FunctionKeySequences) at:key) asText.
		^ self
	    ]
	]
    ].

    ((key == #Paste) or:[key == #Insert]) ifTrue:[self paste. ^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 cursorToBeginOfLine. ^self].
    (key == #EndOfLine) ifTrue:[self cursorToEndOfLine. ^self].
    (key == #NextWord) ifTrue:[self cursorToNextWord. ^self].
    (key == #GotoLine) ifTrue:[self gotoLine. ^self].

    (key == #CursorRight) ifTrue:[
	selectionStartLine notNil ifTrue:[
	    cursorLine := selectionEndLine.
	    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	    cursorCol := selectionEndCol.
	    cursorCol == 0 ifTrue:[
		cursorCol := 1.
	    ].
	    self unselect.
	    self makeCursorVisible.
	    cursorCol == 1 ifTrue:[^ self].
	].
	self cursorRight. ^self
    ].
    (key == #CursorDown) ifTrue:[
	selectionStartLine notNil ifTrue:[
	    cursorLine := selectionEndLine.
	    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	    cursorCol := selectionEndCol.
	    cursorCol == 0 ifTrue:[
		cursorCol := 1.
		cursorLine := cursorLine - 1.
		cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	    ].
	    self makeCursorVisible
	].
	self unselect. 
	self cursorDown. ^self
    ].
    (key == #CursorLeft or:[key == #CursorUp]) ifTrue:[
	selectionStartLine notNil ifTrue:[
	    cursorLine := selectionStartLine.
	    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	    cursorCol := selectionStartCol.
	    self makeCursorVisible
	].
	self unselect. 
	(key == #CursorLeft) ifTrue:[
	    self cursorLeft. ^self
	].
	(key == #CursorUp)        ifTrue:[
	    self cursorUp. ^self
	].
    ].

    (key == #Return)    ifTrue:[
	device shiftDown ifTrue:[
	    self unselect. self cursorReturn. ^self
	].
	self unselect. 
	self makeCursorVisible.
	self insertCharAtCursor:(Character cr). 
	^self
    ].
    (key == #Tab) ifTrue:[
	device shiftDown 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
	    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 ....
	"
	"/ self unselect. self cursorTab. ^self
	self unselect. self insertTabAtCursor. ^self
    ].
    (key == #BackSpace) ifTrue:[

" old version just did unselect here "
"
	self unselect. 
"
" new version deletes selection if any "
	selectionStartLine notNil ifTrue:[
	    Smalltalk at:#CopyBuffer put:(self selection).
	    self deleteSelection. ^ self
	].
	self makeCursorVisible.
	self deleteCharBeforeCursor. ^self
    ].
    (key == #Delete)    ifTrue:[
	selectionStartLine notNil ifTrue:[
	    Smalltalk at:#CopyBuffer put:(self selection).
	    self deleteSelection. ^ self
	].
	self makeCursorVisible.
	self deleteCharBeforeCursor. ^self
    ].
    (key == #Home)      ifTrue:[
	self unselect. self cursorHome. ^self
    ].
    (key == #End)       ifTrue:[
	self unselect. self cursorToBottom. ^self
    ].
    (key == #Escape)    ifTrue:[
	self makeCursorVisible.
	self unselect. self selectCursorLine. ^ self
    ].
    (key == #DeleteLine)    ifTrue:[
	self makeCursorVisible.
	self unselect. self deleteCursorLine. ^self
    ].
    super keyPress:key x:x y:y
!

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

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

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 cursorLine:clickLine col:clickCol
	    ]
	] ifFalse:[
	    lastString := nil. "new selection invalidates remembered string"
	].
	self showCursor
    ].
    super buttonRelease:button x:x y:y
! !