mercurial/HGRepository.st
author vranyj1@bd9d3459-6c23-4dd9-91de-98eeebb81177
Wed, 14 Nov 2012 01:15:30 +0000
changeset 46 d5a192b11a1a
parent 40 e3699c0b00f9
child 54 66045198bfbc
permissions -rw-r--r--
- More Smalltalk/X support

"{ Package: 'stx:libscm/mercurial' }"

Object subclass:#HGRepository
	instanceVariableNames:'path wc changesets'
	classVariableNames:''
	poolDictionaries:''
	category:'SCM-Mercurial-Core'
!

HGRepositoryObject subclass:#Changesets
	instanceVariableNames:'changesets'
	classVariableNames:''
	poolDictionaries:''
	privateIn:HGRepository
!


!HGRepository class methodsFor:'instance creation'!

on: aStringOrFilename
    ^self new initializeOn: aStringOrFilename

    "Created: / 17-10-2012 / 13:30:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGRepository class methodsFor:'utilities'!

discover: aStringOrFilename
    "Find a Mercurial repository in given directory or super-directories
     and return it (as an instance of Filename). If no repository is found, 
     returns nil.

     Currently, it searches for presence of .hg directory"

    | f |
    f := aStringOrFilename.
    f isDirectory ifFalse:[
        f := f directory
    ].
    [ ( f / '.hg' ) exists ] whileFalse:[
        f isRootDirectory ifTrue:[ ^nil ].
        f := f directory.
    ].
    ^f

    "Created: / 13-11-2012 / 22:34:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-11-2012 / 00:02:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGRepository methodsFor:'accessing'!

path
    "Return path to the repository (directory with .hg store)"
    ^ path

    "Modified (comment): / 13-11-2012 / 18:18:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

workingCopy
    wc isNil ifTrue:[
	wc := HGWorkingCopy new setRepository: self.
    ].
    ^wc

    "Created: / 19-10-2012 / 15:42:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGRepository methodsFor:'accessing-changesets'!

changesetWithId: id
    ^changesets changesetWithId: id

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

!HGRepository methodsFor:'initialization'!

initializeOn: aStringOrFilename
    | p |

    p := aStringOrFilename asFilename.
    p exists ifFalse:[
        HGRepositoryError raiseSignal: 'Given path does not exists'.
        ^nil.
    ].
    p isDirectory ifFalse:[
        HGRepositoryError raiseSignal: 'Given path is not a directory'.
        ^nil.
    ].
    (p / '.hg') isDirectory ifFalse:[
        HGRepositoryError raiseSignal: 'Given path does not contain a repository (.hg subdir not found - try use #lookup:)'.
        ^nil.
    ].
    path := p.
    changesets := Changesets new setRepository: self.

    "Created: / 17-10-2012 / 13:35:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-11-2012 / 17:45:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGRepository::Changesets class methodsFor:'documentation'!

documentation
"
    A simple object to maintain and load changesets metadata lazily.

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

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!HGRepository::Changesets class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!HGRepository::Changesets methodsFor:'accessing'!

changesetWithId: anHGNodeId
    ^changesets at: anHGNodeId ifAbsent:[
        | cs |
        cs := HGCommand log
                    workingDirectory: repository path asString;
                    start: anHGNodeId printString;
                    execute.
        cs do:[:changeset|
            changeset setRepository: repository.
            changesets at: changeset id put: changeset.
        ].
        changesets at: anHGNodeId
    ]

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

!HGRepository::Changesets methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    "/ please change as required (and remove this comment)
    changesets := Dictionary new.

    "/ super initialize.   -- commented since inherited method does nothing

    "Modified: / 13-11-2012 / 18:00:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGRepository class methodsFor:'documentation'!

version_SVN
    ^ '$Id::                                                                                                                        $'
! !