core/MetacelloToolBoxConstructor.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 19 Sep 2012 01:38:26 +0000
changeset 20 8caf2f257260
parent 16 25ac697dc747
permissions -rw-r--r--
- fixes for package support

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

MetacelloAbstractVersionConstructor subclass:#MetacelloToolBoxConstructor
	instanceVariableNames:'currentSection methodSections'
	classVariableNames:''
	poolDictionaries:''
	category:'Metacello-Core-Constructors'
!


!MetacelloToolBoxConstructor methodsFor:'api'!

for: attribute do: aBlock
	"conditional version support"

	| methodSection |
	methodSection := (MetacelloVersionMethodSection new)
				attribute: attribute;
				block: aBlock;
				yourself.
	currentSection ~~ nil
		ifTrue: [ currentSection addMethodSection: methodSection ]
		ifFalse: [ self methodSections add: methodSection]
!

for: attribute version: aString
	"conditional symbolicVersion support"

	self methodSections
		add:
			((MetacelloSymbolicVersionSpec new)
				attribute: attribute;
				versionString: aString;
				yourself)
! !

!MetacelloToolBoxConstructor methodsFor:'enumeration'!

methodSectionsDo: aBlock

	self methodSection: self do: aBlock
!

methodSectionsInEvaluationOrder: attributes do: aBlock
	"breadth first traversal ... to collect selected sections, then evaluate individual sections in attribute order"

	| selected |
	selected := OrderedCollection new.
	self methodSection: self inEvaluationOrder: attributes do: [:methodSection | selected add: methodSection ]. 
	attributes
		do: [ :attribute | (selected select: [ :methodSection | methodSection attribute == attribute ]) do: aBlock ].
! !

!MetacelloToolBoxConstructor methodsFor:'extraction'!

extractMethodSectionsFor: sourceVersionString
	| coll pragma |
	coll := self extractAllVersionPragmas at: sourceVersionString ifAbsent: [ ^ #() ].
	coll size > 1
		ifTrue: [ self error: 'More than one pragma defining ' , sourceVersionString printString ].
	pragma := coll at: 1.
	self evaluatePragma: pragma.
	self methodSections do: [ :methodSection | self evaluateMethodSection: methodSection version: sourceVersionString ].
!

extractSymbolicVersionSpecsFor: sourceVersionSymbol
	| coll versionSpec pragma |
	coll := self extractSymbolicVersionPragmas at: sourceVersionSymbol ifAbsent: [ ^ #() ].
	coll size > 1
		ifTrue: [ self error: 'More than one pragma defining ' , sourceVersionSymbol printString ].
	pragma := coll at: 1.
	self evaluatePragma: pragma.
	^ self methodSections

! !

!MetacelloToolBoxConstructor methodsFor:'initialization'!

reset
	super reset.	"not needed, but included for completeness"
	methodSections := nil
! !

!MetacelloToolBoxConstructor methodsFor:'private'!

evaluateMethodSection: methodSection version: sourceVersionString
	| versionSpec |
	versionSpec := self project versionSpec.
	versionSpec versionString: sourceVersionString.
	methodSection versionSpec: versionSpec.
	currentSection := methodSection.
	self with: versionSpec during: methodSection block.
	methodSection methodSections do: [ :ms | self evaluateMethodSection: ms version: sourceVersionString ]
!

methodSection: methodSection do: aBlock

	methodSection methodSections do: aBlock.
	methodSection methodSections do: [ :ms | self methodSection: ms do: aBlock ]
!

methodSection: methodSection inEvaluationOrder: attributes do: aBlock

	| selected |
	selected := OrderedCollection new.
	attributes
		do: [ :attribute | 
			methodSection methodSections
				do: [ :ms | 
					attribute == ms attribute
						ifTrue: [ selected add: ms ] ] ].
	selected do: aBlock.
	attributes size == 1
		ifTrue: [ ^ self ].
	selected
		do: [ :ms | self methodSection: ms inEvaluationOrder: (attributes copyFrom: 2 to: attributes size) do: aBlock ]
!

methodSections

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

!MetacelloToolBoxConstructor class methodsFor:'documentation'!

version_SVN
    ^ '$Id::                                                                                                                        $'
! !