RGAbstractContainer.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 02 Sep 2015 09:18:30 +0100
changeset 4 90637b709fa9
parent 0 43cb9f3e345e
child 5 5cc2caa88b23
permissions -rw-r--r--
Added RGAbstractContainer>>addElements:

"{ Package: 'stx:goodies/ring' }"

"{ NameSpace: Smalltalk }"

RGDefinition subclass:#RGAbstractContainer
	instanceVariableNames:'elements'
	classVariableNames:''
	poolDictionaries:''
	category:'Ring-Core-Containers'
!

RGAbstractContainer comment:'This is the abstract class for container-based elements.
Elements are separated in groups by kind (e.g classes, methods, pools, etc.)
Subclasses have to define the kind of collection for a particular group of entities.
For a container the use of a dictionary or another collection (e.g. SortedCollection) to store group of elements is independent.

'
!


!RGAbstractContainer methodsFor:'accessing'!

elements
    "Retrieves the elements"
    
    ^elements
! !

!RGAbstractContainer methodsFor:'adding/removing'!

addElement: anObject

    anObject addInContainer: self
!

addElement: anObject in: aCollection

    aCollection isDictionary
        ifTrue: [ aCollection at: anObject fullName put: anObject ]
        ifFalse:[ aCollection add: anObject ]
!

addElements: aCollection
    aCollection do:[:each | each addElement: each ]

    "Created: / 01-09-2015 / 21:39:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

removeElement: anObject

    anObject removeFromContainer: self
!

removeElement: anObject from: aCollection

    aCollection isDictionary
        ifTrue: [ aCollection removeKey: anObject fullName ifAbsent:[ ] ]
        ifFalse:[ aCollection remove: anObject ifAbsent:[ ] ]
! !

!RGAbstractContainer methodsFor:'initialization'!

initialize

    super initialize.
    elements:= IdentityDictionary new.
! !

!RGAbstractContainer methodsFor:'initialize-release'!

flushElements

    elements:= IdentityDictionary new
! !

!RGAbstractContainer methodsFor:'iterating elements'!

elementsDo: aBlock
    elements valuesDo: [ :collection | collection do: [ :each | aBlock value: each ] ]
! !

!RGAbstractContainer methodsFor:'lookup elements'!

elementNamed: elementName
    | aSymbol found |
    
    aSymbol:= elementName asSymbol.
    elements do:[ :collection| 		
        (found:= self elementNamed: aSymbol in: collection) notNil ifTrue:[ ^found ] ].
    ^nil
!

elementNamed: elementName in: aCollection
    | aSymbol |
    
    aSymbol:= elementName asSymbol.
    ^aCollection isDictionary
        ifTrue: [ aCollection at: aSymbol ifAbsent: [ nil ] ]
        ifFalse:[ aCollection detect:[ :each| each fullName = aSymbol ] ifNone:[ nil ] ]
! !

!RGAbstractContainer methodsFor:'managing elements groups'!

elementsCategorized: aSymbol
    "Retrieves a group of elements.
    If does not exist set an Set"
    
    ^elements at: aSymbol ifAbsentPut:[ Set ]
!

elementsCategorized: aSymbol with: aCollection
    "Allows to define other groups of elements with a particular kind of collection"
    
    elements at: aSymbol put: aCollection
!

removeElementsCategorized: aSymbol
    "Deletes a group of elements"
    
    elements removeKey: aSymbol ifAbsent:[ ]
! !

!RGAbstractContainer methodsFor:'testing'!

includesElement: anRGDefinition

    ^anRGDefinition isIncludedInContainer: self
!

includesElementNamed: elementName

    ^ elements anySatisfy: [ :collection | self includesElementNamed: elementName asSymbol in: collection ]
!

includesElementNamed: elementName in: aCollection

    ^aCollection isDictionary
        ifTrue: [ aCollection includesKey:  elementName asSymbol ]
        ifFalse:[ aCollection anySatisfy: [ :each| each name = elementName asSymbol ] ]
! !

!RGAbstractContainer class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !