[squeak-dev] The Inbox: System-dtl.1277.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jan 1 20:47:18 UTC 2022


A new version of System was added to project The Inbox:
http://source.squeak.org/inbox/System-dtl.1277.mcz

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

Name: System-dtl.1277
Author: dtl
Time: 1 January 2022, 2:57:48.389886 pm
UUID: 4d975f20-d62d-4b7e-8abb-bc511d976834
Ancestors: System-mt.1276

Look for the sources file in well-known locations on some platforms. For Unix, if not found in the usual locations then look in /usr/share/squeak and /usr/local/share/squeak. Hooks for other platforms may be added to SmalltalkImage>>sourcesFilePaths.

Refactor to reduce duplication of logic in locateSourcesEntry and openSources:forImage: and to ensure that the full set of file paths is searched for stc compressed sources files prior to searching for regular sources files.

=============== Diff against System-mt.1276 ===============

Item was removed:
- ----- Method: FileDirectory class>>openChanges:forImage: (in category '*System-Files') -----
- openChanges: changesName forImage: imageName
- "find the changes file by looking in
- a) the directory derived from the image name
- b) the DefaultDirectory (which will normally be the directory derived from the image name or the SecurityManager's choice)
- If an old file is not found in either place, check for a read-only file in the same places. If that fails, return nil"
- 	| changes fd |
- 	"look for the changes file or an alias to it in the image directory"
- 	fd := FileDirectory on: (FileDirectory dirPathFor: imageName).
- 	(fd fileExists: changesName)
- 		ifTrue: [changes := fd oldFileNamed: changesName].
- 	changes ifNotNil:[^changes].
- 
- 	"look for the changes in the default directory"
- 	fd := DefaultDirectory.
- 	(fd fileExists: changesName)
- 		ifTrue: [changes := fd oldFileNamed: changesName].
- 	changes ifNotNil:[^changes].
- 
- 	"look for read-only changes in the image directory"
- 	fd := FileDirectory on: (FileDirectory dirPathFor: imageName).
- 	(fd fileExists: changesName)
- 		ifTrue: [changes := fd readOnlyFileNamed: changesName].
- 	changes ifNotNil:[^changes].
- 
- 	"look for read-only changes in the default directory"
- 	fd := DefaultDirectory.
- 	(fd fileExists: changesName)
- 		ifTrue: [changes := fd readOnlyFileNamed: changesName].
- 	"this may be nil if the last try above failed to open a file"
- 	^changes
- !

Item was removed:
- ----- 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.
- 	changes := self openChanges: changesName forImage: imageName.
- 
- 	((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 removed:
- ----- Method: FileDirectory class>>openSources:forImage: (in category '*System-Files') -----
- openSources: 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
- !

Item was removed:
- ----- Method: SmalltalkImage>>locateSourcesEntry (in category 'image, changes names') -----
- locateSourcesEntry
- 	| sourcesFilename |
- 	sourcesFilename := SourceFileVersionString , FileDirectory dot , 'sources'.
- 	^ {Smalltalk vmPath. 
- 	FileDirectory default fullName, FileDirectory slash}
- 		detect: [ : each | (each , sourcesFilename) asDirectoryEntry notNil ]
- 		ifFound: [ : foundPath | (foundPath , sourcesFilename) asDirectoryEntry ]
- 		ifNone: [ nil ]!

Item was added:
+ ----- Method: SmalltalkImage>>locateSourcesEntry: (in category 'image, changes names') -----
+ locateSourcesEntry: sourcesFilename
+ 	"Locate sources file entry, looking first in the VM path directory, then in the image
+ 	directory, and finally in some well-known locations for various OS platforms"
+ 
+ 	^ self sourcesFilePaths
+ 		detect: [ : each | (each , sourcesFilename) asDirectoryEntry notNil ]
+ 		ifFound: [ : foundPath | (foundPath , sourcesFilename) asDirectoryEntry ]
+ 		ifNone: [ nil ]!

Item was added:
+ ----- Method: SmalltalkImage>>openChanges:forImage: (in category 'image, changes names') -----
+ openChanges: changesName forImage: imageName
+ "find the changes file by looking in
+ a) the directory derived from the image name
+ b) the DefaultDirectory (which will normally be the directory derived from the image name or the SecurityManager's choice)
+ If an old file is not found in either place, check for a read-only file in the same places. If that fails, return nil"
+ 	| changes fd |
+ 	"look for the changes file or an alias to it in the image directory"
+ 	fd := FileDirectory on: (FileDirectory dirPathFor: imageName).
+ 	(fd fileExists: changesName)
+ 		ifTrue: [changes := fd oldFileNamed: changesName].
+ 	changes ifNotNil:[^changes].
+ 
+ 	"look for the changes in the default directory"
+ 	fd := FileDirectory default.
+ 	(fd fileExists: changesName)
+ 		ifTrue: [changes := fd oldFileNamed: changesName].
+ 	changes ifNotNil:[^changes].
+ 
+ 	"look for read-only changes in the image directory"
+ 	fd := FileDirectory on: (FileDirectory dirPathFor: imageName).
+ 	(fd fileExists: changesName)
+ 		ifTrue: [changes := fd readOnlyFileNamed: changesName].
+ 	changes ifNotNil:[^changes].
+ 
+ 	"look for read-only changes in the default directory"
+ 	fd := FileDirectory default.
+ 	(fd fileExists: changesName)
+ 		ifTrue: [changes := fd readOnlyFileNamed: changesName].
+ 	"this may be nil if the last try above failed to open a file"
+ 	^changes
+ !

Item was changed:
  ----- Method: SmalltalkImage>>openSourceFiles (in category 'sources, changes log') -----
  openSourceFiles
- 
  	self imageName = LastImageName ifFalse:
  		["Reset the author initials to blank when the image gets moved"
  		LastImageName := self imageName.
  		Utilities authorInitials: ''].
+ 	self
+ 		openSourcesAndChanges: self changesName
- 	FileDirectory
- 		openSources: self sourcesName
- 		andChanges: self changesName
  		forImage: LastImageName.
  	SourceFileArray install!

Item was added:
+ ----- Method: SmalltalkImage>>openSources (in category 'image, changes names') -----
+ openSources
+ 	"Open a sources file from one of several possible locations. Check first for
+ 	a compressed sources file and use that if available."
+ 
+ 	(self locateSourcesEntry: self sourcesCompressedFileName)
+ 		ifNotNil: [ :entry | ^ CompressedSourceStream on: entry readStream ].
+ 	(self locateSourcesEntry: self sourcesFileName)
+ 		ifNotNil: [ :entry | ^ entry readStream ].
+ 	^nil.
+ !

Item was added:
+ ----- Method: SmalltalkImage>>openSourcesAndChanges:forImage: (in category 'image, changes names') -----
+ openSourcesAndChanges: 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 := Smalltalk openSources.
+ 	changes := Smalltalk openChanges: changesName forImage: imageName.
+ 
+ 	((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 ' , self 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 added:
+ ----- Method: SmalltalkImage>>sourcesCompressedFileName (in category 'image, changes names') -----
+ sourcesCompressedFileName
+ 	^SourceFileVersionString , FileDirectory dot, 'stc'
+ !

Item was added:
+ ----- Method: SmalltalkImage>>sourcesFileName (in category 'image, changes names') -----
+ sourcesFileName
+ 	^SourceFileVersionString , FileDirectory dot , 'sources'
+ !

Item was added:
+ ----- Method: SmalltalkImage>>sourcesFilePaths (in category 'image, changes names') -----
+ sourcesFilePaths
+ 	"A list of likely locations for the sources file. Look first in the VM path directory, then
+ 	in the image directory, and finally in some well-known locations for this OS platform"
+ 
+ 	| paths vmPath imagePath defaultPath |
+ 	paths := OrderedCollection new.
+ 	paths add: (vmPath := self vmPath).
+ 	paths add: (imagePath := self imagePath, FileDirectory slash).
+ 	imagePath = (defaultPath := FileDirectory default fullName, FileDirectory slash)
+ 		ifFalse: ["imagePath and defaultPath are usually the same"
+ 			paths add: defaultPath].
+ 	('/usr/*/lib/*' match: vmPath)
+ 		ifTrue: ["Unix platform with VM installed in system directories"
+ 			paths
+ 				add: '/usr/share/squeak/';
+ 				add: '/usr/local/share/squeak/' ].
+ 	"Well known paths for other platform types may be added here"
+ 
+ 	^paths
+ !

Item was changed:
  ----- Method: SmalltalkImage>>sourcesName (in category 'image, changes names') -----
  sourcesName
  	"Answer the full path to the version-stable source code if it exists, otherwise the desired location"
+ 	^ (self locateSourcesEntry: self sourcesFileName)
+ 		ifNil: [ self vmPath , self sourcesFileName ]
- 	^ self locateSourcesEntry
- 		ifNil: [ self vmPath , SourceFileVersionString , FileDirectory dot , 'sources' ]
  		ifNotNil: [ : entry | entry fullName ]!



More information about the Squeak-dev mailing list