MCDefinition.st
author Claus Gittinger <cg@exept.de>
Mon, 14 May 2018 02:21:18 +0200
changeset 1048 582b3a028cbc
parent 1040 8c397b8defca
permissions -rw-r--r--
#FEATURE by cg class: MCMethodDefinition changed: #postloadOver:

"{ Encoding: utf8 }"

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

"{ NameSpace: Smalltalk }"

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


!MCDefinition class methodsFor:'as yet unclassified'!

clearInstances

        Instances := nil

    "Modified: / 18-08-2009 / 10:14:13 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

instanceLike: aDefinition 

    Instances ifNil: [ Instances := WeakIdentitySet new ].
    Instances do:
        [:each|each = aDefinition ifTrue:[^each]].
    Instances add: aDefinition.
    ^aDefinition.

    "Instances := nil"

    "Modified: / 18-08-2009 / 10:18:15 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!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'!

< aMCMethodDefinition

    ^self <= aMCMethodDefinition
        and: [(self = aMCMethodDefinition) not]

    "Created: / 18-08-2009 / 10:25:23 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

<= other
	^ self sortKey <= other sortKey
!

= aDefinition
	^ self isRevisionOf: aDefinition
!

description
	self subclassResponsibility
!

fullTimeStamp
	^Timestamp current
!

hash
	^ self description hash
!

isRevisionOf: aDefinition
	^ (aDefinition isKindOf: MCDefinition) and: [aDefinition description = self description]
!

isSameRevisionAs: aDefinition
	^ self = aDefinition
!

sortKey
	self subclassResponsibility 
! !

!MCDefinition methodsFor:'converting'!

addChangesTo:aChangeSet
    "some MCDefinitions will result in multiple changes
     (i.e. ClassDefinitionChange might also generate a comment change).
     The default here is to add the one major change (which was also generated in the past).
     Warning: callers of asChange should change their mind and use this."

    aChangeSet add:self asChange
!

asChange
    "raise an error: must be redefined in concrete subclass(es)"

    ^ 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
!

isOverrideDefinition
    ^false

    "Created: / 08-11-2010 / 17:29:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MCDefinition class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^ '$Id$'
! !