ETxtView.st
author Claus Gittinger <cg@exept.de>
Thu, 25 Apr 1996 19:34:16 +0200
changeset 586 032b3245e53a
parent 567 a71e9e59537e
child 594 b9c5a5e5f905
permissions -rw-r--r--
documentation

"
 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 cursorType undoAction typeOfSelection
		lastString lastReplacement lastAction replacing
		showMatchingParenthesis hasKeyboardFocus acceptAction lockUpdates
		tabMeansNextField autoIndent insertMode'
	classVariableNames:'DefaultCursorForegroundColor DefaultCursorBackgroundColor
		DefaultCursorType'
	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

        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)

        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.

        lockUpdates             <Boolean>       internal, private

        prevCursorState         <Boolean>       temporary, private


    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
        textCursorType            <Symbol>      cursor type; default:  #block

    [author:]
        Claus Gittinger

    [see also:]
        CodeView Workspace TextView
"
!

examples
"
  non MVC operation:

    basic setup:

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

    with vertical scrollbar:

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

    with horizontal & vertical scrollbars:

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


    set the action for accept:

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


  MVC operation:

	(the examples model here is a plug simulating a real model;
	 real world applications would not use a plug ..)

	|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 model:model;
		 changeMessage:#accepted:;
		 listMessage:#getList;
		 aspect:#list.
	top open.

    two textViews on the same model:

	|top1 textView1 top2 textView2 model currentContents|

	model := Plug new.
	model respondTo:#accepted:
		   with:[:newContents |
				Transcript showCr:'accepted'.
				currentContents := newContents.
				self changed:#contents
			].
	model respondTo:#getList
		   with:[self halt. 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 model:model;
		  aspect:#contents;
		  changeMessage:#accepted:;
		  listMessage:#getList.
	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 model:model;
		  aspect:#contents;
		  changeMessage:#accepted:;
		  listMessage:#getList.
	top2 open.

"
! !

!EditTextView class methodsFor:'defaults'!

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

    <resource: #style (#textCursorForegroundColor #textCursorBackgroundColor
                       #textCursorType )>

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

    "Modified: 1.3.1996 / 13:45:41 / cg"
! !

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

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

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

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

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

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"

    readOnly ifFalse:[
	readOnly := true.
	middleButtonMenu notNil ifTrue:[
	    middleButtonMenu disableAll:#(cut paste replace indent)
	]
    ]
!

fromFile:aFileName
    "take contents from a named file"

    self contents:(aFileName asFilename readStream contents)
!

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 the modified flag"

    modifiedChannel value:aBoolean
!

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

    ^ modifiedChannel
!

readOnly
    "make the text readonly"

    readOnly := true
! !

!EditTextView methodsFor:'accessing-look'!

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

    |wasOn|

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

!EditTextView methodsFor:'change & update '!

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

    lockUpdates := true.
     "/
     "/ 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
     ].

     "/
     "/ ST-80 way of doing it
     "/
     self sendChangeMessageWith:self argForChangeMessage.

    lockUpdates := false.
!

argForChangeMessage
    ^ self contents
!

getListFromModel
    "get my contents from the model.
     Redefined to ignore updates resulting from my own change."

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

!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 := newCol.
    self makeCursorVisibleAndShowCursor:wasOn.
!

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

    self cursorDown:1
!

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 := cursorLine + n.
	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	wasOn ifTrue:[self showCursor].
    ] ifFalse:[
	cursorLine isNil ifTrue:[
	    cursorLine := firstLineShown
	].
	cursorLine := cursorLine + n.
	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	self makeCursorVisible.
    ].
    "/ cursor no longer visible ?
    cursorVisibleLine isNil ifTrue:[
	cursorLine > list size ifTrue:[
	    device beep. device sync.
	]
    ]
!

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

    |wasOn|

    wasOn := self hideCursor.
    cursorCol := 1.
    self scrollToTop.
    cursorLine := cursorVisibleLine := 1.
    self makeCursorVisibleAndShowCursor:wasOn.
!

cursorLeft
    "move cursor to left"

    (cursorCol ~~ 1) ifTrue: [
	self cursorCol:(cursorCol - 1)
    ].
!

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

    |wasOn|

    wasOn := self hideCursor.
    cursorLine := line.
    cursorVisibleLine := self listLineToVisibleLine:line.
    cursorCol := col.
    (cursorCol < 1) ifTrue:[
	cursorCol := 1
    ].
    self makeCursorVisibleAndShowCursor:wasOn.
!

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.
    cursorCol := 1.
    cursorLine := cursorLine + 1.
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
    self makeCursorVisibleAndShowCursor:wasOn.
!

cursorRight
    "move cursor to right"

    self cursorCol:(cursorCol + 1)
!

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.
    cursorCol := 1.
    cursorLine := list size.
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.

    self makeCursorVisibleAndShowCursor:wasOn.
!

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.
    cursorCol := 1.
    cursorLine := l.
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.

    self makeCursorVisibleAndShowCursor:wasOn.
!

cursorToEndOfLine
    "move cursor to end of current line"

    |line newCol|

    list isNil ifTrue:[
	newCol := 1
    ] ifFalse:[
	line := list at:cursorLine.
	newCol := line size + 1
    ].
    self cursorCol:newCol
!

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 := nl.
	cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	wasOn ifTrue:[self showCursor].
"/
"/ to make cursor visible (even if below visible end):
"/
"/      self makeCursorVisibleAndShowCursor:wasOn.
    ]
!

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

    |wasOn|

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

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 and #solidCaret"

    |x y w char y2 x1 x2 oldPaint|

    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
    ].
    x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
    y := self yOfVisibleLine:cursorVisibleLine.

    oldPaint := 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
	] ifFalse:[
	    w := fontWidth // 2.
	    y := y + fontHeight - 3.
	    y2 := y + w.
	    x1 := x - w.
	    x2 := x + w.
	    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 paint:oldPaint.
!

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

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

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
!

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 visible; 
     return true if cursor was visible before."

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

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"

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

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) and:[fontIsFixedWidth]) 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; 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
    ]
!

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 single character at colNr in line lineNr"

    |line lineSize newLine drawCharacterOnly wasLargest|

    self checkModificationsAllowed ifFalse:[ ^ self].

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

    wasLargest := (self widthOfLineString:line) == widthOfWidestLine.

    drawCharacterOnly := false.
    (colNr == lineSize) ifTrue:[
        newLine := line copyTo:(lineSize - 1).
        fontIsFixedWidth ifTrue:[
            drawCharacterOnly := true
        ]
    ] ifFalse:[
        newLine := line species 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.
    wasLargest ifTrue:[
        widthOfWidestLine := nil. "/ i.e. unknown
    ].
    self textChanged.
    drawCharacterOnly ifTrue:[
        self redrawLine:lineNr col:colNr
    ] ifFalse:[
        self redrawLine:lineNr from:colNr
    ]

    "Modified: 23.2.1996 / 17:42:23 / cg"
!

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

    |wasOn oldSize lineNrAboveCursor|

    wasOn := self hideCursor.

    (cursorCol == 1) ifFalse:[
	"
	 somewhere in the middle of a line
	"
	self cursorLeft.
	self deleteCharAtLine:cursorLine col:cursorCol.
    ] ifTrue:[
	"
	 at begin of line - merge with previous line;
	 except for the very first line.
	"
	(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.
	    cursorLine := lineNrAboveCursor.
	    cursorCol := oldSize + 1.
	    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
	    self makeCursorVisible
	]
    ].
    wasOn ifTrue:[self showCursor].
!

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

    |line newLine|

    self checkModificationsAllowed ifFalse:[ ^ self].

    line := self listAt: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.
    widthOfWidestLine := nil. "/ i.e. unknown
    self textChanged.
    self redrawLine:lineNr
!

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

    |line lineSize newLine|

    self checkModificationsAllowed ifFalse:[ ^ self].

    line := self listAt: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.
    widthOfWidestLine := nil. "/ i.e. unknown
    self textChanged.
    self redrawLine:lineNr
!

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

    |line lineSize newLine|

    self checkModificationsAllowed ifFalse:[ ^ self].

    line := self listAt: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.
    widthOfWidestLine := nil. "/ i.e. unknown
    self textChanged.
    self redrawLine:lineNr
!

deleteCursorLine
    "delete the line where the cursor sits"

    self deleteLine:cursorLine
!

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

    |line lineSize|

    self checkModificationsAllowed ifFalse:[ ^ 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 , (line species new:(startCol - 1 - lineSize))
            ].
            list at:startLine put:line.
            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

    "Modified: 23.2.1996 / 19:08:21 / cg"
!

deleteFromLine:startLineNr toLine:endLineNr
    "delete some lines"

    |wasOn nLines|

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

    wasOn := self hideCursor.
    list removeFromIndex:startLineNr toIndex:(endLineNr min:list size).
    widthOfWidestLine := nil. "/ i.e. unknown
    self textChanged.
    self redrawFromLine:startLineNr.

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

deleteLine:lineNr
    "delete line"

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

    w := self widthForScrollBetween:lineNr and:(firstLineShown + nLinesShown).
    (self deleteLineWithoutRedraw:lineNr) ifFalse:[^ self].
    shown ifFalse:[^ self].

    wasOn := self hideCursor.

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

    wasOn ifTrue:[self showCursor].
!

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.
    widthOfWidestLine := nil. "/ i.e. unknown
    self textChanged.
    ^ true
!

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.
    widthOfWidestLine := nil. "/ i.e. unknown
    self textChanged.
    ^ true
!

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

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

    |line lineSize newLine drawCharacterOnly|

    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.
    (aCharacter == Character space) ifTrue:[
        (colNr > lineSize)  ifTrue:[
            ^ self
        ]
    ].
    (lineSize == 0) ifTrue:[
        newLine := aCharacter asString species new:colNr.
        drawCharacterOnly := true
    ] ifFalse: [
        (colNr > lineSize) ifTrue: [
            newLine := line species new:colNr.
            newLine replaceFrom:1 to:lineSize
                           with:line startingAt:1.
            drawCharacterOnly := true
        ] ifFalse: [
            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.
    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
        ]
    ]

    "Modified: 23.2.1996 / 19:09:36 / cg"
!

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

    |wasOn|

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

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

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

    wasOn := self hideCursor.

    visLine := self listLineToVisibleLine:lineNr.
    (shown not or:[visLine isNil]) ifTrue:[
	self withoutRedrawInsertLine:aString before:lineNr.
    ] ifFalse:[
	w := self widthForScrollBetween:lineNr
				    and:(firstLineShown + nLinesShown).
	dstY := topMargin + ((visLine ) * fontHeight).
	self catchExpose.
	self withoutRedrawInsertLine:aString before:lineNr.
	self copyFrom:self x:textStartLeft y:(dstY - fontHeight)
			 toX:textStartLeft y:dstY
		       width:w
		      height:((nLinesShown - visLine "- 1") * fontHeight).
	self redrawVisibleLine:visLine.
	self waitForExpose.
    ].
    widthOfWidestLine notNil ifTrue:[
	widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:aString).
    ].
    self textChanged.
    wasOn ifTrue:[self showCursor].
!

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: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:[
	^ self
    ].
    visLine := self listLineToVisibleLine:lineNr.
    (shown not or:[visLine isNil]) ifTrue:[
	self withoutRedrawInsertLines:someText
				 from:start to:end
			       before:lineNr.
    ] ifFalse:[
	nLines := end - start + 1.
	((visLine + nLines) >= nLinesShown) ifTrue:[
	    self withoutRedrawInsertLines:someText
				     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).
	    "
	     stupid: must catchExpose before inserting new
	     stuff - since catchExpose may perform redraws
	    "
	    self catchExpose.
	    self withoutRedrawInsertLines:someText
				     from:start to:end
				   before:lineNr.
	    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
	].
    ].
    widthOfWidestLine notNil ifTrue:[
	someText do:[:line |
	    widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
	]
    ].
    self textChanged.
!

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

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 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 asStringCollection 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
"/    ]
!

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

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

    |wasOn|

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

insertTabAtCursor
    "insert spaces to next tab"

    |wasOn nextTab|

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

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

    |leftPart rightPart bothParts nextLineNr|

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

    "Modified: 7.9.1995 / 15:56:17 / claus"
!

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

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

    self checkForExistingLine:lineNr.
    line := list at:lineNr.
    lineSize := line size.
    (aCharacter == Character space) ifTrue:[
        (colNr > lineSize)  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.
    list at:lineNr put:newLine.
    widthOfWidestLine notNil ifTrue:[
        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:line).
    ].
    self textChanged.
    shown ifTrue:[
        self redrawLine:lineNr col:colNr
    ]

    "Created: 6.3.1996 / 12:29:20 / cg"
!

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

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:[
            (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: 6.3.1996 / 12:26:31 / 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      
     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.
	    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
	    ].
	    widthOfWidestLine := nil. "/ unknown
	    self textChanged.
	]
    ]
!

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 occurrencesOf:(Character tab)) == 0 ifFalse:[
		    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.
!

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 occurrencesOf:(Character tab)) == 0 ifFalse:[
			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.
!

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

    |strLen line lineSize newLine stringType|

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

    strLen := aString size.
    self checkForExistingLine:lineNr.

    stringType := aString species.

    line := list at:lineNr.
    line notNil ifTrue:[
        lineSize := line size.
        line bitsPerCharacter > aString bitsPerCharacter ifTrue:[
            stringType := line species
        ]
    ] ifFalse:[
        lineSize := 0
    ].
    ((colNr == 1) and:[lineSize == 0]) ifTrue: [
        newLine := aString
    ] ifFalse:[
        (lineSize == 0) ifTrue: [
            newLine := stringType new:(colNr + strLen - 1)
        ] ifFalse: [
            (colNr > lineSize) ifTrue: [
                newLine := stringType new:(colNr + strLen - 1).
                newLine replaceFrom:1 to:lineSize
                               with:line startingAt:1
            ] ifFalse: [
                newLine := stringType 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.
    widthOfWidestLine notNil ifTrue:[
        widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:newLine).
    ].
    self textChanged.

    "Modified: 26.2.1996 / 18:07:34 / 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
!

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
!

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

    hasKeyboardFocus := aBoolean.
    cursorShown ifTrue: [self drawCursor].
!

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

    <resource: #keyboard (#Paste #Insert #Cut #Again #Replace 
                          #SelectWord #SearchMatchingParent
                          #SelectMatchingParents #SelectToEnd
                          #SelectFromBeginning
                          #BeginOfLine #EndOfLine #NextWord
                          #GotoLine #Delete #BeginOfText #EndOfText
                          #SelectLine #ExpandSelectionByLine #DeleteLine
                          #InsertLine)>

    |sensor n fKeyMacros shifted i|

    sensor := self sensor.
    shifted := sensor shiftDown.

    (key isMemberOf:Character) ifTrue:[
        readOnly 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.
                                                    Processor activeProcess 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>>:x:y
    "
    (('[fF][0-9]' match:key)
    or:['[fF][0-9][0-9]' match:key]) ifTrue:[
        shifted ifFalse:[
            fKeyMacros := Smalltalk at:#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 cursorToBeginOfLine. ^self].
    (key == #EndOfLine) ifTrue:[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:[
            "/
            "/ treat the whole selection as cursor
            "/
            cursorLine := selectionEndLine.
            cursorVisibleLine := self listLineToVisibleLine:cursorLine.
            cursorCol := selectionEndCol.
            cursorCol == 0 ifTrue:[
                cursorCol := 1.
            ].
            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:[
            "/
            "/ 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:[
                self expandSelectionDown.
                ^ self
            ].
            self unselect. 
        ].

        sensor isNil ifTrue:[
            n := 1
        ] ifFalse:[
            n := 1 + (sensor compressKeyPressEventsWithKey:#CursorDown).
        ].
        self cursorDown:n. 
        ^ 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:[
            "/
            "/ 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:[
                    ^ 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. 
            ^ self
        ].
    ].

    (key == #Return)    ifTrue:[
        shifted ifTrue:[
            self unselect. self cursorReturn. ^self
        ].
        readOnly ifTrue:[
            self unselect; makeCursorVisible.
            self cursorReturn
        ] ifFalse:[
            insertMode ifFalse:[
                self cursorReturn.
                autoIndent == true ifTrue:[
                    i := self leftIndentOfLine:cursorLine.
                    i == 0 ifTrue:[
                        i := self leftIndentForLine:cursorLine.
                    ].
                    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 ....
        "
        "/ self unselect. self cursorTab. ^self
        self unselect. self insertTabAtCursor. 
        ^self
    ].

    (key == #BackSpace) ifTrue:[

        "/ old version just unselected here 
        "/ self unselect. 

        "/ new version deletes selection if any 

        selectionStartLine notNil ifTrue:[
            ^ self copyAndDeleteSelection.
        ].
        self makeCursorVisible.
        self deleteCharBeforeCursor. ^self
    ].

    (key == #Delete)    ifTrue:[
        selectionStartLine notNil ifTrue:[
            ^ 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: 22.4.1996 / 10:06:29 / cg"
!

mapped
    "view was made visible"

    super mapped.
    self makeCursorVisible.
    cursorVisibleLine := self listLineToVisibleLine:cursorLine.
!

pointerEnter:state x:x y:y
    (windowGroup isNil or:[windowGroup focusView isNil]) ifTrue:[
	hasKeyboardFocus := true.
	cursorShown ifTrue: [self drawCursor].
    ].
    super pointerEnter:state x:x y:y
!

pointerLeave:state
    (windowGroup isNil or:[windowGroup focusView isNil]) ifTrue:[
	hasKeyboardFocus := false.
	cursorShown ifTrue: [self drawCursor].
    ].
    super pointerLeave:state
!

showFocus:explicit
    hasKeyboardFocus := true.
    cursorShown ifTrue: [self drawCursor].
    super showFocus:explicit
!

showNoFocus:explicit
    hasKeyboardFocus := false.
    cursorShown ifTrue: [self drawCursor].
    super showNoFocus:explicit
!

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

    |cv|

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

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

    |leftStart lnr|

    leftStart := 0.
    lnr := lineNr.
    [(leftStart == 0) and:[lnr ~~ 1]] whileTrue:[
        lnr := lnr - 1.
        leftStart := self leftIndentOfLine:lnr
    ].
    ^ leftStart

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

!EditTextView methodsFor:'initialization'!

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

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 := false asValue.
    showMatchingParenthesis := false.
    hasKeyboardFocus := false. "/ true.
    tabMeansNextField := false.
    autoIndent := false.
    insertMode := true.

    "Modified: 6.3.1996 / 12:23:50 / cg"
!

realize
    "make the view visible"

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

!EditTextView methodsFor:'menu actions'!

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

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

    |labels selectors m sub shortKeys|

    self sensor ctrlDown ifTrue:[
        labels := #(
                        'again (for all)'
                   ).

        selectors := #(
                        multipleAgain
                       ).
    ] ifFalse:[
        labels := #(
"/                      'undo'
                        'again'
                        '-'
                        'copy'
                        'cut'
                        'paste'
                        '-'
                        'accept'
                        '='
                        'others'
                   ).

        selectors := #(
"/                      undo
                        again
                        nil
                        copySelection
                        cut
                        pasteOrReplace
                        nil
                        accept
                        nil
                        others
                       ).

        shortKeys := #(
"/                        nil
                        #Again 
                        nil
                        #Copy
                        #Cut
                        #Paste
                        nil
                        #Accept 
                        nil
                        nil
                      ).
    ].

    m := PopUpMenu
            labels:(resources array:labels)
            selectors:selectors
            accelerators:shortKeys.

    labels := #(
                    'search ...'
                    'goto ...'
                    '-'
                    'font ...'
                    '-'
                    'indent'
                    'autoIndent \c'
                    'insertMode \c'
                    '-'
                    'save as ...'
                    'print'
                ).

   selectors := #(
                     search
                     gotoLine
                     nil
                     changeFont
                     nil
                     indent
                     autoIndent:
                     insertMode:
                     nil
                     save
                     print
                    ).

    shortKeys := #(
                      #Find
                      #GotoLine
                      nil
                      nil         "/ changeFont
                      nil
                      nil         "/ indent
                      nil
                      nil
                      nil
                      #SaveAs
                      #Print).

    sub := PopUpMenu
                labels:(resources array:labels)
                selectors:selectors
                accelerators:shortKeys
                receiver:model.

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

    readOnly ifTrue:[
        m disable:#paste
    ].
    self hasSelection not ifTrue:[
        m disable:#copySelection.
    ].
    (self hasSelection not or:[readOnly]) ifTrue:[
        m disable:#cut.
        sub disable:#indent.
    ].
    ^ m.

    "Modified: 7.3.1996 / 13:13:03 / cg"
!

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

    |sel|

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

paste:someText
    "paste someText at cursor"

    |s startLine startCol|

    someText notNil ifTrue:[
        s := someText.
        s isString ifTrue:[
            s := s asStringCollection
        ] ifFalse:[
            (s isKindOf:StringCollection) ifFalse:[
                self warn:'selection not convertable to Text'.
                ^ self
            ]
        ].
        startLine := cursorLine.
        startCol := cursorCol.
        self insertLines:(s withTabsExpanded) withCr:false.
        self selectFromLine:startLine col:startCol
                     toLine:cursorLine col:(cursorCol - 1).
        typeOfSelection := #paste.
        undoAction := [self cut].
    ]

    "Modified: 14.2.1996 / 11:14:14 / stefan"
!

pasteOrReplace
    "paste 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|

    sel := self getTextSelection.
    self pasteOrReplace:sel.
!

pasteOrReplace:someText
    "paste 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."

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

replace
    "replace selection by copybuffer"

    |sel|

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

replace:someText
    "replace selection by someText"

    |selected selectedString| 

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

showDeleted
    "open a readonly editor on all deleted text"

    |v|

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

!EditTextView methodsFor:'private'!

checkModificationsAllowed
    readOnly ifTrue: [
	exceptionBlock isNil ifTrue:[
	    ^ false
	].

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

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

    super contentsChanged.
    modifiedChannel value:true.
    contentsWasSaved := false
! !

!EditTextView methodsFor:'queries'!

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

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

    ^ readOnly 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|

    w := super widthOfContents.
    ^ w + (font widthOf:' ')
! !

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

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

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

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: 20.4.1996 / 12:49:51 / 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:[device beep]
!

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

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
!

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

    cursorLine isNil ifTrue:[^ self].
    self searchForwardFor: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: 20.4.1996 / 12:49:41 / 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:[
        searchPattern := 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:[
        (searchPattern isNil
        or:[typeOfSelection ~~ #paste]) ifTrue:[
            self cursorLine:selectionStartLine col:selectionStartCol.
            searchPattern := sel asString withoutSeparators
        ]
    ]

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

!EditTextView methodsFor:'selections'!

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

selectCursorLine
    "select cursorline"

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

selectCursorLineFromBeginning
    "select cursorline up to cursor position"

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

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.
    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 "copyTo:(s size - 1)".
        s := s withoutSpaces.
        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:[
                        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: 18.3.1996 / 14:48:27 / 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
    ]
! !

!EditTextView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg/Attic/ETxtView.st,v 1.65 1996-04-25 17:34:16 cg Exp $'
! !