MCDefinition.st
author Claus Gittinger <cg@exept.de>
Mon, 26 Oct 2009 16:25:27 +0100
changeset 145 a76be9988b5d
parent 47 6b10e4d5edc1
child 244 65b2143f1d94
permissions -rw-r--r--
more porting (but still unfinished)

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

Object subclass:#MCDefinition
	instanceVariableNames:''
	classVariableNames:'Instances'
	poolDictionaries:''
	category:'Monticello-Base'
!


!MCDefinition class methodsFor:'as yet unclassified'!

clearInstances
	WeakArray removeWeakDependent: Instances.
	Instances _ nil
!

instanceLike: aDefinition
        Smalltalk isSmalltalkX ifTrue:[
            Instances ifNil: [ Instances _ WeakIdentitySet new ].
            ^ (Instances like: aDefinition) ifNil: [Instances add: aDefinition]
        ].

        Instances ifNil: [ Instances _ WeakSet new ].
        ^ (Instances like: aDefinition) ifNil: [Instances add: aDefinition]
! !

!MCDefinition methodsFor:'accessing'!

provisions
	^ #()
!

requirements
	^ #()
! !

!MCDefinition methodsFor:'annotations'!

annotations
	^self annotations: Preferences defaultAnnotationRequests
!

annotations: requests
	"Answer a string for an annotation pane, trying to fulfill the annotation requests.
	These might include anything that
		Preferences defaultAnnotationRequests 
	might return. Which includes anything in
		Preferences annotationInfo
	To edit these, use:"
	"Preferences editAnnotations"

	^String streamContents: [ :s | self printAnnotations: requests on: s ].
!

printAnnotations: requests on: aStream
	"Add a string for an annotation pane, trying to fulfill the annotation requests.
	These might include anything that
		Preferences defaultAnnotationRequests 
	might return. Which includes anything in
		Preferences annotationInfo
	To edit these, use:"
	"Preferences editAnnotations"

	aStream nextPutAll: 'not yet implemented'
! !

!MCDefinition methodsFor:'comparing'!

< other
        ^ self sortKey < other sortKey
!

<= other
	^ self sortKey <= other sortKey
!

= aDefinition
	^ self isRevisionOf: aDefinition
!

description
	self subclassResponsibility
!

fullTimeStamp
	^TimeStamp current
!

hash
	^ self description hash
!

isRevisionOf: aDefinition
	^ aDefinition description = self description
!

isSameRevisionAs: aDefinition
	^ self = aDefinition
!

sortKey
	self subclassResponsibility 
! !

!MCDefinition methodsFor:'installing'!

load
	
!

loadOver: aDefinition
	self load
	
!

postload
!

postloadOver: aDefinition
	self postload
!

unload
! !

!MCDefinition methodsFor:'printing'!

printOn: aStream
	super printOn: aStream.
	aStream nextPutAll: '(', self summary, ')'
!

summary
	self subclassResponsibility 
! !

!MCDefinition methodsFor:'testing'!

isClassDefinition
	^false
!

isClassDefinitionExtension
	"Answer true if this definition extends the regular class definition"
	^false
!

isMethodDefinition
	^false
!

isOrganizationDefinition
	^false
! !

!MCDefinition class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDefinition.st,v 1.2 2009-10-26 15:25:27 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCDefinition.st,v 1.2 2009-10-26 15:25:27 cg Exp $'
! !