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

commits at source.squeak.org commits at source.squeak.org
Wed Jan 19 03:04:57 UTC 2022


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

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

Name: DTL-internal-sources-dtl.4
Author: dtl
Time: 18 January 2022, 9:51:18.957782 pm
UUID: e8cfc8eb-75b2-4b42-acf5-6cc17e0d455c
Ancestors: DTL-internal-sources-dtl.3

Move the internalized sources holder to a class var in CompressedSources to simplify package dependencies. Use #initializeCachedSources and #clearCachedSources to set or clear the internal sources. Override FileDirectory class>>#openSources:forImage: in this package (sorry) to look for the internalized CompressedSources.

Package postscript calls #initializeCachedSources to build cached sources and begin using them.

==================== Snapshot ====================

SystemOrganization addCategory: #'DTL-internal-sources'!

(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.'!

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.!

----- 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.!

----- 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
!

----- 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.!

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

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

----- Method: FileDirectory class>>openSources:forImage: (in category '*DTL-internal-sources') -----
openSources: fullSourcesName forImage: imageName 
	"If the sources file is cached in the image use it, otherwise load from a file."

	^ CompressedSources cachedSources
		ifNotNil: [ :cachedSources | cachedSources ]
		ifNil: [ self openSourcesFile: fullSourcesName forImage: imageName ]

!

----- Method: FileDirectory class>>openSourcesFile:forImage: (in category '*DTL-internal-sources') -----
openSourcesFile: fullSourcesName forImage: imageName 
"We first do a check to see if a compressed version ofthe sources file is present.
Open the .sources file read-only after searching in:
a) the directory where the VM lives
b) the directory where the image came from
c) the DefaultDirectory (which is likely the same as b unless the SecurityManager has changed it).
"

	| sources fd sourcesName |
	(fullSourcesName endsWith: 'sources') ifTrue:
		["Look first for a sources file in compressed format."
		sources := self openSources: (fullSourcesName allButLast: 7) , 'stc'
						forImage: imageName.
		sources ifNotNil: [^ CompressedSourceStream on: sources]].

	sourcesName := FileDirectory localNameFor: fullSourcesName.
	"look for the sources file or an alias to it in the VM's directory"
	fd := FileDirectory on: Smalltalk vmPath.
	(fd fileExists: sourcesName)
		ifTrue: [sources := fd readOnlyFileNamed: sourcesName].
	sources ifNotNil: [^ sources].
	"look for the sources file or an alias to it in the image directory"
	fd := FileDirectory on: (FileDirectory dirPathFor: imageName).
	(fd fileExists: sourcesName)
		ifTrue: [sources := fd readOnlyFileNamed: sourcesName].
	sources ifNotNil: [^ sources].
	"look for the sources in the current directory"
	fd := DefaultDirectory.
	(fd fileExists: sourcesName)
		ifTrue: [sources := fd readOnlyFileNamed: sourcesName].
	"sources may still be nil here"
	^sources
!

CompressedSourceStream subclass: #CompressedSources
	instanceVariableNames: ''
	classVariableNames: 'CachedSources'
	poolDictionaries: ''
	category: 'DTL-internal-sources'!

!CompressedSources commentStamp: 'dtl 1/16/2022 17:39' prior: 0!
A CompressedSources is a CompressedSourceStream that holds its sources in the image rather than in an external file.
!

----- Method: CompressedSources class>>cachedSources (in category 'accessing') -----
cachedSources
	^CachedSources!

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

----- Method: CompressedSources class>>initializeCachedSources (in category 'accessing') -----
initializeCachedSources

	"CompressedSources initializeCachedSources"
	"CompressedSources clearCachedSources"

	^ CachedSources := self newFromFiles.
!

----- 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.!

----- Method: CompressedSources>>readOnlyCopy (in category 'file open/close') -----
readOnlyCopy
	^self!

----- Method: CompressedSources>>reopen (in category 'file open/close') -----
reopen
	self position: 0.
!

----- 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.
!

----- 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!



More information about the Squeak-dev mailing list