[squeak-dev] The Trunk: System-nice.299.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Mar 26 20:33:59 UTC 2010


Nicolas Cellier uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-nice.299.mcz

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

Name: System-nice.299
Author: nice
Time: 26 March 2010, 9:33:16.083 pm
UUID: 9ac9e930-bff9-4cb3-9388-09edfb2c844e
Ancestors: System-ar.298

1) fix a few _ assignments
2) allUnsentMessagesIn: ->  allUnSentMessagesIn: http://bugs.squeak.org/view.php?id=7483
3) let nextPutAll: answer it's argument

=============== Diff against System-ar.298 ===============

Item was changed:
  ----- Method: AutoStart class>>checkForUpdates (in category 'updating') -----
  checkForUpdates
  	| availableUpdate updateServer |
  	World 
  		ifNotNil: [
  			World install.
  			ActiveHand position: 100 at 100].
  	HTTPClient isRunningInBrowser
  		ifFalse: [^self processUpdates].
+ 	availableUpdate := (AbstractLauncher extractParameters
- 	availableUpdate _ (AbstractLauncher extractParameters
  		at: 'UPDATE'
  		ifAbsent: [''] ) asInteger.
  	availableUpdate
  		ifNil: [^false].
+ 	updateServer := AbstractLauncher extractParameters
- 	updateServer _ AbstractLauncher extractParameters
  		at: 'UPDATESERVER'
  		ifAbsent: [AbstractLauncher extractParameters
  		at: 'UPDATE_SERVER'
  		ifAbsent: ['Squeakland']].
  	Utilities setUpdateServer: updateServer.
  	^SystemVersion checkAndApplyUpdates: availableUpdate!

Item was changed:
  Object subclass: #CodeLoader
  	instanceVariableNames: 'baseURL sourceFiles segments publicKey'
  	classVariableNames: 'DefaultBaseURL DefaultKey'
  	poolDictionaries: ''
  	category: 'System-Download'!
  
+ !CodeLoader commentStamp: 'nice 3/25/2010 22:59' prior: 0!
- !CodeLoader commentStamp: '<historical>' prior: 0!
  CodeLoader provides a simple facility for loading code from the network.
  
  Examples:
  	| loader |
+ 	loader := CodeLoader new.
- 	loader _ CodeLoader new.
  	loader baseURL:'http://isgwww.cs.uni-magdeburg.de/~raab/test/'.
  	loader localCache: #('.cache' 'source').
  	"Sources and segments can be loaded in parallel"
  	loader loadSourceFiles: #('file1.st' 'file2.st.gz').
  	loader localCache: #('.cache' 'segments').
  	loader loadSegments: #('is1.extseg' 'is2.extseg.gz').
  	"Install sources first - will wait until the files are actually loaded"
  	loader installSourceFiles.
  	"And then the segments"
  	loader installSegments.!

Item was changed:
  ReferenceStream subclass: #SmartRefStream
  	instanceVariableNames: 'structures steady reshaped renamed renamedConv superclasses progressBar objCount classInstVars'
  	classVariableNames: 'ScannedObject'
  	poolDictionaries: ''
  	category: 'System-Object Storage'!
  
+ !SmartRefStream commentStamp: 'nice 3/25/2010 23:03' prior: 0!
- !SmartRefStream commentStamp: '<historical>' prior: 0!
  Ordinary ReferenceStreams assume that the names and order of instance variables is exactly the same when an object file is written and read.  
  	SmartRefStream allows object files to be read even after instance variables have changed or the entire class has been renamed.
  
  When an object file is written, no one knows how the classes will change in the future.  Therefore, all conversion must be done when the file is read.  The key is to store enough information in the file about the names of the instance variables of all outgoing classes.  
  
  SmartRefStream works best with only one tree of objects per file.  You can nextPut: more than once, but each object tree gets its own class structure description, which is big.  
  
  Conversion of old objects is done by a method in each class called (convertToCurrentVersion: varDict refStream: smartRefStrm).  At fileOut time, ChangeSet>>checkForConversionMethods creates a prototype of this method (if Preference #conversionMethodsAtFileOut is true).  The programmer must edit this method to (1) test if the incoming object needs conversion, (2) put non-nil values into any new inst vars that need them, and (3) save the data of any inst vars that are being deleted. 
  
  Determining which old version is represented by the incoming object can be done in several ways: noticing that a current inst var is nil when it should have data, noticing that there is an older inst var name in the variable dictionary (varDict), checking kinds of objects in one or more inst vars, or retrieving the classVersion of the incoming object from the ref stream.  
  
  If a class is renamed, a method goes into SmartRefStream telling the new name.  The conversion method of the new class must be prepared to accept instances of the old class also.  If no inst var names have changed, the conversion method does nothing.
  
  An example:  
  	Suppose we change the representation of class Rectangle from ('origin' 'corner') to ('origin' 'extent').  Suppose lots of Rectangle instances are already out on files (in .pr project files, especially).  
  	The programmer changes the class definition, modifies all the methods, and filesOut.  A series of dialogs appear, asking if instances Rectangle might be in an object file, if 'extent' needs to be non-nil (yes), and if the info in 'corner' needs to be preserved (yes).  This method appears:
  
  Rectangle >> convertToCurrentVersion: varDict refStream: smartRefStrm
  	"These variables are automatically stored into the new instance: #('origin').
  	Test for this particular conversion.  Get values using expressions like (varDict at: 'foo')."
  
  	"New variables: #('extent').  If a non-nil value is needed, please assign it."
  	"These are going away #('corner').  Possibly store their info in some other variable?"
  	"Move your code above the ^ super...  Delete extra comments."
  	^ super convertToCurrentVersion: varDict refStream: smartRefStrm
  
  The programmer modifies it to be:
  
  Rectangle >> convertToCurrentVersion: varDict refStream: smartRefStrm
  
  (varDict includesKey: 'extent') ifFalse: ["old version!!"
  	"Create the new extent, and preserve the info from the old corner"
+ 	extent := (varDict at: 'corner') - origin.
- 	extent _ (varDict at: 'corner') - origin.
  	].
  ^ super convertToCurrentVersion: varDict refStream: smartRefStrm
  
  	This conversion method stays in the system and is ready to convert the old format of Rectangle whenever one is encountered in an object file.  Note that the subclasses of Rectangle, (B3DViewport, CharacterBlock, and Quadrangle) do not need conversion methods.  Their instances will be converted by the code in Rectangle.  
  
  	Files written by SmartRefStream are in standard fileout format.  You can mix raw objects with code to be filed in.  The file starts out in the normal fileOut format.  Definitions of new classes on the front.
  
  structures 	Dictionary of (#Rectangle -> #(<classVersionInteger> 'origin' 'corner')).  Inst 
  				var names are strings.
  steady 		Set of Classes who have the same structure now as on the incoming file.
  				Includes classes with same inst vars except for new ones added on the end.
  reshaped 	Dictionary of Classes who have a different structure now from the incoming file.  
  				Includes those with same inst vars but new version number.
  				(old class name -> method selector to fill in data for version to version)
  renamed	Dictionary of Classes who have a different name.  Make an instance of the new
  			class, and send it the conversion call.
  				(old class name symbol -> new class name).  
  renamedConv	Dictionary of conversion selector for Classes who have a different name.
  				(old class name symbol -> conversion selector).  
  topCall		Tells if next or nextPut: are working on the top object in the tree.  
  			nil if outside, the top object if deep inside.
  
  See DataStream.typeIDFor: for where the tangle of objects is clipped, so the whole system will not be written on the file.
  
  No object that is written on the file is ever a class.  All class definitions are filed in.  A class may be stored inside an ImageSegment that itself is stored in a SmartRefStream.
  
  UniClasses are classes for the instance specific behavior of just one instance.  Subclasses of Player are an example.  When a UniClass is read in, and a class of the same name already exists, the incoming one is renamed.  ObjectScanner converts the filed-in code.
  
  Values in instance variables of UniClasses are stored in the array that tells the class structure.  It is the fourth of the four top level objects.  #(version (class-structure) the-object ((#Player25 scripts slotInfo costumeDictionary) (#Player26 scripts slotInfo costumeDictionary))).
  
  There is a separate subclass for doing veryDeepCopy (in memory).  Currently, any object for which objectToStoreOnDataStream return an object other than self, does this:  The new object (a DiskProxy) is traced.  When it comes time to go through the fields of the old object, they are not found as keys in references (DiskProxies are there instead).  So the old field value is left in the new object.  That is OK for StrikeFont, Class, MetaClass, DisplayScreen.  But the DiskProxies are evaluated, which takes a lot of time.
  
  Some metaclasses are put into the structures table.  This is for when a block has a receiver that is a class.  See checkFatalReshape:.
  
  ImageSegments:
  	A ReferenceStream is used to enumerate objects to put inside an ImageSegment.  If an instance of a UniClass is seen, the class is put in also.
  	A SmartRefStream is used to store the ImageSegment.  Roots are nil, and the segment is a wordArray.  We are encoding the outPointers.  Structures contains all classes from both places.  Must filter out UniClasses for some things, and do include them for putting source code at end of file.  Do not write any class inst vars in file.
  
  --Ted Kaehler and Bob Arning.
  !

Item was changed:
  ----- Method: SmartRefStream>>writeConversionMethod:class:was:fromInstVars:to: (in category 'class changed shape') -----
  writeConversionMethod: sel class: newClass was: oldName fromInstVars: oldList to: newList
  	"The method convertToCurrentVersion:refStream: was not found in newClass.  Write a default conversion method for the author to modify."
  
  	| code newOthers oldOthers copied |
  
+ 	code := WriteStream on: (String new: 500).
- 	code _ WriteStream on: (String new: 500).
  	code nextPutAll: 'convertToCurrentVersion: varDict refStream: smartRefStrm'; cr; tab.
+ 	newOthers := newList asOrderedCollection "copy".
+ 	oldOthers := oldList asOrderedCollection "copy".
+ 	copied := OrderedCollection new.
- 	newOthers _ newList asOrderedCollection "copy".
- 	oldOthers _ oldList asOrderedCollection "copy".
- 	copied _ OrderedCollection new.
  	newList do: [:instVar |
  		(oldList includes: instVar) ifTrue: [
  			instVar isInteger ifFalse: [copied add: instVar].
  			newOthers remove: instVar.
  			oldOthers remove: instVar]].
  	code nextPutAll: '"These variables are automatically stored into the new instance '.
  	code nextPutAll: copied asArray printString; nextPut: $. .
  	code cr; tab; nextPutAll: 'This method is for additional changes.'; 
+ 		nextPutAll: ' Use statements like (foo := varDict at: ''foo'')."'; cr; cr; tab.
- 		nextPutAll: ' Use statements like (foo _ varDict at: ''foo'')."'; cr; cr; tab.
  	(newOthers size = 0) & (oldOthers size = 0) ifTrue: [^ self].
  		"Instance variables are the same.  Only the order changed.  No conversion needed."
  	(newOthers size > 0) ifTrue: [code nextPutAll: '"New variables: ', newOthers asArray printString, '  If a non-nil value is needed, please assign it."\' withCRs].
  	(oldOthers size > 0) ifTrue: [code nextPutAll: '	"These are going away ', oldOthers asArray printString, '.  Possibly store their info in some other variable?"'].
  
  	code cr; tab.
  	code nextPutAll: '^ super convertToCurrentVersion: varDict refStream: smartRefStrm'.
  	newClass compile: code contents classified: 'object fileIn'.
  
  
  	"If you write a conversion method beware that the class may need a version number change.  This only happens when two conversion methods in the same class have the same selector name.  (A) The inst var lists of the new and old versions intials as some older set of new and old inst var lists.  or (B) Twice in a row, the class needs a conversion method, but the inst vars stay the same the whole time.  (For an internal format change.)
  	If either is the case, fileouts already written with the old (wrong) version number, say 2.  Your method must be able to read files that say version 2 but are really 3, until you expunge the erroneous version 2 files from the universe."
  
   !

Item was changed:
  ----- Method: Behavior>>allUnsentMessages (in category '*system-support') -----
  allUnsentMessages
  	"Answer an array of all the messages defined by the receiver that are not sent anywhere in the system."
  
+ 	^ SystemNavigation default allUnSentMessagesIn: self selectors!
- 	^ SystemNavigation default allUnsentMessagesIn: self selectors!

Item was changed:
  Stream subclass: #DataStream
  	instanceVariableNames: 'byteStream topCall basePos'
  	classVariableNames: 'TypeMap'
  	poolDictionaries: ''
  	category: 'System-Object Storage'!
  
+ !DataStream commentStamp: 'nice 3/25/2010 23:01' prior: 0!
- !DataStream commentStamp: '<historical>' prior: 0!
  This is the save-to-disk facility. A DataStream can store one or more objects in a persistent form.
  
  To handle objects with sharing and cycles, you must use a
  ReferenceStream instead of a DataStream.  (Or SmartRefStream.)  ReferenceStream is typically
  faster and produces smaller files because it doesn't repeatedly write the same Symbols.
  
  Here is the way to use DataStream and ReferenceStream:
+ 	rr := ReferenceStream fileNamed: 'test.obj'.
- 	rr _ ReferenceStream fileNamed: 'test.obj'.
  	rr nextPut: <your object>.
  	rr close.
  
  To get it back:
+ 	rr := ReferenceStream fileNamed: 'test.obj'.
+ 	<your object> := rr next.
- 	rr _ ReferenceStream fileNamed: 'test.obj'.
- 	<your object> _ rr next.
  	rr close.
  
  Each object to be stored has two opportunities to control what gets stored.  On the high level, objectToStoreOnDataStream allows you to substitute another object on the way out.  The low level hook is storeDataOn:. The read-in counterparts to these messages are comeFullyUpOnReload and (class) readDataFrom:size:. See these methods, and the class DiskProxy, for more information about externalizing and internalizing.
  
  NOTE: A DataStream should be treated as a write-stream for writing.  It is a read-stream for reading.  It is not a ReadWriteStream.
  !

Item was changed:
  ----- Method: AutoStart class>>checkForPluginUpdate (in category 'updating') -----
  checkForPluginUpdate
  	| pluginVersion updateURL |
  	World 
  		ifNotNil: [
  			World install.
  			ActiveHand position: 100 at 100].
  	HTTPClient isRunningInBrowser
  		ifFalse: [^false].
+ 	pluginVersion := AbstractLauncher extractParameters
- 	pluginVersion _ AbstractLauncher extractParameters
  		at: (SmalltalkImage current platformName copyWithout: Character space) asUppercase
  		ifAbsent: [^false].
+ 	updateURL := AbstractLauncher extractParameters
- 	updateURL _ AbstractLauncher extractParameters
  		at: 'UPDATE_URL'
  		ifAbsent: [^false].
  	^SystemVersion check: pluginVersion andRequestPluginUpdate: updateURL!

Item was changed:
  ----- Method: DummyStream>>nextPutAll: (in category 'accessing') -----
  nextPutAll: aByteArray
+ 	"do nothing"
+ 	
+ 	^aByteArray!
- 	"do nothing"!

Item was changed:
  ----- Method: Project class>>mostRecent:onServer: (in category 'squeaklet on server') -----
  mostRecent: projName onServer: aServerDirectory
  	| stem list max goodName triple num stem1 stem2 rawList nothingFound unEscName |
  	"Find the exact fileName of the most recent version of project with the stem name of projName.  Names are of the form 'projName|mm.pr' where mm is a mime-encoded integer version number.
  	File names may or may not be HTTP escaped, %20 on the server."
  
  	self flag: #bob.		"do we want to handle unversioned projects as well?"
  
+ 	nothingFound := {nil. -1}.
- 	nothingFound _ {nil. -1}.
  	aServerDirectory ifNil: [^nothingFound].
  	"23 sept 2000 - some old projects have periods in name so be more careful"
+ 	unEscName := projName unescapePercents.
+ 	triple := Project parseProjectFileName: unEscName.
+ 	stem := triple first.
+ 	rawList := aServerDirectory fileNames.
- 	unEscName _ projName unescapePercents.
- 	triple _ Project parseProjectFileName: unEscName.
- 	stem _ triple first.
- 	rawList _ aServerDirectory fileNames.
  
  	rawList isString ifTrue: [self inform: 'server is unavailable'. ^nothingFound].
+ 	list := rawList collect: [:nnn | nnn unescapePercents].
+ 	max := -1.  goodName := nil.
- 	list _ rawList collect: [:nnn | nnn unescapePercents].
- 	max _ -1.  goodName _ nil.
  	list withIndexDo: [:aName :ind |
  		(aName beginsWith: stem) ifTrue: [
+ 			num := (Project parseProjectFileName: aName) second.
+ 			num > max ifTrue: [max := num.  goodName := (rawList at: ind)]]].
- 			num _ (Project parseProjectFileName: aName) second.
- 			num > max ifTrue: [max _ num.  goodName _ (rawList at: ind)]]].
  
  	max = -1 ifFalse: [^ Array with: goodName with: max].
  
  	"try with underbar for spaces on server"
  	(stem includes: $ ) ifTrue: [
+ 		stem1 := stem copyReplaceAll: ' ' with: '_'.
- 		stem1 _ stem copyReplaceAll: ' ' with: '_'.
  		list withIndexDo: [:aName :ind |
  			(aName beginsWith: stem1) ifTrue: [
+ 				num := (Project parseProjectFileName: aName) second.
+ 				num > max ifTrue: [max := num.  goodName := (rawList at: ind)]]]].
- 				num _ (Project parseProjectFileName: aName) second.
- 				num > max ifTrue: [max _ num.  goodName _ (rawList at: ind)]]]].
  	max = -1 ifFalse: [^ Array with: goodName with: max].
  	
  	"try without the marker | "
+ 	stem1 := stem allButLast, '.pr'.
+ 	stem2 := stem1 copyReplaceAll: ' ' with: '_'.	"and with spaces replaced"
- 	stem1 _ stem allButLast, '.pr'.
- 	stem2 _ stem1 copyReplaceAll: ' ' with: '_'.	"and with spaces replaced"
  	list withIndexDo: [:aName :ind |
  		(aName beginsWith: stem1) | (aName beginsWith: stem2) ifTrue: [
+ 			(triple := aName findTokens: '.') size >= 2 ifTrue: [
+ 				max := 0.  goodName := (rawList at: ind)]]].	"no other versions"
- 			(triple _ aName findTokens: '.') size >= 2 ifTrue: [
- 				max _ 0.  goodName _ (rawList at: ind)]]].	"no other versions"
  	max = -1 ifFalse: [^ Array with: goodName with: max].
  
  	^nothingFound		"no matches"
  !

Item was changed:
  Object subclass: #ImageSegment
  	instanceVariableNames: 'arrayOfRoots segment outPointers state segmentName fileName endMarker userRootCnt renamedClasses'
  	classVariableNames: 'BiggestFileNumber RecentlyRenamedClasses'
  	poolDictionaries: ''
  	category: 'System-Object Storage'!
  
+ !ImageSegment commentStamp: 'nice 3/25/2010 23:01' prior: 0!
- !ImageSegment commentStamp: 'tk 12/2/2004 12:33' prior: 0!
  I represent a segment of Squeak address space.  I am created from an
  array of root objects.  After storing, my segment contains a binary
  encoding of every object accessible from my roots but not otherwise
  accessible from anywhere else in the system.  My segment contains
  outward pointers that are indices into my table of outPointers.
  	The main use of ImageSegments is to store Projects.  A dummy
  version of SmartRefStream traverses the Project.  Everything it finds
  is classified as either an object that is owned by the project (only
  pointed to inside the project), or an object outside the project that
  is pointed to from inside the project.  The objects that are
  completely owned by the project are compressed into pure binary form
  in an ImageSegment.  The outside objects are put in the 'outPointers'
  array.  The entire ImageSegment (binary part plus outPointers) is
  encoded in a SmartRefStream, and saved on the disk.  (aProject
  exportSegmentWithChangeSet:fileName:directory:) calls (anImageSegment
  writeForExportWithSources:inDirectory:changeSet:).
  	Note that every object inside the project is put into the
  segment's arrayOfRoots.  This is because a dummy SmartRefStream to
  scan the project, in order to make intelligent decisions about what
  belongs in the project.
  	See Project's class comment for what messages are sent to
  objects as they are unpacked in a new image.
  
  ---- Older Details ------
  
  	The primary kind of image segment is an Export Segment.  It
  can be saved on a server and read into a completely different Squeak
  image.
  Old way to create one:
  (ImageSegment new copyFromRootsForExport: (Array with: Baz with: Baz class))
  		writeForExport: 'myFile.extSeg'.
  Old way to create one for a project:
  	(Project named: 'Play With Me - 3') exportSegment.
  To read it into another image:  Select 'myFile.extSeg' in a FileList,
  Menu 'load as project'.  It will install its classes automatically.
  If you need to see the roots array, it is temporarily stored in
  (SmartRefStream scannedObject).
  
  Most of 'states' of an ImageSegment are not used to export a project,
  and have been abandoned.
  
  	When a segment is written out onto a file, it goes in a
  folder called <image name>_segs.  If your image is called
  "Squeak2.6.image", the folder "Squeak2.6_segs" must accompany the
  image whenever your move, copy, or rename it.
  	Whenever a Class is in arrayOfRoots, its class (aClass class)
  must also be in the arrayOfRoots.
  	There are two kinds of image segments.  Normal image segments
  are a piece of a specific Squeak image, and can only be read back
  into that image.  The image holds the array of outPointers that are
  necessary to turn the bits in the file into objects.
  	To put out a normal segment that holds a Project (not the
  current project), execute (Project named: 'xxx') storeSegment.
  
  
  arrayOfRoots	The objects that head the tree we will trace.
  segment			The WordArray of raw bits of all objects in the tree.
  outPointers		Oops of all objects outside the segment
  pointed to from inside.
  state			(see below)
  segmentName	Its basic name.  Often the name of a Project.
  fileName		The local name of the file.  'Foo-23.seg'
  endMarker		An object located in memory somewhere after a
  segment that has
  		just been brought in.  To enumerate the objects in
  the segment, start at
  		the segment and go to this object.
  userRootCnt		number of roots submitted by caller.  Extras
  are added in preparation for saving.
  
  state that an ImageSegment may exist in...
  
  #activeCopy			(has been copied, with the intent to
  become active)
  arrayOfRoots, segment, and outPointers have been created by
  copyFromRoots:.  The tree of objects has been encoded in the segment,
  but those objects are still present in the Squeak system.
  
  #active				(segment is actively holding objects)
  The segment is now the only holder of tree of objects.  Each of the
  original roots has been transmuted into an ImageSegmentRootStub that
  refers back to this image segment.  The original objects in the
  segment will all be garbageCollected.
  
  #onFile
  The segment has been written out to a file and replaced by a file
  pointer.  Only ImageSegmentRootStubs and the array of outPointers
  remains in the image.  To get this far:
  (ImageSegment new copyFromRoots: (Array with: Baz with: Baz class))
  		writeToFile: 'myFile.seg'.
  
  #inactive
  The segment has been brought back into memory and turned back into
  objects.  rootsArray is set, but the segment is invalid.
  
  #onFileWithSymbols
  The segment has been written out to a file, along with the text of
  all the symbols in the outPointers array, and replaced by a file
  pointer.  This reduces the size of the outPointers array, and also
  allows the system to reclaim any symbols that are not referred to
  from elsewhere in the image.  The specific format used is that of a
  literal array as follows:
  	#(symbol1 symbol2 # symbol3 symbol4 'symbolWithSpaces' # symbol5).
  In this case, the original outPointers array was 8 long, but the
  compacted table of outPointers retains only two entries.  These get
  inserted in place of the #'s in the array of symbols after it is read
  back in.  Symbols with embedded spaces or other strange characters
  are written as strings, and converted back to symbols when read back
  in.  The symbol # is never written out.
  	NOTE: All IdentitySets or dictionaries must be rehashed when
  being read back from this format.  The symbols are effectively
  internal.  (No, not if read back into same image.  If a different
  image, then use #imported.  -tk)
  
  #imported
  The segment is on an external file or just read in from one.  The
  segment and outPointers are meant to be read into a foreign image.
  In this form, the image segment can be read from a URL, and
  installed.  A copy of the original array of root objects is
  constructed, with former outPointers bound to existing objects in the
  host system.
  	(Any Class inside the segment MUST be in the arrayOfRoots.
  This is so its association can be inserted into Smalltalk.  The
  class's metaclass must be in roots also.  Methods that are in
  outPointers because blocks point at them, were found and added to the
  roots.
  	All IdentitySets and dictionaries are rehashed when being
  read back from exported segments.)
  
  
  To discover why only some of the objects in a project are being
  written out, try this (***Destructive Test***).  This breaks lots of
  backpointers in the target project, and puts up an array of
  suspicious objects, a list of the classes of the outPointers, and a
  debugger.
  "Close any transcripts in the target project"
  World currentHand objectToPaste ifNotNil: [
  	self inform: 'Hand is holding a Morph in its paste buffer:\' withCRs,
  		World currentHand objectToPaste printString].
+ PV := Project named: 'xxxx'.
+ (IS := ImageSegment new) findRogueRootsImSeg:
- PV _ Project named: 'xxxx'.
- (IS _ ImageSegment new) findRogueRootsImSeg:
  	(Array with: PV world presenter with: PV world).
  IS findOwnersOutPtrs.	"Optionally: write a file with owner chains"
  "Quit and DO NOT save"
  
  When an export image segment is brought into an image, it is like an
  image starting up.  Certain startUp messages need to be run.  These
  are byte and word reversals for nonPointer data that comes from a
  machine of the opposite endianness.  #startUpProc passes over all
  objects in the segment, and:
  	The first time an instance of class X is encountered, (msg _
  X startUpFrom: anImageSegment) is sent.  If msg is nil, the usual
  case, it means that instances of X do not need special work.  X is
  included in the IdentitySet, noStartUpNeeded.  If msg is not nil,
  store it in the dictionary, startUps (aClass -> aMessage).
  	When a later instance of X is encountered, if X is in
  noStartUpNeeded, do nothing.  If X is in startUps, send the message
  to the instance.  Typically this is a message like #swapShortObjects.
  	Every class that implements #startUp, should see if it needs
  a parallel implementation of #startUpFrom:.  !

Item was changed:
  DataStream subclass: #ReferenceStream
  	instanceVariableNames: 'references objects currentReference fwdRefEnds blockers skipping insideASegment'
  	classVariableNames: 'RefTypes'
  	poolDictionaries: ''
  	category: 'System-Object Storage'!
  
+ !ReferenceStream commentStamp: 'nice 3/25/2010 23:03' prior: 0!
- !ReferenceStream commentStamp: '<historical>' prior: 0!
  This is a way of serializing a tree of objects into disk file. A ReferenceStream can store
  one or more objects in a persistent form, including sharing and cycles.
  
  Here is the way to use DataStream and ReferenceStream:
+ 	rr := ReferenceStream fileNamed: 'test.obj'.
- 	rr _ ReferenceStream fileNamed: 'test.obj'.
  	rr nextPut: <your object>.
  	rr close.
  
  To get it back:
+ 	rr := ReferenceStream fileNamed: 'test.obj'.
+ 	<your object> := rr next.
- 	rr _ ReferenceStream fileNamed: 'test.obj'.
- 	<your object> _ rr next.
  	rr close.
  
  ReferenceStreams can now write "weak" references. nextPutWeak:
  writes a "weak" reference to an object, which refers to that object
  *if* it also gets written to the stream by a normal nextPut:.
  
  A ReferenceStream should be treated as a read-stream *or* as a write-stream, *not* as a read/write-stream. The reference-remembering mechanism would probably do bad things if you tried to read and write from the same ReferenceStream.
  
  [TBD] Should we override "close" to do (self forgetReferences)?
  
  Instance variables
   references -- an IdentityDictionary mapping objects already written
  	to their byteStream positions. If asked to write any object a
  	second time, we just write a reference to its stream position.
  	This handles shared objects and reference cycles between objects.
  	To implement "weak references" (for Aliases), the references
  	dictionary also maps objects not (yet?) written to a Collection
  	of byteStream positions with hopeful weak-references to it. If
  	asked to definitely write one of these objects, we'll fixup those
  	weak references.
   objects -- an IdentityDictionary mapping relative byte stream positions to
  	objects already read in. If asked to follow a reference, we
  	return the object already read.
  	This handles shared objects and reference cycles between objects.
   currentReference -- the current reference position. Positon relative to the 
  	start of object data in this file.  (Allows user to cut and paste smalltalk 
  	code from the front of the file without effecting the reference values.)  
  	This variable is used to help install each new object in "objects" as soon
  	as it's created, **before** we start reading its contents, in
  	case any of its content objects reference it.
   fwdRefEnds -- A weak reference can be a forward reference, which
  	requires advance-reading the referrent. When we later come to the
  	object, we must get its value from "objects" and not re-read it so
  	refs to it don't become refs to copies. fwdRefEnds remembers the
  	ending byte stream position of advance-read objects.
   skipping -- true if <what?>
   insideASegment -- true if we are being used to collect objects that will be 
  	included in an ImageSegment.  If so, UniClasses must be noted and traced.
  
  If the object is referenced before it is done being created, it might get created twice.  Just store the object the moment it is created in the 'objects' dictionary.  If at the end, comeFullyUpOnReload returns a different object, some refs will have the temporary object (this is an unlikely case).  At the moment, no implementor of comeFullyUpOnReload returns a different object except DiskProxy, and that is OK.
  !

Item was changed:
  ----- Method: ImageSegment class>>folder (in category 'fileIn/Out') -----
  folder
  	| im |
  	"Full path name of segments folder.  Be sure to duplicate and rename the folder when you duplicate and rename an image.  Is $_ legal in all file systems?"
  
+ 	im := SmalltalkImage current imageName.
- 	im _ SmalltalkImage current imageName.
  	^ (im copyFrom: 1 to: im size - 6 "'.image' size"), '_segs'!




More information about the Squeak-dev mailing list