Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Notes on drag and drop by David N. Smith
Last updated at 8:13 am UTC on 22 August 2016

Drag and Drop

(Feb2000)

This note is an attempt to summarize what I think I learned by playing around with drag and drop. It probably contains errors and I'll happily correct any that anyone finds. This file will eventually find its way to the Squeak swici.


Messages sent to any morph to enable or disable drag and drop on its submorphs:

closeDragAndDrop
	"Don't allow drag or drop operations on submorphs."


openDragAndDrop
	"Allow dragging and dropping for submorphs."


Messages sent to the morph that will be, is being, or just was dragged:

aboutToBeGrabbedBy: aHand
	The receiver is being grabbed by a hand. Do local processing and resend with super, or answer nil to stop the grab. 

justDroppedInto: aMorph event: anEvent

This message is sent to a dropped morph after it has been dropped on–and been accepted by–a drop-sensitive morph. Must resend with super to complete the operation, or must take some action to move the morph elsewhere. (See #slideBackToFormerSituation:.)

 slideBackToFormerSituation: evt

Slides a morph back to where it was grabbed. Sent to a morph when a drop receiver decides it doesn't really want the morph, or in other cases where it makes sense.


Messages sent to the morph over which some other morph is being dragged:

acceptDroppingMorph: aMorph event: evt

This message is sent when a morph is dropped onto a receiving morph that has agreed to accept the dropped morph by responding 'true' to the wantsDroppedMorph:Event: message. The default implementation just adds the given morph to the receiver. May be overridden to do other things.

 repelsMorph: aMorph event: ev

Answer true if the receiver wished to repel (not accept) the given morph, which is being dropped by a hand in response to the given event. The default is false. Used in a morph that accepts drops to reject certain kinds of dropped morphs.

The message is sent to all morphs at the drop point, not just those that have asked to be open for drag and drop events.
It differs from #wantsDroppedMorph:event: in that if any morph under the drop point, taken deepest imbedded morph first, repels the morph then there is no drop, even if a higher morph would have accepted the drop. (See HandMorph>>#dropTargetFor:event: for details.)

 wantsDroppedMorph: aMorph event: evt

Answer true if the receiver wishes to accept the given morph, which is being dropped by a hand in response to the given event. The default is true if the morph is enabled for drag and drop, else false.

The message is sent to all morphs at the drop point, not just those that have asked to be open for drag and drop events.
It differs from #repelsMorph:event: in that any morph under the drop point, taken deepest imbedded morph first, wants the drop then it gets the drop on itself, even if a higher morph also wants the drop. (See HandMorph>>#dropTargetFor:event: for details.)

NOTE: the event is assumed to be in global (world) coordinates."


Missing messages:

 aboutToBeDroppedInto: aMorph event: anEvent

This message should be sent to a morph just before it will be dropped on a drop-sensitive morph. It should answer a boolean indicating whether or not it will accept being
dropped at this point. The method is not implemented in Squeak.


Mouse Event Messages

In addition, one may use mouse events in conjunction with drag and drop messages to, say, give visual feedback on the morph being dragged over. See the TrashCanMorph for an example.


Cautions

Dropping on a trash can is difficult to recover from if the morph didn't want to be dropped on a trash can, since by the time the dropped morph gets control (by justDroppedInto:event:) the morph is already unhooked from its former owner.

Dropping onto some other morph, say one that changes a property such as color, can be only partly undone by justDroppedInto:event: since there is no way to tell what properties might have been changed.



A Minimal Example of Drag and Drop


Two morphs are created, a large white rectangle which holds a small colored rectangle. The smaller rectangle can be dragged and dropped almost anywhere, including in another large white rectangle.

'From Squeak2.8alpha of 12 January 2000 [latest update: #1852] on 18 February 2000 at 4:54:15 pm'!
RectangleMorph subclass: #DavesDragDemo1
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Daves-DragDemos'!
RectangleMorph subclass: #DavesDragDemoPart1
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Daves-DragDemos'!

!DavesDragDemo1 methodsFor: 'as yet unclassified' stamp: 'dns 2/18/2000 16:42'!
openInWorld
	self bounds: (30@30 extent: 100@100);
		openDragAndDrop;
		color: Color white.
	self addMorphFront: (
		DavesDragDemoPart1 new
			bounds: (self topLeft + 10 extent: 20@20)).
	super openInWorld! !

!DavesDragDemoPart1 methodsFor: 'as yet unclassified' stamp: 'dns 2/18/2000 16:45'!
initialize
	super initialize.
	self
		color: Color random;
		borderWidth: 1! !


If we add these two methods, then the dragged morph will make its border wider while being dragged:

!DavesDragDemoPart1 methodsFor: 'as yet unclassified' stamp: 'dns 2/18/2000 17:02'!
aboutToBeGrabbedBy: aHand
	self borderWidth: 2!

justDroppedInto: aMorph event: anEvent
	self borderWidth: 1! !



If we modify #justDroppedInto:event: as below then when the morph is dropped it only stays in large white rectangles. If dropped other (safe) places it slides back to its original location and situation. Unsafe places include the trash can and drop targets that modify the dropped morph upon acceptance.

'From Squeak2.8alpha of 12 January 2000 [latest update: #1852] on 18 February 2000 at 5:12:36 pm'!

!DavesDragDemoPart1 methodsFor: 'as yet unclassified' stamp: 'dns 2/18/2000 17:12'!
justDroppedInto: aMorph event: anEvent
	self borderWidth: 1.
	(owner isKindOf: DavesDragDemo1) ifFalse: [
		self slideBackToFormerSituation: anEvent ]! !


If we add the following method then the color of the dropped morph changes when it is dropped into any white rectangle.

!DavesDragDemo1 methodsFor: 'as yet unclassified' stamp: 'dns 2/18/2000 17:34'!
acceptDroppingMorph: aMorph event: evt
	aMorph color: Color random.
	super acceptDroppingMorph: aMorph event: evt ! !


An additional change assures that only the right kind of morphs (the little rectangles) can be dropped on a white rectangle; otherwise they are slid back where they came from. (Omit the slide and the dragged morph stays where it is placed but lives in the world.

!DavesDragDemo1 methodsFor: 'as yet unclassified' stamp: 'dns 2/18/2000 17:45'!
acceptDroppingMorph: aMorph event: evt
	(aMorph isKindOf: DavesDragDemoPart1) ifTrue: [
		aMorph color: Color random.
		^ super acceptDroppingMorph: aMorph event: evt ].
	aMorph slideBackToFormerSituation: evt ! !


David N. Smith
25Feb2000
dnsmith@watson.ibm.com

https://web.archive.org/web/20031223094732/http://www.dnsmith.com/squeak/dragdrop.html


This page is here for historical reasons. For a recent discussion about drag and drop (2015) see http://wiki.squeak.org/squeak/6194