[squeak-dev] The Trunk: System-ul.688.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Oct 27 20:53:16 UTC 2014


Levente Uzonyi uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-ul.688.mcz

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

Name: System-ul.688
Author: ul
Time: 27 October 2014, 4:43:14.279 pm
UUID: 77747387-55a5-4118-95b5-752979bf1cf7
Ancestors: System-dtl.685

Replaced ExternalSemaphoreTable with ExternalObjectTable to provide faster registration, and give better support to the current users of external objects. Notable changes:

- the table is a separate object instead of a few class side methods
- the whole API can be found in SmalltalkImage in the external objects category
- #newExternalSemaphore, #newExternalSemaphoreDo: and #newExternalSemaphores: provide fast and easy creation and registration of Semaphores
- #unregisterExternalObjects: can unregister multiple objects faster
- #externalObjects will return a copy of the externalObjectsArray
- better scalability
- the maxExternalSemaphores VM parameter will be incremented as the externalObjectsArray grows

=============== Diff against System-dtl.685 ===============

Item was added:
+ Object subclass: #ExternalObjectTable
+ 	instanceVariableNames: 'semaphore externalObjectsArray freeSlotIndexes indexesByObjects'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'System-Support'!
+ ExternalObjectTable class
+ 	instanceVariableNames: 'current'!
+ 
+ !ExternalObjectTable commentStamp: 'ul 10/27/2014 16:26' prior: 0!
+ I'm an enhanced version of JMM's ExternalSemaphoreTable.
+ I'm responsible for maintaining the externalObjectsArray, which can be found at slot 39 of Smalltalk specialObjectsArray. Manipulating the array directly is highly discouraged.
+ 
+ My services are available via the methods of the "external objects" category of SmalltalkImage.
+ 
+ To register anObject simply use Smalltalk registerExternalObject: anObject. Use #unregisterExternalObject: to unregister it. It your responsibility to always unregister these objects.
+ If you'd like the create one or more new Semaphores, and register them for external use, then you should use one of #newExternalSemaphore, #newExternalSemaphoreDo: and #newExternalSemaphores:. If you want to unregister more than one external objects at the same time, then #unregisterExternalObjects: is the method you're looking for.
+ 
+ Implementation details:
+ I maintain a single instance (#current), which can automatically synchronize with externalObjectsArray.
+ All accesses are protected by the semaphore instance variable.
+ To ensure fast access, I keep track of the indexes of the external objects in the externalObjectArray in my indexesByObjects IdentityDictionary.
+ To ensure fast insertion, I keep track of the free slots of the externalObjectsArray in the freeSlotIndexes OrderedCollection. The access pattern is LIFO to avoid unnecessary growth and reordering of the OrderedCollection.
+ I can grow the externalObjectsArray (see #ensureFreeSlot), but I never shrink it.!
+ ExternalObjectTable class
+ 	instanceVariableNames: 'current'!

Item was added:
+ ----- Method: ExternalObjectTable class>>cleanUp: (in category 'initialize-release') -----
+ cleanUp: aggressive
+ 	"It's safe to release the instance"
+ 
+ 	self reset!

Item was added:
+ ----- Method: ExternalObjectTable class>>current (in category 'accessing') -----
+ current
+ 
+ 	^current ifNil: [
+ 		| newInstance |
+ 		newInstance := self new.
+ 		" Check again, because another process might have registered another instance. "
+ 		current ifNil: [ current := newInstance ] ]!

Item was added:
+ ----- Method: ExternalObjectTable class>>reset (in category 'accessing') -----
+ reset
+ 
+ 	current := nil!

Item was added:
+ ----- Method: ExternalObjectTable>>clearExternalObjects (in category 'accessing') -----
+ clearExternalObjects
+ 	"Clear the array of objects that have been registered for use in non-Smalltalk code."
+ 
+ 	semaphore critical: [
+ 		Smalltalk specialObjectsArray at: 39 put: Array new.
+ 		self 
+ 			initializeCaches;
+ 			synchronizeExternalObjectsArrayAndForceUpdate: true ]!

Item was added:
+ ----- Method: ExternalObjectTable>>ensureFreeSlot (in category 'private') -----
+ ensureFreeSlot
+ 	"Make sure there's at least one free slot."
+ 
+ 	| oldSize newSize newExternalObjectsArray specialObjectsArray |
+ 	freeSlotIndexes isEmpty ifFalse: [ ^self ].
+ 	oldSize := externalObjectsArray size.
+ 	newSize := oldSize + 20. "Linear growth is not really a problem, because we never shrink the array."
+ 	newExternalObjectsArray := externalObjectsArray species new: newSize.
+ 	newExternalObjectsArray
+ 		replaceFrom: 1
+ 		to: oldSize
+ 		with: externalObjectsArray
+ 		startingAt: 1.
+ 	specialObjectsArray := Smalltalk specialObjectsArray.
+ 	(specialObjectsArray at: 39) == externalObjectsArray
+ 		ifFalse: [
+ 			"We're not in sync. Try again."
+ 			^self
+ 				synchronizeExternalObjectsArrayAndForceUpdate: true;
+ 				ensureFreeSlot ].
+ 	specialObjectsArray at: 39 put: newExternalObjectsArray.
+ 	externalObjectsArray := newExternalObjectsArray.
+ 	newSize to: oldSize + 1 by: -1 do: [ :each |
+ 		freeSlotIndexes addFirst: each ].
+ 	Smalltalk maxExternalSemaphores ifNotNil: [ :maxExternalSemaphores |
+ 		"Make sure that those new external semaphores can be signaled by the VM. This is not entirely safe, but not incrementing at all is worse."
+ 		newSize > maxExternalSemaphores ifTrue: [
+ 			Smalltalk maxExternalSemaphores: newSize ] ]	
+ 
+ 	!

Item was added:
+ ----- Method: ExternalObjectTable>>externalObjects (in category 'accessing') -----
+ externalObjects
+ 	"Return a copy of the externalObjectsArray."
+ 
+ 	^semaphore critical: [
+ 		self synchronizeExternalObjectsArrayAndForceUpdate: false.
+ 		externalObjectsArray copy ]!

Item was added:
+ ----- Method: ExternalObjectTable>>externalObjectsArray: (in category 'private') -----
+ externalObjectsArray: anArray
+ 	"Update the index mapping using anArray as the new externalObjectsArray."
+ 
+ 	externalObjectsArray := anArray.
+ 	freeSlotIndexes reset.
+ 	indexesByObjects removeAll.
+ 	1 to: externalObjectsArray size do: [ :index |
+ 		(anArray at: index) 
+ 			ifNil: [ freeSlotIndexes addFirst: index ]
+ 			ifNotNil: [ :object | indexesByObjects at: object put: index ] ]!

Item was added:
+ ----- Method: ExternalObjectTable>>initialize (in category 'initialize-release') -----
+ initialize
+ 
+ 	semaphore := Semaphore forMutualExclusion.
+ 	self initializeCaches!

Item was added:
+ ----- Method: ExternalObjectTable>>initializeCaches (in category 'private') -----
+ initializeCaches
+ 
+ 	freeSlotIndexes := OrderedCollection new.
+ 	indexesByObjects := IdentityDictionary new!

Item was added:
+ ----- Method: ExternalObjectTable>>newExternalSemaphore (in category 'accessing') -----
+ newExternalSemaphore
+ 	"Create and register a new Semaphore, and return an array containing itself and its index."
+ 
+ 	| newSemaphore |
+ 	^{
+ 		newSemaphore := Semaphore new.
+ 		semaphore critical: [
+ 			self 
+ 				synchronizeExternalObjectsArrayAndForceUpdate: false;
+ 				safelyRegisterNewExternalObject: newSemaphore ] }!

Item was added:
+ ----- Method: ExternalObjectTable>>newExternalSemaphoreDo: (in category 'accessing') -----
+ newExternalSemaphoreDo: aBlock
+ 	"Create and register a new Semaphore, then evaluate aBlock with it and its index."
+ 
+ 	| newSemaphore |
+ 	^aBlock
+ 		value: (newSemaphore := Semaphore new)
+ 		value: (semaphore critical: [
+ 			self 
+ 				synchronizeExternalObjectsArrayAndForceUpdate: false;
+ 				safelyRegisterNewExternalObject: newSemaphore ])!

Item was added:
+ ----- Method: ExternalObjectTable>>newExternalSemaphores: (in category 'accessing') -----
+ newExternalSemaphores: count
+ 	"Create and register multiple Semaphores, and return an array containing the semaphores and their indexes in separate arrays."
+ 
+ 	| semaphores indexes |
+ 	semaphores := Array new: count.
+ 	1 to: count do: [ :index | semaphores at: index put: Semaphore new ].
+ 	indexes := Array new: count.
+ 	semaphore critical: [
+ 		self synchronizeExternalObjectsArrayAndForceUpdate: false.
+ 		1 to: count do: [ :index |
+ 			indexes at: index put: (
+ 				self safelyRegisterNewExternalObject: (semaphores at: index)) ] ].
+ 	^{ semaphores. indexes }!

Item was added:
+ ----- Method: ExternalObjectTable>>registerExternalObject: (in category 'accessing') -----
+ registerExternalObject: anObject
+ 	"Register the given object in the external objects array and return its index. If it is already there, just return its index."
+ 
+ 	anObject ifNil: [ ^nil ].
+ 	^semaphore critical: [
+ 		self 
+ 			synchronizeExternalObjectsArrayAndForceUpdate: false;
+ 			safelyRegisterExternalObject: anObject ]!

Item was added:
+ ----- Method: ExternalObjectTable>>safelyRegisterExternalObject: (in category 'private') -----
+ safelyRegisterExternalObject: anObject
+ 
+ 	| index |
+ 	(index := indexesByObjects at: anObject ifAbsent: nil) ifNotNil: [
+ 		(externalObjectsArray at: index) == anObject ifTrue: [ ^index ].
+ 		"indexesByObjects is out of sync. Try again."
+ 		^self
+ 			synchronizeExternalObjectsArrayAndForceUpdate: true;
+ 			safelyRegisterExternalObject: anObject ].
+ 	^self safelyRegisterNewExternalObject: anObject!

Item was added:
+ ----- Method: ExternalObjectTable>>safelyRegisterNewExternalObject: (in category 'private') -----
+ safelyRegisterNewExternalObject: anObject
+ 
+ 	| index |
+ 	self ensureFreeSlot.
+ 	index := freeSlotIndexes removeLast.
+ 	(externalObjectsArray at: index) ifNotNil: [
+ 		"Free slot is not empty. Try again."
+ 		^self 
+ 			synchronizeExternalObjectsArrayAndForceUpdate: true;
+ 			safelyRegisterNewExternalObject: anObject ].
+ 	externalObjectsArray at: index put: anObject.
+ 	indexesByObjects at: anObject put: index.
+ 	^index!

Item was added:
+ ----- Method: ExternalObjectTable>>safelyUnregisterExternalObject: (in category 'private') -----
+ safelyUnregisterExternalObject: anObject
+ 
+ 	(indexesByObjects removeKey: anObject ifAbsent: nil)
+ 		ifNotNil: [ :index |
+ 			(externalObjectsArray at: index) == anObject ifFalse: [
+ 				"We're not in sync. Try again."
+ 				^self
+ 					synchronizeExternalObjectsArrayAndForceUpdate: true;
+ 					safelyUnregisterExternalObject: anObject ].
+ 			externalObjectsArray at: index put: nil.
+ 			freeSlotIndexes add: index ]
+ 		ifNil: [
+ 			"Check if we're just out of sync."
+ 			(externalObjectsArray instVarsInclude: anObject) ifFalse: [ ^self ].
+ 			"We're not in sync. Try again."
+ 			^self
+ 				synchronizeExternalObjectsArrayAndForceUpdate: true;
+ 				safelyUnregisterExternalObject: anObject ]!

Item was added:
+ ----- Method: ExternalObjectTable>>synchronizeExternalObjectsArrayAndForceUpdate: (in category 'private') -----
+ synchronizeExternalObjectsArrayAndForceUpdate: forceUpdate
+ 
+ 	| actualExternalObjectsArray |
+ 	actualExternalObjectsArray := Smalltalk specialObjectsArray at: 39.
+ 	(actualExternalObjectsArray == externalObjectsArray and: [ forceUpdate not ])
+ 		ifTrue: [ ^self ].
+ 	self externalObjectsArray: actualExternalObjectsArray!

Item was added:
+ ----- Method: ExternalObjectTable>>unregisterExternalObject: (in category 'accessing') -----
+ unregisterExternalObject: anObject
+ 	"Unregister the given object from the external objects array. Do nothing if it isn't registered."
+ 
+ 	anObject ifNil: [ ^self ].
+ 	semaphore critical: [
+ 		self 
+ 			synchronizeExternalObjectsArrayAndForceUpdate: false;
+ 			safelyUnregisterExternalObject: anObject ]!

Item was added:
+ ----- Method: ExternalObjectTable>>unregisterExternalObjects: (in category 'accessing') -----
+ unregisterExternalObjects: aCollection
+ 	"Unregister the given objects from the external objects array. Do nothing if they aren't registered."
+ 
+ 	semaphore critical: [
+ 		self synchronizeExternalObjectsArrayAndForceUpdate: false.
+ 		aCollection do: [ :each |
+ 			each ifNotNil: [
+ 				self safelyUnregisterExternalObject: each ] ] ]!

Item was removed:
- Object subclass: #ExternalSemaphoreTable
- 	instanceVariableNames: ''
- 	classVariableNames: 'ProtectTable'
- 	poolDictionaries: ''
- 	category: 'System-Support'!
- 
- !ExternalSemaphoreTable commentStamp: '<historical>' prior: 0!
- By John M McIntosh johnmci at smalltalkconsulting.com
- This class was written to mange the external semaphore table. When I was writing a Socket test server I discovered various race conditions on the access to the externalSemaphore table. This new class uses class side methods to restrict access using a mutex semaphore. It seemed cleaner to deligate the reponsibility here versus adding more code and another class variable to SystemDictionary 
- 
- Note that in Smalltalk recreateSpecialObjectsArray we still directly play with the table.!

Item was removed:
- ----- Method: ExternalSemaphoreTable class>>clearExternalObjects (in category 'accessing') -----
- clearExternalObjects
- 	"Clear the array of objects that have been registered for use in non-Smalltalk code."
- 
- 	ProtectTable critical: [Smalltalk specialObjectsArray at: 39 put: Array new].
- !

Item was removed:
- ----- Method: ExternalSemaphoreTable class>>externalObjects (in category 'accessing') -----
- externalObjects
- 	^ProtectTable critical: [Smalltalk specialObjectsArray at: 39].!

Item was removed:
- ----- Method: ExternalSemaphoreTable class>>initialize (in category 'initialize') -----
- initialize
- 	ProtectTable := Semaphore forMutualExclusion!

Item was removed:
- ----- Method: ExternalSemaphoreTable class>>registerExternalObject: (in category 'accessing') -----
- registerExternalObject: anObject
- 	^ ProtectTable critical: [self safelyRegisterExternalObject: anObject]
- !

Item was removed:
- ----- Method: ExternalSemaphoreTable class>>safelyRegisterExternalObject: (in category 'accessing') -----
- safelyRegisterExternalObject: anObject
- 	"Register the given object in the external objects array and return its index. If it is already there, just return its index."
- 
- 	| objects firstEmptyIndex obj sz newObjects |
- 	objects := Smalltalk specialObjectsArray at: 39.
- 
- 	"find the first empty slot"
- 	firstEmptyIndex := 0.
- 	1 to: objects size do: [:i |
- 		obj := objects at: i.
- 		obj == anObject ifTrue: [^ i].  "object already there, just return its index"
- 		(obj == nil and: [firstEmptyIndex = 0]) ifTrue: [firstEmptyIndex := i]].
- 
- 	"if no empty slots, expand the array"
- 	firstEmptyIndex = 0 ifTrue: [
- 		sz := objects size.
- 		newObjects := objects species new: sz + 20.  "grow linearly"
- 		newObjects replaceFrom: 1 to: sz with: objects startingAt: 1.
- 		firstEmptyIndex := sz + 1.
- 		Smalltalk specialObjectsArray at: 39 put: newObjects.
- 		objects := newObjects].
- 
- 	objects at: firstEmptyIndex put: anObject.
- 	^ firstEmptyIndex
- !

Item was removed:
- ----- Method: ExternalSemaphoreTable class>>safelyUnregisterExternalObject: (in category 'accessing') -----
- safelyUnregisterExternalObject: anObject
- 	"Unregister the given object in the external objects array. Do nothing if it isn't registered.
- 	JMM change to return if we clear the element, since it should only appear once in the array"
- 
- 	| objects |
- 	anObject ifNil: [^ self].
- 	objects := Smalltalk specialObjectsArray at: 39.
- 	1 to: objects size do: [:i |
- 		(objects at: i) == anObject ifTrue: 
- 		[objects at: i put: nil.
- 		^self]].
- !

Item was removed:
- ----- Method: ExternalSemaphoreTable class>>unregisterExternalObject: (in category 'accessing') -----
- unregisterExternalObject: anObject
- 	ProtectTable critical: [self safelyUnregisterExternalObject: anObject]
- !

Item was changed:
+ ----- Method: SmalltalkImage>>clearExternalObjects (in category 'external objects') -----
- ----- Method: SmalltalkImage>>clearExternalObjects (in category 'special objects') -----
  clearExternalObjects
  	"Clear the array of objects that have been registered for use in non-Smalltalk code."
  	"Smalltalk clearExternalObjects"
  
+ 	ExternalObjectTable current clearExternalObjects
- 	ExternalSemaphoreTable clearExternalObjects
  !

Item was changed:
+ ----- Method: SmalltalkImage>>externalObjects (in category 'external objects') -----
- ----- Method: SmalltalkImage>>externalObjects (in category 'special objects') -----
  externalObjects
  	"Return an array of objects that have been registered for use in non-Smalltalk code. Smalltalk objects should be referrenced by external code only via indirection through this array, thus allowing the objects to move during compaction. This array can be cleared when the VM re-starts, since variables in external code do not survive snapshots. Note that external code should not attempt to access a Smalltalk object, even via this mechanism, while garbage collection is in progress."
+ 	"Note that this is just a copy of the array used by the VM."
  	"Smalltalk externalObjects"
  
+ 	^ExternalObjectTable current externalObjects
- 	^ ExternalSemaphoreTable externalObjects
  !

Item was added:
+ ----- Method: SmalltalkImage>>newExternalSemaphore (in category 'external objects') -----
+ newExternalSemaphore
+ 	"Create and register a new Semaphore, and return an array containing itself and its index."
+ 
+ 	^ExternalObjectTable current newExternalSemaphore!

Item was added:
+ ----- Method: SmalltalkImage>>newExternalSemaphoreDo: (in category 'external objects') -----
+ newExternalSemaphoreDo: aBlock 
+ 	"Create and register a new Semaphore, then evaluate aBlock with it and its index."
+ 
+ 	^ExternalObjectTable current newExternalSemaphoreDo: aBlock!

Item was added:
+ ----- Method: SmalltalkImage>>newExternalSemaphores: (in category 'external objects') -----
+ newExternalSemaphores: count 
+ 	"Create and register multiple Semaphores, and return an array containing the semaphores and their indexes in separate arrays."
+ 
+ 	^ExternalObjectTable current newExternalSemaphores: count!

Item was changed:
+ ----- Method: SmalltalkImage>>registerExternalObject: (in category 'external objects') -----
- ----- Method: SmalltalkImage>>registerExternalObject: (in category 'special objects') -----
  registerExternalObject: anObject
  	"Register the given object in the external objects array and return its index. If it is already there, just return its index."
  
+ 	^ExternalObjectTable current registerExternalObject: anObject!
- 	^ExternalSemaphoreTable registerExternalObject: anObject!

Item was changed:
+ ----- Method: SmalltalkImage>>unregisterExternalObject: (in category 'external objects') -----
- ----- Method: SmalltalkImage>>unregisterExternalObject: (in category 'special objects') -----
  unregisterExternalObject: anObject
  	"Unregister the given object in the external objects array. Do nothing if it isn't registered."
  
+ 	ExternalObjectTable current unregisterExternalObject: anObject!
- 	ExternalSemaphoreTable unregisterExternalObject: anObject!

Item was added:
+ ----- Method: SmalltalkImage>>unregisterExternalObjects: (in category 'external objects') -----
+ unregisterExternalObjects: aCollection
+ 	"Unregister the given objects from the external objects array. Do nothing if they aren't registered."
+ 
+ 	ExternalObjectTable current unregisterExternalObjects: aCollection!



More information about the Squeak-dev mailing list