Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
ExternalDropHandler
Last updated at 12:23 pm UTC on 13 January 2022
Instance variables are the same since Squeak 3.2

Squeak Squeak 3.10.2 to 5.3
 Object subclass: #ExternalDropHandler
	instanceVariableNames: 'action type extension'
	classVariableNames: 'DefaultHandler RegisteredHandlers'
	poolDictionaries: ''
	category: 'System-Support'

ExternalDropHandler_SRE_Collaboration .png

Analysis: What happens if a file is dropped onto a Morphic desktop?


PasteUpMorph is the desktop


An instance of PasteUpMorph which answers
 self isWorldMorph
as
 true 
is used as a desktop.

This is as well the answer of Project current world.

 PasteUpMorph selectors select: [ :s | s asString includesSubstring: 'drop'] 
gives
  #(#dropFiles: #dropEnabled) 
So when a file is dropped onto the desktop the method #dropFiles: anEvent is called.

The method #dropFiles: then gets with the following method an instance of ExternalDropHandler

 handleDroppedItem: anItem event: anEvent
	
	(ExternalDropHandler lookupExternalDropHandler: anItem)
		ifNotNil: [:handler | handler handle: anItem in: self dropEvent: anEvent].

to handle the dropped item.


ExternalDropHandler>>handleDroppedItem:event:

The class method

 handleDroppedItem: anItem event: anEvent

is called by PasteUpMorph to find out about a handler to process the dropped file.


The code of the method
ExternalDropHandler>>handleDroppedItem:event"


 handleDroppedItem: anItem event: anEvent

	(ExternalDropHandler lookupExternalDropHandler: anItem)
		ifNotNil: [:handler | handler handle: anItem in: self dropEvent: anEvent].

There are internal drop handler (internal to the "ExternalDropHandler") and "external" drop handlers ("external" to the "ExternalDropHandler")
There are only two internal drop handlers (Squeak 6.0a) and more than 40 external ones (mangaged by FileServices).

Get drop handler from file services.


In most cases
ExternalDropHandler lookupExternalDropHandler:
uses the method
ExternalDropHandler lookupServiceBasedHandler:
to find out from FileServices registry about a service to process the dropped file.

 lookupServiceBasedHandler: dropStream
	"The file was just dropped; let's do our job"
	| fileName services theOne |
	fileName := dropStream name.

	services := (FileServices itemsForFile: fileName)
		reject: [:svc | self unwantedSelectors includes: svc selector].

	"no service, default behavior"
	services isEmpty
		ifTrue: [^nil].

	theOne := self chooseServiceFrom: services.
	^theOne
		ifNotNil: [ExternalDropHandler type: nil extension: nil action: [:stream | theOne performServiceFor: stream]].

Then
ExternalDropHandler chooseServiceFrom:


 chooseServiceFrom: aCollection
	"private - choose a service from aCollection asking the user if  needed"
	^aCollection size = 1 
		ifTrue: [aCollection anyOne]
		ifFalse:[UIManager default 
			chooseFrom: (aCollection collect:[:each| each label])
			values: aCollection
			title: 'You dropped a file. Please choose a service:' translated withCRs].

brings up the dialog box for the user to choose from. The dialog box below is shown after dropping a TrueType font file.


Choose_dialog_after_dropping_a_ttf_file_2017-03-29.png

https://sequencediagram.org/
title Dropping a file onto the desktop


aPasteUpMorph->aPasteUpMorph: handleEvent:anEvent

aPasteUpMorph->aPasteUpMorph: handleDropFiles: anEvent

aPasteUpMorph->aPasteUpMorph: dropFiles: anEvent

aPasteUpMorph->aPasteUpMorph:handleDroppedItem: anItem event: anEvent


aPasteUpMorph->ExternalDropHandler: lookupExternalDropHandler: anItem

ExternalDropHandler->ExternalDropHandler:lookupServiceBasedHandler: dropStream


ExternalDropHandler->FileServices:itemsForFile: fileName


ExternalDropHandler->ExternalDropHandler:chooseServiceFrom:

ExternalDropHandler->UIManager:chooseFrom:values:title: 

ExternalDropHandler->SimpleServiceEntry:performServiceFor: stream


Dropping a file onto the desktop.png






 col := AlignmentMorph newColumn.
 col addMorphBack: (StringMorph contents: 'ExternalDropHandler class').
 col addMorphBack: (StringMorph contents: 'lookupExternalDropHandler: stream').
 col openInHand


lookupExternalDropHandler: stream

	| types extension serviceHandler |
	types := stream mimeTypes.

	types ifNotNil: [
		self registeredHandlers do: [:handler | 
			(handler matchesTypes: types)
				ifTrue: [^handler]]].

	extension := FileDirectory extensionFor: stream name.
	self registeredHandlers do: [:handler | 
		(handler matchesExtension: extension)
				ifTrue: [^handler]].
	self halt.		
	serviceHandler := self lookupServiceBasedHandler: stream.
	^serviceHandler
		ifNil: [self defaultHandler]


 lookupServiceBasedHandler: dropStream
	"The file was just dropped; let's do our job"
	| fileName services theOne |
	fileName := dropStream name.

	services := (FileServices itemsForFile: fileName)
		reject: [:svc | self unwantedSelectors includes: svc selector].
	"no service, default behavior"
	services isEmpty
		ifTrue: [^nil].

	theOne := self chooseServiceFrom: services.
	^theOne
		ifNotNil: [ExternalDropHandler type: nil extension: nil action: [:stream | theOne performServiceFor: stream]]


 col := AlignmentMorph newColumn.
 col addMorphBack: (StringMorph contents: '= col := AlignmentMorph newColumn.
 col addMorphBack: (StringMorph contents: 'FileServices class').
 col addMorphBack: (StringMorph contents: 'itemsForFile: fileName').
 col openInHand



See also SRE Execution Tracer