Merged 3f2f7a6d4fe6 and 172822a63cff
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 24 Jun 2014 15:09:53 +0100
changeset 350 762fdff80221
parent 349 3f2f7a6d4fe6 (current diff)
parent 245 172822a63cff (diff)
child 351 8cd1a9df1bf6
Merged 3f2f7a6d4fe6 and 172822a63cff
SmallSense__SmalltalkEditSupport.st
--- a/SmallSense__AbstractJavaCompletionEngineSimple.st	Mon Jun 23 15:27:14 2014 +0100
+++ b/SmallSense__AbstractJavaCompletionEngineSimple.st	Tue Jun 24 15:09:53 2014 +0100
@@ -252,6 +252,7 @@
                     self completeMethodOrFieldIn: tokens before: caretI.
                 ] ifFalse:[ 
                     "/ Else try to complete field.
+                    self completeSnippetsStartingWith: last value.
                     self completeLocalOrFieldIn: tokens before: caretI.
                 ].
             ].
@@ -264,7 +265,7 @@
     ^ result
 
     "Created: / 02-10-2013 / 13:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 19-05-2014 / 13:07:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 24-06-2014 / 11:13:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 completeImport: match
--- a/SmallSense__CompletionController.st	Mon Jun 23 15:27:14 2014 +0100
+++ b/SmallSense__CompletionController.st	Tue Jun 24 15:09:53 2014 +0100
@@ -239,13 +239,14 @@
         list notEmptyOrNil ifTrue:[ 
             first := list first.
             (completionView list allSatisfy:[:e | e class == first class ]) ifTrue:[ 
-                first stringAlreadyWritten 
+                ^ first stringAlreadyWritten 
             ]
         ]
     ].
     ^ support wordBeforeCursor string .
 
     "Created: / 18-05-2014 / 13:55:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 24-06-2014 / 11:40:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 stopCompletionProcess
@@ -300,7 +301,6 @@
     keyOrNil isCharacter ifTrue:[ 
         prefix := prefix , keyOrNil
     ].
-
     matches1 := list select:[:po | matcher1 value: prefix value: po stringToComplete ].
     matches1 notEmptyOrNil ifTrue:[
         matches1 size == 1 ifTrue:[
@@ -342,6 +342,7 @@
     ^ false.
 
     "Created: / 17-06-2014 / 07:19:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 24-06-2014 / 11:41:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !CompletionController methodsFor:'private-API'!
--- a/SmallSense__JavaConstructorPO.st	Mon Jun 23 15:27:14 2014 +0100
+++ b/SmallSense__JavaConstructorPO.st	Tue Jun 24 15:09:53 2014 +0100
@@ -9,8 +9,15 @@
 	category:'SmallSense-Java-Interface-PO'
 !
 
+
 !JavaConstructorPO methodsFor:'accessing'!
 
+hint
+    ^ (classes collect:[:each | each javaPackage ]) asArray asStringWith:' , '.
+
+    "Created: / 24-06-2014 / 11:04:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 label
     label isNil ifTrue:[
 	label := (classes anElement compiledMethodAt: selector) printStringForBrowserWithSelector: selector.
@@ -54,3 +61,11 @@
 
     "Created: / 15-05-2014 / 12:07:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
+
+!JavaConstructorPO class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/SmallSense__SmalltalkEditSupport.st	Mon Jun 23 15:27:14 2014 +0100
+++ b/SmallSense__SmalltalkEditSupport.st	Tue Jun 24 15:09:53 2014 +0100
@@ -17,11 +17,11 @@
         | in |
 
         in := text readStream.
-        [ in atEnd ] whileFalse:[ 
-            in peek == Character cr ifTrue:[ 
+        [ in atEnd ] whileFalse:[
+            in peek == Character cr ifTrue:[
                 out nextPut: in next.
                 out next: level put: Character space.
-            ] ifFalse:[ 
+            ] ifFalse:[
                 out nextPut: in next.
             ].
         ].
@@ -40,11 +40,11 @@
 
         line := lines at: lineNo.
         i := line indexOfNonSeparator.
-        indent isNil ifTrue:[ 
-            (i ~~ 0) ifTrue:[ 
+        indent isNil ifTrue:[
+            (i ~~ 0) ifTrue:[
                 indent := ((i - 1) // tabwidth) * tabwidth.
-                indent == 0 ifTrue:[ 
-                    lineNo == 1 ifTrue:[ 
+                indent == 0 ifTrue:[
+                    lineNo == 1 ifTrue:[
                         indent := nil.
                     ] ifFalse:[
                         ^ text.
@@ -52,17 +52,17 @@
                 ].
             ].
         ].
-        indent notNil ifTrue:[ 
+        indent notNil ifTrue:[
             i > indent ifTrue:[
                 lines at: lineNo put: (line copyFrom: indent + 1).
-            ] ifFalse:[ 
+            ] ifFalse:[
                 ^ text.
             ].
         ].
     ].
     ^ (text last == Character cr) ifTrue:[
         lines asString.
-    ] ifFalse:[ 
+    ] ifFalse:[
         lines asStringWithoutFinalCR
     ].
 
@@ -98,13 +98,13 @@
 
 !SmalltalkEditSupport methodsFor:'editing'!
 
-electricInsert:stringOrLines advanceCursorBy:offsetOrNil 
+electricInsert:stringOrLines advanceCursorBy:offsetOrNil
     | ignore |
 
     (stringOrLines isString and:[ stringOrLines first == lastTypedKey0 ]) ifTrue:[
         ignore := stringOrLines copyFrom:2.
     ].
-    ^ self 
+    ^ self
             electricInsert:stringOrLines
             advanceCursorBy:offsetOrNil
             ignoreKeystrokes:ignore
@@ -138,13 +138,13 @@
     (tokens last > service textView cursorCol) ifTrue:[
         ^ false
     ].
-    ((lastToken0 == #Identifier) 
-        and:[ (service textView cursorCol - 1) == tokens last ]) 
+    ((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) 
+                    (#( #do #select #reject #detect #contains #allSatisfy #anySatisfy )
+                        includes:lastValue0)
                             ifTrue:[
                                 | collectionName  eachName  space  part1  part2 |
 
@@ -195,14 +195,14 @@
     lastToken0 == #Keyword ifTrue:[
         lastValue0 := tokens at:tokens size - 2.
         tokens size > 4 ifTrue:[
-            (#( #do: #select: #reject: #detect: #contains: #allSatisfy: #anySatisfy: ) 
-                includes:lastValue0) 
+            (#( #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 := tokens at:tokens size - 6) last = $s) ifTrue:[
                                 (collectionName endsWith:'ses') ifTrue:[
                                     eachName := collectionName copyButLast:2
                                 ] ifFalse:[
@@ -220,7 +220,7 @@
     ^ false.
 
     "Created: / 22-10-2013 / 03:00:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 22-10-2013 / 12:00:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 23-05-2014 / 11:28:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !SmalltalkEditSupport methodsFor:'event handling'!
@@ -235,13 +235,22 @@
 
     (self keyPressIgnored: key) ifTrue:[
         ^ true.
-    ]. 
+    ].
 
     lastTypedKey3 := lastTypedKey2.
     lastTypedKey2 := lastTypedKey1.
     lastTypedKey1 := lastTypedKey0.
     lastTypedKey0 := key.
 
+    key == #CodeCompletion ifTrue:[
+        | controller |
+
+        (controller := self textView completionSupport) notNil ifTrue:[
+            ^ controller handleKeyPress:key x:x y:y
+        ].
+        ^ false
+    ].
+
     key == #BackSpace ifTrue:[
         backspaceIsUndo ifTrue:[
              textView undo.
@@ -251,7 +260,7 @@
     ].
     backspaceIsUndo := false.
 
-    key == #Paste ifTrue:[ 
+    key == #Paste ifTrue:[
         ^ self keyPressPaste.
     ].
 
@@ -282,7 +291,7 @@
     ^ false.
 
     "Created: / 07-03-2010 / 09:36:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 03-05-2014 / 01:08:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 18-05-2014 / 12:45:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 keyPressDoubleColon
@@ -300,7 +309,7 @@
     line size > textView cursorCol ifTrue: [ ^ false ].
     line size < (textView cursorCol - 1) ifTrue: [ ^ false ].
     (line at: textView cursorCol - 1) == $: ifTrue: [
-        self electricInsert:'= '.  
+        self electricInsert:'= '.
         ^ true
     ].
     ^ false
@@ -315,8 +324,8 @@
     | line |
 
     line := textView listAt: textView cursorLine.
-    line notNil ifTrue:[ 
-        line := line string.  
+    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 ].
@@ -344,28 +353,32 @@
 !
 
 keyPressPaste
-    | textSelected textPasted currentLineNo currentLine |
+    | textSelected textPasted currentLineNo currentLine currentLineIsEmpty |
 
     textView checkModificationsAllowed ifTrue:[
         textSelected := textPasted := textView getTextSelectionOrTextSelectionFromHistory.
         currentLineNo := textView currentLine.
+        currentLineIsEmpty := true.
         ((currentLineNo > textView list size)
-            or:[ (currentLine := textView list at: currentLineNo) isNil 
-                or:[ currentLine indexOfNonSeparator == 0 ]]) ifTrue:[ 
+            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.
+
                 ].
+
         textView undoablePasteOrReplace: textPasted info: nil.
     ].
-
-    
-
-
-
     ^ true
 
     "Created: / 03-05-2014 / 01:08:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified (format): / 04-05-2014 / 23:48:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 23-06-2014 / 20:37:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 keyPressReturn
@@ -401,7 +414,7 @@
         "/ two actions so backspace deletes only the inserted '"/ ' text
         self electricInsert:#( '' '' ) advanceCursorBy:(1 @ i).
         self electricInsert:'"/ '.
-        ^ true   
+        ^ true
     ].
 
     "/ Now insert/reindent closing bracket ( ']' ) for block, byt only
@@ -447,7 +460,7 @@
         [ 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:[  
+            self electricDo:[
                 closingBracketIndex ~~ 0 ifTrue:[
                     self electricDeleteCharacterAtCol: closingBracketIndex
                 ].
@@ -459,7 +472,7 @@
         [ i > 0 and:[ (tokens at: i) == #Identifier ] ] whileTrue:[ i := i - 1 ].
         (i ~~ 0 and: [(tokens at: i) == $|]) ifTrue:[
             RBFormatter emptyLineAfterTemporaries ifTrue:[
-                self electricDo:[  
+                self electricDo:[
                     closingBracketIndex ~~ 0 ifTrue:[
                         self electricDeleteCharacterAtCol: closingBracketIndex
                     ].
@@ -477,8 +490,8 @@
 
 keyPressReturnToken
     RBFormatter spaceAfterReturnToken ifTrue:[
-        self electricDo:[ 
-            textView insertStringAtCursor:'^ ' 
+        self electricDo:[
+            textView insertStringAtCursor:'^ '
         ].
         ^ true
     ].
@@ -490,7 +503,7 @@
 
 !SmalltalkEditSupport methodsFor:'initialization'!
 
-initializeForService: anEditService    
+initializeForService: anEditService
     super initializeForService: anEditService.
     service textView autoIndent:true.
 
@@ -504,7 +517,7 @@
     | line scanner token |
 
     line := (service textView listAt: service textView cursorLine) string.
-    line := line copyTo: textView cursorCol - 1.  
+    line := line copyTo: textView cursorCol - 1.
     line isEmpty ifTrue:[ ^ #() ].
     scanner := Scanner for: line.
     ^ OrderedCollection streamContents:[:tokens |