initial checkin
authorClaus Gittinger <cg@exept.de>
Wed, 22 Nov 2006 14:21:57 +0100
changeset 106 5d9bfc22f97b
parent 105 d759f0b2db69
child 107 1d69365eba70
initial checkin
MCRepository.st
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/MCRepository.st	Wed Nov 22 14:21:57 2006 +0100
@@ -0,0 +1,232 @@
+"{ Package: 'stx:goodies/monticello' }"
+
+Object subclass:#MCRepository
+	instanceVariableNames:'creationTemplate storeDiffs'
+	classVariableNames:'Settings'
+	poolDictionaries:''
+	category:'Monticello-Repositories'
+!
+
+
+!MCRepository class methodsFor:'as yet unclassified'!
+
+allConcreteSubclasses
+	^ self withAllSubclasses reject: [:ea | ea isAbstract]
+!
+
+creationTemplate
+	self subclassResponsibility.
+!
+
+description
+	^ nil
+!
+
+fillInTheBlankConfigure
+	^ self fillInTheBlankConfigure: self creationTemplate
+			
+!
+
+fillInTheBlankConfigure: aTemplateString
+	| chunk repo |
+	
+	aTemplateString ifNil: [ ^ false ].
+	chunk _ FillInTheBlankMorph 
+			request: self fillInTheBlankRequest
+			initialAnswer: aTemplateString
+			centerAt: Sensor cursorPoint
+			inWorld: World
+			onCancelReturn: nil
+			acceptOnCR: false
+			answerExtent: 400@120.
+			
+	chunk 
+		ifNotNil: [ 
+			repo _ self readFrom: chunk readStream.
+			repo creationTemplate: chunk. 
+	].
+
+	^ repo
+!
+
+fillInTheBlankRequest
+	self subclassResponsibility.
+!
+
+isAbstract
+	^ self description isNil
+!
+
+morphicConfigure
+	^ self new
+!
+
+new
+	^ self basicNew initialize
+! !
+
+!MCRepository class methodsFor:'class initialization'!
+
+initialize
+	"self initialize"
+
+	ExternalSettings registerClient: self.
+! !
+
+!MCRepository class methodsFor:'external settings'!
+
+fetchExternalSettingsIn: aDirectory
+	"Scan for settings file"
+	"MCRepository fetchExternalSettingsIn: ExternalSettings preferenceDirectory"
+
+	| stream |
+	(aDirectory fileExists: self settingsFileName)
+		ifFalse: [^self].
+	stream _ aDirectory readOnlyFileNamed: self settingsFileName.
+	stream
+		ifNotNil: [
+			[Settings _ ExternalSettings parseServerEntryArgsFrom: stream]
+				ensure: [stream close]].
+!
+
+releaseExternalSettings
+	Settings := nil.
+!
+
+settingsFileName
+	^ 'mcSettings'
+! !
+
+!MCRepository methodsFor:'as yet unclassified'!
+
+= other
+	^ other species = self species and: [other description = self description]
+!
+
+alwaysStoreDiffs
+	^ storeDiffs ifNil: [false]
+!
+
+asCreationTemplate
+	^ self creationTemplate
+!
+
+basicStoreVersion: aVersion
+	self subclassResponsibility
+!
+
+closestAncestorVersionFor: anAncestry ifNone: errorBlock
+	anAncestry breadthFirstAncestorsDo:
+		[:ancestorInfo |
+		(self versionWithInfo: ancestorInfo) ifNotNilDo: [:v | ^ v]].
+	^ errorBlock value
+!
+
+creationTemplate
+	^ creationTemplate
+!
+
+creationTemplate: aString
+	self creationTemplate ifNotNil: [ self error: 'Creation template already set for this MCRepository instance.' ].
+	
+	creationTemplate _ aString.
+!
+
+description
+	^ self class name
+!
+
+doAlwaysStoreDiffs
+	storeDiffs _ true
+!
+
+doNotAlwaysStoreDiffs
+	storeDiffs _ false
+!
+
+hash
+	^ self description hash
+!
+
+initialize
+!
+
+notificationForVersion: aVersion
+	^ MCVersionNotification version: aVersion repository: self
+!
+
+notifyList
+	^ #()
+!
+
+possiblyNewerVersionsOfAnyOf: someVersions
+	^#()
+!
+
+prepareVersionForStorage: aVersion
+	^ self alwaysStoreDiffs
+		ifTrue: [aVersion asDiffAgainst:
+				 (self closestAncestorVersionFor: aVersion info ifNone: [^ aVersion])]
+		ifFalse: [aVersion]
+!
+
+printOn: aStream
+	super printOn: aStream.
+	aStream
+		nextPut: $(;
+		nextPutAll: self description;
+		nextPut: $).
+!
+
+sendNotificationsForVersion: aVersion
+	| notification notifyList |
+	notifyList _ self notifyList.
+	notifyList isEmpty ifFalse:
+		[notification _ self notificationForVersion: aVersion.
+		notifyList do: [:ea | notification notify: ea]]
+!
+
+storeVersion: aVersion
+	self basicStoreVersion: (self prepareVersionForStorage: aVersion).
+	self sendNotificationsForVersion: aVersion
+! !
+
+!MCRepository methodsFor:'interface'!
+
+includesVersionNamed: aString
+	self subclassResponsibility
+!
+
+morphicOpen
+	self morphicOpen: nil
+!
+
+morphicOpen: aWorkingCopy
+	self subclassResponsibility 
+!
+
+openAndEditTemplateCopy
+	^ self class fillInTheBlankConfigure: (self asCreationTemplate ifNil: [^nil])
+!
+
+versionWithInfo: aVersionInfo
+	^ self versionWithInfo: aVersionInfo ifAbsent: [nil]
+!
+
+versionWithInfo: aVersionInfo ifAbsent: aBlock
+	self subclassResponsibility 
+! !
+
+!MCRepository methodsFor:'testing'!
+
+isValid
+	^true
+! !
+
+!MCRepository class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/goodies/monticello/MCRepository.st,v 1.1 2006-11-22 13:21:57 cg Exp $'
+! !
+
+MCRepository initialize!