IPC and SRP...

Rob Withers withers at vnet.net
Fri Aug 25 06:16:51 UTC 2000


"Göran Hultgren" wrote:
> 
> Hi all!
> 

Hi Göran!  It's great to see that you are interested in this.  I have
also been looking into an 'RMI' solution and one of my big concerns is
that it be cross-dialect.  There is a xdialect Serialization
framework.   SRP runs - I think - on Squeak (2.7+), VW 3.x and 5i, VAST
4.0+?, StX, Dolphin, and ObjectStudio.  Paul has said that we should be
able to decode structures from other languages like Java.  There are
some issues with Squeak wrt Processes, BlockContexts, Semaphores, and I
believe any Class that doesn't have a rule dumps it's entire Meta
hierarchy - this somehow pulls in Smalltalk, though ProtoObject.   What
is missing from a xdialect 'RMI' solution is xdialect Sockets and
Streams.  Perhaps at CS at OOPSLA this will be a project.

I have attached the small extension I made to substitute a handle for a
particular class.  When a graph of objects gets encoded and one of the
objects is of a class included in the HandleSubstitution rule, the
object and it's assigned handle get registered in the HandleManager,
then the handle gets encoded.   When you decode a graph of objects from
a binary stream and you find a handle, then you register that handle as
a proxy.  This is to support GC which I haven't gotten to yet.  I am
currently migrating a small proxy front-end which will DNU the message
to the handle and forward the msg to wherever the proxied object is (I
hope!) - Remote, Persistent, cross-Language...

I also have a client-server framework that I adapted to use SRP streams;
it *isn't* using Flow, yet.  I would really like to see that.  I have
some testCases.  These two pieces together, with a pumped endpoint and
use of when:send:to: could result in a pretty robust base for IPC
between Smalltalks.  It still needs a lot of work in naming/locators,
exceptions and remote event registrations.  I can provide this too you
if you want it.  I'll need some time to consolidate and test.

I hope this helps!

cheers,
Rob

comments below...

> I have been investigating the IPC possibilities in Squeak and have some questions that perhaps
> someone would like to elaborate on:
> 
> 1. Fly-By-Wire and similar stuff. Anyone using it?

Is this the ORB?  I haven't tried it yet; any info would be most
welcome.

> 2. Serialization. Anyone using it for communication? Has anybody tried comparing the marshaling
> techniques available to Squeak (SmartRefStream, SRP by Paul Baumann, Segments)?

I don't know the performance measures of either SRP or SmartRefStream. 
Segments use SmartRefStreams and are really a file-based module delivery
mechanism.

> 3. Flow (former Correspondents). Anyone using it? Is it EVER going to get integrated into Squeak?
> I mean... it seems so much nicer. :-)

It is a really nice framework, minus some confusion I have about the
Stream hierarchy replacements.  It renames the Stream hierarchy,
OldStream, and this stepped on some subclasses I had.  I believe this is
only because it still hasn't made it into the update stream.  This may
be because of the VM changes that recently occurred.  The NetStream is
gorgeous.

later...

> I have only looked at these things with one eye sofar - it would help to know about the major
> differences if somebody else already has investigated them further.
> 
> thanks in advance, Göran
> 
> =====
> Göran Hultgren, goran.hultgren at bluefish.se
> icq#:6136722, GSM: +46 709 472152, http://www.bluefish.se
> "First they ignore you. Then they laugh at you.
> Then they fight you. Then you win." -- Gandhi
> 
> __________________________________________________
> Do You Yahoo!?
> Yahoo! Mail - Free email you can access from anywhere!
> http://mail.yahoo.com/

-- 
--------------------------------------------------
Smalltalking by choice.  Isn't it nice to have one!
-------------- next part --------------
'From Squeak2.8 of 13 June 2000 [latest update: #2348] on 11 August 2000 at 4:09:08 pm'!
Object subclass: #ChatterHandleManager
	instanceVariableNames: 'nextId objectMap handleMap locator nextHandleId config contextId '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SRP-Proxies'!
Object subclass: #ChatterHandleRegistration
	instanceVariableNames: 'referenceCount handle '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SRP-Proxies'!
SrpLoadContext subclass: #ChatterLoadContext
	instanceVariableNames: 'config '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SRP-Proxies'!
Object subclass: #ChatterObjectHandle
	instanceVariableNames: 'locator handleId contextId '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SRP-Proxies'!
Object subclass: #ChatterObjectRegistration
	instanceVariableNames: 'referenceCount object handleId locator handle '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SRP-Proxies'!
SrpObjectStream subclass: #ChatterObjectStream
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SRP-Proxies'!
SrpSaveContext subclass: #ChatterSaveContext
	instanceVariableNames: 'config '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SRP-Proxies'!
SrpMappingRule subclass: #DynamicMappingRule
	instanceVariableNames: 'applicableClassNames isLoad isSave applyRuleBlock '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SRP-Proxies'!
SrpConfiguration subclass: #ChatterConfiguration
	instanceVariableNames: 'transformMappingRules handleManager instanceMappingRules '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SRP-Proxies'!

!ChatterHandleManager methodsFor: 'accessing' stamp: 'slosh 8/10/2000 19:51'!
contextId
	"Answer the receiver's instance variable contextId."

	^contextId! !

!ChatterHandleManager methodsFor: 'accessing' stamp: 'slosh 8/10/2000 19:51'!
contextId: anObject
	"Set the receiver's instance variable contextId to anObject."

	contextId := anObject! !

!ChatterHandleManager methodsFor: 'accessing' stamp: 'slosh 8/10/2000 09:30'!
handleMap
	"Answer the receiver's instance variable handleMap."

	^handleMap ifNil: [handleMap := Dictionary new]
! !

!ChatterHandleManager methodsFor: 'accessing' stamp: 'slosh 8/10/2000 19:52'!
nextHandleId
	"Answer the receiver's instance variable nextHandleId."
	| id |
	id := nextHandleId ifNil: [1].
	nextHandleId := id + 1.
	^ id
! !

!ChatterHandleManager methodsFor: 'accessing' stamp: 'slosh 8/10/2000 09:30'!
objectMap
	"Answer the receiver's instance variable objectMap."

	^objectMap ifNil: [objectMap := Dictionary new]
! !

!ChatterHandleManager methodsFor: 'registration creation' stamp: 'slosh 8/11/2000 15:57'!
createHandleRegistrationFor: aHandle
	| handleRegistration |
	handleRegistration := config handleRegistrationClass on: aHandle.
	self handleMap at: aHandle put: handleRegistration.
	^ handleRegistration
! !

!ChatterHandleManager methodsFor: 'registration creation' stamp: 'slosh 8/11/2000 15:58'!
createObjectRegistrationFor: anObject
	| objectRegistration handle|
	handle := self newHandle.
	objectRegistration := config objectRegistrationClass on: anObject handle: handle.
	self objectMap at: anObject put: objectRegistration.
	^ objectRegistration
! !

!ChatterHandleManager methodsFor: 'registration creation' stamp: 'slosh 8/11/2000 14:47'!
newHandle
	^ ChatterObjectHandle onHandleId: self contextId contextId: self nextHandleId
! !

!ChatterHandleManager methodsFor: 'registration' stamp: 'slosh 8/11/2000 14:45'!
deregisterHandle: aHandle
	self handleMap 
		removeKey: aHandle
		ifAbsent: [nil].

! !

!ChatterHandleManager methodsFor: 'registration' stamp: 'slosh 8/11/2000 14:45'!
deregisterObject: anObject
	^ self objectMap 
		removeKey: anObject
		ifAbsent: [nil].

! !

!ChatterHandleManager methodsFor: 'registration' stamp: 'slosh 8/11/2000 14:44'!
registerHandle: aHandle
	| handleRegistration |
	handleRegistration := self handleMap 
		at: aHandle
		ifAbsent: [self createHandleRegistrationFor: aHandle].
	^ handleRegistration

! !

!ChatterHandleManager methodsFor: 'registration' stamp: 'slosh 8/10/2000 19:50'!
registerObject: anObject
	| objectRegistration |
	objectRegistration := self objectMap 
		at: anObject
		ifAbsent: [self createObjectRegistrationFor: anObject].
	^ objectRegistration


! !

!ChatterHandleManager methodsFor: 'api' stamp: 'slosh 8/8/2000 03:44'!
handleForObject: anObject
	^ (self registerObject: anObject)
		handle

! !

!ChatterHandleManager methodsFor: 'api' stamp: 'slosh 8/11/2000 15:25'!
remapHandle: aHandle
	| objectRegistration |
	objectRegistration := self objectMap 
		detect: [:e | (e handleId = aHandle handleId) and: [e contextId = aHandle contextId]]
		ifNone: [nil].
	^ objectRegistration
		ifNil: [(self registerHandle: aHandle) handle]
		ifNotNil: [objectRegistration object]
! !

!ChatterHandleManager methodsFor: 'initialize-release' stamp: 'slosh 8/11/2000 15:56'!
initializeConfiguration: aConfig
	config := aConfig.
! !


!ChatterHandleManager class methodsFor: 'as yet unclassified' stamp: 'slosh 8/11/2000 15:54'!
new
	self shouldNotImplement.
! !

!ChatterHandleManager class methodsFor: 'as yet unclassified' stamp: 'slosh 8/11/2000 15:58'!
newConfiguration: aConfig
	^ super new initializeConfiguration: aConfig
! !


!ChatterHandleRegistration methodsFor: 'initialize-release' stamp: 'slosh 8/10/2000 09:12'!
initializeOn: aHandle
	handle := aHandle.
! !

!ChatterHandleRegistration methodsFor: 'accessing' stamp: 'slosh 8/8/2000 19:44'!
handle
	"Answer the receiver's instance variable handle."

	^handle! !


!ChatterHandleRegistration class methodsFor: 'instance creation' stamp: 'slosh 8/11/2000 14:42'!
new
	self shouldNotImplement.
! !

!ChatterHandleRegistration class methodsFor: 'instance creation' stamp: 'slosh 8/8/2000 19:43'!
on: anObject
	^ super new initializeOn: anObject
! !


!ChatterLoadContext methodsFor: 'as yet unclassified' stamp: 'slosh 8/8/2000 00:10'!
availableMappingRules
	"Answer a collection of all the mapping rules that
	 are available for use if desired."

	^ SrpMappingLoadRule withAllSubclasses addAll: config availableMappingLoadRules
! !

!ChatterLoadContext methodsFor: 'as yet unclassified' stamp: 'slosh 8/8/2000 00:10'!
initializeConfiguration: aConfig
	"The pre/post map commands are sent #value:value: for each object
	 that is traversed. As variables, the action can be changed to do anything
	 necessary."

	super initializeConfiguration: aConfig.
	config := aConfig.
! !

!ChatterLoadContext methodsFor: 'as yet unclassified' stamp: 'slosh 8/8/2000 19:40'!
remapHandle: aHandle
	^ config remapHandle: aHandle
! !


!ChatterObjectHandle methodsFor: 'accessing' stamp: 'slosh 8/10/2000 19:28'!
contextId
	"Answer the receiver's instance variable contextId."

	^contextId! !

!ChatterObjectHandle methodsFor: 'accessing' stamp: 'slosh 8/10/2000 19:28'!
contextId: anObject
	"Set the receiver's instance variable contextId to anObject."

	contextId := anObject! !

!ChatterObjectHandle methodsFor: 'accessing' stamp: 'slosh 8/10/2000 19:48'!
handleId
	"Answer the receiver's instance variable handleId."

	^handleId! !

!ChatterObjectHandle methodsFor: 'accessing' stamp: 'slosh 8/10/2000 19:48'!
handleId: anObject
	"Set the receiver's instance variable handleId to anObject."

	handleId := anObject! !

!ChatterObjectHandle methodsFor: 'accessing' stamp: 'slosh 8/10/2000 19:48'!
initializeOnHandleId: anId contextId: aContextId
	handleId := anId.
	contextId := aContextId.

! !


!ChatterObjectHandle class methodsFor: 'instance creation' stamp: 'slosh 8/11/2000 14:41'!
new
	self shouldNotImplement.
! !

!ChatterObjectHandle class methodsFor: 'instance creation' stamp: 'slosh 8/11/2000 14:42'!
onHandleId: anId contextId: aContextId
	^ super new
		initializeOnHandleId: anId
		contextId: aContextId

! !


!ChatterObjectRegistration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 14:43'!
contextId
	^ self handle contextId! !

!ChatterObjectRegistration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 14:43'!
contextId: anObject
	self handle contextId: anObject! !

!ChatterObjectRegistration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 14:27'!
handle
	"Answer the receiver's instance variable handle."

	^ handle

! !

!ChatterObjectRegistration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 14:43'!
handleId
	^ self handle handleId! !

!ChatterObjectRegistration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 14:43'!
handleId: anObject
	self handle handleId: anObject! !

!ChatterObjectRegistration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 14:43'!
initializeOn: anObject handle: aHandle
	object := anObject.
	handle := aHandle.
! !

!ChatterObjectRegistration methodsFor: 'accessing' stamp: 'slosh 8/8/2000 11:30'!
object
	"Answer the receiver's instance variable object."

	^object! !


!ChatterObjectRegistration class methodsFor: 'instance creation' stamp: 'slosh 8/11/2000 14:42'!
new
	self shouldNotImplement.
! !

!ChatterObjectRegistration class methodsFor: 'instance creation' stamp: 'slosh 8/11/2000 14:41'!
on: anObject handle: aHandle
	^ super new initializeOn: anObject handle: aHandle
! !


!ChatterObjectStream methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 23:22'!
availableMappingRules
	"Answer a collection of all the mapping rules that
	 are available for use if desired."

	^ SrpMappingRule withAllSubclasses addAll: config availableMappingRules
! !


!ChatterObjectStream class methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 23:15'!
new
	"Answer an instance of the receiver for reading
	 and/or writing object structures on a new stream
	 in binary."

	^self newConfiguration: ChatterConfiguration new.! !


!ChatterSaveContext methodsFor: 'as yet unclassified' stamp: 'slosh 8/8/2000 00:10'!
availableMappingRules
	"Answer a collection of all the mapping rules that
	 are available for use if desired."

	^ SrpMappingSaveRule withAllSubclasses addAll: config availableMappingSaveRules
! !

!ChatterSaveContext methodsFor: 'as yet unclassified' stamp: 'slosh 8/10/2000 10:51'!
handleForObject: object
	^ config handleForObject: object
! !

!ChatterSaveContext methodsFor: 'as yet unclassified' stamp: 'slosh 8/8/2000 00:10'!
initializeConfiguration: aConfig
	"The pre/post map commands are sent #value:value: for each object
	 that is traversed. As variables, the action can be changed to do anything
	 necessary."

	super initializeConfiguration: aConfig.
	config := aConfig.
! !


!DynamicMappingRule methodsFor: 'accessing' stamp: 'slosh 8/7/2000 21:48'!
applicableClassNames
	"Answer the receiver's instance variable applicableClassNames."

	^applicableClassNames! !

!DynamicMappingRule methodsFor: 'accessing' stamp: 'slosh 8/7/2000 22:54'!
applicableClassNames: anObject
	"Set the receiver's instance variable applicableClassNames to anObject."

	applicableClassNames := anObject! !

!DynamicMappingRule methodsFor: 'accessing' stamp: 'slosh 8/7/2000 22:54'!
applyRuleBlock
	"Answer the receiver's instance variable applyRuleBlock."

	^applyRuleBlock! !

!DynamicMappingRule methodsFor: 'accessing' stamp: 'slosh 8/7/2000 22:54'!
applyRuleBlock: anObject
	"Set the receiver's instance variable applyRuleBlock to anObject."

	applyRuleBlock := anObject! !

!DynamicMappingRule methodsFor: 'accessing' stamp: 'slosh 8/7/2000 22:54'!
isLoad
	"Answer the receiver's instance variable isLoad."

	^isLoad! !

!DynamicMappingRule methodsFor: 'accessing' stamp: 'slosh 8/7/2000 22:54'!
isLoad: anObject
	"Set the receiver's instance variable isLoad to anObject."

	isLoad := anObject! !

!DynamicMappingRule methodsFor: 'accessing' stamp: 'slosh 8/7/2000 22:54'!
isSave
	"Answer the receiver's instance variable isSave."

	^isSave! !

!DynamicMappingRule methodsFor: 'accessing' stamp: 'slosh 8/7/2000 22:54'!
isSave: anObject
	"Set the receiver's instance variable isSave to anObject."

	isSave := anObject! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 21:49'!
, anOldMappingRuleClass 
	"Add a mapping rule while keeping rules sorted by priority. Higher
	 priority is before lower priority. Duplicates are ignored."

	self == anOldMappingRuleClass ifTrue: [^self].
	^SrpMappingRuleCollection new , anOldMappingRuleClass , self! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 21:49'!
applicationPriority
	"Answer a value that will be used to sequence mapping 
	 rules in case there are multiple rules defined for the same
	 class. Higher values have priority over lower values."

	^500
! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 22:58'!
applyTo: anObject context: context
	"The receiver is given the opportunity to apply mapping
	 rules to anObject. Answer anObject or another object
	 that is to take the place of anObject."

	^self applyRuleBlock value: anObject value: context

! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 22:45'!
asNative
	"Answer an object that is to represent the receiver.
	 Keep in mind that each slot of the receiver may
	 have a loader socket around it. Also be aware that
	 when an object references the receiver, and the receiver
	 also references that object, that the slots for that
	 object may not be fully loaded yet."
! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 22:00'!
copyright
	^ self class copyright
! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 21:51'!
debugPrintOn: aStream

	self printOn: aStream.
	aStream cr; tab; nextPutAll: 'priority: '.
	self applicationPriority printOn: aStream.
	aStream cr; tab; nextPutAll: 'applies to any of: '.
	self applicableClassNames printOn: aStream.
! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 21:57'!
documentation
"
 This class is a instance-based MappingRule that can be tuned 
 by the user of that instance.  It currently modifies the object 
 into a squeak remote handle.  You should be able to set a remap
 block so that you can control what things get converted to.

 Note:  I think I will be modifying the Marshaller to not check for 
 equivalent classes, or overriding the #srpClass method of the Shadow or Soul.

"! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 21:58'!
includes: aMappingRule
	"Receiver is not a rule collection, so just return
	 boolean whether the receiver is the rule."

	^self == aMappingRule
! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 22:58'!
initialize
	applicableClassNames := Array new.
	isLoad := false.
	isSave := false.
	applyRuleBlock := [:object :context | object].
! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 21:58'!
isDefaultRule
	"Answer boolean whether this rule should added to
	 the collection of active rules by default. By default,
	 all mapping rules will be added. You must override
	 this method to answer false if you want to add rules
	 only under certain conditions--which you also specify."

	^ false

! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/8/2000 00:24'!
isLoadRule
	"Answer boolean whether this rule can be used
	 when loading."

	^self isLoad! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/8/2000 00:25'!
isSaveRule
	"Answer boolean whether this rule can be used
	 when saving."

	^self isSave! !

!DynamicMappingRule methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 21:59'!
without: aMappingRule
	"Receiver is not a rule collection, so just return
	 nil if the receiver was the rule to be removed."

	^self = aMappingRule
		ifTrue: [nil]
		ifFalse: [self]
! !


!DynamicMappingRule class methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 22:50'!
applicableClassNames
	"Answer a collection of all class names whose instances
	 are affected by the receiver. The receiver will be applied
	 to all instances of classes named in the list."

	^#()
! !

!DynamicMappingRule class methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 22:50'!
applyTo: anObject context: context
	"The receiver is given the opportunity to apply mapping
	 rules to anObject. Answer anObject or another object
	 that is to take the place of anObject."

	^ anObject
! !

!DynamicMappingRule class methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 21:51'!
copyright

"Copyright (C) 2000 Robert Withers
 Distributed under terms of the Squeak License.
 More information can be found by inspecting the code below."
	^SrpObjectStream copyright.
! !

!DynamicMappingRule class methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 22:50'!
isDefaultRule
	"Answer boolean whether this rule should added to
	 the collection of active rules by default. By default,
	 all mapping rules will be added. You must override
	 this method to answer false if you want to add rules
	 only under certain conditions--which you also specify."

	^false

! !

!DynamicMappingRule class methodsFor: 'as yet unclassified' stamp: 'slosh 8/7/2000 22:55'!
new
	^ super new initialize
! !


!SrpConfiguration methodsFor: 'context creation' stamp: 'slosh 8/8/2000 00:03'!
loadContext
	^ SrpLoadContext newConfiguration: self
! !

!SrpConfiguration methodsFor: 'context creation' stamp: 'slosh 8/8/2000 00:02'!
saveContext
	^ SrpSaveContext newConfiguration: self
! !


!ChatterConfiguration methodsFor: 'rules' stamp: 'slosh 8/11/2000 14:25'!
addMappingRules: rules
	self availableMappingRules addAll: rules.
! !

!ChatterConfiguration methodsFor: 'rules' stamp: 'slosh 8/11/2000 14:25'!
availableMappingLoadRules
	^self availableMappingRules select: [:ea | ea isLoadRule ]! !

!ChatterConfiguration methodsFor: 'rules' stamp: 'slosh 8/11/2000 14:25'!
availableMappingRules
	"Answer a collection of all the mapping rules that
	 are available for use if desired."

	^ instanceMappingRules ifNil: [instanceMappingRules := OrderedCollection new]
! !

!ChatterConfiguration methodsFor: 'rules' stamp: 'slosh 8/11/2000 14:25'!
availableMappingSaveRules
	^self availableMappingRules select: [:ea | ea isSaveRule ]! !

!ChatterConfiguration methodsFor: 'rules' stamp: 'slosh 8/11/2000 14:26'!
removeMappingRules: aCollection
	"Removes aCollection of mapping rules that will be used to
	 perform special operations on instances as they are
	 encountered."

	aCollection do: [:ea | self availableMappingRules remove: ea ifAbsent: []].
! !

!ChatterConfiguration methodsFor: 'rules' stamp: 'slosh 8/11/2000 14:26'!
shouldApplyRule: aRule
	^ (super shouldApplyRule: aRule) or: [self availableMappingRules includes: aRule]
! !

!ChatterConfiguration methodsFor: 'handle api' stamp: 'slosh 8/10/2000 10:51'!
handleForObject: anObject
	^ self handleManager handleForObject: anObject
! !

!ChatterConfiguration methodsFor: 'handle api' stamp: 'slosh 8/8/2000 19:41'!
remapHandle: aHandle
	^ self handleManager remapHandle: aHandle
! !

!ChatterConfiguration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 14:37'!
contextId
	"Answer the receiver's instance variable handleManager."

	^ self handleManager contextId

! !

!ChatterConfiguration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 14:37'!
contextId: anId
	"Answer the receiver's instance variable handleManager."

	self handleManager contextId: anId.


! !

!ChatterConfiguration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 15:59'!
handleManager
	"Answer the receiver's instance variable handleManager."

	^handleManager ifNil: [handleManager := self handleManagerClass newConfiguration: self]
! !

!ChatterConfiguration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 15:28'!
handleManagerClass
	^ ChatterHandleManager
! !

!ChatterConfiguration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 15:57'!
handleRegistrationClass
	^ ChatterHandleRegistration
! !

!ChatterConfiguration methodsFor: 'accessing' stamp: 'slosh 8/8/2000 01:35'!
loadContext
	^ ChatterLoadContext newConfiguration: self

! !

!ChatterConfiguration methodsFor: 'accessing' stamp: 'slosh 8/11/2000 15:57'!
objectRegistrationClass
	^ ChatterObjectRegistration
! !

!ChatterConfiguration methodsFor: 'accessing' stamp: 'slosh 8/7/2000 23:11'!
objectStreamClass
	^ChatterObjectStream! !

!ChatterConfiguration methodsFor: 'accessing' stamp: 'slosh 8/8/2000 01:35'!
saveContext
	^ChatterSaveContext newConfiguration: self
! !


!ChatterConfiguration class methodsFor: 'as yet unclassified' stamp: 'slosh 8/10/2000 09:38'!
default   "ChatterConfiguration default"
	| config |
	config := self new.
	config addMappingRules: self handleMappingRules.
	^ config

! !

!ChatterConfiguration class methodsFor: 'as yet unclassified' stamp: 'slosh 8/11/2000 15:01'!
handleMappingRules
	| rules |
	rules := OrderedCollection new.
	rules add: (DynamicMappingRule new
		applicableClassNames: #(Process Socket Semaphore);
		isSave: true;
		applyRuleBlock: [:complexObject :context | context handleForObject: complexObject];
		yourself).
	rules add: (DynamicMappingRule new
		applicableClassNames: #(ChatterObjectHandle);
		isLoad: true;
		applyRuleBlock: [:handle :context | context remapHandle: handle];
		yourself).
	rules add: (DynamicMappingRule new
		applicableClassNames: #(ChatterObjectHandle);
		isLoad: true;
		applyRuleBlock: [:handle :context | context remapHandle: handle];
		yourself).
	^ rules
! !

!ChatterConfiguration class methodsFor: 'as yet unclassified' stamp: 'slosh 8/11/2000 14:53'!
testHandleManager   "ChatterConfiguration testHandleManager"
	| config1 config2 byteArray|
	config1 := ChatterConfiguration default.
	config1 contextId: 1.
	config1 explore.
	config2 := ChatterConfiguration default.
	config2 contextId: 2.
	config2 explore.
	byteArray := config1 newStream nextPut: (Semaphore new);
					reset;
					streamContents.
	^ config2 newStream on: (ReadStream on: byteArray);
		next

! !


!SrpObjectLoader methodsFor: 'Initialization' stamp: 'slosh 8/8/2000 00:01'!
initializeConfiguration: aConfig
	"Private."

	super initializeConfiguration: aConfig.
	context := aConfig loadContext.
	directCommand := aConfig directLoadCommand.
	aConfig beingUsedForObjectLoader: self.! !


!SrpObjectSaver methodsFor: 'Initialization' stamp: 'slosh 8/8/2000 00:01'!
initializeConfiguration: aConfig
	"Private."

	super initializeConfiguration: aConfig.
	hitList := self newHitList.
	duplicationTypes := aConfig duplicationTypes asSet.
	context := aConfig saveContext.
	directCommand := aConfig directSaveCommand.
	aConfig beingUsedForObjectSaver: self.! !


!SrpPortableBehaviorSqueak methodsFor: 'As yet unclassified' stamp: 'slosh 8/6/2000 09:21'!
shortNameForBehavior: aClass
	"This would return #String for both String and String 
	 class (not #Metaclass)."
	^aClass isMeta
		ifTrue: [ aClass soleInstance name ]
		ifFalse: [ aClass name ]! !

!SrpPortableBehaviorSqueak methodsFor: 'as yet unclassified' stamp: 'slosh 8/6/2000 09:19'!
behaviorIsMetaclass: aBehavior

	^aBehavior isMeta! !


!ChatterObjectRegistration class reorganize!
('instance creation' new on:handle:)
!


!ChatterObjectHandle class reorganize!
('instance creation' new onHandleId:contextId:)
!


!ChatterHandleRegistration class reorganize!
('instance creation' new on:)
!



More information about the Squeak-dev mailing list