mercurial/HGChangeset.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 01 Feb 2013 12:02:22 +0000
changeset 210 54a73fa50d40
parent 193 ad31a280c0d4
child 212 8ec5884fba41
permissions -rw-r--r--
Added copyright notice.

"
 COPYRIGHT (c) 2012-2013 by Jan Vrany
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libscm/mercurial' }"

HGRepositoryObject subclass:#HGChangeset
	instanceVariableNames:'lazy id branches author timestamp message parent1 parent2 root
		changes'
	classVariableNames:'NullChangeset'
	poolDictionaries:''
	category:'SCM-Mercurial-Core'
!

!HGChangeset class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2012-2013 by Jan Vrany
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    A HGChangeset represent one changeset in Mercurial repository.

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]
        http://mercurial.selenic.com/wiki/UnderstandingMercurial

"
! !

!HGChangeset class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!HGChangeset class methodsFor:'accessing'!

null
    NullChangeset isNil ifTrue:[
        NullChangeset := self new.
        NullChangeset setId: HGChangesetId null.
    ].
    ^NullChangeset

    "
        HGChangesetId null
    "

    "Created: / 19-10-2012 / 15:51:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-01-2013 / 13:37:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangeset methodsFor:'accessing'!

/ name
    "Return an HGChangesetFile representing a file 
    (in root of the directory)"

    self ensureNotLazy.
    ^self construct: name

    "Created: / 16-11-2012 / 22:24:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-12-2012 / 00:34:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

author
    self ensureNotLazy.
    ^ author

    "Modified: / 16-12-2012 / 00:33:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

branch
    "Return branch (as HGBranch) in which this changeset is commited. It the changeset is commited in
     multiple branches, raise an error"

    self ensureNotLazy.
    branches size ~~ 1 ifTrue:[
        HGError 
            raiseSignalWith: self 
            errorString:('Changeset %1 commited in more than one branch' bindWith: id)
    ].
    ^self branches anElement

    "Created: / 27-11-2012 / 20:49:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-12-2012 / 00:34:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

branches
    "Return list of branches (as HGBranch) in which this changeset is commited"

    self ensureNotLazy.
    (branches anySatisfy:[:b|b isString]) ifTrue:[
        | all |

        all := repository branches.
        branches := branches collect:[:nm|all detect:[:b|b name = nm] ifNone:[HGNoSuchBranchError raiseSignalWith: nm errorString:'No such branch: ', nm]]
    ].
    ^branches.

    "Created: / 27-11-2012 / 20:40:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-12-2012 / 00:34:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

changes
    "Return a list of HGChange that describes differences against parent1 changeset"

    self ensureNotLazy.
    ^ changes

    "Created: / 05-12-2012 / 18:36:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-12-2012 / 00:34:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

children
    | ids |

    self ensureNotLazy.
    ids := HGCommand log
            workingDirectory: repository pathName;
            childrenOnly: true;
            revset: id revno printString;
            execute.
    self assert: ids size == 1.
    self assert: ids first first = id.
    ^ids first second collect:[:e|repository changesetWithId: e].

    "Created: / 05-12-2012 / 17:31:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-01-2013 / 16:17:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

construct: name
    "Return an HGChangesetFile representing a file 
    (in root of the directory)"

    self ensureNotLazy.    
    ^self root construct: name

    "Created: / 16-11-2012 / 22:25:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-12-2012 / 00:34:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

id
    ^ id

    "Modified: / 16-12-2012 / 00:34:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

message
    self ensureNotLazy.
    ^ message

    "Modified (format): / 16-12-2012 / 00:35:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parent1
    self ensureNotLazy.
    parent1 class == HGChangesetId ifTrue:[
        parent1 := repository changesetWithId: parent1
    ].
    ^parent1

    "Modified: / 16-12-2012 / 00:35:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parent2
    self ensureNotLazy.
    parent2 class == HGChangesetId ifTrue:[
        parent2 := repository changesetWithId: parent2
    ].
    ^parent2

    "Modified: / 16-12-2012 / 00:35:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

root
    "Return an HGChangesetFile represening the root of
     the changeset,i.e, root of the directory tree 
     represented by given changeset"

    | filenames |

    root notNil ifTrue:[ ^ root ].
    self ensureNotLazy.
    filenames := HGCommand locate
                    workingDirectory: repository pathName;
                    revision: id revno;
                    execute.
    root := HGChangesetFile new setChangeset: self name: ''.
    filenames do:[:each|root create: each].

    ^root.

    "Created: / 16-11-2012 / 22:26:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-12-2012 / 00:35:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

timestamp
    self ensureNotLazy.
    ^ timestamp

    "Modified: / 16-12-2012 / 00:35:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangeset methodsFor:'converting'!

asHGChangesetId
    ^self id

    "Created: / 14-01-2013 / 16:04:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangeset methodsFor:'enumerating'!

allChildrenDo: oneArgBlock
    "Evaluates given block for each child recursively."

    self childrenDo:[:e|
        oneArgBlock value: e.
        e allChildrenDo: oneArgBlock         
    ]

    "Created: / 05-12-2012 / 19:36:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

allParentsDo: oneArgBlock
    "Evaluates given block for each parent recursively."

    self parentsDo:[:e|
        oneArgBlock value: e.
        e allParentsDo: oneArgBlock         
    ]

    "Created: / 05-12-2012 / 19:36:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

childrenDo: oneArgBlock
    "Evaluates given block for each immediate child (i.e., does not
     recurse - use #allChildrenDo: to enmerate grand-children as well"

    self children do: oneArgBlock.

    "Created: / 05-12-2012 / 19:34:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parentsDo: oneArgBlock
    "Evaluates given block for each immediate parent (i.e., does not
     recurse - use #allParentsDo: to enmerate grand-parents as well"

    | p |

    p := self parent1.
    p notNil ifTrue:[oneArgBlock value:p].
    p := self parent2.
    p notNil ifTrue:[oneArgBlock value:p].

    "Created: / 05-12-2012 / 19:37:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangeset methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    "/ super initialize.   -- commented since inherited method does nothing
    lazy := true.

    "Modified: / 16-12-2012 / 00:33:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setAuthor: aString
    author := aString

    "Created: / 13-11-2012 / 10:23:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-11-2012 / 17:30:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setBranches: aCollection
    branches := aCollection.

    "Created: / 27-11-2012 / 20:25:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setChanges: aCollection
    changes := aCollection

    "Created: / 05-12-2012 / 18:36:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setId: anHGNodeId
    id := anHGNodeId

    "Created: / 13-11-2012 / 10:08:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setMessage: aString
    message := aString

    "Created: / 13-11-2012 / 10:23:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setNonLazy
    lazy := false.

    "Created: / 16-12-2012 / 00:37:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setParent1Id: anHGNodeId
    anHGNodeId ~~ HGChangesetId null ifTrue:[
        parent1 := anHGNodeId
    ]

    "Created: / 13-11-2012 / 10:23:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-11-2012 / 18:05:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setParent2Id: anHGNodeId
    anHGNodeId ~~ HGChangesetId null ifTrue:[
        parent2 := anHGNodeId
    ]

    "Created: / 13-11-2012 / 10:23:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-11-2012 / 18:05:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setSlotsFrom: otherChangeset
    "Fetches all instvars from given pre-initialized changeset"

    self class instVarNames withIndexDo:[:nm :i|
        (#(id root) includes: nm) ifFalse:[
            self instVarAt: i put: (otherChangeset instVarAt: i)
        ].        
    ]

    "Created: / 16-12-2012 / 00:28:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setTimestamp: aTimestamp
    timestamp := aTimestamp

    "Created: / 13-11-2012 / 17:24:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangeset methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation if the receiver to the argument, aStream"

    super printOn:aStream.
    aStream nextPutAll:'('.
    id printOn:aStream.
    aStream space.
    lazy ifTrue:[
        aStream nextPut:$L.
    ] ifFalse:[
        aStream nextPut:$N.
    ].
    aStream nextPutAll:')'.

    "Modified: / 22-01-2013 / 20:53:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangeset methodsFor:'private'!

ensureNotLazy
    | loaded |
    lazy ifFalse:[ ^ self ].
    loaded := repository changesetWithId: id into: self.
    "/just a defensive check
    self assert: loaded == self.

    "Created: / 16-12-2012 / 00:33:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-01-2013 / 16:40:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

loaded
    ^lazy not

    "Created: / 22-01-2013 / 16:02:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-01-2013 / 20:52:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangeset methodsFor:'testing'!

isHGChangeset
    ^true

    "Created: / 22-01-2013 / 13:38:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangeset class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
!

version_SVN
    ^ '§Id::                                                                                                                        §'
! !