Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
DropZoneMorph
Last updated at 5:38 am UTC on 9 May 2018
'From Squeak5.1 of 23 August 2016 [latest update: #16548] on 2 May 2018 at 8:05:03 am'!
"Change Set:		DropZone
Date:			2 May 2018
Author:			Bob Arning

DropZoneMorph is a place to drop things to execute a user-supplied action. Examples in class comment"!

Morph subclass: #DropZoneMorph
	instanceVariableNames: 'label action '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!

!DropZoneMorph commentStamp: 'raa 5/2/2018 08:02' prior: 0!
DropZoneMorph new 
	openLabel: 'explore' 
	action: [ :m | m explore. #reject]

DropZoneMorph new 
	openLabel: 'to project unnamed' 
	action: [ :m | (Project named: 'Unnamed') world addMorph: m.]
	
DropZoneMorph new 
	openLabel: 'take a picture' 
	action: [ :m | m imageForm asMorph openInWorld. #reject]
	
!


!DropZoneMorph methodsFor: 'as yet unclassified' stamp: 'raa 5/2/2018 07:31'!
acceptDroppingMorph: aMorph event: evt

	self halt.! !

!DropZoneMorph methodsFor: 'as yet unclassified' stamp: 'raa 5/2/2018 07:49'!
openLabel: l action: a

	label _ l.
	action _ a.
	self
		listDirection: #leftToRight;
		hResizing: #shrinkWrap;
		vResizing: #shrinkWrap;
		extent: 1@1;
		borderWidth: 0;
		rubberBandCells: true;
		color: Color paleBlue;
		addMorph: (StringMorph contents: label) lock.
	self openInWorld! !

!DropZoneMorph methodsFor: 'as yet unclassified' stamp: 'raa 5/2/2018 07:58'!
rejectDropEvent: anEvent

	anEvent wasHandled: true.

	(action value: anEvent contents) = #reject ifTrue: [
		anEvent contents rejectDropMorphEvent: anEvent.
	].
! !

!DropZoneMorph methodsFor: 'as yet unclassified' stamp: 'raa 5/2/2018 07:59'!
wantsDroppedMorph: aMorph event: evt

	self halt.

	! !



Updated version DropZoneMorph 2