core/MetacelloMemberListSpec.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 18 Sep 2012 18:24:44 +0000
changeset 16 25ac697dc747
parent 14 f01fe37493e9
child 27 bf1c8f371c50
permissions -rw-r--r--
- Updated from branch master

"{ Package: 'stx:goodies/metacello/core' }"

MetacelloSpec subclass:#MetacelloMemberListSpec
	instanceVariableNames:'list memberMap'
	classVariableNames:''
	poolDictionaries:''
	category:'Metacello-Core-Members'
!


!MetacelloMemberListSpec methodsFor:'accessing'!

list

	list == nil ifTrue: [ list := OrderedCollection new ].
	^list
!

list: aCollection

	list := aCollection.
	self clearMemberMap
!

map
	
	| map |
	memberMap ~~ nil ifTrue: [ ^memberMap ].
	map := Dictionary new.
	self list do: [:member | 
		member
			applyAdd: [:memberSpec | self mapAdd: memberSpec into: map ] 
			copy: [:memberSpec | self mapCopy: memberSpec into: map ]
			merge: [:memberSpec | self mapMerge: memberSpec into: map ] 
			remove: [:memberSpec | self mapRemove: memberSpec into: map ]].
	memberMap := map.
	^memberMap
! !

!MetacelloMemberListSpec methodsFor:'actions'!

add: aSpec

	self subclassResponsibility
!

copy: aMemberSpec

	self addMember: aMemberSpec
!

copy: specNamed to: aSpec

	self subclassResponsibility
!

merge: aSpec

	self subclassResponsibility
!

remove: aSpec

	self subclassResponsibility
! !

!MetacelloMemberListSpec methodsFor:'adding'!

addMember: aMember

	self list add: aMember.
	self clearMemberMap
! !

!MetacelloMemberListSpec methodsFor:'copying'!

postCopy

	super postCopy.
	list := list copy.
	self clearMemberMap
! !

!MetacelloMemberListSpec methodsFor:'enumeration'!

collect: aBlock 
	| newCollection |
	newCollection :=OrderedCollection new.
	self do: [:each | newCollection add: (aBlock value: each)].
	^ newCollection
!

detect: aBlock
	"Evaluate aBlock with each of the receiver's elements as the argument. 
	Answer the first element for which aBlock evaluates to true."

	^ self detect: aBlock ifNone: [ self error: 'Object is not in the collection.' ]
!

detect: aBlock ifNone: exceptionBlock
	"Evaluate aBlock with each of the receiver's elements as the argument.  
	Answer the first element for which aBlock evaluates to true. If none  
	evaluate to true, then evaluate the argument, exceptionBlock."

	self
		do: [ :each | 
			(aBlock value: each)
				ifTrue: [ ^ each ] ].
	^ exceptionBlock value
!

do: aBlock

	self map values do: aBlock
!

select: aBlock 
	| newCollection |
	newCollection := OrderedCollection new.
	self do: [:each | (aBlock value: each) ifTrue: [newCollection add: each]].
	^newCollection
!

specListDetect: aBlock
	"Evaluate aBlock with each of the receiver's elements as the argument. 
	Answer the first element for which aBlock evaluates to true."

	^ self specListDetect: aBlock ifNone: [ self error: 'Object is not in the collection.' ]
!

specListDetect: aBlock ifNone: exceptionBlock
	"Evaluate aBlock with each of the receiver's elements as the argument.  
	Answer the first element for which aBlock evaluates to true. If none  
	evaluate to true, then evaluate the argument, exceptionBlock."

	self
		specListDo: [ :each | 
			(aBlock value: each)
				ifTrue: [ ^ each ] ].
	^ exceptionBlock value
!

specListDo: aBlock

	self list do: [:member |  aBlock value: member spec ]
!

specListSelect: aBlock 
	| newCollection |
	newCollection := OrderedCollection new.
	self specListDo: [:each | (aBlock value: each) ifTrue: [newCollection add: each]].
	^newCollection
! !

!MetacelloMemberListSpec methodsFor:'merging'!

mergeSpec: anotherSpec

	| newSpec val |
	newSpec := super mergeSpec: anotherSpec.
	newSpec list: self list copy.
	anotherSpec list do: [:groupMember | groupMember applyToList: newSpec ].
	^newSpec
! !

!MetacelloMemberListSpec methodsFor:'private'!

clearMemberMap

	memberMap := nil.
!

mapAdd: aMemberSpec into: map
	
	map at: aMemberSpec name put: aMemberSpec spec
!

mapCopy: aMemberSpec into: map
    | spec |
    spec := map at: aMemberSpec sourceName ifAbsent: [  ].
    spec == nil
        ifTrue: [ ^ self error: 'Source spec named ' , aMemberSpec sourceName printString , ' not found' ]
        ifFalse: [ 
            spec aboutToCopy.
            map at: aMemberSpec name put: (spec copy mergeSpec: aMemberSpec spec copy) ]
!

mapMerge: aMemberSpec into: map
	| spec |
	spec :=  map at: aMemberSpec name ifAbsent: [].
	spec == nil
		ifTrue: [ map at: aMemberSpec name put: aMemberSpec spec copy ]
		ifFalse: [ map at: aMemberSpec name put: (spec mergeSpec: aMemberSpec spec)]
!

mapRemove: aMemberSpec into: map
	
	map removeKey: aMemberSpec name ifAbsent: []
! !

!MetacelloMemberListSpec methodsFor:'testing'!

isEmpty

	^self list isEmpty
!

notEmpty

	^self list notEmpty
! !

!MetacelloMemberListSpec class methodsFor:'documentation'!

version_SVN
    ^ '$Id::                                                                                                                        $'
! !