mercurial/HGChangesetId.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 30 Nov 2012 23:56:15 +0000
changeset 116 b690f5845323
parent 115 b1ed2d29054b
child 118 5a8b78ad48ae
permissions -rw-r--r--
Class revision ID refactoring. HGChangesetId now prints itself using short form. Revision taken from version_HG method now consults binary revision (for there're nothing real in the string)

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

ByteArray variableByteSubclass:#HGChangesetId
	instanceVariableNames:'revno'
	classVariableNames:'NullId'
	poolDictionaries:''
	category:'SCM-Mercurial-Core'
!

!HGChangesetId class methodsFor:'documentation'!

documentation
"
    Represent a changeset id in Mercurial repository.

    !!!!!! WARNING !!!!!!

    Due to a stupid design here, DO NOT USE put it into hashed collections!!
    I have to change it later...

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

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!HGChangesetId class methodsFor:'instance creation'!

fromBytes: aByteArrayOrString

    | sz |

    sz := aByteArrayOrString size.
    (sz ~~ 20 and:[sz ~~ 6]) ifTrue:[
        self error:'Node ID has either 20 or 6 bytes (short form)'.
        ^nil.
    ].
    ^(self new: sz) replaceBytesFrom: 1 to: sz with: aByteArrayOrString startingAt: 1

    "Created: / 25-09-2012 / 21:00:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-11-2012 / 16:47:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fromString: aString
    ^self readFrom: aString readStream

    "Created: / 10-09-2012 / 10:49:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-11-2012 / 16:49:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

new
    ^self new: 20

    "Created: / 10-09-2012 / 10:42:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 19-10-2012 / 15:51:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

new: size
    (size ~~ 0 and:[size ~~ 20 and:[size ~~ 6]]) ifTrue:[
        self error: 'Size of HGNodeId must be either 20 bytes or 6 bytes (short form) or 0 (revno only)'.
        ^nil.
    ].
    ^super new: size

    "Created: / 10-09-2012 / 10:44:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-11-2012 / 21:24:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

readFrom: aStringOrStream 
    ^self readFrom: aStringOrStream onError:[:msg|self error:msg].

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

readFrom: aStringOrStream onError: aBlock
    "Parses node id from stream and returns it. Support both,
     short and full node ids"

    | stream c c2 sign revno hash short |

    stream := aStringOrStream readStream.
    stream peek == $- ifTrue:[        
        stream next.
        sign := -1.
    ] ifFalse:[
        sign := 1.
    ].

    "/ Read revno...
    revno := 0.
    [ (c := stream peek) == $: ] whileFalse:[
        c isDigit ifFalse:[
            self error:'Digit ([0-9]) expected but ', c , 'found'.
        ].
        revno := (revno * 10) + c digitValue.
        stream next.
    ].
    stream next. "/eat :
    revno := revno * sign.

    "/ Read hash
    hash := ByteArray new: 20.
    short := true.
    1 to: 6 do:[:i|
        stream atEnd ifTrue:[
            aBlock valueWithOptionalArgument:'Unexpected end of stream, hex digit expected'.
        ].
        c := stream peek.
        c isHexDigit ifFalse:[
            aBlock valueWithOptionalArgument:'Hex digit ([0-9a-z]) expected but ', c , ' found'.
        ].
        stream next.
        stream atEnd ifTrue:[
            aBlock valueWithOptionalArgument:'Unexpected end of stream, hex digit expected'.
        ].
        c2 := stream peek.
        c2 isHexDigit ifFalse:[
            aBlock valueWithOptionalArgument:'Hex digit ([0-9a-z]) expected but ', c , ' found'.
        ].
        hash at:i put: (c digitValue << 4) | c2 digitValue.
        stream next.
    ].
    (stream atEnd not and:[stream peek isHexDigit]) ifTrue:[
        "/OK, full 40-char node id
        short := false.
        7 to: 20 do:[:i|
            stream atEnd ifTrue:[
                aBlock valueWithOptionalArgument:'Unexpected end of stream, hex digit expected'.
            ].
                        c := stream peek.
            c isHexDigit ifFalse:[
                aBlock valueWithOptionalArgument:'Hex digit ([0-9a-z]) expected but ', c , ' found'.
            ].
            stream next.
            stream atEnd ifTrue:[
                aBlock valueWithOptionalArgument:'Unexpected end of stream, hex digit expected'.
            ].
            c2 := stream peek.
            c2 isHexDigit ifFalse:[
                aBlock valueWithOptionalArgument:'Hex digit ([0-9a-z]) expected but ', c , ' found'.
            ].
            hash at:i put: (c digitValue << 4) + c2 digitValue.
            stream next.
        ].
    ].
    (revno == -1) ifTrue:[
        (hash = #[0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0] 
            or:[hash = #[0 0 0 0 0 0]]) ifTrue:[
            ^self null
        ].
    ].
    short ifTrue:[
        ^(HGChangesetId new: 6)
            revno: revno;
            replaceBytesFrom: 1 to: 6 with: hash startingAt: 1;
            yourself
    ] ifFalse:[
        ^(HGChangesetId fromBytes: hash) revno: revno.
    ]

    "
    HGNodeId fromString:'4:6f88e1f44d9eb86e0b56ca15e30e5d786acd83c7'

    Bad ones:

    HGNodeId fromString:'4:6f88e1f44d9eb86e0b56ca15e30e5d786acd' 
    HGNodeId fromString:'4:6f88Z1f44d9eb86e0b56ca15e30e5d786acd83c7' 
    "

    "Created: / 13-11-2012 / 16:49:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangesetId class methodsFor:'accessing'!

null
    NullId isNil ifTrue:[
        NullId := self new.
        NullId revno: -1
    ].
    ^NullId

    "
        HGChangesetId null
    "

    "Created: / 19-10-2012 / 15:51:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 30-11-2012 / 22:00:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangesetId methodsFor:'accessing'!

revno
    ^ revno

    "Created: / 13-11-2012 / 09:52:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-11-2012 / 22:05:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

revno:anInteger
    revno := anInteger.
! !

!HGChangesetId methodsFor:'comparing'!

= anotherId

    self class == anotherId class ifFalse:[ ^ false].
    (self size == 0 or:[anotherId size == 0]) ifTrue:[
        ^(self revno == anotherId revno and:[ self revno ~~ -2 ])
    ].
    self size == anotherId size ifTrue:[
        ^super = anotherId
    ].
    "One of them must be short, another long"
    1 to: 6 do:[:i|
        (self at:i) ~~ (anotherId at:i) ifTrue:[ ^ false ].
    ].
    ^true

    "Created: / 13-11-2012 / 17:37:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-11-2012 / 21:39:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

hash
    ^self size > 0 
        ifTrue:[self computeXorHashFrom:1 to:6]
        ifFalse:[revno hash].

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

!HGChangesetId methodsFor:'converting'!

asHGChangesetId
    ^ self

    "Created: / 16-11-2012 / 21:22:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

asString
    ^self printString

    "Created: / 17-11-2012 / 01:08:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangesetId methodsFor:'printing & storing'!

displayOn:aStream

    ^self printOn: aStream

    "Created: / 13-11-2012 / 09:55:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-11-2012 / 22:01:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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

    | rn |

    rn := self revno.
    rn notNil ifTrue:[
        rn printOn: aStream.
        self isEmpty ifTrue:[ ^ self ].
        aStream nextPut: $:.
    ].

    aStream nextPutAll: (self copyTo: 6) hexPrintString asLowercase

    "Modified: / 30-11-2012 / 23:42:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangesetId methodsFor:'queries'!

hasHashOnly
    ^revno isNil

    "Created: / 16-11-2012 / 21:54:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

hasRevnoOnly
    ^self size == 0

    "Created: / 16-11-2012 / 21:54:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGChangesetId class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '§Id::                                                                                                                        §'
! !