Baisc support for changesets (revision log)
authorvranyj1@bd9d3459-6c23-4dd9-91de-98eeebb81177
Tue, 13 Nov 2012 18:09:24 +0000
changeset 40 e3699c0b00f9
parent 39 10e693b3e034
child 41 543fb47189aa
Baisc support for changesets (revision log)
mercurial/HGChangeset.st
mercurial/HGCommand.st
mercurial/HGCommandParser.st
mercurial/HGCommandParserTests.st
mercurial/HGNodeId.st
mercurial/HGRepository.st
mercurial/HGRevision.st
mercurial/HGTests.st
mercurial/HGWorkingCopy.st
mercurial/Make.proto
mercurial/Make.spec
mercurial/abbrev.stc
mercurial/bc.mak
mercurial/libInit.cc
mercurial/mercurial.rc
mercurial/stx_libscm_mercurial.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/mercurial/HGChangeset.st	Tue Nov 13 18:09:24 2012 +0000
@@ -0,0 +1,122 @@
+"{ Package: 'stx:libscm/mercurial' }"
+
+HGRepositoryObject subclass:#HGChangeset
+	instanceVariableNames:'id branch author timestamp message parent1 parent2'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SCM-Mercurial-Core'
+!
+
+
+!HGChangeset class methodsFor:'instance creation'!
+
+new
+    "return an initialized instance"
+
+    ^ self basicNew initialize.
+! !
+
+!HGChangeset methodsFor:'accessing'!
+
+author
+    ^ author
+!
+
+id
+    ^ id
+!
+
+parent1
+    parent1 class == HGNodeId ifTrue:[
+        parent1 := repository changesetWithId: parent1
+    ].
+    ^parent1
+
+    "Modified: / 13-11-2012 / 18:04:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+parent2
+    parent2 class == HGNodeId ifTrue:[
+        parent2 := repository changesetWithId: parent2
+    ].
+    ^parent2
+
+    "Modified: / 13-11-2012 / 18:05:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+timestamp
+    ^ timestamp
+! !
+
+!HGChangeset methodsFor:'initialization'!
+
+initialize
+    "Invoked when a new instance is created."
+
+    "/ please change as required (and remove this comment)
+    "/ id := nil.
+    "/ user := nil.
+    "/ timestamp := nil.
+    "/ files := nil.
+    "/ message := nil.
+
+
+    "/ super initialize.   -- commented since inherited method does nothing
+
+    "Modified: / 19-10-2012 / 16:08:00 / 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>"
+!
+
+setBranch: aString
+    branch := aString
+
+    "Created: / 13-11-2012 / 10:16:10 / 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>"
+!
+
+setParent1Id: anHGNodeId
+    anHGNodeId ~~ HGNodeId 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 ~~ HGNodeId 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>"
+!
+
+setTimestamp: aTimestamp
+    timestamp := aTimestamp
+
+    "Created: / 13-11-2012 / 17:24:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGChangeset class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- a/mercurial/HGCommand.st	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/HGCommand.st	Tue Nov 13 18:09:24 2012 +0000
@@ -384,6 +384,24 @@
     "Modified: / 12-11-2012 / 22:38:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!HGCommand::log methodsFor:'accessing'!
+
+start
+    ^ start
+!
+
+start:something
+    start := something.
+!
+
+stop
+    ^ stop
+!
+
+stop:something
+    stop := something.
+! !
+
 !HGCommand::log methodsFor:'private'!
 
 argumentsCommandOn:stream
@@ -392,13 +410,15 @@
     stream nextPut:'--rev'.
     start isNil ifTrue:[
         self error:'No start revision given'.
-        stop notNil ifTrue:[
-            stream nextPut:(start printString , ':' , stop printString)
-        ] ifFalse:[
-            stream nextPut:start
-        ].
     ].
 
+    stop notNil ifTrue:[
+        stream nextPut:(start printString , ':' , stop printString)
+    ] ifFalse:[
+        stream nextPut:start
+    ].
+
+
 
     stream 
         nextPut:'--debug';
@@ -406,6 +426,7 @@
         nextPut:HGCommandParser templateLog.
 
     "Created: / 13-11-2012 / 09:05:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-11-2012 / 17:15:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 parse: stream
--- a/mercurial/HGCommandParser.st	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/HGCommandParser.st	Tue Nov 13 18:09:24 2012 +0000
@@ -10,11 +10,17 @@
 
 !HGCommandParser class methodsFor:'instance creation'!
 
-on: aStream
-    ^self new stream: aStream readStream
+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 (format): / 13-11-2012 / 11:02:08 / 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'!
@@ -27,10 +33,11 @@
 {author}
 {date|isodate}
 {desc}
-**EOE**'
+**EOE**
+'
 
     "Created: / 12-11-2012 / 23:06:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 13-11-2012 / 10:21:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-11-2012 / 17:18:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !HGCommandParser methodsFor:'accessing'!
@@ -57,9 +64,22 @@
 !HGCommandParser methodsFor:'parsing'!
 
 parseDate
-    self shouldImplement
+    | 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>"
 !
 
 parseLog
@@ -87,98 +107,33 @@
 
     | rev line message |
 
-    rev := HGRevision new.
+    rev := HGChangeset new.
     rev setId: self parseNodeId. self nextLineEnd.
     rev setBranch: self nextLine.
     rev setParent1Id: self parseNodeId. self nextSpace.
-    rev setParent2Id: self parseNodeId. self nextLineEnd.
+    rev setParent2Id: self parseNodeId. self nextSpace. self nextLineEnd.
     rev setAuthor: self nextLine.
-    rev setDate: self parseDate. self nextLineEnd.
+    rev setTimestamp: self parseDate. self nextLineEnd.
     message := String streamContents:[:s|
         [ line := self nextLine . line = '**EOE**' ] whileFalse:[
             s nextPutLine: line
         ].
     ].
-    rev setMessage: message
+    rev setMessage: message.
+
+    ^rev
 
     "Created: / 13-11-2012 / 09:45:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-11-2012 / 17:29:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 parseNodeId
     "Parses node id from stream and returns it. Support both,
      short and full node ids"
 
-    | c c2 sign short revno hash |
-
-    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.
+    ^HGNodeId readFrom: stream onError:[:msg|self error: msg]
 
-    "/ Read hash
-    hash := ByteArray new: 20.
-    short := true.
-    1 to: 6 do:[:i|
-        stream atEnd ifTrue:[
-            self error:'Unexpected end of stream, hex digit expected'.
-        ].
-        c := stream peek.
-        c isHexDigit ifFalse:[
-            self error:'Hex digit ([0-9a-z]) expected but ', c , ' found'.
-        ].
-        stream next.
-        stream atEnd ifTrue:[
-            self error:'Unexpected end of stream, hex digit expected'.
-        ].
-        c2 := stream peek.
-        c isHexDigit ifFalse:[
-            self error:'Hex digit ([0-9a-z]) expected but ', c , ' found'.
-        ].
-        hash at:i put: (c digitValue << 4) + c2 digitValue.
-        stream next.
-    ].
-    stream peek isHexDigit ifTrue:[
-        "/OK, full 40-char node id
-        short := false.
-        7 to: 20 do:[:i|
-            stream atEnd ifTrue:[
-                self error:'Unexpected end of stream, hex digit expected'.
-            ].
-                        c := stream peek.
-            c isHexDigit ifFalse:[
-                self error:'Hex digit ([0-9a-z]) expected but ', c , ' found'.
-            ].
-            stream next.
-            stream atEnd ifTrue:[
-                self error:'Unexpected end of stream, hex digit expected'.
-            ].
-            c2 := stream peek.
-            c isHexDigit ifFalse:[
-                self error:'Hex digit ([0-9a-z]) expected but ', c , ' found'.
-            ].
-            hash at:i put: (c digitValue << 4) + c2 digitValue.
-            stream next.
-        ].
-    ].
-    ^short ifTrue:[
-        self halt: 'Not yet supported'
-    ] ifFalse:[
-        (HGNodeId fromBytes: hash) revno: revno.
-    ]
+
 
     "
         (HGCommandParser on: '4:6f88e1f44d9eb86e0b56ca15e30e5d786acd83c7' readStream) parseNodeId
@@ -191,6 +146,7 @@
     "
 
     "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>"
 ! !
 
 !HGCommandParser methodsFor:'parsing - commands'!
@@ -237,11 +193,13 @@
 
 nextLineEnd
     | c |
-    ((c := stream next) ~= Character cr) ifTrue:[
+    ((c := stream peek) ~= Character cr) ifTrue:[
         self error:'New line expected. ''', c , ''' found!!'
-    ]
+    ].
+    stream next.
 
     "Created: / 13-11-2012 / 10:17:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-11-2012 / 17:18:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 nextSpace
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/mercurial/HGCommandParserTests.st	Tue Nov 13 18:09:24 2012 +0000
@@ -0,0 +1,102 @@
+"{ Package: 'stx:libscm/mercurial' }"
+
+TestCase subclass:#HGCommandParserTests
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SCM-Mercurial-Core-Tests'
+!
+
+
+!HGCommandParserTests methodsFor:'tests - misc'!
+
+test_misc_01
+
+    | id |
+
+    id := (HGCommandParser on: '4:6f88e1f44d9eb86e0b56ca15e30e5d786acd83c7') parseNodeId.
+    self assert: ( id revno == 4 ).
+    self assert: ( id hexPrintString = '6F88E1F44D9EB86E0B56CA15E30E5D786ACD83C7' ).
+
+    id := (HGCommandParser on: '4:6f88e1f44d9e') parseNodeId.
+    self assert: ( id revno == 4 ).
+    self assert: ( id hexPrintString = '6F88E1F44D9E' ).
+
+    id := (HGCommandParser on: '-1:0000000000000000000000000000000000000000') parseNodeId.
+    self assert: id == HGNodeId null.
+
+    id := (HGCommandParser on: '-1:000000000000') parseNodeId.
+    self assert: id == HGNodeId null.
+
+
+    "/ Too short id
+    self 
+        should:[id := (HGCommandParser on: '4:6f88e1f44d9eb86e0b56ca15e30e5d786acd83') parseNodeId.]
+        raise: Error.
+    self 
+        should:[id := (HGCommandParser on: '4:6f88e1f44d9') parseNodeId.]
+        raise: Error.
+
+
+    "/ Invalid char
+    self 
+        should:[id := (HGCommandParser on: '4:6f88e1f44d9eb86e0b56ca15e30e5d786acd8X') parseNodeId.]
+        raise: Error.
+
+        self 
+        should:[id := (HGCommandParser on: '4:6f88e1f44d9X') parseNodeId.]
+        raise: Error.
+
+    "Created: / 13-11-2012 / 16:34:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_misc_03
+
+    | rev |
+
+    rev := (HGCommandParser on: '4:6f88e1f44d9eb86e0b56ca15e30e5d786acd83c7
+default
+3:912a64597e4f133ffbc1fdabdda99167a2d69ce2 -1:0000000000000000000000000000000000000000 
+Jan Vrany <jan.vrany@fit.cvut.cz>
+2012-10-17 13:20 +0200
+Commit 4
+**EOE**
+') parseLogEntry.
+
+    self assert: rev id revno = 4.
+    self assert: rev author = 'Jan Vrany <jan.vrany@fit.cvut.cz>'.
+    self assert: rev timestamp hour = 13
+
+    "Created: / 13-11-2012 / 17:16:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_misc_04
+
+    | revs |
+
+    revs := (HGCommandParser on: '4:6f88e1f44d9eb86e0b56ca15e30e5d786acd83c7
+default
+3:912a64597e4f133ffbc1fdabdda99167a2d69ce2 -1:0000000000000000000000000000000000000000 
+Jan Vrany <jan.vrany@fit.cvut.cz>
+2012-10-17 13:20 +0200
+Commit 4
+**EOE**
+3:912a64597e4f133ffbc1fdabdda99167a2d69ce2
+default
+2:db43a5baa9acaf2536d8b12c070b4f5e0363d45c -1:0000000000000000000000000000000000000000 
+Jan Vrany <jan.vrany@fit.cvut.cz>
+2012-10-17 13:20 +0200
+Commit 3
+**EOE**
+') parseLog.
+
+    self assert: revs size == 2
+
+    "Created: / 13-11-2012 / 17:31:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGCommandParserTests class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
--- a/mercurial/HGNodeId.st	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/HGNodeId.st	Tue Nov 13 18:09:24 2012 +0000
@@ -12,41 +12,24 @@
 
 fromBytes: aByteArrayOrString
 
-    ^self new replaceBytesFrom: 1 to: 20 with: aByteArrayOrString startingAt: 1
+    | 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
-
-"/    | oid |
-"/
-"/    oid := self new.
-"/    GitPrimitives prim_git_oid_fromstr: oid str: aString.
-"/    ^oid.
-
-
-    | sz oid s hi lo |
-
-    sz := aString size.
-    sz ~~ 40 ifTrue:[
-	self error:'Not a SHA-1 hex string (must have 40 chars)'.
-	^nil
-    ].
-    oid := self new.
-    s := aString readStream.
-    1 to: 20 do: [ :idx |
-	hi := s next digitValue.
-	lo := s next digitValue.
-	oid at:idx put: ((hi bitShift:4) bitOr: lo)
-    ].
-    ^ oid
-
-    "
-    GitOid fromString: '7164acf359f5da8a4bc9cd3e03e2e461013c3811'
-    "
+    ^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
@@ -57,14 +40,120 @@
 !
 
 new: size
-    size ~~ 20 ifTrue:[
-	self error: 'Size of HGNodeId must be exactly 20 bytes, its a SHA-1 hash'.
-	^nil.
+    (size ~~ 20 and:[size ~~ 6]) ifTrue:[
+        self error: 'Size of HGNodeId must be either 20 bytes or 6 bytes (short form) '.
+        ^nil.
     ].
     ^super new: size
 
     "Created: / 10-09-2012 / 10:44:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 19-10-2012 / 15:52:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-11-2012 / 16:48:38 / 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] ifTrue:[
+            ^self null
+        ].
+        hash = #[0 0 0 0 0 0] ifTrue:[
+            ^self null
+        ].
+    ].
+    ^short ifTrue:[
+        (HGNodeId new: 6)
+            revno: revno;
+            replaceBytesFrom: 1 to: 6 with: hash startingAt: 1;
+            yourself
+    ] ifFalse:[
+        (HGNodeId 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>"
 ! !
 
 !HGNodeId class methodsFor:'accessing'!
@@ -96,6 +185,23 @@
     revno := anInteger.
 ! !
 
+!HGNodeId methodsFor:'comparing'!
+
+= anotherId
+
+    self class == anotherId class ifFalse:[ ^ false].
+    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>"
+! !
+
 !HGNodeId methodsFor:'printing & storing'!
 
 displayOn:aStream
@@ -110,15 +216,14 @@
     | rn |
 
     rn := self revno.
-    rn == -2 ifTrue:[
-        aStream nextPut:$?.
-    ] ifFalse:[
+    rn ~~ -2 ifTrue:[
         rn printOn: aStream.
+        aStream nextPut: $:.
     ].
-    aStream nextPut: $:.
+
     self hexPrintOn:aStream.
 
-    "Modified: / 13-11-2012 / 09:52:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-11-2012 / 18:01:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !HGNodeId class methodsFor:'documentation'!
--- a/mercurial/HGRepository.st	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/HGRepository.st	Tue Nov 13 18:09:24 2012 +0000
@@ -1,12 +1,19 @@
 "{ Package: 'stx:libscm/mercurial' }"
 
 Object subclass:#HGRepository
-	instanceVariableNames:'path wc'
+	instanceVariableNames:'path wc changesets'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'SCM-Mercurial-Core'
 !
 
+HGRepositoryObject subclass:#Changesets
+	instanceVariableNames:'changesets'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:HGRepository
+!
+
 
 !HGRepository class methodsFor:'utilities'!
 
@@ -35,6 +42,14 @@
     "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
@@ -53,9 +68,69 @@
         HGRepositoryError raiseSignal: 'Given path does not contain a repository (.hg subdir not found - try use #lookup:)'.
         ^nil.
     ].
-    path := p
+    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'!
--- a/mercurial/HGRevision.st	Tue Nov 13 11:06:16 2012 +0000
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,77 +0,0 @@
-"{ Package: 'stx:libscm/mercurial' }"
-
-Object subclass:#HGRevision
-	instanceVariableNames:'id branch user timestamp message parent1 parent2'
-	classVariableNames:''
-	poolDictionaries:''
-	category:'SCM-Mercurial-Core'
-!
-
-
-!HGRevision class methodsFor:'instance creation'!
-
-new
-    "return an initialized instance"
-
-    ^ self basicNew initialize.
-! !
-
-!HGRevision methodsFor:'initialization'!
-
-initialize
-    "Invoked when a new instance is created."
-
-    "/ please change as required (and remove this comment)
-    "/ id := nil.
-    "/ user := nil.
-    "/ timestamp := nil.
-    "/ files := nil.
-    "/ message := nil.
-
-
-    "/ super initialize.   -- commented since inherited method does nothing
-
-    "Modified: / 19-10-2012 / 16:08:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-setAuthor: aString
-    message := aString
-
-    "Created: / 13-11-2012 / 10:23:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-setBranch: aString
-    branch := aString
-
-    "Created: / 13-11-2012 / 10:16:10 / 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>"
-!
-
-setParent1Id: anHGNodeId
-    parent1 := anHGNodeId
-
-    "Created: / 13-11-2012 / 10:23:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-setParent2Id: anHGNodeId
-    parent1 := anHGNodeId
-
-    "Created: / 13-11-2012 / 10:23:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
-!HGRevision class methodsFor:'documentation'!
-
-version_SVN
-    ^ '$Id::                                                                                                                        $'
-! !
--- a/mercurial/HGTests.st	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/HGTests.st	Tue Nov 13 18:09:24 2012 +0000
@@ -70,13 +70,16 @@
 
     "Test modification of working copy and commit back"
 
-    | repo wc f1_txt |
+    | repo wc f1_txt oldTip newTip |
 
     repo := self repositoryNamed: 'test_repo_01'.
     "
     UserPreferences fileBrowserClass openOn: repo directory.    
     "
     wc := repo workingCopy.
+    oldTip := wc tip.
+
+    self assert: oldTip id revno == 4.
 
     "Modify some file"
     f1_txt := wc / 'f1.txt'.
@@ -88,11 +91,14 @@
     self assert: f1_txt isModified.
 
     wc commit: 'test_01a commit 1'.
+    newTip := wc tip.
 
     self assert: f1_txt isModified not.
+    self assert: newTip id revno == 5.
+    self assert: newTip parent1 = oldTip.
 
     "Created: / 19-09-2012 / 23:06:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 12-11-2012 / 22:41:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 13-11-2012 / 18:07:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !HGTests class methodsFor:'documentation'!
--- a/mercurial/HGWorkingCopy.st	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/HGWorkingCopy.st	Tue Nov 13 18:09:24 2012 +0000
@@ -21,6 +21,22 @@
 
 root
     ^ root
+!
+
+tip
+    "Return an HGChangeset representing the checked-out changeset
+     (revision) of the receiver"
+
+    | id |
+
+    (root asFilename / '.hg' / 'dirstate') readingFileDo:[:s|
+        s binary.
+        id := HGNodeId fromBytes: (s next: 20).
+    ].
+
+    ^repository changesetWithId: id.
+
+    "Created: / 13-11-2012 / 17:58:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !HGWorkingCopy methodsFor:'actions'!
--- a/mercurial/Make.proto	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/Make.proto	Tue Nov 13 18:09:24 2012 +0000
@@ -146,15 +146,15 @@
 $(OUTDIR)HGCommandParser.$(O) HGCommandParser.$(H): HGCommandParser.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGError.$(O) HGError.$(H): HGError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGNodeId.$(O) HGNodeId.$(H): HGNodeId.st $(INCLUDE_TOP)/stx/libbasic/ByteArray.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)HGRepository.$(O) HGRepository.$(H): HGRepository.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGRepositoryError.$(O) HGRepositoryError.$(H): HGRepositoryError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGRepositoryObject.$(O) HGRepositoryObject.$(H): HGRepositoryObject.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)HGRevision.$(O) HGRevision.$(H): HGRevision.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGStatus.$(O) HGStatus.$(H): HGStatus.st $(INCLUDE_TOP)/stx/libbasic2/Singleton.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGWorkingCopyFile.$(O) HGWorkingCopyFile.$(H): HGWorkingCopyFile.st $(INCLUDE_TOP)/stx/libscm/git/GitStatusCodes.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)stx_libscm_mercurial.$(O) stx_libscm_mercurial.$(H): stx_libscm_mercurial.st $(INCLUDE_TOP)/stx/libbasic/LibraryDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/ProjectDefinition.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGBranch.$(O) HGBranch.$(H): HGBranch.st $(INCLUDE_TOP)/stx/libscm/mercurial/HGRepositoryObject.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)HGChangeset.$(O) HGChangeset.$(H): HGChangeset.st $(INCLUDE_TOP)/stx/libscm/mercurial/HGRepositoryObject.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGCommandError.$(O) HGCommandError.$(H): HGCommandError.st $(INCLUDE_TOP)/stx/libscm/mercurial/HGError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)HGRepository.$(O) HGRepository.$(H): HGRepository.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libscm/mercurial/HGRepositoryObject.$(H) $(STCHDR)
 $(OUTDIR)HGWorkingCopy.$(O) HGWorkingCopy.$(H): HGWorkingCopy.st $(INCLUDE_TOP)/stx/libscm/git/GitStatusCodes.$(H) $(INCLUDE_TOP)/stx/libscm/mercurial/HGRepositoryObject.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/mercurial/Make.spec	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/Make.spec	Tue Nov 13 18:09:24 2012 +0000
@@ -52,9 +52,9 @@
 COMMON_CLASSES= \
 	HGCommand \
 	HGCommandParser \
-	HGRepository \
+	HGRepositoryObject \
 	HGRepositoryError \
-	HGRepositoryObject \
+	HGRepository \
 	HGWorkingCopyFile \
 	stx_libscm_mercurial \
 	HGBranch \
@@ -63,7 +63,7 @@
 	HGStatus \
 	HGError \
 	HGCommandError \
-	HGRevision \
+	HGChangeset \
 
 
 
@@ -71,9 +71,9 @@
 COMMON_OBJS= \
     $(OUTDIR)HGCommand.$(O) \
     $(OUTDIR)HGCommandParser.$(O) \
-    $(OUTDIR)HGRepository.$(O) \
+    $(OUTDIR)HGRepositoryObject.$(O) \
     $(OUTDIR)HGRepositoryError.$(O) \
-    $(OUTDIR)HGRepositoryObject.$(O) \
+    $(OUTDIR)HGRepository.$(O) \
     $(OUTDIR)HGWorkingCopyFile.$(O) \
     $(OUTDIR)stx_libscm_mercurial.$(O) \
     $(OUTDIR)HGBranch.$(O) \
@@ -82,7 +82,7 @@
     $(OUTDIR)HGStatus.$(O) \
     $(OUTDIR)HGError.$(O) \
     $(OUTDIR)HGCommandError.$(O) \
-    $(OUTDIR)HGRevision.$(O) \
+    $(OUTDIR)HGChangeset.$(O) \
 
 
 
--- a/mercurial/abbrev.stc	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/abbrev.stc	Tue Nov 13 18:09:24 2012 +0000
@@ -16,4 +16,5 @@
 HGStatus HGStatus stx:libscm/mercurial 'SCM-Mercurial-Core' 1
 HGError HGError stx:libscm/mercurial 'SCM-Mercurial-Core' 1
 HGCommandError HGCommandError stx:libscm/mercurial 'SCM-Mercurial-Core' 1
-HGRevision HGRevision stx:libscm/mercurial 'SCM-Mercurial-Core' 0
+HGCommandParserTests HGCommandParserTests stx:libscm/mercurial 'SCM-Mercurial-Core-Tests' 1
+HGChangeset HGChangeset stx:libscm/mercurial 'SCM-Mercurial-Core' 0
--- a/mercurial/bc.mak	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/bc.mak	Tue Nov 13 18:09:24 2012 +0000
@@ -82,15 +82,15 @@
 $(OUTDIR)HGCommandParser.$(O) HGCommandParser.$(H): HGCommandParser.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGError.$(O) HGError.$(H): HGError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGNodeId.$(O) HGNodeId.$(H): HGNodeId.st $(INCLUDE_TOP)\stx\libbasic\ByteArray.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)HGRepository.$(O) HGRepository.$(H): HGRepository.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGRepositoryError.$(O) HGRepositoryError.$(H): HGRepositoryError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGRepositoryObject.$(O) HGRepositoryObject.$(H): HGRepositoryObject.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)HGRevision.$(O) HGRevision.$(H): HGRevision.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGStatus.$(O) HGStatus.$(H): HGStatus.st $(INCLUDE_TOP)\stx\libbasic2\Singleton.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGWorkingCopyFile.$(O) HGWorkingCopyFile.$(H): HGWorkingCopyFile.st $(INCLUDE_TOP)\stx\libscm\git\GitStatusCodes.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)stx_libscm_mercurial.$(O) stx_libscm_mercurial.$(H): stx_libscm_mercurial.st $(INCLUDE_TOP)\stx\libbasic\LibraryDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\ProjectDefinition.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGBranch.$(O) HGBranch.$(H): HGBranch.st $(INCLUDE_TOP)\stx\libscm\mercurial\HGRepositoryObject.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)HGChangeset.$(O) HGChangeset.$(H): HGChangeset.st $(INCLUDE_TOP)\stx\libscm\mercurial\HGRepositoryObject.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGCommandError.$(O) HGCommandError.$(H): HGCommandError.st $(INCLUDE_TOP)\stx\libscm\mercurial\HGError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)HGRepository.$(O) HGRepository.$(H): HGRepository.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libscm\mercurial\HGRepositoryObject.$(H) $(STCHDR)
 $(OUTDIR)HGWorkingCopy.$(O) HGWorkingCopy.$(H): HGWorkingCopy.st $(INCLUDE_TOP)\stx\libscm\git\GitStatusCodes.$(H) $(INCLUDE_TOP)\stx\libscm\mercurial\HGRepositoryObject.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
--- a/mercurial/libInit.cc	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/libInit.cc	Tue Nov 13 18:09:24 2012 +0000
@@ -31,15 +31,15 @@
 _HGCommandParser_Init(pass,__pRT__,snd);
 _HGError_Init(pass,__pRT__,snd);
 _HGNodeId_Init(pass,__pRT__,snd);
-_HGRepository_Init(pass,__pRT__,snd);
 _HGRepositoryError_Init(pass,__pRT__,snd);
 _HGRepositoryObject_Init(pass,__pRT__,snd);
-_HGRevision_Init(pass,__pRT__,snd);
 _HGStatus_Init(pass,__pRT__,snd);
 _HGWorkingCopyFile_Init(pass,__pRT__,snd);
 _stx_137libscm_137mercurial_Init(pass,__pRT__,snd);
 _HGBranch_Init(pass,__pRT__,snd);
+_HGChangeset_Init(pass,__pRT__,snd);
 _HGCommandError_Init(pass,__pRT__,snd);
+_HGRepository_Init(pass,__pRT__,snd);
 _HGWorkingCopy_Init(pass,__pRT__,snd);
 
 
--- a/mercurial/mercurial.rc	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/mercurial.rc	Tue Nov 13 18:09:24 2012 +0000
@@ -25,7 +25,7 @@
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2012\nCopyright eXept Software AG 1998-2012\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "6.2.3.1\0"
-      VALUE "ProductDate", "Tue, 13 Nov 2012 11:08:02 GMT\0"
+      VALUE "ProductDate", "Tue, 13 Nov 2012 18:11:09 GMT\0"
     END
 
   END
--- a/mercurial/stx_libscm_mercurial.st	Tue Nov 13 11:06:16 2012 +0000
+++ b/mercurial/stx_libscm_mercurial.st	Tue Nov 13 18:09:24 2012 +0000
@@ -27,10 +27,10 @@
      exclude individual packages in the #excludedFromPrerequisites method."
 
     ^ #(
-        #'stx:goodies/sunit'    "TestResource - superclass of HGRepositoriesResource "
-        #'stx:libbasic'    "ProjectDefinition - superclass of stx_libscm_mercurial "
-        #'stx:libbasic2'    "Singleton - superclass of HGStatus::Added "
-        #'stx:libscm/git'    "GitSignature - referenced by HGTests>>performTest "
+        #'stx:goodies/sunit'    "TestCase - superclass of HGCommandParserTests "
+        #'stx:libbasic'    "LibraryDefinition - superclass of stx_libscm_mercurial "
+        #'stx:libbasic2'    "Singleton - superclass of HGStatus::Missing "
+        #'stx:libscm/git'    "GitCommitterQuery - referenced by HGTests>>performTest "
     )
 ! !
 
@@ -59,7 +59,8 @@
         HGStatus
         HGError
         HGCommandError
-        HGRevision
+        (HGCommandParserTests autoload)
+        HGChangeset
     )
 !