[ENH] Basis for flexible source code management

Hans-Martin Mosner hm.mosner at cityweb.de
Wed Apr 26 20:03:29 UTC 2000


Hi,
recently, the source file size limit of 16M was raised to 32M, with the
side-effect of only allowing 2 source files from then on. This somehow
conflicts with my plans for a Squeak source code management system
(Collage) which has separate source files for every application. To keep
that path open while still supporting larger source files, I've written
these changes which concentrate all translation between sourcePointers
and source file indexes/positions in one single place.

I've chosen to replace the global variable SourceFiles, which is
currently an Array of two FileStreams (normally), by an instance of a
subclass of SourceFileArray, which can hold such files and additionally
provides the appropriate mapping methods. Using this approach, it should
be fairly easy to change source file access to a multi-file system as
used by Collage, or a database or network server interface such as that
used for the SqueakCVS project.

Please, SqC: Consider these changes for inclusion in the standard
release. I think that apart from the better extensibility of this
scheme, it has the big advantage of keeping all this ugly stuff in a
central place, making its maintenance easier.

Note: These changesets must be loaded in the correct order, and you
should load them after 2004BigSources-di because they have conflicting
method definitions.

Cheers,
Hans-Martin
-------------- next part --------------
'From Squeak2.8alpha of 19 January 2000 [latest update: #2005] on 26 April 2000 at 9:44:26 pm'!
"Change Set:		NewSources-2-hmm
Date:			26 April 2000
Author:			Hans-Martin Mosner <hmm at heeg.de>

Second part of the modification of the SourceFiles mechanism. In this change set, all methods that think they know about the structure of sourcePointers are replaced by versions that delegate to SourceFiles."!


!CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 20:44'!
fileIndex
	^SourceFiles fileIndexFromSourcePointer: self sourcePointer! !

!CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 20:45'!
filePosition
	^SourceFiles filePositionFromSourcePointer: self sourcePointer! !

!CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 21:00'!
setSourcePointer: srcPointer
	srcPointer = 0 ifTrue: [
		self at: self size put: 0.
		^self].
	(srcPointer between: 16r1000000 and: 16r4FFFFFF) ifFalse: [self error: 'Source pointer out of range'].
	self at: self size put: (srcPointer bitShift: -24) + 251.
	1 to: 3 do: [:i |
		self at: self size-i put: ((srcPointer bitShift: (i-3)*8) bitAnd: 16rFF)]! !

!CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 21:02'!
setSourcePosition: position inFile: fileIndex 
	self setSourcePointer: (SourceFiles sourcePointerFromFileIndex: fileIndex andPosition: position)! !

!CompiledMethod methodsFor: 'source code management' stamp: 'hmm 4/26/2000 20:44'!
sourcePointer
	"Answer the integer which can be used to find the source file and position for this method.
	The returned value is either 0 (if no source is stored) or a number between 16r1000000 and 16r4FFFFFF.
	The actual interpretation of this number is up to the SourceFileArray stored in the global variable SourceFiles."

	| pos |
	self last < 252 ifTrue: [^ 0  "no source"].
	pos _ self last - 251.
	self size - 1 to: self size - 3 by: -1 do: [:i | pos _ pos * 256 + (self at: i)].
	^pos! !


!RemoteString methodsFor: 'accessing' stamp: 'hmm 4/26/2000 21:28'!
setSourcePointer: aSourcePointer
	sourceFileNumber _ SourceFiles fileIndexFromSourcePointer: aSourcePointer.
	filePositionHi _ SourceFiles filePositionFromSourcePointer: aSourcePointer! !

!RemoteString methodsFor: 'accessing' stamp: 'hmm 4/26/2000 20:47'!
sourcePointer
	sourceFileNumber ifNil: [^ 0].
	^SourceFiles sourcePointerFromFileIndex: sourceFileNumber andPosition: filePositionHi! !

-------------- next part --------------
'From Squeak2.8alpha of 19 January 2000 [latest update: #2005] on 26 April 2000 at 9:44:17 pm'!
"Change Set:		NewSources-1-hmm
Date:			26 April 2000
Author:			Hans-Martin Mosner <hmm at heeg.de>

First part of a modification that concentrates all mapping from source pointers to actual source files in one place. This is needed for more sophisticated source code management schemes, such as that needed for Collage."!

SequenceableCollection subclass: #SourceFileArray
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'System-Source Files'!

!SourceFileArray commentStamp: 'hmm 4/25/2000 21:56' prior: 0!
This class is an abstract superclass for source code access mechanisms. It defines the messages that need to be understood by those subclasses that store and retrieve source chunks on files, over the network or in databases.
The first concrete subclass, StandardSourceFileArray, supports access to the traditional sources and changes files. Other subclasses might implement multiple source files for different applications, or access to a network source server.!
]style[(254 23 184)f1,f1LStandardSourceFileArray Comment;,f1!
SourceFileArray subclass: #StandardSourceFileArray
	instanceVariableNames: 'files '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'System-Source Files'!

!StandardSourceFileArray commentStamp: 'hmm 4/25/2000 21:58' prior: 0!
This class implements the source file management behavior of traditional Squeak, with a sources file and a changes file. File positions are mapped such that those files can be up to 32MBytes in size.

Structure:
 files		Array -- storing the actual source files
!

!SourceFileArray methodsFor: 'accessing' stamp: 'hmm 4/26/2000 21:42'!
at: index
	self subclassResponsibility! !

!SourceFileArray methodsFor: 'accessing' stamp: 'hmm 4/26/2000 21:43'!
at: index put: aFileStream
	self subclassResponsibility! !

!SourceFileArray methodsFor: 'accessing' stamp: 'hmm 4/26/2000 21:09'!
collect: aBlock
	^(1 to: self size) collect: [:i | aBlock value: (self at: i)]! !

!SourceFileArray methodsFor: 'accessing' stamp: 'hmm 4/26/2000 21:43'!
size
	self subclassResponsibility! !

!SourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'hmm 4/25/2000 22:00'!
fileIndexFromSourcePointer: anInteger
	"Return the index of a source file corresponding to the given source pointer."
	self subclassResponsibility! !

!SourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'hmm 4/25/2000 22:00'!
filePositionFromSourcePointer: anInteger
	"Return the position within a source file for the given source pointer."
	self subclassResponsibility! !

!SourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'hmm 4/25/2000 22:01'!
sourcePointerFromFileIndex: index andPosition: position
	"Return a sourcePointer encoding the given file index and position"
	self subclassResponsibility! !


!StandardSourceFileArray methodsFor: 'initialize-release' stamp: 'hmm 4/25/2000 21:20'!
initialize
	files _ Array new: 2.
	files at: 1 put: (SourceFiles at: 1).
	files at: 2 put: (SourceFiles at: 2)! !

!StandardSourceFileArray methodsFor: 'accessing' stamp: 'hmm 4/25/2000 21:20'!
at: index
	^files at: index! !

!StandardSourceFileArray methodsFor: 'accessing' stamp: 'hmm 4/25/2000 21:20'!
at: index put: aFile
	files at: index put: aFile! !

!StandardSourceFileArray methodsFor: 'accessing' stamp: 'hmm 4/25/2000 21:20'!
size
	^files size! !

!StandardSourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'hmm 4/25/2000 21:44'!
fileIndexFromSourcePointer: anInteger
	"Return the index of the source file which contains the source chunk addressed by anInteger"
	"This implements the recent 32M source file algorithm"

	| hi |
	hi _ anInteger // 16r1000000.
	^hi < 3
		ifTrue: [hi]
		ifFalse: [hi - 2]! !

!StandardSourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'hmm 4/25/2000 21:44'!
filePositionFromSourcePointer: anInteger
	"Return the position of the source chunk addressed by anInteger"
	"This implements the recent 32M source file algorithm"

	| hi lo |
	hi _ anInteger // 16r1000000.
	lo _ anInteger \\ 16r1000000.
	^hi < 3
		ifTrue: [lo]
		ifFalse: [lo + 16r1000000]! !

!StandardSourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'hmm 4/25/2000 21:48'!
sourcePointerFromFileIndex: index andPosition: position
	| hi lo |
	"Return a source pointer according to the new 32M algorithm"
	((index between: 1 and: 2) and: [position between: 0 and: 16r1FFFFFF])
		ifFalse: [self error: 'invalid source code pointer'].
	hi _ index.
	lo _ position.
	lo >= 16r1000000 ifTrue: [
		hi _ hi+2.
		lo _ lo - 16r1000000].
	^hi * 16r1000000 + lo! !


!StandardSourceFileArray class methodsFor: 'initialize-release' stamp: 'hmm 4/25/2000 21:19'!
install
	"Replace SourceFiles by an instance of me with the standard sources and changes files.
	This only works if SourceFiles is either an Array or an instance of this class"
	"StandardSourceFileArray install"
	SourceFiles _ self new initialize! !


!StandardSourceFileArray reorganize!
('initialize-release' initialize)
('accessing' at: at:put: changesFile size sourcesFile)
('sourcePointer conversion' fileIndexFromSourcePointer: filePositionFromSourcePointer: sourcePointerFromFileIndex:andPosition:)
!

"Postscript:
After defining the necessary classes, install the standard SourceFileArray which defines a sourcePointer mapping compatible to the old way."

StandardSourceFileArray install!



More information about the Squeak-dev mailing list