core/MetacelloProject.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 18 Sep 2012 13:10:10 +0000
changeset 14 f01fe37493e9
parent 11 d354ac2af7ec
child 16 25ac697dc747
permissions -rw-r--r--
- MetacelloProjectSpecForLoad added: #version_SVN - MetacelloRemoveMemberSpec added: #version_SVN - MetacelloValueHolderSpec added: #version_SVN - MetacelloProjectSpecGenerator added: #version_SVN - MetacelloPackagesSpec added: #version_SVN - MetacelloSemanticVersionNumber added: #version_SVN - MetacelloProjectSpecLoadError added: #version_SVN - MetacelloAddMemberSpec added: #version_SVN - MetacelloCannotUpdateReleasedVersionError added: #version_SVN - MetacelloMergeMemberSpec added: #version_SVN - MetacelloValidationFailure added: #version_SVN - MetacelloAllowProjectDowngrade added: #version_SVN - MetacelloVersion added: #version_SVN - MetacelloScriptApiExecutor added: #version_SVN - MetacelloScriptProjectSpecNotification added: #version_SVN - MetacelloAllowConflictingProjectUpgrade added: #version_SVN - MetacelloBaseConfiguration added: #version_SVN - MetacelloConflictingProjectError added: #version_SVN - MetacelloProjectRegistration added: #version_SVN - MetacelloValidationIssue added: #version_SVN - MetacelloSymbolicVersionDoesNotExistError added: #version_SVN - MetacelloClearStackCacheNotification added: #version_SVN - MetacelloVersionMethodSpec added: #version_SVN - MetacelloLookupProjectSpecForLoad added: #version_SVN - MetacelloSymbolicVersionNotDefinedError added: #version_SVN - MetacelloPackageSpecResolutionError added: #version_SVN - stx_goodies_metacello_core changed: #classNamesAndAttributes #extensionMethodNames #preRequisites - MetacelloValidationCriticalWarning added: #version_SVN - MetacelloStackCacheNotification added: #version_SVN - MetacelloVersionMethodSection added: #version_SVN - MetacelloProject added: #version_SVN - MetacelloErrorInProjectConstructionNotification added: #version_SVN - MetacelloGroupSpec added: #version_SVN - MetacelloAbstractConstructor added: #version_SVN - MetacelloConfigurationSpecGenerator added: #version_SVN - MetacelloVersionValidator added: #version_SVN - MetacelloSymbolicVersionMethodSpec added: #version_SVN - MetacelloScriptImageExecutor added: #version_SVN - MetacelloLockedProjectError added: #version_SVN - MetacelloProjectReferenceSpec added: #version_SVN - MetacelloLookupBaselineSpecForEnsureLoad added: #version_SVN - MetacelloToolBoxConstructor added: #version_SVN - MetacelloValidationError added: #version_SVN - MetacelloValidationWarning added: #version_SVN - MetacelloScriptGitHubDownloadNotification added: #version_SVN - MetacelloProjectSpecLoadedNotification added: #version_SVN - MetacelloScriptNotification added: #version_SVN - MetacelloScriptingError added: #version_SVN - MetacelloCopyMemberSpec added: #version_SVN - MetacelloScriptRegistryExecutor added: #version_SVN - MetacelloCleanNotification added: #version_SVN - MetacelloSpecLoader added: #version_SVN - MetacelloAllowProjectUpgrade added: #version_SVN - MetacelloValidationNotification added: #version_SVN - MetacelloScriptEnsureProjectLoadedForDevelopment added: #version_SVN - MetacelloScriptExecutor added: #version_SVN - MetacelloSpec added: #version_SVN - MetacelloCleanLoadAndTestsNotification added: #version_SVN - MetacelloMemberSpec added: #version_SVN - MetacelloProjectSpecLoadConflict added: #version_SVN - MetacelloResolveProjectUpgrade added: #version_SVN - MetacelloGenericProjectSpec added: #version_SVN - MetacelloMethodSpec added: #version_SVN - MetacelloVersionConstructor added: #version_SVN - MetacelloVersionDefinitionError added: #version_SVN - MetacelloBaselineConstructor added: #version_SVN - MetacelloScriptEngine added: #version_SVN - MetacelloUseUpgradeError added: #version_SVN - MetacelloSymbolicVersionSpec added: #version_SVN - MetacelloProjectSpec added: #version_SVN - MetacelloVersionDoesNotExistError added: #version_SVN - MetacelloMethodSectionPath added: #version_SVN - MetacelloCleanLoadNotification added: #version_SVN - MetacelloSkipDirtyPackageLoad added: #version_SVN - MetacelloPlatform added: #version_SVN changed: #createRepository: - MetacelloLookupProjectSpec added: #version_SVN - MetacelloMethodSection added: #version_SVN - MetacelloProjectRegistry added: #version_SVN - MetacelloMemberListSpec added: #version_SVN - MetacelloVersionSpec added: #version_SVN - MetacelloAbstractVersionConstructor added: #version_SVN - MetacelloVersionNumber added: #version_SVN - MetacelloAbstractPackageSpec added: #version_SVN - MetacelloBaselineSpecGenerator added: #version_SVN - extensions ...

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

Object subclass:#MetacelloProject
	instanceVariableNames:'versionMap symbolicVersionMap loader loaderClass loadType
		configuration projectAttributes'
	classVariableNames:''
	poolDictionaries:''
	category:'Metacello-Core-Model'
!


!MetacelloProject class methodsFor:'instance creation'!

new

	| inst |
	inst := self basicNew.
	^inst configuration: inst; yourself
!

on: aConfig

	^self basicNew configuration: aConfig; yourself
! !

!MetacelloProject methodsFor:'accessing'!

configuration
	^ configuration
!

configuration: anObject
	configuration := anObject
!

defaultBlessing

	^#release
!

label

	^self configuration class name
!

loadType
	"#atomic or #linear"

	loadType == nil ifTrue: [ ^#atomic ].
	^loadType
!

loadType: aSymbol
	"#atomic or #linear"

	loadType := aSymbol
!

map
	versionMap ifNil: [ ^ Dictionary new ].
	^ versionMap
!

map: aDictionary

	versionMap := aDictionary
!

project

	^self
!

symbolicVersionMap

	^symbolicVersionMap
				
				
!

symbolicVersionMap: aDictionary

	symbolicVersionMap := aDictionary
				
				
! !

!MetacelloProject methodsFor:'loading'!

load: aVersionString

	^(self version: aVersionString) load
! !

!MetacelloProject methodsFor:'printing'!

printOn: aStream
	| label |
	self configuration class printOn: aStream.
	aStream nextPut: $(.
	self versions
		do: [ :vrsn | 
			aStream nextPutAll: vrsn versionString.
			vrsn spec ~~ nil
				ifTrue: [ 
					(label := vrsn spec projectLabel) isEmpty
						ifFalse: [ aStream nextPutAll: ' [' , label , ']' ] ].
			aStream
				nextPut: $,;
				space ].
	aStream nextPut: $)
! !

!MetacelloProject methodsFor:'private'!

attributes

	^(OrderedCollection with: #common)
		addAll: self platformAttributes;
		yourself
!

defaultPlatformAttributes

	^ MetacelloPlatform current defaultPlatformAttributes
!

excludeFromLatestVersion

	^#(development broken baseline)
!

platformAttributes

	 ^self projectPlatformAttributes
!

pragmaKeywords

	^#(version:attribute: blessing:attribute: description:attribute: required:attribute: groups:attribute: doits:attribute:)
!

projectAttributes

	projectAttributes ~~ nil ifTrue: [ ^projectAttributes ].
	^#()
!

projectAttributes: aList

	projectAttributes := aList
!

projectPlatformAttributes

	| list aBlock |
	list := OrderedCollection new.
	(aBlock := self projectAttributes) ~~ nil 
		ifTrue: [ list addAll: aBlock value ].
	^self defaultPlatformAttributes, list
!

sortedAndFilteredVersions

		^(self map values asArray sort: [:a :b | a >= b ]) select: [:vrsn | (#(broken baseline) includes: vrsn blessing) not ].
! !

!MetacelloProject methodsFor:'spec classes'!

defaultLoaderClass

	^MetacelloSpecLoader
!

groupSpec

	^self groupSpecClass for: self
!

groupSpecClass

	^MetacelloGroupSpec
!

loader

	^loader
!

loader: aLoader

	loader := aLoader
!

loaderClass

	loaderClass == nil ifTrue: [ loaderClass := self defaultLoaderClass ].
	^loaderClass
!

loaderClass: aMetacelloSpecLoader

	loaderClass := aMetacelloSpecLoader
!

packagesSpec

	^self packagesSpecClass for: self
!

packagesSpecClass

	^MetacelloPackagesSpec
!

projectReferenceSpec

	^self projectReferenceSpecClass for: self
!

projectReferenceSpecClass

	^MetacelloProjectReferenceSpec
!

projectSpec

	^self projectSpecClass for: self
!

projectSpecClass

	^self subclassResponsibility
!

valueHolderSpec

	^self valueHolderSpecClass for: self
!

valueHolderSpecClass

	^MetacelloValueHolderSpec
!

versionSpec

	^self versionSpecClass for: self
!

versionSpecClass

	^MetacelloVersionSpec
! !

!MetacelloProject methodsFor:'versions'!

bleedingEdge

	^self version: #bleedingEdge
!

currentVersion
	| cacheKey cv |
	cacheKey := self configuration class.
	^ MetacelloPlatform current
		stackCacheFor: #currentVersion
		at: cacheKey
		doing: [ :cache | 
			cv := self currentVersionAgainst: nil.
			^ cache at: cacheKey put: cv ]
!

currentVersionAgainst: resolvedPackageAndProjectNames
	| cacheKey |
	cacheKey := resolvedPackageAndProjectNames isNil
		ifTrue: [ Array with: self configuration class with: nil ]
		ifFalse: [ Array with: self configuration class with: (resolvedPackageAndProjectNames sort: [ :a :b | a <= b ]) ].
	^ MetacelloPlatform current
		stackCacheFor: #currentVersionAgainst:
		at: cacheKey
		doing: [ :cache | 
			| cv versions latestSomethingLoaded |
			cv := nil.
			versions := self sortedAndFilteredVersions.
			versions
				do: [ :version | 
					| status matchBlock |
					status := resolvedPackageAndProjectNames isNil
						ifTrue: [ version spec isPartiallyCurrent ]
						ifFalse: [ version spec isPartiallyCurrentAgainst: resolvedPackageAndProjectNames ].
					matchBlock := [ :matchStatus | 
					cv := version copy.
					cv versionStatus: matchStatus.
					^ cache at: cacheKey put: cv ].
					status isAllLoadedToSpec: matchBlock.
					status isLoadedToSpec: matchBlock.
					status isLoadedMatchConstraints: matchBlock.
					status
						isSomethingLoaded: [ :matchStatus | 
							latestSomethingLoaded isNil
								ifTrue: [ 
									cv := version copy.
									cv versionStatus: matchStatus.
									latestSomethingLoaded := cv ] ] ].
			latestSomethingLoaded ifNotNil: [ ^ cache at: cacheKey put: latestSomethingLoaded ].
			^ cache at: cacheKey put: nil ]
!

development

	^self version: #development
!

hasVersion: versionString

	self version: versionString ifAbsent: [ ^false ].
	^true
!

lastVersion

	| coll |
	coll := (self map values asArray sort: [:a :b | a <= b ]) asOrderedCollection.
	coll isEmpty ifTrue: [ ^nil ].
	^coll last
!

latestVersion

	| excluded |
"	self deprecated: 'Please use #stableVersion instead.'.
"	self flag: 'deprecate after version 1.0'.
	excluded := self excludeFromLatestVersion.
	^(self map values select: [:version |  
		(excluded includes: version blessing) not ]) detectMax: [:version | version ]
!

latestVersion: blessing

	^(self map values select: [:version | blessing = version blessing ]) detectMax: [:version | version ]
!

latestVersionMatching: versionPatternString
	"Answer whether the version number of the receiver matches the given pattern string.

	 A Metacello version number is made up of version sequences delimited by the characters $. and $-.
	 The $. introduces a numeric version sequence and $- introduces an alphanumeric version sequence.
	 
	 A version pattern is made up of version pattern match sequences. also delimited by the characters $. 
	 and $-.. Each pattern match sequence is tested against the corresponding version sequence of the 
	 receiver, using the 'standard' pattern matching rules. All sequences must answer true for a match.
	
	 The special pattern sequence '?' is a match for the corresponding version sequence and all subsequent 
	 version sequences. '?' as the version pattern matches all versions. No more version pattern 
	 sequences are permitted once the '?' sequence is used. If used, it is the last version pattern
	 sequence."

	^self 
		latestVersionMatching: versionPatternString 
		includedBlessings: #()
		excludedBlessings: self excludeFromLatestVersion
!

latestVersionMatching: versionPatternString excludedBlessings: excluded

	^self 
		latestVersionMatching: versionPatternString 
		includedBlessings: #()
		excludedBlessings: excluded
!

latestVersionMatching: versionPatternString includedBlessings: included

	^self 
		latestVersionMatching: versionPatternString 
		includedBlessings: included
		excludedBlessings: self excludeFromLatestVersion
!

latestVersionMatching: versionPatternString includedBlessings: included excludedBlessings: excludedBlessings

	| excluded |
	excluded := excludedBlessings asSet copy.
	excluded removeAllFoundIn: included.
	^(self map values select: [:version |
		(included isEmpty or: [ included includes: version blessing ]) 
			and: [ (excluded includes: version blessing) not 
				and: [ version versionNumber match: versionPatternString ]]])
		detectMax: [:version | version ]
!

stableVersion

	^self version: #stable
!

symbolicVersionSymbols

	^self symbolicVersionMap keys asArray sort: [:a :b | a <= b ]
!

version: aVersionString
	| vrsn |
	aVersionString isSymbol
		ifTrue: [ 
			| symbolicVersionString |
			symbolicVersionString := self symbolicVersionMap
				at: aVersionString
				ifAbsent: [ (MetacelloSymbolicVersionDoesNotExistError project: self project versionString: aVersionString) signal ].
			symbolicVersionString == #notDefined
				ifTrue: [ (MetacelloSymbolicVersionNotDefinedError project: self project versionString: aVersionString) signal ].
			^ self map
				at: symbolicVersionString
				ifAbsent: [ (MetacelloSymbolicVersionDoesNotExistError project: self project versionString: symbolicVersionString) signal ] ].
	^ self map
		at: aVersionString
		ifAbsent: [ (MetacelloVersionDoesNotExistError project: self project versionString: aVersionString) signal ]
!

version: aVersionString ifAbsent: aBlock

	^[ self version: aVersionString ] on: MetacelloVersionDoesNotExistError do: [:ex | aBlock value ].
!

versions

	^self map values asArray sort: [:a :b | a <= b ]
! !

!MetacelloProject class methodsFor:'documentation'!

version_SVN
    ^ '$Id::                                                                                                                        $'
! !