[squeak-dev] The Trunk: MorphicExtras-fbs.115.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jul 6 14:01:06 UTC 2013


Frank Shearar uploaded a new version of MorphicExtras to project The Trunk:
http://source.squeak.org/trunk/MorphicExtras-fbs.115.mcz

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

Name: MorphicExtras-fbs.115
Author: fbs
Time: 6 July 2013, 2:59:42.606 pm
UUID: 98dc0312-78ac-334c-96da-c32edff86852
Ancestors: MorphicExtras-fbs.114

Move ObjectOut to MorphicExtras-SqueakPage to be closer to the other sqp stuff. This at least separates SqueakPage code from Kernel, while we figure out how to properly disentagle things.

=============== Diff against MorphicExtras-fbs.114 ===============

Item was added:
+ ProtoObject subclass: #ObjectOut
+ 	instanceVariableNames: 'url page recursionFlag'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicExtras-SqueakPage'!
+ 
+ !ObjectOut commentStamp: '<historical>' prior: 0!
+ I am a stand-in for an object that is out on the disk.  The object that is out on the disk is the head of a tree of objects that are out.  See SqueakPage.
+ 
+ When any message is sent to me, I don't understand it, and bring in my true object.  I become myself with the objects and resend the message.  
+ 
+ I may not represent the object nil.  
+ The file is represented as a url, and that url may point at any file on the net.  
+ 
+ page is a SqueakPage.
+ If the cache already has an object, widely in use, that claims to be the object for my url, what do I do?  I can't become him, since others believe that he is the true object.  Run through memory and replace refs to me with refs to him.  Be careful not to trigger a fault.  Become me to a string, then find pointers and replace?
+ 
+ [[[They don't want to end up holding an ObjectOut.  (would oscillate back and forth)  This is a problem.  A user could bring in two trees that both refer to a 3rd url.  (check with cache before installing any new ObjectOut) Two trees could be written to the same url.
+ Or, I remain an ObjectOut, and keep getting notUnderstood, and keep returning the other guy.
+ Or I smash the cache, and install MY page and object.  Other guy is a copy -- still in, but with no place in the cache.  When we both write to the same url, there will be trouble.]  No -- search and replace.]]]
+ !

Item was added:
+ ----- Method: ObjectOut>>comeFullyUpOnReload: (in category 'object storage') -----
+ comeFullyUpOnReload: smartRefStream
+ 	"Normally this read-in object is exactly what we want to store.  Try to dock first.  If it is here already, use that one."
+ 
+ 	| sp |
+ 	"Transcript show: 'has ref to: ', url; cr."
+ 	(sp := SqueakPageCache pageCache at: page ifAbsent: [nil]) ifNotNil: [
+ 		sp isContentsInMemory ifTrue: [^ sp contentsMorph]].
+ 	^ self!

Item was added:
+ ----- Method: ObjectOut>>doesNotUnderstand: (in category 'fetch from disk') -----
+ doesNotUnderstand: aMessage 
+ 	"Bring in the object, install, then resend aMessage"
+ 	| realObject oldFlag response |
+ 	oldFlag := recursionFlag.
+ 	recursionFlag := true.
+ 	"fetch the object"
+ 	realObject := self xxxFetch.		"watch out for the become!!"
+ 			"Now we ARE the realObject"
+ 	oldFlag == true ifTrue: [
+ 		response := (UIManager default chooseFrom: #('proceed normally' 'debug')
+ 			title: 'Object being fetched for a second time.
+ Should not happen, and needs to be fixed later.').
+ 		response = 2 ifTrue: [self halt]].	"We are already the new object"
+ 
+ 	"Can't be a super message, since this is the first message sent to this object"
+ 	^ realObject perform: aMessage selector withArguments: aMessage arguments!

Item was added:
+ ----- Method: ObjectOut>>isInMemory (in category 'basics') -----
+ isInMemory
+ 	"We are a place holder for an object that is out."
+ 	^ false!

Item was added:
+ ----- Method: ObjectOut>>objectForDataStream: (in category 'object storage') -----
+ objectForDataStream: refStrm
+     "Return an object to store on a data stream (externalize myself)."
+ 
+     ^ self!

Item was added:
+ ----- Method: ObjectOut>>readDataFrom:size: (in category 'object storage') -----
+ readDataFrom: aDataStream size: varsOnDisk
+ 	"Make self be an object based on the contents of aDataStream, which was generated by the object's storeDataOn: method. Return self."
+ 	| cntInstVars |
+ 	cntInstVars := self xxxClass instSize.
+ 	self xxxClass isVariable
+ 		ifTrue: [self xxxClass error: 'needs updating']	"assume no variable subclasses"
+ 		ifFalse: [cntInstVars := varsOnDisk].
+ 
+ 	aDataStream beginReference: self.
+ 	1 to: cntInstVars do:
+ 		[:i | self xxxInstVarAt: i put: aDataStream next].
+ "	1 to: cntIndexedVars do:
+ 		[:i | self basicAt: i put: aDataStream next].
+ "
+ 	^ self!

Item was changed:
+ ----- Method: ObjectOut>>sqkPage (in category 'access') -----
- ----- Method: ObjectOut>>sqkPage (in category '*MorphicExtras-access') -----
  sqkPage
  	^ page!

Item was added:
+ ----- Method: ObjectOut>>storeDataOn: (in category 'object storage') -----
+ storeDataOn: aDataStream
+ 	"Store myself on a DataStream. See also objectToStoreOnDataStream.
+ 	must send 'aDataStream beginInstance:size:'"
+ 	| cntInstVars |
+ 
+ 	cntInstVars := self class instSize.
+ 	"cntIndexedVars := self basicSize."
+ 	aDataStream
+ 		beginInstance: self xxxClass
+ 		size: cntInstVars "+ cntIndexedVars".
+ 	1 to: cntInstVars do:
+ 		[:i | aDataStream nextPut: (self xxxInstVarAt: i)].
+ "	1 to: cntIndexedVars do:
+ 		[:i | aDataStream nextPut: (self basicAt: i)]
+ "!

Item was changed:
+ ----- Method: ObjectOut>>url (in category 'access') -----
- ----- Method: ObjectOut>>url (in category '*MorphicExtras-access') -----
  url
  	^ url!

Item was added:
+ ----- Method: ObjectOut>>url: (in category 'access') -----
+ url: aString
+ 
+ 	url := aString!

Item was added:
+ ----- Method: ObjectOut>>veryDeepCopyWith: (in category 'object storage') -----
+ veryDeepCopyWith: deepCopier
+ 	"Copy me and the entire tree of objects I point to.  An object in the tree twice is copied once, and both references point to him.  deepCopier holds a dictionary of objects we have seen.  Some classes refuse to be copied.  Some classes are picky about which fields get deep copied."
+ 	| class index sub subAss new absent |
+ 	new := deepCopier references at: self ifAbsent: [absent := true].
+ 	absent ifNil: [^ new].	"already done"
+ 	class := self xxxClass.
+ 	class isMeta ifTrue: [^ self].		"a class"
+ 	new := self xxxClone.
+ 	"not a uniClass"
+ 	deepCopier references at: self put: new.	"remember"
+ 	"class is not variable"
+ 	index := class instSize.
+ 	[index > 0] whileTrue: 
+ 		[sub := self xxxInstVarAt: index.
+ 		(subAss := deepCopier references associationAt: sub ifAbsent: [nil])
+ 			ifNil: [new xxxInstVarAt: index put: (sub veryDeepCopyWith: deepCopier)]
+ 			ifNotNil: [new xxxInstVarAt: index put: subAss value].
+ 		index := index - 1].
+ 	new rehash.	"force Sets and Dictionaries to rehash"
+ 	^ new
+ !

Item was added:
+ ----- Method: ObjectOut>>xxxClass (in category 'basics') -----
+ xxxClass
+ 	"Primitive. Answer the object which is the receiver's class. Essential. See 
+ 	Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 111>
+ 	self primitiveFailed!

Item was added:
+ ----- Method: ObjectOut>>xxxClone (in category 'basics') -----
+ xxxClone
+ 
+ 	<primitive: 148>
+ 	self primitiveFailed!

Item was changed:
+ ----- Method: ObjectOut>>xxxFetch (in category 'fetch from disk') -----
- ----- Method: ObjectOut>>xxxFetch (in category '*MorphicExtras-SqueakPage') -----
  xxxFetch
  	"Bring in my object and replace all references to me with references to him.  First try looking up my url in the pageCache.  Then try the page (and install it, under its url).  Then start from scratch with the url."
  
  	| truePage object existing |
  	existing := SqueakPageCache pageCache at: url ifAbsent: [nil].
  	existing ifNotNil: [existing isContentsInMemory
  		ifTrue: [page := truePage := existing]].	"This url already has an object in this image"
  	truePage ifNil: [
  		truePage := SqueakPageCache atURL: url oldPage: page].
  	object := truePage isContentsInMemory 
  		ifTrue: [truePage contentsMorph]
  		ifFalse: [truePage fetchInformIfError].	"contents, not the page"
  			"Later, collect pointers to object and fix them up.  Not scan memory"
  	object ifNil: [^ 'Object could not be fetched.'].
  	"recursionFlag := false."  	"while I still have a pointer to myself"
  	truePage contentsMorph: object.
  	page := truePage.
  	self xxxFixup.
  	^ object	"the final object!!"
   !

Item was changed:
+ ----- Method: ObjectOut>>xxxFixup (in category 'fetch from disk') -----
- ----- Method: ObjectOut>>xxxFixup (in category '*MorphicExtras-SqueakPage') -----
  xxxFixup
  	"There is already an object in memory for my url.  All pointers to me need to be pointers to him.  Can't use become, because other pointers to him must stay valid."
  
  	| real temp list |
  	real := page contentsMorph.
  	real == self ifTrue: [page error: 'should be converted by now'].
  	temp := self.
  	list := (PointerFinder pointersTo: temp) asOrderedCollection.
  	list add: thisContext.  list add: thisContext sender.
  	list do: [:holder |
  		1 to: holder class instSize do:
  			[:i | (holder instVarAt: i) == temp ifTrue: [holder instVarAt: i put: real]].
  		1 to: holder basicSize do:
  			[:i | (holder basicAt: i) == temp ifTrue: [holder basicAt: i put: real]].
  		].
  	^ real!

Item was added:
+ ----- Method: ObjectOut>>xxxInstVarAt: (in category 'basics') -----
+ xxxInstVarAt: index 
+ 	"Primitive. Answer a fixed variable in an object. The numbering of the 
+ 	variables corresponds to the named instance variables. Fail if the index 
+ 	is not an Integer or is not the index of a fixed variable. Essential. See 
+ 	Object documentation whatIsAPrimitive."
+ 
+ 	<primitive: 73>
+ 	self primitiveFailed !

Item was added:
+ ----- Method: ObjectOut>>xxxInstVarAt:put: (in category 'basics') -----
+ xxxInstVarAt: anInteger put: anObject 
+ 	"Primitive. Store a value into a fixed variable in the receiver. The 
+ 	numbering of the variables corresponds to the named instance variables. 
+ 	Fail if the index is not an Integer or is not the index of a fixed variable. 
+ 	Answer the value stored as the result. Using this message violates the 
+ 	principle that each object has sovereign control over the storing of 
+ 	values into its instance variables. Essential. See Object documentation 
+ 	whatIsAPrimitive."
+ 
+ 	<primitive: 74>
+ 	self primitiveFailed !

Item was added:
+ ----- Method: ObjectOut>>xxxReset (in category 'access') -----
+ xxxReset
+ 	"mark as never brought in"
+ 	recursionFlag := nil!

Item was changed:
+ ----- Method: ObjectOut>>xxxSetUrl:page: (in category 'fetch from disk') -----
- ----- Method: ObjectOut>>xxxSetUrl:page: (in category '*MorphicExtras-SqueakPage') -----
  xxxSetUrl: aString page: aSqkPage
  
  	url := aString.
  	page := aSqkPage.!



More information about the Squeak-dev mailing list