ETxtView.st
changeset 7 15a9291b9bd0
parent 5 7b4fb1b170e5
child 10 a288b33897a5
--- a/ETxtView.st	Sat Dec 11 02:41:07 1993 +0100
+++ b/ETxtView.st	Sat Dec 11 02:51:34 1993 +0100
@@ -17,7 +17,10 @@
                               exceptionBlock
                               errorMessage
                               cursorFgColor cursorBgColor
-                              undoAction redoAction'
+                              undoAction  
+                              typeOfSelection 
+                              lastString lastReplacement lastAction 
+                              replacing showMatchingParenthesis'
        classVariableNames:''
        poolDictionaries:''
        category:'Views-Text'
@@ -28,7 +31,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
             All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/Attic/ETxtView.st,v 1.3 1993-10-13 02:47:29 claus Exp $
+$Header: /cvs/stx/stx/libwidg/Attic/ETxtView.st,v 1.4 1993-12-11 01:43:01 claus Exp $
 
 written jun-89 by claus
 '!
@@ -53,6 +56,13 @@
     errorMessage            <String>        message text 
     cursorFgColor           <Color>         color used for cursor drawing
     cursorBgColor           <Color>         color used for cursor drawing
+    undoAction              <Block>         block which undoes last cut, paste or replace
+    typeOfSelection         <Symbol>        #paste, if selection created by paste, nil otherwise
+    lastCut                 <String>        last cut or replaced string
+    lastReplacement         <String>        last replacement
+    replacing               <Boolean>       true if entered characters replace last selection
+    showMatchingParenthesis <Boolean>       if true, shows matching parenthesis
+                                            when entering one
 "
 ! !
 
@@ -66,11 +76,12 @@
     readOnly := false.
     fixedSize := false.
     exceptionBlock := [:errorText | ].
-    cursorShown := true.
+    cursorShown := prevCursorState := true.
     cursorLine := 1.
     cursorVisibleLine := 1.
     cursorCol := 1.
-    modified := false
+    modified := false.
+    showMatchingParenthesis := false
 !
 
 initStyle
@@ -86,10 +97,12 @@
 initializeMiddleButtonMenu
     |labels|
  
-    labels := resources array:#("
+    labels := resources array:#(
+"
                                        'undo'
+"
+                                       'again'
                                        '-'
-                                      "
                                        'copy'
                                        'cut'
                                        'paste'
@@ -107,8 +120,12 @@
 
     self middleButtonMenu:(PopUpMenu 
                                 labels:labels
-                             selectors:#("undo
-                                         nil"
+                             selectors:#(
+"
+                                         undo
+"
+                                         again
+                                         nil
                                          copySelection
                                          cut
                                          paste
@@ -202,6 +219,12 @@
     "return true if text was modified"
 
     ^ modified
+!
+
+characterUnderCursor
+    "return the character under the cursor - space if behond line"
+
+    ^ self characterAtLine:cursorLine col:cursorCol
 ! !
 
 !EditTextView methodsFor:'private'!
@@ -595,9 +618,10 @@
     start := 1.
     end := aString size.
     [start <= end] whileTrue:[
-        stop := aString indexOf:(Character cr)
-                     startingAt:start
-                       ifAbsent:[end + 1].
+        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:[
@@ -628,9 +652,10 @@
 
     "insert the 1st line"
     (cursorCol ~~ 1) ifTrue:[
-        stop := aString indexOf:(Character cr)
-                     startingAt:start
-                       ifAbsent:[end + 1].
+        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).
@@ -639,9 +664,10 @@
     "insert the block of full lines"
 
     [start <= end] whileTrue:[
-        stop := aString indexOf:(Character cr)
-                     startingAt:start
-                       ifAbsent:[end + 1].
+        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:[
@@ -1089,10 +1115,22 @@
     "delete the selection (if any) and insert something, a character or string;
      leave cursor after insertion"
 
-    self deleteSelection.
+    |sel|
+
+    sel := self selection.
+    sel notNil ifTrue:[
+        lastString := sel.
+        self deleteSelection.
+        replacing := true.
+        lastReplacement := ''
+    ].
     (something isMemberOf:Character) ifTrue:[
+        lastReplacement notNil ifTrue:[
+            lastReplacement := lastReplacement copyWith:something.
+        ].
         self insertCharAtCursor:something
     ] ifFalse:[
+        lastReplacement := something.
         self insertStringAtCursor:something
     ]
 ! !
@@ -1114,19 +1152,21 @@
 !
 
 indentFromLine:start toLine:end
-    "indent a line-range"
+    "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 s delta line spaces|
+    |leftStart lnr delta d line spaces|
 
     "find a line to base indent on..."
-    leftStart := 0.
-    s := start.
-    [(leftStart == 0) and:[s ~~ 1]] whileTrue:[
-        s := s - 1.
-        leftStart := self leftIndentOfLine:s
+    leftStart := -1.
+    lnr := start.
+    [(leftStart == -1) and:[lnr ~~ 1]] whileTrue:[
+        lnr := lnr - 1.
+        leftStart := self leftIndentOfLine:lnr
     ].
 
-    (leftStart == 0) ifTrue:[^ self].
+    (leftStart == -1) ifTrue:[^ self].
 
     delta := leftStart - (self leftIndentOfLine:start).
     (delta == 0) ifTrue:[^ self].
@@ -1142,7 +1182,14 @@
                 (delta > 0) ifTrue:[
                     line := spaces , line
                 ] ifFalse:[
-                    line := line copyFrom:(delta negated + 1)
+                    "check if deletion is ok"
+                    d := delta negated + 1.
+
+                    line size > d ifTrue:[
+                        (line copyFrom:1 to:(d - 1)) withoutSeparators isEmpty ifTrue:[
+                            line := line copyFrom:d
+                        ]
+                    ]
                 ].
                 list at:lineNr put:line.
                 modified := true.
@@ -1264,6 +1311,9 @@
     "move cursor up; scroll if at start of visible text"
 
     (cursorLine == 1) ifFalse: [
+        cursorLine isNil ifTrue:[
+            cursorLine := firstLineShown + nFullLinesShown - 1.
+        ].
         self withCursorOffDo:[
             (cursorVisibleLine == 1) ifTrue:[self scrollUp].
             cursorLine := cursorLine - 1.
@@ -1283,6 +1333,9 @@
             cursorVisibleLine := self listLineToVisibleLine:cursorLine
         ]
     ] ifFalse:[
+        cursorLine isNil ifTrue:[
+            cursorLine := firstLineShown
+        ].
         cursorLine := cursorLine + 1.
         cursorVisibleLine := self listLineToVisibleLine:cursorLine
     ].
@@ -1410,12 +1463,70 @@
     self cursorLine:aLineNumber col:1
 ! !
 
-!EditTextView methodsFor:'undo'!
+!EditTextView methodsFor:'undo & again'!
 
 undo
     "currently not implemented"
 
-    ^ self
+    undoAction notNil ifTrue:[
+        undoAction value
+    ]
+!
+
+again
+    "repeat the last action (which was a cut or replace).
+     If current selection is not last string, search forward to
+     next occurence of it before repeating the last operation."
+
+    |s l c sel|
+
+    lastString notNil ifTrue:[
+        s := lastString asString.
+        "remove final cr"
+        s := s copyTo:(s size - 1).
+
+        sel := self selection.
+
+        "if we are already there (after a find), ommit search"
+
+        (sel notNil and:[sel asString withoutSeparators = s]) ifTrue:[
+            undoAction := [self insertLines:lastString atLine:cursorLine col:cursorCol].
+            l := selectionStartLine "cursorLine". 
+            c := selectionStartCol "cursorCol".
+            self deleteSelection.
+            lastReplacement notNil ifTrue:[
+                self insertLines:lastReplacement asText withCr:false.
+                self selectFromLine:l col:c
+                             toLine:cursorLine col:(cursorCol - 1).
+            ].
+            ^ true
+        ].
+
+        self searchForwardFor:s startingAtLine:cursorLine col:cursorCol
+        ifFound:[:line :col |
+            self selectFromLine:line col:col
+                         toLine:line col:(col + s size - 1).
+            self makeLineVisible:line.
+            undoAction := [self insertLines:lastString atLine:line col:col].
+
+            self deleteSelection.
+            lastReplacement notNil ifTrue:[
+                self insertLines:lastReplacement asText withCr:false.
+                self selectFromLine:line col:col
+                             toLine:cursorLine col:(cursorCol - 1).
+            ].
+            ^ true
+        ] else:[
+            self showNotFound.
+            ^ false
+        ]
+    ]
+!
+
+multipleAgain
+    "repeat the last action (which was a cut or replace) until search fails"
+
+    [self again] whileTrue:[]
 ! !
 
 !EditTextView methodsFor:'cut & paste'!
@@ -1423,30 +1534,109 @@
 cut
     "cut selection into copybuffer"
 
-    Smalltalk at:#CopyBuffer put:(self selection).
-    self deleteSelection
+    |line col|
+
+    lastString := self selection.
+    lastString notNil ifTrue:[
+        line := selectionStartLine.
+        col := selectionStartCol.
+        undoAction := [self insertLines:lastString atLine:line col:col].
+
+        Smalltalk at:#CopyBuffer put:lastString.
+        self deleteSelection.
+        lastReplacement := nil
+    ]
+!
+
+paste:someText
+    "paste someText at cursor"
+
+    |startLine startCol|
+
+    someText notNil ifTrue:[
+        startLine := cursorLine.
+        startCol := cursorCol.
+        self insertLines:someText asText withCr:false.
+        self selectFromLine:startLine col:startCol
+                     toLine:cursorLine col:(cursorCol - 1).
+        typeOfSelection := #paste.
+        undoAction := [self cut].
+    ]
 !
 
 paste
     "paste copybuffer at cursor"
 
-    |text startLine startCol|
-
-    text := Smalltalk at:#CopyBuffer.
-    text notNil ifTrue:[
-        startLine := cursorLine.
-        startCol := cursorCol.
-        self insertLines:text asText withCr:false.
-        self selectFromLine:startLine col:startCol
-                     toLine:cursorLine col:(cursorCol - 1)
-    ]
+    self paste:(Smalltalk at:#CopyBuffer).
 !
 
 replace
     "replace selection by copybuffer"
 
+    |selected selectedString replacement replacementString 
+     cutOffSpace addSpace t|
+
+    selected := self selection.
+    selected isNil ifTrue:[
+        ^ self paste
+    ].
     self deleteSelection.
-    self paste
+
+    "take care, if we replace a selection without space by a word selected
+     with one - in this case we usually do not want the space.
+     But, if we replace a word-selected selection by something without a
+     space, we DO want the space added."
+
+    cutOffSpace := false.
+    addSpace := false.
+
+    replacement := (Smalltalk at:#CopyBuffer) copy.
+
+    selected size == 1 ifTrue:[
+        selectedString := selected at:1.
+    ].
+    selectedString notNil ifTrue:[
+        ((selectedString startsWith:' ') or:[selectedString endsWith:' ']) ifFalse:[
+           "selection has no space"
+
+            wordSelectStyle notNil ifTrue:[
+                cutOffSpace := true
+            ]
+        ] ifTrue:[
+            addSpace := true
+        ]
+    ].
+
+    replacement size == 1 ifTrue:[
+        replacementString := replacement at:1.
+        cutOffSpace ifTrue:[
+            (replacementString startsWith:' ') ifTrue:[
+                replacementString := replacementString withoutSpaces
+            ].
+        ] ifFalse:[
+            wordSelectStyle == #left ifTrue:[
+                "want a space at left"
+                (replacementString startsWith:' ') ifFalse:[
+                    replacementString := replacementString withoutSpaces.
+                    replacementString := ' ' , replacementString
+                ]
+            ].
+            wordSelectStyle == #right 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:(Smalltalk at:#CopyBuffer).
+    ].
+    lastString := selectedString.
+    lastReplacement := Smalltalk at:#CopyBuffer
 ! !
 
 !EditTextView methodsFor:'selections'!
@@ -1504,10 +1694,11 @@
 
 selectFromLine:startLine col:startCol toLine:endLine col:endCol
     "when a range is selected, position the cursor behind the selection
-     for easier editing"
+     for easier editing. Also typeOfSelection is nilled here."
 
     super selectFromLine:startLine col:startCol toLine:endLine col:endCol.
-    self cursorLine:selectionEndLine col:(selectionEndCol + 1)
+    self cursorLine:selectionEndLine col:(selectionEndCol + 1).
+    typeOfSelection := nil
 ! !
 
 !EditTextView methodsFor:'scrolling'!
@@ -1564,6 +1755,14 @@
 
     |sel|
 
+    "if last operation was a replcae, set pattern to last
+     original string (for search after again)"
+
+    (lastString notNil and:[lastReplacement notNil]) ifTrue:[
+        searchPattern := lastString asString withoutSeparators.
+        ^ self
+    ].
+
     sel := self selection.
     sel notNil ifTrue:[
         self cursorLine:selectionStartLine col:selectionStartCol.
@@ -1599,28 +1798,33 @@
     ]
 !
 
-searchForMatchingParentesis:parChar
-    "search for a matching parenthesis, parChar is one of '$( $[ ${ $) $] $}'. Search
-     for the corresponding character is done forward if its an opening, backwards if
-     its a closing parenthesis.
-     Positions the cursor if found, peeps if not"
+searchForMatchingParenthesisFromLine:startLine col:startCol
+                     ifFound:foundBlock 
+                  ifNotFound:notFoundBlock
+                     onError:failBlock
 
-    |i direction lineString line col charSet ignoreSet closingChar 
-     ignoring delta endCol cc incSet decSet nesting|
+    "search for a matching parenthesis, parChar is one of '$( $[ ${ $) $] $}'. 
+     Search for the corresponding character is done forward if its an opening,
+     backwards if its a closing parenthesis.
+     Performs foundBlock with line/col as argument if found, notFoundBlock if not.
+     If there is a parth. nesting error, performs failBlock."
+
+    |i direction lineString line col parChar charSet ignoreSet closingChar 
+     ignoring delta endCol cc incSet decSet nesting maxLine|
 
     charSet := #( $( $) $[ $] ${ $} ).
     ignoreSet := #( $' $" ).
 
+    parChar := self characterAtLine:startLine col:startCol.
     i := charSet indexOf:parChar.
     i == 0 ifTrue:[
-        device beep.
-        ^ self
+        ^ failBlock value   "not a parenthesis"
     ].
     direction := #( fwd bwd fwd bwd fwd bwd) at:i.
     closingChar := #( $) $( $] $[ $} ${ ) at:i.
 
-    col := cursorCol.
-    line := cursorLine.
+    col := startCol.
+    line := startLine.
     direction == #fwd ifTrue:[
         delta := 1.
         incSet := #( $( $[ ${ ).
@@ -1634,6 +1838,7 @@
     nesting := 1.
     ignoring := false.
     lineString := list at:line.
+    maxLine := list size.
 
     col := col + delta.
     [nesting ~~ 0] whileTrue:[
@@ -1662,15 +1867,16 @@
                     "check if legal"
 
                     cc == closingChar ifFalse:[
-                        device beep.
-                    ] ifTrue:[
-                        self cursorLine:line col:runCol.
+                        ^ failBlock value
                     ].
-                    ^ self
+                    ^ foundBlock value:line value:runCol.
                 ]
             ].
         ].
         line := line + delta.
+        (line < 1 or:[line > maxLine]) ifTrue:[
+            ^ failBlock value
+        ].
         lineString := list at:line.
         direction == #fwd ifTrue:[
             col := 1
@@ -1679,24 +1885,31 @@
         ]
     ].
 
-    self showNotFound
+    ^ notFoundBlock value
 !
 
-searchForMatchingParentesis
-    "search for a matching parenthesis if one is under cusor"
-
-    |line col lineString|
+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"
 
-    col := cursorCol.
-    line := cursorLine.
-    lineString := list at:line.
-    lineString notNil ifTrue:[
-        col <= lineString size ifTrue:[
-            self searchForMatchingParentesis:(lineString at:col).
-            ^ self
-        ]
-    ].
-    device beep
+     self searchForMatchingParenthesisFromLine:cursorLine col:cursorCol
+                               ifFound:[:line :col | self cursorLine:line col:col]
+                            ifNotFound:[self showNotFound]
+                               onError:[device beep]
+!
+
+searchForAndSelectMatchingParenthesis
+    "select characters enclosed by matching parenthesis if one is under cusor"
+
+    self searchForMatchingParenthesisFromLine:cursorLine col:cursorCol
+                              ifFound:[:line :col | 
+                                          self selectFromLine:cursorLine col:cursorCol
+                                                       toLine:line col:col
+                                      ]
+                           ifNotFound:[self showNotFound]
+                              onError:[device beep]
 ! !
 
 !EditTextView methodsFor:'redrawing'!
@@ -1783,6 +1996,14 @@
     "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"
+
         (wordSelectStyle == #left) ifTrue:[
             self replaceSelectionBy:(' ' copyWith:key)
         ] ifFalse:[
@@ -1794,11 +2015,51 @@
             ]
         ].
         wordSelectStyle := nil.
+
+        showMatchingParenthesis ifTrue:[
+            "emacs style parenthesis shower"
+            (#( $( $) $[ $] ${ $} ) includes:key) ifTrue:[
+            self searchForMatchingParenthesisFromLine:cursorLine col:(cursorCol - 1)
+                               ifFound:[:line :col |
+                                            |savLine savCol|
+
+                                            savLine := cursorLine.
+                                            savCol := cursorCol.
+                                            self cursorLine:line col:col.
+                                            device synchronizeOutput.
+                                            OperatingSystem millisecondDelay:200.
+                                            self cursorLine:savLine col:savCol
+                                       ]
+                            ifNotFound:[self showNotFound]
+                               onError:[device beep]
+            ].
+        ].
         ^ self
     ].
 
+    replacing := false.
+
+    "Fn      pastes a key-sequence,
+     Cmd-Fn evaluates a key-sequence"
+    (#(F1 F2 F3 F4 F5 F6 F7 F8 F9) includes:key) ifTrue:[
+        device shiftDown ifFalse:[
+            device metaDown ifTrue:[
+                (Smalltalk at:#FunctionKeySequences) notNil ifTrue:[
+                    Parser evaluate:((Smalltalk at:#FunctionKeySequences) at:key) asString
+                           receiver:self
+                          notifying:nil
+                ]
+            ] ifFalse:[
+                (Smalltalk at:#FunctionKeySequences) notNil ifTrue:[
+                    self paste:((Smalltalk at:#FunctionKeySequences) at:key) asText.
+                ]
+            ]
+        ]
+    ].
+
     ((key == #Paste) or:[key == #Insert]) ifTrue:[self paste. ^self].
     (key == #Cut) ifTrue:[self cut. ^self].
+    (key == #Again) ifTrue:[self again. ^self].
 
     (key == #Replace) ifTrue:[self replace. ^self].
     (key == #Cmdw) ifTrue:[
@@ -1808,7 +2069,11 @@
     ].
 
     (key == #Ctrlm) ifTrue:[
-        self searchForMatchingParentesis. 
+        self searchForMatchingParenthesis. 
+        ^self
+    ].
+    (key == #Cmdm) ifTrue:[
+        self searchForAndSelectMatchingParenthesis. 
         ^self
     ].
 
@@ -1842,18 +2107,26 @@
         self insertCharAtCursor:(Character cr). 
         ^self
     ].
-    (key == #BackSpace) ifTrue:[
-        self unselect. 
-        self makeCursorVisible.
-        self deleteCharBeforeCursor. 
-        ^self
-    ].
     (key == #Tab) ifTrue:[
         device shiftDown ifTrue:[
             self unselect. self cursorBacktab. ^self
         ].
         self unselect. self cursorTab. ^self
     ].
+    (key == #BackSpace) ifTrue:[
+
+" old version just did unselect here "
+"
+        self unselect. 
+"
+" new version deletes selection if any "
+        selectionStartLine notNil ifTrue:[
+            Smalltalk at:#CopyBuffer put:(self selection).
+            self deleteSelection. ^ self
+        ].
+        self makeCursorVisible.
+        self deleteCharBeforeCursor. ^self
+    ].
     (key == #Delete)    ifTrue:[
         selectionStartLine notNil ifTrue:[
             Smalltalk at:#CopyBuffer put:(self selection).
@@ -1892,6 +2165,8 @@
     "move the cursor to the click-position of previous button press"
 
     (button == 1) ifTrue:[
+        lastString := nil. "new selection invalidates remembered string"
+        typeOfSelection := nil. 
         selectionStartLine isNil ifTrue:[
             clickCol notNil ifTrue:[
                 self cursorLine:clickLine col:clickCol