MCPackage.st
author Claus Gittinger <cg@exept.de>
Sun, 04 Dec 2011 15:53:25 +0100
changeset 542 0a74443b8b71
parent 441 051b9184d951
child 660 9fee0266bf4d
permissions -rw-r--r--
changed: #packageInfo category of:

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

Object subclass:#MCPackage
	instanceVariableNames:'name'
	classVariableNames:''
	poolDictionaries:''
	category:'Monticello-Base'
!


!MCPackage class methodsFor:'as yet unclassified'!

named: aString
	^ self new name: aString
! !

!MCPackage methodsFor:'accessing'!

name
	^ name
!

name: aString
	name := aString
! !

!MCPackage methodsFor:'comparing'!

= other
	^ other species = self species and: [other name sameAs: name]
!

hash
	^ name asLowercase hash
! !

!MCPackage methodsFor:'operations'!

snapshot
	| packageInfo definitions categories |
	packageInfo := self packageInfo.
	definitions := OrderedCollection new.
	categories := packageInfo systemCategories.
	categories isEmpty ifFalse: [ definitions add: (MCOrganizationDefinition categories: categories) ].
	packageInfo methods do: [:ea | definitions add: ea asMethodDefinition] displayingProgress: 'Snapshotting methods...'.
	(packageInfo respondsTo: #overriddenMethods) ifTrue:
		[packageInfo overriddenMethods
			do: [:ea | definitions add:
					(packageInfo changeRecordForOverriddenMethod: ea) asMethodDefinition]
			displayingProgress: 'Searching for overrides...'].
	packageInfo classes do: [:ea | definitions addAll: ea classDefinitions] displayingProgress: 'Snapshotting classes...'.
	(packageInfo respondsTo: #hasPreamble) ifTrue: [
		packageInfo hasPreamble ifTrue: [definitions add: (MCPreambleDefinition from: packageInfo)].
		packageInfo hasPostscript ifTrue: [definitions add: (MCPostscriptDefinition from: packageInfo)].
		packageInfo hasPreambleOfRemoval ifTrue: [definitions add: (MCRemovalPreambleDefinition from: packageInfo)].
		packageInfo hasPostscriptOfRemoval ifTrue: [definitions add: (MCRemovalPostscriptDefinition from: packageInfo)]]. 
	^ MCSnapshot fromDefinitions: definitions

!

unload
	^ self workingCopy unload
! !

!MCPackage methodsFor:'printing & storing'!

printOn: aStream
	super printOn: aStream.
	aStream
		nextPut: $(;
		nextPutAll: name;
		nextPut: $)
!

storeOn: aStream
	aStream
		nextPutAll: 'MCPackage';
		space; nextPutAll: 'named: '; store: name.
! !

!MCPackage methodsFor:'queries'!

hasWorkingCopy
	^ MCWorkingCopy registry includesKey: self
!

packageInfo

    (Smalltalk allProjectIDs includes: name) ifTrue:[
        ^ MCStXPackageInfo named: name
    ] ifFalse:[
        ^ PackageInfo named: name
    ]

    "Modified: / 23-08-2011 / 13:31:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-12-2011 / 15:53:22 / cg"
!

workingCopy
	^ MCWorkingCopy forPackage: self.
! !

!MCPackage class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCPackage.st,v 1.9 2011-12-04 14:53:25 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCPackage.st,v 1.9 2011-12-04 14:53:25 cg Exp $'
!

version_SVN
    ^ '§Id: MCPackage.st 5 2010-08-29 07:30:29Z vranyj1 §'
! !