SmallSense__SmalltalkEditSupport.st
branchcvs_MAIN
changeset 917 c1a6a847be65
parent 841 088d207d9275
child 1101 97cebca30710
--- a/SmallSense__SmalltalkEditSupport.st	Tue Jan 26 21:32:58 2016 +0100
+++ b/SmallSense__SmalltalkEditSupport.st	Tue Jan 26 21:40:42 2016 +0100
@@ -5,7 +5,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -37,7 +37,7 @@
 This library is free software; you can redistribute it and/or
 modify it under the terms of the GNU Lesser General Public
 License as published by the Free Software Foundation; either
-version 2.1 of the License. 
+version 2.1 of the License.
 
 This library is distributed in the hope that it will be useful,
 but WITHOUT ANY WARRANTY; without even the implied warranty of
@@ -54,17 +54,17 @@
 
 indent: text by: level
     ^ String streamContents:[ :out |
-        | in |
+	| in |
 
-        in := text readStream.
-        [ in atEnd ] whileFalse:[
-            in peek == Character cr ifTrue:[
-                out nextPut: in next.
-                out next: level put: Character space.
-            ] ifFalse:[
-                out nextPut: in next.
-            ].
-        ].
+	in := text readStream.
+	[ in atEnd ] whileFalse:[
+	    in peek == Character cr ifTrue:[
+		out nextPut: in next.
+		out next: level put: Character space.
+	    ] ifFalse:[
+		out nextPut: in next.
+	    ].
+	].
     ]
 
     "Created: / 04-05-2014 / 23:29:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -73,45 +73,45 @@
 undent: stringOrStringCollection
     | lines indent tabwidth ignoreIndentOfFirstLineIfZero indentOfFirstLineIsZero |
 
-    stringOrStringCollection isStringCollection ifTrue:[ 
-        ignoreIndentOfFirstLineIfZero := false.
-        stringOrStringCollection removeLast.
-        lines := stringOrStringCollection.
+    stringOrStringCollection isStringCollection ifTrue:[
+	ignoreIndentOfFirstLineIfZero := false.
+	stringOrStringCollection removeLast.
+	lines := stringOrStringCollection.
     ] ifFalse:[
-        ignoreIndentOfFirstLineIfZero := true.
-        lines := stringOrStringCollection asStringCollection.
+	ignoreIndentOfFirstLineIfZero := true.
+	lines := stringOrStringCollection asStringCollection.
     ].
     tabwidth := (ListView userDefaultTabPositions = ListView tab4Positions) ifTrue:[ 4 ] ifFalse: [ 8 ].
     indent := nil.
     indentOfFirstLineIsZero := false.
 
     1 to: lines size do:[:lineNo |
-        | line lineIndent |
+	| line lineIndent |
 
-        line := lines at: lineNo.
-        lineIndent := line indexOfNonSeparator.
-        (lineIndent ~~ 0) ifTrue:[
-            indent isNil ifTrue:[
-                indent := ((lineIndent - 1) // tabwidth) * tabwidth.
-            ] ifFalse:[ 
-                indent := (((lineIndent - 1) // tabwidth) * tabwidth) min: indent.
-            ].
-            indent == 0 ifTrue:[
-                (lineNo == 1 and:[ignoreIndentOfFirstLineIfZero]) ifTrue:[
-                    indent := nil.
-                    indentOfFirstLineIsZero := true.
-                ] ifFalse:[
-                    ^ stringOrStringCollection isStringCollection
-                        ifTrue:[ stringOrStringCollection asStringWithoutFinalCR ]
-                        ifFalse:[ stringOrStringCollection ]
-                ].
-            ].
-        ].
+	line := lines at: lineNo.
+	lineIndent := line indexOfNonSeparator.
+	(lineIndent ~~ 0) ifTrue:[
+	    indent isNil ifTrue:[
+		indent := ((lineIndent - 1) // tabwidth) * tabwidth.
+	    ] ifFalse:[
+		indent := (((lineIndent - 1) // tabwidth) * tabwidth) min: indent.
+	    ].
+	    indent == 0 ifTrue:[
+		(lineNo == 1 and:[ignoreIndentOfFirstLineIfZero]) ifTrue:[
+		    indent := nil.
+		    indentOfFirstLineIsZero := true.
+		] ifFalse:[
+		    ^ stringOrStringCollection isStringCollection
+			ifTrue:[ stringOrStringCollection asStringWithoutFinalCR ]
+			ifFalse:[ stringOrStringCollection ]
+		].
+	    ].
+	].
     ].
-    1 to: lines size do:[:lineNr |  
-        (lineNr ~~ 1 or:[indentOfFirstLineIsZero not]) ifTrue:[ 
-            lines at: lineNr put: ((lines at: lineNr) copyFrom: indent + 1).
-        ].
+    1 to: lines size do:[:lineNr |
+	(lineNr ~~ 1 or:[indentOfFirstLineIsZero not]) ifTrue:[
+	    lines at: lineNr put: ((lines at: lineNr) copyFrom: indent + 1).
+	].
     ].
     ^ lines asStringWithoutFinalCR
 
@@ -152,22 +152,22 @@
     | ignore |
 
     (stringOrLines isString and:[ stringOrLines first == lastTypedKey0 ]) ifTrue:[
-        ignore := stringOrLines copyFrom:2.
+	ignore := stringOrLines copyFrom:2.
     ].
     ^ self
-            electricInsert:stringOrLines
-            advanceCursorBy:offsetOrNil
-            ignoreKeystrokes:ignore
+	    electricInsert:stringOrLines
+	    advanceCursorBy:offsetOrNil
+	    ignoreKeystrokes:ignore
 
     "Created: / 20-01-2014 / 09:27:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 electricInsertSnippet
     lastTypedKey0 == Character space ifTrue:[
-        ^ self electricInsertSnippetAfterSpace
+	^ self electricInsertSnippetAfterSpace
     ].
     lastTypedKey0 == $: ifTrue:[
-        ^ self electricInsertSnippetAfterDoubleColon
+	^ self electricInsertSnippetAfterDoubleColon
     ].
     ^ false.
 
@@ -179,49 +179,49 @@
 
     tokens := self scanLineAtCursor.
     tokens isEmptyOrNil ifTrue:[
-        ^ false
+	^ false
     ].
     lastToken0 := tokens at:(tokens size - 3).
     lastToken0 = 'Error' ifTrue:[
-        ^ false
+	^ false
     ].
     (tokens last > service textView cursorCol) ifTrue:[
-        ^ false
+	^ false
     ].
     ((lastToken0 == #Identifier)
-        and:[ (service textView cursorCol - 1) == tokens last ])
-            ifTrue:[
-                lastValue0 := tokens at:tokens size - 2.
-                tokens size > 4 ifTrue:[
-                    (#( #do #select #reject #detect #contains #allSatisfy #anySatisfy )
-                        includes:lastValue0)
-                            ifTrue:[
-                                | collectionName  eachName  space  part1  part2 |
+	and:[ (service textView cursorCol - 1) == tokens last ])
+	    ifTrue:[
+		lastValue0 := tokens at:tokens size - 2.
+		tokens size > 4 ifTrue:[
+		    (#( #do #select #reject #detect #contains #allSatisfy #anySatisfy )
+			includes:lastValue0)
+			    ifTrue:[
+				| collectionName  eachName  space  part1  part2 |
 
-                                space := RBFormatter spaceAfterKeywordSelector ifTrue:[
-                                        ' '
-                                    ] ifFalse:[ '' ].
-                                eachName := 'each'.
-                                tokens size > 4 ifTrue:[
-                                    ((collectionName := tokens at:tokens size - 6) last = $s) ifTrue:[
-                                        (collectionName endsWith:'ses') ifTrue:[
-                                            eachName := collectionName copyButLast:2
-                                        ] ifFalse:[
-                                            eachName := collectionName copyButLast:1
-                                        ].
-                                    ].
-                                ].
-                                part1 := ':' , space , '[:' , eachName , ' | '.
-                                part2 := ' ]'.
-                                self electricInsert:part1 , part2 advanceCursorBy:part1 size.
-                                ^ true.
-                            ].
-                    RBFormatter spaceAfterKeywordSelector ifTrue:[
-                        self electricInsert:': '.
-                        ^ true.
-                    ]
-                ].
-            ].
+				space := RBFormatter spaceAfterKeywordSelector ifTrue:[
+					' '
+				    ] ifFalse:[ '' ].
+				eachName := 'each'.
+				tokens size > 4 ifTrue:[
+				    ((collectionName := tokens at:tokens size - 6) last = $s) ifTrue:[
+					(collectionName endsWith:'ses') ifTrue:[
+					    eachName := collectionName copyButLast:2
+					] ifFalse:[
+					    eachName := collectionName copyButLast:1
+					].
+				    ].
+				].
+				part1 := ':' , space , '[:' , eachName , ' | '.
+				part2 := ' ]'.
+				self electricInsert:part1 , part2 advanceCursorBy:part1 size.
+				^ true.
+			    ].
+		    RBFormatter spaceAfterKeywordSelector ifTrue:[
+			self electricInsert:': '.
+			^ true.
+		    ]
+		].
+	    ].
     ^ false.
 
     "Created: / 22-10-2013 / 03:05:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -233,39 +233,39 @@
 
     tokens := self scanLineAtCursor.
     tokens isEmptyOrNil ifTrue:[
-        ^ false
+	^ false
     ].
     lastToken0 := tokens at:(tokens size - 3).
     lastToken0 = 'Error' ifTrue:[
-        ^ false
+	^ false
     ].
     (tokens last > service textView cursorCol) ifTrue:[
-        ^ false
+	^ false
     ].
     lastToken0 == #Keyword ifTrue:[
-        lastValue0 := tokens at:tokens size - 2.
-        tokens size > 4 ifTrue:[
-            (#( #do: #select: #reject: #detect: #contains: #allSatisfy: #anySatisfy: )
-                includes:lastValue0)
-                    ifTrue:[
-                        | collectionName  eachName  part1  part2 |
+	lastValue0 := tokens at:tokens size - 2.
+	tokens size > 4 ifTrue:[
+	    (#( #do: #select: #reject: #detect: #contains: #allSatisfy: #anySatisfy: )
+		includes:lastValue0)
+		    ifTrue:[
+			| collectionName  eachName  part1  part2 |
 
-                        eachName := 'each'.
-                        tokens size > 4 ifTrue:[
-                            ((collectionName := tokens at:tokens size - 6) last = $s) ifTrue:[
-                                (collectionName endsWith:'ses') ifTrue:[
-                                    eachName := collectionName copyButLast:2
-                                ] ifFalse:[
-                                    eachName := collectionName copyButLast:1
-                                ].
-                            ].
-                        ].
-                        part1 := ' [:' , eachName , ' | '.
-                        part2 := ' ]'.
-                        self electricInsert:part1 , part2 advanceCursorBy:part1 size.
-                        ^ true.
-                    ].
-        ]
+			eachName := 'each'.
+			tokens size > 4 ifTrue:[
+			    ((collectionName := tokens at:tokens size - 6) last = $s) ifTrue:[
+				(collectionName endsWith:'ses') ifTrue:[
+				    eachName := collectionName copyButLast:2
+				] ifFalse:[
+				    eachName := collectionName copyButLast:1
+				].
+			    ].
+			].
+			part1 := ' [:' , eachName , ' | '.
+			part2 := ' ]'.
+			self electricInsert:part1 , part2 advanceCursorBy:part1 size.
+			^ true.
+		    ].
+	]
     ].
     ^ false.
 
@@ -284,7 +284,7 @@
     view ~~ textView ifTrue:[ ^ false ].
 
     (self keyPressIgnored: key) ifTrue:[
-        ^ true.
+	^ true.
     ].
 
     lastTypedKey3 := lastTypedKey2.
@@ -293,49 +293,49 @@
     lastTypedKey0 := key.
 
     key == #CodeCompletion ifTrue:[
-        | controller |
+	| controller |
 
-        (controller := self textView completionSupport) notNil ifTrue:[
-            ^ controller handleKeyPress:key x:x y:y
-        ].
-        ^ false
+	(controller := self textView completionSupport) notNil ifTrue:[
+	    ^ controller handleKeyPress:key x:x y:y
+	].
+	^ false
     ].
 
     key == #BackSpace ifTrue:[
-        backspaceIsUndo ifTrue:[
-             textView undo.
-             backspaceIsUndo := false.
-             ^ true.
-        ].
+	backspaceIsUndo ifTrue:[
+	     textView undo.
+	     backspaceIsUndo := false.
+	     ^ true.
+	].
     ].
     backspaceIsUndo := false.
 
     key == #Paste ifTrue:[
-        ^ self keyPressPaste.
+	^ self keyPressPaste.
     ].
 
 
     key == $^ ifTrue:[
-        ^ self keyPressReturnToken
+	^ self keyPressReturnToken
     ].
     key == #Return ifTrue: [
-        ^ self keyPressReturn
+	^ self keyPressReturn
     ].
 
     key == $: ifTrue: [
-        ^ self keyPressDoubleColon.
+	^ self keyPressDoubleColon.
     ].
 
     key == $= ifTrue: [
-        ^ self keyPressEqual
+	^ self keyPressEqual
     ].
 
     key == Character space ifTrue:[
-        ^ self electricInsertSnippet
+	^ self electricInsertSnippet
     ].
 
     key == $[ ifTrue:[
-        ^ self keyPressOpenBracket.
+	^ self keyPressOpenBracket.
     ].
 
     ^ false.
@@ -359,8 +359,8 @@
     line size > textView cursorCol ifTrue: [ ^ false ].
     line size < (textView cursorCol - 1) ifTrue: [ ^ false ].
     (line at: textView cursorCol - 1) == $: ifTrue: [
-        self electricInsert:'= '.
-        ^ true
+	self electricInsert:'= '.
+	^ true
     ].
     ^ false
 
@@ -375,26 +375,26 @@
 
     line := textView listAt: textView cursorLine.
     line notNil ifTrue:[
-        line := line string.
-        line size > textView cursorCol ifTrue: [
-            line size downTo: textView cursorCol - 1 do:[:i |
-                (line at:i) == Character space ifFalse:[ ^ false ].
-            ]
-        ].
+	line := line string.
+	line size > textView cursorCol ifTrue: [
+	    line size downTo: textView cursorCol - 1 do:[:i |
+		(line at:i) == Character space ifFalse:[ ^ false ].
+	    ]
+	].
     ].
 
     RBFormatter spaceAfterBlockStart ifTrue:[
-        RBFormatter spaceBeforeBlockEnd ifTrue:[
-            self electricInsert:'[  ]' advanceCursorBy: 2.
-        ] ifFalse:[
-            self electricInsert:'[ ]' advanceCursorBy: 2.
-        ].
+	RBFormatter spaceBeforeBlockEnd ifTrue:[
+	    self electricInsert:'[  ]' advanceCursorBy: 2.
+	] ifFalse:[
+	    self electricInsert:'[ ]' advanceCursorBy: 2.
+	].
     ] ifFalse:[
-        RBFormatter spaceBeforeBlockEnd ifTrue:[
-            self electricInsert:'[ ]' advanceCursorBy: 1.
-        ] ifFalse:[
-            self electricInsert:'[]' advanceCursorBy: 1.
-        ].
+	RBFormatter spaceBeforeBlockEnd ifTrue:[
+	    self electricInsert:'[ ]' advanceCursorBy: 1.
+	] ifFalse:[
+	    self electricInsert:'[]' advanceCursorBy: 1.
+	].
     ].
     ^ true.
 
@@ -405,27 +405,27 @@
 keyPressPaste
     | textSelected textPasted currentLineNo currentLine currentLineIsEmpty |
 
-    UserPreferences current smallSenseSmalltalkIndentOnPasteEnabled ifFalse:[ ^ false ].
+    (UserPreferences current smallSenseSmalltalkIndentOnPasteEnabled == true) ifFalse:[ ^ false ].
 
     textView checkModificationsAllowed ifTrue:[
-        textSelected := textPasted := textView getTextSelectionOrTextSelectionFromHistory.
-        currentLineNo := textView currentLine.
-        currentLineIsEmpty := true.
-        ((currentLineNo > textView list size)
-            or:[ (currentLine := textView list at: currentLineNo) isNil
-                or:[ (currentLineIsEmpty := currentLine indexOfNonSeparator == 0) ]]) ifTrue:[
-                    | indent |
+	textSelected := textPasted := textView getTextSelectionOrTextSelectionFromHistory.
+	currentLineNo := textView currentLine.
+	currentLineIsEmpty := true.
+	((currentLineNo > textView list size)
+	    or:[ (currentLine := textView list at: currentLineNo) isNil
+		or:[ (currentLineIsEmpty := currentLine indexOfNonSeparator == 0) ]]) ifTrue:[
+		    | indent |
 
-                    currentLineIsEmpty ifTrue:[
-                        indent := textView leftIndentForLine: currentLineNo.
-                        textView setCursorCol: indent + 1.
-                    ].
-                    textPasted := self class undent: textPasted.
-                    textPasted := self class indent: textPasted by: textView cursorCol - 1.
+		    currentLineIsEmpty ifTrue:[
+			indent := textView leftIndentForLine: currentLineNo.
+			textView setCursorCol: indent + 1.
+		    ].
+		    textPasted := self class undent: textPasted.
+		    textPasted := self class indent: textPasted by: textView cursorCol - 1.
 
-                ].
+		].
 
-        textView undoablePasteOrReplace: textPasted info: nil.
+	textView undoablePasteOrReplace: textPasted info: nil.
     ].
     ^ true
 
@@ -446,15 +446,15 @@
     "/ ']', then remeber it.
     closingBracketIndex := 0.
     line size > textView cursorCol ifTrue: [
-        line size downTo: ((textView cursorCol - 1) max: 1) do:[:i |
-            (c :=line at:i) == Character space ifFalse:[
-                (c == $] and:[closingBracketIndex == 0]) ifTrue:[
-                    closingBracketIndex := i.
-                ] ifFalse:[
-                    ^ false
-                ].
-            ].
-        ]
+	line size downTo: ((textView cursorCol - 1) max: 1) do:[:i |
+	    (c :=line at:i) == Character space ifFalse:[
+		(c == $] and:[closingBracketIndex == 0]) ifTrue:[
+		    closingBracketIndex := i.
+		] ifFalse:[
+		    ^ false
+		].
+	    ].
+	]
     ].
 
     (line indexOfAny:'[|/') == 0 ifTrue:[ ^ false ].
@@ -462,11 +462,11 @@
     "/ Insert "/ at the beggining of the line if current line starts with "/
     i := currentLineIndent := line indexOfNonSeparator.
     (i ~~ 0 and:[ i < line size and:[(line at:i) == $" and:[(line at:i + 1) == $/]]]) ifTrue:[
-        "/ OK, current line contains eol-comment. Split into
-        "/ two actions so backspace deletes only the inserted '"/ ' text
-        self electricInsert:#( '' '' ) advanceCursorBy:(1 @ i).
-        self electricInsert:'"/ '.
-        ^ true
+	"/ OK, current line contains eol-comment. Split into
+	"/ two actions so backspace deletes only the inserted '"/ ' text
+	self electricInsert:#( '' '' ) advanceCursorBy:(1 @ i).
+	self electricInsert:'"/ '.
+	^ true
     ].
 
     "/ Now insert/reindent closing bracket ( ']' ) for block, byt only
@@ -486,53 +486,53 @@
     [ (line at: i) isSeparator and:[i > 0] ] whileTrue:[ i := i - 1 ].
     i == 0 ifTrue:[ ^ false ].
     (line at: i) == $[ ifTrue:[
-        self electricDo:[
-            closingBracketIndex ~~ 0 ifTrue:[
-                self electricDeleteCharacterAtCol: closingBracketIndex
-            ].
-            self electricInsertBlockOpenedBy:nil closedBy:'].'.
-        ].
-        ^ true
+	self electricDo:[
+	    closingBracketIndex ~~ 0 ifTrue:[
+		self electricDeleteCharacterAtCol: closingBracketIndex
+	    ].
+	    self electricInsertBlockOpenedBy:nil closedBy:'].'.
+	].
+	^ true
     ].
     tokens := self tokensAtCursorLine.
     tokens isEmpty ifTrue:[ ^ false ].
     i := tokens size.
     t := tokens at: i.
     t == $[ ifTrue:[
-        self electricDo:[
-            closingBracketIndex ~~ 0 ifTrue:[
-                self electricDeleteCharacterAtCol: closingBracketIndex
-            ].
-            self electricInsertBlockOpenedBy:nil closedBy:'].'.
-        ].
-        ^ true
+	self electricDo:[
+	    closingBracketIndex ~~ 0 ifTrue:[
+		self electricDeleteCharacterAtCol: closingBracketIndex
+	    ].
+	    self electricInsertBlockOpenedBy:nil closedBy:'].'.
+	].
+	^ true
     ].
     t == $| ifTrue:[
-        i := i - 1.
-        [ i > 1 and:[ (tokens at: i) == #Identifier and:[ (tokens at: i - 1) == $: ]] ] whileTrue:[ i := i - 2 ].
+	i := i - 1.
+	[ i > 1 and:[ (tokens at: i) == #Identifier and:[ (tokens at: i - 1) == $: ]] ] whileTrue:[ i := i - 2 ].
 
-        (i ~~ 0 and: [(tokens at: i) == $[]) ifTrue:[
-            self electricDo:[
-                closingBracketIndex ~~ 0 ifTrue:[
-                    self electricDeleteCharacterAtCol: closingBracketIndex
-                ].
-                self electricInsertBlockOpenedBy:nil closedBy:'].'.
-            ].
-            ^ true
-        ].
-        i := tokens size  - 1.
-        [ i > 0 and:[ (tokens at: i) == #Identifier ] ] whileTrue:[ i := i - 1 ].
-        (i ~~ 0 and: [(tokens at: i) == $|]) ifTrue:[
-            RBFormatter emptyLineAfterTemporaries ifTrue:[
-                self electricDo:[
-                    closingBracketIndex ~~ 0 ifTrue:[
-                        self electricDeleteCharacterAtCol: closingBracketIndex
-                    ].
-                    self electricInsert:#( '' '' '' ) advanceCursorBy:2 @ currentLineIndent.
-                ].
-                ^ true
-            ]
-        ]
+	(i ~~ 0 and: [(tokens at: i) == $[]) ifTrue:[
+	    self electricDo:[
+		closingBracketIndex ~~ 0 ifTrue:[
+		    self electricDeleteCharacterAtCol: closingBracketIndex
+		].
+		self electricInsertBlockOpenedBy:nil closedBy:'].'.
+	    ].
+	    ^ true
+	].
+	i := tokens size  - 1.
+	[ i > 0 and:[ (tokens at: i) == #Identifier ] ] whileTrue:[ i := i - 1 ].
+	(i ~~ 0 and: [(tokens at: i) == $|]) ifTrue:[
+	    RBFormatter emptyLineAfterTemporaries ifTrue:[
+		self electricDo:[
+		    closingBracketIndex ~~ 0 ifTrue:[
+			self electricDeleteCharacterAtCol: closingBracketIndex
+		    ].
+		    self electricInsert:#( '' '' '' ) advanceCursorBy:2 @ currentLineIndent.
+		].
+		^ true
+	    ]
+	]
     ].
     ^ false.
 
@@ -542,10 +542,10 @@
 
 keyPressReturnToken
     RBFormatter spaceAfterReturnToken ifTrue:[
-        self electricDo:[
-            textView insertStringAtCursor:'^ '
-        ].
-        ^ true
+	self electricDo:[
+	    textView insertStringAtCursor:'^ '
+	].
+	^ true
     ].
     ^ false
 
@@ -573,9 +573,9 @@
     line isEmpty ifTrue:[ ^ #() ].
     scanner := Scanner for: line.
     ^ OrderedCollection streamContents:[:tokens |
-        [ token := scanner nextToken.token ~~ #EOF ] whileTrue:[
-            tokens nextPut: token.
-        ].
+	[ token := scanner nextToken.token ~~ #EOF ] whileTrue:[
+	    tokens nextPut: token.
+	].
     ].
 
     "Created: / 25-07-2013 / 00:07:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"