2.4 File Selector

So far, we have observed existing morphs. Let’s now build our own new morph.

2.4.1 Poor Man Implementation

First, let’s do something quick and fun: a poor man’s file selector. All it takes is to get the entries of a given directory, collect them as previews, and add them all in a flow layout:

| directories |
directories := DirectoryEntry userBaseDirectory children collect: [:anEntry |
   FilePreviewMorph 
      object: anEntry 
      image: ((anEntry isFileEntry ifTrue: [Theme current genericTextIcon] ifFalse: [Theme current fetch: #( '16x16' 'places' 'folder' )]) magnifyTo: 64@64)
      buttons: nil
      label: anEntry baseName ::
      borderColor: Color transparent;
      color: Color transparent].
FlowLayoutMorph new ::
   openInWorld;
   cells: directories 

Of course, at this stage, we can’t browse the directory tree:

ch02-fileSelectorBasic

Figure 2.6: A basic tool to list the files in a folder

To add more behavior to our poor man’s file selector, we want to make our first morph by reusing existing components.

2.4.2 First Morph Design by Reuse

Our morph visually presents files and directories at a given location on the host’s disk. As we want this morph to be reused by other GUI designers, it doesn’t present itself in a window but in a simple surface, a pane. Therefore, we name it FileSelectorPane. It emits events when the user selects a file and updates itself with new contents when the user double-clicks on a folder.

Because we may have numerous files and directories to present, we create our FileSelectorPane as a subclass of FlowLayoutMorph:

FlowLayoutMorph subclass: #FileSelectorPane
   instanceVariableNames: ''
   classVariableNames: ''
   poolDictionaries: ''
   category: 'ArtOfMorph'

In its parent’s hierarchy, our FileSelectorPane has the PluggableMorph ancestor, which observes a model. In the present context, the model represents the currently observed DirectoryEntry. It is set by default to the user base directory:

initialize
super initialize.
self open: DirectoryEntry userBaseDirectory

When opening a new location, directories and files are collected and sorted separately into two groups to build meaningful previews:

open: aDirectoryEntry
| entryViews |
model := aDirectoryEntry.
entryViews := OrderedCollection new.
model isRoot ifFalse: [ | parentView |
   parentView := self entryPreviewFor: model parent.
   parentView relabel: '..' bold.
   entryViews add: parentView].
entryViews 
   addAll: (self previewsFor: model directories);
   addAll: (self previewsFor: model files ).
self cells: entryViews

The directory and file entries are sorted appropriately, and each one is flanked with a preview:

previewsFor: entries
^ (entries sort: [:a :b | a baseName asUppercase < b baseName asUppercase ])
      collect: [:anEntry | self entryPreviewFor: anEntry]

The special directory “..” above is inserted first for the user to browse to the parent directory of the model.

Observe below how each directory preview is listening to the double-click event. In that circumstance, the related directory is opened.

entryPreviewFor: fileEntry
| fileView |
fileView := FilePreviewMorph 
   object: fileEntry 
   image: ((fileEntry isFileEntry 
      ifTrue: [Theme current genericTextIcon] 
      ifFalse: [Theme current fetch: #( '16x16' 'places' 'folder' )]) magnifyTo: 48@48)
   buttons: nil
   label: fileEntry baseName ::
   borderColor: Color transparent;
   color: Color transparent.
fileEntry isDirectoryEntry ifTrue: [
   fileView when: #doubleClick send: #open: to: self with: fileEntry].
^ fileView 

We are relying on FilePreviewMorph, a composition of several morphs, which itself emits events to notify about user activities.

To integrate this widget with other morphs, particularly to behave as a file selector, we want it to trigger events when the user selects a file. A FilePreviewMorph emits a #selected event each time the user clicks it. Let’s capture this event to manage it internally:

entryPreviewFor: fileEntry
../..
fileView when: #selected send: #toggleSelection: to: self with: fileView.
^ fileView

Then, we define the behavior for the #toggleSelection: message:

toggleSelection: fileView
| selectedView |
selectedView := cells detect: [:aFileView | aFileView isSelected] ifNone: [nil].	
selectedView = fileView
   ifTrue: [ " unselect view, no view selected anymore "
      fileView toggleSelection.
      selectedView := nil]			
   ifFalse: [
      selectedView ifNotNil: [selectedView toggleSelection].
      fileView selected: true.
      selectedView := fileView].
selectedView 
   ifNil: [self triggerEvent: #noSelection]
   ifNotNil: [self triggerEvent: #selectedFile with: selectedView fileEntry]

To visualize in the Transcript window the event propagation, instantiate a new file selector and capture its events:

| selector |
selector := FileSelectorPane new openInWorld.
selector when: #noSelection send: #print to: 'no entry'.
selector when: #selectedFile send: #show: to: Transcript

To stop listening to events, just send the #removeAllActions message to the listener: selector removeAllActions.

Morphs are both listeners and emitters of events. Doing so is important for decoupling objects from each other and improving object reuse.

We designed the FileSelectorPane to be itself reusable in other morphs. In the next section, we illustrate its use to improve the usability of the StringRequestMorph, a morph used—among other things—to ask the user to key in a file name; we want to improve it to make it more user-friendly.

2.4.3 Beyond String Request Morph

As illustrated by the sketch below, the idea is to have a file pane that expands on user request. The user then selects a file or a directory directly by pointing to it on the pane.

ch02-fileSelectorSketch

Figure 2.7: A sketch depicting a file selector and its behavior

Let’s extend the behavior of StringRequestMoprh:

StringRequestMorph subclass: #FileRequestMorph
   instanceVariableNames: 'fileBrowser'
   classVariableNames: ''
   poolDictionaries: ''
   category: 'ArtOfMorph'

We add the instance variable fileBrowser to hold our file selector when it is unfolded. We override a few methods from StringRequestMorph. We add a button to unfold/fold the file browser:

addTextPane
super addTextPane.
submorphs first addMorph: 
   ((PluggableButtonMorph model: self action: #toggleFileBrowser)
      setBalloonText: 'Browse the file system to select a file or directory';
      icon: (Theme current fetch: #( '16x16' 'places' 'folder' )) )

When unfolding the file browser, we check its current status. If it’s absent, we instantiate a new one just below the text entry; otherwise, we just delete it from the screen:

toggleFileBrowser
fileBrowser ifNotNil: [
   fileBrowser delete.
   fileBrowser := nil.
   ^ self].
fileBrowser := FileSelectorPane new open: self directoryEntry.
fileBrowser when: #selectedFile send: #entry: to: self.
fileBrowser 
   color: (Color white alpha: 0.8);
   morphPosition: self morphPosition + (0  (self morphHeight + 5));
   morphExtent: self morphExtent * (1@5);
   openInWorld

In this method, two important points: the directoryEntry method returns the current directory as edited by the user, and the #selectedFile event emitted by the FileSelectorPane is observed and dispatched to the entry: method. Each time the user selects a file, the message #entry: is sent to the FileRequestMorph instance:

entry: anEntry
textMorph hasUnacceptedEdits: false.
response := anEntry asString.
self changed: #response.
textMorph hasUnacceptedEdits: true
ch02-FileRequestMorph

Figure 2.8: File request morph and its file browser unfolded

We end here our chapter on designing morphs by reusing existing ones. From the usability perspective, our FileRequestMorph example is far from complete; user interfaces grow on small details. There is a lot of room for improvements: the printed filenames below the icons are ridiculously short, a distinction between file and folder selection when the tool is invoked would allow for more precise usability behavior, and the button to unfold and fold the file browser could have a selected state. These improvements are good exercises to strengthen your skills.