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

commits at source.squeak.org commits at source.squeak.org
Sun Dec 27 17:08:59 UTC 2009


Andreas Raab uploaded a new version of Files to project The Trunk:
http://source.squeak.org/trunk/Files-dtl.62.mcz

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

Name: Files-dtl.62
Author: dtl
Time: 27 December 2009, 11:32:03 am
UUID: c0cbd563-4914-455a-9a6e-c5c7339d6bb8
Ancestors: Files-dtl.61

Add ExpandedSourceFileArray and ExpandedSourceFileArrayTest to support larger sources and changes file sizes, backward compatible with StandardSourceFileArray. Uses new CompiledMethodTrailer to permit large addresses.

Move #checkOKToAdd:at: implementation from CompiledMethod to SourceFileArray subclasses.

Add SourceFileArray class>>concreteClass to specify default source file array. Set default to ExpandedSourceFileArray.

SourceFiles will be an ExpandedSourceFileArray after the next image restart.

To change to another SourceFileArray implementation, or to revert to StandardSourceFileArray as default, update the SourceFileArray class>>concreteClass method.


=============== Diff against Files-dtl.61 ===============

Item was added:
+ ----- Method: ExpandedSourceFileArray>>checkOKToAdd:at: (in category 'sourcePointer conversion') -----
+ checkOKToAdd: size at: filePosition
+ 	"No check is required"
+ 
+ 	^ self!

Item was added:
+ ----- Method: ExpandedSourceFileArrayTest>>testSourcePointerFromFileIndexAndPosition (in category 'testing') -----
+ 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)
+ !

Item was added:
+ ----- Method: ExpandedSourceFileArray>>fileIndexFromSourcePointer: (in category 'sourcePointer conversion') -----
+ 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"]]!

Item was added:
+ ----- Method: SourceFileArray>>checkOKToAdd:at: (in category 'sourcePointer conversion') -----
+ 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!

Item was added:
+ ----- Method: SourceFileArray class>>install (in category 'initialize-release') -----
+ 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!

Item was added:
+ ----- Method: ExpandedSourceFileArrayTest>>testSourcesFileAddressRange (in category 'testing') -----
+ 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)]
+ !

Item was added:
+ ----- Method: ExpandedSourceFileArray>>filePositionFromSourcePointer: (in category 'sourcePointer conversion') -----
+ 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"]!

Item was added:
+ ----- Method: ExpandedSourceFileArray>>initialize (in category 'initialize-release') -----
+ initialize
+ 	files := Array new: 2.
+ 	files at: 1 put: (SourceFiles at: 1).
+ 	files at: 2 put: (SourceFiles at: 2)!

Item was added:
+ ----- Method: ExpandedSourceFileArrayTest>>testFilePositionFromSourcePointer (in category 'testing') -----
+ 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)
+ !

Item was added:
+ ----- Method: ExpandedSourceFileArrayTest>>testAddressRange (in category 'testing') -----
+ 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]
+ !

Item was added:
+ ----- Method: ExpandedSourceFileArrayTest>>testFileIndexFromSourcePointer (in category 'testing') -----
+ 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)
+ 
+ !

Item was added:
+ ----- Method: StandardSourceFileArray>>checkOKToAdd:at: (in category 'sourcePointer conversion') -----
+ 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.'!

Item was added:
+ 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.
+ !

Item was added:
+ ----- Method: ExpandedSourceFileArray>>initialize: (in category 'initialize-release') -----
+ initialize: nFiles
+ 	files := Array new: nFiles!

Item was added:
+ ----- Method: ExpandedSourceFileArray>>at: (in category 'accessing') -----
+ at: index
+ 	^files at: index!

Item was added:
+ ----- Method: ExpandedSourceFileArrayTest>>testChangesFileAddressRange (in category 'testing') -----
+ 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)]
+ 
+ 
+ 
+ !

Item was added:
+ ----- Method: ExpandedSourceFileArrayTest>>testCompatibilityWithStandardSourceFileArray (in category 'testing') -----
+ 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]
+ 
+ !

Item was added:
+ ----- Method: ExpandedSourceFileArray>>at:put: (in category 'accessing') -----
+ at: index put: aFile
+ 	files at: index put: aFile!

Item was added:
+ ----- Method: ExpandedSourceFileArray class>>new: (in category 'initialize-release') -----
+ new: nFiles
+ 	^self new initialize: nFiles.!

Item was added:
+ ----- Method: SourceFileArray class>>concreteClass (in category 'initialize-release') -----
+ concreteClass
+ 
+ 	^ ExpandedSourceFileArray!

Item was added:
+ ----- Method: ExpandedSourceFileArray>>sourcePointerFromFileIndex:andPosition: (in category 'sourcePointer conversion') -----
+ 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
+ !

Item was added:
+ 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.
+ !

Item was added:
+ ----- Method: ExpandedSourceFileArray>>size (in category 'accessing') -----
+ size
+ 	^files size!

Item was removed:
- ----- Method: StandardSourceFileArray class>>install (in category 'initialize-release') -----
- 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!




More information about the Squeak-dev mailing list