MetacelloVersionSpec.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 05 Sep 2012 16:35:54 +0000
changeset 7 759ff40b4754
parent 1 9e312de5f694
child 8 e046a5b3427f
permissions -rw-r--r--
- stx_goodies_metacello_stx added: #extensionMethodNames changed: #classNamesAndAttributes #preRequisites

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

MetacelloSpec subclass:#MetacelloVersionSpec
	instanceVariableNames:'versionString blessing description author timestamp preLoadDoIt
		postLoadDoIt'
	classVariableNames:''
	poolDictionaries:''
	category:'Metacello-Core-Specs'
!


!MetacelloVersionSpec methodsFor:'accessing'!

author

	author == nil 
		ifTrue: [
			^self project valueHolderSpec
				value: '';
				yourself].
	^ author
!

author: anObject

	anObject setAuthorInMetacelloVersion: self
!

blessing

	blessing == nil 
		ifTrue: [
			^self project valueHolderSpec
				value: self project defaultBlessing;
				yourself].
	^ blessing
!

blessing: anObject

	anObject setBlessingInMetacelloVersion: self
!

description

	description == nil 
		ifTrue: [
			^self project valueHolderSpec
				value: '';
				yourself].
	^ description
!

description: anObject

	anObject setDescriptionInMetacelloVersion: self
!

getAuthor
	^author
!

getBlessing
	^blessing
!

getDescription
	^description
!

getPostLoadDoIt
	^postLoadDoIt
!

getPreLoadDoIt
	^preLoadDoIt
!

getTimestamp
	^timestamp
!

postLoadDoIt: anObject

	anObject setPostLoadDoItInMetacelloSpec: self
!

preLoadDoIt: anObject

	anObject setPreLoadDoItInMetacelloSpec: self
!

projectLabel

	^self project label
!

setAuthor: anObject
	author := anObject
!

setBlessing: anObject
	blessing := anObject
!

setDescription: anObject
	description := anObject
!

setPostLoadDoIt: aSymbol

	postLoadDoIt := aSymbol
!

setPreLoadDoIt: aSymbol

	preLoadDoIt := aSymbol
!

setTimestamp: anObject
	timestamp := anObject
!

timestamp

	timestamp == nil 
		ifTrue: [
			^self project valueHolderSpec
				value: '';
				yourself].
	^ timestamp
!

timestamp: anObject

	anObject setTimestampInMetacelloVersion: self
!

versionString: anObject
	versionString := anObject
! !

!MetacelloVersionSpec methodsFor:'construction'!

author: aBlockOrString constructor: aVersionConstructor
    aVersionConstructor authorForVersion: aBlockOrString
!

blessing: aBlockOrString constructor: aVersionConstructor
    aVersionConstructor blessingForVersion: aBlockOrString
!

description: aBlockOrString constructor: aVersionConstructor
    aVersionConstructor descriptionForVersion: aBlockOrString
!

postLoadDoIt: aSymbol constructor: aVersionConstructor
    aVersionConstructor postLoadDoItForVersion: aSymbol
!

preLoadDoIt: aSymbol constructor: aVersionConstructor
    aVersionConstructor preLoadDoItForVersion: aSymbol
!

repositories: aBlock constructor: aVersionConstructor
    aVersionConstructor repositoriesForVersion: aBlock
!

repository: anObject constructor: aVersionConstructor
    aVersionConstructor repositoryForVersion: anObject
!

repository: aString username: username password: password constructor: aVersionConstructor
    aVersionConstructor repositoryForVersion: aString username: username password: password
!

timestamp: aBlockOrStringOrDateAndTime constructor: aVersionConstructor
    aVersionConstructor timestampForVersion: aBlockOrStringOrDateAndTime
! !

!MetacelloVersionSpec methodsFor:'copying'!

postCopy

	super postCopy.
	blessing := blessing copy.
	description := description copy.
	author := author copy.
	timestamp := timestamp copy.
	
! !

!MetacelloVersionSpec methodsFor:'merging'!

mergeMap

	| map |
	map := super mergeMap.
	map at: #versionString put: versionString.
	map at: #blessing put: blessing.
	map at: #description put: description.
	map at: #author put: author.
	map at: #timestamp put: timestamp.
	map at: #preLoadDoIt put: preLoadDoIt.
	map at: #postLoadDoIt put: postLoadDoIt.
	^map
! !

!MetacelloVersionSpec methodsFor:'printing'!

configMethodOn: aStream for: spec selector: selector last: last indent: indent
	spec == nil
		ifTrue: [ ^ self ].
	aStream
		tab: indent;
		nextPutAll: 'spec ' , selector , ' [';
		cr.
	spec configMethodOn: aStream indent: indent + 1.
	aStream nextPutAll: ' ].'.
	last
		ifFalse: [ aStream cr ]
!

configMethodOn: aStream indent: indent

	self configMethodOn: aStream last: true indent: indent
!

configMethodOn: aStream last: last indent: indent
	| values lastIndex lastBlock |
	last
		ifTrue: [ 
			"need to calculate last statement with a value"
			values := {(self getBlessing).
			(self getDescription).
			(self getPreLoadDoIt).
			(self getPostLoadDoIt).
			(self getAuthor).
			(self getTimestamp)}.
			1 to: values size do: [ :index | 
				(values at: index) ~~ nil
					ifTrue: [ lastIndex := index ] ].
			lastBlock := [ :arg | arg = lastIndex ] ]
		ifFalse: [ lastBlock := [ :arg | false ] ].
	self
		configMethodValueOn: aStream
		for: self getBlessing
		selector: 'blessing:'
		last: (lastBlock value: 1)
		indent: indent.
	self
		configMethodValueOn: aStream
		for: self getDescription
		selector: 'description:'
		last: (lastBlock value: 2)
		indent: indent.
	self
		configMethodValueOn: aStream
		for: self getPreLoadDoIt
		selector: 'preLoadDoIt:'
		last: (lastBlock value: 3)
		indent: indent.
	self
		configMethodValueOn: aStream
		for: self getPostLoadDoIt
		selector: 'postLoadDoIt:'
		last: (lastBlock value: 4)
		indent: indent.
	self
		configMethodValueOn: aStream
		for: self getAuthor
		selector: 'author:'
		last: (lastBlock value: 5)
		indent: indent.
	self
		configMethodValueOn: aStream
		for: self getTimestamp
		selector: 'timestamp:'
		last: (lastBlock value: 6)
		indent: indent
!

configMethodValueOn: aStream for: spec selector: selector last: last indent: indent
	| valuePrintString |
	spec == nil
		ifTrue: [ ^ self ].
	valuePrintString := spec value isSymbol
		ifTrue: [ '#' , spec value asString printString ]
		ifFalse: [ spec value printString ].
	aStream
		tab: indent;
		nextPutAll: 'spec ' , selector , ' ' , valuePrintString , '.'.
	last
		ifFalse: [ aStream cr ]
!

configSpawnMethodOn: aStream indent: indent

	self configMethodValueOn: aStream for: self getBlessing selector: 'blessing:' last: false indent: indent.
	self configMethodValueOn: aStream for: self getAuthor selector: 'author:' last: false indent: indent.
	self configMethodValueOn: aStream for: self getTimestamp selector: 'timestamp:' last: false indent: indent.

!

label

	^self versionString, ' [', self projectLabel, ']'
! !

!MetacelloVersionSpec methodsFor:'private'!

createVersion

	^self versionClass fromSpec: self
!

versionClass

	^MetacelloVersion
!

versionNumber
    ^ self project versionNumberClass fromString: self versionString
! !

!MetacelloVersionSpec methodsFor:'querying'!

postLoadDoIt

	^postLoadDoIt
!

preLoadDoIt

	^preLoadDoIt
!

versionString
	versionString == nil ifTrue: [ ^'' ].
	^ versionString
! !

!MetacelloVersionSpec methodsFor:'testing'!

isPartiallyCurrent: notLoadedMatters useEquality: useEquality

	self subclassResponsibility
!

isPossibleBaseline
    self subclassResponsibility
! !

!MetacelloVersionSpec class methodsFor:'documentation'!

version_SVN
    ^ '$Id::                                                                                                                        $'
! !