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

commits at source.squeak.org commits at source.squeak.org
Sat Oct 28 20:20:24 UTC 2017


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

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

Name: Tools-tpr.770
Author: tpr
Time: 28 October 2017, 1:20:10.016299 pm
UUID: 70254f01-f4e8-47ae-8907-de13158e10f4
Ancestors: Tools-tpr.769

Add FileChooserDialog and FileSaverDialog; these are experimental modal dialogs intended as replacements for FileList2>modalFileSelector, FileChooser, StandardFileMenu and several other ugly horrors.

=============== Diff against Tools-tpr.769 ===============

Item was changed:
  SystemOrganization addCategory: #'Tools-ArchiveViewer'!
  SystemOrganization addCategory: #'Tools-Base'!
  SystemOrganization addCategory: #'Tools-Browser'!
  SystemOrganization addCategory: #'Tools-Changes'!
  SystemOrganization addCategory: #'Tools-Debugger'!
  SystemOrganization addCategory: #'Tools-Explorer'!
  SystemOrganization addCategory: #'Tools-File Contents Browser'!
  SystemOrganization addCategory: #'Tools-FileList'!
  SystemOrganization addCategory: #'Tools-Inspector'!
  SystemOrganization addCategory: #'Tools-Menus'!
  SystemOrganization addCategory: #'Tools-MethodFinder'!
  SystemOrganization addCategory: #'Tools-Process Browser'!
+ SystemOrganization addCategory: #'Tools-FileDialogs'!

Item was added:
+ Model subclass: #FileAbstractSelectionDialog
+ 	instanceVariableNames: 'pattern directory directoryCache list listIndex fileName finalChoice'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Tools-FileDialogs'!
+ 
+ !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 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 added:
+ ----- 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 added:
+ ----- Method: FileAbstractSelectionDialog>>acceptFileName (in category 'initialize-release') -----
+ acceptFileName
+ 
+ 	finalChoice := fileName.
+ 	self changed: #close!

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 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) .
+ 	^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;
+ 				extent: self initialExtent;
+ 				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"
+ 	"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 added:
+ ----- Method: FileAbstractSelectionDialog>>buttonHeight (in category 'ui details') -----
+ buttonHeight
+ 	
+ 	^ Preferences standardButtonFont height * 2!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>cancelFileChooser (in category 'initialize-release') -----
+ cancelFileChooser
+ 
+ 	fileName := nil.
+ 	self changed: #close.!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>directory (in category 'directory tree') -----
+ directory
+ 
+ 	^ directory!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>directory: (in category 'directory tree') -----
+ directory: aFileDirectory 
+ 	"Set the path of the directory to be displayed."
+ 	self okToChange ifFalse: [ ^ self ].
+ 	self modelSleep.
+ 	directory := aFileDirectory.
+ 	self modelWakeUp.
+ 	self changed: #directory.
+ 	self pattern: pattern!

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: patternString
+ 	"Answer a list of directory entries which match the patternString.
+ 	The patternString may consist of multiple patterns separated by ';'.
+ 	Each pattern can include a '*' or '#' as wildcards - see String>>match:"
+ 
+ 	| entries patterns |
+ 	entries := directory entries reject:[:e| Smalltalk isMorphic and: [e isDirectory]].
+ 	patterns := patternString findTokens: ';'.
+ 	(patterns anySatisfy: [:each | each = '*'])
+ 		ifTrue: [^ entries].
+ 	^ entries select: [:entry | patterns 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"
+ 	
+ 	^list!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>fileListIndex (in category 'file list') -----
+ fileListIndex
+ 	"return the index in the list of files for the currently selected filey"
+ 	
+ 	^listIndex!

Item was added:
+ ----- 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 added:
+ ----- 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 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"
+ 
+ 	^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>>hasMoreDirectories: (in category 'directory tree') -----
+ hasMoreDirectories: aDirectory
+ 	^directoryCache at: aDirectory ifAbsentPut:[
+ 		[aDirectory directoryNames notEmpty] on: Error do:[:ex| true].
+ 	].!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>initialize (in category 'initialize-release') -----
+ initialize
+ 	super initialize.
+ 	directoryCache := WeakIdentityKeyDictionary new.
+ 	self directory: FileDirectory default!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>listForPatterns: (in category 'path and pattern') -----
+ listForPatterns: anArray
+ 	"return a list of those file names which match any of the patterns in the array."
+ 
+ 	| sizePad newList |
+ 	newList := Set new.
+ 	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 asArray!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>pattern: (in category 'path and pattern') -----
+ pattern: textOrStringOrNil
+ 
+ 	textOrStringOrNil
+ 		ifNil: [pattern := '*']
+ 		ifNotNil: [pattern := textOrStringOrNil asString].
+ 	pattern isEmpty ifTrue: [pattern := '*'].
+ 	self updateFileList.
+ 	^ true
+ !

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>rootDirectoryList (in category 'directory tree') -----
+ rootDirectoryList
+ 	| dirList dir |
+ 	dir := FileDirectory on: ''.
+ 	dirList := dir directoryNames collect:[:each| dir directoryNamed: each]..
+ 	dirList isEmpty ifTrue:[dirList := Array with: FileDirectory default].
+ 	^dirList!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>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: 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 changed: #fileList.
+ 	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>>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 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 , '*']]].
+ 
+ 	list := self listForPatterns: patterns.
+ 	listIndex := 0.
+ 	fileName := nil.
+ 	self changed: #fileList]!

Item was added:
+ FileAbstractSelectionDialog subclass: #FileChooserDialog
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Tools-FileDialogs'!
+ 
+ !FileChooserDialog commentStamp: 'tpr 10/28/2017 12:57' 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'
+ 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 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"
+ 
+ 	^self openOn: aDirectory pattern: nil
+ 
+ 	!

Item was added:
+ ----- 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 added:
+ ----- 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 := self fileNameFromFormattedItem: (list at: anInteger)].  "open the file selected"
+ 
+ 	self 
+ 		changed: #fileListIndex!

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

Item was added:
+ ----- Method: FileChooserDialog>>inputText: (in category 'path and pattern') -----
+ inputText: stringOrText
+ 	"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 changed: #inputText.
+ 	self changed: #selectedPath.!

Item was added:
+ ----- 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.
+ 	pattern := aPatternString.
+ 	
+ 	ToolBuilder open: self.
+ 	^self finalChoice!

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: 'Tools-FileDialogs'!
+ 
+ !FileSaverDialog commentStamp: 'tpr 10/28/2017 12:58' 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 directry, providing a way to specify a completely new file.
+ This will not affect the selected directory path.
+ 
+ Normal usage would be 
+ 	myFilename := FileSaverDialog openOn: myApplicationDefaultDirectory initialFilename: 'foo.myapp'
+ 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.
+ 
+ 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 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"
+ 
+ 	^self new openOn: aDirectory  initialFilename: nil
+ 
+ 	!

Item was added:
+ ----- 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 := self fileNameFromFormattedItem: (list at: anInteger)].  "open the file selected"
+ 
+ 	self 
+ 		changed: #fileListIndex;
+ 		changed: #inputText!

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

Item was added:
+ ----- 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 currect list, highlight it"
+ 
+ 	fileName := aText asString.
+ 	listIndex := list findFirst:[: nm| (self fileNameFromFormattedItem: nm) = fileName].
+ 	listIndex = 0  ifFalse:
+ 			[fileName := self fileNameFromFormattedItem: (list at: listIndex)].
+ 
+ 	self 
+ 		changed: #fileListIndex;
+ 		changed: #inputFilename!

Item was added:
+ ----- 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"
+ 
+ 	directory := aDirectory.
+ 	fileName := aFilename.
+ 	
+ 	ToolBuilder open: self.
+ 	^self finalChoice!

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



More information about the Squeak-dev mailing list