[squeak-dev] The Trunk: Tools-tpr.772.mcz

Chris Muller asqueaker at gmail.com
Sat Nov 11 01:36:54 UTC 2017


I haven't tried this yet, but I do hope you haven't broken the
list-filtering function or other keyboard shortcuts.  For me, a
multicolumn list is much less important to usability than the ability
to interact with the file list via the keyboard.

On Fri, Nov 10, 2017 at 6:32 PM,  <commits at source.squeak.org> wrote:
> tim Rowledge uploaded a new version of Tools to project The Trunk:
> http://source.squeak.org/trunk/Tools-tpr.772.mcz
>
> ==================== Summary ====================
>
> Name: Tools-tpr.772
> Author: tpr
> Time: 10 November 2017, 4:32:21.463175 pm
> UUID: 87c216c9-58b6-4a00-90ce-c7761cd1fa86
> Ancestors: Tools-eem.771
>
> Fixes and extensions to FileChooser/Saver Dialogs -
> use a mutli-column list for the file list
> clean up operation so we don't repeatedly read the directory contents repeatedly again
> add hooks for a user message, and a default for each kind of dialog
>
> =============== Diff against Tools-eem.771 ===============
>
> Item was changed:
>   Model subclass: #FileAbstractSelectionDialog
> +       instanceVariableNames: 'pattern directory directoryCache message listIndex fileName finalChoice nameList sizeList dateList'
> -       instanceVariableNames: 'pattern directory directoryCache list listIndex fileName finalChoice'
>         classVariableNames: ''
>         poolDictionaries: ''
>         category: 'Tools-FileDialogs'!
>
> + !FileAbstractSelectionDialog commentStamp: 'tpr 11/9/2017 15:37' prior: 0!
> - !FileAbstractSelectionDialog commentStamp: 'tpr 10/28/2017 12:55' prior: 0!
>   FileAbstractSelectionDialog is the abstract superclass for the file chooser & saver modal dialogs.
>
>   The UI provides a text input field, a directory tree widget and a list of files within any chosen directory, and buttons to accept the selected file name/path or cancel the operation. See subclass comments and class side methods for specific usage examples.
>
>   Instance Variables
>         directory:              <FileDirectory> used for the currently selected directory
>         directoryCache:         <WeakIdentityKeyDictionary> used to cache a boolean to help us more quickly populate the directory tree widget when revisiting a directory
>         fileName:               <String|nil> the name of the currently selected file, if any
>         finalChoice:            <String|nil> pathname of the finally chosen file, returned as the result of accepting; nil is returned otherwise
>         list:           <Array> the list of String of filenames (and date/size) that match the current pattern
>         listIndex:              <Integer> list index of the currently selected file
> +       pattern:                <String> the pattern is held as a string that may include * or # wildcasrds. See FileAbstractSelectionDialog>>#parsePatternString for details!
> -       pattern:                <String> the pattern is held as a string with three simple tokens;
> -                                               a) a ; or LF or CR splits the string into separate patterns and filenames matching any of them will be included in list
> -                                               b) a * matches any number of characters
> -                                               c) a # matches one character
> -                                       The usage of pattern (see entriesMatching:, updateFileList , listForPatterns:) definitely needs improving.!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>acceptFileName (in category 'initialize-release') -----
>   acceptFileName
> +       "User clicked to accept the current state so save the filename and close the dialog"
>
>         finalChoice := fileName.
>         self changed: #close!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>buildFileListWith: (in category 'toolbuilder') -----
>   buildFileListWith: builder
>         | listSpec |
> +       listSpec := builder pluggableMultiColumnListSpec new.
> -       listSpec := builder pluggableListSpec new.
>         listSpec
>                  model: self ;
>                  list: #fileList ;
>                  getIndex: #fileListIndex ;
>                  setIndex: #fileListIndex: ;
>                  menu: nil ;
>                  keyPress: nil ;
>                  frame:
>                 (self
>                         frameOffsetFromTop:0
>                         fromLeft: 0
>                         width: 1
> +                       bottomFraction: 1);
> +               hScrollBarPolicy: #always .
> -                       bottomFraction: 1) .
>         ^listSpec!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>buildWindowWith: (in category 'toolbuilder') -----
>   buildWindowWith: builder
>         "Since a file chooser is a modal dialog we over-ride the normal window build to use a dialog as the top component"
>
>         | windowSpec |
>         windowSpec := builder pluggableDialogSpec new.
>         windowSpec model: self;
>                                 label: #windowTitle;
> +                               message: #userMessage;
>                                 extent: self initialExtent;
>                                 children: OrderedCollection new;
>                                 buttons: OrderedCollection new.
>         ^windowSpec!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>buildWith: (in category 'toolbuilder') -----
>   buildWith: builder
>         "assemble the spec for the common chooser/saver dialog UI"
> +
> -       "ToolBuilder open: FileChooserDialog"
> -       "ToolBuilder open: FileSaverDialog"
>         | windowSpec window |
>         windowSpec := self buildWindowWith: builder specs: {
>                 (self topConstantHeightFrame: self textViewHeight
>                         fromLeft: 0
>                         width: 1) -> [self buildTextInputWith: builder].
>                 (self frameOffsetFromTop: self textViewHeight
>                         fromLeft: 0.25
>                         width: 0.75
>                         offsetFromBottom: self buttonHeight) -> [self buildFileListWith: builder].
>                 (self frameOffsetFromTop: self textViewHeight
>                         fromLeft: 0
>                         width: 0.25
>                         offsetFromBottom: self buttonHeight) -> [self buildDirectoryTreeWith: builder].
>         }.
>         windowSpec buttons add:( builder pluggableButtonSpec new
>                                                 model: self;
>                                                 label: 'Accept';
>                                                 action: #acceptFileName).
>         windowSpec buttons add:( builder pluggableButtonSpec new
>                                                 model: self;
>                                                 label: 'Cancel';
>                                                 action: #cancelFileChooser).
>         window := builder build: windowSpec.
>         self changed: #selectedPath.
>         ^window
>   !
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>cancelFileChooser (in category 'initialize-release') -----
>   cancelFileChooser
> +       "User clicked to cancel the current state so nil the filename and close the dialog"
>
>         fileName := nil.
>         self changed: #close.!
>
> Item was added:
> + ----- Method: FileAbstractSelectionDialog>>defaultPattern (in category 'path and pattern') -----
> + defaultPattern
> +
> +       ^'*'!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>directory (in category 'directory tree') -----
>   directory
> +       "If nobody has set a specific directory we need a plausible default"
>
> +       ^ directory ifNil: [ FileDirectory default]!
> -       ^ directory!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>directory: (in category 'directory tree') -----
>   directory: aFileDirectory
> +       "Set the path of the directory to be displayed in the directory tree pane"
> +
> -       "Set the path of the directory to be displayed."
>         self okToChange ifFalse: [ ^ self ].
>         self modelSleep.
>         directory := aFileDirectory.
>         self modelWakeUp.
> +       self changed: #directory!
> -       self changed: #directory.
> -       self pattern: pattern!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>fileList (in category 'file list') -----
>   fileList
> +       "return the list of files in the currently selected directory; if we haven't yet read an actual directory return empty lists for now"
> +
> +       nameList ifNil: [nameList := dateList := sizeList := #()].
> +       ^Array with: nameList with: dateList with: sizeList!
> -       "return the list of files in the currently selected directory"
> -
> -       ^list!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>fileListIndex (in category 'file list') -----
>   fileListIndex
> +       "return the index in the list of files for the currently selected file; we initialise this to 0 so that the initial listmorph doesn't get upset before we actually populate it with file details - which we don't do until a directory is selected"
> -       "return the index in the list of files for the currently selected filey"
>
>         ^listIndex!
>
> Item was removed:
> - ----- Method: FileAbstractSelectionDialog>>fileNameFormattedFrom:sizePad: (in category 'path and pattern') -----
> - fileNameFormattedFrom: entry sizePad: sizePad
> -       "entry is a 5-element array of the form:
> -               (name creationTime modificationTime dirFlag fileSize)"
> -       | sizeStr nameStr dateStr |
> -       nameStr := entry isDirectory
> -               ifTrue: [entry name , self folderString]
> -               ifFalse: [entry name].
> -       dateStr := ((Date fromSeconds: entry modificationTime )
> -                                       printFormat: #(3 2 1 $. 1 1 2)) , ' ' ,
> -                               (String streamContents: [:s |
> -                                       (Time fromSeconds: entry modificationTime \\ 86400)
> -                                               print24: true on: s]).
> -       sizeStr := entry fileSize asStringWithCommas.
> -       ^ nameStr , '    (' , dateStr , ' ' , sizeStr , ')'
> - !
>
> Item was removed:
> - ----- Method: FileAbstractSelectionDialog>>fileNameFromFormattedItem: (in category 'file list') -----
> - fileNameFromFormattedItem: item
> -       "Extract fileName and folderString from a formatted fileList item string"
> -
> -       | from to |
> -       from := item lastIndexOf: $(.
> -       to := item lastIndexOf: $).
> -       ^ (from * to = 0
> -               ifTrue: [item]
> -               ifFalse: [item copyReplaceFrom: from to: to with: '']) withBlanksTrimmed!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>hasMoreDirectories: (in category 'directory tree') -----
>   hasMoreDirectories: aDirectory
> +       "The directory tree morph needs to know if a specific directory has subdirectories; we cache the answer to speed up later visits to the same directory"
> +
>         ^directoryCache at: aDirectory ifAbsentPut:[
>                 [aDirectory directoryNames notEmpty] on: Error do:[:ex| true].
>         ].!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>initialize (in category 'initialize-release') -----
>   initialize
>         super initialize.
>         directoryCache := WeakIdentityKeyDictionary new.
> +       listIndex := 0.
> +       pattern := self defaultPattern!
> -       self directory: FileDirectory default!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>listForPatterns: (in category 'path and pattern') -----
> + listForPatterns: arrayOfPatterns
> - listForPatterns: anArray
>         "return a list of those file names which match any of the patterns in the array."
>
> +       | newList |
> -       | sizePad newList |
>         newList := Set new.
> +       arrayOfPatterns do: [ :pat | newList addAll: (self entriesMatching: pat) ].
> -       anArray do: [ :pat | newList addAll: (self entriesMatching: pat) ].
> -       sizePad := (newList inject: 0 into: [:mx :entry | mx max: entry fileSize])
> -                                       asStringWithCommas size.
> -       newList := newList collect: [ :e | self fileNameFormattedFrom: e sizePad: sizePad ].
>
> +       newList := newList sorted: [:a :b|
> +                                                       a name <= b name].
> +       nameList := newList collect:[:e| e name].
> +       dateList := newList collect:[:e| ((Date fromSeconds: e modificationTime )
> +                                       printFormat: #(3 2 1 $. 1 1 2)) , ' ' ,
> +                               (String streamContents: [:s |
> +                                       (Time fromSeconds: e modificationTime \\ 86400)
> +                                               print24: true on: s])].
> +       sizeList := newList collect:[:e| e  fileSize asStringWithCommas]
> + !
> -       ^ newList asArray!
>
> Item was added:
> + ----- Method: FileAbstractSelectionDialog>>parsePatternString (in category 'file list') -----
> + parsePatternString
> +       "The pattern is held as a string that may have three simple tokens included along with normal characters;
> +       a) a ; or LF or CR splits the string into separate patterns and filenames matching any of them will be included in list
> +       b) a * matches any number of characters
> +       c) a # matches one character"
> +
> +       | patterns |
> +       patterns := OrderedCollection new.
> +       (pattern findTokens: (String with: Character cr with: Character lf with: $;))
> +               do: [ :each |
> +                       (each includes: $*) | (each includes: $#)
> +                                       ifTrue: [ patterns add: each]
> +                                       ifFalse: [each isEmpty
> +                                                                               ifTrue: [ patterns add: '*']
> +                                                                               ifFalse: [ patterns add: '*' , each , '*']]].
> +
> +       ^patterns!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>pattern: (in category 'path and pattern') -----
>   pattern: textOrStringOrNil
> +       "Make sure the pattern source string is neither nil nor empty"
>
>         textOrStringOrNil
>                 ifNil: [pattern := '*']
>                 ifNotNil: [pattern := textOrStringOrNil asString].
> +       pattern isEmpty ifTrue: [pattern := '*']!
> -       pattern isEmpty ifTrue: [pattern := '*'].
> -       self updateFileList.
> -       ^ true
> - !
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>rootDirectoryList (in category 'directory tree') -----
>   rootDirectoryList
> +       "Return a list of know root directories; forms the root nodes ot the directory tree morph"
> +
>         | dirList dir |
>         dir := FileDirectory on: ''.
>         dirList := dir directoryNames collect:[:each| dir directoryNamed: each]..
>         dirList isEmpty ifTrue:[dirList := Array with: FileDirectory default].
>         ^dirList!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>selectedPath (in category 'path and pattern') -----
>   selectedPath
> +       "Return an array of directories representing the path from directory up to the root; used to build the directory tree morph"
> +
>         | top here |
>         top := FileDirectory root.
>         here := directory.
>         ^(Array streamContents:[:s| | next |
>                 s nextPut: here.
>                 [next := here containingDirectory.
>                 top pathName = next pathName] whileFalse:[
>                         s nextPut: next.
>                         here := next.
>                 ]]) reversed.!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>setDirectoryTo: (in category 'directory tree') -----
>   setDirectoryTo: dir
>         "Set the current directory shown in the FileList.
>         Does not allow setting the directory to nil since this blows up in various places."
> +
>         dir ifNil:[^self].
>         self directory: dir.
> +       self updateFileList.
> +       self changed: #inputText!
> -       self changed: #fileList.
> -       self changed: #inputText.!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>subDirectoriesOf: (in category 'directory tree') -----
>   subDirectoriesOf: aDirectory
> +
>         ^aDirectory directoryNames collect:[:each| aDirectory directoryNamed: each].!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>textViewHeight (in category 'ui details') -----
>   textViewHeight
>         " Take a whole font line and 50 % for space "
> +
>         ^ (self textViewFont height * 1.5) ceiling!
>
> Item was changed:
>   ----- Method: FileAbstractSelectionDialog>>updateFileList (in category 'file list') -----
>   updateFileList
> +       "Update my files list with file names in the current directory that match the pattern.
> +       The pattern string may have embedded newlines or semicolons; these separate multiple different patterns."
> -       "Update my files list with file names in the current directory
> -       that match the pattern.
> -       The pattern string may have embedded newlines or semicolons; these separate different patterns."
> -       | patterns |
> -       patterns := OrderedCollection new.
> -       Cursor wait showWhile: [
> -       (pattern findTokens: (String with: Character cr with: Character lf with: $;))
> -               do: [ :each |
> -                       (each includes: $*) | (each includes: $#)
> -                                       ifTrue: [ patterns add: each]
> -                                       ifFalse: [each isEmpty
> -                                                                               ifTrue: [ patterns add: '*']
> -                                                                               ifFalse: [ patterns add: '*' , each , '*']]].
>
> +               Cursor wait
> +                       showWhile: [self listForPatterns: self parsePatternString.
> +                               listIndex := 0.
> +                               self changed: #fileList]!
> -       list := self listForPatterns: patterns.
> -       listIndex := 0.
> -       fileName := nil.
> -       self changed: #fileList]!
>
> Item was changed:
>   ----- Method: FileChooserDialog>>fileListIndex: (in category 'file list') -----
>   fileListIndex: anInteger
> +       "We've selected the file at the given index, so find the file name."
> -       "We've selected the file at the given index,so find the file name."
>
>         self okToChange ifFalse: [^ self].
>         listIndex := anInteger.
>         listIndex = 0
>                 ifTrue: [fileName := nil]
> +               ifFalse: [fileName :=nameList at: anInteger].  "open the file selected"
> -               ifFalse:
> -                       [fileName := self fileNameFromFormattedItem: (list at: anInteger)].  "open the file selected"
>
> +       self  changed: #fileListIndex!
> -       self
> -               changed: #fileListIndex!
>
> Item was changed:
>   ----- Method: FileChooserDialog>>inputText (in category 'path and pattern') -----
>   inputText
>         "Answers path and pattern together"
> +
>         ^directory fullName, directory slash, pattern!
>
> Item was changed:
>   ----- Method: FileChooserDialog>>inputText: (in category 'path and pattern') -----
>   inputText: stringOrText
> +       "both path and pattern are in the text, so split them apart and then change both directory and the match for the filenames before updating the file list"
> +
> -       "both path and pattern are in the text, so split them apart"
>         | base pat aString |
>         aString := stringOrText asString.
>         base := aString copyUpToLast: directory pathNameDelimiter.
>         pat := aString copyAfterLast: directory pathNameDelimiter.
>         self changed: #inputText. "avoid asking if it's okToChange"
> +
> -       pattern := pat.
>         self directory: (FileDirectory on: base).
> +       self pattern: pat.
> +       self updateFileList.
>         self changed: #inputText.
>         self changed: #selectedPath.!
>
> Item was changed:
>   ----- Method: FileChooserDialog>>openOn:pattern: (in category 'initialize-release') -----
>   openOn: aDirectory pattern: aPatternString
>         "open a modal dialog to choose a file from aDirectory as filtered by aPattern"
>
>         directory := aDirectory.
> +       self pattern: aPatternString.
> -       pattern := aPatternString.
>
>         ToolBuilder open: self.
>         ^self finalChoice!
>
> Item was added:
> + ----- Method: FileChooserDialog>>userMessage (in category 'ui details') -----
> + userMessage
> +       "return the string to present to the user  in order to explain the purpose of this dialog appearing"
> +
> +       ^message ifNil:['Choose a file name']!
>
> Item was added:
> + ----- Method: FileSaverDialog class>>openOn:initialFilename: (in category 'instance creation') -----
> + openOn: aDirectory initialFilename: aString
> +       "open a modal dialog to save a file. Start the dialog with aDirectory selected and the suggested file name"
> +
> +       ^self new openOn: aDirectory  initialFilename: aString
> +
> +       !
>
> Item was added:
> + ----- Method: FileSaverDialog class>>openOnInitialFilename: (in category 'instance creation') -----
> + openOnInitialFilename: aString
> +       "open a modal dialog to save a file. Start the dialog with the default directory selected and the suggested file name"
> +
> +       ^self new openOn: FileDirectory default  initialFilename: aString
> +
> +       !
>
> Item was added:
> + ----- Method: FileSaverDialog>>acceptFileName (in category 'initialize-release') -----
> + acceptFileName
> +       "make sure to accept any edit in the filename before closing"
> +
> +       self changed: #acceptChanges.
> +       ^super acceptFileName!
>
> Item was changed:
>   ----- Method: FileSaverDialog>>fileListIndex: (in category 'file list') -----
>   fileListIndex: anInteger
> +       "We've selected the file at the given index, so find the file name."
> -       "We've selected the file at the given index,so find the file name."
>
>         self okToChange ifFalse: [^ self].
>         listIndex := anInteger.
>         listIndex = 0
>                 ifTrue: [fileName := nil]
> +               ifFalse: [fileName := nameList at: anInteger].  "open the file selected"
> -               ifFalse:
> -                       [fileName := self fileNameFromFormattedItem: (list at: anInteger)].  "open the file selected"
>
>         self
>                 changed: #fileListIndex;
>                 changed: #inputText!
>
> Item was changed:
>   ----- Method: FileSaverDialog>>inputText: (in category 'filename') -----
>   inputText: aText
> +       "user has entered a potential filename in the text field. If it is a file in the current list, highlight it"
> -       "user has entered a potential filename in the text field. If it is a file in the currect list, highlight it"
>
>         fileName := aText asString.
> +       listIndex := nameList findFirst:[: nm| nm = fileName].
> -       listIndex := list findFirst:[: nm| (self fileNameFromFormattedItem: nm) = fileName].
> -       listIndex = 0  ifFalse:
> -                       [fileName := self fileNameFromFormattedItem: (list at: listIndex)].
>
>         self
>                 changed: #fileListIndex;
> +               changed: #inputText!
> -               changed: #inputFilename!
>
> Item was removed:
> - ----- Method: FileSaverDialog>>selectedPath (in category 'path and pattern') -----
> - selectedPath
> -       | top here |
> -       top := FileDirectory root.
> -       here := directory.
> -       ^(Array streamContents:[:s| | next |
> -               s nextPut: here.
> -               [next := here containingDirectory.
> -               top pathName = next pathName] whileFalse:[
> -                       s nextPut: next.
> -                       here := next.
> -               ]]) reversed.!
>
> Item was added:
> + ----- Method: FileSaverDialog>>userMessage (in category 'ui details') -----
> + userMessage
> +       "return the string to present to the user  in order to explain the purpose of this dialog appearing"
> +
> +       ^message ifNil:['Choose a file name; you can also edit the name below to create a new file name']!
>
>


More information about the Squeak-dev mailing list