EditTextView.st
changeset 3549 569d0e4ab5a3
parent 3542 30ed44ed0178
child 3550 4d8ee421926c
--- a/EditTextView.st	Mon Feb 04 16:37:00 2008 +0100
+++ b/EditTextView.st	Mon Feb 04 17:14:07 2008 +0100
@@ -2917,7 +2917,18 @@
 joinLines
     self 
         undoableDo:[
-            self mergeLine:cursorLine removeBlanks:true
+            |line col lineLen|
+
+            line := cursorLine.
+            col := cursorCol.
+            lineLen := (list at:line) size.
+            col > lineLen ifTrue:[
+                self insertString:(String new:col-lineLen) atLine:line col:col+1.
+            ] ifFalse:[
+                self deleteCharsAtLine:line fromCol:col toCol:lineLen.
+            ].
+            self mergeLine:line removeBlanks:true.
+            self cursorLine:line col:col.
         ]
         info:'Join'
 !
@@ -3140,22 +3151,30 @@
     "Modified: 9.10.1996 / 16:14:35 / cg"
 !
 
-replaceString:aString to:aNewString ignoreCase:ign
-|continue count|
-self cursorToTop.
-self selectFromBeginning.
-count := 0.
-continue := true.
-[continue] whileTrue:[
-     (self selectionAsString notNil and:[self selectionAsString sameAs:aString ignoreCase: ign])
-        ifTrue:[self replaceSelectionWith: aNewString.          
-                count := count + 1.].
-     self searchFwd: aString 
-        ignoreCase:ign 
-        ifAbsent:[Dialog information: aString, ' has been replaced to ', aNewString, ' ',count printString, ' times'.
-                  continue := false.].
-
-].
+replaceString:aString to:aNewString ignoreCase:ign 
+    |continue count|
+
+    self cursorToTop.
+    self selectFromBeginning.
+    count := 0.
+    continue := true.
+    [ continue ] whileTrue:[
+        (self selectionAsString notNil 
+        and:[ self selectionAsString sameAs:aString ignoreCase:ign ]) 
+            ifTrue:[
+                self replaceSelectionWith:aNewString.
+                count := count + 1.
+            ].
+        self 
+            searchFwd:aString
+            ignoreCase:ign
+            ifAbsent:[
+                Dialog 
+                    information:aString , ' has been replaced to ' , aNewString , ' ' 
+                            , count printString , ' times'.
+                continue := false.
+            ].
+    ].
 
     "Created: / 10-07-2006 / 16:42:48 / fm"
 !
@@ -3210,64 +3229,64 @@
 !EditTextView methodsFor:'editing-basic'!
 
 basicDeleteCharsAtLine:lineNr fromCol:startCol toCol:endCol
-    "delete characters from startCol to endCol in line lineNr
-    "
+    "delete characters from startCol to endCol in line lineNr"
+
     |line lineSize newLine start stop prevWidth newWidth|
 
     line := self listAt:lineNr.
 
     (self checkModificationsAllowed and:[line notNil]) ifTrue:[
-	lineSize := line size.
-
-	startCol == 0     ifFalse:[ start := startCol ]
-			   ifTrue:[ start := 1 ].
-
-	endCol > lineSize ifFalse:[ stop  := endCol ]
-			   ifTrue:[ stop  := lineSize ].
-
-	stop >= start ifTrue:[
-	    start ~~ 1 ifTrue:[ newLine := line copyFrom:1 to:(start-1) ]
-		      ifFalse:[ newLine := '' ].
-
-	    stop == lineSize ifFalse:[
-		line bitsPerCharacter > newLine bitsPerCharacter ifTrue:[
-		    newLine := line string species fromString:newLine.
-		].
-		newLine := newLine, (line copyFrom:(stop + 1) to:lineSize)
-	    ].
-
-	    (trimBlankLines and:[newLine isBlank]) ifTrue:[
-		newLine := nil
-	    ].
-
-	    prevWidth := self widthOfLine:lineNr.
-
-	    list at:lineNr put:newLine.
-
-	    (prevWidth = widthOfWidestLine) ifTrue:[
-		"/ remember old width of this line,
-		"/ only clear widthOfWidestLine, if this lines
-		"/ length was (one of) the longest.
-		"/ avoids slow delete with huge texts.
-		widthOfWidestLine := nil.   "i.e. unknown"
-
-		"/ scroll left if reqiured
-		viewOrigin x > 0 ifTrue:[
-		    newWidth := self widthOfLine:lineNr.
-		    newWidth < (viewOrigin x + width) ifTrue:[
-			self scrollHorizontalTo:(newWidth
-						 - width
-						 + margin + margin
-						 + (font widthOf:'  '))
-		    ]
-		].
-		self textChanged.
-	    ] ifFalse:[
-		self textChanged "/ textChangedButNoSizeChange
-	    ].
-	    self redrawLine:lineNr from:start.
-
-	]
+        lineSize := line size.
+
+        startCol == 0     ifFalse:[ start := startCol ]
+                           ifTrue:[ start := 1 ].
+
+        endCol > lineSize ifFalse:[ stop  := endCol ]
+                           ifTrue:[ stop  := lineSize ].
+
+        stop >= start ifTrue:[
+            start ~~ 1 ifTrue:[ newLine := line copyFrom:1 to:(start-1) ]
+                      ifFalse:[ newLine := '' ].
+
+            stop == lineSize ifFalse:[
+                line bitsPerCharacter > newLine bitsPerCharacter ifTrue:[
+                    newLine := line string species fromString:newLine.
+                ].
+                newLine := newLine, (line copyFrom:(stop + 1) to:lineSize)
+            ].
+
+            (trimBlankLines and:[newLine isBlank]) ifTrue:[
+                newLine := nil
+            ].
+
+            prevWidth := self widthOfLine:lineNr.
+
+            list at:lineNr put:newLine.
+
+            (prevWidth = widthOfWidestLine) ifTrue:[
+                "/ remember old width of this line,
+                "/ only clear widthOfWidestLine, if this lines
+                "/ length was (one of) the longest.
+                "/ avoids slow delete with huge texts.
+                widthOfWidestLine := nil.   "i.e. unknown"
+
+                "/ scroll left if reqiured
+                viewOrigin x > 0 ifTrue:[
+                    newWidth := self widthOfLine:lineNr.
+                    newWidth < (viewOrigin x + width) ifTrue:[
+                        self scrollHorizontalTo:(newWidth
+                                                 - width
+                                                 + margin + margin
+                                                 + (font widthOf:'  '))
+                    ]
+                ].
+                self textChanged.
+            ] ifFalse:[
+                self textChanged "/ textChangedButNoSizeChange
+            ].
+            self redrawLine:lineNr from:start.
+
+        ]
     ]
 
     "Modified: / 11.11.1998 / 00:01:09 / cg"
@@ -3793,8 +3812,8 @@
 !
 
 deleteCharsAtLine:lineNr fromCol:startCol toCol:endCol
-    "delete characters from startCol to endCol in line lineNr
-    "
+    "delete characters from startCol to endCol in line lineNr"
+
     |deleted|
 
     deleted := self textFromLine:lineNr col:startCol toLine:lineNr col:endCol.
@@ -7202,5 +7221,5 @@
 !EditTextView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.422 2008-02-04 12:19:29 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/EditTextView.st,v 1.423 2008-02-04 16:14:07 cg Exp $'
 ! !