The Trunk: ToolBuilder-Morphic-mt.206.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: ToolBuilder-Morphic-mt.206.mcz

commits-2
Marcel Taeumel uploaded a new version of ToolBuilder-Morphic to project The Trunk:
http://source.squeak.org/trunk/ToolBuilder-Morphic-mt.206.mcz

==================== Summary ====================

Name: ToolBuilder-Morphic-mt.206
Author: mt
Time: 18 January 2018, 8:04:13.518364 am
UUID: 9cae2bea-8752-ba41-91d4-4dcea85b35b8
Ancestors: ToolBuilder-Morphic-tpr.205

Move new file dialogs into ToolBuilder-Morphic package due to its Morphic dependency. (Compares with ListChooser.)

=============== Diff against ToolBuilder-Morphic-tpr.205 ===============

Item was changed:
  SystemOrganization addCategory: #'ToolBuilder-Morphic'!
+ SystemOrganization addCategory: #'ToolBuilder-Morphic-Tools'!

Item was added:
+ FileAbstractSelectionDialog subclass: #DirectoryChooserDialog
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'ToolBuilder-Morphic-Tools'!
+
+ !DirectoryChooserDialog commentStamp: 'tpr 12/21/2017 11:32' prior: 0!
+ A DirectoryChooserDialog is a modal dialog to allow choosing a directory. The full directory name is returned, or nil if no selection was made.
+
+ Normal usage would be
+ myDirname := DirectoryChooserDialog openOn: myApplicationDefaultDirectory label: 'Choose the directory to use'
+ !

Item was added:
+ ----- Method: DirectoryChooserDialog class>>openOn:label: (in category 'instance creation') -----
+ openOn: aDirectory label: labelString
+ "open a directory chooser starting with aDirectory"
+
+ "DirectoryChooserDialog openOn: FileDirectory default label: 'Choose the directory to use' "
+
+ ^super new
+ directory: aDirectory;
+ message: labelString;
+ getUserResponse!

Item was added:
+ ----- Method: DirectoryChooserDialog>>acceptFileName (in category 'initialize-release') -----
+ acceptFileName
+ "User clicked to accept the current state so save the directory and close the dialog"
+
+ finalChoice := directory.
+ self changed: #close!

Item was added:
+ ----- Method: DirectoryChooserDialog>>buildWith: (in category 'toolbuilder') -----
+ buildWith: builder
+ "assemble the spec for the chooser dialog UI"
+
+ | windowSpec window |
+ windowSpec := self buildWindowWith: builder specs: {
+ (self frameOffsetFromTop: 0
+ fromLeft: 0
+ width: 1
+ offsetFromBottom: 0) -> [self buildDirectoryTreeWith: builder].
+ }.
+ windowSpec buttons addAll: ( self buildButtonsWith: builder ).
+ window := builder build: windowSpec.
+ window addKeyboardCaptureFilter: self.
+ self changed: #selectedPath.
+ ^window
+ !

Item was added:
+ ----- Method: DirectoryChooserDialog>>finalChoice (in category 'ui details') -----
+ finalChoice
+ "return the chosen directory that was saved by an accept click or nil; client must check for validity"
+
+ ^ finalChoice
+ ifNotNil: [self directory]!

Item was added:
+ ----- Method: DirectoryChooserDialog>>initialExtent (in category 'toolbuilder') -----
+ initialExtent
+ "Since this is a single list it can be a bit narrower than a FileChooserDialog"
+
+ ^ super initialExtent * (0.5 @ 1)!

Item was added:
+ ----- Method: DirectoryChooserDialog>>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 directory name']!

Item was added:
+ Model subclass: #FileAbstractSelectionDialog
+ instanceVariableNames: 'patternList directory directoryCache message listIndex fileName finalChoice nameList sizeList dateList'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'ToolBuilder-Morphic-Tools'!
+
+ !FileAbstractSelectionDialog commentStamp: 'tpr 11/21/2017 18:18' prior: 0!
+ FileAbstractSelectionDialog is the abstract superclass for the file chooser & saver modal dialogs.
+
+ The UI provides a message  to the user, 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
+ patternList: <OrderedCollection of String> the patterns are held as a collection of string that may include * or # wildcards. See FileAbstractSelectionDialog>>#parsePatternString for details
+ message: <String> a message to the user to explain what is expected
+ nameList,DateList, sizeList: <Array> the list of file names matching the pattern and the appropriate date and size values, formatted for a PluggableMultiColumnListMorph!

Item was added:
+ ----- 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 added:
+ ----- Method: FileAbstractSelectionDialog>>buildButtonsWith: (in category 'toolbuilder') -----
+ buildButtonsWith: builder
+
+ ^ {
+ builder pluggableButtonSpec new
+ model: self;
+ label: 'Accept' translated;
+ color: (self userInterfaceTheme get: #okColor for: #DialogWindow);
+ action: #acceptFileName.
+ builder pluggableButtonSpec new
+ model: self;
+ label: 'Cancel';
+ color: (self userInterfaceTheme get: #cancelColor for: #DialogWindow);
+ action: #cancelFileChooser}!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>buildDirectoryTreeWith: (in category 'toolbuilder') -----
+ buildDirectoryTreeWith: builder
+ | treeSpec |
+ treeSpec := builder pluggableTreeSpec new.
+ treeSpec
+ model: self ;
+ roots: #rootDirectoryList ;
+ hasChildren: #hasMoreDirectories: ;
+ getChildren: #subDirectoriesOf: ;
+ getSelectedPath: #selectedPath ;
+ setSelected: #setDirectoryTo: ;
+ getSelected: #directory;
+ label: #directoryNameOf: ;
+ menu: nil ;
+ autoDeselect: false.
+ ^ treeSpec!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>buildFileListWith: (in category 'toolbuilder') -----
+ buildFileListWith: builder
+ | listSpec |
+ listSpec := builder pluggableMultiColumnListSpec 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 .
+ ^listSpec!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>buildTextInputWith: (in category 'toolbuilder') -----
+ buildTextInputWith: builder
+ | textSpec |
+ textSpec := builder pluggableInputFieldSpec new.
+ textSpec
+ model: self;
+ font: self textViewFont;
+ getText: #inputText;
+ setText: #inputText:.
+ ^textSpec
+ !

Item was added:
+ ----- 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;
+ spacing: self viewSpacing;
+ children: OrderedCollection new;
+ buttons: OrderedCollection new.
+ ^windowSpec!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>buildWith: (in category 'toolbuilder') -----
+ buildWith: builder
+ "assemble the spec for the common chooser/saver dialog UI"
+
+ ^self subclassResponsibility!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>buttonHeight (in category 'ui details') -----
+ buttonHeight
+
+ ^ Preferences standardButtonFont height * 2!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>cancelFileChooser (in category 'initialize-release') -----
+ cancelFileChooser
+ "User clicked to cancel the current state so nil the filename and close the dialog"
+
+ directory := finalChoice := fileName := nil.
+ self changed: #close.!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>defaultPatternList (in category 'path and pattern') -----
+ defaultPatternList
+
+ ^#('*')!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>directory (in category 'directory tree') -----
+ directory
+ "If nobody has set a specific directory we need a plausible default"
+
+ ^ directory ifNil: [ directory := FileDirectory default]!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>directory: (in category 'directory tree') -----
+ directory: aFileDirectory
+ "Set the path of the directory to be displayed in the directory tree pane"
+
+ directory := aFileDirectory!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>directoryNameOf: (in category 'directory tree') -----
+ directoryNameOf: aDirectory
+ "Return a name for the selected directory in the tree view"
+
+ ^aDirectory localName!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>entriesMatching: (in category 'file list') -----
+ entriesMatching: patternList
+ "Answer a list of directory entries which match any of the patterns.
+ See #parsePatternString for the pattern rules"
+
+ | entries  |
+ "This odd clause helps supports MVC projects; the file list & directory views are built from a list that includes directories. In Morphic we filter out the directories because they are entirely handled by the direcctory tree morph"
+ entries := Smalltalk isMorphic
+ ifTrue:[self directory fileEntries ]
+ ifFalse:[self directory entries].
+
+ (patternList anySatisfy: [:each | each = '*'])
+ ifTrue: [^ entries].
+
+ ^ entries select: [:entry | patternList anySatisfy: [:each | each match: entry name]]!

Item was added:
+ ----- 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!

Item was added:
+ ----- 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"
+
+ ^listIndex!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>fileListIndex: (in category 'file list') -----
+ fileListIndex: anInteger
+ "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"
+
+ self
+ changed: #fileListIndex;
+ changed: #inputText!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>filterEvent:for: (in category 'event handling') -----
+ filterEvent: aKeyboardEvent for: aMorph
+
+ | char |
+ aKeyboardEvent isKeystroke ifFalse: [^ aKeyboardEvent].
+ aKeyboardEvent anyModifierKeyPressed ifTrue: [^ aKeyboardEvent].
+
+ char := aKeyboardEvent keyCharacter.
+
+ (char = Character cr or: [char = Character enter])
+ ifTrue: [self acceptFileName. aKeyboardEvent ignore].
+ char = Character escape
+ ifTrue: [self cancelFileChooser. aKeyboardEvent ignore].
+
+ ^ aKeyboardEvent!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>finalChoice (in category 'initialize-release') -----
+ finalChoice
+ "return the chosen directory/filename that was saved by an accept click or nil; client must check for validity"
+ ^ finalChoice
+ ifNotNil: [self directory fullNameFor: finalChoice]!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>frameOffsetFromTop:fromLeft:width:bottomFraction: (in category 'ui details') -----
+ frameOffsetFromTop: height fromLeft: leftFraction width: widthFraction bottomFraction: bottomFraction
+ "return a layout frame that starts at the fixed upper offset and goes down to the bottomFraction, and runs widthFraction from the leftFraction"
+
+ ^LayoutFrame new
+ topFraction: 0 offset: height;
+ leftFraction: leftFraction offset: 0;
+ rightFraction: (leftFraction + widthFraction) offset: 0;
+ bottomFraction: bottomFraction offset: 0;
+ yourself.!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>frameOffsetFromTop:fromLeft:width:offsetFromBottom: (in category 'ui details') -----
+ frameOffsetFromTop: height fromLeft: leftFraction width: widthFraction offsetFromBottom: bottomOffset
+ "return a layout frame that starts at the fixed upper offset and goes down to the bottom - the offsetn, and runs widthFraction from the leftFraction"
+
+ ^LayoutFrame new
+ topFraction: 0 offset: height;
+ leftFraction: leftFraction offset: 0;
+ rightFraction: (leftFraction + widthFraction) offset: 0;
+ bottomFraction: 1 offset: bottomOffset negated;
+ yourself.!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>getUserResponse (in category 'toolbuilder') -----
+ getUserResponse
+ "open the dialog modally and get a user response"
+
+ ToolBuilder open: self.
+ ^self finalChoice!

Item was added:
+ ----- 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 hasSubDirectories] on: Error do:[:ex| true].
+ ].!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>initialize (in category 'initialize-release') -----
+ initialize
+ super initialize.
+ directoryCache := WeakIdentityKeyDictionary new.
+ listIndex := 0.
+ patternList := self defaultPatternList!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>listForPatterns: (in category 'path and pattern') -----
+ listForPatterns: arrayOfPatterns
+ "build lists of name, date and size for those file names which match any of the patterns in the array.
+ We use a Set to avoid duplicates and sort them by name"
+
+ | newList |
+ newList := Set new.
+ newList addAll: (self entriesMatching: arrayOfPatterns).
+
+ 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]
+ !

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>message: (in category 'ui details') -----
+ message: aStringOrText
+ "set the user message to be dispalyed at the top of the dialog - it should guide the user as to what they must do"
+
+ message := aStringOrText!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>parsePatternString: (in category 'file list') -----
+ parsePatternString: aStringOrNil
+ "The pattern is 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 |
+ aStringOrNil ifNil:[^self defaultPatternList].
+ patterns := OrderedCollection new.
+ (aStringOrNil findTokens: (String with: Character cr with: Character lf with: $;))
+ do: [ :each |
+ (each includes: $*) | (each includes: $#)
+ ifTrue: [ patterns add: each]
+ ifFalse: [each isEmptyOrNil
+ ifTrue: [ patterns add: '*']
+ ifFalse: [ patterns add: '*' , each , '*']]].
+
+ ^patterns!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>pattern: (in category 'path and pattern') -----
+ pattern: textOrStringOrNil
+ "Make sure the pattern source string is neither nil nor empty.
+ We can strictly speaking handle arbitrary patterns to match against the filenames but in general we need to use suffices, so see #suffix: and #suffixList: "
+
+ patternList := self parsePatternString: textOrStringOrNil!

Item was added:
+ ----- 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 root.
+ dirList := self subDirectoriesOf: dir.
+ dirList isEmpty ifTrue:[dirList := Array with: FileDirectory default].
+ ^dirList ,(ServerDirectory servers values) "looks odd because #servers returns the Dictionary of known servers with local names instead of the actaul server directories"!

Item was added:
+ ----- 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 := self 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: 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].
+ "okToChange is probably redundant.
+ modelSleep/Wake is related to use of ServerDirectories, which are not yet hooked up"
+ self okToChange ifFalse: [ ^ self ].
+ self modelSleep.
+ self directory: dir.
+ self modelWakeUp.
+ self changed: #directory.
+ self updateFileList.
+ self changed: #inputText!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>subDirectoriesOf: (in category 'directory tree') -----
+ subDirectoriesOf: aDirectory
+
+ ^aDirectory directoryNames collect:[:each| aDirectory directoryNamed: each].!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>suffix: (in category 'path and pattern') -----
+ suffix: textOrStringOrNil
+ "Make a pattern from a single filename suffix string, i.e. 'jpg'"
+
+ self suffixList: (Array with: textOrStringOrNil )!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>suffixList: (in category 'path and pattern') -----
+ suffixList: listOfStrings
+ "Make a pattern list from a one or more filename suffix strings in a list , i.e. #('jpg' 'mpeg') "
+
+ listOfStrings isEmptyOrNil
+ ifTrue: [patternList := self defaultPatternList]
+ ifFalse: [patternList := OrderedCollection new.
+ listOfStrings do: [:each|
+ each isEmptyOrNil ifFalse:[ patternList add: '*.',each] ] ]!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>textViewFont (in category 'ui details') -----
+ textViewFont
+
+ ^ Preferences standardDefaultTextFont!

Item was added:
+ ----- 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 added:
+ ----- Method: FileAbstractSelectionDialog>>topConstantHeightFrame:fromLeft:width: (in category 'ui details') -----
+ topConstantHeightFrame: height fromLeft: leftFraction width: widthFraction
+ "return a layout to make a fixed height frame that starts at the top of its parent and runs widthFraction from the leftFraction."
+
+ ^LayoutFrame new
+ topFraction: 0 offset: 0;
+ leftFraction: leftFraction offset: 0;
+ rightFraction: (leftFraction + widthFraction) offset: 0;
+ bottomFraction: 0 offset: height;
+ yourself.!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>updateFileList (in category 'file list') -----
+ updateFileList
+ "Update my files list with file names in the current directory that match the patternList."
+
+ Cursor wait
+ showWhile: [self listForPatterns: patternList.
+ listIndex := 0.
+ self changed: #fileList]!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>viewSpacing (in category 'ui details') -----
+ viewSpacing
+
+ ^ 5 "pixels"!

Item was added:
+ FileAbstractSelectionDialog subclass: #FileChooserDialog
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'ToolBuilder-Morphic-Tools'!
+
+ !FileChooserDialog commentStamp: 'dtl 12/21/2017 22:18' prior: 0!
+ A FileChooserDialog is a modal dialog to allow choosing a file. The full file name is returned, or nil if no selection was made.
+
+ Normal usage would be
+ myFilename := FileChooserDialog openOn: myApplicationDefaultDirectory pattern: '*.myapp' label: 'Choose the file to load'
+ to find a file with a name matching *.myapp and with the directory initial choice set to myApplicationDefaultDirectory.  Only filenames matching the pattern will appear in the file list view.
+ !

Item was added:
+ ----- Method: FileChooserDialog class>>openOn: (in category 'instance creation') -----
+ openOn: aDirectory
+ "Open a modal dialog to choose a file. Start the dialog with aDirectory selected
+ and files matching the default 'everything' pattern"
+
+ "FileChooserDialog openOn: FileDirectory default"
+
+ ^self openOn: aDirectory pattern: nil label: nil
+ !

Item was added:
+ ----- Method: FileChooserDialog class>>openOn:pattern:label: (in category 'instance creation') -----
+ openOn: aDirectory pattern: matchString label: labelString
+ "Open a modal dialog to choose a file. Start the dialog with aDirectory selected
+ and files matching the matchString pattern. Set the user message to labelString."
+
+ "FileChooserDialog openOn: FileDirectory default pattern: '*.changes' label: 'Do something with the selected files' "
+
+ ^self new
+ directory: aDirectory;
+ pattern: matchString;
+ message: labelString;
+ getUserResponse!

Item was added:
+ ----- Method: FileChooserDialog class>>openOn:suffixList:label: (in category 'instance creation') -----
+ openOn: aDirectory suffixList: patternList label: labelString
+ "Open a modal dialog to choose a file. Start the dialog with aDirectory selected
+ and files matching the file name suffixes in patternList. Set the user message
+ to labelString."
+
+ "FileChooserDialog openOn: FileDirectory default suffixList: { '*.changes' . '*image' } label: 'Do something with the selected files' "
+
+ ^self new
+ directory: aDirectory;
+ suffixList: patternList;
+ message: labelString;
+ getUserResponse!

Item was added:
+ ----- Method: FileChooserDialog class>>openOnPattern:label: (in category 'instance creation') -----
+ openOnPattern: matchString label: labelString
+ "Open a modal dialog to choose a file. Start the dialog with a default directory
+ selected and with files matching the default 'everything' pattern  Set the user
+ message to labelString"
+
+ "FileChooserDialog openOnPattern: '*.changes' label: 'Do something with the selected files' "
+
+ ^self openOn: nil pattern: matchString label: labelString
+ !

Item was added:
+ ----- Method: FileChooserDialog class>>openOnSuffixList:label: (in category 'instance creation') -----
+ openOnSuffixList: patternList label: labelString
+ "Open a modal dialog to choose a file. Start the dialog with a default directory
+ selected and with files matching the file name suffixes in patternList. Set the
+ user message to labelString."
+
+ "FileChooserDialog openOnSuffixList: { '*.changes' . '*image' } label: 'Do something with the selected files' "
+
+ ^self openOn: nil suffixList: patternList label: labelString
+ !

Item was added:
+ ----- Method: FileChooserDialog>>buildWith: (in category 'toolbuilder') -----
+ buildWith: builder
+ "assemble the spec for the chooser dialog UI"
+
+ | windowSpec window |
+ windowSpec := self buildWindowWith: builder specs: {
+ (self frameOffsetFromTop: 0
+ fromLeft: 0.25
+ width: 0.75
+ offsetFromBottom: 0) -> [self buildFileListWith: builder].
+ (self frameOffsetFromTop: 0
+ fromLeft: 0
+ width: 0.25
+ offsetFromBottom: 0) -> [self buildDirectoryTreeWith: builder].
+ }.
+ windowSpec buttons addAll: ( self buildButtonsWith: builder ).
+ window := builder build: windowSpec.
+ window addKeyboardCaptureFilter: self.
+ self changed: #selectedPath.
+ ^window
+ !

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: FileChooserDialog>>windowTitle (in category 'ui details') -----
+ windowTitle
+ "return the window label; would be some application dependent string but I suspect we will want to make the outer morph a dialogue box with no label anyway"
+
+ ^'File Chooser'!

Item was added:
+ FileAbstractSelectionDialog subclass: #FileSaverDialog
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'ToolBuilder-Morphic-Tools'!
+
+ !FileSaverDialog commentStamp: 'dtl 12/21/2017 22:47' prior: 0!
+ A FileSaverDialog is a modal dialog for choosing a file name to use for saving a file.
+
+ Users can enter a filename in the text input view that will
+ a) if it exists in the current directry listing, be selected
+ b) over ride any filenames in the current directory, providing a way to specify a completely new file.
+ This will not affect the selected directory path.
+
+ Normal usage would be
+ myFilename := FileSaverDialog openOnInitialFilename: myApp saveFileName
+ which would derive a directory, an initial filename and filename suffix from the given file name. Thus a typical application save might be
+ ...  openOnInitialFilename: '/home/pi/myApp/examplePicture.jpg'
+ and would set the initial directory to /home/pi/myapp, the initial filename to examplePicture.jpg and set a suffix pattern of 'jpg'. Only filenames with the specified suffix will appear in the file list view. It is possible to specify several suffices, (see #suffixList:) and use wildcards within the suffix.
+
+ myFilename := FileSaverDialog openOn: myApplicationDefaultDirectory initialFilename: 'foo.myapp'
+ would set directory initial choice set to myApplicationDefaultDirectory and ignore any directory found in the filename. It would be quite possible to choose a file from any other directory and with any other name  that matches the suffix if the user wishes, so the file name must be carefully checked.
+
+ The full set of options would involve
+ myFilename := FileSaverDialog  openOn: myApplicationDefaultDirectory initialFilename: 'foo.myapp' suffix: 'mya' message: 'Save your myApp file to ... '
+
+ It is also possible to set a more general pattern to match filenames against but since this seems less useful for normal application usage there are no convenience messages as yet.
+
+ See the class side methods for details. See my parent class for most implementation details!

Item was added:
+ ----- Method: FileSaverDialog class>>openOn: (in category 'instance creation') -----
+ openOn: aDirectory
+ "open a modal dialog to save a file. Start the dialog with aDirectory selected
+ and no suggested file name"
+
+ "FileSaverDialog openOn: FileDirectory default"
+
+ ^self openOn: aDirectory initialFilename: nil label: nil
+ !

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 aString as the suggested file name. Note that we set the directory after
+ the initialFilename becuase we want a specific directory and not neccesarily
+ the directory of the file."
+
+ "FileSaverDialog openOn: FileDirectory default initialFilename: 'aSuggestedFileName' "
+
+ ^self openOn: aDirectory initialFilename: aString label: nil
+ !

Item was added:
+ ----- Method: FileSaverDialog class>>openOn:initialFilename:label: (in category 'instance creation') -----
+ openOn: aDirectory initialFilename: aString label: labelString
+ "Open a modal dialog to save a file. Start the dialog with aDirectory selected
+ and aString as the suggested file name. Set the user message to labelString.
+ Note that we set the directory after the initialFilename becuase we want a
+ specific directory and not neccesarily the directory of the file"
+
+ "FileSaverDialog openOn: FileDirectory default initialFilename: 'aSuggestedFileName' label: 'Select a flie and do something with it' "
+
+ ^self new
+ initialFilename: aString;
+ directory: aDirectory;
+ message: labelString;
+ getUserResponse
+
+ !

Item was added:
+ ----- Method: FileSaverDialog class>>openOnInitialFilename: (in category 'instance creation') -----
+ openOnInitialFilename: filenameString
+ "Open a modal dialog to save a file. Start the dialog with the default directory
+ selected and the suggested file name."
+
+ "FileSaverDialog openOnInitialFilename: 'aSuggestedFileName' "
+
+ ^self openOn: nil initialFilename: filenameString label: nil
+ !

Item was added:
+ ----- Method: FileSaverDialog class>>openOnInitialFilename:label: (in category 'instance creation') -----
+ openOnInitialFilename: filenameString label: labelString
+ "Open a modal dialog to save a file. Start the dialog with the default directory
+ selected and the suggested file name, set the user message to labelString"
+
+ "FileSaverDialog openOnInitialFilename: 'aSuggestedFileName' label: 'Select a flie and do something with it' "
+
+ ^self openOn: nil initialFilename: filenameString label: labelString
+ !

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 added:
+ ----- Method: FileSaverDialog>>buildWith: (in category 'toolbuilder') -----
+ buildWith: builder
+ "assemble the spec for the saver dialog UI and build the window"
+
+ | window windowSpec |
+ windowSpec := self buildWindowWith: builder specs: {
+ (self topConstantHeightFrame: self textViewHeight + self viewSpacing
+ fromLeft: 0
+ width: 1) -> [self buildTextInputWith: builder].
+ (self frameOffsetFromTop: self textViewHeight + self viewSpacing
+ fromLeft: 0.25
+ width: 0.75
+ offsetFromBottom: 0) -> [self buildFileListWith: builder].
+ (self frameOffsetFromTop: self textViewHeight + self viewSpacing
+ fromLeft: 0
+ width: 0.25
+ offsetFromBottom: 0) -> [self buildDirectoryTreeWith: builder].
+ }.
+ windowSpec buttons addAll: ( self buildButtonsWith: builder ).
+ window := builder build: windowSpec.
+ window addKeyboardCaptureFilter: self.
+ self changed: #selectedPath.
+ self inputText: fileName.
+ ^window
+ !

Item was added:
+ ----- Method: FileSaverDialog>>initialFilename: (in category 'initialize-release') -----
+ initialFilename: aFilenameOrNil
+ "Set the initial choice of filename to highlight.
+ We split the potential filename to see if it includes a path and if so, use that as the chosen directory - the client can manually change that with a subsequent send of #directory: if wanted.
+ We split the root filename to find an extension and use that as the suffix - again, the client can manually change that later"
+
+ | e f p |
+ aFilenameOrNil ifNil:[^self].
+
+ p := FileDirectory dirPathFor: aFilenameOrNil.
+ p isEmpty ifFalse:[self directory: (FileDirectory on: p)].
+ f := FileDirectory localNameFor: aFilenameOrNil.
+ fileName := f.
+ e := FileDirectory extensionFor: f.
+ e isEmpty ifFalse:[self suffix: e]!

Item was added:
+ ----- Method: FileSaverDialog>>inputText (in category 'filename') -----
+ inputText
+ "return the filename to appear in the text field"
+
+ ^fileName ifNil:['Enter a filename here or choose from list' translated]!

Item was added:
+ ----- Method: FileSaverDialog>>inputText: (in category 'filename') -----
+ inputText: aText
+ "user has entered a potential filename in the text field.
+ Check it against the current pattern; if it is ok we can accept it and then if it is a file in
+ the current list, highlight it.
+ If it would not match the pattern, alert the user as best we can"
+ | candidate |
+ candidate := aText asString.
+ (patternList anySatisfy: [:p | p match: candidate])
+ ifTrue: [fileName := candidate.
+ listIndex := nameList findFirst: [:nm | nm = fileName].
+ self changed: #fileListIndex.
+ ^true]
+ ifFalse: [fileName := nil.
+ self changed: #flash.
+ ^false]!

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']!

Item was added:
+ ----- Method: FileSaverDialog>>windowTitle (in category 'ui details') -----
+ windowTitle
+ "return the window label; would be some application dependent string but I suspect we will want to make the outer morph a dialogue box with no label anyway"
+
+ ^'FileSaver'!

Item was changed:
  Model subclass: #ListChooser
  instanceVariableNames: 'selectedIndex items searchText addAllowed result title listMorph dialogMorph'
  classVariableNames: ''
  poolDictionaries: ''
+ category: 'ToolBuilder-Morphic-Tools'!
- category: 'ToolBuilder-Morphic'!
 
  !ListChooser commentStamp: 'MAD 3/14/2010 16:20' prior: 0!
  I am a simple dialog to allow the user to pick from a list of strings or symbols.
  I support keyboard and mouse navigation, and interactive filtering of the displayed items.
 
  You can specify whether you want the index, or the value of the selected item. If you're interested in the value, you can also allow users to Add a new value not in the list.
 
  cmd-s or <enter> or double-click answers the currently selected item's value/index;
  cmd-l or <escape> or closing the window answers nil/zero.
 
  Now using ToolBuilder, so needs Morphic-MAD.381.
 
  Released under the MIT Licence.!

Item was changed:
  Model subclass: #ListMultipleChooser
  instanceVariableNames: 'selection labels values title choice'
  classVariableNames: ''
  poolDictionaries: ''
+ category: 'ToolBuilder-Morphic-Tools'!
- category: 'ToolBuilder-Morphic'!
 
  !ListMultipleChooser commentStamp: 'mt 4/14/2015 17:09' prior: 0!
  I am like the ListChooser but for multiple choices. I have no extra search field. Enable the preference #filterableLists if lists get too big to choose from. Also, I do not support adding new items to the choice.!