collect cursor events for widget move;
authorClaus Gittinger <cg@exept.de>
Wed, 22 Sep 1999 10:56:01 +0200
changeset 1222 bcb8b0ec295c
parent 1221 473547d0dad1
child 1223 23a55549641a
collect cursor events for widget move; shift-cursor does fast move (by 10 pixels)
UIObjectView.st
--- a/UIObjectView.st	Tue Sep 21 20:28:08 1999 +0200
+++ b/UIObjectView.st	Wed Sep 22 10:56:01 1999 +0200
@@ -21,13 +21,6 @@
 	category:'Interface-UIPainter'
 !
 
-Object subclass:#ResizeData
-	instanceVariableNames:'object selector delta'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:UIObjectView
-!
-
 Object subclass:#UndoHistory
 	instanceVariableNames:'startIdentifier identifier painter history transaction enabled'
 	classVariableNames:''
@@ -42,6 +35,13 @@
 	privateIn:UIObjectView::UndoHistory
 !
 
+Object subclass:#ResizeData
+	instanceVariableNames:'object selector delta'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:UIObjectView
+!
+
 !UIObjectView class methodsFor:'documentation'!
 
 copyright
@@ -503,20 +503,41 @@
     "any key pressed
     "
     <resource: #keyboard ( #CursorUp #CursorDown #CursorLeft #CursorRight
-			   #Delete #BackSpace #Cut #Copy #Paste #Cmdu ) >
+                           #Delete #BackSpace #Cut #Copy #Paste #Cmdu ) >
+
+    |n sensor|
 
     (key == #Cut or:[key == #Delete or:[key == #BackSpace]]) ifTrue: [
-	^ self deleteSelection
+        ^ self deleteSelection
     ].
     key == #Copy  ifTrue:[ ^ self copySelection].
     key == #Paste ifTrue:[ ^ self pasteBuffer].
     key == #Cmdu  ifTrue:[ ^ self undoLast ].           "/ #Undo
 
-    key == #CursorUp ifTrue:[^self moveSelectionUp].
-    key == #CursorDown ifTrue:[^self moveSelectionDown].
-    key == #CursorRight ifTrue:[^self moveSelectionRight].
-    key == #CursorLeft ifTrue:[^self moveSelectionLeft].
-
+    ( #(CursorUp CursorDown CursorRight CursorLeft)
+    includes:key) ifTrue:[
+        (sensor := self sensor) isNil ifTrue:[
+            n := 1
+        ] ifFalse:[
+            n := 1 + (sensor compressKeyPressEventsWithKey:key).
+            sensor shiftDown ifTrue:[
+                n := n * 10.
+            ].
+        ].
+
+        key == #CursorUp ifTrue:[
+            ^ self moveSelectionUp:n
+        ].
+        key == #CursorDown ifTrue:[
+            ^ self moveSelectionDown:n
+        ].
+        key == #CursorRight ifTrue:[
+            ^ self moveSelectionRight:n
+        ].
+        key == #CursorLeft ifTrue:[
+            ^ self moveSelectionLeft:n
+        ].
+    ].
     super keyPress:key x:x y:y
 
     "Modified: / 6.3.1999 / 22:47:48 / cg"
@@ -1662,85 +1683,116 @@
 moveSelectionDown
     "move selection down
     "
+    self moveSelectionDown:1
+
+!
+
+moveSelectionDown:howMany
+    "move selection down
+    "
     |gridY n|
 
     gridAlign notNil ifTrue:[gridY := gridAlign y]
-		    ifFalse:[gridY := 1].
+                    ifFalse:[gridY := 1].
 
     self moveDo:[:aView|
-	aligning ifTrue:[
-	    n := ((aView computeCorner y) \\ gridY).
-
-	    n ~~ 0 ifTrue:[
-		n := gridY - n + 1.
-	    ] ifFalse:[
-		n := gridY
-	    ]
-	] ifFalse:[
-	    n := 1
-	].
-	self shiftLayout:aView top:n bottom:n
+        aligning ifTrue:[
+            n := ((aView computeCorner y) \\ gridY).
+
+            n ~~ 0 ifTrue:[
+                n := gridY - n + 1.
+            ] ifFalse:[
+                n := gridY
+            ]
+        ] ifFalse:[
+            n := 1
+        ].
+        n := n * howMany.
+        self shiftLayout:aView top:n bottom:n
     ]
 !
 
 moveSelectionLeft
     "move selection left
     "
+    self moveSelectionLeft:1
+
+!
+
+moveSelectionLeft:howMany
+    "move selection left
+    "
     |gridX n|
 
     gridAlign notNil ifTrue:[gridX := gridAlign x]
-		    ifFalse:[gridX := 1].
+                    ifFalse:[gridX := 1].
 
     self moveDo:[:aView|
-	aligning ifTrue:[
-	    n := ((aView computeOrigin x) \\ gridX).
-	    n == 0 ifTrue:[n := gridX].
-	    n := n negated.
-	] ifFalse:[
-	    n := -1
-	].
-	self shiftLayout:aView left:n right:n
+        aligning ifTrue:[
+            n := ((aView computeOrigin x) \\ gridX).
+            n == 0 ifTrue:[n := gridX].
+            n := n negated.
+        ] ifFalse:[
+            n := -1
+        ].
+        n := n * howMany.
+        self shiftLayout:aView left:n right:n
     ]
 !
 
 moveSelectionRight
     "move selection right
     "
+    self moveSelectionRight:1
+
+!
+
+moveSelectionRight:howMany
+    "move selection right
+    "
     |gridX n|
 
     gridAlign notNil ifTrue:[gridX := gridAlign x]
-		    ifFalse:[gridX := 1].
+                    ifFalse:[gridX := 1].
 
     self moveDo:[:aView|
-	aligning ifTrue:[
-	    n := ((aView computeCorner x) \\ gridX).
-
-	    n ~~ 0 ifTrue:[n := n negated]
-		  ifFalse:[n := gridX]
-	] ifFalse:[
-	    n := 1
-	].
-	self shiftLayout:aView left:n right:n
+        aligning ifTrue:[
+            n := ((aView computeCorner x) \\ gridX).
+
+            n ~~ 0 ifTrue:[n := n negated]
+                  ifFalse:[n := gridX]
+        ] ifFalse:[
+            n := 1
+        ].
+        n := n * howMany.
+        self shiftLayout:aView left:n right:n
     ]
 !
 
 moveSelectionUp
     "move selection up
     "
+    self moveSelectionUp:1
+!
+
+moveSelectionUp:howMany
+    "move selection up
+    "
     |gridY n|
 
     gridAlign notNil ifTrue:[gridY := gridAlign y]
-		    ifFalse:[gridY := 1].
+                    ifFalse:[gridY := 1].
 
     self moveDo:[:aView|
-	aligning ifTrue:[
-	    n := ((aView computeOrigin x) \\ gridY).
-	    n == 0 ifTrue:[n := gridY].
-	    n := n negated.
-	] ifFalse:[
-	    n := -1
-	].
-	self shiftLayout:aView top:n bottom:n
+        aligning ifTrue:[
+            n := ((aView computeOrigin x) \\ gridY).
+            n == 0 ifTrue:[n := gridY].
+            n := n negated.
+        ] ifFalse:[
+            n := -1
+        ].
+        n := n * howMany.
+        self shiftLayout:aView top:n bottom:n
     ]
 
 ! !
@@ -2231,34 +2283,6 @@
     ].
 ! !
 
-!UIObjectView::ResizeData methodsFor:'accessing'!
-
-delta
-    ^ delta
-
-    "Created: / 2.2.1998 / 13:40:32 / cg"
-!
-
-object
-    ^ object
-
-    "Created: / 2.2.1998 / 13:40:24 / cg"
-!
-
-object:anObject selector:aSymbol delta:anInteger
-    object := anObject.
-    selector := aSymbol.
-    delta := anInteger.
-
-    "Created: / 2.2.1998 / 13:39:22 / cg"
-!
-
-selector
-    ^ selector
-
-    "Created: / 2.2.1998 / 13:40:42 / cg"
-! !
-
 !UIObjectView::UndoHistory class methodsFor:'constants'!
 
 maxHistorySize
@@ -2597,6 +2621,34 @@
     ^ actions isNil
 ! !
 
+!UIObjectView::ResizeData methodsFor:'accessing'!
+
+delta
+    ^ delta
+
+    "Created: / 2.2.1998 / 13:40:32 / cg"
+!
+
+object
+    ^ object
+
+    "Created: / 2.2.1998 / 13:40:24 / cg"
+!
+
+object:anObject selector:aSymbol delta:anInteger
+    object := anObject.
+    selector := aSymbol.
+    delta := anInteger.
+
+    "Created: / 2.2.1998 / 13:39:22 / cg"
+!
+
+selector
+    ^ selector
+
+    "Created: / 2.2.1998 / 13:40:42 / cg"
+! !
+
 !UIObjectView class methodsFor:'documentation'!
 
 version