[squeak-dev] The Trunk: System-mt.1294.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jan 29 10:00:40 UTC 2022


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

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

Name: System-mt.1294
Author: mt
Time: 29 January 2022, 11:00:35.415024 am
UUID: 7058e5d6-9433-cb4f-a362-f011386f5164
Ancestors: System-mt.1293

Complements Multilingual-mt.261

=============== Diff against System-mt.1293 ===============

Item was changed:
  ----- Method: ChangeSet class>>scanFile:from:to: (in category 'scanning') -----
  scanFile: file from: startPosition to: stopPosition
  	| changeList |
  	changeList := OrderedCollection new.
  	file position: startPosition.
  'Scanning ', file localName, '...'
  	displayProgressFrom: startPosition to: stopPosition
  	during: [:bar | | itemPosition item prevChar |
+ 	[ [file position < stopPosition] whileTrue:[
- 	[file position < stopPosition] whileTrue:[
  		bar value: file position.
  		[file atEnd not and: [file peek isSeparator]]
  			whileTrue: [prevChar := file next].
  		(file peekFor: $!!) ifTrue:[
  			(prevChar = Character cr or: [prevChar = Character lf])
  				ifTrue: [changeList addAll: (self scanCategory: file)].
  		] ifFalse:[
  			itemPosition := file position.
  			item := file nextChunk.
  			file skipStyleChunk.
  			item size > 0 ifTrue:[
+ 				changeList add: (ChangeRecord new file: file position: itemPosition type: #doIt)]]]
+ 	] on: InvalidUTF8 do: [:ex |
+ 		file isSourceFile ifTrue: [ex pass] ifFalse: [
+ 			self notify: ex messageText, '\\Proceed to try the legacy MacRoman encoding.' translated withCRs.
+ 			file reset; setConverterForOldCode.
+ 			^ self scanFile: file from: startPosition to: stopPosition]] ].
- 				changeList add: (ChangeRecord new file: file position: itemPosition type: #doIt).
- 			].
- 		].
- 	]].
  	^changeList!

Item was changed:
  ----- Method: FileDirectory class>>openSources:andChanges:forImage: (in category '*System-Files') -----
  openSources: sourcesName andChanges: changesName forImage: imageName 
  	"Open the changes and sources files and install them in SourceFiles. Inform the user of problems regarding write permissions or CR/CRLF mixups."
  	"Note: SourcesName and imageName are full paths; changesName is a  
  	local name."
  	| sources changes msg wmsg |
  	msg := 'Squeak cannot locate &fileRef.
  
  Please check that the file is named properly and is in the
  same directory as this image.'.
  	wmsg := 'Squeak cannot write to &fileRef.
  
  Please check that you have write permission for this file.
  
  You won''t be able to save this image correctly until you fix this.'.
  
  	sources := self openSources: sourcesName forImage: imageName.
+ 	sources ifNotNil: [sources setConverterForCode].
  	changes := self openChanges: changesName forImage: imageName.
+ 	changes ifNotNil: [changes setConverterForCode].
  
  	((sources == nil or: [sources atEnd])
  			and: [Preferences valueOfFlag: #warnIfNoSourcesFile])
  		ifTrue: [Smalltalk platformName = 'Mac OS'
  				ifTrue: [msg := msg , '
  Make sure the sources file is not an Alias.'].
  self inform: (msg copyReplaceAll: '&fileRef' with: 'the sources file named ' , sourcesName)].
  
  	(changes == nil
  			and: [Preferences valueOfFlag: #warnIfNoChangesFile])
  		ifTrue: [self inform: (msg copyReplaceAll: '&fileRef' with: 'the changes file named ' , changesName)].
  
  	((Preferences valueOfFlag: #warnIfNoChangesFile) and: [changes notNil])
  		ifTrue: [changes isReadOnly
  				ifTrue: [self inform: (wmsg copyReplaceAll: '&fileRef' with: 'the changes file named ' , changesName)].
  
  			((changes next: 200)
  					includesSubstring: String crlf)
  				ifTrue: [self inform: 'The changes file named ' , changesName , '
  has been injured by an unpacking utility.  Crs were changed to CrLfs.
  Please set the preferences in your decompressing program to 
  "do not convert text files" and unpack the system again.']].
  
  	SourceFiles := Array with: sources with: changes!

Item was changed:
  ----- Method: InternalTranslator>>fileOutHeaderOn: (in category 'user interface') -----
  fileOutHeaderOn: aStream 
+ 	aStream nextPutUTF8BOM.
- 	aStream binary.
- 	UTF8TextConverter writeBOMOn: aStream.
- 	aStream text.
  	aStream nextChunkPut: self fileOutHeader;
  		 cr.
  	aStream timeStamp; cr.
  	aStream nextPut: $!!.
  	aStream nextChunkPut: '(' , self class name , ' localeID: ' , id storeString , ')'.
  	aStream cr!

Item was changed:
  ----- Method: InternalTranslator>>fileOutHeaderOn:withBOM: (in category 'user interface') -----
  fileOutHeaderOn: aStream withBOM: bomFlag
+ 	bomFlag ifTrue: [aStream nextPutUTF8BOM].
- 	bomFlag ifTrue: [
- 		aStream binary.
- 		UTF8TextConverter writeBOMOn: aStream.
- 		aStream text.
- 	].
  	aStream nextChunkPut: self fileOutHeader;
  		 cr.
  	aStream timeStamp; cr.
  	aStream nextPut: $!!.
  	aStream nextChunkPut: '(' , self class name , ' localeID: ' , id storeString , ')'.
  	aStream cr!

Item was changed:
  ----- Method: MczInstaller>>contentsForMember: (in category 'private') -----
  contentsForMember: member
  	^[(member contentStreamFromEncoding: 'utf8') text contents] on: InvalidUTF8
  		do: [:exc | 
  			"Case of legacy encoding, presumably it is latin-1.
  			But if contents starts with a null character, it might be a case of WideString encoded in UTF-32BE"
  			| str |
+ 			self flag: #discuss. "mt: Isn't our mac-roman legacy more likely than latin-1?"
  			str := (member contentStreamFromEncoding: 'latin1') text..
  			exc return: ((str peek = Character null and: [ str size \\ 4 = 0 ])
  				ifTrue: [WideString fromByteArray: str contents asByteArray]
  				ifFalse: [str contents])]!

Item was changed:
  ----- Method: PositionableStream>>fileInFor:announcing: (in category '*System-Changes-fileIn/Out') -----
  fileInFor: client announcing: announcement
  	"This is special for reading expressions from text that has been formatted 
  	with exclamation delimitors. The expressions are read and passed to the 
  	Compiler. Answer the result of compilation.  Put up a progress report with
       the given announcement as the title."
  
  	| val |
  	announcement 
  		displayProgressFrom: 0
  		to: self size
  		during: 
  			[:bar | 
+ 			[ [self atEnd] whileFalse: 
- 			[self atEnd] whileFalse: 
  					[bar value: self position.
  					self skipSeparators.
  					
  					[ | chunk |
  					val := (self peekFor: $!!) 
  								ifTrue: [ | ch |
  									ch := self nextChunk.
  									(self shouldIgnore: ch)
  										ifTrue: [Transcript showln: 'Ignoring chunk: ', ch]
  										ifFalse: [(Compiler evaluate: ch for: client logged: true) scanFrom: self]]
  								ifFalse: 
  									[chunk := self nextChunk.
  									self checkForPreamble: chunk.
  									Compiler evaluate: chunk for: client logged: true]] 
  							on: InMidstOfFileinNotification
  							do: [:ex | ex resume: true].
+ 					self skipStyleChunk]
+ 			] on: InvalidUTF8 do: [:ex |
+ 				self notify: ex messageText, '\\Proceed to try the legacy MacRoman encoding.' translated withCRs.
+ 				self reset; setConverterForOldCode.
+ 				^ self fileInFor: client announcing: announcement].
- 					self skipStyleChunk].
  			self close].
  	"Note:  The main purpose of this banner is to flush the changes file."
  	Smalltalk logChange: '----End fileIn of ' , self name , '----'.
  	self flag: #ThisMethodShouldNotBeThere.	"sd"
  	^val!



More information about the Squeak-dev mailing list