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

commits at source.squeak.org commits at source.squeak.org
Sat Jan 29 10:01:25 UTC 2022


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

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

Name: Tools-mt.1117
Author: mt
Time: 29 January 2022, 11:01:21.856024 am
UUID: fc3e3c9c-6252-7a43-a8d9-2815b8648925
Ancestors: Tools-mt.1116

Complements Multilingual-mt.261

=============== Diff against Tools-mt.1116 ===============

Item was changed:
  ----- Method: ChangeList class>>browseCompressedChangesFile: (in category 'fileIn/Out') -----
  browseCompressedChangesFile: fullName 
  	"Browse the selected file in fileIn format."
  
+ 	| unzipped |
- 	| unzipped stream |
  	fullName ifNil: [^Beeper beep].
+ 	FileStream readOnlyFileNamed: fullName do: [:stream |
+ 		unzipped := (GZipReadStream on: stream) contents].
+ 	ChangeList browseStream: (MultiByteBinaryOrTextStream with: unzipped asString)!
- 	stream := FileStream readOnlyFileNamed: fullName.
- 	[ | zipped |stream converter: Latin1TextConverter new.
- 	zipped := GZipReadStream on: stream.
- 	unzipped := zipped contents asString]
- 		ensure: [stream close].
- 	stream := (MultiByteBinaryOrTextStream with: unzipped) reset.
- 	ChangeList browseStream: stream!

Item was changed:
  ----- Method: ChangeList class>>browseMethodVersions (in category 'public access') -----
  browseMethodVersions
  	
  	| changeList end changesFile filteredRecords |
  	changesFile := (SourceFiles at: 2) readOnlyCopy.
- 	changesFile setConverterForCode.
  	end := changesFile size.
  	changeList := self new.
  	Cursor read showWhile: [
+ 		changeList scanFile: changesFile from: 0 to: end].
- 		[changeList scanFile: changesFile from: 0 to: end]
- 			on: InvalidUTF8 do: [:err | err resume: '']].
  	changesFile close.
  	
  	filteredRecords := Dictionary new.
  	changeList changeList
  		do: [:changeRecord |
  			changeRecord methodSelector ifNotNil: [:selector |
  				| class |
  				class := changeRecord methodClass.
  				"Only collect records that point to not-installed methods."
  				(class isNil or: [(class includesSelector: selector) not]) ifTrue: [				
  					(filteredRecords at: selector ifAbsentPut: [OrderedCollection new])
  						add: changeRecord]]]
  		displayingProgress: [:changeRecord | 'Parsing source code at {1}...' translated format: {changeRecord position}]. 	
  	filteredRecords explore. "Open explorer to allow user to repeat the following step manually."
  	self browseMethodVersions: filteredRecords.!

Item was changed:
  ----- Method: ChangeList>>scanFile:from:to: (in category 'scanning') -----
  scanFile: aFile from: startPosition to: stopPosition
  	
  	file := aFile.
  	changeList := OrderedCollection new.
  	list := OrderedCollection new.
  	listIndex := 0.
  	file position: startPosition.
  ('Scanning {1}...' translated format: {aFile localName})
  	displayProgressFrom: startPosition to: stopPosition
  	during: [:bar | | prevChar itemPosition item |
+ 	[ [file position < stopPosition]
- 	[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: [self scanCategory]]
  		ifFalse:
  			[itemPosition := file position.
  			item := file nextChunk.
  			file skipStyleChunk.
  			item size > 0 ifTrue:
  				[(item beginsWith: '----')
  					ifTrue:
  						[self addItem: (ChangeRecord new
  								file: file position: itemPosition type: #misc)
  								text: 'misc: ' , (item contractTo: 50)]
  					ifFalse:
  						[self addItem: (ChangeRecord new
  								file: file position: itemPosition type: #doIt)
+ 								text: 'do it: ' , (item contractTo: 50)]]]]
+ 	] on: InvalidUTF8 do: [:ex |
+ 		aFile isSourceFile ifTrue: [ex pass] ifFalse: [
+ 			self notify: ex messageText, '\\Proceed to try the legacy MacRoman encoding.' translated withCRs.
+ 			aFile reset; setConverterForOldCode.
+ 			^ self scanFile: aFile from: startPosition to: stopPosition]] ].
- 								text: 'do it: ' , (item contractTo: 50)]]]]].
  	self resetListSelections.!

Item was removed:
- ----- Method: FileList>>defaultEncoderFor: (in category 'private') -----
- defaultEncoderFor: aFileName
- 
- 	"This method just illustrates the stupidest possible implementation of encoder selection."
- 	| l |
- 	l := aFileName asLowercase.
- "	((l endsWith: FileStream multiCs) or: [
- 		l endsWith: FileStream multiSt]) ifTrue: [
- 		^ UTF8TextConverter new.
- 	].
- "
- 	((l endsWith: FileStream cs) or: [
- 		l endsWith: FileStream st]) ifTrue: [
- 		^ MacRomanTextConverter new.
- 	].
- 
- 	^ Latin1TextConverter new.
- 
- 	!

Item was changed:
  ----- Method: FileList>>readContentsBrief: (in category 'private') -----
  readContentsBrief: brevityFlag
  	"Read the contents of the receiver's selected file, unless it is too long, in which case show just the first 5000 characters. Don't create a file if it doesn't already exist."
  	| f fileSize first5000 |
  
  	brevityFlag ifTrue: [
  		directory isRemoteDirectory ifTrue: [^ self readServerBrief]].
  	f := directory oldFileOrNoneNamed: self fullName.
  	f ifNil: [^ 'For some reason, this file cannot be read' translated].
+ 	self setDefaultEncoderFor: f.
- 	f converter: (self defaultEncoderFor: self fullName).
  	(brevityFlag not or: [(fileSize := f size) <= 100000]) ifTrue:
  		[contents := f contentsOfEntireFile.
  		brevityState := #fullFile.   "don't change till actually read"
  		^ contents].
  
  	"if brevityFlag is true, don't display long files when first selected"
  	first5000 := f next: 5000.
  	f close.
  	contents := 'File ''{1}'' is {2} bytes long.
  You may use the ''get'' command to read the entire file.
  
  Here are the first 5000 characters...
  ------------------------------------------
  {3}
  ------------------------------------------
  ... end of the first 5000 characters.' translated format: {fileName. fileSize. first5000}.
  	brevityState := #briefFile.   "don't change till actually read"
  	^ contents.
  !

Item was added:
+ ----- Method: FileList>>setDefaultEncoderFor: (in category 'private') -----
+ setDefaultEncoderFor: fileStream
+ 	"Based on former #defaultEncoderFor:."
+ 
+ 	| l |
+ 	l := fileStream fullName asLowercase.
+ "	((l endsWith: FileStream multiCs) or: [
+ 		l endsWith: FileStream multiSt]) ifTrue: [
+ 		^ UTF8TextConverter new.
+ 	].
+ "
+ 	((l endsWith: FileStream cs) or: [l endsWith: FileStream st])
+ 		ifTrue: [fileStream setConverterForCode]
+ 		ifFalse: [fileStream converter: ISO88591TextConverter new].!



More information about the Squeak-dev mailing list