[FIX][Module] Module and ImageSegment

Bergel Alexandre bergel at iam.unibe.ch
Mon Mar 11 16:37:19 UTC 2002


Hello,

ImageSegment now works with image3.3. I hope I have broke nothing...

Regards,
Alexandre

-- 
_,.;:~^~:;._,.;:~^~:;._,.;:~^~:;._,.;:~^~:;._
Bergel Alexandre  http://www.iam.unibe.ch/~bergel
^~:;._,.;:~^~:;._,.;:~^~:;._,.;:~^~:;._,.;:~^
-------------- next part --------------
'From Squeak3.3alpha of 30 January 2002 [latest update: #4730] on 11 March 2002 at 5:07:57 pm'!
TestCase subclass: #ModuleTestsImageSegment
	instanceVariableNames: ''
	classVariableNames: ''
	module: #(Squeak Language Modules Tests)!

!Module methodsFor: 'image segment' stamp: 'AB 3/11/2002 15:35'!
readDataFrom: aDataStream size: varsOnDisk 
	| modulePath subref |
	version _ aDataStream next.
	modulePath _ aDataStream next.

	neighborModules _ aDataStream next.
	definedNames _ aDataStream next.
	exportedNames _ aDataStream next.
	repository _ aDataStream next.
	"parentModule _ Module fromPath: modulePath allButLast."
	(Module fromPath: modulePath)
		ifNotNil: [
			^ Module fromPath: modulePath].
	modulePath
		inject: Module root
		into: [:lparentModule :localName | 
			subref _ lparentModule neighborModuleRefs
						detect: [:ref | ref refersToSubmodule | ref refersToDeltaModule
								and: [ref name asLowercase = localName asLowercase]]
						ifNone: ["creation phase 1: create unresolved  
							reference (i.e. not the module)"
							lparentModule
								submodule: nil
								name: localName
								version: nil
								importNames: false].
			subref isModuleResolved not
				ifTrue: ["creation phase 2: resolve the module reference"
					subref resolvedModule: self].
			subref module].
	parentModule _ Module fromPath: modulePath allButLast.
	self assert: [(Module fromPath: modulePath) notNil].
	^ Module fromPath: modulePath! !

!Module methodsFor: 'image segment' stamp: 'AB 2/27/2002 16:15'!
storeDataOn: aDataStream 
	aDataStream beginInstance: self class size: self class instSize.
	aDataStream nextPut: self version;
		 nextPut: self path;
		 nextPut: self neighborModuleRefs;
		 nextPut: self definedNames;
		 nextPut: self exportedNames;
		 nextPut: nil
	"instead of parent module"! !


!ModuleTestsImageSegment methodsFor: 'as yet unclassified' stamp: 'AB 3/11/2002 15:55'!
createClassTest
	Object
		subclass: #TotoPopo
		instanceVariableNames: ''
		classVariableNames: ''
		poolDictionaries: ''
		category: 'Temporary-ImageSegmentTest'! !

!ModuleTestsImageSegment methodsFor: 'as yet unclassified' stamp: 'AB 3/11/2002 15:57'!
getClassTest
	^Smalltalk at: #TotoPopo! !

!ModuleTestsImageSegment methodsFor: 'as yet unclassified' stamp: 'AB 2/25/2002 23:38'!
loadImageSegment
	"return the arrayRoots"
	| name stream |
	name _ 'toto.extSeg'.
	stream _ FileStream fileNamed: name.
	^stream fileInObjectAndCode install arrayOfRoots.
! !

!ModuleTestsImageSegment methodsFor: 'as yet unclassified' stamp: 'AB 3/11/2002 16:28'!
removeClassTest
	(Smalltalk at: #TotoPopo) removeFromSystem! !

!ModuleTestsImageSegment methodsFor: 'as yet unclassified' stamp: 'AB 3/11/2002 16:13'!
removeOldFileIfExists
	| f |
	f _ FileDirectory default.
	(f fileExists: 'toto.extSeg')
		ifTrue: [f deleteFileNamed: 'toto.extSeg']! !

!ModuleTestsImageSegment methodsFor: 'as yet unclassified' stamp: 'AB 2/25/2002 23:40'!
saveImageSegmentWith: array
	"self new testImageSegment"
	| t |
	t _ ImageSegment new
				copyFromRootsForExport: array.
	t writeForExport: 'toto.extSeg'! !

!ModuleTestsImageSegment methodsFor: 'as yet unclassified' stamp: 'AB 3/11/2002 16:14'!
testImportSegment
	"self new testImportSegment"
	| array cls ans |
	self removeOldFileIfExists.
	self createClassTest.
	cls _ self getClassTest.
	array _ Array with: cls with: cls class.
	self saveImageSegmentWith: array.
	self removeClassTest.
	ans _ self loadImageSegment.
	self assert: ans size = 2;
		 assert: (ans at: 1) name = (array at: 1) name;
		 assert: (ans at: 2) name = (array at: 2) name;
		 assert: (ans at: 1) module = (Module @ #(#Temporary #ImageSegmentTest )).
	self removeClassTest! !

!ModuleTestsImageSegment methodsFor: 'as yet unclassified' stamp: 'AB 3/11/2002 16:01'!
testReferenceStream
	"self new testReferenceStream"
	| rr t |
	rr _ ReferenceStream fileNamed: 'test.obj'.
	rr nextPut: Module @ #(#Temporary #ImageSegment ).
	rr close.
	rr _ ReferenceStream fileNamed: 'test.obj'.
	t _ rr next.
	rr close.
	self assert: t = (Module @ #(#Temporary #ImageSegment ))! !

ModuleTestsImageSegment removeSelector: #removeOldFile!


More information about the Squeak-dev mailing list