Hi. I am not sure if I understand which is the bug and it is difficult to do a clear diff. You mean that weak references should NOT be serialized ?  While thinking about this in Fuel I asked in the mailing list and the conclusion was that we shouldn't do anything special in Fuel for weak references. In this case, if I understand, you are saying the opposite: do something different for weak references, basically to consider them "transient". Can you please explain me why it is needed a specific behavior for weak references?

Thanks in advance!


On Sun, Nov 27, 2011 at 6:28 PM, Juan Vuletich <juan@jvuletich.org> wrote:
Hi Folks,

I found a bug in Cuis that made weak references to be improperly dumped in SmartRefStreams due to a bug in ReferenceStream. When I tried to reproduce the bug and fix in Squeak, I found out that in Squeak weak references are always dumped (and not just the more subtle bug in Cuis). The attach includes a test and fix. I'm confident about the fix in the context of Cuis, but I only played a few minutes with this in Squeak.

Can anybody check this for Squeak and consider it for inclusion?

Thanks,
Juan Vuletich

'From Squeak4.2 of 20 November 2011 [latest update: #11796] on 27 November 2011 at 2:56:53 pm'!
TestCase subclass: #ReferenceStreamTest
       instanceVariableNames: ''
       classVariableNames: ''
       poolDictionaries: ''
       category: 'System-Object Storage-Tests'!

!Object methodsFor: 'objects from disk' stamp: 'jmv 11/27/2011 14:56'!
storeDataOn: aDataStream
       "Store myself on a DataStream.  Answer self.  This is a low-level DataStream/ReferenceStream method. See also objectToStoreOnDataStream.  NOTE: This method must send 'aDataStream beginInstance:size:' and then (nextPut:/nextPutWeak:) its subobjects.  readDataFrom:size: reads back what we write here."
       | cntInstVars cntIndexedVars |

       cntInstVars := self class instSize.
       cntIndexedVars := self basicSize.
       aDataStream
               beginInstance: self class
               size: cntInstVars + cntIndexedVars.
       1 to: cntInstVars do:
               [:i | aDataStream nextPut: (self instVarAt: i)].

       "Write fields of a variable length object.  When writing to a dummy
               stream, don't bother to write the bytes"
       ((aDataStream byteStream class == DummyStream) and: [self class isBits]) ifFalse: [
               self class isWeak
                       ifTrue: [
                               "For weak classes (for example DependentsArray) write the referenced object only
                               if referenced from elsewhere in the dumped object graph.
                               This means, for instance that if we only dump a model, no dependents are stored,
                               but if we store a view (i.e. a Morph), it is properly handled as a dependent after the object graph is revived."
                               1 to: cntIndexedVars do: [ :i |
                                       aDataStream nextPutWeak: (self basicAt: i)]]
                       ifFalse: [
                               1 to: cntIndexedVars do: [ :i |
                                       aDataStream nextPut: (self basicAt: i)]]]! !


!DiskProxy methodsFor: 'i/o' stamp: 'jmv 11/25/2011 13:20'!
storeDataOn: aReferenceStream
       "Besides just storing, get me inserted into references, so structures will know about class DiskProxy."

       super storeDataOn: aReferenceStream.

       "just so instVarInfo: will find it and put it into structures"
"       aReferenceStream references at: self put: #none."
       aReferenceStream addSpecialReference: self! !


!ReferenceStream methodsFor: 'statistics' stamp: 'jmv 11/25/2011 13:21'!
statisticsOfRefs
       "Analyze the information in references, the objects being written out"

       | parents ownerBags tallies n nm owners normalReferences |
       normalReferences := self references.    "Exclude unrealized weaks"
       parents := IdentityDictionary new: normalReferences size * 2.
       n := 0.
       'Finding Owners...'
       displayProgressFrom: 0 to: normalReferences size
       during: [:bar |
       normalReferences keysDo:
               [:parent | | kids |
               bar value: (n := n+1).
               kids := parent class isFixed
                       ifTrue: [(1 to: parent class instSize) collect: [:i | parent instVarAt: i]]
                       ifFalse: [parent class isBits ifTrue: [Array new]
                                        ifFalse: [(1 to: parent basicSize) collect: [:i | parent basicAt: i]]].
               (kids select: [:x | normalReferences includesKey: x])
                       do: [:child | parents at: child put: parent]]].
       ownerBags := Dictionary new.
       tallies := Bag new.
       n := 0.
       'Tallying Owners...'
       displayProgressFrom: 0 to: normalReferences size
       during: [:bar |
       normalReferences keysDo:  "For each class of obj, tally a bag of owner classes"
               [:obj | | objParent | bar value: (n := n+1).
               nm := obj class name.
               tallies add: nm.
               owners := ownerBags at: nm ifAbsent: [ownerBags at: nm put: Bag new].
               (objParent := parents at: obj ifAbsent: [nil]) == nil
                       ifFalse: [owners add: objParent class name]]].
       ^ String streamContents:
               [:strm |  tallies sortedCounts do:
                       [:assn | n := assn key.  nm := assn value.
                       owners := ownerBags at: nm.
                       strm cr; nextPutAll: nm; space; print: n.
                       owners size > 0 ifTrue:
                               [strm cr; tab; print: owners sortedCounts]]]! !

!ReferenceStream methodsFor: 'writing' stamp: 'jmv 11/25/2011 13:20'!
addSpecialReference: aDiskProxy
       "See senders. Added to avoid breaking encapsulation (assuming that #references would answer the actual collection)"
       references at: aDiskProxy put: #none! !

!ReferenceStream methodsFor: 'writing' stamp: 'jmv 11/27/2011 14:56'!
references
       "Do not include provisory references created in #nextPutWeak that never became normal references,
       because the referenced object was never added from a call to #nextPut:"
       ^ references select: [ :value | value isNumber ]! !


!ReferenceStreamTest methodsFor: 'testing' stamp: 'jmv 11/27/2011 14:56'!
testWeakDumps
       "Test that if we serialize a model with weak references to views, only the model is serialized and not the views.

       Note: The bug became apparent only when dumping a model to a SmartRefStream, that calls #references, and the serialized stream
       was later materialized in an image where the view classes had been deleted. In such rare cases, materialization would fail when trying to reference these
       absent classes. If serializing to a ReferenceStream, the bug didn't become apparent (views were never serialized). If serializing to a SmartRefStream, but
       view classes still existed, the bug didn't really become apparent (because views were not actually deserialized), the only effect was a larger file.

       ReferenceStreamTest new testWeakDumps
       "
       | oldInstance refStream |
       oldInstance :=StringHolder new contents: 'This is a text'.
       oldInstance addDependent: Morph new.
       refStream := ReferenceStream on: (DummyStream on: nil).
       refStream nextPut: oldInstance.
       self deny: (refStream references keys anySatisfy: [ :dumpedObject | dumpedObject isKindOf: Morph ])! !







--
Mariano
http://marianopeck.wordpress.com