MCVersionInfo.st
author Claus Gittinger <cg@exept.de>
Mon, 14 May 2018 02:21:18 +0200
changeset 1048 582b3a028cbc
parent 700 2f3535bb1260
child 1003 0ebeea1cdeeb
permissions -rw-r--r--
#FEATURE by cg class: MCMethodDefinition changed: #postloadOver:

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

MCAncestry subclass:#MCVersionInfo
	instanceVariableNames:'id name message date time author'
	classVariableNames:''
	poolDictionaries:''
	category:'SCM-Monticello-Versioning'
!

MCVersionInfo comment:'Adds to the record of ancestry, other identifying details.'
!


!MCVersionInfo class methodsFor:'as yet unclassified'!

name: vName id: id message: message date: date time: time author: author ancestors: ancestors
	^ self 
		name: vName
		id: id
		message: message
		date: date
		time: time
		author: author
		ancestors: ancestors
		stepChildren: #()
!

name: vName id: id message: message date: date time: time author: author ancestors: ancestors stepChildren: stepChildren
	^ self new
		initializeWithName: vName
		id: id
		message: message
		date: date
		time: time
		author: author
		ancestors: ancestors
		stepChildren: stepChildren
! !

!MCVersionInfo methodsFor:'accessing'!

message
	^ message ifNil: ['']
!

name
	^ name ifNil: ['<working copy>']
!

summary
	^ String streamContents:
		[:s |
		s
			nextPutAll: self summaryHeader; cr; cr;
			nextPutAll: self message.
		]
!

summaryHeader
        ^ String streamContents:
                [:s |
                s
                        nextPutAll: 'Name: '; nextPutAll: self name; cr.
                date ifNotNil:
                        [s
                                nextPutAll: 'Author: '; nextPutAll: author; cr;
                                nextPutAll: 'Time: '; nextPutAll:  date asString, ', ', time asString; cr].
                id ifNotNil:
                        [s nextPutAll: 'UUID: '; nextPutAll: id printString; cr].
                s
                        nextPutAll: 'Ancestors: '; nextPutAll: self ancestorString.
                self stepChildren isEmpty ifFalse:
                        [s cr; nextPutAll: 'Backported From: '; nextPutAll: self stepChildrenString].
                ]

    "Modified: / 05-09-2011 / 09:07:31 / cg"
!

timeStamp
    Smalltalk isSmalltalkX ifTrue:[
        ^ Timestamp fromDate: date andTime: time
    ].
    ^ TimeStamp date: date time: time

    "Modified: / 02-12-2011 / 14:36:15 / cg"
!

timeString
	^ date asString, ', ', time asString
! !

!MCVersionInfo methodsFor:'comparing'!

= other
	^ other species = self species
		and: [other hasID: id]
!

hash
	^ id hash
! !

!MCVersionInfo methodsFor:'converting'!

asDictionary
	^ Dictionary new
		at: #name put: name;
		at: #id put: id;
		at: #message put: message;
		at: #date put: date;
		at: #time put: time;
		at: #author put: author;
		at: #ancestors put: (self ancestors collect: [:a | a asDictionary]);
		yourself
! !

!MCVersionInfo methodsFor:'initialize-release'!

initializeWithName: vName id: aUUID message: aString date: aDate time: aTime author: initials ancestors: aCollection stepChildren: stepCollection
	name _ vName.
	id _ aUUID.
	message _ aString.
	date _ aDate.
	time _ aTime.
	author _ initials.
	ancestors _  aCollection.
	stepChildren _ stepCollection
! !

!MCVersionInfo methodsFor:'pillaging'!

author
	^ author
!

date
	^ date
!

id
	^ id 
!

time
	^ time
! !

!MCVersionInfo methodsFor:'printing'!

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

!MCVersionInfo methodsFor:'private'!

hasID: aUUID
	^ id = aUUID
! !

!MCVersionInfo class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCVersionInfo.st,v 1.4 2012-09-11 21:30:28 cg Exp $'
! !