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

commits at source.squeak.org commits at source.squeak.org
Wed Nov 22 02:24:58 UTC 2017


tim Rowledge uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-tpr.775.mcz

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

Name: Tools-tpr.775
Author: tpr
Time: 21 November 2017, 6:24:43.547157 pm
UUID: 7acfda2c-b48e-4d7e-8504-abba58b1a5e8
Ancestors: Tools-dtl.774

Change FileSaverDialog etc to prefer to use filename suffices instead of general patterns - though the patterns still work - and rework the way they are built to allow a bit more flexibility.
Remove the text entry view from the FileChooserDialog since it served no very helpful purpose.

=============== Diff against Tools-dtl.774 ===============

Item was changed:
  Model subclass: #FileAbstractSelectionDialog
+ 	instanceVariableNames: 'patternList directory directoryCache message listIndex fileName finalChoice nameList sizeList dateList'
- 	instanceVariableNames: 'pattern directory directoryCache message listIndex fileName finalChoice nameList sizeList dateList'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tools-FileDialogs'!
  
+ !FileAbstractSelectionDialog commentStamp: 'tpr 11/21/2017 18:18' prior: 0!
- !FileAbstractSelectionDialog commentStamp: 'tpr 11/13/2017 11:08' 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
- 	pattern:		<String> the pattern is held as a string that may include * or # wildcasrds. 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 removed:
- ----- Method: FileAbstractSelectionDialog class>>open (in category 'instance creation') -----
- open
- 	"open a modal dialog to choose or save a file. Start the dialog with the default directory selected"
- 
- 	^self openOn: FileDirectory default
- 
- 	!

Item was changed:
  ----- Method: FileAbstractSelectionDialog>>buildWith: (in category 'toolbuilder') -----
  buildWith: builder
  	"assemble the spec for the common chooser/saver dialog UI"
  
+ 	^self subclassResponsibility!
- 	| 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 removed:
- ----- Method: FileAbstractSelectionDialog>>defaultPattern (in category 'path and pattern') -----
- defaultPattern
- 
- 	^'*'!

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

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: [ directory := FileDirectory default]!
- 	^ directory ifNil: [ FileDirectory default]!

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"
  
+ 	directory := aFileDirectory!
- 	self okToChange ifFalse: [ ^ self ].
- 	self modelSleep.
- 	directory := aFileDirectory.
- 	self modelWakeUp.
- 	self changed: #directory!

Item was changed:
  ----- 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].
- 		ifTrue:[directory fileEntries ]
- 		ifFalse:[directory entries].
  
  	(patternList anySatisfy: [:each | each = '*'])
  		ifTrue: [^ entries].
  
  	^ entries select: [:entry | patternList anySatisfy: [:each | each match: entry name]]!

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>>getUserResponse (in category 'toolbuilder') -----
+ getUserResponse	
+ 	"open the dialog modally and get a user response"
+ 
+ 	ToolBuilder open: self.
+ 	^self finalChoice!

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

Item was changed:
  ----- 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"
- 	"return a list of those file names which match any of the patterns in the array."
  
  	| 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 removed:
- ----- 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 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 changed:
  ----- 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: "
- 	"Make sure the pattern source string is neither nil nor empty"
  
+ 	patternList := self parsePatternString: textOrStringOrNil!
- 	textOrStringOrNil
- 		ifNil: [pattern := '*']
- 		ifNotNil: [pattern := textOrStringOrNil asString].
- 	pattern isEmpty ifTrue: [pattern := '*']!

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

Item was changed:
  FileAbstractSelectionDialog subclass: #FileChooserDialog
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tools-FileDialogs'!
  
+ !FileChooserDialog commentStamp: 'tpr 11/21/2017 18:02' prior: 0!
- !FileChooserDialog commentStamp: 'tpr 11/13/2017 11:46' 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.
- Users can enter a pattern in the text input field that will be read as a directory path and an optional pattern (see comments about pattern in my superclass) to define the files in the file list. 
  
  Normal usage would be 
  	myFilename := FileChooserDialog openOn: myApplicationDefaultDirectory pattern: '*.myapp' message: '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.
+ !
- to find a file with a name matching *.myapp and with the directory initial choice set to myApplicationDefaultDirectory. It would be quite possible to choose a file from any other directory and with any other pattern match if the user wishes, so the file name must be carefully checked.
- 
- Simpler usage might be
- 	myFilename := FileChooserDialog open
- or
- 	myFilename := FileChoosverDialog openOn: FileDirectory default	
- - see the class side methods for details. See my parent class for most implementation details!

Item was changed:
  ----- 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"
  
+ 	^self new directory: aDirectory;
+ 		getUserResponse!
- 	^self openOn: aDirectory pattern: nil
- 
- 	!

Item was removed:
- ----- Method: FileChooserDialog class>>openOn:pattern: (in category 'instance creation') -----
- openOn: aDirectory pattern: aPatternString
- 	"open a modal dialog to choose a file. Start the dialog with aDirectory selected and files matching the pattern"
- 
- 	^self new openOn: aDirectory pattern: aPatternString
- 
- 	!

Item was removed:
- ----- Method: FileChooserDialog class>>openOn:pattern:message: (in category 'instance creation') -----
- openOn: aDirectory pattern: aPatternString message: messageString
- 	"open a modal dialog to choose a file. Start the dialog with aDirectory selected and files matching the pattern"
- 
- 	^self new openOn: aDirectory pattern: aPatternString message: messageString
- 
- 	!

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: self buttonHeight) -> [self buildFileListWith: builder].
+ 		(self frameOffsetFromTop: 0
+ 			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 removed:
- ----- Method: FileChooserDialog>>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!

Item was removed:
- ----- Method: FileChooserDialog>>inputText (in category 'path and pattern') -----
- inputText
- 	"Answers path and pattern together"
- 
- 	^directory fullName, directory slash, pattern!

Item was removed:
- ----- 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"
- 
- 	| 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"
- 
- 	self directory: (FileDirectory on: base).
- 	self pattern: pat.
- 	self updateFileList.
- 	self changed: #inputText.
- 	self changed: #selectedPath.!

Item was removed:
- ----- 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"
- 
- 	^self openOn: aDirectory pattern: aPatternString message: nil
- !

Item was removed:
- ----- Method: FileChooserDialog>>openOn:pattern:message: (in category 'initialize-release') -----
- openOn: aDirectory pattern: aPatternString message: messageString
- 	"open a modal dialog to choose a file from aDirectory as filtered by aPattern"
- 
- 	directory := aDirectory.
- 	self pattern: aPatternString.
- 	message := messageString.
- 	
- 	ToolBuilder open: self.
- 	^self finalChoice!

Item was changed:
  FileAbstractSelectionDialog subclass: #FileSaverDialog
  	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tools-FileDialogs'!
  
+ !FileSaverDialog commentStamp: 'tpr 11/21/2017 17:53' prior: 0!
- !FileSaverDialog commentStamp: 'tpr 11/13/2017 11:49' 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.
- b) over ride any filenames in the current directry, 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. 
- to find a file with a name matching foo.myapp and with the directory initial choice set to myApplicationDefaultDirectory. It would be quite possible to choose a file from any other directory and with any other name if the user wishes, so the file name must be carefully checked. The full set of options would invovle
- 	myFilename := FileSaverDialog  openOn: myApplicationDefaultDirectory initialFilename: 'foo.myapp' pattern: '*.mya' message: 'Save your myApp file to ... '
  
+ 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 ther are no convenience messages as yet.
+ 
+ See the class side methods for details. See my parent class for most implementation details!
- Simpler usage might be
- 	myFilename := FileSaverDialog open
- or
- 	myFilename := FileSaverDialog openOn: FileDirectory default
- - see the class side methods for details. See my parent class for most implementation details!

Item was changed:
  ----- 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"
  
+ 	^self new directory: aDirectory;
+ 		getUserResponse
- 	^self new openOn: aDirectory  initialFilename: nil
  
  	!

Item was changed:
  ----- 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. Note that we set the directory after the initialFilename becuase we want a specific directory and not neccesarily the directory of the file"
- 	"open a modal dialog to save a file. Start the dialog with aDirectory selected and the suggested file name"
  
+ 	^self new 
+ 		initialFilename: aString;
+ 		directory: aDirectory;
+ 		getUserResponse
- 	^self new openOn: aDirectory  initialFilename: aString
  
  	!

Item was removed:
- ----- Method: FileSaverDialog class>>openOn:initialFilename:pattern: (in category 'instance creation') -----
- openOn: aDirectory initialFilename: aString pattern: patternString
- 	"open a modal dialog to save a file. Start the dialog with aDirectory selected and the suggested file name. Visible filenames are limited by the pattern"
- 
- 	^self new openOn: aDirectory  initialFilename: aString pattern: patternString
- 
- 	!

Item was removed:
- ----- Method: FileSaverDialog class>>openOn:initialFilename:pattern:message: (in category 'instance creation') -----
- openOn: aDirectory initialFilename: aString pattern: patternString message: messageString
- 	"open a modal dialog to save a file. Start the dialog with aDirectory selected and the suggested file name. Visible filenames are limited by the pattern. Use the messageString to explain what ther user needs to know"
- 
- 	^self new openOn: aDirectory  initialFilename: aString pattern: patternString message: messageString
- 
- 	!

Item was changed:
  ----- Method: FileSaverDialog class>>openOnInitialFilename: (in category 'instance creation') -----
+ openOnInitialFilename: filenameString
- 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 initialFilename: filenameString;
+ 		getUserResponse
- 	^self new openOn: FileDirectory default  initialFilename: aString
  
  	!

Item was changed:
  ----- Method: FileSaverDialog>>buildWith: (in category 'toolbuilder') -----
  buildWith: builder
+ 	"assemble the spec for the saver dialog UI and build the window"
- 	"assemble the spec for the common chooser/saver dialog UI"
  
+ 	| window windowSpec |
+ 	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  |
- 	window := super buildWith: builder.
  	self inputText: fileName.
  	^window
  !

Item was removed:
- ----- Method: FileSaverDialog>>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: FileSaverDialog>>initialFilename: (in category 'initialize-release') -----
+ initialFilename: aFilename
+ 	"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 |
+ 	p := FileDirectory dirPathFor: aFilename.
+ 	p isEmpty ifFalse:[self directory: (FileDirectory on: p)].	
+ 	f := FileDirectory localNameFor: aFilename.
+ 	fileName := f.
+ 	e := FileDirectory extensionFor: f.
+ 	e isEmpty ifFalse:[self suffix: e]!

Item was changed:
  ----- 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]!
- 	^fileName ifNil:['Enter a filename here']!

Item was changed:
  ----- 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])
- 	(self parsePatternString 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 removed:
- ----- Method: FileSaverDialog>>openOn:initialFilename: (in category 'initialize-release') -----
- openOn: aDirectory initialFilename: aFilename
- 	"open a modal dialog to choose a file name to save to aDirectory"
- 
- 	^self openOn: aDirectory initialFilename: aFilename pattern: nil!

Item was removed:
- ----- Method: FileSaverDialog>>openOn:initialFilename:pattern: (in category 'initialize-release') -----
- openOn: aDirectory initialFilename: aFilename pattern: patternString
- 	"open a modal dialog to choose a file name to save to aDirectory; limit visible files in the file list with the pattern"
- 
- 	^self openOn: aDirectory initialFilename: aFilename pattern: patternString message: nil
- !

Item was removed:
- ----- Method: FileSaverDialog>>openOn:initialFilename:pattern:message: (in category 'initialize-release') -----
- openOn: aDirectory initialFilename: aFilename pattern: patternString message: messageString
- 	"open a modal dialog to choose a file name to save to aDirectory; limit visible files in the file list with the pattern. Set the user message"
- 
- 	directory := aDirectory.
- 	fileName := aFilename.
- 	message:= messageString.
- 	self pattern: patternString.
- 	
- 	ToolBuilder open: self.
- 	^self finalChoice!



More information about the Squeak-dev mailing list