MCRepositoryTest.st
author Claus Gittinger <cg@exept.de>
Wed, 25 Feb 2015 01:14:48 +0100
changeset 975 9d3047664305
parent 294 9626cae7fa9c
permissions -rw-r--r--
class: ProjectDefinition changed: #monticelloName

"{ Package: 'stx:goodies/monticello' }"

MCTestCase subclass:#MCRepositoryTest
	instanceVariableNames:'repository ancestors'
	classVariableNames:''
	poolDictionaries:''
	category:'Monticello-Tests'
!


!MCRepositoryTest class methodsFor:'as yet unclassified'!

isAbstract
	^ self = MCRepositoryTest
! !

!MCRepositoryTest methodsFor:'accessing'!

snapshotAt: aVersionInfo
	^ (repository versionWithInfo: aVersionInfo) snapshot
! !

!MCRepositoryTest methodsFor:'actions'!

addVersion: aVersion
	self subclassResponsibility 
!

addVersionWithSnapshot: aSnapshot name: aString
	| version |
	version := self versionWithSnapshot: aSnapshot name: aString.
	self addVersion: version.
	^ version info
!

saveSnapshot1
	^ self saveSnapshot: self snapshot1 named: 'rev1'
!

saveSnapshot2
	^ self saveSnapshot: self snapshot2 named: 'rev2'
!

saveSnapshot: aSnapshot named: aString
	| version |
	version := self versionWithSnapshot: aSnapshot name: aString.
	repository storeVersion: version.
	^ version info
	
! !

!MCRepositoryTest methodsFor:'asserting'!

assertMissing: aVersionInfo
	self assert: (repository versionWithInfo: aVersionInfo) isNil
!

assertVersionInfos: aCollection
	self assert: repository allVersionInfos asSet = aCollection asSet
! !

!MCRepositoryTest methodsFor:'building'!

snapshot1
	^ (MCSnapshot fromDefinitions: (Array with: (MCOrganizationDefinition categories: #('y'))))
!

snapshot2
	^ (MCSnapshot fromDefinitions: (Array with: (MCOrganizationDefinition categories: #('x'))))
!

versionWithSnapshot: aSnapshot name: aString
	| info |
	info := self mockVersionInfo: aString. 
	^ MCVersion 
		package: (MCPackage new name: aString)
		info: info
		snapshot: aSnapshot
! !

!MCRepositoryTest methodsFor:'tests'!

testAddAndLoad
	| node |
	node := self addVersionWithSnapshot: self snapshot1 name: 'rev1'.
	self assert: (self snapshotAt: node) = self snapshot1.

!

testIncludesName
	self deny: (repository includesVersionNamed: 'MonticelloTest-xxx.1-rev1').
	self saveSnapshot1.
	self assert: (repository includesVersionNamed: 'MonticelloTest-xxx.1-rev1').
	self deny: (repository includesVersionNamed: 'MonticelloTest-xxx.1-rev2').
	self saveSnapshot2.
	self assert:  (repository includesVersionNamed: 'MonticelloTest-xxx.1-rev2').
!

testLoadMissingNode
	| node |
	node := MCVersionInfo new.
	self assertMissing: node
!

testStoreAndLoad
	| node node2 |
	node := self saveSnapshot1.
	node2 := self saveSnapshot2.
	self assert: (self snapshotAt: node) = self snapshot1.
	self assert: (self snapshotAt: node2) = self snapshot2.
! !

!MCRepositoryTest class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCRepositoryTest.st,v 1.2 2011-08-20 12:06:01 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCRepositoryTest.st,v 1.2 2011-08-20 12:06:01 cg Exp $'
!

version_SVN
    ^ '§Id: MCRepositoryTest.st 5 2010-08-29 07:30:29Z vranyj1 §'
! !