SmallSense__SmalltalkEditSupport.st
changeset 174 3e08d765d86f
parent 144 a43236d0c411
child 176 df6d3225d1e4
--- a/SmallSense__SmalltalkEditSupport.st	Tue Nov 19 13:02:56 2013 +0000
+++ b/SmallSense__SmalltalkEditSupport.st	Wed Feb 26 19:06:00 2014 +0100
@@ -39,93 +39,123 @@
 
 !SmalltalkEditSupport methodsFor:'editing'!
 
-insertElectricSnippet
+electricInsert:stringOrLines advanceCursorBy:offsetOrNil 
+    | ignore |
+
+    (stringOrLines isString and:[ stringOrLines first == lastTypedKey0 ]) ifTrue:[
+        ignore := stringOrLines copyFrom:2.
+    ].
+    ^ self 
+            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 insertElectricSnippetAfterSpace
+        ^ self electricInsertSnippetAfterSpace
     ].
     lastTypedKey0 == $: ifTrue:[
-        ^ self insertElectricSnippetAfterDoubleColon
+        ^ self electricInsertSnippetAfterDoubleColon
     ].
-
     ^ false.
 
     "Created: / 22-10-2013 / 02:55:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-insertElectricSnippetAfterDoubleColon
-    | tokens lastToken0 lastValue0 |
+electricInsertSnippetAfterDoubleColon
+    | tokens  lastToken0  lastValue0 |
 
     tokens := self scanLineAtCursor.
-    tokens isEmptyOrNil ifTrue:[ ^ false ].
-    lastToken0 := tokens at: (tokens size - 3).
-    lastToken0 = 'Error' ifTrue:[ ^ false ].
-    (tokens last > service textView cursorCol) ifTrue:[ ^ 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 |
-                space := RBFormatter spaceAfterKeywordSelector ifTrue:[' '] ifFalse:[''].
-                eachName := 'each'.
+    tokens isEmptyOrNil ifTrue:[
+        ^ false
+    ].
+    lastToken0 := tokens at:(tokens size - 3).
+    lastToken0 = 'Error' ifTrue:[
+        ^ false
+    ].
+    (tokens last > service textView cursorCol) ifTrue:[
+        ^ false
+    ].
+    ((lastToken0 == #Identifier) 
+        and:[ (service textView cursorCol - 1) == tokens last ]) 
+            ifTrue:[
+                lastValue0 := tokens at:tokens size - 2.
                 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
-                        ].
-                    ].
+                    (#( #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.
+                    ]
                 ].
-                part1 := ':', space , '[:' , eachName , ' | '.
-                part2 := ' ]'.
-                self insertElectric: part1 , part2 advanceCursorBy: part1 size.
-                ^ true.
-            ]. 
-            RBFormatter spaceAfterKeywordSelector ifTrue:[
-                self insertElectric: ': '.
-                ^ true.
-            ]
-        ].
-
-    ].
+            ].
     ^ false.
 
     "Created: / 22-10-2013 / 03:05:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 22-10-2013 / 12:00:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-insertElectricSnippetAfterSpace
-    | tokens lastToken0 lastValue0 |
+electricInsertSnippetAfterSpace
+    | tokens  lastToken0  lastValue0 |
 
     tokens := self scanLineAtCursor.
-    tokens isEmptyOrNil ifTrue:[ ^ false ].
-    lastToken0 := tokens at: (tokens size - 3).
-    lastToken0 = 'Error' ifTrue:[ ^ false ].
-    (tokens last > service textView cursorCol) ifTrue:[ ^ false ].
-
+    tokens isEmptyOrNil ifTrue:[
+        ^ false
+    ].
+    lastToken0 := tokens at:(tokens size - 3).
+    lastToken0 = 'Error' ifTrue:[
+        ^ false
+    ].
+    (tokens last > service textView cursorCol) ifTrue:[
+        ^ false
+    ].
     lastToken0 == #Keyword ifTrue:[
-        lastValue0 := tokens at: tokens size - 2.
-
+        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
+            (#( #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.
                     ].
-                ].
-                part1 := ' [:' , eachName , ' | '.
-                part2 := ' ]'.
-                self insertElectric: part1 , part2 advanceCursorBy: part1 size.
-                ^ true.
-            ]. 
         ]
     ].
     ^ false.
@@ -144,6 +174,10 @@
 
     view ~~ textView ifTrue:[ ^ false ].
 
+    (self keyPressIgnored: key) ifTrue:[
+        ^ true.
+    ]. 
+
     lastTypedKey3 := lastTypedKey2.
     lastTypedKey2 := lastTypedKey1.
     lastTypedKey1 := lastTypedKey0.
@@ -174,14 +208,22 @@
         ^ self keyPressEqual
     ].
 
-    ^ super keyPress: key x:x y:y in: view
+    key == Character space ifTrue:[
+        ^ self electricInsertSnippet
+    ].
+
+    key == $[ ifTrue:[
+        ^ self keyPressOpenBracket.
+    ].
+
+    ^ false.
 
     "Created: / 07-03-2010 / 09:36:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 22-10-2013 / 11:09:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 29-01-2014 / 10:31:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 keyPressDoubleColon
-    ^ self insertElectricSnippetAfterDoubleColon
+    ^ self electricInsertSnippetAfterDoubleColon
 
     "Created: / 22-10-2013 / 03:08:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -195,7 +237,7 @@
     line size > textView cursorCol ifTrue: [ ^ false ].
     line size < (textView cursorCol - 1) ifTrue: [ ^ false ].
     (line at: textView cursorCol - 1) == $: ifTrue: [
-        self insertElectric:'= '.  
+        self electricInsert:'= '.  
         ^ true
     ].
     ^ false
@@ -203,13 +245,65 @@
     "Created: / 22-10-2013 / 11:01:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+keyPressOpenBracket
+    "Opening `[` has been pressed. Complete closing bracket and position
+     cursor in between them, but only of there's no other text on current line"
+
+    | line |
+
+    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 ].
+            ]
+        ].
+    ].
+
+    RBFormatter spaceAfterBlockStart ifTrue:[
+        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.
+        ].
+    ].
+    ^ true.
+
+    "Created: / 22-01-2014 / 21:35:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 29-01-2014 / 10:30:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 keyPressReturn
-    | line tokens i t currentLineIndent |
+    | line tokens c i t currentLineIndent closingBracketIndex |
 
     line := textView listAt: textView cursorLine.
     line isNil ifTrue:[ ^ false ].
     line := line string.
-    line size > textView cursorCol ifTrue: [ ^ false ].
+
+    "/ Check whether there is any text afer cursor
+    "/ except of single closing `]`. If there's some text
+    "/ don't do anything smart. If there's only single closing
+    "/ ']', then remeber it.
+    closingBracketIndex := 0.
+    line size > textView cursorCol ifTrue: [
+        line size downTo: textView cursorCol - 1 do:[:i |
+            (c :=line at:i) == Character space ifFalse:[
+                (c == $] and:[closingBracketIndex == 0]) ifTrue:[
+                    closingBracketIndex := i.
+                ] ifFalse:[
+                    ^ false
+                ].
+            ].
+        ]
+    ].
+
     (line indexOfAny:'[|/') == 0 ifTrue:[ ^ false ].
 
     "/ Insert "/ at the beggining of the line if current line starts with "/
@@ -217,17 +311,34 @@
     (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 insertElectric: #('' '') advanceCursorBy: (1 @ i).
-        self insertElectric: '"/ '.
+        self electricInsert:#( '' '' ) advanceCursorBy:(1 @ i).
+        self electricInsert:'"/ '.
         ^ true   
     ].
 
-    ('[|' includes: lastTypedKey1) ifFalse:[ ^ false ].
-    i := line size.
+    "/ Now insert/reindent closing bracket ( ']' ) for block, byt only
+    "/ if current preference is C-style blocks
+    RBFormatter cStyleBlocks ifFalse:[ ^ false ].
+    "/ There are two possible cases:
+    "/ (i)  there is no single closing bracket on the line, then
+    "/      add closing ] but only iff last typed character is
+    "/      either [ or |  !!!!!!!! Otherwise we would get annoying behaviour
+    "/      when there's already valid code and someone position cursor after
+    "/      opening bracket and press enter.
+    "/ (ii) there's single closing bracket on current line
+    "/      (closingBracketIndex is non-zero)
+    (closingBracketIndex == 0 and:[('[|' includes: lastTypedKey1) not]) ifTrue:[ ^ false ].
+
+    i := textView cursorCol - 1.
     [ (line at: i) isSeparator and:[i > 0] ] whileTrue:[ i := i - 1 ].
     i == 0 ifTrue:[ ^ false ].
     (line at: i) == $[ ifTrue:[
-        self insertElectricBlockOpenedBy: nil closedBy: '].'.
+        self electricDo:[
+            closingBracketIndex ~~ 0 ifTrue:[
+                self electricDeleteCharacterAtCol: closingBracketIndex
+            ].
+            self electricInsertBlockOpenedBy:nil closedBy:'].'.
+        ].
         ^ true
     ].
     tokens := self tokensAtCursorLine.
@@ -235,7 +346,12 @@
     i := tokens size.
     t := tokens at: i.
     t == $[ ifTrue:[
-        self insertElectricBlockOpenedBy: nil closedBy: '].'.
+        self electricDo:[
+            closingBracketIndex ~~ 0 ifTrue:[
+                self electricDeleteCharacterAtCol: closingBracketIndex
+            ].
+            self electricInsertBlockOpenedBy:nil closedBy:'].'.
+        ].
         ^ true
     ].
     t == $| ifTrue:[
@@ -243,14 +359,24 @@
         [ i > 1 and:[ (tokens at: i) == #Identifier and:[ (tokens at: i - 1) == $: ]] ] whileTrue:[ i := i - 2 ].
 
         (i ~~ 0 and: [(tokens at: i) == $[]) ifTrue:[
-            self insertElectricBlockOpenedBy: nil closedBy: '].'.
+            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 insertElectric:#('' '' '')  advanceCursorBy: 2 @ currentLineIndent.
+                self electricDo:[  
+                    closingBracketIndex ~~ 0 ifTrue:[
+                        self electricDeleteCharacterAtCol: closingBracketIndex
+                    ].
+                    self electricInsert:#( '' '' '' ) advanceCursorBy:2 @ currentLineIndent.
+                ].
                 ^ true
             ]
         ]
@@ -258,12 +384,12 @@
     ^ false.
 
     "Created: / 25-07-2013 / 00:02:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified (comment): / 19-11-2013 / 12:41:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 22-01-2014 / 21:44:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 keyPressReturnToken
     RBFormatter spaceAfterReturnToken ifTrue:[
-        self insertDo:[ 
+        self electricDo:[ 
             textView insertStringAtCursor:'^ ' 
         ].
         ^ true
@@ -271,7 +397,7 @@
     ^ false
 
     "Created: / 24-07-2013 / 23:59:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 17-09-2013 / 23:20:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 22-01-2014 / 21:10:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !SmalltalkEditSupport methodsFor:'initialization'!
@@ -287,9 +413,12 @@
 !SmalltalkEditSupport methodsFor:'private'!
 
 tokensAtCursorLine
-    | scanner token |
+    | line scanner token |
 
-    scanner := Scanner for: (service textView listAt: service textView cursorLine) string.
+    line := (service textView listAt: service textView cursorLine) string.
+    line := line copyTo: textView cursorCol - 1.  
+    line isEmpty ifTrue:[ ^ #() ].
+    scanner := Scanner for: line.
     ^ OrderedCollection streamContents:[:tokens |
         [ token := scanner nextToken.token ~~ #EOF ] whileTrue:[
             tokens nextPut: token.
@@ -297,6 +426,7 @@
     ].
 
     "Created: / 25-07-2013 / 00:07:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 22-01-2014 / 21:41:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !SmalltalkEditSupport class methodsFor:'documentation'!