Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
How to transfer part of an image to another image using ImageSegments
Last updated at 1:44 pm UTC on 16 January 2006
Here is some code for the second way of using ImageSegments for export into possibly other images:

checkpoint
    "Export me using an ImageSegment. Return nil on fail.
    This is used for checkpointing the account on disk
    in a form that can be brought into an independent image.
    We do not overwrite older versions - when the image does a
    snapshot it can purge old checkpoints."

    | is fname myParent dir stream |
    myParent _ parent.
    lastCheckPoint _ TimeStamp current.
    dir _ self dir.
    fname _ dir nextNameFor: self fileName extension: self fileNameExtension.
    stream _ dir newFileNamed: fname.
    [ parent _ nil.
    is _ ImageSegment new.
    is copyFromRoots: (Array with: self) sizeHint: 1000000 areUnique: true.
    is writeForExportOn: stream ]
        ifError: [parent _ myParent. ^nil].
    parent _ myParent.
    ^is

The method above nils out a parent pointer but that is just to "make sure" - I don't think it is needed. The sizeHint is good to set high because otherwise there will be numerous "tries" when dumping large structures and that takes a lot of time. The writeForExportOn: method wraps the ImageSegment in a ReferenceStream in order to gracefully deal with the outpointers.
This needs a new simple method in ImageSegment to work:

writeForExportOn: fileStream
    "Write the segment on the disk with all info needed to reconstruct it in a new image. Outpointers are encoded as normal objects on the disk."

    | temp |
    state = #activeCopy ifFalse: [self error: 'wrong state'].
    temp _ endMarker.
    endMarker _ nil.
    fileStream fileOutClass: nil andObject: self.
        "remember extra structures.  Note class names."
    endMarker _ temp

And this is how I load them back, a method in my account class (on theclass side):

loadFrom: aDirectory
    "Load the account from given directory."

    | stream account fileName |
    fileName _ aDirectory lastNameFor: self fileName extension: self fileNameExtension.
    fileName ifNil: [self error: 'Account files not found! Account not loaded.'].
    stream _ aDirectory oldFileNamed: fileName.
    account _ (stream fileInObjectAndCode) install arrayOfRoots first.
    stream close.
    ^account


In order for the above code to work I also needed a method inFileDirectory:
lastNameFor: baseFileName extension: extension
    "Assumes a file name includes a version number encoded as '.' followed by digits preceding the file extension.  Increment the version number and answer the new file name.
    If a version number is not found, set the version to 1 and answer a new file name"

    | files splits |

    files _ self fileNamesMatching: (baseFileName,'', self class dot,
extension).
    splits _ files 
            collect: [:file | self splitNameVersionExtensionFor: file]
            thenSelect: [:split | (split at: 1) = baseFileName].
    splits _ splits asSortedCollection: [:a :b | (a at: 2)  (b at: 2)].
    ^splits isEmpty 
            ifTrue: [nil]
            ifFalse: [(baseFileName, '.', (splits last at: 2) asString, self class dot, extension) asFileName]

Well, perhaps it helped!

And... you can see this stuff "in action" at SqueakDot - just sign up,go to "My SqueakDot", play with "checkpoint" and "account analysis". You can also see some code by clicking on "source for this page" at the bottom of most webpages.

Göran Hultgren