added comments & docu, examples.
authorClaus Gittinger <cg@exept.de>
Sat, 19 Apr 1997 17:22:38 +0200
changeset 548 1a81d6be65b4
parent 547 7764165d89b8
child 549 51c6f1d918c2
added comments & docu, examples. grab the pointer while dragging, to suppress any pointerEnter/leave events to be delivered to other views in the meanwhile
DragAndDropManager.st
--- a/DragAndDropManager.st	Sat Apr 19 17:21:04 1997 +0200
+++ b/DragAndDropManager.st	Sat Apr 19 17:22:38 1997 +0200
@@ -1,13 +1,27 @@
+"
+ COPYRIGHT (c) 1996 by eXept Software AG / Claus Gittinger
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+
 Object subclass:#DragAndDropManager
 	instanceVariableNames:'dragView motionAction releaseAction initialPoint previousPoint
 		rememberedDelegate dragBlock lineMode dropAction opaque saveUnder
-		dragSize dragOffset dropObjects saveCursor lastView'
+		dragSize dragOffset dropObjects saveCursor lastView
+		lastScreenPosition'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Interface-Support'
 !
 
-View subclass:#DemoView2
+View subclass:#DemoView
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -21,7 +35,7 @@
 	privateIn:DragAndDropManager
 !
 
-View subclass:#DemoView
+View subclass:#DemoView2
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -30,30 +44,226 @@
 
 !DragAndDropManager class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 1996 by eXept Software AG / Claus Gittinger
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+!
+
 documentation
 "
     this class provides low-level drag & drop mechanisms.
 
+    Easy to use interface interfaces:
+
+    A drag is usually initiated by a view or its application model,
+    when a selection is moved (for example, SelectionInListView can
+    be initializd to do so). 
+    There, the view creates a collection of dropObjects from its selection,
+    and starts the drag operation with:
+
+        DragAndDropManager startDrag:collectionOfDragObjects from:aView.
+
+    This easy to use interface starts a drag and also drops the collection
+    into the target view.
+    While dragging, a thumbsUp cursor is shown, if the view-under-the-drag
+    can handle a drop, a thumbsDown is shown if not, and a question mark
+    is shown for alien views (which means: we dont know).
+    Alien view drop is supported (but no 'canDrop' query).
+
+    For rubber-band line dragging, two more easy-to-use startup methods are
+    provided:
+
+        DragAndDropManager
+                startLineDragIn:aView at:position
+                atEnd:aFourArgEndBlock
+
+    and:
+        DragAndDropManager
+                startArrowDragIn:aView at:position
+                atEnd:aFourArgEndBlock
+
+    both of the above expect a 4-arg block to be passed, which will be
+    evaluated at end-drag, with the target view, its viewID, the drop position
+    on the screen and within the target view as arguments.
+
+
+    Expert interface:
+
+    More control over the dragging (i.e. the drawing procedure)
+    can be optained, by passing a dragBlock and an endDrag action:
+        
+        aDragAndDropMgr := DragAndDropManager new.
+        aDragAndDropMgr dropObjects:(self collectionOfDragObjects).
+        aDragAndDropMgr 
+            startOpaqueDrag:[:aPoint :aView :dropObjects | 
+                                self 
+                                    showDragging:dropObjects
+                                    in:aView 
+                                    at:aPoint - (xOffset@0)
+                            ]
+            offset:clickOffset
+            extent:saveUnderExtent
+            in:self
+            at:clickPoint
+            atEnd:[:v :vId :posScreen :posView | ... ]
+
+    the arguments are:
+      startOpaqueDrag:
+        a 3-arg block, which is evaluated by the d&d manager whenever the
+        mouse moves; it is supposed to draw the dropObjects at some position
+        in the passed view.
+
+      offset:
+        a clickOffset; drawing is offset by this amount
+
+      extent:  
+        a save extent; the size of the screen area that must be saved during
+        the drag operation
+
+      in:
+        initiating view
+
+      at:
+        position where d&d operation starts
+
+      atEnd:
+        a 4-arg block that is evaluated when the d&d is finished.
+        It gets the target view (or nil, for alien views), the targets
+        view ID (needed if its an alien view), the screen position and the
+        relative position within the target view of the drop as arguments.
+
+        For internal (ST/X) views, the dropBlock should perform
+        a simple canDrop:/doDrop message.
+
+        For alien views, the Displays d&d functions can be used.
+
+
     [author:]
         Claus Gittinger
+
+    [see also:]
+        DemoView DemoView2 DemoView3 - examples
+        SelectionInListView FileBrowser - for a concrete example
+
 "
 
 !
 
-history
+examples
+"
+  a button, which initiates dragging of a file-object
+  Notice that this can be dropped into the launchers panel,
+  to open a fileBrowser on that file ...
+                                                                [exBegin]
+     |o top v|
+
+     top := StandardSystemView new.
+     v := Button label:'press for drag' in:top.
+     v pressAction:[
+                |o|
+                o := DropObject newFile:('/etc').
+                DragAndDropManager startDrag:o from:v.
+                v turnOff
+              ].
+     top openWithExtent:200@200
+                                                                [exEnd]
+
+  initiate a drag with some offset:
+                                                                [exBegin]
+     |o top v|
 
-    "Created: 26.10.1996 / 15:02:00 / cg"
-    "Modified: 26.10.1996 / 15:21:42 / cg"
+     top := StandardSystemView new.
+     v := Button label:'press for drag' in:top.
+     v pressAction:[
+                |o|
+                o := DropObject newFile:('.').
+                DragAndDropManager startDrag:o from:v offset:10@10.
+                v turnOff
+              ].
+     top openWithExtent:200@200
+                                                                [exEnd]
+
+  initiate a line drag:
+                                                                [exBegin]
+     |o top v endAction|
+
+     endAction := [ :v :vID :sPos :vPos |
+                    Transcript show:'end drag in '.
+                    v isNil ifTrue:[
+                        Transcript show:'alien view'
+                    ] ifFalse:[
+                        Transcript show:v
+                    ].
+                    Transcript show:' at screen: '; show:sPos;
+                               show:' in view: '; showCR:vPos
+                ].
+     top := StandardSystemView new.
+     v := Button label:'press for drag' in:top.
+     v pressAction:[
+                DragAndDropManager 
+                    startLineDragIn:v at:10@10 atEnd:endAction.
+                v turnOff
+              ].
+     top openWithExtent:200@200
+                                                                [exEnd]
+
+"
+
 ! !
 
 !DragAndDropManager class methodsFor:'simple start'!
 
+startArrowDragIn:aView at:dragPoint atEnd:aFourArgBlock
+    "start a rubber-arrow-line dragging in aView at dragPoint.
+     When finished, evaluate the fourArgBlock with targetView,
+     targetID, screenPosition and targetViewPosition as arguments"
+
+    ^ self new
+        startArrowDragIn:aView at:dragPoint atEnd:aFourArgBlock
+
+    "
+     |o v|
+
+     v := Button label:'press me'.
+     v pressAction:[
+                |o|
+                o := DropObject newFile:('.').
+                v turnOff; repairDamage.
+                DragAndDropManager 
+                    startArrowDragIn:v 
+                    at:0@0 
+                    atEnd:[:v :vID :sPos :vPos |
+                                v isNil ifTrue:[
+                                    Transcript show:'alien view'
+                                ] ifFalse:[
+                                    Transcript show:'view: ';
+                                               show:v
+                                ].
+                                Transcript show:' screen: '; show:sPos;
+                                           show:' inView: '; showCR:vPos.
+                          ].
+              ].
+     v openAt:100@100
+    "
+
+    "Modified: 19.4.1997 / 12:04:08 / cg"
+!
+
 startDrag:anObjectOrCollection from:aView
     "start a drop at the current pointer position"
 
     (self new) startDrag:anObjectOrCollection from:aView offset:0@0
 
-
     "
      |o v|
 
@@ -67,6 +277,7 @@
      v openAt:100@100
     "
 
+    "Modified: 19.4.1997 / 11:42:40 / cg"
 !
 
 startDrag:anObjectOrCollection from:aView offset:offset
@@ -74,7 +285,6 @@
 
     (self new) startDrag:anObjectOrCollection from:aView offset:offset
 
-
     "
      |o v|
 
@@ -88,21 +298,65 @@
      v openAt:100@100
     "
 
+    "Modified: 19.4.1997 / 11:42:45 / cg"
+!
+
+startLineDragIn:aView at:dragPoint atEnd:aFourArgBlock
+    "start a rubber-line dragging in aView at dragPoint.
+     When finished, evaluate the fourArgBlock with targetView,
+     targetID, screenPosition and targetViewPosition as arguments"
+
+    ^ self new
+        startLineDragIn:aView at:dragPoint atEnd:aFourArgBlock
+
+    "
+     |o v|
+
+     v := (Button label:'press me').
+     v pressAction:[
+                |o|
+                o := DropObject newFile:('.').
+                v turnOff; repairDamage.
+                DragAndDropManager 
+                    startLineDragIn:v 
+                    at:0@0 
+                    atEnd:[:v :vID :sPos :vPos |
+                                v isNil ifTrue:[
+                                    Transcript show:'alien view'
+                                ] ifFalse:[
+                                    Transcript show:'view: ';
+                                               show:v
+                                ].
+                                Transcript show:' screen: '; show:sPos;
+                                           show:' inView: '; showCR:vPos.
+                          ].
+              ].
+     v openAt:100@100
+    "
+
+    "Modified: 19.4.1997 / 12:02:02 / cg"
 ! !
 
 !DragAndDropManager methodsFor:'accessing'!
 
 dropObjects
+    "return the current dropObject collection"
+
     ^ dropObjects
+
+    "Modified: 19.4.1997 / 10:19:06 / cg"
 !
 
-dropObjects:anObjectOrCollection
+dropObjects:aCollectionOfDropObjects
+    "set the current dropObject collection"
 
-    anObjectOrCollection isCollection ifTrue:[
-        dropObjects := anObjectOrCollection
+    aCollectionOfDropObjects isCollection ifTrue:[
+        dropObjects := aCollectionOfDropObjects
     ] ifFalse:[
-        dropObjects := Array with:anObjectOrCollection
+        dropObjects := Array with:aCollectionOfDropObjects
     ].
+
+    "Modified: 19.4.1997 / 10:19:33 / cg"
 ! !
 
 !DragAndDropManager methodsFor:'dragging - generic'!
@@ -114,13 +368,14 @@
     |view newCursor|
 
     previousPoint notNil ifTrue:[
-        opaque ifTrue:[
+        (opaque and:[dragSize notNil]) ifTrue:[
             self restoreGenericAt:previousPoint
         ] ifFalse:[
             self invertGenericAt:previousPoint
         ]
     ].
     previousPoint := x @ y.
+    lastScreenPosition := nil.
 
     view := self destinationViewAt:previousPoint.
     view ~~ lastView ifTrue:[
@@ -139,60 +394,21 @@
         lastView := view
     ].
 
-    opaque ifTrue:[
+    (opaque and:[dragSize notNil]) ifTrue:[
         self drawGenericAt:previousPoint.
     ] ifFalse:[
         self invertGenericAt:previousPoint
     ].
 
-    "Modified: 6.4.1997 / 14:29:44 / cg"
-!
-
-drawGenericAt:ip
-    |t offs p rootView|
-
-    rootView := dragView device rootView.
-
-    p := ip.
-
-    "
-     get device coordinates
-    "
-    (t := dragView transformation) notNil ifTrue:[
-        p := t applyTo:p.
-    ].
-
-    "
-     translate to screen
-    "
-    offs := dragView device 
-                translatePoint:0@0 
-                from:(dragView id) to:(rootView id).
-    p := p + offs.
-
-    rootView clippedByChildren:false.
-    saveUnder isNil ifTrue:[
-        saveUnder := Form width:dragSize x height:dragSize y depth:rootView device depth on:dragView device.
-        saveUnder clippedByChildren:false.
-    ].
-    saveUnder 
-        copyFrom:rootView 
-        x:p x - dragOffset x 
-        y:p y - dragOffset y
-        toX:0 
-        y:0 
-        width:dragSize x 
-        height:dragSize y.
-
-    rootView lineWidth:0. 
-    dragBlock value:p value:rootView.
-    rootView flush
-
+    "Modified: 19.4.1997 / 11:33:54 / cg"
 !
 
 endGenericDragX:x y:y
+    "finish a drag; restore from saveUnder (or reinvert),
+     then call for the endAction"
+
     previousPoint notNil ifTrue:[
-        opaque ifTrue:[
+        (opaque and:[dragSize notNil]) ifTrue:[
             self restoreGenericAt:previousPoint
         ] ifFalse:[
             self invertGenericAt:previousPoint
@@ -203,81 +419,13 @@
     self endDragAt:x @ y
 
     "Created: 26.10.1996 / 15:17:20 / cg"
-    "Modified: 26.10.1996 / 15:22:41 / cg"
-
-!
-
-invertGenericAt:ip
-    |t offs p rootView|
-
-    rootView := dragView device rootView.
-
-    p := ip.
-
-    "
-     get device coordinates
-    "
-    (t := dragView transformation) notNil ifTrue:[
-        p := t applyTo:p.
-    ].
-
-    "
-     translate to screen
-    "
-    offs := dragView device 
-                translatePoint:0@0 
-                from:(dragView id) to:(rootView id).
-    p := p + offs.
-
-    rootView clippedByChildren:false.
-    rootView xoring:[
-        rootView lineWidth:0. 
-        dragBlock value:p value:rootView.
-        rootView flush
-    ].
-
-    "Created: 26.10.1996 / 15:15:26 / cg"
-    "Modified: 26.10.1996 / 15:27:09 / cg"
-
-!
-
-restoreGenericAt:ip
-    |t offs p rootView|
-
-
-    rootView := dragView device rootView.
-    p := ip.
-
-    "
-     get device coordinates
-    "
-    (t := dragView transformation) notNil ifTrue:[
-        p := t applyTo:p.
-    ].
-
-    "
-     translate to screen
-    "
-    offs := dragView device 
-                translatePoint:0@0 
-                from:(dragView id) to:(rootView id).
-    p := p + offs.
-
-    rootView clippedByChildren:false.
-    rootView 
-        copyFrom:saveUnder 
-        x:0 
-        y:0 
-        toX:p x - dragOffset x
-        y:p y - dragOffset y
-        width:dragSize x 
-        height:dragSize y.
-
-
+    "Modified: 19.4.1997 / 10:41:57 / cg"
 !
 
 startGenericDrag:aTwoArgDragBlock in:aView at:p atEnd:aFourArgEndBlock
     "start a generic (caller-provided drag);
+     Here, an inverting drag is initiated (i.e. the drawing is undone
+     by inverting again). See startOpaqueDrag for another variant.
      the dragBlock, aTwoArgDragBlock will be called with two args
      aPoint and a drawingGC, to perform the drawing at some dragPoint.
      The drag starts in aView at point p.
@@ -293,9 +441,8 @@
     dragBlock := aTwoArgDragBlock.
     dropAction := aFourArgEndBlock.
 
-    "Modified: 26.10.1996 / 15:09:26 / cg"
     "Created: 26.10.1996 / 15:16:13 / cg"
-
+    "Modified: 19.4.1997 / 10:44:32 / cg"
 !
 
 startOpaqueDrag:aTwoArgDragBlock offset:offs extent:ext in:aView at:p atEnd:aFourArgEndBlock
@@ -326,34 +473,165 @@
 
 ! !
 
+!DragAndDropManager methodsFor:'dragging - generic - inverting'!
+
+invertGenericAt:ip
+    "draw for a generic inverting drag"
+
+    |t offs p rootView|
+
+    rootView := dragView device rootView.
+
+    (p := lastScreenPosition) isNil ifTrue:[
+        p := ip.
+
+        "
+         get device coordinates
+        "
+        (t := dragView transformation) notNil ifTrue:[
+            p := t applyTo:p.
+        ].
+
+        "
+         translate to screen
+        "
+        offs := dragView device 
+                    translatePoint:0@0 
+                    from:(dragView id) to:(rootView id).
+        p := p + offs.
+
+        lastScreenPosition := p.
+    ].
+
+    rootView clippedByChildren:false.
+    rootView xoring:[
+        rootView lineWidth:0. 
+        self callForDragActionAt:p in:rootView.
+        rootView flush
+    ].
+
+    "Created: 26.10.1996 / 15:15:26 / cg"
+    "Modified: 19.4.1997 / 11:35:33 / cg"
+! !
+
+!DragAndDropManager methodsFor:'dragging - generic - opaque'!
+
+drawGenericAt:ip
+    "draw for a generic opaque drag"
+
+    |t offs p rootView szX szY|
+
+    rootView := dragView device rootView.
+
+    p := ip.
+
+    "/
+    "/ get device coordinates
+    "/
+    (t := dragView transformation) notNil ifTrue:[
+        p := t applyTo:p.
+    ].
+
+    "/
+    "/ translate to screen
+    "/
+    offs := dragView device 
+                translatePoint:0@0 
+                from:(dragView id) to:(rootView id).
+    p := p + offs.
+
+    rootView clippedByChildren:false.
+
+    "/
+    "/ copy from screen to saveUnder
+    "/
+    szX := dragSize x.
+    szY := dragSize y.
+    saveUnder isNil ifTrue:[
+        saveUnder := Form 
+                            width:szX 
+                            height:szY 
+                            depth:rootView device depth 
+                            on:dragView device.
+        saveUnder clippedByChildren:false.
+    ].
+
+    lastScreenPosition := p - dragOffset.
+    saveUnder 
+        copyFrom:rootView 
+        x:lastScreenPosition x 
+        y:lastScreenPosition y
+        toX:0 
+        y:0 
+        width:szX 
+        height:szY.
+
+    "/
+    "/ draw using the dragAction block
+    "/
+    rootView lineWidth:0. 
+    self callForDragActionAt:p in:rootView.
+    rootView flush
+
+    "Modified: 19.4.1997 / 10:45:48 / cg"
+!
+
+restoreGenericAt:ip
+    "restore from saveUnder for a generic opaque drag"
+
+    |rootView|
+
+    rootView := dragView device rootView.
+
+    "/
+    "/ copy from saveUnder back to screen
+    "/
+    rootView clippedByChildren:false.
+    rootView 
+        copyFrom:saveUnder 
+        x:0 y:0 
+        toX:lastScreenPosition x y:lastScreenPosition y
+        width:dragSize x 
+        height:dragSize y.
+
+    "Modified: 19.4.1997 / 10:46:39 / cg"
+! !
+
 !DragAndDropManager methodsFor:'dragging - lines'!
 
 doLineDragX:x y:y
+    "do a line drag - invert previous and draw at new position"
+
     previousPoint notNil ifTrue:[
         self invertLineFrom:initialPoint to:previousPoint
     ].
     previousPoint := x @ y.
     self invertLineFrom:initialPoint to:previousPoint
 
-    "Modified: 26.10.1996 / 15:16:59 / cg"
-
-
+    "Modified: 19.4.1997 / 12:39:43 / cg"
 !
 
 endLineDragX:x y:y
+    "end a line drag - invert previous, deinstall event catcher 
+     and call for endDrag action"
+
     previousPoint notNil ifTrue:[
         self invertLineFrom:initialPoint to:previousPoint
     ].
+
     previousPoint := nil.
+    dragView device sync.
+
     self uncatchEvents.
-    self endDragAt:x @ y
+    self endDragAt:x @ y.
 
     "Created: 26.10.1996 / 15:17:20 / cg"
-    "Modified: 26.10.1996 / 15:22:41 / cg"
-
+    "Modified: 19.4.1997 / 12:40:14 / cg"
 !
 
 invertLineFrom:ip1 to:ip2
+    "invert for a line drag"
+
     |t offs p1 p2 rootView a|
 
     rootView := dragView device rootView.
@@ -392,8 +670,7 @@
     ].
 
     "Created: 26.10.1996 / 15:15:26 / cg"
-    "Modified: 26.10.1996 / 15:27:09 / cg"
-
+    "Modified: 19.4.1997 / 12:40:29 / cg"
 !
 
 startArrowDragIn:aView at:p atEnd:aBlock
@@ -441,22 +718,48 @@
 !DragAndDropManager methodsFor:'drawing'!
 
 showDragging:items in:aView at:p
+    "helper for dragging dragObjects: draw them all"
+
     |offs|
 
-    items size > 1 ifTrue:[
-        offs := 0.
-        items do:[:item |
-            item displayOn:aView at:p + (0@offs).
-            offs := offs + (item heightOn:self)
-        ]
-    ] ifFalse:[
-        items first displayOn:aView at:p.
+    offs := 0.
+    items do:[:item |
+        item displayOn:aView at:p + (0@offs).
+        offs := offs + (item heightOn:self)
     ]
 
-    "Created: 14.11.1996 / 15:31:31 / cg"
-    "Modified: 14.11.1996 / 16:32:00 / cg"
+    "Modified: 19.4.1997 / 12:41:24 / cg"
+! !
+
+!DragAndDropManager methodsFor:'dropping'!
+
+drop:something in:targetView at:aPoint from:sourceView ifOk:okAction ifFail:failAction
+    "try to drop some object in a targetView;
+     if any view along the targetViews superView chain takes it, 
+     the okAction is evaluated; if not, failAction is evaluated.
+     This may be sent from a drag initiators endDrag block."
+
+    |v pnt|
+
+    v := targetView.
+    pnt := aPoint.
 
+    [v notNil] whileTrue:[
+        (v canDrop:something) ifTrue:[
+            v 
+                drop:something 
+                at:aPoint 
+                from:sourceView 
+                with:[:o | okAction. ^ true]
+                ifFail:[:o | failAction. ^ false].
+        ].
+        v := v superView.
+        pnt := nil
+    ].
+    failAction value.
+    ^ false
 
+    "Modified: 19.4.1997 / 12:42:36 / cg"
 ! !
 
 !DragAndDropManager methodsFor:'easy drag & drop'!
@@ -496,38 +799,9 @@
 !
 
 buttonRelease:button x:x y:y view:aView
-    self perform:releaseAction with:x with:y
-
-    "Created: 26.10.1996 / 15:09:14 / cg"
-
-!
-
-drop:something in:targetView at:aPoint from:sourceView ifOk:okAction ifFail:failAction
-    "try to drop some object in a targetView;
-     if any view along the targetViews superView chain takes it, 
-     the okAction is evaluated; if not, failAction is evaluated."
-
-    |v pnt|
-
-    v := targetView.
-    pnt := aPoint.
+    self perform:releaseAction with:x with:y.
 
-    [v notNil] whileTrue:[
-        (v canDrop:something) ifTrue:[
-            v 
-                drop:something 
-                at:aPoint 
-                from:sourceView 
-                with:[:o | okAction. ^ true]
-                ifFail:[:o | failAction. ^ false].
-        ].
-        v := v superView.
-        pnt := nil
-    ].
-    failAction value.
-    ^ false
-
-    "Modified: 4.4.1997 / 18:25:18 / cg"
+    "Modified: 19.4.1997 / 12:37:02 / cg"
 !
 
 handlesButtonMotion:button inView:aView
@@ -552,17 +826,37 @@
 
 !DragAndDropManager methodsFor:'private'!
 
+callForDragActionAt:aPoint in:aView
+    "evaluate the user supplied dragAction.
+     Look how many args it expects and invoke with
+        position
+        dragView
+        dragObjects"
+
+    |numArgs|
+
+    (numArgs := dragBlock numArgs) == 1 ifTrue:[
+        dragBlock value:aPoint
+    ] ifFalse:[
+        numArgs == 2 ifTrue:[
+            dragBlock value:aPoint value:aView
+        ] ifFalse:[
+            dragBlock value:aPoint value:aView value:dropObjects.
+        ]
+    ]
+
+    "Created: 19.4.1997 / 10:05:55 / cg"
+!
+
 catchEventsFrom:aView
     dragView   := aView.
     saveCursor := dragView cursor.
 
     rememberedDelegate := aView delegate.
     aView delegate:self.
+    aView device grabPointerInView:aView.
 
-    "Created: 26.10.1996 / 15:03:12 / cg"
-    "Modified: 26.10.1996 / 15:21:57 / cg"
-
-
+    "Modified: 19.4.1997 / 12:36:04 / cg"
 !
 
 destinationViewAt:ip
@@ -598,11 +892,12 @@
 !
 
 endDragAt:ip
-    |rootPoint t viewId offs destinationId lastViewId destinationView
+    |rootPoint t rootId viewId offs destinationId lastViewId destinationView
      rootView destinationPoint device|
 
     dragView cursor:saveCursor now:true.
     device := dragView device.
+    device ungrabPointer.
     rootView := device rootView.
     rootPoint := ip.
 
@@ -612,12 +907,12 @@
     (t := dragView transformation) notNil ifTrue:[
         rootPoint := t applyTo:ip.
     ].
-    viewId := rootView id.
+    viewId := rootId := rootView id.
 
     "
      translate to screen
     "
-    offs := device translatePoint:0@0 from:(dragView id) to:viewId.
+    offs := device translatePoint:0@0 from:(dragView id) to:rootId.
     rootPoint := rootPoint + offs.
 
     "search view the drop is in"
@@ -630,6 +925,11 @@
     destinationView := device viewFromId:lastViewId.
     destinationId := lastViewId.
 
+    "/
+    "/ translate to destination view
+    "/
+    destinationPoint := device translatePoint:rootPoint from:rootId to:destinationId.
+
     dropAction notNil ifTrue:[
         "/ initiator wants to do it himself, manually.
 
@@ -683,7 +983,7 @@
         position:destinationPoint 
         rootPosition:rootPoint
 
-    "Modified: 4.4.1997 / 18:32:43 / cg"
+    "Modified: 19.4.1997 / 12:36:29 / cg"
 !
 
 uncatchEvents
@@ -698,6 +998,123 @@
     "
 ! !
 
+!DragAndDropManager::DemoView class methodsFor:'documentation'!
+
+documentation
+"
+    demonstrates rubber-line dragging.
+
+    See the buttonPress method, where a drag is initiated.
+    At endDrop, look at the transcript.
+
+    [author:]
+        Claus Gittinger
+
+    [start with:]
+        DemoView new open
+"
+! !
+
+!DragAndDropManager::DemoView methodsFor:'events'!
+
+buttonPress:button x:x y:y
+    DragAndDropManager new
+        startLineDragIn:self at:(x@y) 
+        atEnd:[:view
+               :viewID
+               :rootPoint
+               :viewPoint | 
+
+               Transcript show:'dropped at ';
+                          show:viewPoint;
+                          show:' (screen: ';
+                          show:rootPoint;
+                          show:') in '.
+               view notNil ifTrue:[
+                   Transcript showCR:view
+               ] ifFalse:[
+                   Transcript show:'alien view ';
+                              showCR:viewID address
+               ] 
+        ].
+
+    "
+     self new open
+    "
+
+    "Modified: 19.4.1997 / 11:40:46 / cg"
+! !
+
+!DragAndDropManager::DemoView3 class methodsFor:'documentation'!
+
+documentation
+"
+    demonstrates arrow-line dragging.
+
+    See the buttonPress method, where a drag is initiated.
+    At endDrop, look at the transcript.
+
+    [author:]
+        Claus Gittinger
+
+    [start with:]
+        DemoView3 new open
+"
+
+
+! !
+
+!DragAndDropManager::DemoView3 methodsFor:'events'!
+
+buttonPress:button x:x y:y
+    DragAndDropManager new
+        startArrowDragIn:self 
+        at:(x@y)
+        atEnd:[:view
+               :viewID
+               :rootPoint
+               :viewPoint | 
+
+               Transcript show:'dropped at ';
+                          show:viewPoint;
+                          show:' (screen: ';
+                          show:rootPoint;
+                          show:') in '.
+               view notNil ifTrue:[
+                   Transcript showCR:view
+               ] ifFalse:[
+                   Transcript show:'alien view ';
+                              showCR:viewID address
+               ] 
+        ].
+
+    "
+     self new open
+    "
+
+    "Modified: 19.4.1997 / 12:45:29 / cg"
+! !
+
+!DragAndDropManager::DemoView2 class methodsFor:'documentation'!
+
+documentation
+"
+    demonstrates string dragging.
+
+    See the buttonPress method, where a drag is initiated.
+    At endDrop, look at the transcript.
+
+
+    [author:]
+        Claus Gittinger
+
+    [start with:]
+        DemoView2 new open
+"
+
+
+! !
+
 !DragAndDropManager::DemoView2 methodsFor:'events'!
 
 buttonPress:button x:x y:y
@@ -718,50 +1135,8 @@
 
 ! !
 
-!DragAndDropManager::DemoView3 methodsFor:'events'!
-
-buttonPress:button x:x y:y
-    DragAndDropManager new
-        startArrowDragIn:self 
-        at:(x@y)
-        atEnd:[:view
-               :viewID
-               :rootPoint
-               :viewPoint | ]
-
-    "
-     self new open
-    "
-! !
-
-!DragAndDropManager::DemoView methodsFor:'events'!
-
-buttonPress:button x:x y:y
-    DragAndDropManager new
-        startLineDragIn:self at:(x@y) 
-        atEnd:[:view
-               :viewID
-               :rootPoint
-               :viewPoint | 
-
-               Transcript show:'dropped at ';
-                          show:viewPoint;
-                          show:' in '.
-               view notNil ifTrue:[
-                   Transcript showCR:view
-               ] ifFalse:[
-                   Transcript show:'alien view ';
-                              showCR:viewID address
-               ] 
-        ].
-
-    "
-     self new open
-    "
-! !
-
 !DragAndDropManager class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/DragAndDropManager.st,v 1.12 1997-04-06 13:03:43 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/DragAndDropManager.st,v 1.13 1997-04-19 15:22:38 cg Exp $'
 ! !