mercurial/HGCommandParser.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 05 Dec 2012 18:09:53 +0000
changeset 134 565c8bd9c9e8
parent 115 b1ed2d29054b
child 135 c74b92e6a2f8
permissions -rw-r--r--
Added children support to changesets. HGChangeset>>children returns all child changesets of given one. This can be used to figure out newer changesets.

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

Object subclass:#HGCommandParser
	instanceVariableNames:'stream'
	classVariableNames:''
	poolDictionaries:''
	category:'SCM-Mercurial-Internal'
!


!HGCommandParser class methodsFor:'instance creation'!

on: aStringOrStream
    | stream |

    stream := aStringOrStream isStream 
                ifTrue:[aStringOrStream]
                ifFalse:[aStringOrStream readStream].

    ^self new stream: stream

    "Created: / 23-10-2012 / 11:07:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-11-2012 / 16:36:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGCommandParser class methodsFor:'templates'!

templateHeads
    ^'{rev}:{node}\n'

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

templateLog
    ^
'{rev}:{node}
{branch}
{parents}
{children}
{author}
{date|isodate}
{desc}
**EOE**
'

    "Created: / 12-11-2012 / 23:06:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 05-12-2012 / 17:21:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGCommandParser methodsFor:'accessing'!

stream
    ^ stream
!

stream:something
    stream := something.
! !

!HGCommandParser methodsFor:'error reporting'!

error: aString
    <context: #return>
    <resource: #skipInDebuggersWalkBack>

    HGCommandParseError raiseWith:#error: errorString:aString

    "Created: / 14-11-2012 / 19:59:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGCommandParser methodsFor:'parsing'!

parseBranches
    "Parse output of 'hg branches' command. Return collection
     of orphaned HGBranch"

    | branches |

    branches := OrderedCollection new.
    [ stream atEnd ] whileFalse:[
        branches add: self parseBranchesEntry
    ].
    ^branches

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

parseBranchesEntry
    | branch |

    branch := HGBranch new.
    branch setName: self parseName.

    stream skipSeparators.
    self parseNodeId.
    stream peek == Character space ifTrue:[
        stream next.
        stream peek == $( ifFalse:[self error:'''('' expected but ''' , stream peek , ''' found'].
        stream next.
        stream peek == $i ifTrue:[
            self expect:'inactive)'.
            branch setActive: false.
        ] ifFalse:[
            stream peek == $c ifTrue:[
                self expect:'closed)'.
                branch setClosed: true.
            ] ifFalse:[
                self error:'Unexpected branch attribute (only ''closed'' and ''inactive'' supported)'''
            ]
        ].
    ].
    self expectLineEnd.
    ^branch

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

parseDate
    | ts |
    ts := Timestamp readIso8601FormatFrom:stream.
    (stream peek == $+ or:[stream peek == $-]) ifFalse:[
        self error:'Timezone expected, ' , stream peek , ' found'
    ].
    stream next.
    4 timesRepeat:[
        ('0123456789' includes: stream peek) ifFalse:[
            self error:'Timezone expected, ' , stream peek , ' found'
        ].
        stream next.
    ].
    ^ts

    "Created: / 13-11-2012 / 10:22:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-11-2012 / 17:28:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseInteger
    "Parses integer from stream and returns it"

    ^Integer readFrom: stream onError:[self error: 'integer value expected']

    "
    (HGCommandParser on: '12 34' readStream) parseInteger; skipSeparators; parseInteger
    "

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

parseLog
    "Parse output of 'hg log' command, assuming the template given
     was HGCommandParser templateLog. Return a list of HGRevision."

    | revs |

    revs := OrderedCollection new.
    [ stream atEnd ] whileFalse:[
        | rev |

        rev := self parseLogEntry.
        revs add: rev.
    ].

    ^revs.

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

parseLogEntry
    "Parse single revision entry, assuming the template given
     was HGCommandParser templateLog. Return a HGRevision."

    | rev branches line message |

    rev := HGChangeset new.
    rev setId: self parseNodeId. self expectLineEnd.
    branches := self parseNameList. self expectLineEnd.
    rev setBranches: branches.
    rev setParent1Id: self parseNodeId. self expectSpace.
    rev setParent2Id: self parseNodeId. self expectSpace. self expectLineEnd.
    rev setChildren: self parseNodeIdList. self expectLineEnd.
    rev setAuthor: self nextLine.
    rev setTimestamp: self parseDate. self expectLineEnd.
    message := String streamContents:[:s|
        line := self nextLine.
        s nextPutAll: line.
        [ line := self nextLine . line = '**EOE**' ] whileFalse:[
            s cr.
            s nextPutAll: line
        ].
    ].
    rev setMessage: message.

    ^rev

    "Created: / 13-11-2012 / 09:45:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 05-12-2012 / 17:32:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseName
    ^String streamContents:[:out|
        [ stream peek isSeparator ] whileFalse:[
            out nextPut:stream next
        ]
    ].

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

parseNameList
    | list |

    stream atEnd ifTrue:[ ^#() ].
    stream peek isSeparator ifTrue:[ ^#() ].
    list := OrderedCollection new.
    list add: self parseName.
    [ stream atEnd not and:[stream peek == Character space]] whileTrue:[
        stream next. "/eat space.
        list add: self parseName.
    ].
    ^list.

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

parseNodeId
    "Parses node id from stream and returns it. Support both,
     short and full node ids"

    ^HGChangesetId readFrom: stream onError:[:msg|self error: msg]



    "
        (HGCommandParser on: '4:6f88e1f44d9eb86e0b56ca15e30e5d786acd83c7' readStream) parseNodeId

        Bad ones:

        (HGCommandParser on: '4:6f88e1f44d9eb86e0b56ca15e30e5d786acd' readStream) parseNodeId
        (HGCommandParser on: '4:6f88Z1f44d9eb86e0b56ca15e30e5d786acd83c7' readStream) parseNodeId

    "

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

parseNodeIdList
    "Parses node id list from stream and returns it. Support both,
     short and full node ids."

    | ids |

    stream atEnd ifTrue:[ ^ #() ].
    stream peek == Character cr ifTrue:[ ^ #() ].
    ids := OrderedCollection new.
    [ stream peek ~~ Character cr ] whileTrue:[
        ids add: self parseNodeId.
        stream peek == Character space ifTrue:[stream next].
    ].
    ^ids

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

!HGCommandParser methodsFor:'parsing - commands'!

parseCommandBranches
    "Parse output of 'hg branches' command. Return collection
     of orphaned HGBranch"

    ^self parseBranches

    "Created: / 27-11-2012 / 19:16:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 27-11-2012 / 20:21:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseCommandHeads
    "Parse output of 'hg heads' command, assuming the template given
     was HGCommandParser templateHeads. Return a list of HGChangesetId."

    | ids |

    ids := OrderedCollection new.
    [ stream atEnd ] whileFalse:[
        ids add: self parseNodeId. self expectLineEnd.
    ].
    ^ids

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

parseCommandLocate
    "Filenames are 0-byte separated. Yeah, Mercurial is easy
     to parse"

    | filenames zero |
    zero := Character codePoint: 0.
    filenames := OrderedCollection new.
    [ stream atEnd ] whileFalse:[
        | filename |

        filename := stream upTo: zero.
        "/ Workaround for Mercurial 2.3.x which includes trailing new line
        (filename size ~~ 1 or:[filename first ~~ Character cr]) ifTrue:[
            filenames add:  filename
        ]
    ].
    ^filenames.

    "Created: / 16-11-2012 / 22:35:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 17-11-2012 / 19:40:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseCommandLog
    "Parse output of 'hg log' command, assuming the template given
     was HGCommandParser templateLog. Return a list of HGChangeset."

    ^self parseLog

    "Created: / 13-11-2012 / 09:09:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 27-11-2012 / 21:24:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseCommandStatus
    | statusesAndPaths |
    statusesAndPaths := OrderedCollection new.
    [ stream atEnd ] whileFalse:[
        | status path |

        stream peek == Character space ifTrue:[
            statusesAndPaths last first"status" isAdded ifTrue:[
                stream next.
                self expectSpace.
                path := self nextLine.
                statusesAndPaths last at:1 put: (HGStatus copied source: path)
            ] ifFalse:[
                self error:'Malformed status output, status code expected, got space'
            ]
        ] ifFalse:[
            status := HGStatus forCode: self next.
            self expectSpace.
            path := self nextLine.
            statusesAndPaths add: { status . path }
        ].
    ].
    ^ statusesAndPaths

    "Created: / 23-10-2012 / 10:57:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-11-2012 / 01:09:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parseCommandVersion
    "Parse output of 'hg --version'"

    "
    Mercurial Distributed SCM (version 2.3.2)
    (see http://mercurial.selenic.com for more information)
    
    Copyright (C) 2005-2012 Matt Mackall and others
    This is free software; see the source for copying conditions. There is NO
    warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
    "

    | major minor revision |

    self 
        expect:'Mercurial'; skipSeparators;
        expect:'Distributed'; skipSeparators;
        expect:'SCM'; skipSeparators;
        expect:$(; skipSeparators;
        expect:'version'.

    major := self parseInteger.
    self expect:$..
    minor := self parseInteger.
    stream peek == $. ifTrue:[
        stream next.
        revision := self parseInteger.
    ].

    self skipSeparators.
    self expect:$).

    ^(Array with: major with: minor with: revision)

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

!HGCommandParser methodsFor:'parsing-utils'!

expect: aStringOrChar

    | c |
    aStringOrChar isCharacter ifTrue:[
        (stream atEnd or:[(c := stream next) ~= aStringOrChar]) ifTrue:[
            self error:('Expected ''%1'' got ''%2''.' bindWith: aStringOrChar with: c).
        ].
        ^self.
    ].
    aStringOrChar isString ifTrue:[
        aStringOrChar do:[:expected|
            (stream atEnd or:[(c := stream next) ~= expected]) ifTrue:[
                self error:('Expected ''%1''.' bindWith: aStringOrChar).
            ].
        ].
        ^self.
    ].

    self error:'Invalid expected value'.

    "Created: / 19-11-2012 / 20:08:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

expectLineEnd
    self expect: Character cr.

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

expectSpace
    self expect: Character space.

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

next
    ^stream next.

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

nextLine
    ^stream nextLine

    "Created: / 23-10-2012 / 11:05:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 09-11-2012 / 12:02:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

skipSeparators
    stream skipSeparators

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

!HGCommandParser class methodsFor:'documentation'!

version_HG

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

version_SVN
    ^ '§Id::                                                                                                                        §'
! !