SVNSourceCodeManager.st
author Claus Gittinger <cg@exept.de>
Tue, 10 Jan 2012 13:09:33 +0100
changeset 929 b74f9f659232
parent 925 d14d4d0e3414
child 955 5b6779c9e055
permissions -rw-r--r--
*** empty log message ***

"
 Copyright (c) 2007-2010 Jan Vrany
 Copyright (c) 2009-2010 eXept Software AG

 Permission is hereby granted, free of charge, to any person
 obtaining a copy of this software and associated documentation
 files (the 'Software'), to deal in the Software without
 restriction, including without limitation the rights to use,
 copy, modify, merge, publish, distribute, sublicense, and/or sell
 copies of the Software, and to permit persons to whom the
 Software is furnished to do so, subject to the following
 conditions:

 The above copyright notice and this permission notice shall be
 included in all copies or substantial portions of the Software.

 THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
 EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
 OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
 NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
 HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
 WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
 FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
 OTHER DEALINGS IN THE SOFTWARE.
"
"{ Package: 'stx:libsvn' }"

AbstractSourceCodeManager subclass:#SVNSourceCodeManager
	instanceVariableNames:''
	classVariableNames:'LoadInProgressQuery'
	poolDictionaries:''
	category:'System-SourceCodeManagement'
!

!SVNSourceCodeManager class methodsFor:'documentation'!

copyright
"
 Copyright (c) 2007-2010 Jan Vrany
 Copyright (c) 2009-2010 eXept Software AG

 Permission is hereby granted, free of charge, to any person
 obtaining a copy of this software and associated documentation
 files (the 'Software'), to deal in the Software without
 restriction, including without limitation the rights to use,
 copy, modify, merge, publish, distribute, sublicense, and/or sell
 copies of the Software, and to permit persons to whom the
 Software is furnished to do so, subject to the following
 conditions:

 The above copyright notice and this permission notice shall be
 included in all copies or substantial portions of the Software.

 THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
 EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
 OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
 NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
 HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
 WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
 FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
 OTHER DEALINGS IN THE SOFTWARE.

"
!

documentation
"
    For now, this is a dummy SourceCodeManager.
    It is only provided to deliver the correct versionMethodNameTemplates
    and versionMethod names.

    Might get more in the future.
"
! !

!SVNSourceCodeManager class methodsFor:'Signal constants'!

loadInProgressQuery

    LoadInProgressQuery ifNil:
	[LoadInProgressQuery := QuerySignal new].
    ^LoadInProgressQuery
! !

!SVNSourceCodeManager class methodsFor:'basic access'!

checkinClass:aClass fileName:classFileName directory:packageDir module:moduleDir source:sourceFile logMessage:logMessage force:force
    "checkin of a class into the source repository.
     Return true if ok, false if not."

    ^ self shouldImplement
!

checkoutModule:aModule directory:aPackage andDo:aBlock
    "check out everything from a package into a temporary directory.
     Then evaluate aBlock, passing the name of that temp-directory.
     Afterwards, the tempDir is removed.
     Return true, if OK, false if any error occurred."

    | pkg tempDir repo workingCopy ok |
    pkg := (PackageId module: aModule directory: aPackage) asSymbol.
    repo := SVN::RepositoryManager repositoryForPackage: pkg.
    repo ifNil:[self error:('No repository for package %1' bindWith: pkg)].
    [ok := false.
    tempDir := Filename newTemporaryDirectory.
    workingCopy := repo workingCopyIn: tempDir.
    workingCopy checkout.
    ok := true.
    aBlock value: tempDir] ensure:
	[[tempDir recursiveRemove]
	    on: Error do:
		[:ex|
		OperatingSystem isMSWINDOWSlike
		    ifTrue:[Delay waitForSeconds: 3.[tempDir recursiveRemove] on: Error do:["nothing"]]
		    ifFalse:[ex pass]]].
    ^ok

    "Modified: / 19-04-2010 / 20:13:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

streamForClass:aClass fileName:classFileName revision:revisionString directory:packageDir module:moduleDir cache:doCache
    "extract a classes source code and return an open readStream on it.
     A revision of nil selects the current (in image) revision.
     The classes source code is extracted using the revision and the sourceCodeInfo,
     which itself is extracted from the classes packageString."

    | pkg repo rev |
    pkg := moduleDir , ':' , packageDir.
    repo := SVN::RepositoryManager repositoryForPackage: pkg.
    repo ifNil:[^self error:'No repository for package ', pkg].
    rev := SVN::Revision fromString: revisionString.
    ^(repo cat: classFileName revision: rev) readStream

    "Modified: / 02-01-2010 / 13:25:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SVNSourceCodeManager class methodsFor:'basic administration'!

checkForExistingContainer:fileName inModule:moduleName directory:dirName
    "check for a container to be present"

    ^ self shouldImplement
!

checkForExistingModule:moduleName
    "check for a module directory to be present"

    ^ self shouldImplement
!

checkForExistingModule:moduleDir directory:packageDir
    "check for a package directory to be present"

    ^ self shouldImplement
!

createContainerFor:aClass inModule:moduleName directory:dirName container:fileName
    "create a new container & check into it an initial version of aClass"

    ^ self shouldImplement
!

createModule:moduleName
    "create a new module directory"

    ^ self shouldImplement
!

createModule:module directory:directory
    "create a new package directory"

    ^ self shouldImplement
!

initialRevisionStringFor:aClass inModule:moduleDir directory:packageDir container:fileName
    "return a string usable as initial revision string"

    ^ self shouldImplement
!

revisionLogOf:clsOrNil fromRevision:rev1OrNil toRevision:rev2OrNil numberOfRevisions:limitOrNil fileName:classFileName directory:packageDir module:moduleDir
    "actually do return a revisionLog. The main worker method.
     This must be implemented by a concrete source-code manager"

    ^ self shouldImplement
! !

!SVNSourceCodeManager class methodsFor:'misc'!

savePreferencesOn:aFileStream

    "Nothing to do, since my preferences are stored in
    UserPreferences dictionary"

    "Created: / 10-06-2011 / 14:15:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SVNSourceCodeManager class methodsFor:'queries'!

isExperimental
    ^ false
    "/^ OperatingSystem getLoginName ~= 'cg'.
    "/^ true

    "Modified: / 05-12-2009 / 10:23:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isResponsibleForPackage: packageId

    UserPreferences current svnEnabled ifFalse:[^false].

    ^SVN::RepositoryManager current hasRepositoryForPackage: packageId

    "Created: / 05-12-2009 / 10:36:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-09-2010 / 14:55:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

managerTypeName
    ^ 'SubVersion'

    "Modified: / 07-07-2011 / 23:11:41 / jv"
!

managerTypeNameShort
    "Answers short version manager name suitable for UI,
     i,e., CVS, SVN, P4. Used in cases where sorter strings
     are preferred. Defaults to #managerTypeName"

    ^'SVN'

    "Created: / 03-10-2011 / 13:28:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 04-12-2011 / 10:15:36 / cg"
!

nameOfVersionMethodForExtensions
    ^ #'extensionsVersion_SVN'
!

nameOfVersionMethodInClasses
    ^ #'version_SVN'
!

settingsApplicationClass
    "link to my settings application (needed for the settings dialog"

    ^ SVN::ConfigurationApp

    "Modified: / 07-07-2011 / 23:12:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

versionMethodKeyword

    "Answers the keyword used by the version management system to
     expand a current version in a file (_without_ dollars). For
     CVS it is 'Header', for SVN 'Id', others may use different
     keywords. If nil is returned, then the version management does
     not use any keyword."

    ^'Id'

    "Created: / 27-09-2011 / 16:46:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SVNSourceCodeManager class methodsFor:'source code access'!

loadPackageWithId: aPackageId fromRepositoryAsAutoloaded: doLoadAsAutoloaded

     "Return true if loaded, false otherwise."

    | retval loadBlock |

    loadBlock := [
	| repo packageDir manager|
	manager := SVN::RepositoryManager current.
	repo := manager repositoryForPackage: aPackageId.
	retval := (repo notNil and:[repo exists]) ifTrue:[
	    repo workingCopy checkout: SVN::Revision head full: true.
	    packageDir := Smalltalk packageDirectoryForPackageId:aPackageId.
	    "Quick and dirty hack to support old version of Smalltalk/X"
	    (Smalltalk respondsTo: #loadPackage:fromDirectory:asAutoloaded:)
		ifTrue:
		    ["New API"
		    Smalltalk
			loadPackage:aPackageId
			fromDirectory:packageDir
			asAutoloaded:doLoadAsAutoloaded]
		ifFalse:
		    ["Old API"
		    Smalltalk
			loadPackageWithId:aPackageId
			fromDirectory:packageDir
			asAutoloaded:doLoadAsAutoloaded
	    ].
	] ifFalse:[false]
    ].

    (SVNSourceCodeManager loadInProgressQuery query == true)
	ifTrue:[loadBlock value]
	ifFalse:[
	    SVNSourceCodeManager loadInProgressQuery
		answer: true
		do:[
		    SVN::ProgressDialog
			openOn: loadBlock
			title: ' Loading...'
			subtitle: aPackageId asText allItalic
		]
    ].

    ^ retval

    "Created: / 09-04-2009 / 17:20:01 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 25-04-2011 / 15:20:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!SVNSourceCodeManager class methodsFor:'source code administration'!

getExistingContainersInModule:aModule directory:aPackage
    "{ Pragma: +optSpace }"

    ^ self shouldImplement
!

getExistingDirectoriesInModule:aModule
    "{ Pragma: +optSpace }"

    ^ self shouldImplement
!

getExistingModules
    "{ Pragma: +optSpace }"

    ^ self shouldImplement
!

revisionInfoFromString:aString
    "{ Pragma: +optSpace }"

    "return a dictionary filled with revision info.
     This extracts the relevant info from aString."


    ^ SVNVersionInfo fromSVNString:aString


    "
     self revisionInfoFromString:(Array version_SVN)

     self revisionInfoFromString:(stx_libbasic2 extensionsVersion_CVS)
    "


    "Modified: / 29-01-1997 / 19:00:35 / cg"
    "Modified: / 03-10-2011 / 13:02:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 29-09-2011 / 21:54:26 / cg"

! !

!SVNSourceCodeManager class methodsFor:'subclass responsibility'!

reportHistoryLogSince:timeGoal filterSTSources:filter filterUser:userFilter filterRepository:repositoryFilter filterModules:moduleFilter inTo:aBlock
    "superclass AbstractSourceCodeManager class says that I am responsible to implement this method"

    ^ self shouldImplement
! !

!SVNSourceCodeManager class methodsFor:'testing'!

isSVN
    ^ true
! !

!SVNSourceCodeManager class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^ '§Id§'
! !