support/Xtreams__RecyclingCenter.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 01 Feb 2012 00:37:59 +0000
changeset 98 bd334e72464f
parent 93 cc18004ec5a5
child 109 9587e2df7029
permissions -rw-r--r--
Fix in #read:into:at:

"{ Package: 'stx:goodies/xtreams/support' }"

"{ NameSpace: Xtreams }"

Object subclass:#RecyclingCenter
	instanceVariableNames:'recycled mutex'
	classVariableNames:''
	poolDictionaries:'Xtreams::XtreamsPool'
	category:'Xtreams-Support'
!

RecyclingCenter class instanceVariableNames:'objectspace1 fixedspace1 objectspaceN fixedspaceN cacheSize'

"
 No other class instance variables are inherited by this class.
"
!

RecyclingCenter comment:'Instance Variables
	recycled	<IdentityDictionary key: Class value: (Array of: SequenceableCollection)> caches fixed number of collections (3) per sequenceable collection class
	mutex	<Semaphore>

Class Instance Variables
	objectspace1	<RecyclingCenter> old space collections size 1
	fixedspace1	<RecyclingCenter> fixed space collections size 1
	objectspaceN	<RecyclingCenter> old space collections of cacheSize
	fixedspaceN	<RecyclingCenter> fixed space collection of cacheSize
	cacheSize	<SmallInteger> default collection size

'
!


!RecyclingCenter class methodsFor:'class initialization'!

initialize
        | cacheLimit |
        cacheSize := DefaultBufferSize.
        cacheLimit := 3.
        objectspace1 := self new initialize: cacheLimit.
        fixedspace1 := self new initialize: cacheLimit.
        objectspaceN := self new initialize: cacheLimit.
        fixedspaceN := self new initialize: cacheLimit
! !

!RecyclingCenter class methodsFor:'recycling'!

new: anInteger class: aClass
	anInteger == 1 ifTrue: [^objectspace1 new: anInteger class: aClass].
	anInteger == cacheSize ifTrue: [^objectspaceN new: anInteger class: aClass].
	^aClass withSize: anInteger
!

newInFixedSpace: anInteger class: aClass
	anInteger == 1 ifTrue: [^fixedspace1 newInFixedSpace: anInteger class: aClass].
	anInteger == cacheSize ifTrue: [^fixedspaceN newInFixedSpace: anInteger class: aClass].
	^aClass newInFixedSpace: anInteger
!

recycle: aCollection
	aCollection == nil ifTrue: [^nil].
	aCollection isFixedArgument
		ifTrue:
			[aCollection size == 1 ifTrue: [fixedspace1 recycle: aCollection].
			aCollection size == cacheSize ifTrue: [fixedspaceN recycle: aCollection]]
		ifFalse:
			[aCollection size == 1 ifTrue: [objectspace1 recycle: aCollection].
			aCollection size == cacheSize ifTrue: [objectspaceN recycle: aCollection]]
! !

!RecyclingCenter methodsFor:'initialize-release'!

initialize: aCacheLimit
	mutex := Semaphore forMutualExclusion.
	recycled := IdentityDictionary new.
	SequenceableCollection allSubclassesDo: [:aClass | recycled at: aClass put: (Array new: aCacheLimit)].
	recycled at: InterpretedBytes put: (Array new: aCacheLimit)
! !

!RecyclingCenter methodsFor:'recycling'!

existing: aClass
        | queue collection |
        queue := recycled at: aClass.
        mutex critical: [
        1 to: queue size do: [:index |
                collection := queue at: index.
                collection == nil ifFalse:
                        [queue at: index put: nil.
                        mutex signal.
                        ^collection]]].
        ^nil
!

new: anInteger class: aClass
	| collection |
	(collection := self existing: aClass) == nil ifTrue: [collection := aClass withSize: anInteger].
	^collection
!

newInFixedSpace: anInteger class: aClass
	| collection |
	(collection := self existing: aClass) == nil ifTrue: [collection := aClass newInFixedSpace: anInteger].
	^collection
!

recycle: aCollection
        | queue |
        queue := recycled at: aCollection class.
        mutex critical: [
        1 to: queue size do: [:index |
                (queue at: index) == nil ifTrue:
                        [queue at: index put: aCollection.
                        mutex signal.
                        ^self]]]
! !

!RecyclingCenter class methodsFor:'documentation'!

version_SVN
    ^ '$Id$'
! !

RecyclingCenter initialize!