mercurial/HGRevisionInfo.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 01 Feb 2013 12:02:22 +0000
changeset 210 54a73fa50d40
parent 133 013175ca84d5
child 335 7e19ab19148b
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' }"

Object subclass:#HGRevisionInfo
	instanceVariableNames:'changesetId className'
	classVariableNames:''
	poolDictionaries:''
	category:'SCM-Mercurial-StX'
!

!HGRevisionInfo 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 Mercurial-specific VersionInfo.

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

    [see also:]
        VersionInfo
        CVSVersionInfo
"
! !

!HGRevisionInfo class methodsFor:'instance creation'!

readFrom: aStringOrStream onError: aBlock
    | s id |

    s := aStringOrStream readStream.
    s skipSeparators.
    s peek ~~ $$ ifTrue:[^aBlock value].
    s next.
    s skipSeparators.
    s peek == $H ifTrue:[
        "Some rubbish $Header$?"
        (s next: 6) ~= 'Header' ifTrue:[^aBlock value].
        id := HGChangesetId null.
    ] ifFalse:[
        (s next: 10) ~= 'Changeset:' ifTrue:[^aBlock value].
        s skipSeparators.
        s peek == $< ifTrue:[
            "/Not expanded...
            id := HGChangesetId null.
        ] ifFalse:[
            id := HGChangesetId fromHexString: (s next: 40).    
        ].
    ].
    ^self new changesetId: id

    "Created: / 20-11-2012 / 00:33:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-12-2012 / 13:17:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGRevisionInfo methodsFor:'accessing'!

at:aKey
    "backward compatible dictionary-like accessing"

    (self respondsTo:aKey) ifTrue:[
        ^ self perform:aKey
    ].
    ^ self errorKeyNotFound:aKey

    "
     self new at:#binaryRevision
     self new at:#foo
    "

    "Modified: / 22-10-2008 / 20:23:31 / cg"
!

at:aKey ifAbsent:replacement
    "backward compatible dictionary-like accessing"

    (self respondsTo:aKey) ifTrue:[
        ^ (self perform:aKey) ? replacement
    ].
    ^ replacement

    "
     self new at:#binaryRevision
     self new at:#foo ifAbsent:#bar
    "

    "Created: / 22-10-2008 / 20:19:42 / cg"
!

at:aKey put:value
    "backward compatible dictionary-like accessing"

    (self respondsTo:aKey) ifTrue:[
        self perform:(aKey,':') asSymbol with:value.
        ^ value "/ sigh
    ].
    ^ self errorKeyNotFound:aKey

    "
     self new at:#binaryRevision put:#bar
     self new at:#foo put:#bar
    "

    "Created: / 22-10-2008 / 20:20:54 / cg"
!

changesetId
    ^ changesetId
!

changesetId:anHGNodeId
    changesetId := anHGNodeId.
!

className
    ^ className
!

className:something
    className := something.
! !

!HGRevisionInfo methodsFor:'accessing-properties'!

author
    ^ self user

    "Created: / 21-12-2011 / 23:09:54 / cg"
!

binaryRevision
    ^ changesetId printString

    "Modified: / 20-11-2012 / 10:26:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

binaryRevision: aString

    "Created: / 20-11-2012 / 10:15:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

date
    ^ nil

    "Modified: / 20-11-2012 / 10:26:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileName
    | cls fn |

    className isNil ifTrue:[ ^ nil ].
    cls := Smalltalk at: className.
    cls notNil ifTrue:[
        fn := className , '.' , (cls programmingLanguage sourceFileSuffix)
    ] ifFalse:[
        fn := className , '.st'
    ].
    (fn includes: $:) ifTrue:[fn replaceAll:$: with:$_].
    ^fn.

    "Modified: / 04-12-2012 / 12:03:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

repositoryPathName

    ^ self fileName

    "Modified: / 20-11-2012 / 10:03:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

revision
    ^ changesetId printString

    "Modified: / 20-11-2012 / 10:15:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

time
    ^ nil

    "Modified: / 20-11-2012 / 10:15:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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

    ^ nil "Not known"

    "Modified: / 23-11-2011 / 13:54:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

user
    ^ nil

    "Modified: / 20-11-2012 / 10:15:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGRevisionInfo methodsFor:'enumerating'!

keysAndValuesDo:aBlock
    self class instVarNames do:[:nm |
        aBlock value:(nm asSymbol) value:(self perform:nm asSymbol)
    ].

    "Created: / 22-10-2008 / 20:48:08 / cg"
! !

!HGRevisionInfo methodsFor:'printing & storing'!

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

    super printOn:aStream.
    aStream nextPutAll:'['.
    className printOn:aStream.
    aStream space.
    changesetId printOn:aStream.
    aStream nextPutAll:']'.

    "Modified: / 30-11-2012 / 22:13:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGRevisionInfo methodsFor:'private'!

properties
    #(
        revision
        binaryRevision
        user
        date
        time
        fileName
        repositoryPathName
    )

    "Created: / 20-11-2012 / 10:01:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGRevisionInfo class methodsFor:'documentation'!

version_HG

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