[squeak-dev] The Trunk: Tools-mt.1075.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Nov 25 10:48:55 UTC 2021


Marcel Taeumel uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-mt.1075.mcz

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

Name: Tools-mt.1075
Author: mt
Time: 25 November 2021, 11:48:52.151354 am
UUID: 089e5a95-68d9-1a44-957c-5ddbc897d40e
Ancestors: Tools-mt.1074

Refactors and extends "save contents to file" feature in workspaces and all kinds of tools that use PluggableTextMorph's (with their TextEditor). This also simplifies the rather recent "file-out workspace contents on accept" feature (see preferences).

Thanks to Eliot (eem) for the idea and change set that served as a valuable template for this refactoring.

Thanks to Christoph (ct) for pointing out the strange nature of that "file-out file path" preference.

Note that all open workspaces should be updated automatically. See postscript.

=============== Diff against Tools-mt.1074 ===============

Item was changed:
  ----- Method: FileList>>viewContentsInWorkspace (in category 'own services') -----
  viewContentsInWorkspace
+ 	"View the contents of my selected file in a new workspace."
- 	"View the contents of my selected file in a new workspace"
  	
+ 	| fileContents workspace lineConversion |
+ 	fileContents := self directory
+ 		readOnlyFileNamed: self fileName
+ 		do: [:fileStream |
+ 			fileStream
+ 				setConverterForCode;
+ 				wantsLineEndConversion: true.
+ 			lineConversion := fileStream detectLineEndConvention.
+ 			fileStream contents].		
+ 	workspace := (Project uiManager edit: fileContents label: nil shouldStyle: Workspace shouldStyle) model.
+ 	
+ 	"Remember certain information to allow edits in the same file."
+ 	workspace
+ 		windowTitle: (self directory localNameFor: self fileName);
+ 		fileDirectory: self directory;
+ 		setProperty: #fileLineConversion toValue: lineConversion;
+ 		saveContentsInFileOnAccept.
+ !
- 	| aFileStream aName lineConversion w | 
- 	aFileStream := (directory readOnlyFileNamed: self fullName) setConverterForCode.
- 	aFileStream wantsLineEndConversion: true.
- 	lineConversion := aFileStream detectLineEndConvention.
- 	aName := aFileStream localName.
- 	w := UIManager default
- 			edit: ([aFileStream contentsOfEntireFile] ensure: [aFileStream close])
- 			label: ((aName includesSubstring: 'Workspace')
- 					ifTrue: [#('.text' '.txt') inject: aName into: [:name :ext| (name endsWith: ext) ifTrue: [name allButLast: ext size] ifFalse: [name]]]
- 					ifFalse: ['Workspace from ', aName]).
- 	w setProperty: #lineConversion toValue: lineConversion.
- 	directory ~= FileDirectory default ifTrue: [w setProperty: #myDir toValue: directory]!

Item was removed:
- ----- Method: Workspace class>>fileOut: (in category 'support') -----
- fileOut: contents
- 	"Write the given contents into the workspace file-out file path."
- 
- 	| filePath |
- 	filePath := self fileOutFilePath.
- 	(FileDirectory default on: filePath) containingDirectory assureExistence.
- 	FileStream
- 		fileNamed: filePath
- 		do: [:stream |
- 			stream
- 				setToEnd;
- 				nextPutAll: '"----ACCEPT----';
- 				nextPutAll: DateAndTime now asString;
- 				nextPutAll: '"';
- 				cr; nextPutAll: contents; cr].
- 	Transcript showln: 'Workspace contents successfully appended to: ', filePath printString.!

Item was removed:
- ----- Method: Workspace class>>fileOutFilePath (in category 'preferences') -----
- fileOutFilePath
- 	<preference: 'File-out file path for workspace' 
- 		categoryList: #('browsing' 'tools')
- 		description: 'Set the file-out location for #fileOutOnAccept in workspaces.' 
- 		type: #String>
- 	^ FileOutFilePath ifNil: [ 'workspace.st' ]!

Item was removed:
- ----- Method: Workspace class>>fileOutFilePath: (in category 'preferences') -----
- fileOutFilePath: aString
- 
- 	FileOutFilePath := aString.!

Item was changed:
  ----- Method: Workspace class>>fileOutOnAccept (in category 'preferences') -----
  fileOutOnAccept
  	<preference: 'File-out workspace contents on accept' 
  		categoryList: #('browsing' 'tools')
+ 		description: 'If true, accepting contents in a workspace will append them to a file on disk. The file name is derived from the workspace''s current window title and can thus be changed. The default name is thus ''Workspace.text''.'
- 		description: 'If true, accepting contents in a workspace will append them to a known location in the file system. See #fileOutFilePath.' 
  		type: #Boolean>
  	^ FileOutOnAccept ifNil: [ true ]!

Item was changed:
  ----- Method: Workspace class>>open (in category 'instance creation') -----
  open
  
  	| workspace |
  	workspace := self new.
+ 	self fileOutOnAccept
+ 		ifTrue: [workspace appendContentsToFileOnAccept].
- 	self fileOutOnAccept ifTrue: [
- 		workspace acceptAction: [:string | self fileOut: string]].
  	^ self embedTranscript
  		ifTrue: [workspace buildAndOpenWorkspaceTranscript]
  		ifFalse: [workspace buildAndOpen]!

Item was changed:
  ----- Method: Workspace>>acceptContents: (in category 'accessing') -----
  acceptContents: aString
+ 
+ 	^ (acceptAction ifNotNil: [acceptAction value: aString]) ~~ false
+ 		and: [super acceptContents: aString]!
- 	acceptAction ifNotNil:[acceptAction value: aString].
- 	^super acceptContents: aString.!

Item was changed:
  ----- Method: Workspace>>addModelItemsToWindowMenu: (in category 'menu commands') -----
  addModelItemsToWindowMenu: aMenu 
  	
  	aMenu addLine.
  	aMenu
+ 		add: 'change file name...'
+ 		target: self
+ 		action: #changeFileName.
+ 	aMenu
  		add: 'save contents to file...'
  		target: self
  		action: #saveContentsInFile.
  	aMenu
+ 		addUpdating: #saveContentsInFileOnAcceptWording
+ 		target: self
+ 		action: #saveContentsInFileOnAccept.
+ 	aMenu
+ 		addUpdating: #appendContentsToFileOnAcceptWording
+ 		target: self
+ 		action: #appendContentsToFileOnAccept.
+ 	aMenu addLine.
+ 	aMenu
  		add: 'inspect variables'
  		target: self
  		action: #inspectBindings.
  	aMenu
  		add: 'reset variables'
  		target: self
+ 		action: #resetBindings.
+ 	aMenu addLine.
- 		action: #initializeBindings.
  	aMenu
  		addUpdating: #mustDeclareVariableWording
  		target: self
  		action: #toggleVariableDeclarationMode.
  	aMenu
  		addUpdating: #acceptDroppedMorphsWording
  		target: self
  		action: #toggleDroppingMorphForReference.
  
  	self addToggleStylingMenuItemTo: aMenu.
  !

Item was added:
+ ----- Method: Workspace>>appendContentsToFileOnAccept (in category 'menu commands') -----
+ appendContentsToFileOnAccept
+ 	"Arrange that the contents will be appended to a file when the user accepts."
+ 
+ 	self saveContentsInFileOnAcceptEnabled
+ 		ifTrue: [(Project uiManager confirm: 'Do you really want to change file access mode\from #update to #append?\\You might corrupt data when accepting changes.' withCRs translated)
+ 			ifFalse: [^ self]].
+ 
+ 	self acceptAction: (self appendContentsToFileOnAcceptEnabled ifTrue: [ "no action" ] ifFalse: [
+ 		[:freshContents | | fileName stringToAppend |
+ 			"Ensure to compute fileName as late as possible to consider recent changes of the #windowTitle."
+ 			fileName := self suggestedFileNameForSave.
+ 			
+ 			stringToAppend := '"----ACCEPT----{1}"\{2}\' withCRs
+ 				format: { DateAndTime now asString. freshContents }.
+ 			
+ 			((FileDirectory forFileName: fileName) fileExists: fileName)
+ 				ifFalse: [ "If the default file name, which is derived from the current window title, does not exist, ask the user once to confirm the location."		
+ 					self
+ 						saveContents: stringToAppend
+ 						accessMode: #create]
+ 				ifTrue: [ "Update/replace the contents in the existing file."
+ 					self
+ 						saveContents: stringToAppend
+ 						onFileNamed: fileName
+ 						accessMode: #append]] ]).!

Item was added:
+ ----- Method: Workspace>>appendContentsToFileOnAcceptEnabled (in category 'menu commands') -----
+ appendContentsToFileOnAcceptEnabled
+ 
+ 	^ (acceptAction notNil and: [acceptAction home selector = #appendContentsToFileOnAccept])!

Item was added:
+ ----- Method: Workspace>>appendContentsToFileOnAcceptWording (in category 'menu commands') -----
+ appendContentsToFileOnAcceptWording
+ 
+ 	^ (self appendContentsToFileOnAcceptEnabled
+ 		ifTrue: ['<yes> append contents to {1} on accept']
+ 		ifFalse: ['<no> append contents to {1} on accept']) translated
+ 			format: { self suggestedFileNameForSave contractTo: 32 }!

Item was added:
+ ----- Method: Workspace>>changeFileName (in category 'menu commands') -----
+ changeFileName
+ 	"Let the user specify a new file name (and path) for save-contents requests."
+ 	
+ 	(Project uiManager
+ 		saveFilenameRequest: 'Save text contents in file...'
+ 		initialAnswer: self suggestedFileNameForSave)
+ 			ifNotNil: [:newFileName |
+ 				newFileName ifNotEmpty: [self setFileName: newFileName]].!

Item was added:
+ ----- Method: Workspace>>defaultFileNameForSave (in category 'user edits') -----
+ defaultFileNameForSave
+ 	"Overwritten to combine selected properties. Also see FileList >> #viewContentsInWorkspace to understand where different directories might originate."
+ 
+ 	^ self fileDirectory fullNameFor: self windowTitle!

Item was added:
+ ----- Method: Workspace>>fileDirectory (in category 'accessing') -----
+ fileDirectory
+ 	"Answer the current directory for save-contents requests."
+ 	
+ 	^ self valueOfProperty: #fileDirectory ifAbsent: [FileDirectory default]!

Item was added:
+ ----- Method: Workspace>>fileDirectory: (in category 'accessing') -----
+ fileDirectory: aDirectory
+ 	"Do not save the default directory so that the image and its surrounding files can be moved across the disk."
+ 	
+ 	aDirectory = FileDirectory default
+ 		ifTrue: [self removeProperty: #fileDirectory]
+ 		ifFalse: [self setProperty: #fileDirectory toValue: aDirectory].!

Item was added:
+ ----- Method: Workspace>>saveContents:onFileNamed:accessMode: (in category 'user edits') -----
+ saveContents: stringContents onFileNamed: fileName accessMode: accessMode
+ 	"Overwritten to set conversion rule of line-end character. See FileList >> #viewContentsInWorkspace."
+ 	
+ 	^ self
+ 		saveContents: stringContents
+ 		onFileNamed: fileName
+ 		accessMode: accessMode
+ 		workBlock: [:fileStream |
+ 			fileStream
+ 				lineEndConvention: (self valueOfProperty: #fileLineConversion); "nil is fine here..."
+ 				nextPutAll: stringContents]!

Item was added:
+ ----- Method: Workspace>>saveContents:onFileNamed:accessMode:workBlock: (in category 'user edits') -----
+ saveContents: stringContents onFileNamed: fileName accessMode: accessMode workBlock: workBlock
+ 	"Overwritten to update #fileDirectory property and #windowTitle on success."
+ 	
+ 	^ (super
+ 		saveContents: stringContents
+ 		onFileNamed: fileName
+ 		accessMode: accessMode
+ 		workBlock: workBlock)
+ 			ifFalse: [false "no success"]
+ 			ifTrue: [self setFileName: fileName. true "success"]!

Item was changed:
  ----- Method: Workspace>>saveContentsInFile (in category 'menu commands') -----
  saveContentsInFile
+ 	"Save the view's current contents in a file. Dispatch goes through the view (or morph). See commentary in and senders of #saveContents:accessMode:."
- 	"Pass along this message to the controller or morph.  (Possibly this Workspace menu item could be deleted, since it's now in the text menu.)"
  
+ 	self changed: #saveContents.!
- 	self changed: #saveContents
- !

Item was added:
+ ----- Method: Workspace>>saveContentsInFileOnAccept (in category 'menu commands') -----
+ saveContentsInFileOnAccept
+ 	"Arrange that the contents will be saved to a file on each save (or accept). Replace any existing file contents."
+ 
+ 	self flag: #discuss. "mt: Is it 'onFile' or rather 'inFile'? Note that there are different access modes."
+ 
+ 	self appendContentsToFileOnAcceptEnabled
+ 		ifTrue: [(Project uiManager confirm: 'Do you really want to change file access mode\from #append to #update?\\You might lose data when accepting changes.' withCRs translated)
+ 			ifFalse: [^ self]].
+ 	
+ 	self acceptAction: (self saveContentsInFileOnAcceptEnabled
+ 		ifFalse: [ [:stringToSave | | fileName |
+ 			"Ensure to compute fileName as late as possible to consider recent changes of the #windowTitle."
+ 			fileName := self suggestedFileNameForSave.
+ 			
+ 			((FileDirectory forFileName: fileName) fileExists: fileName)
+ 				ifFalse: [ "If the default file name, which is derived from the current window title, does not exist, ask the user once to confirm the location."		
+ 					self
+ 						saveContents: stringToSave
+ 						accessMode: #create]
+ 				ifTrue: [ "Update/replace the contents in the existing file."
+ 					self
+ 						saveContents: stringToSave
+ 						onFileNamed: fileName
+ 						accessMode: #update]] ]).!

Item was added:
+ ----- Method: Workspace>>saveContentsInFileOnAcceptEnabled (in category 'menu commands') -----
+ saveContentsInFileOnAcceptEnabled
+ 
+ 	^ (acceptAction notNil and: [acceptAction home selector = #saveContentsInFileOnAccept])!

Item was added:
+ ----- Method: Workspace>>saveContentsInFileOnAcceptWording (in category 'menu commands') -----
+ saveContentsInFileOnAcceptWording
+ 
+ 	^ (self saveContentsInFileOnAcceptEnabled
+ 		ifTrue: ['<yes> save contents to {1} on accept']
+ 		ifFalse: ['<no> save contents to {1} on accept']) translated
+ 			format: { self suggestedFileNameForSave contractTo: 32 }!

Item was added:
+ ----- Method: Workspace>>setFileName: (in category 'initialize-release') -----
+ setFileName: fileName
+ 
+ 	| directory |
+ 	directory := FileDirectory forFileName: fileName.
+ 	self fileDirectory: directory.
+ 	self windowTitle: (directory localNameFor: fileName).!

Item was added:
+ ----- Method: Workspace>>windowReqNewLabel: (in category 'user edits') -----
+ windowReqNewLabel: newLabel
+ 	"The user has edited the window label. Remember for a later save-to-file request. See #defaultFileNameForSave."
+ 	
+ 	self setProperty: #windowTitle toValue: newLabel.
+ 	^ true!

Item was added:
+ ----- Method: Workspace>>windowTitle (in category 'accessing') -----
+ windowTitle
+ 
+ 	^ self valueOfProperty: #windowTitle ifAbsent: ['Workspace']!

Item was added:
+ ----- Method: Workspace>>windowTitle: (in category 'accessing') -----
+ windowTitle: aString
+ 	"Normalize window title to not expose file extension in regular workspaces."
+ 	
+ 	| normalizedTitle |
+ 	normalizedTitle := ((aString includesSubstring: 'Workspace') and: [aString endsWithAnyOf: #('.text' '.txt')])
+ 		ifTrue: [aString copyFrom: 1 to: (aString lastIndexOf: $.) - 1]
+ 		ifFalse: [aString].
+ 
+ 	self setProperty: #windowTitle toValue: normalizedTitle.
+ 	self changed: #windowTitle.!

Item was changed:
  (PackageInfo named: 'Tools') postscript: 'ChangeSorter allSubInstancesDo: [:sorter |
  	(sorter instVarNamed: ''contentsAreStyleable'') ifNil: [
+ 		sorter instVarNamed: ''contentsAreStyleable'' put: true]].
+ 
+ "Convert existing properties from Morphic windows to the model. For MVC compatibility."
+ Workspace allInstancesDo: [:workspace | 
+ 	workspace containingWindow ifNotNil: [:window |
+ 		(window valueOfProperty: #myDir) ifNotNil: [:directory |
+ 			workspace setProperty: #fileDirectory toValue: directory].
+ 		(window valueOfProperty: #lineConversion) ifNotNil: [:symbol |
+ 			workspace setProperty: #fileLineConversion toValue: symbol].
+ 		workspace setProperty: #windowTitle toValue: window label].
+ 	(workspace acceptAction notNil and: [workspace acceptAction home selector = #open])
+ 		ifTrue: [workspace appendContentsToFileOnAccept]].'!
- 		sorter instVarNamed: ''contentsAreStyleable'' put: true]].'!



More information about the Squeak-dev mailing list