[squeak-dev] The Trunk: Files-dtl.61.mcz

David T. Lewis lewis at mail.msen.com
Sat Dec 26 20:41:21 UTC 2009


On Sat, Dec 26, 2009 at 02:37:48PM -0500, David T. Lewis wrote:
> On Sat, Dec 26, 2009 at 05:49:48AM +0100, Levente Uzonyi wrote:
> > On Fri, 25 Dec 2009, David T. Lewis wrote:
> > 
> > >I ran into problems saving the large changes file patches, and reverted
> > >the update.  Sorry for the noise.
> > >
> > 
> > I guess the problem is related to #fileIndexFromSourcePointer: which 
> > returns 0 if sent to a StandardSourceFileArray when the argument is less 
> > than 16777216 (16r1000000), while ExpandedSourceFileArray returns 2. I 
> > guess that 0 is a valid result and some code expects this value.
> > 
> > Another difference between the two implementations is that 
> > ExpandedSourceFileArray new filePositionFromSourcePointer: 0 ===> -16777216
> > while
> > StandardSourceFileArray new filePositionFromSourcePointer: 0 ===> 0
> 
> Thank you, you're right. I'll fix this and spend some more time testing.
>

For reference, I'm attaching an update that is backward compatible
over the sourcePointer range 0 through 16rFFFFFF.

I think the actual problem that I had in loading this to truck was
something to do with Montecello load ordering, which I obviously
don't understand well enough at this point. I'll spend some more
time figuring this out before I risk messing up the trunk again.
Meantime these change sets can be loaded directly with no apparent
problems.

Dave
 
-------------- next part --------------
'From Squeak3.10.2 of 26 December 2009 [latest update: #8575] on 26 December 2009 at 3:26:19 pm'!
"Change Set:		ExpandedSourceFileArray-part1-dtl
Date:			26 December 2009
Author:			David T. Lewis

This is a variation on StandardSourceFileArray that permits large sources and changes files. It requires CompiledMethodTrailer as a prerequisite (currently available in Squeak trunk).

The available address space for source pointers in a traditional CompiledMethod is 16r1000000 through 16r4FFFFFF. StandardSourceFileArray maps positions in the sources file to address range 16r1000000 through 16r1FFFFFF and 16r3000000 through 16r3FFFFFF, and positions in the changes file to address range 16r2000000 through 16r2FFFFFF and 16r4000000 through 16r4FFFFFF. This permits a maximum file size of 16r2000000 (32MB) for both the sources file and the changes file. 

This implementation extends the source pointer address space using bit 25 of the source pointer to identify the external sources and changes files, with the remaining high order bits treated as address extension. This limits the number of external file references to two (the traditional sources and changes files). If additional external file references are needed in the future, some higher order bits in the source pointer address space should be allocated for that purpose.

The use of bit 25 of the source pointer for file references permits backward compatibility with StandardSourceFileArray, with essentially unlimited address space expansion for the sources and changes files.

ExpandedSourceFileArray will be the default kind of SourceFiles after restarting the image.

After loading this change set, load ExpandedSourceFileArray-part2-dtl to update CompiledMethod to avoid unnecessary checks for exceeding the changes file limit.
"!

TestCase subclass: #ExpandedSourceFileArrayTest
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Files-Tests'!

!ExpandedSourceFileArrayTest commentStamp: 'dtl 12/22/2009 23:10' prior: 0!
This test documents the source pointer address conversion methods for ExpandedSourceFileArray.

The available address space for source pointers in a traditional CompiledMethod is 16r1000000 through 16r4FFFFFF. StandardSourceFileArray maps positions in the sources file to address range 16r1000000 through 16r1FFFFFF and 16r3000000 through 16r3FFFFFF, and positions in the changes file to address range 16r2000000 through 16r2FFFFFF and 16r4000000 through 16r4FFFFFF. This permits a maximum file size of 16r2000000 (32MB) for both the sources file and the changes file. 

ExpandedSourceFileArray extends the source pointer address space using bit 25 of the source pointer to identify the external sources and changes files, with the remaining high order bits treated as address extension. This limits the number of external file references to two (the traditional sources and changes files). If additional external file references are needed in the future, some higher order bits in the source pointer address space should be allocated for that purpose.

The use of bit 25 of the source pointer for file references permits backward compatibility with StandardSourceFileArray, with essentially unlimited address space expansion for the sources and changes files.
!

SourceFileArray subclass: #ExpandedSourceFileArray
	instanceVariableNames: 'files'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Files-System'!

!ExpandedSourceFileArray commentStamp: 'dtl 12/22/2009 23:09' prior: 0!
This is a variation on StandardSourceFileArray that provides a larger maximum changes file size.

The available address space for source pointers in a traditional CompiledMethod is 16r1000000 through 16r4FFFFFF. StandardSourceFileArray maps positions in the sources file to address range 16r1000000 through 16r1FFFFFF and 16r3000000 through 16r3FFFFFF, and positions in the changes file to address range 16r2000000 through 16r2FFFFFF and 16r4000000 through 16r4FFFFFF. This permits a maximum file size of 16r2000000 (32MB) for both the sources file and the changes file. 

This implementation extends the source pointer address space using bit 25 of the source pointer to identify the external sources and changes files, with the remaining high order bits treated as address extension. This limits the number of external file references to two (the traditional sources and changes files). If additional external file references are needed in the future, some higher order bits in the source pointer address space should be allocated for that purpose.

The use of bit 25 of the source pointer for file references permits backward compatibility with StandardSourceFileArray, with essentially unlimited address space expansion for the sources and changes files.
!


!ExpandedSourceFileArrayTest methodsFor: 'testing' stamp: 'dtl 12/22/2009 23:05'!
testAddressRange
	"Test source pointer to file position address translation across a wide address range"
	
	| sf i p a |
	sf := ExpandedSourceFileArray new.
	(16r1000000 to: 16r10000000 by: 4093) do: [:e |
		i := sf fileIndexFromSourcePointer: e.
		p := sf filePositionFromSourcePointer: e.
		a := sf sourcePointerFromFileIndex: i andPosition: p.
		self assert: a = e]
! !

!ExpandedSourceFileArrayTest methodsFor: 'testing' stamp: 'dtl 12/22/2009 23:05'!
testChangesFileAddressRange
	"Test file position to source pointer address translation for the changes file"
	
	| sf i p a a2 |
	sf := ExpandedSourceFileArray new.
	(0 to: 16r1FFFFFFF by: 4093) do: [:e |
		a := sf sourcePointerFromFileIndex: 2 andPosition: e.
		i := sf fileIndexFromSourcePointer: a.
		self assert: i == 2.
		p := sf filePositionFromSourcePointer: a.
		self assert: p = e.
		a2 := sf sourcePointerFromFileIndex: 2 andPosition: p.
		self assert: a2 = a].
	(0 to: 16rFFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 2 andPosition: e.
		self assert: (a between: 16r2000000 and: 16r2FFFFFF)].
	(16r1000000 to: 16r1FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 2 andPosition: e.
		self assert: (a between: 16r4000000 and: 16r4FFFFFF)].
	(16r2000000 to: 16r2FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 2 andPosition: e.
		self assert: (a between: 16r6000000 and: 16r6FFFFFF)].
	(16r3000000 to: 16r3FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 2 andPosition: e.
		self assert: (a between: 16r8000000 and: 16r8FFFFFF)].
	(16r4000000 to: 16r4FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 2 andPosition: e.
		self assert: (a between: 16rA000000 and: 16rAFFFFFF)].
	(16r5000000 to: 16r5FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 2 andPosition: e.
		self assert: (a between: 16rC000000 and: 16rCFFFFFF)].
	(16r6000000 to: 16r6FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 2 andPosition: e.
		self assert: (a between: 16rE000000 and: 16rEFFFFFF)].
	(16r7000000 to: 16r7FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 2 andPosition: e.
		self assert: (a between: 16r10000000 and: 16r10FFFFFF)]



! !

!ExpandedSourceFileArrayTest methodsFor: 'testing' stamp: 'dtl 12/26/2009 15:22'!
testCompatibilityWithStandardSourceFileArray
	"Test compatibility with StandardSourceFileArray across the address range of
	StandardSourceFileArray, including the unused address space below 16r1000000"
	
	| ssf esf i1 i2 p1 p2 a1 a2 |
	ssf := StandardSourceFileArray new.
	esf := ExpandedSourceFileArray new.
	(0 to: 16rFFFFFF by: 811) do: [:e |
		i1 := ssf fileIndexFromSourcePointer: e.
		i2 := esf fileIndexFromSourcePointer: e.
		self assert: i1 = i2.
		self assert: i1 = 0. "This is unused address space"
		p1 := ssf filePositionFromSourcePointer: e.
		p2 := esf filePositionFromSourcePointer: e.
		self assert: p1 = p2].
	(16r4FFFFFF to: 16r4FFFFFF by: 811) do: [:e |
		i1 := ssf fileIndexFromSourcePointer: e.
		i2 := esf fileIndexFromSourcePointer: e.
		self assert: i1 = i2.
		p1 := ssf filePositionFromSourcePointer: e.
		p2 := esf filePositionFromSourcePointer: e.
		self assert: p1 = p2.
		a1 := ssf sourcePointerFromFileIndex: i1 andPosition: p1.
		a2 := esf sourcePointerFromFileIndex: i2 andPosition: p2.
		self assert: a1 = a2.
		self assert: a1= e]

! !

!ExpandedSourceFileArrayTest methodsFor: 'testing' stamp: 'dtl 12/26/2009 14:56'!
testFileIndexFromSourcePointer
	"Test derivation of file index for sources or changes file from source pointers"

	| sf |
	sf := ExpandedSourceFileArray new.
	"sources file mapping"
	self assert: 1 = (sf fileIndexFromSourcePointer: 16r1000000).
	self assert: 1 = (sf fileIndexFromSourcePointer: 16r1000013).
	self assert: 1 = (sf fileIndexFromSourcePointer: 16r1FFFFFF).
	self assert: 1 = (sf fileIndexFromSourcePointer: 16r3000000).
	self assert: 1 = (sf fileIndexFromSourcePointer: 16r3000013).
	self assert: 1 = (sf fileIndexFromSourcePointer: 16r3FFFFFF).

	self assert: 1 = (sf fileIndexFromSourcePointer: 16r5000000).
	self assert: 1 = (sf fileIndexFromSourcePointer: 16r5000013).
	self assert: 1 = (sf fileIndexFromSourcePointer: 16r5FFFFFF).

	(16r1000000 to: 16r1FFFFFF by: 811) do: [:e | self assert: 1 = (sf fileIndexFromSourcePointer: e)].
	(16r3000000 to: 16r3FFFFFF by: 811) do: [:e | self assert: 1 = (sf fileIndexFromSourcePointer: e)].
	"changes file mapping"
	self assert: 2 = (sf fileIndexFromSourcePointer: 16r2000000).
	self assert: 2 = (sf fileIndexFromSourcePointer: 16r2000013).
	self assert: 2 = (sf fileIndexFromSourcePointer: 16r2FFFFFF).
	self assert: 2 = (sf fileIndexFromSourcePointer: 16r4000000).
	self assert: 2 = (sf fileIndexFromSourcePointer: 16r4000013).
	self assert: 2 = (sf fileIndexFromSourcePointer: 16r4FFFFFF).

	self assert: 2 = (sf fileIndexFromSourcePointer: 16r6000000).
	self assert: 2 = (sf fileIndexFromSourcePointer: 16r6000013).
	self assert: 2 = (sf fileIndexFromSourcePointer: 16r6FFFFFF).

	(16r2000000 to: 16r2FFFFFF by: 811) do: [:e | self assert: 2 = (sf fileIndexFromSourcePointer: e)].
	(16r4000000 to: 16r4FFFFFF by: 811) do: [:e | self assert: 2 = (sf fileIndexFromSourcePointer: e)].

	"the following numeric ranges are unused but currently produces results as follows"
	self assert: 0 = (sf fileIndexFromSourcePointer: 16r0000000).
	self assert: 0 = (sf fileIndexFromSourcePointer: 16r0000013).
	self assert: 0 = (sf fileIndexFromSourcePointer: 16r0FFFFFF)

! !

!ExpandedSourceFileArrayTest methodsFor: 'testing' stamp: 'dtl 12/26/2009 14:56'!
testFilePositionFromSourcePointer
	"Test derivation of file position for sources or changes file from source pointers"

	| sf |
	sf := ExpandedSourceFileArray new.
	"sources file"
	self assert: 0 = (sf filePositionFromSourcePointer: 16r1000000).
	self assert: 16r13 = (sf filePositionFromSourcePointer: 16r1000013).
	self assert: 16rFFFFFF = (sf filePositionFromSourcePointer: 16r1FFFFFF).
	self assert: 16r1000000 = (sf filePositionFromSourcePointer: 16r3000000).
	self assert: 16r1000013 = (sf filePositionFromSourcePointer: 16r3000013).
	self assert: 16r1FFFFFF = (sf filePositionFromSourcePointer: 16r3FFFFFF).
	"changes file"
	self assert: 0 = (sf filePositionFromSourcePointer: 16r2000000).
	self assert: 16r13 = (sf filePositionFromSourcePointer: 16r2000013).
	self assert: 16rFFFFFF = (sf filePositionFromSourcePointer: 16r2FFFFFF).
	self assert: 16r1000000 = (sf filePositionFromSourcePointer: 16r4000000).
	self assert: 16r1000013 = (sf filePositionFromSourcePointer: 16r4000013).
	self assert: 16r1FFFFFF = (sf filePositionFromSourcePointer: 16r4FFFFFF).
	"the following numeric ranges are unused but currently produces results as follows"
	self assert: 0 = (sf filePositionFromSourcePointer: 16r0000000).
	self assert: 16r13 = (sf filePositionFromSourcePointer: 16r0000013).
	self assert: 16rFFFFFF = (sf filePositionFromSourcePointer: 16r0FFFFFF)
! !

!ExpandedSourceFileArrayTest methodsFor: 'testing' stamp: 'dtl 12/22/2009 23:05'!
testSourcePointerFromFileIndexAndPosition
	"Test valid input ranges"

	| sf |
	sf := ExpandedSourceFileArray new.
	self should: [sf sourcePointerFromFileIndex: 0 andPosition: 0] raise: Error.
	self shouldnt: [sf sourcePointerFromFileIndex: 1 andPosition: 0] raise: Error.
	self shouldnt: [sf sourcePointerFromFileIndex: 2 andPosition: 0] raise: Error.
	self should: [sf sourcePointerFromFileIndex: 0 andPosition: 3] raise: Error.
	self should: [sf sourcePointerFromFileIndex: 1 andPosition: -1] raise: Error.
	self shouldnt: [sf sourcePointerFromFileIndex: 1 andPosition: 16r1FFFFFF] raise: Error.
	self shouldnt: [sf sourcePointerFromFileIndex: 1 andPosition: 16r2000000] raise: Error.
	self should: [sf sourcePointerFromFileIndex: 3 andPosition: 0] raise: Error.
	self should: [sf sourcePointerFromFileIndex: 4 andPosition: 0] raise: Error.
	
	self assert: 16r1000000 = (sf sourcePointerFromFileIndex: 1 andPosition: 0).
	self assert: 16r1000013 = (sf sourcePointerFromFileIndex: 1 andPosition: 16r13).
	self assert: 16r1FFFFFF = (sf sourcePointerFromFileIndex: 1 andPosition: 16rFFFFFF).
	self assert: 16r2000000 = (sf sourcePointerFromFileIndex: 2 andPosition: 0).
	self assert: 16r2000013 = (sf sourcePointerFromFileIndex: 2 andPosition: 16r13).
	self assert: 16r2FFFFFF = (sf sourcePointerFromFileIndex: 2 andPosition: 16rFFFFFF).
	self assert: 16r3000000 = (sf sourcePointerFromFileIndex: 1 andPosition: 16r1000000).
	self assert: 16r3000013 = (sf sourcePointerFromFileIndex: 1 andPosition: 16r1000013).
	self assert: 16r3FFFFFF = (sf sourcePointerFromFileIndex: 1 andPosition: 16r1FFFFFF).
	self assert: 16r4000000 = (sf sourcePointerFromFileIndex: 2 andPosition: 16r1000000).
	self assert: 16r4000013 = (sf sourcePointerFromFileIndex: 2 andPosition: 16r1000013).
	self assert: 16r4FFFFFF = (sf sourcePointerFromFileIndex: 2 andPosition: 16r1FFFFFF)
! !

!ExpandedSourceFileArrayTest methodsFor: 'testing' stamp: 'dtl 12/22/2009 23:05'!
testSourcesFileAddressRange
	"Test file position to source pointer address translation for the sources file"
	
	| sf i p a a2 |
	sf := ExpandedSourceFileArray new.
	(0 to: 16r1FFFFFFF by: 4093) do: [:e |
		a := sf sourcePointerFromFileIndex: 1 andPosition: e.
		i := sf fileIndexFromSourcePointer: a.
		self assert: i == 1.
		p := sf filePositionFromSourcePointer: a.
		self assert: p = e.
		a2 := sf sourcePointerFromFileIndex: 1 andPosition: p.
		self assert: a2 = a].
	(0 to: 16rFFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 1 andPosition: e.
		self assert: (a between: 16r1000000 and: 16r1FFFFFF)].
	(16r1000000 to: 16r1FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 1 andPosition: e.
		self assert: (a between: 16r3000000 and: 16r3FFFFFF)].

	(16r2000000 to: 16r2FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 1 andPosition: e.
		self assert: (a between: 16r5000000 and: 16r5FFFFFF)].
	(16r3000000 to: 16r3FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 1 andPosition: e.
		self assert: (a between: 16r7000000 and: 16r7FFFFFF)].
	(16r4000000 to: 16r4FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 1 andPosition: e.
		self assert: (a between: 16r9000000 and: 16r9FFFFFF)].
	(16r5000000 to: 16r5FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 1 andPosition: e.
		self assert: (a between: 16rB000000 and: 16rBFFFFFF)].
	(16r6000000 to: 16r6FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 1 andPosition: e.
		self assert: (a between: 16rD000000 and: 16rDFFFFFF)].
	(16r7000000 to: 16r7FFFFFF by: 811) do: [:e |
		a := sf sourcePointerFromFileIndex: 1 andPosition: e.
		self assert: (a between: 16rF000000 and: 16rFFFFFFF)]
! !


!SmalltalkImage methodsFor: 'sources, changes log' stamp: 'dtl 12/24/2009 00:02'!
openSourceFiles

	self imageName = LastImageName ifFalse:
		["Reset the author initials to blank when the image gets moved"
		LastImageName := self imageName.
		Utilities setAuthorInitials: ''].
	FileDirectory
		openSources: self sourcesName
		andChanges: self changesName
		forImage: LastImageName.
	SourceFileArray install! !


!SourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'dtl 12/24/2009 10:05'!
checkOKToAdd: size at: filePosition
	"Issue several warnings as the end of the changes file approaches its limit,
	and finally halt with an error when the end is reached."

	^ self subclassResponsibility! !


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

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

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

!ExpandedSourceFileArray methodsFor: 'initialize-release' stamp: 'stephaneducasse 2/4/2006 20:32'!
initialize
	files := Array new: 2.
	files at: 1 put: (SourceFiles at: 1).
	files at: 2 put: (SourceFiles at: 2)! !

!ExpandedSourceFileArray methodsFor: 'initialize-release' stamp: 'stephaneducasse 2/4/2006 20:32'!
initialize: nFiles
	files := Array new: nFiles! !

!ExpandedSourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'dtl 12/24/2009 10:06'!
checkOKToAdd: size at: filePosition
	"No check is required"

	^ self! !

!ExpandedSourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'dtl 12/26/2009 15:03'!
fileIndexFromSourcePointer: anInteger
	"Return the index of the source file which contains the source chunk addressed by anInteger"

	(anInteger bitAnd: 16r1000000) ~= 0
		ifTrue: [^1 "sources file"]
		ifFalse: [anInteger >= 16r1000000
			ifTrue: [^2 "changes file"]
			ifFalse: [^0 "compatibility with StandardSourceFileArray"]]! !

!ExpandedSourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'dtl 12/26/2009 15:10'!
filePositionFromSourcePointer: anInteger 
	"Return the position of the source chunk addressed by anInteger"

	| hi lo |
	hi := anInteger // 33554432.
	lo := anInteger \\ 16777216.
	((anInteger bitAnd: 16777216) ~= 0
			or: [anInteger < 16777216 "compatibility with StandardSourceFileArray"])
		ifTrue: [^ hi * 16777216 + lo"sources file"]
		ifFalse: [^ hi - 1 * 16777216 + lo"changes file"]! !

!ExpandedSourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'dtl 12/23/2009 12:45'!
sourcePointerFromFileIndex: index andPosition: position
	"Return a sourcePointer encoding the given file index and position"

	| hi lo |
	(index = 1 or: [index = 2])
		ifFalse: [self error: 'invalid source file index'].
	position < 0 ifTrue: [self error: 'invalid source code pointer'].
	hi := position // 16r1000000 *2 + index.
	lo := position \\ 16r1000000.
	^ hi * 16r1000000 + lo
! !


!SourceFileArray class methodsFor: 'initialize-release' stamp: 'dtl 12/24/2009 13:01'!
concreteClass

	^ ExpandedSourceFileArray! !

!SourceFileArray class methodsFor: 'initialize-release' stamp: 'dtl 12/24/2009 00:01'!
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"

	"SourceFileArray install"

	^ SourceFiles := self concreteClass new! !


!ExpandedSourceFileArray class methodsFor: 'initialize-release' stamp: 'ar 5/17/2000 18:27'!
new: nFiles
	^self new initialize: nFiles.! !


!StandardSourceFileArray methodsFor: 'sourcePointer conversion' stamp: 'dtl 12/24/2009 10:04'!
checkOKToAdd: size at: filePosition
	"Issue several warnings as the end of the changes file approaches its limit,
	and finally halt with an error when the end is reached."

	| fileSizeLimit margin |
	fileSizeLimit := 16r2000000.
	3 to: 1 by: -1 do:
		[:i | margin := i*100000.
		(filePosition + size + margin) > fileSizeLimit
			ifTrue: [(filePosition + margin) > fileSizeLimit ifFalse:
						[self inform: 'WARNING: your changes file is within
' , margin printString , ' characters of its size limit.
You should take action soon to reduce its size.
You may proceed.']]
			ifFalse: [^ self]].
	(filePosition + size > fileSizeLimit) ifFalse: [^ self].
	self error: 'You have reached the size limit of the changes file.
You must take action now to reduce it.
Close this error.  Do not attempt to proceed.'! !

StandardSourceFileArray class removeSelector: #install!
-------------- next part --------------
'From Squeak3.10.2 of 26 December 2009 [latest update: #8575] on 26 December 2009 at 3:26:24 pm'!
"Change Set:		ExpandedSourceFileArray-part2-dtl
Date:			26 December 2009
Author:			David T. Lewis

Update CompiledMethod to avoid unnecessary checks for exceeding the changes file limit. Load this change set after ExpandedSourceFileArray-part1-dtl."!


!CompiledMethod methodsFor: 'source code management' stamp: 'dtl 12/24/2009 10:12'!
checkOKToAdd: size at: filePosition
	"Issue several warnings if the end of the changes file is approaching
	a fixed size limit, and finally halt with an error if the limit is reached."

	^ SourceFiles checkOKToAdd: size at: filePosition
! !



More information about the Squeak-dev mailing list