[squeak-dev] The Trunk: ToolBuilder-Morphic-ct.320.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jul 9 17:31:35 UTC 2022


Christoph Thiede uploaded a new version of ToolBuilder-Morphic to project The Trunk:
http://source.squeak.org/trunk/ToolBuilder-Morphic-ct.320.mcz

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

Name: ToolBuilder-Morphic-ct.320
Author: ct
Time: 9 July 2022, 7:31:16.926611 pm
UUID: b0d78612-83dd-624c-81ed-41909b6f1026
Ancestors: ToolBuilder-Morphic-ct.319

Merges polish-file-dialogs:
	Cleans up, tests, and improves the convenience of file selection dialogs.
	
	UI improvements:
	* Add input field for file path to all dialogs. In file dialogs, a directory path can be entered to navigate to the relevant directory in the tree.
	* Update enablement of canAccept button based on input
	* Improve automatic selection of filenames
	* Use explicit help texts instead of filling the input field with a help message
	* Fixes handling of patterns/suffixes in save dialog
	* Double click a file/directory to choose it
	* Save dialog: Assure that the name of an existing directory cannot be chosen as a new file name
	* Small MVC improvements (however, modal invocation in MVC is still broken at the moment)

	Refactoring:
	* Overall deduplication
	* Consistent spelling of fileName (instead of filename)
	* Add new suite of acceptance tests

Revision:
* Fix default selection in directory chooser
* Improve todo notes
* Update tests to recent ClassTestCase refactoring
* Prepare tree selection for path normalization

=============== Diff against ToolBuilder-Morphic-ct.319 ===============

Item was added:
+ ----- Method: DirectoryChooserDialog>>acceptDirectory: (in category 'directory tree') -----
+ acceptDirectory: dir
+ 
+ 	self setDirectoryTo: dir.
+ 	self acceptFileName.!

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

Item was changed:
  ----- Method: DirectoryChooserDialog>>buildDirectoryTreeWith: (in category 'toolbuilder') -----
  buildDirectoryTreeWith: builder
  
  	^ (super buildDirectoryTreeWith: builder)
  		hScrollBarPolicy: #never; "Use the dialog grips to see more"
+ 		doubleClick: #acceptDirectory:;
  		yourself!

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

Item was added:
+ ----- Method: DirectoryChooserDialog>>canAccept (in category 'accessing') -----
+ canAccept
+ 
+ 	^ directory notNil and: [directory exists]!

Item was added:
+ ----- Method: DirectoryChooserDialog>>inputText (in category 'filename') -----
+ inputText
+ 
+ 	^ directory fullName!

Item was added:
+ ----- Method: DirectoryChooserDialog>>inputText: (in category 'filename') -----
+ inputText: aText 
+ 
+ 	^ self selectFileName: aText!

Item was added:
+ ----- Method: DirectoryChooserDialog>>selectFileName: (in category 'filename') -----
+ selectFileName: aStringOrText
+ 
+ 	aStringOrText ifNil: [^ self].
+ 	self directory: ([FileDirectory on: aStringOrText asString] ifError: [^ self]).
+ 	isUpdating := true.
+ 	[self changed: #selectedPath]
+ 		ensure: [isUpdating := false].
+ 	self updateFileList.
+ 	self changed: #canAccept.!

Item was changed:
  Model subclass: #FileAbstractSelectionDialog
+ 	instanceVariableNames: 'patternList directory directoryCache message listIndex fileName finalChoice nameList sizeList dateList suffixList isUpdating'
- 	instanceVariableNames: 'patternList directory directoryCache message listIndex fileName finalChoice nameList sizeList dateList suffixList'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'ToolBuilder-Morphic-Tools'!
  
+ !FileAbstractSelectionDialog commentStamp: 'ct 7/9/2022 16:42' prior: 0!
- !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.
  
+ See some todo notes on my class side.
+ 
  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 class>>todo (in category 'documentation') -----
+ todo
+ 
+ 	self flag: #forLater. "Possible future adventures for the file dialogs:
+ 	
+ 		* Allow users to enter patterns with stars to filter the current fileList (as known from Microsoft Windows file dialogs)
+ 		* Add support for multiple file selection
+ 		* Add MVC support (currently, modal dialog invocations windows seems not to work there). See also existing #mvc flag.
+ 		* Normalize paths with parentDirectoryNickname to fix selection in tree view"!

Item was changed:
+ ----- Method: FileAbstractSelectionDialog>>acceptFileName (in category 'accessing') -----
- ----- Method: FileAbstractSelectionDialog>>acceptFileName (in category 'initialize-release') -----
  acceptFileName
- 	"User clicked to accept the current state so save the filename and close the dialog"
  
+ 	self canAccept ifFalse: [^ false].
+ 	self checkOrCorrectSuffix ifFalse: [^ false].
+ 	^ self basicAcceptFileName!
- 	finalChoice := fileName.
- 	self changed: #close!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>acceptFileName: (in category 'filename') -----
+ acceptFileName: aStringOrText
+ 
+ 	self selectFileName: aStringOrText.
+ 	^ self acceptFileName!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>basicAcceptFileName (in category 'accessing') -----
+ basicAcceptFileName
+ 	"Accept the file name without checking for patterns or suffices."
+ 
+ 	self canAccept ifFalse: [^ false].
+ 	finalChoice := fileName.
+ 	self changed: #close.
+ 	^ true!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>basicAcceptFileName: (in category 'filename') -----
+ basicAcceptFileName: aStringOrText
+ 	"Allow the user to press Cmd + S instead of enter to enforce a file name that does not match the pattern/suffx requirements."
+ 
+ 	self selectFileName: aStringOrText.
+ 	^ self basicAcceptFileName!

Item was changed:
  ----- 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;
+ 				enabled: #canAccept;
+ 				yourself.
- 				action: #acceptFileName.
  		builder pluggableButtonSpec new
  				model: self;
  				label: 'Cancel' translated;
  				color: (self userInterfaceTheme get: #cancelColor for: #DialogWindow);
+ 				action: #cancelFileChooser;
+ 				yourself}!
- 				action: #cancelFileChooser}!

Item was changed:
  ----- Method: FileAbstractSelectionDialog>>buildFileListWith: (in category 'toolbuilder') -----
+ buildFileListWith: builder
+ 
- buildFileListWith: builder 
  	| listSpec |
  	listSpec := builder pluggableListSpec new.
  	listSpec
+ 		model: self;
+ 		list: #fileList;
+ 		getIndex: #fileListIndex;
+ 		setIndex: #fileListIndex:;
+ 		doubleClick: #acceptFileName;
+ 		keyPress: nil;
+ 		frame:
+ 			(self
+ 				frameOffsetFromTop:0
+ 				fromLeft: 0
+ 				width: 1
+ 				bottomFraction: 1).
+ 	^ 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 changed:
  ----- Method: FileAbstractSelectionDialog>>buildTextInputWith: (in category 'toolbuilder') -----
  buildTextInputWith: builder
  	| textSpec |
  	textSpec := builder pluggableInputFieldSpec new.
  	textSpec 
  		model: self;
  		name: #inputText ;
- 		font: self textViewFont;
  		getText: #inputText;
+ 		editText: #selectFileName:;
+ 		setText: #basicAcceptFileName:;
+ 		selection: #contentsSelection;
+ 		help: 'Enter a filename here or choose from list' translated.
+ 	^textSpec!
- 		setText: #selectFilename:;
- 		selection: #contentsSelection.
- 	^textSpec
- !

Item was changed:
  ----- Method: FileAbstractSelectionDialog>>buildWith: (in category 'toolbuilder') -----
  buildWith: builder
- 	"assemble the spec for the common chooser/saver dialog UI"
  
+ 	| windowSpec window |
+ 	windowSpec := self buildWindowWith: builder specs: {
+ 		(self topConstantHeightFrame: self textViewHeight
+ 			fromLeft: 0
+ 			width: 1) -> [self buildTextInputWith: builder].
+ 		(self frameOffsetFromTop: self textViewHeight
+ 			fromLeft: 0.35
+ 			width: 0.65
+ 			offsetFromBottom: 0) -> [self buildFileListWith: builder].
+ 		(self frameOffsetFromTop: self textViewHeight
+ 			fromLeft: 0
+ 			width: 0.35
+ 			offsetFromBottom: 0) -> [self buildDirectoryTreeWith: builder].
+ 	}.
+ 	windowSpec buttons addAll: ( self buildButtonsWith: builder ).
+ 	window := builder build: windowSpec.
+ 	(window respondsTo: #addKeyboardCaptureFilter:) ifTrue: [
+ 		window addKeyboardCaptureFilter: self].
+ 	self changed: #selectedPath.
+ 	self inputText: fileName.
+ 	(window respondsTo: #positionOverWidgetNamed:) ifTrue: [
+ 		window positionOverWidgetNamed: #inputText].
+ 	^window!
- 	^self subclassResponsibility!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>canAccept (in category 'accessing') -----
+ canAccept
+ 
+ 	^ fileName isEmptyOrNil not
+ 		and: [self directory fileExists: fileName]!

Item was changed:
+ ----- Method: FileAbstractSelectionDialog>>cancelFileChooser (in category 'accessing') -----
- ----- 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>>checkOrCorrectSuffix (in category 'filename') -----
+ checkOrCorrectSuffix
+ 
+ 	^ patternList anySatisfy: [:each |
+ 		each match: fileName "caseSensitive: FileDirectory default isCaseSensitive"]!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>contentsSelection (in category 'toolbuilder') -----
+ contentsSelection
+ 	"Initial selection covers entire initial file name/path if any"
+ 
+ 	^ 1 to: (self inputText ifNil: [0] ifNotNil: #size)!

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 flag: #mvc. "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 directory tree morph"
+ 			self directory entries copyWith:
+ 				(self directory entryAt: self directory class parentDirectoryNickname)].
+ 	
- 		ifTrue:[self directory fileEntries ]
- 		ifFalse:[self directory entries].
- 
  	(patternList anySatisfy: [:each | each = '*'])
  		ifTrue: [^ entries].
  
+ 	^ entries select: [:entry |
+ 		patternList anySatisfy: [:each |
+ 			entry isDirectory or: [each match: entry name]]]!
- 	^ entries select: [:entry | patternList anySatisfy: [:each | each match: entry name]]!

Item was changed:
  ----- 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.
+ 	fileName := nameList at: anInteger ifAbsent: [nil].
+ 	
+ 	(fileName notNil and: [self directory directoryExists: fileName]) ifTrue:
+ 		[self flag: #mvc. "file list contains directories"
+ 		self setDirectoryTo: (self directory on: (self directory entryAt: fileName) fullName).
+ 		self changed: #selectedPath.
+ 		fileName := nil].
+ 	
- 	listIndex = 0 
- 		ifTrue: [fileName := nil]
- 		ifFalse: [fileName := nameList at: anInteger].  "open the file selected"
- 
  	self 
  		changed: #fileListIndex;
+ 		changed: #inputText;
+ 		changed: #canAccept.!
- 		changed: #inputText!

Item was changed:
+ ----- Method: FileAbstractSelectionDialog>>finalChoice (in category 'accessing') -----
- ----- 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 changed:
  ----- Method: FileAbstractSelectionDialog>>initialize (in category 'initialize-release') -----
  initialize
  	super initialize.
  	directoryCache := WeakIdentityKeyDictionary new.
  	listIndex := 0.
  	patternList := self defaultPatternList.
+ 	suffixList := OrderedCollection new.
+ 	isUpdating := false.!
- 	suffixList := OrderedCollection new!

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"
  
  	| newList |
  	newList := Set new.
  	newList addAll: (self entriesMatching: arrayOfPatterns).
  
  	newList := newList sorted: [:a :b|
  							a name <= b name].
  	nameList := newList collect:[:e| e name].
+ 	
+ 	self flag: #dead. "dates and sizes are not in use"
  	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].!
- 	sizeList := newList collect:[:e| e  fileSize asStringWithCommas] 
- !

Item was changed:
  ----- Method: FileAbstractSelectionDialog>>newDirectoryName (in category 'directory tree') -----
  newDirectoryName
  	"Create a new directory; will be a subdirectory of the current chosen directory. 
  	If the user input is empty, or if the directory creation fails, fail this method.
  	Update the directory tree display afterwards and set the current directory to the newly created directory"
  	|userInput|
+ 	userInput := Project uiManager request: 'New directory name' translated initialAnswer: 'newDir'.
- 	userInput := UIManager default request: 'New directory name' translated initialAnswer: 'newDir'.
  	userInput isEmptyOrNil ifTrue: [^nil].
  	
  	[self directory createDirectory: userInput] ifError:[^nil]. "I hate using ifError: - it's so indiscriminate. Really ought to be a more precise error to catch properly"
+ 	
- 
  	self changed: #rootDirectoryList.
  	self directory: (self directory / userInput).
  	self changed: #selectedPath!

Item was added:
+ ----- Method: FileAbstractSelectionDialog>>selectFileName: (in category 'filename') -----
+ selectFileName: aText 
+ 
+ 	| result |
+ 	fileName := aText asString.
+ 	
+ 	(directory class dirPathFor: aText asString) ifNotEmpty: [:otherDirPath |
+ 		([directory on: otherDirPath] ifError: [nil]) ifNotNil: [:otherDir |
+ 			otherDir exists ifTrue:
+ 				[self setDirectoryTo: otherDir.
+ 				self changed: #selectedPath.
+ 				fileName := directory class localNameFor: aText asString.
+ 				self changed: #inputText.
+ 				self changed: #canAccept.
+ 				^ self selectFileName: fileName]]].
+ 	
+ 	result := self selectExistingFileName.
+ 	self changed: #canAccept.
+ 	^ result!

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].
+ 	dir isString ifTrue: [
+ 		self flag: #mvc. "PluggableListView auto-converts all items to strings :("
+ 		^ self setDirectoryTo: (FileDirectory on: (Scanner new scanTokens: dir) third)].
  "okToChange is probably redundant.
  modelSleep/Wake is related to use of ServerDirectories, which are not yet hooked up"
  	self okToChange ifFalse: [ ^ self ].
  	self modelSleep.
+ 	isUpdating
+ 		ifTrue:
+ 			[directory := dir.
+ 			self changed: #directory]
+ 		ifFalse:
+ 			[self directory: dir.
+ 			self modelWakeUp.
+ 			isUpdating := true.
+ 				[directory = dir
+ 					ifTrue:
+ 						[self changed: #directory]
+ 					ifFalse: "directory was normalized in #directory:"
+ 						[self flag: #workaround. "Must not signal #directory because PluggableTreeMorph does not perform equality comparison when reselecting items. See: http://lists.squeakfoundation.org/pipermail/squeak-dev/2021-October/216808.html"
+ 						self changed: #selectedPath].
+ 				self updateFileList.
+ 				self changed: #inputText]
+ 					ensure: [isUpdating := false]].!
- 	self directory: dir.
- 	self modelWakeUp.
- 	self changed: #directory.
- 	self updateFileList.
- 	self changed: #inputText!

Item was removed:
- ----- Method: FileAbstractSelectionDialog>>textViewFont (in category 'ui details') -----
- textViewFont
- 
- 	^ TextStyle defaultFont!

Item was removed:
- ----- 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.35
- 			width: 0.65
- 			offsetFromBottom: 0) -> [self buildFileListWith: builder].
- 		(self frameOffsetFromTop: 0
- 			fromLeft: 0
- 			width: 0.35
- 			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>>inputText (in category 'filename') -----
+ inputText
+ 	"return the filename to appear in the text field"
+ 
+ 	^fileName!

Item was added:
+ ----- Method: FileChooserDialog>>inputText: (in category 'filename') -----
+ inputText: aText 
+ 	"Initialize the filename entry field to aString.  If a file with that name already exists, set up to highlight it."
+ 	aText ifNil: [^ self].
+ 	fileName := aText asString.
+ 	self selectExistingFileName!

Item was added:
+ ----- Method: FileChooserDialog>>selectExistingFileName (in category 'private') -----
+ selectExistingFileName
+ 	"Answer whether an existing file in the list matches my proposed filename, selecting it if it does."
+ 
+ 	listIndex := nameList findFirst: [:each |
+ 		fileName isEmptyOrNil not and:
+ 			[each beginsWith: fileName "caseSensitive: FileDirectory default isCaseSensitive"]].
+ 	fileName := nameList at: listIndex ifAbsent: [nil].
+ 	
+ 	self changed: #fileListIndex.
+ 	self changed: #canAccept.
+ 	
+ 	^ listIndex ~= 0!

Item was changed:
  ----- 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"
- 	"return the string to present to the user  in order to explain the purpose of this dialog appearing"
  	
  	^message ifNil: ['Choose a file name' translated]!

Item was removed:
- ----- 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>>buildButtonsWith: (in category 'toolbuilder') -----
  buildButtonsWith: builder
+ 
+ 	^ (super buildButtonsWith: builder)
+ 		copyWith:
+ 			(builder pluggableButtonSpec new
- 	"add a 'new directory' button to the beginning of the row of buttons"
- 	^{ builder pluggableButtonSpec new
  				model: self;
  				label: 'New Directory' translated;
  				color: (self userInterfaceTheme get: #buttonColor for: #DialogWindow);
+ 				action: #newDirectoryName;
+ 				yourself)!
- 				action: #newDirectoryName}, (super buildButtonsWith: builder)!

Item was removed:
- ----- 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
- 			fromLeft: 0
- 			width: 1) -> [self buildTextInputWith: builder].
- 		(self frameOffsetFromTop: self textViewHeight
- 			fromLeft: 0.35
- 			width: 0.65
- 			offsetFromBottom: 0) -> [self buildFileListWith: builder].
- 		(self frameOffsetFromTop: self textViewHeight
- 			fromLeft: 0
- 			width: 0.35
- 			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 positionOverWidgetNamed: #inputText.
- 	^window
- !

Item was added:
+ ----- Method: FileSaverDialog>>canAccept (in category 'accessing') -----
+ canAccept
+ 
+ 	^ fileName isEmptyOrNil not
+ 		and: [(self directory directoryExists: fileName) not]!

Item was added:
+ ----- Method: FileSaverDialog>>checkOrCorrectSuffix (in category 'filename') -----
+ checkOrCorrectSuffix
+ 
+ 	| suffix |
+ 	super checkOrCorrectSuffix ifTrue: [^ true].
+ 	
+ 	suffixList ifEmpty: [^ false].
+ 	
+ 	suffixList size = 1 ifTrue:
+ 		[((suffix := '.' , suffixList anyOne)
+ 			compare: (fileName last: (suffix size min: fileName size))
+ 			caseSensitive: directory isCaseSensitive)
+ 				= 2 ifFalse: [ fileName := fileName , suffix ].
+ 		^ true].
+ 	
+ 	suffix := (Project uiManager
+ 		chooseFrom: suffixList
+ 		values: suffixList
+ 		title: 'Please choose the type of file to save.' translated)
+ 			ifNil: [^ false].
+ 	fileName := fileName , '.' , suffix.
+ 	self acceptFileName.
+ 	^ true!

Item was removed:
- ----- Method: FileSaverDialog>>contentsSelection (in category 'ui details') -----
- contentsSelection
- 	^ 1 to: 9999!

Item was changed:
+ ----- Method: FileSaverDialog>>initialFilename: (in category 'accessing') -----
- ----- 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 changed:
  ----- Method: FileSaverDialog>>inputText (in category 'filename') -----
  inputText
  	"return the filename to appear in the text field"
  
+ 	^fileName!
- 	^fileName ifNil:['Enter a filename here or choose from list' translated]!

Item was changed:
  ----- Method: FileSaverDialog>>inputText: (in category 'filename') -----
  inputText: aText 
  	"Initialize the filename entry field to aString.  If a file with that name already exists, set up to highlight it."
  	aText ifNil: [^ self].
  	fileName := aText asString.
+ 	self selectExistingFileName!
- 	self selectExistingFilename!

Item was added:
+ ----- Method: FileSaverDialog>>selectExistingFileName (in category 'private') -----
+ selectExistingFileName
+ 	"Answer whether an existing file in the list matches my proposed filename, selecting it if it does."
+ 
+ 	listIndex := nameList findFirst: [:each | each = fileName].
+ 	self changed: #fileListIndex.
+ 	^ true!

Item was removed:
- ----- Method: FileSaverDialog>>selectExistingFilename (in category 'private') -----
- selectExistingFilename
- 	"Answer whether an existing file in the list matches my proposed filename, selecting it if it does."
- 	^ (patternList anySatisfy:
- 		[ : each | (each
- 			compare: fileName
- 			caseSensitive: FileDirectory default isCaseSensitive) = 2 ])
- 		and:
- 			[ listIndex := nameList findFirst: [ : each | each = fileName ].
- 			true ]!

Item was removed:
- ----- Method: FileSaverDialog>>selectFilename: (in category 'filename') -----
- selectFilename: aText 
- 	"The 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."
- 	fileName := aText asString.
- 	^ self selectExistingFilename
- 		ifTrue:
- 			[ self changed: #fileListIndex.
- 			true ]
- 		ifFalse:
- 			[ suffixList size = 1
- 				ifTrue:
- 					[ | suffix |
- 					((suffix := '.' , suffixList anyOne)
- 						compare: (fileName last: (suffix size min: fileName size))
- 						caseSensitive: FileDirectory default isCaseSensitive) = 2 ifFalse: [ fileName := fileName , suffix ].
- 					true ]
- 				ifFalse:
- 					[ suffixList
- 						at:
- 							(UIManager default
- 								chooseFrom: suffixList
- 								title: 'Please choose the type of file to save.' translated)
- 						ifPresent:
- 							[ : choice | fileName := fileName , '.' , choice.
- 							true ]
- 						ifAbsent:
- 							[ suffixList isEmpty or:
- 								[ self inform: ('WARNING:  File not saved!!  A filename matching one of {1} patterns is required.' translated format: {patternList asArray}).
- 								false ] ] ] ]!



More information about the Squeak-dev mailing list