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

commits at source.squeak.org commits at source.squeak.org
Wed Jan 19 10:47:16 UTC 2022


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

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

Name: Tools-mt.1108
Author: mt
Time: 19 January 2022, 11:47:15.336855 am
UUID: 0765184b-16e8-bf47-97b0-e8cc76adf54e
Ancestors: Tools-mt.1107

Fixes GetText export: "withCRs translated" -> "translated withCRs"

=============== Diff against Tools-mt.1107 ===============

Item was changed:
  ----- Method: ChangeList>>contents: (in category 'viewing access') -----
  contents: aString
  	listIndex = 0 ifTrue: [self changed: #flash. ^ false].
  	lostMethodPointer ifNotNil: [^ self restoreDeletedMethod].
  	self okToChange "means not dirty" ifFalse: ["is dirty"
+ 		self inform: 'This is a view of a method on a file.\Please cancel your changes.  You may\accept, but only when the method is untouched.' translated withCRs.  ^ false].
- 		self inform: 'This is a view of a method on a file.\Please cancel your changes.  You may\accept, but only when the method is untouched.' withCRs translated.  ^ false].
  		"Can't accept changes here.  Method text must be unchanged!!"
  	(changeList at: listIndex) fileIn.
  	^ true!

Item was changed:
  ----- Method: ChangeList>>selectSuchThat (in category 'menu actions') -----
  selectSuchThat
  	"query the user for a selection criterio.  By Lex Spoon.  NB: the UI for invoking this from a changelist browser is currently commented out; to reenfranchise it, you'll need to mild editing to ChangeList method #changeListMenu:"
  	| code block |
+ 	code := Project uiManager request: ('selection criteria for a change named aChangeRecord?\For instance, "{1}"' translated withCRs format: {'aChangeRecord category = ''System-Network'''}).
- 	code := Project uiManager request: ('selection criteria for a change named aChangeRecord?\For instance, "{1}"' withCRs translated format: {'aChangeRecord category = ''System-Network'''}).
  
  	code isEmpty ifTrue: [^ self ].
  
  	block := Compiler evaluate: '[:aChangeRecord | ', code, ']'.
  
  	self selectSuchThat: block!

Item was changed:
  ----- Method: ChangeSorter class>>browseChangeSetsWithClass:selector: (in category 'browse') -----
  browseChangeSetsWithClass: class selector: selector
  	"Put up a menu comprising a list of change sets that hold changes for the given class and selector.  If the user selects one, open a single change-sorter onto it"
  
  	| hits index |
  	hits := ChangeSet allChangeSets select: 
  		[:cs | (cs atSelector: selector class: class) ~~ #none].
+ 	hits isEmpty ifTrue: [^ self inform: ('{1}\is not in any change set' translated withCRs format: {class name, ' >> #', selector})].
- 	hits isEmpty ifTrue: [^ self inform: ('{1}\is not in any change set' withCRs translated format: {class name, ' >> #', selector})].
  	index := hits size = 1
  		ifTrue:	[1]
  		ifFalse:	[(Project uiManager chooseFrom: (hits collect: [:cs | cs name])
  					lines: #())].
  	index = 0 ifTrue: [^ self].
  	(ChangeSorter new myChangeSet: (hits at: index)) open.
  !

Item was changed:
  ----- Method: ChangeSorter class>>browseChangeSetsWithSelector: (in category 'browse') -----
  browseChangeSetsWithSelector: aSelector
  	"Put up a list of all change sets that contain an addition, deletion, or change of any method with the given selector"
  
  	| hits index |
  	hits := ChangeSet allChangeSets select: 
  		[:cs | cs hasAnyChangeForSelector: aSelector].
+ 	hits isEmpty ifTrue: [^ self inform: ('{1}\is not in any change set' translated withCRs format: {aSelector})].
- 	hits isEmpty ifTrue: [^ self inform: ('{1}\is not in any change set' withCRs translated format: {aSelector})].
  	index := hits size = 1
  		ifTrue:	[1]
  		ifFalse:	[(Project uiManager chooseFrom: (hits collect: [:cs | cs name])
  					lines: #())].
  	index = 0 ifTrue: [^ self].
  	(ChangeSetBrowser new myChangeSet: (hits at: index)) open
  
  "ChangeSorter browseChangeSetsWithSelector: #clearPenTrails"
  !

Item was changed:
  ----- Method: ChangeSorter>>clearChangeSet (in category 'changeSet menu') -----
  clearChangeSet
  	"Clear out the current change set, after getting a confirmation."
  	| message |
  
  	self okToChange ifFalse: [^ self].
  	myChangeSet isEmpty ifFalse:
+ 		[message := 'Are you certain that you want to\forget all the changes in this set?' translated withCRs.
- 		[message := 'Are you certain that you want to\forget all the changes in this set?' withCRs translated.
  		(self confirm: message) ifFalse: [^ self]].
  	myChangeSet clear.
  	self changed: #classList.
  	self changed: #messageList.
  	self setContents.
  	self contentsChanged.
  !

Item was changed:
  ----- Method: Debugger>>contents:notifying: (in category 'accessing') -----
  contents: aText notifying: aController
  	"Accept new method source of the selected context."
  
  	| selector classOfMethod category ctxt newMethod |
  	contextStackIndex = 0 ifTrue: [^ false].
  	
  	"First, handle some edge cases"
  	selector := self selectedClass newParser parseSelector: aText.
  	"selector isDoIt ifTrue: [
  		currentCompiledMethod := self compileDoIt: aText]."
  	self flag: #todo. "ct: Recompile doIt method *without* creating method litters!! See Compiler>>#evaluateCue:ifFail:."
  	selector = self selectedMessageName ifFalse: [
  		"Different message compiled, delegating to super"
  		^ super contents: aText notifying: aController].
  	
  	self selectedContext isExecutingBlock ifTrue: [
  		"If we are in a block context, we need to rewind the stack before ."
  		| home |
  		home := self selectedContext activeHome.
  		home ifNil: [
  			self inform: 'Method for block not found on stack, can''t edit and continue' translated.
  			^ false].
+ 		(self confirm: 'I will have to revert to the method from\which this block originated. Is that OK?' translated withCRs) ifFalse: [
- 		(self confirm: 'I will have to revert to the method from\which this block originated. Is that OK?' withCRs translated) ifFalse: [
  			^ false].
  		
  		self resetContext: home changeContents: false.
  		"N.B. Only reset the contents if the compilation succeeds. If contents would be reset when compilation fails, both compiler error message and modifications were lost."
  		^ (self contents: aText notifying: aController)
  			ifTrue: [self contentsChanged];
  			yourself].
  	
  	classOfMethod := self selectedClass.
  	category := self selectedMessageCategoryName.
  	
  	"Do the actual compilation"
  	selector := classOfMethod
  		compile: aText
  		classified: category
  		notifying: aController.
  	selector ifNil: [^ false]. "compilation cancelled"
  	
  	"Update views"
  	contents := aText.
  	newMethod := classOfMethod compiledMethodAt: selector.
  	newMethod isQuick ifTrue: [
  		self cutBackExecutionToSenderContext].
  	ctxt := interruptedProcess popTo: self selectedContext.
  	ctxt == self selectedContext
+ 		ifFalse: [self inform: 'Method saved, but current context unchanged\because of unwind error. Click OK to see error' translated withCRs]
- 		ifFalse: [self inform: 'Method saved, but current context unchanged\because of unwind error. Click OK to see error' withCRs translated]
  		ifTrue: [
  			newMethod isQuick ifFalse: [
  				interruptedProcess restartTopWith: newMethod.
  				interruptedProcess stepToSendOrReturn].
  			contextVariablesInspector object: nil].
  	self resetContext: ctxt.
  	
  	Project current addDeferredUIMessage: [
  		self changed: #contentsSelection].
  	^ true!

Item was changed:
  ----- Method: StandardToolSet class>>debugProcess:context:label:contents:fullView: (in category 'debugging') -----
  debugProcess: aProcess context: aContext label: aString contents: contents fullView: aBool
  
  	(aProcess isTerminated and: [aString isNil or: [aString beginsWith: 'Debug it']]) ifTrue: [
+ 		^ Project uiManager inform: 'Nothing to debug. Process has terminated.\Expression optimized.' translated withCRs].
- 		^ Project uiManager inform: 'Nothing to debug. Process has terminated.\Expression optimized.' withCRs translated].
  
  	^ Debugger
  		openOn: aProcess
  		context: aContext
  		label: aString
  		contents: contents
  		fullView: aBool!

Item was changed:
  ----- Method: StandardToolSet class>>handleWarning: (in category 'debugging - handlers') -----
  handleWarning: aWarning
  	"Double dispatch. Let the processor take care of that warning, which usually calls back here to #debugProcess:..."
  
  	| message |
  	message := '{1}\\{2}' withCRs asText format: {
  		"First, show the actual text of this warning."
  		aWarning messageText.
  		"Second, append some helpful information that apply to all kinds of warnings."
  		('{1} {2}' asText format: {
  			'Select "Proceed" to continue or close this window to cancel the operation.' translated.
  			'If you do not want to be interrupted anymore, you can {1} this kind of warning. You can also {2}, which resets such warnings on the next image startup.' translated asText format: {
  				"Provide clickable text links so that the user can directly suppress warnings."
  				'always suppress' asText
  					addAttribute: (PluggableTextAttribute evalBlock: [
  						aWarning class suppressWarnings.
  						self inform: ('All ''{1}'' warnings will be suppressed.' translated format: {aWarning class name})]).
  				'suppress temporarily' asText
  					addAttribute: (PluggableTextAttribute evalBlock: [
  						aWarning class suppressAndResetOnStartUp.
+ 						self inform: ('All ''{1}'' warnings will be suppressed\and reset on the next image startup.' translated withCRs format: {aWarning class name})])}.
- 						self inform: ('All ''{1}'' warnings will be suppressed\and reset on the next image startup.' withCRs translated format: {aWarning class name})])}.
  			}) addAttribute: (
  				"Show this helpful information in a smaller font."
  				TextFontReference toFont: Preferences standardButtonFont)}.
  	
  	^ Processor
  		debugContext: aWarning signalerContext
  		title: 'Warning' translated
  		full: false
  		contents: message!

Item was changed:
  ----- 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.' translated withCRs)
- 		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 changed:
  ----- 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.' translated withCRs)
- 		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]] ]).!



More information about the Squeak-dev mailing list