[squeak-dev] The Inbox: DTL-internal-sources-dtl.9.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jan 24 01:13:08 UTC 2022


A new version of DTL-internal-sources was added to project The Inbox:
http://source.squeak.org/inbox/DTL-internal-sources-dtl.9.mcz

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

Name: DTL-internal-sources-dtl.9
Author: dtl
Time: 22 January 2022, 8:00:02.326226 pm
UUID: 2a689c21-85bf-49dc-8b27-2fc19ac33dc9
Ancestors: DTL-internal-sources-dtl.8

Remove file system initialization that is no longer needed. Use the 'Cache sources file' preference in category 'Files' to enable or disable use of an internal sources file.

=============== Diff against DTL-internal-sources-dtl.4 ===============

Item was removed:
- ----- Method: CompressedSources class>>clearCachedSources (in category 'accessing') -----
- clearCachedSources
- 	^ CachedSources := nil.
- !

Item was added:
+ ----- Method: CompressedSources class>>fromSourceFileArray (in category 'instance creation') -----
+ fromSourceFileArray
+ 	"Answer a new instance created from the existing SourceFiles"
+ 
+ 	"CompressedSources fromSourceFileArray"
+ 
+ 	| f sourcesName |
+ 	f := SourceFiles first readOnlyCopy.
+ 	sourcesName := f localName.
+ 	(sourcesName endsWith: 'sources')
+ 		ifTrue: [^self fromSourcesFile: f].
+ 	^f asCompressedSources.
+ !

Item was added:
+ ----- Method: CompressedSources class>>fromSourcesFile: (in category 'private') -----
+ fromSourcesFile: f
+ 
+ 	| cf |
+ 	f binary. "binary to preserve utf8 encoding"
+ 	cf := (CompressedSources on: (ReadWriteStream with: ByteArray new))
+ 				segmentSize: 65536 maxSize: f size.
+ 
+ 	"Copy the sources"
+ 'Compressing Sources File...'
+ 	displayProgressAt: Sensor cursorPoint
+ 	from: 0 to: f size
+ 	during:
+ 		[:bar | f position: 0.
+ 		[f atEnd] whileFalse:
+ 			[cf nextPutAll: (f next: 65536).
+ 			bar value: f position]].
+ 	^cf.
+ !

Item was removed:
- ----- Method: CompressedSources class>>initializeCachedSources (in category 'accessing') -----
- initializeCachedSources
- 
- 	"CompressedSources initializeCachedSources"
- 	"CompressedSources clearCachedSources"
- 
- 	^ CachedSources := self newFromFiles.
- !

Item was added:
+ ----- Method: CompressedSources class>>internalizeSources (in category 'accessing') -----
+ internalizeSources
+ 
+ 	<preference: 'Cache sources file'
+ 	category: 'Files'
+ 	description: 'If true, a compressed sources file will be kept in the image to avoid file system access'
+ 	type: #Boolean>
+ 	^CachedSources notNil
+ !

Item was added:
+ ----- Method: CompressedSources class>>internalizeSources: (in category 'accessing') -----
+ internalizeSources: internalize
+ 
+ 	internalize
+ 		ifTrue: [CachedSources := self fromSourceFileArray position: 0]
+ 		ifFalse: [CachedSources := nil].
+ 	Smalltalk openSourceFiles.
+ !

Item was removed:
- ----- Method: CompressedSources class>>newFromFiles (in category 'instance creation') -----
- newFromFiles
- 	"Try updating FileDirectory class>>*openSources:forImage: to answer this."
- 	
- 	"Smalltalk openSourceFiles"
- 
- 	"CompressedSources newFromFiles"
- 
- 	^ self on: CompressedSourcesHolder newFromFiles.!

Item was added:
+ ----- Method: CompressedSources>>asCompressedSources (in category 'converting') -----
+ asCompressedSources
+ 	^self!

Item was changed:
  ----- Method: CompressedSources>>readOnlyCopy (in category 'file open/close') -----
  readOnlyCopy
+ 	"Not required for source file management, just answer a copy"
+ 	^self copy!
- 	^self!

Item was removed:
- ReadWriteStream subclass: #CompressedSourcesHolder
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'DTL-internal-sources'!
- 
- !CompressedSourcesHolder commentStamp: 'dtl 1/16/2022 17:42' prior: 0!
- A CompressedSourcesHolder replaces the file stream in a CompressedSourceStream with an in-image copy of the sources file data.!

Item was removed:
- ----- Method: CompressedSourcesHolder class>>compressedSourcesBytes (in category 'source files') -----
- compressedSourcesBytes
- 	"Contents of the compressed sources file"
- 
- 	| fs bytes |
- 	[fs := FileStream fileNamed: self compressedSourcesName.
- 	fs binary.
- 	bytes := fs contentsOfEntireFile]
- 		ensure: [fs close].
- 	^bytes.!

Item was removed:
- ----- Method: CompressedSourcesHolder class>>compressedSourcesName (in category 'source files') -----
- compressedSourcesName
- 
- 	| srcName |
- 	srcName := Smalltalk sourcesName.
- 	(srcName last: 7) = 'sources'
- 		ifTrue: [srcName := (srcName allButLast: 7), 'stc'].
- 	(FileDirectory default fileExists: srcName)
- 		ifFalse: [Smalltalk compressSources].
- 	(FileDirectory default fileExists: srcName)
- 		ifFalse: [self error: 'unable to find or create ', srcName].
- 	^srcName
- !

Item was removed:
- ----- Method: CompressedSourcesHolder class>>newFromFiles (in category 'instance creation') -----
- newFromFiles
- 	"Try updating FileDirectory class>>*openSources:forImage: to answer this."
- 	
- 	"Smalltalk openSourceFiles"
- 
- 	"CompressedSourcesHolder newFromFiles"
- 
- 	^ self on: self compressedSourcesBytes.!

Item was removed:
- ----- Method: CompressedSourcesHolder class>>on: (in category 'instance creation') -----
- on: bytes
- 	^ (super on: bytes) initializeSize.!

Item was removed:
- ----- Method: CompressedSourcesHolder>>initializeSize (in category 'initialize-release') -----
- initializeSize
- 	readLimit := writeLimit. "makes #size work as expected"!

Item was added:
+ TestCase subclass: #CompressedSourcesTest
+ 	instanceVariableNames: 'fileBasedStream testFile'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'DTL-internal-sources'!
+ 
+ !CompressedSourcesTest commentStamp: 'dtl 1/22/2022 11:23' prior: 0!
+ A CompressedSourcesTest verifies that CompressedSources matches the behavior of CompressedSourceStream. See CompressedSourceStream>>test
+ !

Item was added:
+ ----- Method: CompressedSourcesTest>>setUp (in category 'running') -----
+ setUp
+ 
+ 	testFile := 'test-tmp.stc'.
+ 	(FileDirectory default fileExists: testFile) ifTrue: [FileDirectory default deleteFileNamed: testFile].
+ 	fileBasedStream := CompressedSourceStream on: (FileStream newFileNamed: testFile).
+ !

Item was added:
+ ----- Method: CompressedSourcesTest>>tearDown (in category 'running') -----
+ tearDown
+ 
+ 	fileBasedStream close.
+ 	(FileDirectory default fileExists: testFile) ifTrue: [FileDirectory default deleteFileNamed: testFile].
+ !

Item was added:
+ ----- Method: CompressedSourcesTest>>testContentsOfEntireFile (in category 'tests') -----
+ testContentsOfEntireFile
+ 
+ 	| expectedData compressedSources actual |
+ 	fileBasedStream fileOutChanges.
+ 	expectedData := fileBasedStream contentsOfEntireFile.
+ 	compressedSources := CompressedSources on: (ReadWriteStream with: ByteArray new).
+ 	compressedSources fileOutChanges.
+ 	actual := compressedSources contentsOfEntireFile.
+ 	self assert: expectedData equals: actual.
+ 	
+ 
+ !

Item was added:
+ ----- Method: CompressedSourcesTest>>testFileOutChanges (in category 'tests') -----
+ testFileOutChanges
+ 	"A filie out from CompressedSources should produce the same data as that of CompressedSourceStream"
+ 
+ 	| fs expectedData compressedSources segmentFile |
+ 	fileBasedStream fileOutChanges.
+ 	[expectedData := (fs := FileStream fileNamed: testFile) binary contentsOfEntireFile] ensure: [fs close].
+ 	compressedSources := CompressedSources on: (ReadWriteStream with: ByteArray new).
+ 	compressedSources fileOutChanges.
+ 	segmentFile := compressedSources instVarAt: 6.
+ 	self assert: expectedData equals: segmentFile contents.
+ 	
+ 
+ !

Item was added:
+ ----- Method: CompressedSourcesTest>>testFileOutChangesWithSegmentCount (in category 'tests') -----
+ testFileOutChangesWithSegmentCount
+ 	"Specifying the segment count does not affect validity of the data. Use values
+ 	similar to (but different from) the defaults"
+ 
+ 	"(CompressedSourcesTest selector: #testFileOutChangesWithSegmentCount) debug"
+ 
+ 	| fs expectedData compressedSources segmentFile |
+ 	fileBasedStream segmentSize: 22345 maxSize: 34123456.
+ 	fileBasedStream fileOutChanges.
+ 	[expectedData := (fs := FileStream fileNamed: testFile) binary contentsOfEntireFile] ensure: [fs close].
+ 	compressedSources := CompressedSources on: (ReadWriteStream with: ByteArray new).
+ 	compressedSources  segmentSize: 22345 maxSize: 34123456.
+ 	compressedSources fileOutChanges.
+ 	segmentFile := compressedSources instVarAt: 6.
+ 	self assert: expectedData equals: segmentFile contents.
+ 	
+ 
+ !

Item was removed:
- ----- Method: RemoteString>>textDTL (in category '*DTL-internal-sources') -----
- textDTL
- 	"Answer the receiver's string asText if remote files are enabled."
- 
- 	| theFile |
- 	theFile := (CurrentReadOnlySourceFiles at: (sourceFileNumber ifNil: [ ^nil ])) ifNil: [ ^nil ].
- 	^ self textDTL: theFile.
- !

Item was removed:
- ----- Method: RemoteString>>textDTL: (in category '*DTL-internal-sources') -----
- textDTL: theFile
- 	"Answer the receiver's string asText if remote files are enabled."
- 
- 	theFile size <= filePositionHi ifTrue: [ 
- 		 "SourceFiles might have been appended to since theFile was opened. Flush the written data and reopen theFile to make it see the changes."
- 		(SourceFiles at: sourceFileNumber) flush.
- 		theFile reopen. "Currently the only way to re-read the size field of a read-only file on unix..." ].
- 	theFile size < filePositionHi ifTrue: [
- 		self error: 'RemoteString past end of file' ].
- 	^theFile
- 		position: filePositionHi;
- 		nextChunkText!

Item was removed:
- (PackageInfo named: 'DTL-internal-sources') postscript: '"Initialized the internal copy of the compressed sources file. Create an .stc file if it does not yet exist on the file system, then load and save its data in CompressedSources."
- 
- 	CompressedSources initializeCachedSources.
- 	Smalltalk openSourceFiles.'!



More information about the Squeak-dev mailing list