mercurial/HGStXTests.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 01 Feb 2013 12:02:22 +0000
changeset 210 54a73fa50d40
parent 183 8f8315881c72
child 226 e2f6e7330c37
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' }"

HGTestCase subclass:#HGStXTests
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'SCM-Mercurial-Tests'
!

!HGStXTests 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
"
    Tests for Mercurial-Smalltalk/X integration. Mapping packages
    to Mercurial repositories, commitning packages from image
    and so on...

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

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!HGStXTests methodsFor:'running'!

loadPackage: packageId
    "A utility method to prepare a repository for package
     and load package from it"

    self repositoryNamed: (packageId copyReplaceAll:$: with:$/).
    Smalltalk loadPackage: packageId.

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

tearDown
    | classes methods |
    super tearDown.

    "Also, wipe out all mocks"
    classes := OrderedCollection new.
    methods := OrderedCollection new.
    Smalltalk allClassesDo:[:cls|
        (cls package notNil and:[cls package startsWith:'mocks']) ifTrue:[
            classes add: cls
        ] ifFalse:[
            cls methodsDo:[:m|(m package notNil and:[m package startsWith:'mocks']) ifTrue:[methods add: cls]].
            cls class methodsDo:[:m|(m package notNil and:[m package startsWith:'mocks']) ifTrue:[methods add: cls]].
        ]
    ].
    Class withoutUpdatingChangesDo:[ 
        classes do:[:cls|Smalltalk removeClass: cls].
        methods do:[:m|m mclass removeSelector: m selector]
    ].
"/    Delay waitForSeconds: 1.

    "/ Also, wipe out cached sources...
    [ 
        (AbstractSourceCodeManager cacheDirectoryName asFilename / 'mocks') recursiveRemove
    ] on: Error do:[:ex|
        Delay waitForSeconds: 1.
        (AbstractSourceCodeManager cacheDirectoryName asFilename / 'mocks') recursiveRemove.
    ]

    "Created: / 16-11-2012 / 19:00:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-12-2012 / 02:14:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_infrastructure
    "
        This is kind of meta-test that tests if the
        setUp/tearDown actually works. Especially, if
        no mock classes/methods are left in the image 
        after tearDown. Also, make sure that all
        HGPackageModels for mocks
    "
    | pm |

    self loadPackage:'mocks:hg/p1'.

    self assert: (Smalltalk at: #'mocks_hg_p1') notNil.
    pm := HGPackageModelRegistry packageNamed:'mocks:hg/p1'.
    self assert: pm notNil.
    self assert: ((HGPackageModelRegistry current instVarNamed:#packages) includesKey: #'mocks:hg/p1').

    pm := nil. 
    self cleanup.

    self assert: (Smalltalk at: #'mocks_hg_p1') isNil.
    self assert: repositories isNil.
    self assert: ((HGPackageModelRegistry current instVarNamed:#packages) includesKey: #'mocks:hg/p1') not.

    "Created: / 16-11-2012 / 19:25:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-11-2012 / 19:32:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-11-2012 / 15:31:54 / jv"
! !

!HGStXTests methodsFor:'tests - commit'!

test_commit_01
    "
        Simple commit
    "

    | repo pm ct |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').
    self dumpRepositoryLog: repo. 


    self deny:   ((repo @ 1 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').

    (MockHGP1Bar compile:'zork ^ 1' classified:'test') package: MockHGP1Bar package.
    pm := HGPackageModel named: 'mocks:hg/p1'.
    ct := pm commitTask.
    ct message:'test_commit_01'.
    ct do.
    self dumpRepositoryLog: repo. 

    "
        repo workingCopy browse
    "
    self assert: ((repo @ 2 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').
    self assert: (Smalltalk at:#mocks_hg_p1) hgLogicalRevision revno = 2.

    "Created: / 16-11-2012 / 18:51:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-12-2012 / 15:10:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_commit_02a
    "
    Repeated commit
    "

    | repo pm ct |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    Smalltalk loadPackage:'mocks:hg/p1'.
    pm := HGPackageModel named: 'mocks:hg/p1'.
    self dumpRepositoryLog: repo. 

    (MockHGP1Bar compile:'zork ^ 1' classified:'test') package: MockHGP1Bar package.

    self deny:   ((repo @ 1 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').

    ct := pm commitTask.
    ct message:'test_commit_02-1'.
    ct do.
    self dumpRepositoryLog: repo.

    self assert: ((repo @ 2 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').
    self assert: ((repo @ 2 ) parent1 == (repo @ 1 )).

    (MockHGP1Bar compile:'zork ^ 2' classified:'test') package: MockHGP1Bar package.

    ct := pm commitTask.
    ct message:'test_commit_02-2'.
    ct do.
    self dumpRepositoryLog: repo.

    self assert:  (repo @ 3) message = 'test_commit_02-2'.
    self assert: ((repo @ 3 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 2').
    self assert: ((repo @ 3 ) parent1 == (repo @ 2 )).

    "
    repo workingCopy browse
    "

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

test_commit_02b
    "
    Repeated commit, remove the working copy between commits
    "

    | repo pm ct |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    Smalltalk loadPackage:'mocks:hg/p1'.
    pm := HGPackageModel named: 'mocks:hg/p1'.
    (MockHGP1Bar compile:'zork ^ 1' classified:'test') package: MockHGP1Bar package.

    self deny:   ((repo @ 1 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').

    ct := pm commitTask.
    ct message:'test_commit_02-1'.
    ct do.

    self assert: ((repo @ 2 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').
    self assert: ((repo @ 2 ) parent1 == (repo @ 1 )).

    (MockHGP1Bar compile:'zork ^ 2' classified:'test') package: MockHGP1Bar package.
    pm temporaryWorkingCopy path recursiveRemove.

    ct := pm commitTask.
    ct message:'test_commit_02-2'.
    ct do.

    self assert: ((repo @ 3 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 2').
    self assert: ((repo @ 3 ) parent1 == (repo @ 2 )).

    "
    repo workingCopy browse
    "

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

test_commit_03a
    "
    Two images A, B working in parallel, commiting to same repo

    1) A: checkout, modify commit package (cs1)
    2) B: checkout, commit change         (cs2)
    2) A: modify, checkout                (cs3)

    The changeset cs3 should have cs1 as its parent1

    <skip>

    "

    | repo pmA ctA wcB s |

    "=== A modifies & commits =============================== "
    repo := self repositoryNamed: 'mocks/hg/p1'.
    Smalltalk loadPackage:'mocks:hg/p1'.
    self dumpRepositoryLog: repo.

    pmA := HGPackageModel named: 'mocks:hg/p1'.
    (MockHGP1Bar compile:'zork ^ 1' classified:'test') package: MockHGP1Bar package.

    self deny:   ((repo @ 1 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').

    ctA := pmA commitTask.
    ctA message:'test_commit_03a A-1'.
    ctA do.
    self dumpRepositoryLog: repo.

    self assert: ((repo @ 2 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').
    self assert: ((repo @ 2 ) parent1 == (repo @ 1 )).

    "=== B modifies & commits =============================== "
    wcB := repo workingCopy.
    s := ( wcB / 'abbrev.stc' ) appendStream.
    [ s nextPutLine:'# Modification '] ensure:[s close].
    wcB commit: 'test_commit_03a B-2'.
    self dumpRepositoryLog: repo.
    self assert: ((repo @ 3 ) parent1 == (repo @ 1 )).


    "=== A modifies & commits =============================== "    
    (MockHGP1Bar compile:'zork ^ 2' classified:'test') package: MockHGP1Bar package.

    ctA := pmA commitTask.
    ctA message:'test_commit_03a A-3'.
    ctA do.
    self dumpRepositoryLog: repo.

    self assert: ((repo @ 4 ) parent1 == (repo @ 2 )).

    "
    repo workingCopy browse
    "

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

test_commit_03b
    "
    Two images A, B working in parallel, commiting to same repo

    1) A: checkout, modify commit package (cs1)
    2) B: checkout, commit change         (cs2)
    3) A: flushes its temp working copy
    4) A: modify, checkout                (cs3)

    The changeset cs3 should have cs1 as its parent1
    "

    | repo pmA ctA wcB s |

    "=== A modifies & commits =============================== "
    repo := self repositoryNamed: 'mocks/hg/p1'.
    Smalltalk loadPackage:'mocks:hg/p1'.
    pmA := HGPackageModel named: 'mocks:hg/p1'.
    (MockHGP1Bar compile:'zork ^ 1' classified:'test') package: MockHGP1Bar package.

    self deny:   ((repo @ 1 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').

    ctA := pmA commitTask.
    ctA message:'test_commit_03a A-1'.
    ctA do.

    self assert: ((repo @ 2 / 'MockHGP1Bar.st') contents asString includesString:'zork ^ 1').
    self assert: ((repo @ 2 ) parent1 == (repo @ 1 )).

    "=== B modifies & commits =============================== "
    wcB := repo workingCopy.
    s := ( wcB / 'abbrev.stc' ) appendStream.
    [ s nextPutLine:'# Modification '] ensure:[s close].
    wcB commit: 'test_commit_03a B-2'.
    self assert: ((repo @ 3 ) parent1 == (repo @ 1 )).

    "=== A flushed its working copy ========================= "
    pmA temporaryWorkingCopy path recursiveRemove.

    
    "=== A modifies & commits =============================== "    
    (MockHGP1Bar compile:'zork ^ 2' classified:'test') package: MockHGP1Bar package.

    ctA := pmA commitTask.
    ctA message:'test_commit_03a A-3'.
    ctA do.

    self assert: ((repo @ 4 ) parent1 == (repo @ 2 )).

    "
    repo workingCopy browse
    "

    "Created: / 20-11-2012 / 19:51:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-12-2012 / 00:30:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_commit_03c
    "
    Two images A, B working in parallel, commiting to same repo

                                                  (cs1) - base changeset
    2) B: checkout, modifu, commit change         (cs2)
    4) A: checkout, modify, commit change         (cs3)

    The changeset cs3 should have cs1 as its parent1
    "

    | repo pmA ctA wcB s |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    Smalltalk loadPackage:'mocks:hg/p1'.
    pmA := HGPackageModel named: 'mocks:hg/p1'.

    "=== B modifies & commits =============================== "
    wcB := repo workingCopy.
    s := ( wcB / 'abbrev.stc' ) appendStream.
    [ s nextPutLine:'# Modification '] ensure:[s close].
    wcB commit: 'test_commit_03c B-1'.
    self assert: ((repo @ 2 ) parent1 == (repo @ 1 )).

    "=== A modifies & commits =============================== "    
    (MockHGP1Bar compile:'zork ^ 2' classified:'test') package: MockHGP1Bar package.

    ctA := pmA commitTask.
    ctA message:'test_commit_03c A-2'.
    ctA do.

    self assert: ((repo @ 3 ) parent1 == (repo @ 1 )).

    "
    repo workingCopy browse
    "

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

test_commit_04a
    "
    Two packages in single repository:
      mocks:hg/p1/n1
      mocks:hg/p2/n2

    1) load both (they should be of same revision)
    2) modify & commit n1
    3) check that n2 has same logical revision as n1.
    "

    <skip> "/ not yet supported

    | repo pmN1 pmN2 ctN1 |

    repo := self repositoryNamed: 'mocks/hg/p2'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p2/n1').
    self assert: (Smalltalk loadPackage:'mocks:hg/p2/n2').
    pmN1 := HGPackageModel named: 'mocks:hg/p2/n1'.
    pmN2 := HGPackageModel named: 'mocks:hg/p2/n2'.
    self assert: pmN1 revision = pmN2 revision.

        "=== A modifies & commits =============================== "    
    (MocksHgP2N1Foo compile:'zork ^ 2' classified:'test') package: MocksHgP2N1Foo package.

    ctN1 := pmN1 commitTask.
    ctN1 message:'test_commit_04a 1'.
    ctN1 do.

    self assert: pmN1 revision = pmN2 revision.

    "
    repo workingCopy browse
    "

    "Created: / 01-12-2012 / 17:20:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_commit_05a
    "
    Setup: 
    Two repositories: package + upstream repo (package's default).

    1) checkout, modify.
    2) commit, setup autopush to default remote.

    Check whether remote gets updated/
    "
    | path upstreamP upstream repo pm ct |

    path := (self repositoryNamed: 'mocks/hg/p1') path.
    upstreamP := repositories add:(Filename newTemporaryDirectory).
    path moveTo: (upstreamP / 'upstream').
    upstream := HGRepository on: (upstreamP / 'upstream').
    repo := upstream cloneTo: path.

    self assert: (Smalltalk loadPackage: 'mocks:hg/p1').

    "=== modifyes & commits =============================== "    
    (MockHGP1Foo compile:'zork ^ 2' classified:'test') package: MockHGP1Foo package.

    pm := HGPackageModel named: 'mocks:hg/p1'.
    ct := pm commitTask.
    ct message:'test_commit_05a 1'.
    ct remote: repo remoteDefault.
    ct do.

    self assert: (upstream @ 2) message = 'test_commit_05a 1'.


    "
    repo workingCopy browse
    "

    "Created: / 10-12-2012 / 01:58:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_commit_05b
    "
    Setup: 
    Two repositories: package + upstream repo (package's default).

    1) checkout, modify.
    2) modify & commit in upstream
    3) commit, setup autopush to default remote.

    Check that an exception is raised as commit would create new
    head.
    "
    | path upstreamP upstream repo wc pm ct |

    path := (self repositoryNamed: 'mocks/hg/p1') path.
    upstreamP := repositories add:(Filename newTemporaryDirectory).
    path moveTo: (upstreamP / 'upstream').
    upstream := HGRepository on: (upstreamP / 'upstream').
    repo := upstream cloneTo: path.

    self assert: (Smalltalk loadPackage: 'mocks:hg/p1').

    "=== modify & commit into upstream ================== "
    wc := upstream workingCopy.
    ( wc / 'MockHGP1Foo.st' ) appendingFileDo:[:s|s nextPutLine: 'Just a comment'].
    wc commit: 'test_commit_05b 1 into upstream'.

    "=== modify & commits =============================== "    
    (MockHGP1Foo compile:'zork ^ 2' classified:'test') package: MockHGP1Foo package.

    pm := HGPackageModel named: 'mocks:hg/p1'.
    ct := pm commitTask.
    ct message:'test_commit_05b 2'.
    ct remote: repo remoteDefault.

    self should: [ ct do ] raise: HGPushWouldCreateNewHeadError





    "
    repo workingCopy browse
    "

    "Created: / 10-12-2012 / 02:09:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_commit_06a
    "
    Test commit into new branch
    "
    | repo pm ct |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage: 'mocks:hg/p1').

    "=== modify & commit =============================== "    
    (MockHGP1Foo compile:'zork ^ 2' classified:'test') package: MockHGP1Foo package.

    pm := HGPackageModel named: 'mocks:hg/p1'.
    ct := pm commitTask.
    ct message:'test_commit_06a 1'.
    ct branch:'test_commit_06a'.
    ct do.

    "=== check for the branch ========================= "
    self assert: (repo branches size  == 2).
    self assert: (repo @ 2) branches size == 1.
    self assert: (repo @ 2) branches anElement name = 'test_commit_06a'.
    self assert: (repo workingCopy branch name) = 'test_commit_06a'.

    "=== update original wc ========================== "
    self assert: ((repo workingCopy / 'MockHGP1Foo.st') contents asString includesString:'zork ^ 2') not.
    repo workingCopy update.
    self assert: ((repo workingCopy / 'MockHGP1Foo.st') contents asString includesString:'zork ^ 2').


    "
    repo workingCopy browse
    "

    "Created: / 10-12-2012 / 03:24:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 10-12-2012 / 11:27:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_commit_06b
    "
    Test commit into same branch
    "
    | repo pm ct |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage: 'mocks:hg/p1').

    "=== modifyes & commits =============================== "    
    (MockHGP1Foo compile:'zork ^ 2' classified:'test') package: MockHGP1Foo package.

    pm := HGPackageModel named: 'mocks:hg/p1'.
    ct := pm commitTask.
    ct message:'test_commit_06a 1'.
    ct branch:'default'.
    ct do.

    self assert: (repo branches size  == 1).
    self assert: (repo @ 2) branches size == 1.
    self assert: (repo @ 2) branches anElement name = 'default'.


    "
    repo workingCopy browse
    "

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

test_commit_06c
    "
    Test commit into existing branch should raise an error
    (theoretically possible, but would be tricky to support :-)
    "
    | repo pm ct |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage: 'mocks:hg/p1').

    "=== create the branch beforehand ===================== "
    (repo workingCopy / 'abbrev.stc' ) appendingFileDo:[:s|s cr;cr;cr].
    repo workingCopy branch: 'test_commit_06c'.
    repo workingCopy commit: 'test_commit_06c into branch test_commit_06c'.
    repo workingCopy update: 0.

    "=== modify & commit ================================== "    
    (MockHGP1Foo compile:'zork ^ 2' classified:'test') package: MockHGP1Foo package.

    pm := HGPackageModel named: 'mocks:hg/p1'.
    ct := pm commitTask.
    ct message:'test_commit_06a 1'.
    ct branch:'test_commit_06c'.

    self should: [ ct do] raise: HGCommitError


    "
    repo workingCopy browse
    "

    "Created: / 10-12-2012 / 03:28:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-01-2013 / 14:37:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_commit_07
    "
        Tests commit to an empty repository
    "

    | repo cls pm ct |

    repo := self repositoryNamed: 'mocks/hg/p4_empty' unpack: false.
    self dumpRepositoryLog: repo. 

    cls := Object subclass:#MockHGP4_EmptyFoo instanceVariableNames:'' classVariableNames:'' poolDictionaries:''.
    cls package: #'mocks:hg/p4_empty'.
    (cls compile:'zork ^ 1' classified:'test') package: #'mocks:hg/p4_empty'.

    pm := HGPackageModel named: #'mocks:hg/p4_empty'.
    ct := pm commitTask.
    ct message:'test_commit_07'.
    ct do.
    self dumpRepositoryLog: repo. 

    "
        repo workingCopy browse
    "
    self assert: ((repo @ 0 / 'MockHGP4_EmptyFoo.st') contents asString includesString:'zork ^ 1').
    self assert: (Smalltalk at:#mocks_hg_p4_empty) hgLogicalRevision revno = 0.

    "Created: / 14-01-2013 / 13:20:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_commit_08
    "
    Test commit into fresh branch created in repo (but with no
    changeset yet)
    "
    | repo pm ct |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    repo workingCopy branch: 'branch_test_commit_08'.
    self assert: (Smalltalk loadPackage: 'mocks:hg/p1').

    "=== modifyes & commits =============================== "    
    (MockHGP1Foo compile:'zork ^ 2' classified:'test') package: MockHGP1Foo package.

    pm := HGPackageModel named: 'mocks:hg/p1'.
    ct := pm commitTask.
    ct message:'test_commit_08 1'.
    ct do.

    self assert: (repo branches size == 2).
    self assert: (repo @ 2) branches size == 1.
    self assert: (repo @ 2) branches anElement name = 'branch_test_commit_08'.


    "
    repo workingCopy browse
    pm temporaryWorkingCopy browse.
    "

    "Created: / 14-01-2013 / 14:14:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGStXTests methodsFor:'tests - manager API'!

test_log_01

    | log repo |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    log := HGSourceCodeManager 
                revisionLogOf:MockHGP1Bar 
                fromRevision:0 toRevision:0 
                numberOfRevisions:nil 
                fileName:'MockHGP1Bar.st' 
                directory: 'hg/p1'
                module:'mocks'.

    self assert: (log at: #container) = 'MockHGP1Bar.st'.
    self assert: (log at: #cvsRoot) = repo pathName.
    self assert: (log at: #newestRevision) = '1:e0bec585af86'.
    self assert: (log at: #revisions) size == 1.

    "Created: / 04-12-2012 / 01:07:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_log_02

    | log repo |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    log := HGSourceCodeManager 
                revisionLogOf:MockHGP1Bar 
                fromRevision:nil toRevision:nil
                numberOfRevisions:nil 
                fileName:'MockHGP1Bar.st' 
                directory: 'hg/p1'
                module:'mocks'.

    self assert: (log at: #container) = 'MockHGP1Bar.st'.
    self assert: (log at: #cvsRoot) = repo pathName.
    self assert: (log at: #newestRevision) = '1:e0bec585af86'.
    self assert: (log at: #revisions) size == 2.
    self assert: ((log at: #revisions) first  at:#revision) = '1:e0bec585af86'.
    self assert: ((log at: #revisions) second at:#revision) = '0:99acfa83a3bf'.

    "Created: / 04-12-2012 / 01:26:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_log_03

    | log repo |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    log := HGSourceCodeManager 
                revisionLogOf:MockHGP1Bar 
                fromRevision:nil toRevision:nil
                numberOfRevisions:1 
                fileName:'MockHGP1Bar.st' 
                directory: 'hg/p1'
                module:'mocks'.

    self assert: (log at: #container) = 'MockHGP1Bar.st'.
    self assert: (log at: #cvsRoot) = repo pathName.
    self assert: (log at: #newestRevision) = '1:e0bec585af86'.
    self assert: (log at: #revisions) size == 1.
    self assert: ((log at: #revisions) first  at:#revision) = '1:e0bec585af86'.

    "Created: / 04-12-2012 / 01:31:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_log_04a

    | log repo |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    log := HGSourceCodeManager 
                revisionLogOf:MockHGP1Bar 
                fromRevision:'1:e0bec585af86' toRevision:nil
                numberOfRevisions:nil 
                fileName:'MockHGP1Bar.st' 
                directory: 'hg/p1'
                module:'mocks'.

    self assert: (log at: #container) = 'MockHGP1Bar.st'.
    self assert: (log at: #cvsRoot) = repo pathName.
    self assert: (log at: #newestRevision) = '1:e0bec585af86'.
    self assert: (log at: #revisions) size == 2.
    self assert: ((log at: #revisions) first  at:#revision) = '1:e0bec585af86'.
    self assert: ((log at: #revisions) second at:#revision) = '0:99acfa83a3bf'.

    "Created: / 04-12-2012 / 01:32:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_log_04b

    | log repo |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    log := HGSourceCodeManager 
                revisionLogOf:MockHGP1Bar 
                fromRevision:'1:e0bec585af86' toRevision:'0:99acfa83a3bf'
                numberOfRevisions:nil 
                fileName:'MockHGP1Bar.st' 
                directory: 'hg/p1'
                module:'mocks'.

    self assert: (log at: #container) = 'MockHGP1Bar.st'.
    self assert: (log at: #cvsRoot) = repo pathName.
    self assert: (log at: #newestRevision) = '1:e0bec585af86'.
    self assert: (log at: #revisions) size == 2.
    self assert: ((log at: #revisions) first  at:#revision) = '1:e0bec585af86'.
    self assert: ((log at: #revisions) second at:#revision) = '0:99acfa83a3bf'.

    "Created: / 04-12-2012 / 01:32:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_log_04c

    | log repo |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    log := HGSourceCodeManager 
                revisionLogOf:MockHGP1Bar 
                fromRevision:nil toRevision:'0:99acfa83a3bf'
                numberOfRevisions:nil 
                fileName:'MockHGP1Bar.st' 
                directory: 'hg/p1'
                module:'mocks'.

    self assert: (log at: #container) = 'MockHGP1Bar.st'.
    self assert: (log at: #cvsRoot) = repo pathName.
    self assert: (log at: #newestRevision) = '1:e0bec585af86'.
    self assert: (log at: #revisions) size == 2.
    self assert: ((log at: #revisions) first  at:#revision) = '1:e0bec585af86'.
    self assert: ((log at: #revisions) second at:#revision) = '0:99acfa83a3bf'.

    "Created: / 04-12-2012 / 01:32:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_log_04d

    | log repo |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    log := HGSourceCodeManager 
                revisionLogOf:MockHGP1Bar 
                fromRevision:'0:99acfa83a3bf' toRevision:'0:99acfa83a3bf'
                numberOfRevisions:nil 
                fileName:'MockHGP1Bar.st' 
                directory: 'hg/p1'
                module:'mocks'.

    self assert: (log at: #container) = 'MockHGP1Bar.st'.
    self assert: (log at: #cvsRoot) = repo pathName.
    self assert: (log at: #newestRevision) = '1:e0bec585af86'.
    self assert: (log at: #revisions) size == 1.
    self assert: ((log at: #revisions) first at:#revision) = '0:99acfa83a3bf'.

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

test_stream_01a

    | stream repo contents |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    stream := HGSourceCodeManager 
                streamForClass:MockHGP1Bar 
                fileName:'MockHGP1Bar.st'
                revision: '0:99acfa83a3bf'
                directory: 'hg/p1'
                module:'mocks'
                cache: false.
    contents := stream contents.

    self assert: contents first = '"{ Package: ''mocks/hg/p1'' }"'

    "Created: / 04-12-2012 / 02:04:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_stream_01b

    | stream repo contents |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    stream := HGSourceCodeManager 
                streamForClass:MockHGP1Bar 
                fileName:'MockHGP1Bar.st'
                revision: '1:e0bec585af86'
                directory: 'hg/p1'
                module:'mocks'
                cache: false.
    contents := stream contents.

    self assert: contents first = '"{ Package: ''mocks:hg/p1'' }"'

    "Created: / 04-12-2012 / 02:05:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_stream_02a

    | stream repo contents |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    stream := HGSourceCodeManager 
                streamForClass:MockHGP1Bar 
                fileName:'MockHGP1Bar.st'
                revision: '0:99acfa83a3bf'
                directory: 'hg/p1'
                module:'mocks'
                cache: true.

    contents := stream contents.

    self assert: contents first = '"{ Package: ''mocks/hg/p1'' }"'.
    self assert: stream isFileStream.

    stream := HGSourceCodeManager 
                streamForClass:MockHGP1Bar 
                fileName:'MockHGP1Bar.st'
                revision: '0:99acfa83a3bf'
                directory: 'hg/p1'
                module:'mocks'
                cache: true.

    contents := stream contents.

    self assert: contents first = '"{ Package: ''mocks/hg/p1'' }"'.
    self assert: stream isFileStream.

    "Created: / 04-12-2012 / 02:08:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-12-2012 / 10:12:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_stream_02b

    | stream repo contents |


    repo := self repositoryNamed: 'mocks/hg/p1'.
    self assert: (Smalltalk loadPackage:'mocks:hg/p1').

    stream := HGSourceCodeManager 
                streamForClass:MockHGP1Bar 
                fileName:'MockHGP1Bar.st'
                revision: '1:e0bec585af86'
                directory: 'hg/p1'
                module:'mocks'
                cache: true.
    contents := stream contents.

    self assert: contents first = '"{ Package: ''mocks:hg/p1'' }"'

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

!HGStXTests methodsFor:'tests - misc'!

test_misc_fileReleaseAndRevisionNr
    "
    ProjectDefinition>>fileReleaseNr and ProjectDefinition>>fileRevisionNr
    are used to generate package.rc used on Windows.

    String returned must be an integer and must be a valid short value 
    - otherwise, BCC won't compile/link the library.

    If this test fail it means that implementation fileReleaseNr/fileRevisionNr
    is rubbish. As of 2012-11-23, it uses 'self revision' and expects
    (but does not check!!) the resulting string is in X.Y form. In mercurial,
    #revision returns node id (SHA1 hash string).

    It has to be fixed there!!
    "

    | repo |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    Smalltalk loadPackage:'mocks:hg/p1'.

    self assert: ((Smalltalk at:#'mocks_hg_p1') fileReleaseNr allSatisfy:[:c|c isDigit]).
    self assert: ((Smalltalk at:#'mocks_hg_p1') fileReleaseNr asInteger < 16r7FFF).

    self assert: ((Smalltalk at:#'mocks_hg_p1') fileRevisionNr allSatisfy:[:c|c isDigit]).
    self assert: ((Smalltalk at:#'mocks_hg_p1') fileRevisionNr asInteger < 16r7FFF).

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

test_misc_hgRevision_01
    | repo |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    Smalltalk loadPackage:'mocks:hg/p1'.
    self dumpRepositoryLog: repo. 

    self assert: (Smalltalk at:#'mocks_hg_p1') hgLogicalRevision asString = '1:e0bec585af86'.

    "Created: / 23-11-2012 / 11:00:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 30-11-2012 / 23:44:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_misc_packagemodel_01
    | repo pm |

    repo := self repositoryNamed: 'mocks/hg/p1'.
    Smalltalk loadPackage:'mocks:hg/p1'.
    pm := HGPackageModel named: 'mocks:hg/p1'.
    self assert: pm parent == nil.

    "Created: / 03-12-2012 / 15:45:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_misc_packagemodel_02
    | repo pmP2 pmP2N1|

    repo := self repositoryNamed: 'mocks/hg/p2'.
    Smalltalk loadPackage:'mocks:hg/p1'.
    pmP2 := HGPackageModel named: 'mocks:hg/p2'.
    pmP2N1 := HGPackageModel named: 'mocks:hg/p2/n1'.

    self assert: pmP2 parent isNil.
    self assert: pmP2N1 parent == pmP2.
    self assert: (pmP2 construct:'n1') == pmP2N1

    "Created: / 03-12-2012 / 15:46:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_misc_packagemodel_03
    | repo pmP2N1 pmP2N2|

    repo := self repositoryNamed: 'mocks/hg/p2'.
    Smalltalk loadPackage:'mocks:hg/p1'.
    pmP2N1 := HGPackageModel named: 'mocks:hg/p2/n1'.
    pmP2N2 := HGPackageModel named: 'mocks:hg/p2/n2'.

    self assert: pmP2N1 parent == pmP2N2 parent.

    "Created: / 03-12-2012 / 15:48:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

test_misc_packagemodel_03b
    | repo pmP2N1 pmP2N2|

    repo := self repositoryNamed: 'mocks/hg/p2'.
    Smalltalk loadPackage:'mocks:hg/p1/n1'.
    Smalltalk loadPackage:'mocks:hg/p1/n2'.
    pmP2N1 := HGPackageModel named: 'mocks:hg/p2/n1'.
    pmP2N2 := HGPackageModel named: 'mocks:hg/p2/n2'.

    self assert: pmP2N1 parent == pmP2N2 parent.

    "Created: / 03-12-2012 / 15:48:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGStXTests methodsFor:'utilities'!

cleanup
    "Wipeout all mock package leftovers. Could be used
     to simulate work from another fresh image"

    self tearDown

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

!HGStXTests class methodsFor:'documentation'!

version_HG

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