EditTextView.st
changeset 77 565b052f5277
parent 70 14443a9ea4ec
child 81 0c97b2905d5b
--- a/EditTextView.st	Mon Feb 06 01:52:01 1995 +0100
+++ b/EditTextView.st	Mon Feb 06 01:53:30 1995 +0100
@@ -32,7 +32,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
 	    All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.18 1994-11-28 21:04:55 claus Exp $
+$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.19 1995-02-06 00:52:03 claus Exp $
 '!
 
 !EditTextView class methodsFor:'documentation'!
@@ -53,7 +53,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.18 1994-11-28 21:04:55 claus Exp $
+$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.19 1995-02-06 00:52:03 claus Exp $
 "
 !
 
@@ -89,7 +89,6 @@
 
     used globals:
 
-    CopyBuffer              <Text>          text of last copy or cut
     DeleteHistory           <Text>          last 1000 lines of deleted text
 "
 ! !
@@ -121,10 +120,7 @@
     cursorCol := 1.
     modified := false.
     showMatchingParenthesis := false.
-    "
-     this will change - focusIn/Out seems to not work always
-    "
-    hasKeyboardFocus := true.
+    hasKeyboardFocus := false. "/ true.
 !
 
 initStyle
@@ -450,20 +446,23 @@
     |visLine w 
      dstY "{ Class: SmallInteger }" |
 
+    visLine := self listLineToVisibleLine:lineNr.
+    (shown not or:[visLine isNil]) ifTrue:[
+	self withoutRedrawInsertLine:aString before:lineNr.
+	^ self
+    ].
+
+    w := self widthForScrollBetween:lineNr
+				and:(firstLineShown + nLinesShown).
+    dstY := topMargin + ((visLine ) * fontHeight).
+    self catchExpose.
     self withoutRedrawInsertLine:aString before:lineNr.
-    visLine := self listLineToVisibleLine:lineNr.
-    visLine notNil ifTrue:[
-	w := self widthForScrollBetween:lineNr
-				    and:(firstLineShown + nLinesShown).
-	dstY := topMargin + ((visLine ) * fontHeight).
-	self catchExpose.
-	self copyFrom:self x:textStartLeft y:(dstY - fontHeight)
-			 toX:textStartLeft y:dstY
-		       width:w
-		      height:((nLinesShown - visLine "- 1") * fontHeight).
-	self redrawVisibleLine:visLine.
-	self waitForExpose
-    ]
+    self copyFrom:self x:textStartLeft y:(dstY - fontHeight)
+		     toX:textStartLeft y:dstY
+		   width:w
+		  height:((nLinesShown - visLine "- 1") * fontHeight).
+    self redrawVisibleLine:visLine.
+    self waitForExpose
 !
 
 insertLines:someText from:start to:end before:lineNr
@@ -473,31 +472,42 @@
      srcY "{ Class: SmallInteger }"
      dstY "{ Class: SmallInteger }" |
 
-    readOnly ifTrue: [
-	exceptionBlock value:errorMessage.
+    readOnly ifTrue:[
+	^ self
+    ].
+    visLine := self listLineToVisibleLine:lineNr.
+    (shown not or:[visLine isNil]) ifTrue:[
+	self withoutRedrawInsertLines:someText
+				 from:start to:end
+			       before:lineNr.
 	^ self
     ].
-    self withoutRedrawInsertLines:someText
-			     from:start to:end
-			   before:lineNr.
-    visLine := self listLineToVisibleLine:lineNr.
-    visLine notNil ifTrue:[
-	nLines := end - start + 1.
-	((visLine + nLines) >= nLinesShown) ifTrue:[
-	    self redrawFromVisibleLine:visLine to:nLinesShown
-	] ifFalse:[
-	    w := self widthForScrollBetween:(lineNr + nLines)
-					and:(firstLineShown + nLines + nLinesShown).
-	    srcY := topMargin + ((visLine - 1) * fontHeight).
-	    dstY := srcY + (nLines * fontHeight).
-	    self catchExpose.
-	    self copyFrom:self x:textStartLeft y:srcY
-			     toX:textStartLeft y:dstY
-			   width:w
-			  height:(height - dstY).
-	    self redrawFromVisibleLine:visLine to:(visLine + nLines - 1).
-	    self waitForExpose
-	]
+
+    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
     ]
 !
 
@@ -548,10 +558,12 @@
     list at:lineNr put:newLine.
     modified := true.
     contentsWasSaved := false.
-    drawCharacterOnly ifTrue:[
-	self redrawLine:lineNr col:colNr
-    ] ifFalse:[
-	self redrawLine:lineNr from:colNr
+    shown ifTrue:[
+	drawCharacterOnly ifTrue:[
+	    self redrawLine:lineNr col:colNr
+	] ifFalse:[
+	    self redrawLine:lineNr from:colNr
+	]
     ]
 !
 
@@ -655,7 +667,7 @@
     "insert aString (which has no crs) at lineNr/colNr"
 
     self withoutRedrawInsertStringWithoutCRs:aString atLine:lineNr col:colNr.
-    self redrawLine:lineNr from:colNr
+    shown ifTrue:[self redrawLine:lineNr from:colNr]
 !
 
 insertStringWithoutCRsAtCursor:aString
@@ -831,13 +843,13 @@
 insertTabAtCursor
     "insert spaces to next tab"
 
-    |nextTab|
-
     self withCursorOffDo:[
+	|nextTab|
+
 	nextTab := self nextTabAfter:cursorCol.
 	self insertStringAtCursor:(String new:(nextTab - cursorCol)).
+	self makeCursorVisible.
     ].
-    self makeCursorVisible.
 !
 
 deleteFromLine:startLine col:startCol toLine:endLine col:endCol
@@ -957,6 +969,7 @@
     w := self widthForScrollBetween:lineNr
 				and:(firstLineShown + nLinesShown).
     (self deleteLineWithoutRedraw:lineNr) ifFalse:[^ self].
+    shown ifFalse:[^ self].
     visLine := self listLineToVisibleLine:lineNr.
     visLine notNil ifTrue:[
 	srcY :=  margin + topMargin + (visLine * fontHeight).
@@ -1193,25 +1206,24 @@
 deleteSelection
     "delete the selection"
 
-    |startLine startCol endLine endCol|
-
     readOnly ifTrue: [
 	exceptionBlock value:errorMessage.
 	^ self
     ].
     selectionStartLine notNil ifTrue:[
-	startLine := selectionStartLine.
-	startCol := selectionStartCol.
-	endLine := selectionEndLine.
-	endCol := selectionEndCol.
 	self withCursorOffDo:[
+	    |startLine startCol endLine endCol|
+
+	    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 makeLineVisible:cursorLine
 	    self makeCursorVisible
 	]
     ]
@@ -1382,7 +1394,8 @@
 !
 
 drawCursor:cursorType with:fgColor and:bgColor
-    "draw the normal cursor."
+    "draw a cursor; the argument cursorType specifies what type
+     of cursor should be drawn."
 
     |x y w char|
 
@@ -1392,6 +1405,7 @@
 	"
 	^ super redrawVisibleLine:cursorVisibleLine col:cursorCol.
     ].
+
     cursorType == #block ifTrue:[
 	super drawVisibleLine:cursorVisibleLine 
 			  col:cursorCol 
@@ -1399,11 +1413,12 @@
 			  and:bgColor.
 	^ self
     ].
+    x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
+    y := self yOfVisibleLine:cursorVisibleLine.
+
     cursorType == #frame ifTrue:[
 	super redrawVisibleLine:cursorVisibleLine col:cursorCol.
 
-	x := self xOfCol:cursorCol inVisibleLine:cursorVisibleLine.
-	y := self yOfVisibleLine:cursorVisibleLine.
 	char := self characterUnderCursor asString.
 	self paint:bgColor.
 	self displayRectangleX:x y:y width:(font widthOf:char)
@@ -1411,8 +1426,6 @@
 	^ self
     ].
     cursorType == #ibeam ifTrue:[
-	x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
-	y := self yOfVisibleLine:cursorVisibleLine.
 
 	self paint:bgColor.
 	self displayLineFromX:x-1 y:y toX:x-1 y:(y + fontHeight - 1). 
@@ -1420,8 +1433,7 @@
 	^ self
     ].
     cursorType == #caret ifTrue:[
-	x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
-	y := (self yOfVisibleLine:cursorVisibleLine) + fontHeight - 3.
+	y := y + fontHeight - 3.
 	w := fontWidth // 2.
 	self paint:bgColor.
 	self lineWidth:2.
@@ -1429,8 +1441,7 @@
 	self displayLineFromX:x y:y toX:x+w y:y+w. 
     ].
     cursorType == #solidCaret ifTrue:[
-	x := (self xOfCol:cursorCol inVisibleLine:cursorVisibleLine) - leftOffset.
-	y := (self yOfVisibleLine:cursorVisibleLine) + fontHeight - 3.
+	y := y + fontHeight - 3.
 	w := fontWidth // 2.
 	self paint:bgColor.
 	self fillPolygon:(Array with:(x-w) @ (y+w)
@@ -1439,7 +1450,6 @@
     ].
 !
 
-
 drawFocusCursor
     "draw the cursor when the focus is in the view."
 
@@ -1468,7 +1478,7 @@
     cursorVisibleLine notNil ifTrue:[
 	((cursorType == #caret) or:[cursorType == #solidCaret]) ifTrue:[
 	    "caret-cursor touches 4 characters"
-	    cursorCol > 1 ifTrue:[
+	    ((cursorCol > 1) and:[fontIsFixedWidth]) ifTrue:[
 		super redrawVisibleLine:cursorVisibleLine from:cursorCol-1 to:cursorCol.
 		super redrawVisibleLine:cursorVisibleLine+1 from:cursorCol-1 to:cursorCol.
 	    ] ifFalse:[
@@ -1541,9 +1551,9 @@
 cursorToBottom
     "move cursor to last line of text"
 
-    |newTop|
-
     self withCursorOffDo:[
+	|newTop|
+
 	newTop := list size - nFullLinesShown.
 	(newTop < 1) ifTrue:[
 	    newTop := 1
@@ -1622,13 +1632,17 @@
 cursorToEndOfLine
     "move cursor to end of current line"
 
-    |line|
-
     self withCursorOffDo:[
-	line := list at:cursorLine.
-	cursorCol := line size + 1
+	|line|
+
+	list isNil ifTrue:[
+	    cursorCol := 1
+	] ifFalse:[
+	    line := list at:cursorLine.
+	    cursorCol := line size + 1
+	].
+	self makeCursorVisible.
     ].
-    self makeCursorVisible.
 !
 
 cursorTab
@@ -1831,19 +1845,29 @@
 paste
     "paste copybuffer; if there is a selection, replace it.
      otherwise paste at cursor position. Replace is not done
-     for selections originating by a paste, to allow multiple
+     for originating by a paste, to allow multiple
      paste."
 
-    (self hasSelection notNil and:[typeOfSelection ~~ #paste]) ifTrue:[
+    |sel|
+
+    ((self hasSelection == true) and:[typeOfSelection ~~ #paste]) ifTrue:[
 	^ self replace
     ].
-    self paste:(Smalltalk at:#CopyBuffer).
+    sel := self getTextSelection.
+    sel notNil ifTrue:[
+	self paste:sel.
+    ]
 !
 
 replace
     "replace selection by copybuffer"
 
-    self replace:(Smalltalk at:#CopyBuffer)
+    |sel|
+
+    sel := self getTextSelection.
+    sel notNil ifTrue:[
+	self replace:sel
+    ]
 !
 
 cut
@@ -1861,7 +1885,7 @@
 	"
 	 remember in CopyBuffer
 	"
-	Smalltalk at:#CopyBuffer put:lastString.
+	self setTextSelection:lastString.
 
 	"
 	 append to DeleteHistory (if there is one)
@@ -1890,12 +1914,21 @@
 paste:someText
     "paste someText at cursor"
 
-    |startLine startCol|
+    |s startLine startCol|
 
     someText notNil ifTrue:[
+	s := someText.
+	s isString ifTrue:[
+	    s := s asText
+	] ifFalse:[
+	    (s isMemberOf:Text) ifFalse:[
+		self warn:'selection not convertable to Text'.
+		^ self
+	    ]
+	].
 	startLine := cursorLine.
 	startCol := cursorCol.
-	self insertLines:someText asText withCr:false.
+	self insertLines:s asText withCr:false.
 	self selectFromLine:startLine col:startCol
 		     toLine:cursorLine col:(cursorCol - 1).
 	typeOfSelection := #paste.
@@ -2159,8 +2192,14 @@
 searchFwd:pattern ifAbsent:aBlock
     "do a forward search"
 
+    self searchFwd:pattern startingAtLine:cursorLine col:cursorCol ifAbsent:aBlock
+!
+
+searchFwd:pattern startingAtLine:startLine col:startCol ifAbsent:aBlock
+    "do a forward search"
+
     cursorLine isNil ifTrue:[^ self].
-    self searchForwardFor:pattern startingAtLine:cursorLine col:cursorCol
+    self searchForwardFor:pattern startingAtLine:startLine col:startCol
     ifFound:[:line :col |
 	self cursorLine:line col:col.
 	self selectFromLine:line col:col
@@ -2386,65 +2425,83 @@
 !
 
 pointerEnter:state x:x y:y
-    hasKeyboardFocus := true.
-    self drawCursor.
+    (windowGroup isNil or:[windowGroup focusView isNil]) ifTrue:[
+	hasKeyboardFocus := true.
+	cursorShown ifTrue: [self drawCursor].
+    ].
     super pointerEnter:state x:x y:y
 !
 
 pointerLeave:state
-    hasKeyboardFocus := false.
-    self drawCursor.
+    (windowGroup isNil or:[windowGroup focusView isNil]) ifTrue:[
+	hasKeyboardFocus := false.
+	cursorShown ifTrue: [self drawCursor].
+    ].
     super pointerLeave:state
 !
 
+showFocus
+    hasKeyboardFocus := true.
+    cursorShown ifTrue: [self drawCursor].
+    super showFocus
+!
+
+showNoFocus
+    hasKeyboardFocus := false.
+    cursorShown ifTrue: [self drawCursor].
+    super showNoFocus
+
+!
 
 keyPress:key x:x y:y
     "handle keyboard input"
 
     (key isMemberOf:Character) ifTrue:[
-	typeOfSelection == #paste ifTrue:[
-	    "pasted selection will NOT be replaced by keystroke"
-	    self unselect
-	].
-
-	"replace selection by what is typed in -
-	 if word was selected with a space, keep it"
-
-	(selectStyle == #wordLeft) ifTrue:[
-	    self replaceSelectionBy:(' ' copyWith:key)
-	] ifFalse:[
-	    (selectStyle == #wordRight) ifTrue:[
-		self replaceSelectionBy:(key asString , ' ').
-		self cursorLeft
+	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:[
-		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:[
+		(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:[
-	    self searchForMatchingParenthesisFromLine:cursorLine col:(cursorCol - 1)
-			       ifFound:[:line :col |
-					    |savLine savCol|
-
-					    savLine := cursorLine.
-					    savCol := cursorCol.
-					    self cursorLine:line col:col.
-					    device synchronizeOutput.
-					    OperatingSystem millisecondDelay:200.
-					    self cursorLine:savLine col:savCol
-				       ]
-			    ifNotFound:[self showNotFound]
-			       onError:[device beep]
+		(#( $( $) $[ $] ${ $} ) includes:key) ifTrue:[
+"
+		(#( $) $] $} ) includes:key) ifTrue:[
+		self searchForMatchingParenthesisFromLine:cursorLine col:(cursorCol - 1)
+				   ifFound:[:line :col |
+						|savLine savCol|
+
+						savLine := cursorLine.
+						savCol := cursorCol.
+						self cursorLine:line col:col.
+						device synchronizeOutput.
+						OperatingSystem millisecondDelay:200.
+						self cursorLine:savLine col:savCol
+					   ]
+				ifNotFound:[self showNotFound]
+				   onError:[device beep]
+		].
 	    ].
 	].
 	^ self
@@ -2577,7 +2634,7 @@
 "
 " new version deletes selection if any "
 	selectionStartLine notNil ifTrue:[
-	    Smalltalk at:#CopyBuffer put:(self selection).
+	    self setTextSelection:(self selection).
 	    self deleteSelection. ^ self
 	].
 	self makeCursorVisible.
@@ -2585,7 +2642,7 @@
     ].
     (key == #Delete)    ifTrue:[
 	selectionStartLine notNil ifTrue:[
-	    Smalltalk at:#CopyBuffer put:(self selection).
+	    self setTextSelection:(self selection).
 	    self deleteSelection. ^ self
 	].
 	self makeCursorVisible.