[squeak-dev] The Inbox: System-hsj.453.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Aug 18 09:47:49 UTC 2011


A new version of System was added to project The Inbox:
http://source.squeak.org/inbox/System-hsj.453.mcz

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

Name: System-hsj.453
Author: hsj
Time: 18 August 2011, 11:47:23.92 am
UUID: 2e054529-adf7-4ac2-8156-53d736d9edfd
Ancestors: System-hsj.452

Reverted back to maxExternalSemaphores, it is in fact a more accurate name.
Added more comments
Changed all uses of ProtectTable lock, and removed it from definition.

=============== Diff against System-hsj.452 ===============

Item was changed:
  Object subclass: #ExternalSemaphoreTable
  	instanceVariableNames: ''
+ 	classVariableNames: 'ProtectAdd ProtectRemove'
- 	classVariableNames: 'ProtectAdd ProtectRemove ProtectTable'
  	poolDictionaries: ''
  	category: 'System-Support'!
  
+ !ExternalSemaphoreTable commentStamp: 'HenrikSperreJohansen 8/18/2011 11:25' prior: 0!
- !ExternalSemaphoreTable commentStamp: 'HenrikSperreJohansen 8/17/2011 14:52' 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 two mutex semaphores, one for removal and one for additions to the table. 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.
  
+ Henrik Sperre Johansen
+ The name is somewhat of a misnomer; the table can be used for any objects, not just semaphores.
+ That is its main usage though, so a split which deals with semaphores and other external objects differently 
+ (In the same underlying table) is not currently worth it.
+ Therefore, while in general not all users will care if the table is above a certain size, we still guard  against adding more objects than the limit above which external signals would be lost (on some VMs.)
+ !
- 
- Note that in Smalltalk recreateSpecialObjectsArray we still directly play with the table.!

Item was changed:
  ----- Method: ExternalSemaphoreTable class>>clearExternalObjects (in category 'accessing') -----
  clearExternalObjects
  	"Clear the array of objects that have been registered for use in non-Smalltalk code."
+ 	"Only lock additions, removals executing in parallel would have little effect on the resulting array"
+ 
- 	"Only protect adds, concurrent removals would make little difference as to how empty the table is..."
  	ProtectAdd critical: [
  		self unprotectedExternalObjects: Array new].
  !

Item was changed:
  ----- Method: ExternalSemaphoreTable class>>collectionBasedOn:withRoomFor: (in category 'private') -----
+ collectionBasedOn: externalObjects withRoomFor: anObject
+ 	"Called if no slots to put anObject in have been found in externalObjects "
+ 	"Return a externalObject collection which does, either:
+ 		- Same collection with some slots freed up by finalization logic
+ 		- A larger array, which has replaced the parameter as canonical externalObject array.
+ 	An error must be raised if this method is incapable of fulfilling its duties"
+ 	
+ 	| newObjects newSize |
+ 	"grow linearly"
+ 	newSize :=  externalObjects size +20.
+ 	(self freedSlotsIn: externalObjects ratherThanIncreaseSizeTo: newSize) 
+ 		ifTrue: [newObjects := externalObjects]
- collectionBasedOn: aCollection withRoomFor: anObject
- 	"Return a collection with room to store anObject, either aCollection itself with free slots, or a larger copy"
- 	| sz newObjects newSize |
- 	sz := aCollection size.
- 	newSize := sz +20.  "grow linearly"
- 	(self freedSlotsIn: aCollection ratherThanIncreaseSizeTo: newSize) 
- 		ifTrue: [newObjects := aCollection]
  		ifFalse: [
+ 			newObjects := externalObjects species new: newSize. 
+ 			newObjects replaceFrom: 1 to:  externalObjects size with: externalObjects startingAt: 1.	
- 			newObjects := aCollection species new: newSize. 
- 			newObjects replaceFrom: 1 to: sz with: aCollection startingAt: 1.	
  			self unprotectedExternalObjects: newObjects.].
  	^newObjects!

Item was changed:
  ----- Method: ExternalSemaphoreTable class>>externalObjects (in category 'accessing') -----
  externalObjects
+ 	"Not really sure why this is protected, once called you are out of protection of the locks anyways, and any use of the object is dangerous...
+ 	Only additions can potentially change the actual array in use though, so only lock that."
+ 	^ProtectAdd critical: [self unprotectedExternalObjects].!
- 	^ProtectTable critical: [Smalltalk specialObjectsArray at: 39].!

Item was changed:
  ----- Method: ExternalSemaphoreTable class>>freedSlotsIn:ratherThanIncreaseSizeTo: (in category 'private') -----
  freedSlotsIn: externalObjects ratherThanIncreaseSizeTo: newSize
  	"In some VM's, the external object table has a max size, which has to be increased for vm to reference them correctly."
  	"In that case, try to gc to free slots first before actually increasing the max size"
  	"Return whether I ended up freeing slots by GC'ing, or one should increase the size of "
+ 	^Smalltalk vm maxExternalSemaphores
- 	^Smalltalk vm maxExternalObjects 
  		ifNotNil: [:maxSize |
  			(maxSize < newSize) and: 
+ 				[| needToGrow |
- 				[| freedEnoughSlots |
  				Smalltalk garbageCollect.
  				"Do we have free slots now? If not, performing the GC didn't help and we still have to grow."
+ 				needToGrow := externalObjects includes: nil.
- 				freedEnoughSlots := externalObjects includes: nil.
  				
+ 				needToGrow 
- 				freedEnoughSlots 
  					ifTrue: ["If we did GC, warn we had to gc so actions could be taken if appropriate."
+ 						Transcript cr; show: TimeStamp now printString; cr;
+ 							show:  'WARNING:  Had to GC to make room for more external objects.'; cr;
+ 							show: 'If this happens often, it would be a good idea to either:'; cr;
+ 							tab; show: '- Raise the maxExternalObjects size.'; cr;
+ 							tab; show: '- Write your code to explicitly release them rather than wait for finalization.']
+ 					ifFalse:  [Smalltalk vm maxExternalSemaphores: newSize].
+ 				needToGrow]]
- 						Transcript cr; show: TimeStamp now printString, 
- 						'
- WARNING:  Had to GC to make room for more external objects.
- If this happens often, it would be a good idea to either:
- 	- Raise the maxExternalObjects size.
- 	- Write your code to explicitly release them rather than wait for finalization.' ]
- 					ifFalse:  [Smalltalk vm maxExternalObjects: newSize].
- 				freedEnoughSlots]]
  		ifNil:[false]!

Item was changed:
  ----- 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 := self unprotectedExternalObjects.
- 	objects := Smalltalk specialObjectsArray at: 39.
  
  	"find the first empty slot"
+ 	firstEmptyIndex := 
+ 		(self slotFor: anObject in: objects) 
+ 			ifNil: ["if object has no empty slots,  we need to get a collection which does"
+ 				objects := self collectionBasedOn: objects withRoomFor: anObject.
+ 				self slotFor: anObject in: objects.].
- 	firstEmptyIndex := self slotFor: anObject in: objects.
- 
- 	"if object has no empty slots,  we need to get a collection which does"
- 	firstEmptyIndex = 0 ifTrue: [
- 		objects := self collectionBasedOn: objects 
- 						withRoomFor: anObject.
- 		firstEmptyIndex := self slotFor: anObject in: objects.].
- 
  	objects at: firstEmptyIndex put: anObject.
  	^ firstEmptyIndex
  !

Item was changed:
  ----- Method: ExternalSemaphoreTable class>>slotFor:in: (in category 'private') -----
  slotFor: anObject in: aCollection
+ 	"Return the first empty slot, or nil if there is none"
- 	"find the first empty slot"
  	"The following was written in an atomic fashion using special methods with no suspension points, not sure if on purpose, but keeping it that way for now.
  	Uses should be protected by the ProtectTable semaphore anyhow, but... it's too much work to reason 100% about it"
  
  	| firstEmptyIndex |
  	1 to: aCollection size do: [:i | | obj |
  		obj := aCollection at: i.
  		obj == anObject ifTrue: [^ i].  "object already there, just return its index"
  		(firstEmptyIndex == nil and: [obj == nil])  ifTrue: [firstEmptyIndex := i]].
+ 	^firstEmptyIndex!
- 	^firstEmptyIndex ifNil: [0]!

Item was removed:
- ----- Method: SmalltalkImage>>maxExternalObjects (in category 'vm parameters') -----
- maxExternalObjects
- 	"The size of array where external objects are registered. Only in Cog"
- 	self isRunningCog ifFalse: [^nil].
- 	^self vmParameterAt: 49!

Item was removed:
- ----- Method: SmalltalkImage>>maxExternalObjects: (in category 'vm parameters') -----
- maxExternalObjects: aSize
- 	"This method should never be called as result of normal program execution.
- 	If it is however, handle it differently:
- 	- In development, signal an error to promt user to set a bigger size at startup immediately.
- 	- In production, accept the cost of potentially unhandled interrupts, but log the action for later review.
- 	
- 	See comment in maxExternalObjectsSilently: why this behaviour is desirable,"
- 		
- 	"Can't find a place where development/production is decided.
- 	Suggest Smalltalk image inProduction, but use an overridable temp meanwhile."
- 	|inProduction|
- 	
- 	self isRunningCog ifFalse: [^0].
- 
- 	inProduction := false.
- 	^"Smalltalk image" inProduction
- 		 ifFalse: [self error: 'Not enough space for external objects, set a larger size at startup!!']
- 		ifTrue: [
- 			self maxExternalObjectsSilently: aSize.
- 			Transcript cr; 
- 				show: 'WARNING: Had to increase size of external object table due to many concurrently in use!!'; cr;
- 				show: 'You should increase this size at startup using #maxExternalObjectsSilently:';
- 				cr;
- 				show: 'Current table size: ', self maxExternalObjects printString]!

Item was removed:
- ----- Method: SmalltalkImage>>maxExternalObjectsSilently: (in category 'vm parameters') -----
- maxExternalObjectsSilently: aSize
- 	"Changes the size of array where external objects are registered. 
- 	The size can only grow, and will always be the next power of two larger than the parameter.
- 	
- 	The intended use is to set the table size to some adequate maximum as part of a non-resuming image startUp.
- 	
- 	Setting this at any time other than start-up can potentially lose requests.
- 	 i.e. during the realloc new storage is allocated, the old contents are copied and then pointers are switched. 
- 	 Requests occurring during copying won't be seen if they occur to indices already copied. "
- 	
- 	self isRunningCog ifFalse: [^0].
- 	"The vm-header field is a short, maximum 64k entries. Well, on most platforms anyways "
- 	(aSize < 0 or: [aSize > 16rFFFF]) ifTrue: [^DomainError signalFrom: 0 to: 16rFFFF].
- 	^self vmParameterAt: 49 put: aSize!

Item was changed:
  ----- Method: SmalltalkImage>>maxExternalSemaphores (in category 'vm parameters') -----
  maxExternalSemaphores
+ 	"The size of array in some VM's where external signals for semaphores in externalObjects are handled.
+ 	Essentially, if a semaphore is registered in externalObjects outside its bounds, they will not be signalled."
+ 	^[self vmParameterAt: 49] on: PrimitiveFailed do: [:ex | ex return: nil]!
- 	"The size of table where external semaphores are registered. Only in Cog"
- 	self isRunningCog ifFalse: [^nil].
- 	^self vmParameterAt: 49!

Item was changed:
  ----- Method: SmalltalkImage>>maxExternalSemaphores: (in category 'vm parameters') -----
  maxExternalSemaphores: aSize
+ 	"This method should never be called as result of normal program execution.
+ 	If it is however, handle it differently:
+ 	- In development, signal an error to promt user to set a bigger size at startup immediately.
+ 	- In production, accept the cost of potentially unhandled interrupts, but log the action for later review.
- 	"Changes the size of table where external semaphores are registered. 
- 	The size can only grow, and will always be the next power of two larger than the parameter.
  	
+ 	See comment in maxExternalObjectsSilently: why this behaviour is desirable,"
+ 		
+ 	"Can't find a place where development/production is decided.
+ 	Suggest Smalltalk image inProduction, but use an overridable temp meanwhile."
+ 	|inProduction|
- 	Setting this at any time other than start-up can potentially lose requests.
- 	 i.e. during the realloc new storage is allocated, t
- 	he old contents are copied and then pointers are switched. 
- 	 Requests occurring during copying won't be seen if they occur to indices already copied. 
- 	The intended use is to set the table to some adequate maximum at start-up"
  	
+ 	self maxExternalSemaphores ifNil: [^0].
+ 
+ 	inProduction := false.
+ 	^"Smalltalk image" inProduction
+ 		 ifFalse: [self error: 'Not enough space for external objects, set a larger size at startup!!']
+ 		ifTrue: [
+ 			self maxExternalSemaphoresSilently: aSize.
+ 			Transcript show: 'WARNING: Had to increase size of semaphore signal handling table due to many external objects concurrently in use'; cr;
+ 				show: 'You should increase this size at startup using #maxExternalObjectsSilently:'; cr;
+ 				show: 'Current table size: ', self maxExternalSemaphores printString]!
- 	self isRunningCog ifFalse: [^0].
- 	"The vm-header field is a short, maximum 64k entries. Well, on most platforms anyways "
- 	(aSize < 0 or: [aSize > 16rFFFF]) ifTrue: [^DomainError signalFrom: 0 to: 16rFFFF].
- 	^self vmParameterAt: 49 put: aSize!

Item was added:
+ ----- Method: SmalltalkImage>>maxExternalSemaphoresSilently: (in category 'vm parameters') -----
+ maxExternalSemaphoresSilently: aSize
+ 	"Changes the size of array where external signals for semaphores in externalObjects are handled.. 
+ 	The size can only grow, and will always be the next power of two larger than the parameter.
+ 	
+ 	The intended use is to set the table size to some adequate maximum as part of a non-resuming image startUp.
+ 	
+ 	Setting this at any time other than start-up can potentially result in lost signals during reallocation.
+ 	 i.e. 	 Requests handled during copying og signals from old to new array won't be seen if they occur to indices already copied, before pointers to the new and old arrays are switched. "
+ 	
+ 	self maxExternalSemaphores ifNil: [^0].
+ 	"The vm-header field where the size is stored is a short, maximum 64k entries. 
+ 	Well, on most platforms anyways "
+ 	(aSize < 0 or: [aSize > 16rFFFF]) ifTrue: [^DomainError signalFrom: 0 to: 16rFFFF].
+ 	^self vmParameterAt: 49 put: aSize!




More information about the Squeak-dev mailing list