Squeak
  links to this page:    
View this PageEdit this Page (locked)Uploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Drag and Drop
Last updated at 11:47 am UTC on 8 December 2004
How to do Drag and Drop
by David N. Smith
http://www.dnsmith.com/squeak/dragdrop.html
(Out of date as of mid-2001 – DNS)


=======================================
Hmmm.. the above link appears to be dead.

Here is what I did to get custom playing card images to Drag 'n Drop.

Tell the system you are interested by adding a method #handlesMouseDown: which answers true.


 handlesMouseDown: evt 
	^ true
When you get a #mouseDown: event, ask the HandMorph to handle the rest of the gesture:

 mouseDown: evt 
	"Do nothing upon mouse-down except inform the hand to watch for a 
	double-click; wait until an ensuing click:, doubleClick:, or drag: 
	message gets dispatched"
	
	(self owner okToPickUp: self)
	ifFalse: [ ^self ] 
	ifTrue: [evt hand
		waitForClicksOrDrag: self
		event: evt
		selectors: {#click:. #doubleClick:. #firstClickTimedOut:. nil}
		threshold: 5]
I ignore #click: and #doubleClick: but you might not...

 click: evt 
	"ignore this and wait until #firstClickTimedOut: arrives"
	^ self

 doubleClick: evt 
	"ignore"
	^ self
When the mouse has been held down long enough, #firstClickTimeout: occurs. This is when the Morph under the hand is picked up.

 firstClickTimedOut: evt
	"Start the Drag with the hand grabbing me"
	
	evt hand grabMorph: self
Now the HandMorph is about to "pick up" the Morph under it. It lets the selected Morph know via #aboutToBeGrabbedBy: so that it can change its appearance if it needs to. You probably don't need this, but in my case...

 aboutToBeGrabbedBy: aHand 
	"I'm about to be grabbed by the hand. If other cards are
	 above me in a Card Container, then move them from the 
	 Container to being submorphs of me"

	| idx |
	super aboutToBeGrabbedBy: aHand.
	idx := owner submorphs
				indexOf: self
				ifAbsent: [^ self].
	idx = 1
		ifTrue: [^ self].
	(owner submorphs copyFrom: 1 to: idx - 1)
		do: [:m | m class = self class
				ifTrue: [self addMorphBack: m]]
Now, when a Drop gesture/event occurs, both the Morph dropped on and the dropped Morph get a chance to "say no".

The Morph which has been dropped on is asked via #wantsDroppedMorph:event: . Test whatever you need here to make sure you want the drop.

 wantsDroppedMorph: aMorph event: evt 
	"Ask my container."
	
	(self owner isKindOf: AltCardContainerMorph)
	ifTrue: [ ^(self owner) wantsDroppedMorph: aMorph 
		                event: evt ]
	ifFalse: [^ false]
The dropped morph is asked via #wantsToBeDroppedInto:

 wantsToBeDroppedInto: aMorph 
	"I want to be dropped onto a Card or Card Container"
	^ (aMorph isKindOf: AltCardContainerMorph)
		| (aMorph isKindOf: AltCardMorph)
If either the the dropped or dropped-upon Morphs answer false, the dropped Morph returns to where it was picked up. In this case #rejectDropMorphEvent: is sent to the Morph that was picked up so that its appearance can be re-adjusted. You probably don't need to do thie either, but in my case..

 rejectDropMorphEvent: evt
	"Drop rejected. If have submorphs, give them back 
	to the container."
	
	super rejectDropMorphEvent: evt.
	(self owner isKindOf: AltCardContainerMorph) 
	& (self submorphCount > 0)
	ifTrue: [ self submorphs 
		     reverseDo: [ :m | self owner addMorph: m].
		  self layoutChanged ]
Assuming both Morphs want the drop, the dropped-upon Morph gets the message #acceptDroppingMorph:event:

 acceptDroppingMorph: aMorph event: evt 
	"Delegate to my owning Card Container"
	
	(self owner isKindOf: AltCardContainerMorph)
	ifTrue: [ ^(self owner) acceptDroppingMorph: aMorph
				event: evt ]
	ifFalse: [ ^false ]
Finally, the Morph which was dropped gets the #justDroppedInto:event: message so that it can do any required state changes as well.

 justDroppedInto: aMorph event: anEvent
    self owner checkStrategy

That's it!


See also: the DoubleClickExample Morph code as well as HandMorph.

Happy Squeaking!
KenDickey [KenD]