PerforceSourceCodeManager.st
author Claus Gittinger <cg@exept.de>
Wed, 20 Apr 2011 12:49:45 +0200
changeset 2359 62c8ea518b59
parent 2355 6c21470136d2
child 2364 90ed7ea7d1e2
permissions -rw-r--r--
changed: #settingsApplicationClass

"{ Package: 'stx:libbasic3' }"

AbstractSourceCodeManager subclass:#PerforceSourceCodeManager
	instanceVariableNames:''
	classVariableNames:'PerforceExecutable PerforceModuleRoots PerforceClient
		PerforcePort PerforceUser PerforcePassword PerforceTempDir
		Verbose PerforceCommandSemaphore PerforceEnabled
		PerforceCacheDirectoryName'
	poolDictionaries:''
	category:'System-SourceCodeManagement'
!

Object subclass:#CheckInDefinition
	instanceVariableNames:'class packageDir classFileName sourceFileName force logMessage
		moduleName manager tempDirectory workSpaceDefinition
		newestRevision definitionClass'
	classVariableNames:''
	poolDictionaries:''
	privateIn:PerforceSourceCodeManager
!

VersionInfo subclass:#PerforceVersionInfo
	instanceVariableNames:'repositoryPathName'
	classVariableNames:''
	poolDictionaries:''
	privateIn:PerforceSourceCodeManager
!

Object subclass:#WorkSpaceDefinition
	instanceVariableNames:'client host localDir owner repositoryDir root workSpaceName
		workSpaceDefinitionFilename moduleName'
	classVariableNames:''
	poolDictionaries:''
	privateIn:PerforceSourceCodeManager
!


!PerforceSourceCodeManager class methodsFor:'initialization'!

forgetDisabledModules
    ^ self
!

initialize

    PerforceCommandSemaphore := Semaphore new:10.
! !

!PerforceSourceCodeManager class methodsFor:'accessing'!

cacheDirectoryName
    "return the name of the cache directory, where checked out class
     sources are kept for faster access. The default is '/tmp/stx_sourceCache'.
     This cache is shared among all ST/X users on a system."

    ^ PerforceCacheDirectoryName

    "Modified: 12.9.1996 / 02:20:45 / cg"
!

cacheDirectoryName:aStringOrFilename
    "set the name of the cache directory, where checked out class
     sources are kept for faster access. The default is '/tmp/stx_sourceCache'.
     This cache is shared among all ST/X users on a system.
     The directory is typically set via the launchers setting menu, or
     from a startup rc-file."

    PerforceCacheDirectoryName := aStringOrFilename

    "Created: 16.12.1995 / 15:18:43 / cg"
    "Modified: 12.9.1996 / 02:21:35 / cg"
!

perforceClient
    |envVar|

    PerforceClient notNil ifTrue:[ ^ PerforceClient].
    envVar := OperatingSystem getEnvironment:'P4CLIENT'.
    envVar notEmptyOrNil ifTrue:[ ^ envVar].
    ^ 'workspace'
!

perforceClient:something
    PerforceClient := something.
!

perforceEnabled

    PerforceEnabled notNil ifTrue:[ ^ false].
    ^ PerforceEnabled
!

perforceEnabled:enable

    PerforceEnabled := enable.
!

perforceExecutable
    ^ PerforceExecutable ? 'p4'
!

perforceExecutable:aString
    "set the name of the cvs executable."

    aString isEmptyOrNil ifTrue:[
        PerforceExecutable := nil
    ] ifFalse:[
        PerforceExecutable := aString.
    ].

    "Created: / 21-09-2006 / 15:31:59 / cg"
    "Modified: / 21-09-2006 / 16:41:33 / cg"
!

perforcePassword
    |envVar|

    PerforcePassword notNil ifTrue:[ ^ PerforcePassword].
    envVar := OperatingSystem getEnvironment:'P4PASSWD'.
    envVar notEmptyOrNil ifTrue:[ ^ envVar].
    ^ 'pass'

    "Modified: / 19-04-2011 / 10:46:56 / cg"
!

perforcePassword:something
    PerforcePassword := something.
!

perforcePort
    |envVar|

    PerforcePort notNil ifTrue:[ ^ PerforcePort].
    envVar := OperatingSystem getEnvironment:'P4PORT'.
    envVar notEmptyOrNil ifTrue:[ ^ envVar].
    ^ 'localhost:1666'
!

perforcePort:something
    PerforcePort := something.
!

perforceUser
    |envVar|

    PerforceUser notNil ifTrue:[ ^ PerforceUser].
    envVar := OperatingSystem getEnvironment:'P4USER'.
    envVar notEmptyOrNil ifTrue:[ ^ envVar].
    ^ OperatingSystem getLoginName ? 'user'
!

perforceUser:something
    PerforceUser := something.
!

repositoryInfoPerModule
    "Superclass AbstractSourceCodeManager class says that I am responsible to implement this method"

    ^ PerforceModuleRoots ? Dictionary new
!

repositoryInfoPerModule:aDictionary
    "set the dictionary, which associates CVSRoots to module names.
     If no entry is contained in this dictionary for some module,
     the default cvsRoot (CVSRoot) will be used."

    PerforceModuleRoots := aDictionary
!

repositoryName
    "return the name of the repository.
     Since this is an abstract class, return nil (i.e. none)"

    ^ (self perforceClient ,':',
       self perforceUser, ':',
       (self perforcePassword ? 'pass'), '@',
       self perforcePort)
    "Modified: 12.9.1996 / 02:20:45 / cg"
    "Created: 14.9.1996 / 13:21:37 / cg"
!

repositoryName:settingsString
    "return the name of the repository.
     Since this is an abstract class, return nil (i.e. none)"

    |settings|

    settings := self getPerforceSettingsFromString:settingsString.
    self perforceClient:(settings at:#client ifAbsent:nil).
    self perforceUser:(settings at:#user ifAbsent:nil).
    self perforcePassword:(settings at:#password ifAbsent:nil).
    self perforcePort:(settings at:#port ifAbsent:nil).
    "Modified: 12.9.1996 / 02:20:45 / cg"
    "Created: 14.9.1996 / 13:21:37 / cg"
!

repositoryNameForModule:aModuleName

    |settings|

    settings := self getPerforceSettingsForModule:aModuleName.
    settings isNil ifTrue:[ ^ ''].
    ^ ((settings at:#client ifAbsent:'') ,':',
       (settings at:#user ifAbsent:''), ':',
       (settings at:#password ifAbsent:''), '@',
       (settings at:#port ifAbsent:''))
!

verboseSourceCodeAccess

    ^ Verbose

    "Created: / 19-04-2011 / 10:52:29 / cg"
!

verboseSourceCodeAccess:aBoolean

    Verbose := aBoolean

    "Created: / 19-04-2011 / 10:52:43 / cg"
! !

!PerforceSourceCodeManager class methodsFor:'basic access'!

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."

    self shouldImplement
!

createTempDirectory:packageDir forModule:moduleDir
    "create a temp directory for checking out"

    |tempdir dir|

    "/ if CVSTempDir isNil, use current.
    OperatingSystem errorSignal handle:[:ex |
        self reportError:('cannot create temporary directory').
        ^ nil.
    ] do:[
        tempdir := Filename newTemporaryDirectoryIn:(self perforceTmpDirectory).
    ].

    moduleDir notNil ifTrue:[
        dir := tempdir construct:moduleDir.
        dir makeDirectory.

        packageDir notNil ifTrue:[
            dir := dir construct:packageDir.
            dir recursiveMakeDirectory.
        ].
        dir exists ifFalse:[
            (tempdir construct:moduleDir) recursiveRemove.
            tempdir recursiveRemove.
            self reportError:('cannot create temporary directory').
            ^ nil.
        ].
    ].
    ^ tempdir

    "self createTempDirectory:'fooPackage' forModule:'fooModule'"

    "Created: / 09-12-1995 / 19:14:35 / cg"
    "Modified: / 19-12-1995 / 16:13:02 / stefan"
    "Modified: / 29-08-2006 / 13:16:23 / cg"
!

savePreferencesOn:aStream
    aStream nextPutLine:'  PerforceSourceCodeManager notNil ifTrue:['.
    aStream nextPutLine:'    PerforceSourceCodeManager repositoryInfoPerModule:' , self repositoryInfoPerModule storeString , '.'.
    PerforceExecutable notNil ifTrue:[
        aStream nextPutLine:'    PerforceSourceCodeManager perforceExecutable:' , PerforceExecutable storeString , '.'.
    ].
    (Smalltalk at:#SourceCodeManager) == self ifTrue:[
        aStream nextPutLine:'    Smalltalk at:#SourceCodeManager put: PerforceSourceCodeManager.'.
        aStream nextPutLine:'    PerforceSourceCodeManager initializeForRepository:' , self repositoryName storeString , '.'.
    ].
    aStream nextPutLine:'  ].'.

    "Created: / 09-11-2006 / 15:09:25 / cg"
    "Modified: / 10-11-2006 / 18:14:16 / cg"
!

streamForClass:cls fileName:fileName revision:revision 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."

    |cacheIt cacheDir classFileName fullName cachedSourceFilename cacheSubDir cachedFile tempdir checkoutName
     checkoutNameLocal revisionArg revMsg fullTempName fullCachedName stream tempFile cmd inDirectory inStream outStream
     line modulDir lineNr result|

    cacheIt := doCache.
    (cacheIt and:[revision ~~ #newest and:[revision notNil]]) ifTrue:[
        (cacheDir := self sourceCacheDirectory) isNil ifTrue:[
            'PerforceSourceCodeManager [warning]: no source cache directory' errorPrintCR.
        ]
    ].

    classFileName := fileName.
    classFileName isNil ifTrue:[classFileName := cls classBaseFilename].

    (classFileName endsWith:',v') ifTrue:[
        classFileName := classFileName copyWithoutLast:2.
    ].
    (classFileName endsWith:'.st') ifTrue:[
        cls notNil ifTrue:[
            classFileName := classFileName copyWithoutLast:3.
        ]
    ].
    fullName := moduleDir , '/' , packageDir , '/' , classFileName.
    cls notNil ifTrue:[
        fullName := fullName , '.st'.
    ].

    (revision isNil or:[revision == #newest]) ifTrue:[
        cachedSourceFilename := classFileName.
    ] ifFalse:[
        cachedSourceFilename := classFileName , '_' , revision.
    ].

    cacheDir notNil ifTrue:[
        cacheSubDir := cacheDir construct:moduleDir.
        cacheSubDir exists ifTrue:[
            cacheSubDir := cacheSubDir construct:packageDir.
            cacheSubDir exists ifTrue:[
                cachedFile := cacheSubDir construct:cachedSourceFilename.
                cachedFile exists ifTrue:[
                    ^ cachedFile readStream
                ].
            ].
        ].
    ].

    "/
    "/ first, create a temporary work tree
    "/ Do not make module and package directories, their existence cause cvs checkout to fail in server mode
    "/
    tempdir := self createTempDirectory:nil forModule:nil.


    "/
    "/ check it out there
    "/
    checkoutName :=  fullName.

    modulDir := moduleDir asFilename construct:packageDir.
    checkoutNameLocal := modulDir constructString:(fullName asFilename baseName).

    (revision isNil or:[revision == #newest]) ifTrue:[
        cachedSourceFilename := classFileName.
        revisionArg := ''.
        revMsg := ''.
    ] ifFalse:[
        cachedSourceFilename := classFileName , '_' , revision.
        revisionArg := ' -r ' , revision.
        revMsg := ' (' , revision , ')'.
    ].
    self activityNotification:'checking out source ' , checkoutName , revMsg.

    fullTempName := tempdir construct:checkoutNameLocal.
    cmd := ('print ' , classFileName, '.st#', revision).

    inDirectory := (Filename currentDirectory asAbsoluteFilename construct:modulDir) pathName.
    result := self executePerforceCommand:cmd
                    module:moduleDir
                    inDirectory:inDirectory
                    log:false
                    pipe:false.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: error execute command ', cmd) errorPrintCR.
        ^ nil
    ].
    inStream := self executePerforceCommand:cmd
                    module:moduleDir
                    inDirectory:inDirectory
                    log:true
                    pipe:true.

    inStream isNil ifTrue:[
        ('PerforceSourceCodeManager [error]: could not get Stream from ', cmd) errorPrintCR.
        ^ nil
    ].
    FileStream openErrorSignal handle:[:ex|
        ('PerforceSourceCodeManager [error]: can not create ', fullTempName pathName) errorPrintCR.
        ^ nil.
    ] do:[
        fullTempName directory recursiveMakeDirectory.
        outStream := fullTempName writeStream.
    ].
    lineNr := 1.
    [inStream atEnd not] whileTrue:[
        line:= inStream nextLine.
        line notNil ifTrue:[
            lineNr = 1 ifTrue:[
            ] ifFalse:[
                outStream nextPutLine:line.
            ].
        ].
        lineNr := lineNr + 1.
    ].
    outStream close.

    (cacheSubDir isNil) ifTrue:[
        cacheIt := false
    ] ifFalse:[
        cacheSubDir recursiveMakeDirectory.
        fullCachedName := cacheSubDir constructString:cachedSourceFilename.
    ].
    fullTempName exists ifFalse:[
        ('PerforceSourceCodeManager [error]: failed to checkout ', fullTempName pathName, ' (file does not exist after cvs co)') errorPrintCR.
        tempdir recursiveRemove.
        ^ nil
    ].

    (cacheIt
    and:[cachedFile notNil
    and:[fullTempName exists]])
    ifTrue:[
        (OperatingSystem errorSignal catch:[
            fullTempName moveTo:fullCachedName
        ]) ifTrue:[
            ('CVSSourceCodeManager [error]: failed to rename ', fullTempName pathName, ' to ', cachedSourceFilename) errorPrintCR.
            tempdir recursiveRemove.
            ^ nil
        ].
        fullCachedName asFilename exists ifTrue:[
            stream := fullCachedName asFilename readStream.
        ].
    ] ifFalse:[
        OperatingSystem isUNIXlike ifFalse:[
            "/ cannot remove files which are still open ...
            "/ sigh - need a delete-on-close flag in FileStream.
            "/
            tempFile := Filename newTemporary.
            fullTempName copyTo:tempFile.
            stream := tempFile readStream.
            stream notNil ifTrue:[
                stream removeOnClose:true.
            ].
        ] ifTrue:[
            stream := fullTempName readStream.
        ]
    ].

    ^ stream
! !

!PerforceSourceCodeManager class methodsFor:'basic administration'!

checkForExistingContainer:fileName inModule:moduleDir directory:packageDir
    "check for a container to exist"

    |newestRevision class className|

    fileName isString ifTrue:[
        className := fileName asFilename withoutSuffix baseName.
        class := Smalltalk at:(className asSymbol).
    ] ifFalse:[
        class := fileName.
    ].
    newestRevision := self newestRevisionOf:class.
    ^ newestRevision notNil
!

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

    |workSpaceDefinition|

    workSpaceDefinition := self getWorkSpaceForModule:moduleName modulePath:nil.
    ^ workSpaceDefinition notNil.


"
self checkForExistingModule:'applistx'
self checkForExistingModule:'balla'
"

    "Modified: / 19-04-2011 / 11:30:41 / cg"
!

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

    |modulePath cmd inDirectory inStream line workSpaceDefinition repositoryDir|

    modulePath :=  moduleName , '/' , packageDir.

    inDirectory := (Filename currentDirectory asAbsoluteFilename) pathName.
    workSpaceDefinition := self getWorkSpaceForModule:moduleName modulePath:modulePath.
    workSpaceDefinition isNil ifTrue:[
        ('PerforceSourceCodeManager [error]: cant get perforce client info for ', moduleName) errorPrintCR.
        ^ false
    ].
    repositoryDir := workSpaceDefinition repositoryDir.
    (repositoryDir endsWith:'...') ifTrue:[
        repositoryDir := repositoryDir copyTo:(repositoryDir size - 3).
    ].
    cmd := ('sync ' , repositoryDir, modulePath, '/...').
    inStream := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:inDirectory
                        log:true
                        pipe:true.
    inStream isNil ifTrue:[
        ('PerforceSourceCodeManager [error]: cannot open pipe to perforce sync ', moduleName) errorPrintCR.
        ^ false
    ].

    "/
    "/ read the commands pipe output and extract the container info
    "/
    [inStream atEnd not] whileTrue:[
        line:= inStream nextLine.
        line notNil ifTrue:[
            (line endsWith:'no such file(s).') ifTrue:[
                ^ false
            ].
        ]
    ].
    ^ true

"
    self checkForExistingModule:'testModule' directory:'libTestPerforce'
"
!

checkinClass:cls fileName:classFileName directory:packageDir module:moduleName logMessage:logMessage force:forceArg
    "enter a classes source code
     into the source repository. If the force argument is true, no merge is done;
     instead, the code is checked in as given (Dangerous).
     Return true if ok, false if not."

    |tempdir cmd checkoutName logMsg locRevision newestRevision binRevision newVersionString
     workspaceDefinitionFile workSpaceName result checkInDefinition workSpaceDefinition depotRoot|

    cls isPrivate ifTrue:[
        self reportError:'refuse to check in private classes.'.
        ^ false.
    ].
    checkInDefinition := CheckInDefinition new.
    checkInDefinition definitionClass:cls.
    checkInDefinition classFileName:classFileName.
    checkInDefinition force:forceArg.
    checkInDefinition moduleName:moduleName.
    checkInDefinition packageDir:packageDir.
    checkInDefinition manager:self.
    (checkInDefinition setLogMessage:logMessage) ifFalse:[
        self reportError:'perforce cannot handle unicode in logMessage'.
        ^ false
    ].


    locRevision := checkInDefinition getLocalRevisionNumber.
    (binRevision := checkInDefinition getBinaryRevisionNumber) notNil ifTrue:[
        locRevision ~= binRevision ifTrue:[
            ('PerforceSourceCodeManager [info]: class ' , checkInDefinition className , ' is based upon ' , binRevision printString, ' but has revision ' , (locRevision printString ? '?')) infoPrintCR
        ]
    ].

    locRevision isNil ifTrue:[
        locRevision := checkInDefinition getLocalRevisionNumberFromRepository.
    ].

    "/
    "/ first, create a temporary work tree
    "/
    tempdir := checkInDefinition tempDirectory.

    tempdir notNil ifTrue:[
            [
            checkoutName :=  checkInDefinition classFileName.

            workSpaceDefinition := self createWorkspaceFor:checkInDefinition.
            workSpaceDefinition isNil ifTrue:[
                ('PerforceSourceCodeManager [error]: failed to create workspace for', checkoutName)  errorPrintCR.
                ^ false
            ].
            checkInDefinition workSpaceDefinition:workSpaceDefinition.

            workspaceDefinitionFile := checkInDefinition workSpaceDefinitionFilename.
            workspaceDefinitionFile notNil ifTrue:[
                [
                    workSpaceName := checkInDefinition workSpaceName.
                    newestRevision := checkInDefinition getNewestRevisionNumber.

                    newestRevision isNil ifTrue:[
                        " create container for class initial check in"
                        (binRevision notNil) ifTrue:[
                            (Dialog confirm:('Someone seems to have removed the source container for ',cls name,'\\Force new checkin ?') withCRs) ifTrue:[
                                cls setBinaryRevision:nil.
                                ^ self checkinClass:cls fileName:classFileName directory:packageDir module:moduleName logMessage:logMsg force:forceArg.
                            ].
                        ].
                        "initial checkin here"
                        ^ self initialCheckinFor:checkInDefinition.
                    ].
                    "/ is the version correct ?
                    locRevision > newestRevision ifTrue:[
                        (Dialog confirm:('The version-info of ',cls name allBold,' is wrong \(The class version (',locRevision allBold,') is newer than the newest version in the repository (',newestRevision printString allBold,').\\Patch the version and retry checkin ?') withCRs)
                        ifTrue:[
                            newVersionString := self updatedRevisionStringOf:cls forRevision:newestRevision with:cls revisionString.
                            cls updateVersionMethodFor:newVersionString.
                            ^ self checkinClass:cls fileName:classFileName directory:packageDir module:moduleName logMessage:logMsg force:forceArg.
                        ].
                    ].
                    newestRevision > locRevision ifTrue:[
                        "someone changed repository in the meanwhile"
                        self activityNotification:'merging ' , cls name , ' with repository version...'.
                        self mergeOrResolveConflictsFor:checkInDefinition.
                        self postCheckInClass:cls checkInDefinition:checkInDefinition.
                    ] ifFalse:[
                        result := self standardCheckinFor:checkInDefinition localRevision:locRevision.
                        result ifFalse:[
                            ('PerforceSourceCodeManager [error]: failed to checkin ', checkoutName)  errorPrintCR.
                            ^ false
                        ].
                    ].
                ]
                ensure:[
                    " we have to revert all before delete workspace "
                    depotRoot := workSpaceDefinition repositoryDir.
                    depotRoot notNil ifTrue:[
                        cmd := ('revert  ' , depotRoot).
                        result := self executePerforceCommand:cmd
                                        module:moduleName
                                        inDirectory:tempdir
                                        log:true
                                        pipe:false
                                        clientName:workSpaceName.
                    ].
                    cmd := ('client -d  ' , workSpaceName).
                    result := self executePerforceCommand:cmd
                                        module:moduleName
                                        inDirectory:tempdir
                                        log:true
                                        pipe:false
                                        clientName:workSpaceName.

                ].
            ].
        ] ensure:[
            tempdir recursiveRemove.
        ].
    ].
    ^ true

    "
     SourceCodeManager checkinClass:Array logMessage:'testing only'
    "

    "Created: / 11-09-1996 / 16:16:11 / cg"
    "Modified: / 26-02-1998 / 17:34:16 / stefan"
    "Modified: / 25-10-2006 / 17:41:46 / cg"
!

checkinClass:cls fileName:classFileName directory:packageDir module:moduleName source:sourceFileName logMessage:logMessage force:forceArg
    "enter a classes source code (which has been already filed out into sourceFileName)
     here we have to create our own source file
     into the source repository. If the force argument is true, no merge is done;
     instead, the code is checked in as given (Dangerous).
     Return true if ok, false if not."

    ^ self checkinClass:cls fileName:classFileName directory:packageDir module:moduleName logMessage:logMessage force:forceArg

    "
     SourceCodeManager checkinClass:Array logMessage:'testing only'
    "

    "Created: / 11-09-1996 / 16:16:11 / cg"
    "Modified: / 26-02-1998 / 17:34:16 / stefan"
    "Modified: / 25-10-2006 / 17:41:46 / cg"
!

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

    self shouldImplement
!

createContainerFor:cls inModule:moduleName package:packageDir container:classFileName

    ^ self checkinClass:cls fileName:classFileName directory:packageDir module:moduleName logMessage:'Initial check in' force:false.
!

createContainerFor:cls inModule:moduleName package:packageDir container:classFileName logMessage:logMessage


    ^ self checkinClass:cls fileName:classFileName directory:packageDir module:moduleName logMessage:logMessage force:false.
!

createModule:moduleName
    "create a new module directory"

    self shouldImplement
!

createModule:module directory:directory
    "nothing to do with PerforceSourceCodeManager
     subdirectory in repository will created with adding the file "

    ^ true
!

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


    |modulePath workSpaceDefinition version checkoutName repositoryDir repositoryPathName|

    modulePath :=  moduleDir , '/' , packageDir.
    checkoutName :=  modulePath , '/' , aClass name, '.st'.
    workSpaceDefinition := self getWorkSpaceForModule:moduleDir modulePath:modulePath.
    version := PerforceVersionInfo new.
    repositoryDir := workSpaceDefinition repositoryDir.
    (repositoryDir endsWith:'...') ifTrue:[
        repositoryDir := repositoryDir copyTo:(repositoryDir size - 3).
    ].

    repositoryPathName := repositoryDir asFilename construct:checkoutName.
    version repositoryPathName:repositoryPathName pathName.
    version revision:'1'.
    ^ version getVersionString.
!

readRevisionLogEntryFromStream:inStream
    "read and parse a single revision info-entry from the cvs log output.
     Return nil on end.

     The returned information is a structure (IdentityDictionary)
     filled with:
              #revision              -> the revision string
              #author                -> who checked that revision into the repository
              #date                  -> when was it checked in
              #state                 -> the RCS state
              #numberOfChangedLines  -> the number of changed line w.r.t the previous
              #logMessage            -> the checkIn log message
    "

    |revLine1 atEnd|

    atEnd := false.

    revLine1 := inStream nextLine.
    ^ self readRevisionLogEntryFromString:revLine1.
!

readRevisionLogEntryFromString:revLine1
    "read and parse a single revision info-entry from the cvs log output.
     Return nil on end.

     The returned information is a structure (IdentityDictionary)
     filled with:
              #revision              -> the revision string
              #author                -> who checked that revision into the repository
              #date                  -> when was it checked in
              #state                 -> the RCS state
              #numberOfChangedLines  -> the number of changed line w.r.t the previous
              #logMessage            -> the checkIn log message
    "

    | record revisionLineElements noOfRevisionLineElements posText|

    (revLine1 notNil) ifTrue:[
        record := IdentityDictionary new.
        revisionLineElements := revLine1 asCollectionOfWords.
        noOfRevisionLineElements := revisionLineElements size.
        noOfRevisionLineElements > 1 ifTrue:[
            record at:#revision put:((revisionLineElements at:2) copyFrom:2).
        ].
        noOfRevisionLineElements > 8 ifTrue:[
            record at:#author put:(revisionLineElements at:9).
        ].
        noOfRevisionLineElements > 6 ifTrue:[
            record at:#date put:(revisionLineElements at:7).
        ].
        noOfRevisionLineElements > 4 ifTrue:[
            record at:#state put:(revisionLineElements at:5).
        ].
        noOfRevisionLineElements > 10 ifTrue:[
            posText := 0.
            1 to:9 do:[:ele| posText := posText + (revisionLineElements at:ele) size + 1].
            record at:#logMessage put:(revLine1 copyFrom:posText).
        ].
    ].
    ^record.
!

revisionLogOf:clsOrNil 
fromRevision:firstRev 
toRevision:lastRef 
numberOfRevisions:numRevisions 
fileName:classFileName 
directory:packageDir 
module:moduleName
    "return info about the repository container and
     (part of) the revisionlog as a collection of revision entries.
     Return nil on failure.

     If numRevisions is notNil, it limits the number of revision records returned -
     only numRevions of the newest revision infos will be collected.

     The returned information is a structure (IdentityDictionary)
     filled with:
            #newestRevision     -> the revisionString of the newest revision
            #numberOfRevisions  -> the number of revisions in the container (nil for all)
            #revisions          -> collection of per-revision info (see below)

            firstRev / lastRef specify from which revisions a logEntry is wanted:
             -If firstRev is nil, the first revision is the initial revision
              otherwise, the log starts with that revision.
             -If lastRef is nil, the last revision is the newest revision
              otherwise, the log ends with that revision.

             -If both are nil, all logEntries are extracted.
             -If both are 0 (not nil), no logEntries are extracted (i.e. only the header).

            per revision info consists of one record per revision:

              #revision              -> the revision string
              #author                -> who checked that revision into the repository
              #date                  -> when was it checked in
              #state                 -> the RCS state
              #numberOfChangedLines  -> the number of changed line w.r.t the previous
              #logMessage            -> the checkIn log message

            revisions are ordered newest first
            (i.e. the last entry is for the initial revision; the first for the most recent one)
            Attention: if state = 'dead' that revision is no longer valid.
        "

    |fullName inStream atEnd line inHeaderInfo workSpaceDefinition
     info record revisionRecords headerOnly msg revArg inDirectory infoAndLogString elements newestRevision foundView|


    [
        |cmd moduleDir|

        revArg := ''.
        headerOnly := false.
        (firstRev notNil or:[lastRef notNil]) ifTrue:[
            (firstRev == 0 and:[lastRef == 0]) ifTrue:[
                headerOnly := true.
            ]
        ].
        workSpaceDefinition := self getWorkSpaceForModule:moduleName.

        workSpaceDefinition isNil ifTrue:[
            self error:('Perforce cant get workspace definition for module ', moduleName, '.').
            ^ nil.
        ].
        headerOnly ifTrue:[
            msg := 'fetching revision info '
        ] ifFalse:[
            msg := 'reading revision log '
        ].
        foundView := workSpaceDefinition getDepotPackageDirDorModule:packageDir classFileName:classFileName.

        clsOrNil isNil ifTrue:[
            msg := msg , 'in ' , foundView.
        ] ifFalse:[
            msg := msg , 'of ', clsOrNil name.
        ].
        self activityNotification:msg,'...'.

        cmd := ('filelog ' , foundView).

        inDirectory := (Filename currentDirectory asAbsoluteFilename) pathName.
        inStream := self executePerforceCommand:cmd
                            module:moduleName
                            inDirectory:inDirectory
                            log:true
                            pipe:true.
        inStream isNil ifTrue:[
            ('PerforceSourceCodeManager [error]: cannot open pipe to perforce filelog ', fullName) errorPrintCR.
            ^ nil
        ].

        "/
        "/ read the commands pipe output and extract the container info
        "/
        info := IdentityDictionary new.
        inHeaderInfo := true.
        revisionRecords := OrderedCollection new.
        [inHeaderInfo and:[inStream atEnd not]] whileTrue:[
            line:= inStream nextLine.
            line notNil ifTrue:[
                |gotIt|

                gotIt := false.
                infoAndLogString := line asCollectionOfSubstringsSeparatedBy:$'.
                elements := infoAndLogString size.
                elements > 1 ifTrue:[
                    record := self readRevisionLogEntryFromString:line.
                    newestRevision := record at:#revision.
                    info at:#newestRevision put:newestRevision.
                    info at:#numberOfRevisions put:newestRevision asNumber.
                    revisionRecords add:record.
                    inHeaderInfo := false
                ].
            ]
        ].

        info isEmpty ifTrue:[
            ('PerforceSourceCodeManager [warning]: no log for ', foundView) errorPrintCR.
            ^ nil
        ].

        "/ strip selected revisions from the total-revisions entry
        headerOnly ifFalse:[
            "/
            "/ continue to read the commands pipe output
            "/ and extract revision info records
            "/
            info at:#revisions put:revisionRecords.

            atEnd := false.
            [atEnd or:[inStream atEnd]] whileFalse:[
                record := self readRevisionLogEntryFromStream:inStream.
                record isNil ifTrue:[
                    atEnd := true.
                ] ifFalse:[
                    revisionRecords add:record.
                ].
                (numRevisions notNil and:[revisionRecords size >= numRevisions]) ifTrue:[
                    atEnd := true
                ]
            ].
        ].
    ] ensure:[
        inStream notNil ifTrue:[inStream close].

        self activityNotification:nil.
    ].
    ^ info

    "
     AbstractSourceCodeManager revisionLogOf:ExtIF
     SourceCodeManager revisionLogOf:Array fromRevision:'1.40' toRevision:'1.43'
     SourceCodeManager revisionLogOf:Array fromRevision:'1.40' toRevision:nil
     SourceCodeManager revisionLogOf:Array fromRevision:nil toRevision:'1.3'
     SourceCodeManager revisionLogOf:Array fromRevision:nil toRevision:nil
     SourceCodeManager revisionLogOf:Array fromRevision:0 toRevision:0
    "

    "Created: / 16-11-1995 / 13:25:30 / cg"
    "Modified: / 29-01-1997 / 16:51:30 / stefan"
    "Modified: / 29-08-2006 / 14:57:26 / cg"
! !

!PerforceSourceCodeManager class methodsFor:'execute'!

executePerforceCommand:cvsCommand module:moduleName inDirectory:dir
    "execute command and prepend cvs command name and global options.
     if dir ~= nil, execute command in that directory.
     This also leads to a log-entry to be added to cvs's logfile."

    ^ self
        executePerforceCommand:cvsCommand
        module:moduleName
        inDirectory:dir
        log:true
!

executePerforceCommand:cvsCommand module:moduleName inDirectory:dir log:doLog
    "execute command and prepend cvs command name and global options.
     if dir ~= nil, execute command in that directory.
     The doLog argument, if false supresses a logEntry to be added
     in the cvs log file (used when reading / extracting history)"

    ^ self
        executePerforceCommand:cvsCommand module:moduleName inDirectory:dir log:doLog
        pipe:false
!

executePerforceCommand:perforceCommand module:moduleName inDirectory:dirArg log:doLog pipe:doPipe
    "execute command and prepend perforce command name and global options.
     execute command in the dirArg directory.
     The doLog argument, if false supresses a logEntry to be added
     in the cvs log file (used when reading / extracting history)"

    ^ self executePerforceCommand:perforceCommand module:moduleName inDirectory:dirArg log:doLog pipe:doPipe clientName:nil
!

executePerforceCommand:perforceCommand module:moduleName inDirectory:dirArg log:doLog pipe:doPipe clientName:clientName
    "execute command and prepend perforce command name and global options.
     execute command in the dirArg directory.
     The doLog argument, if false supresses a logEntry to be added
     in the cvs log file (used when reading / extracting history)"

    ^ self executePerforceCommand:perforceCommand module:moduleName inDirectory:dirArg log:doLog pipe:doPipe clientName:clientName inputFrom:nil.
!

executePerforceCommand:perforceCommand module:moduleName inDirectory:dirArg log:doLog pipe:doPipe clientName:clientName inputFrom:inputStream
    "execute command and prepend perforce command name and global options.
     execute command in the dirArg directory.
     The doLog argument, if false supresses a logEntry to be added
     in the cvs log file (used when reading / extracting history)"

    |command perforceSettings rslt ok pathOfDir errorString commandStream password user port client executable|

    dirArg notNil ifTrue:[
        pathOfDir := dirArg asFilename pathName.
    ].

    perforceSettings := self getPerforceSettingsForModule:moduleName.
    perforceSettings isNil ifTrue:[ ^ nil].

    commandStream := WriteStream on:''.
    executable := self perforceExecutable.
    (executable includes:Character space) ifTrue:[
        commandStream nextPut:$".
        commandStream nextPutAll:executable.
        commandStream nextPut:$".
    ] ifFalse:[
        commandStream nextPutAll:executable.
    ].
    commandStream space.
    port := perforceSettings at:#port ifAbsent:nil.
    port notNil ifTrue:[
        commandStream space.
        commandStream nextPutAll:'-p '.
        commandStream nextPutAll:(perforceSettings at:#port).
        commandStream space.
    ].
    clientName notNil ifTrue:[
        client := clientName.
    ] ifFalse:[
        client := perforceSettings at:#client ifAbsent:nil.
    ].
    client notEmptyOrNil ifTrue:[
        commandStream space.
        commandStream nextPutAll:'-c '.
        commandStream nextPutAll:client.
        commandStream space.
    ].
    user := perforceSettings at:#user ifAbsent:nil.
    user notNil ifTrue:[
        commandStream space.
        commandStream nextPutAll:'-u '.
        commandStream nextPutAll:(perforceSettings at:#user).
        commandStream space.
    ].
    password := perforceSettings at:#password ifAbsent:nil.
    password notNil ifTrue:[
        commandStream space.
        commandStream nextPutAll:'-P '.
        commandStream nextPutAll:(perforceSettings at:#password ifAbsent:'').
        commandStream space.
    ].
    commandStream nextPutAll:perforceCommand.

    command := commandStream contents.
    Verbose == true ifTrue:[
        ('PerforceSourceCodeManager [info]: executing: ' , command , ' [in ' , (pathOfDir?'.') , ']') infoPrintCR.
    ].
    doPipe ifTrue:[
        rslt := PipeStream readingFrom:command errorDisposition:#inline inDirectory:pathOfDir.
        ok := rslt notNil.
    ] ifFalse:[
        Processor isDispatching ifFalse:[
            rslt := ok := OperatingSystem executeCommand:command
                            inputFrom:inputStream
                            outputTo:nil
                            errorTo:nil
                            auxFrom:nil
                            inDirectory:pathOfDir
                            lineWise:true
                            onError:[:status| false].
        ] ifTrue:[
            PerforceCommandSemaphore critical:[
                |p errOut|

                errOut := WriteStream on:String new.
                p := [
                    rslt := ok := OperatingSystem executeCommand:command
                                    inputFrom:inputStream
                                    outputTo:nil
                                    errorTo:nil
                                    auxFrom:nil
                                    inDirectory:pathOfDir
                                    lineWise:true
                                    onError:[:status| false].
                ] fork.

                (p waitUntilTerminatedWithTimeout:300) ifTrue:[
                    ('PerforceSourceCodeManager [info]: command timeout: ' , command) errorPrintCR.
                    ok := false.
                    errorString := 'Perforce command timeout'.
                ] ifFalse:[
                    ok ifFalse:[
                        errorString := errOut contents.
                    ].
                ].
            ].
        ].
    ].

    ok ifFalse:[
        ('PerforceSourceCodeManager [info]: command failed: ' , command) errorPrintCR.

        SourceCodeManagerError isHandled ifTrue:[
            SourceCodeManagerError raiseErrorString:(errorString ? 'Perforce Error').
        ].
    ].
    ^ rslt.

    "Modified: / 23-04-1996 / 15:24:00 / stefan"
    "Created: / 20-05-1998 / 16:06:34 / cg"
    "Modified: / 29-09-2006 / 15:06:42 / cg"
! !

!PerforceSourceCodeManager class methodsFor:'private'!

checkinTroubleDialog:title message:message log:log abortable:abortable option:optionTitle
    "trouble checking in - open a dialog"

    ^ self
        checkinTroubleDialog:title
        message:message
        log:log
        abortable:abortable
        option:optionTitle
        option2:nil

    "Created: 10.12.1995 / 17:34:33 / cg"
    "Modified: 12.9.1996 / 02:39:06 / cg"
!

checkinTroubleDialog:title message:message log:log abortable:abortable option:optionTitle option2:optionTitle2
    ^self
        checkinTroubleDialog:title
        message:message
        log:log
        abortable:abortable
        option:optionTitle
        option2:optionTitle2
        option3:nil
!

checkinTroubleDialog:title message:message log:log abortable:abortable option:optionTitle option2:optionTitle2 option3:optionTitle3
    "trouble checking in - open a dialog"

    |l box list listView optionPressed option2Pressed option3Pressed|

    l := log collect:[:line | line withTabsExpanded].
    list := SelectionInList with:l.

    box := Dialog new.
    box label:(title).

    (box addTextLabel:message) borderWidth:0.

    listView := SelectionInListView on:list.
    listView disable.
    listView height:200.
    box addComponent:(HVScrollableView forView:listView miniScrollerH:true) tabable:false.
    box addVerticalSpace.

    abortable ifTrue:[
        box addAbortButton
    ].
    optionTitle notNil ifTrue:[
        box addOkButton:(Button label:optionTitle action:[optionPressed := true. box hide]).
    ].
    optionTitle2 notNil ifTrue:[
        box addOkButton:(Button label:optionTitle2 action:[option2Pressed := true. box hide]).
    ].
    optionTitle3 notNil ifTrue:[
        box addOkButton:(Button label:optionTitle3 action:[option3Pressed := true. box hide]).
    ].
    box addOkButton.

    box extent:(box preferredExtent).
    box minExtent:box extent.
    box maxExtent:box extent.

    box open.

    box destroy.
    optionPressed == true ifTrue:[^ #option].
    option2Pressed == true ifTrue:[^ #option2].
    option3Pressed == true ifTrue:[^ #option3].
    ^ box accepted

    "Created: 9.9.1996 / 19:12:45 / cg"
    "Modified: 12.9.1996 / 02:39:10 / cg"
!

createWorkspaceFor:checkInDefinition
    "
        create an temporary workspace for handle checkin
    "

    |workSpaceName workSpaceDefinitionFilename ws cmd foundView result
     workSpaceDefinition readStream moduleName modulePath directory|

    moduleName := checkInDefinition moduleName.
    modulePath := checkInDefinition modulePath.
    directory := checkInDefinition tempDirectory.
    workSpaceDefinition := self getWorkSpaceForModule:moduleName modulePath:modulePath.
    workSpaceDefinition isNil ifTrue:[
        self error:('Perforce cant get workspace definition for module ', moduleName, '.').
        ^ nil.
    ].
    directory exists ifFalse:[
        self error:('Perforce create workspace directory ', directory pathName, ' not exists.').
        ^ nil.
    ].
    foundView := workSpaceDefinition repositoryDir.
    workSpaceName := UUID genUUID displayString.
    workSpaceName := 'stxTestWorkSpace'.
    workSpaceDefinition workSpaceName:workSpaceName.
    workSpaceDefinitionFilename := directory asFilename construct:workSpaceName.
    workSpaceDefinition workSpaceDefinitionFilename:workSpaceDefinitionFilename.
    ws := workSpaceDefinitionFilename writeStream.
    ws nextPutAll:'Client: '.
    ws nextPutAll:workSpaceName.
    ws cr.
    ws nextPutAll:'Owner: '.
    ws nextPutAll:(workSpaceDefinition owner).
    ws cr.
    ws nextPutAll:'Host: '.
    ws nextPutAll:(workSpaceDefinition host).
    ws cr.
    ws nextPutAll:'Description: '.
    ws nextPutAll:'Used temporary for Smalltalk/X'.
    ws cr.
    ws nextPutAll:'Root: '.
    ws nextPutAll:directory asFilename pathName.
    ws cr.
    ws nextPutAll:'Options: '.
    ws nextPutAll:'allwrite noclobber nocompress unlocked nomodtime normdir'.
    ws cr.
    ws nextPutAll:'SubmitOptions: '.
    ws nextPutAll:'submitunchanged'.
    ws cr.
    ws nextPutAll:'LineEnd: '.
    ws nextPutAll:'local'.
    ws cr.
    ws nextPutAll:'View: '.
    ws nextPutAll:foundView.
    ws space.
    ws nextPutAll:'//', workSpaceName, '/'.
    (foundView endsWith:'...') ifTrue:[
        ws nextPutAll:'...'.
    ].
    ws cr.
    ws close.
    readStream := ReadStream on:workSpaceDefinitionFilename contents asString.
    cmd := 'client -i '.
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:directory pathName
                        log:true
                        pipe:false
                        clientName:nil
                        inputFrom:readStream.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: cannot create perforce client ', workSpaceDefinitionFilename baseName) errorPrintCR.
        ^ nil
    ].

    ^ workSpaceDefinition.
!

diffTextComment

    |ws|

    ws := WriteStream on:''.
    ws nextPutLine:'"/ ***************************************************************'.
    ws nextPutLine:'"/ This text contains your current versions code (blue)'.
    ws nextPutLine:'"/ merged with the conflicting code as found in the repository (red) which resulted'.
    ws nextPutLine:'"/ from some other checkin.'.
    ws nextPutLine:'"/ Each such conflict is surrounded by green text (like this paragraph).'.
    ws nextPutLine:'"/ '.
    ws nextPutLine:'"/ Please have a look at ALL the conflicts and fix things as appropriate.'.
    ws nextPutLine:'"/ Delete the green lines as a confirmation - I will not checkin the changed text,'.
    ws nextPutLine:'"/ unless no more green parts are present. This includes this comment at the top.'.
    ws nextPutLine:'"/ ***************************************************************'.
    ^ ws contents
!

getWorkSpaceDepotPrefixToModuleFrom:workSpaceDefinition
!

getWorkSpaceForModule:aModule
    "
        create an temporary workspace for handle checkin
    "

    ^ self getWorkSpaceForModule:aModule modulePath:nil
!

getWorkSpaceForModule:aModule modulePath:modulePath
    "
        create an temporary workspace for handle checkin
    "

    |cmd inStream line views nextKey root myBaseDirectory client localDir position
     newLocalDir foundDir foundView workSpaceDefinition pathToModule restAfterRoot|

    pathToModule := Smalltalk packageDirectoryForPackageId:aModule.
    workSpaceDefinition := WorkSpaceDefinition new.
    cmd := 'client -o'.
    myBaseDirectory := (Filename currentDirectory asAbsoluteFilename) pathName.
    inStream := self executePerforceCommand:cmd
                        module:aModule
                        inDirectory:myBaseDirectory
                        log:true
                        pipe:true.
    inStream isNil ifTrue:[
        ('PerforceSourceCodeManager [error]: cannot open pipe to perforce client ') errorPrintCR.
        ^ nil
    ].
    views := OrderedCollection new.
    [inStream atEnd not] whileTrue:[
        line:= inStream nextLine.
        line notEmptyOrNil ifTrue:[
                line first = $# ifFalse:[
                (line startsWith:'Owner:') ifTrue:[
                    workSpaceDefinition owner:line asCollectionOfWords second.
                ].
                (line startsWith:'Host:') ifTrue:[
                    workSpaceDefinition host:line asCollectionOfWords second.
                ].
                (line startsWith:'Client:') ifTrue:[
                    client := line asCollectionOfWords second.
                    workSpaceDefinition client:client.
                ].
                (line startsWith:'Root:') ifTrue:[
                    root := line asCollectionOfWords second.
                    workSpaceDefinition root:root.
                ].
                (line startsWith:'View:') ifTrue:[
                    nextKey := false.
                    [nextKey not and:[inStream atEnd not]] whileTrue:[
                        line:= inStream nextLine.
                        line notEmptyOrNil ifTrue:[
                            line first isSeparator ifTrue:[
                                views add:(line asCollectionOfWords).
                            ] ifFalse:[
                                nextKey := true.
                            ].
                        ].
                    ].
                ].
            ].
        ].
    ].

    views do:[:reposAndlocalDir |
        localDir := reposAndlocalDir second.
        position := localDir findString:client ifAbsent:nil.
        position isNil ifTrue:[
            ('PerforceSourceCodeManager [error]: cannot get client view') errorPrintCR.
            ^ nil
        ].
        restAfterRoot := (localDir copyFrom:(position + client size + 1)).
        newLocalDir := root asFilename construct:restAfterRoot.
        newLocalDir asAbsoluteFilename = pathToModule ifTrue:[
            foundDir := newLocalDir.
            foundView := reposAndlocalDir first.
        ]
    ].
    foundDir isNil ifTrue:[
        ('PerforceSourceCodeManager [error]: cannot open find my view in perforce client ') errorPrintCR.
        ^ nil
    ].
    workSpaceDefinition moduleName:aModule.
    workSpaceDefinition localDir:foundDir.
    workSpaceDefinition repositoryDir:foundView.
    ^ workSpaceDefinition.
!

initialCheckinFor:checkInDefinition

    |modulePath checkoutName fullFileName classFileName packageDir moduleName logMsg force s class cmd result|

    modulePath := checkInDefinition modulePath.
    checkoutName := checkInDefinition checkoutName.
    classFileName := checkInDefinition classFileName.
    class := checkInDefinition definitionClass.
    packageDir := checkInDefinition packageDir.
    moduleName := checkInDefinition moduleName.
    logMsg := checkInDefinition logMessage.
    force := checkInDefinition force.

    (class binaryRevision notNil) ifTrue:[
        (Dialog confirm:('Someone seems to have removed the source container for ',class name,'\\Force new checkin ?') withCRs) ifTrue:[
            class setBinaryRevision:nil.
            ^ self checkinClass:class fileName:classFileName directory:packageDir module:moduleName logMessage:logMsg force:force.
        ].
    ].
    "initial checkin here"
    fullFileName := checkInDefinition tempDirectory construct:checkoutName.
    fullFileName directory recursiveMakeDirectory.
    s := fullFileName writeStream.
    self fileOutSourceCodeOf:class on:s.
    s close.
    cmd := ('add  -t +k ' , checkoutName).
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:checkInDefinition tempDirectory
                        log:true
                        pipe:false
                        clientName:checkInDefinition workSpaceName.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: failed to add ', checkoutName)  errorPrintCR.
        ^ false
    ].
    ^ self submitModule:moduleName inDirectory:checkInDefinition tempDirectory logMessage:logMsg workSpaceDefinition:checkInDefinition workSpaceDefinition.
!

mergeOrResolveConflictsFor:checkInDefinition

    |modulePath checkoutName classFileName packageDir moduleName logMsg force class fileNameAndRev cmd result tempdir workSpaceName
     changesDict words fullFileName inStream line chunksPart s mySource mergedSource localRevision resultSource changesAsLogged msg
     answer checkInRepaired emphasizedText emSep diffTextComment didAccept editor repairedText|

    modulePath := checkInDefinition modulePath.
    checkoutName := checkInDefinition checkoutName.
    classFileName := checkInDefinition classFileName.
    class := checkInDefinition definitionClass.
    packageDir := checkInDefinition packageDir.
    tempdir := checkInDefinition tempDirectory.
    moduleName := checkInDefinition moduleName.
    logMsg := checkInDefinition logMessage.
    force := checkInDefinition force.
    workSpaceName := checkInDefinition workSpaceName.
    localRevision := checkInDefinition getLocalRevision.
    fullFileName := tempdir construct:checkoutName.

    fileNameAndRev := checkoutName, '#', localRevision printString.


    " first we need a sync to get resolve notification "
    cmd := ('sync -f ' , fileNameAndRev).
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:tempdir
                        log:true
                        pipe:false
                        clientName:workSpaceName.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: could not sync ', checkoutName) errorPrintCR.
        ^ false
    ].
    cmd := ('edit  ' , checkoutName).
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:tempdir
                        log:true
                        pipe:false
                        clientName:workSpaceName.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: could not sync ', checkoutName) errorPrintCR.
        ^ false
    ].

    "write my code"
    s := fullFileName writeStream.
    self fileOutSourceCodeOf:class on:s.
    s close.
    "before resolving we need a sync"
    cmd := ('sync ' , checkoutName).
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:tempdir
                        log:true
                        pipe:false
                        clientName:workSpaceName.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: could not sync ', checkoutName) errorPrintCR.
        ^ false
    ].

    cmd := ('resolve -af ' , checkoutName).
    inStream := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:tempdir
                        log:true
                        pipe:true
                        clientName:workSpaceName.


    inStream isNil ifTrue:[
        ('PerforceSourceCodeManager [error]: could not get Stream when resolving ', checkoutName) errorPrintCR.
        ^ false
    ].
    "check if we have conflicts"
    changesAsLogged := StringCollection new.
    [inStream atEnd not] whileTrue:[
        line:= inStream nextLine.
        line notNil ifTrue:[
            (line startsWith:'Diff chunks:') ifTrue:[
                changesAsLogged add:line.
                changesDict := Dictionary new.
                chunksPart := line copyFrom:('Diff chunks:' size + 1).
                (chunksPart asCollectionOfSubstringsSeparatedBy:$+) do:[:eachElement|
                    words := eachElement asCollectionOfWords.
                    changesDict at:words second asSymbol put:words first asNumber.
                ].
            ].
        ].
    ].
    s := WriteStream on:String new.
    self fileOutSourceCodeOf:class on:s.
    mergedSource := fullFileName readStream contents asString.
    mySource := s contents asString.
    (changesDict notNil and:[(changesDict at:#conflicting) > 0]) ifTrue:[
        "ooops must resolve conflicts"
        msg := self messageForConflictsInClass:class revision:localRevision.
        answer := self checkinTroubleDialog:'Version conflict'
             message:msg
             log:changesAsLogged
             abortable:false
             option:'show conflicts'
             option2:'resolve conflicts'.

        answer == #option ifTrue:[
            "/
            "/ show conflicts in a 3-way DiffTextView ...
            "/
            Diff3TextView
                openOnMergedText:mergedSource
                label:'your version (checkin attempt)'
                label:'original (base version)'
                label:'newest repository version'.
        ].

        checkInRepaired := false.
        answer == #option2 ifTrue:[
            "/
            "/ allow checkin of repair version
            "/ this is error prone ...
            "/
            "/
            "/ show merged version in an editor ...
            "/ ... accept will check it in.
            "/
            emphasizedText := mergedSource asStringCollection.
            emSep := (Array with:(#color->Color black)
                         with:(#backgroundColor->Color green)).
            emphasizedText := Diff3TextView
                        emphasizeMergedDiff3TextPerorce:emphasizedText
                        origEmphasize:(Array with:(#color->Color black)
                                          with:(#backgroundColor->Color yellow))
                        otherEmphasize:(Array with:(#color->Color white)
                                          with:(#backgroundColor->Color red))
                        yourEmphasize:(Array with:(#color->Color white)
                                          with:(#backgroundColor->Color red))
                        separatorEmphasize:emSep.

            diffTextComment := self diffTextComment.
            diffTextComment := (Text string:diffTextComment emphasis:emSep) asStringCollection.
            emphasizedText := diffTextComment , emphasizedText.

            didAccept := false. checkInRepaired := true.
            [didAccept not and:[checkInRepaired]] whileTrue:[
                editor := RCSConflictEditTextView
                            setupWith:emphasizedText
                            title:'Resolve conflicts in ' , checkoutName , ', then accept & close to checkin'.

                editor acceptAction:[:dummy |
                    repairedText := editor list.
                    didAccept := true.
                ].
                didAccept := false.
                editor topView openModal.

                didAccept ifFalse:[
                    (Dialog confirm:'You did not accept the new text. Edit again ?')
                    ifFalse:[
                        checkInRepaired := false.
                    ]
                ] ifTrue:[
                    "/ check if all green-stuff (separators) have been removed
                    (repairedText findFirst:[:line | line notNil and:[line notEmpty and:[(line emphasisAt:1) = emSep]]]) ~~ 0 ifTrue:[
                        self warn:'You have to look at ALL conflicts, and remove ALL green lines as a confirmation !!'.
                        didAccept := false.
                    ]
                ].
            ].
            resultSource := repairedText asString string.
        ].

        checkInRepaired ifTrue:[
            Transcript showCR:'checking in ' , checkoutName , ' (manually repaired version) ...'
        ] ifFalse:[
            'PerforceSourceCodeManager [warning]: cannot (for now) checkin; conflicts found' infoPrintCR.
            Transcript showCR:'checkin of ' , checkoutName , ' aborted (conflicting changes; repository unchanged)'.
            ^ true.
        ]
    ] ifFalse:[
        mySource = mergedSource ifTrue:[
            msg := self messageForNoChangesInClass:class.
            self checkinTroubleDialog:'Merging versions'
                           message:msg
                           log:changesAsLogged
                           abortable:false
                           option:nil.
        ] ifFalse:[
            msg := self messageForChangesInClass:class revision:localRevision.
            answer := self checkinTroubleDialog:'Merging versions'
                           message:msg
                           log:changesAsLogged
                           abortable:true
                           option:'Stop - see first'.
            answer ~~ true ifTrue:[
                answer == #option ifTrue:[
                    DiffCodeView
                        openOn:mySource
                        label:'current version'
                        and:mergedSource
                        label:'merged version'.

                ].
                Transcript showCR:'checkin aborted - (no merge; repository unchanged)'.
                ^ false.
            ].
            resultSource := mergedSource.
        ].
    ].
    "now we have a merge - lets get latest revision and write on it "
    cmd := ('revert ' , checkoutName).
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:tempdir
                        log:true
                        pipe:false
                        clientName:workSpaceName.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: could not revert ', checkoutName) errorPrintCR.
        ^ false
    ].

    fullFileName remove.
    cmd := ('sync -f ' , checkoutName).
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:tempdir
                        log:true
                        pipe:false
                        clientName:workSpaceName.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: could not sync ', checkoutName) errorPrintCR.
        ^ false
    ].
    cmd := ('edit ' , checkoutName).
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:tempdir
                        log:true
                        pipe:false
                        clientName:workSpaceName.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: could not edit ', checkoutName) errorPrintCR.
        ^ false
    ].
    "write my result"
    s := fullFileName writeStream.
    s nextPutAll:resultSource.
    s close.

    ^ self submitModule:moduleName inDirectory:tempdir logMessage:logMsg workSpaceDefinition:checkInDefinition workSpaceDefinition.
!

messageForChangesInClass:class revision:revisionNumber

    |msgStream|

    msgStream := WriteStream on:''.
    msgStream nextPutAll:'The source of '; nextPutAll:class className; nextPutAll:'has been changed in the meanwhile as listed below.'.
    msgStream cr.
    msgStream nextPutAll:'If you continue, your new changes (based upon rev. '; nextPutAll:revisionNumber printString; nextPutAll:') will be MERGED'.
    msgStream nextPutAll:'into the newest revision. This will combine the other version with your changes'.
    msgStream nextPutAll:'into a new common revision which may be different from both.'.
    msgStream nextPutAll:'Although this is a nice feature, it may fail to create the expected result in certain situations.'.
    msgStream cr.
    msgStream nextPutAll:'You should carefully check the result - by comparing the current version with the'.
    msgStream nextPutAll:'most recent version in the repository. If that does not contain an acceptable version,'.
    msgStream nextPutAll:'change methods as required and check in again.'.
    msgStream nextPutAll:'Be aware, that after that, the actual repository version is different from your current classes,'.
    msgStream nextPutAll:'and you should update your class from the repository.'.
    msgStream cr.
    msgStream nextPutAll:'Continue ?'.
    ^ msgStream contents
!

messageForConflictsInClass:class revision:revisionNumber

    |msgStream|

    msgStream := WriteStream on:''.
    msgStream nextPutAll:'The source of '; nextPutAll:class className; nextPutAll:'has been changed in the meanwhile as listed below.'.
    msgStream cr.
    msgStream nextPutAll:'Your new changes (based upon rev. '; nextPutAll:revisionNumber printString; nextPutAll:') CONFLICT with those changes'.
    msgStream cr.
    msgStream nextPutAll:'You should fix things by comparing your class with the most recent repository version'.
    msgStream nextPutAll:'and change your methods avoiding conflicts. The checkin again.'.
    msgStream cr.
    ^ msgStream contents
!

messageForNoChangesInClass:class

    |msgStream|

    msgStream := WriteStream on:''.
    msgStream nextPutAll:'The source of '; nextPutAll:class className; nextPutAll:'has been changed in the meanwhile as listed below.'.
    msgStream cr.
    msgStream nextPutAll:'I have merged your version with the newest repository version,'.
    msgStream nextPutAll:'and found no differences between the result and your current version'.
    msgStream nextPutAll:'(i.e. your version seemed up-to-date).'.
    ^ msgStream contents
!

postCheckInClass:class checkInDefinition:checkInDefinition

    |newestRevisionAfterSubmit checkoutName localRevision newRevisionLog|

    checkoutName := checkInDefinition checkoutName.
    localRevision := checkInDefinition getLocalRevision asNumber.
    checkInDefinition newestRevision:nil.
    newestRevisionAfterSubmit := checkInDefinition getNewestRevisionNumber.
    newestRevisionAfterSubmit isNil ifTrue:[
        ('PerforceSourceCodeManager [error]: failed to get revision log after checkin for ', checkoutName)  errorPrintCR.
        ^ false
    ].
    newestRevisionAfterSubmit > localRevision ifTrue:[
        newRevisionLog := self updatedRevisionStringOf:class forRevision:newestRevisionAfterSubmit with:class revisionInfo getVersionString.
        class updateVersionMethodFor:newRevisionLog.
        class revision ~= newestRevisionAfterSubmit asString ifTrue:[
            'PerforceSourceCodeManager [error]: failed to update revisionString' errorPrintCR.
            ^ false
        ]
    ] ifFalse:[
        self error:'ooops no new version ????'.
        self postCheckInClass:class.
    ].
    ^ true
!

standardCheckinFor:checkInDefinition localRevision:locRevision

    |modulePath checkoutName fullFileName classFileName packageDir moduleName
     logMsg force s class cmd result fileNameAndRev tempdir workSpaceName fullFileNameAndRev
    workSpaceDefinition newestRevision|

    modulePath := checkInDefinition modulePath.
    checkoutName := checkInDefinition checkoutName.
    classFileName := checkInDefinition classFileName.
    class := checkInDefinition definitionClass.
    packageDir := checkInDefinition packageDir.
    moduleName := checkInDefinition moduleName.
    newestRevision := checkInDefinition newestRevision.
    logMsg := checkInDefinition logMessage.
    force := checkInDefinition force.
    tempdir := checkInDefinition tempDirectory.
    workSpaceName := checkInDefinition workSpaceName.
    workSpaceDefinition := checkInDefinition workSpaceDefinition.
    fullFileName := tempdir construct:checkoutName.

    fileNameAndRev := checkoutName, '#', newestRevision printString.


    cmd := ('sync  ' , fileNameAndRev).
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:tempdir
                        log:true
                        pipe:false
                        clientName:workSpaceName.
    fullFileNameAndRev := tempdir construct:fileNameAndRev.
    fullFileName copyTo:fullFileNameAndRev.

    cmd := ('edit  ' , checkoutName).
    result := self executePerforceCommand:cmd
                        module:moduleName
                        inDirectory:tempdir
                        log:true
                        pipe:false
                        clientName:workSpaceName.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: failed to edit ', checkoutName)  errorPrintCR.
        ^ false
    ].
    s := fullFileName writeStream.
    self fileOutSourceCodeOf:class on:s.
    s close.
    result := self submitModule:moduleName inDirectory:tempdir logMessage:checkInDefinition logMessage workSpaceDefinition:workSpaceDefinition.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: failed to edit ', checkoutName)  errorPrintCR.
        ^ false
    ].
    ^ true
!

submitModule:moduleDir inDirectory:inDirectory logMessage:logMessage workSpaceDefinition:workSpaceDefinition

    |cmd changeListStream result workSpaceName changeListFile inStream logLines line lastLineWasFiles elements changes currentDefinition currentContent changeFiles readStream|

    workSpaceName := workSpaceDefinition at:#workSpaceName ifAbsent:nil.
    cmd := 'change -o'.
    inStream := self executePerforceCommand:cmd
                        module:moduleDir
                        inDirectory:inDirectory
                        log:true
                        pipe:true
                        clientName:workSpaceName.

    inStream isNil ifTrue:[
        ('PerforceSourceCodeManager [error]: could not get Stream from ', cmd) errorPrintCR.
        ^ false
    ].
    changes := Dictionary new.
    logLines := logMessage asStringCollection.
    changeListFile := inDirectory construct:'change'.
    changeListStream := changeListFile writeStream.
    lastLineWasFiles := false.
    [inStream atEnd not] whileTrue:[
        line:= inStream nextLine.
        line notNil ifTrue:[
            (line notEmpty and:[line first isSeparator or:[line first = $#]]) ifTrue:[
                currentContent := line.
            ] ifFalse:[
                elements := line asCollectionOfSubstringsSeparatedBy:$:.
                elements size > 1 ifTrue:[
                    currentDefinition := elements first.
                    currentContent := (line copyFrom:currentDefinition size + 2).
                ] ifFalse:[
                    currentContent := line.
                ].
            ].
            (currentDefinition notNil and:[currentDefinition = 'Files' and:[currentContent notEmptyOrNil]]) ifTrue:[
                elements := currentContent asCollectionOfWords.
                elements size > 2 ifTrue:[
                    changeFiles := changes at:elements second ifAbsent:nil.
                    changeFiles isNil ifTrue:[
                        changeFiles := OrderedCollection new.
                        changes at:elements third put:changeFiles.
                    ].
                    changeFiles add:elements first.
                ].
            ].
            (line includesString:'<enter description here>') ifTrue:[
                logLines do:[:aLine|
                    changeListStream nextPut:Character tab.
                    changeListStream nextPutLine:aLine.
                ].
            ] ifFalse:[
                changeListStream nextPutLine:line.
            ].
        ].
    ].
    changeListStream close.
    readStream := changeListFile contents asString readStream.
    cmd := ('submit -f submitunchanged -i ').
    result := self executePerforceCommand:cmd
                        module:moduleDir
                        inDirectory:inDirectory
                        log:true
                        pipe:false
                        clientName:workSpaceName
                        inputFrom:readStream.
    result ifFalse:[
        ('PerforceSourceCodeManager [error]: could not submit ', cmd) errorPrintCR.
    ].
    ^ result
!

updatedRevisionStringOf:aClass forRevision:newRevision with:originalVersionString
    "update a revision string"

    |versionInfo|

    originalVersionString isEmptyOrNil ifTrue:[^ nil].
    versionInfo := PerforceVersionInfo fromRCSString:originalVersionString.
    versionInfo revision:newRevision printString.
    ^ versionInfo getVersionString.



"
    self updatedRevisionStringOf:nil
            forRevision:'6'
            with:'$','Header','$'
"
! !

!PerforceSourceCodeManager class methodsFor:'queries'!

getPerforceClientForModule:aModuleName

    | settings settingsString|

    aModuleName isNil ifTrue:[^ nil].
    settingsString := self getPerforceSettingsForModule:aModuleName.
    settingsString isNil ifTrue:[^ PerforceClient].
    settings := self getPerforceSettingsFromString:settingsString.
    ^ settings at:#client ifAbsent:PerforceClient.
!

getPerforceDefaultSettingsString

    ^(PerforceSourceCodeManager perforceClient ,':',
       PerforceSourceCodeManager perforceUser, ':',
       (PerforceSourceCodeManager perforcePassword), '@',
       PerforceSourceCodeManager perforcePort).

    "Modified: / 19-04-2011 / 10:46:37 / cg"
!

getPerforcePasswordForModule:aModuleName

    | settings settingsString|

    aModuleName isNil ifTrue:[^ nil].
    settingsString := self getPerforceSettingsForModule:aModuleName.
    settingsString isNil ifTrue:[^ PerforcePassword].
    settings := self getPerforceSettingsFromString:settingsString.
    ^ settings at:#password ifAbsent:PerforcePassword.
!

getPerforcePortForModule:aModuleName

    | settings settingsString|

    aModuleName isNil ifTrue:[^ nil].
    settingsString := self getPerforceSettingsForModule:aModuleName.
    settingsString isNil ifTrue:[^ PerforcePort].
    settings := self getPerforceSettingsFromString:settingsString.
    ^ settings at:#port ifAbsent:PerforcePort.
!

getPerforceSettingsForModule:aModuleName

    |settingsString|

    PerforceModuleRoots isNil ifTrue:[^ nil].
    aModuleName isNil ifTrue:[^ nil].
    settingsString := PerforceModuleRoots at:aModuleName ifAbsent:nil.
    settingsString isNil ifTrue:[^ nil].
    ^ self getPerforceSettingsFromString:settingsString.
!

getPerforceSettingsFromString:aString

    |clientAndPort noOfClientAndPortElements userAndClientAndPassword noOfUserAndClient settings |

    settings := Dictionary new.
    clientAndPort := aString asCollectionOfSubstringsSeparatedBy:$@.
    noOfClientAndPortElements := clientAndPort size.
    noOfClientAndPortElements > 0 ifTrue:[
        userAndClientAndPassword := clientAndPort first asCollectionOfSubstringsSeparatedBy:$:.
        noOfUserAndClient := userAndClientAndPassword size.
        noOfUserAndClient > 0 ifTrue:[
            settings at:#client put:userAndClientAndPassword first.
        ].
        noOfUserAndClient > 1 ifTrue:[
            settings at:#user put:userAndClientAndPassword second.
        ].
        noOfUserAndClient > 2 ifTrue:[
            settings at:#password put:userAndClientAndPassword third.
        ].
    ].
    noOfClientAndPortElements > 1 ifTrue:[
        settings at:#port put:clientAndPort second.
    ].
    ^ settings
!

getPerforceUserForModule:aModuleName

    | settings settingsString|

    aModuleName isNil ifTrue:[^ nil].
    settingsString := self getPerforceSettingsForModule:aModuleName.
    settingsString isNil ifTrue:[^ PerforcePassword].
    settings := self getPerforceSettingsFromString:settingsString.
    ^ settings at:#password ifAbsent:PerforcePassword.
!

isPerforce
    "Superclass AbstractSourceCodeManager class says that I am responsible to implement this method"

    ^ true
!

managerTypeName
    "Superclass AbstractSourceCodeManager class says that I am responsible to implement this method"

    ^ 'Perforce'
!

nameOfVersionMethodForExtensions
    ^ #'extensionsVersion_P4'
!

nameOfVersionMethodInClasses
    ^ #'version_P4'
!

perforceTmpDirectory
    "return the name of the tmp repository.
     Thats the directory, where temporary files are created for checkin/checkout.
     If nil, the systems default tempDirectory is used."

    ^ (PerforceTempDir ? Filename tempDirectory pathName)

    "
     PerforceTempDir := nil
    "
!

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

    ^ PerforceSourceCodeManagementSettingsAppl

    "Created: / 19-04-2011 / 12:45:13 / cg"
    "Modified: / 20-04-2011 / 12:49:41 / cg"
! !

!PerforceSourceCodeManager 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 }"

    ^ PerforceVersionInfo fromRCSString:aString.

"
|stream|
stream := WriteStream on:''.
SourceCodeManagerUtilities repositoryLogOf:ExtIF onto:stream.
^ stream contents.
"
!

revisionLogOf:clsOrNil numberOfRevisions:numRevisions fileName:classFileName directory:packageDir module:moduleDir
    ^ self
        revisionLogOf:clsOrNil
        fromRevision:nil
        toRevision:nil
        numberOfRevisions:numRevisions
        fileName:classFileName
        directory:packageDir
        module:moduleDir
! !

!PerforceSourceCodeManager 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
! !

!PerforceSourceCodeManager::CheckInDefinition methodsFor:'accessing'!

classFileName
    ^ classFileName
!

classFileName:something
    classFileName := something.
!

definitionClass
    ^ definitionClass
!

definitionClass:something
    definitionClass := something.
!

force
    ^ force
!

force:something
    force := something.
!

logMessage
    ^ logMessage
!

logMessage:something
    logMessage := something.
!

manager

    ^ manager
!

manager:something
    manager := something.
!

moduleName
    ^ moduleName
!

moduleName:something
    moduleName := something.
!

newestRevision
    ^ newestRevision
!

newestRevision:something
    newestRevision := something.
!

packageDir
    ^ packageDir
!

packageDir:something
    packageDir := something.
!

setLogMessage:something
    something isNil ifTrue:[
        logMessage := ''.
    ] ifFalse:[
        logMessage := something asSingleByteStringIfPossible.
        logMessage bitsPerCharacter ~~ 8 ifTrue:[
            ^ false.
        ].
    ].
    ^ true
!

sourceFileName
    ^ sourceFileName
!

sourceFileName:something
    sourceFileName := something.
!

tempDirectory

    tempDirectory isNil ifTrue:[
        tempDirectory := self manager createTempDirectory:nil forModule:nil.
    ].
    ^ tempDirectory
!

tempDirectory:something
    tempDirectory := something.
!

workSpaceDefinition
    ^ workSpaceDefinition
!

workSpaceDefinition:something
    workSpaceDefinition := something.
! !

!PerforceSourceCodeManager::CheckInDefinition methodsFor:'actions'!

getBinaryRevision

    |locRevision |

    locRevision := definitionClass binaryRevision.
    ^ locRevision
!

getBinaryRevisionNumber

    |locRevision |

    locRevision := self getBinaryRevision.
    locRevision notNil ifTrue:[
        locRevision := locRevision asNumber.
    ].
    ^ locRevision
!

getLocalRevision

    |locRevision |

    locRevision := definitionClass revision.
    ^ locRevision
!

getLocalRevisionFromRepository

    |locRevision |

    locRevision := self manager newestRevisionOf:definitionClass.
    locRevision isNil ifTrue:[
        force ifTrue:[
            locRevision := self manager newestRevisionInFile:classFileName directory:packageDir module:moduleName.
            locRevision isNil ifTrue:[
                locRevision := '1'   "/ initial checkin
            ].
        ] ifFalse:[
            locRevision := '1'   "/ initial checkin
        ]
    ] ifFalse:[
        locRevision == #deleted ifTrue:[
            locRevision := '0'     "/ to force cvs-adding, which resurrects the file from the Attic
        ].
    ].
    ^ locRevision
!

getLocalRevisionNumber

    |locRevision |

    locRevision := self getLocalRevision.
    locRevision notNil ifTrue:[
        locRevision := locRevision asNumber.
    ].
    ^ locRevision
!

getLocalRevisionNumberFromRepository

    |locRevision |

    locRevision := self getLocalRevisionFromRepository.
    locRevision notNil ifTrue:[
        locRevision := locRevision asNumber.
    ].
    ^ locRevision
!

getNewestRevision

    newestRevision := self manager newestRevisionOf:definitionClass.
    ^ newestRevision
!

getNewestRevisionNumber

    newestRevision isNil ifTrue:[
        newestRevision := self getNewestRevision.
        newestRevision notNil ifTrue:[
            newestRevision := newestRevision asNumber.
        ].
    ].
    ^ newestRevision
! !

!PerforceSourceCodeManager::CheckInDefinition methodsFor:'queries'!

className

    ^ definitionClass name.
!

workSpaceDefinitionFilename

    workSpaceDefinition isNil ifTrue:[ ^ nil ].
    ^ workSpaceDefinition at:#workSpaceDefinitionFilename ifAbsent:nil.
! !

!PerforceSourceCodeManager::PerforceVersionInfo class methodsFor:'documentation'!

documentation
"
    Class used to return a Dictionary when asked for versionInfo.
    This has been replaced by instances of VersionInfo and subclasses.

    Notice, that CVSVersionInfo adds some CVS specific data.

    [author:]
        cg (cg@AQUA-DUO)
"
! !

!PerforceSourceCodeManager::PerforceVersionInfo class methodsFor:'instance creation'!

fromRCSString:aString
    "{ Pragma: +optSpace }"

    "I know how to parse RCS/CVS version id strings.
     Return an instance filled with revision info which is
     extracted from aString. This must be in RCS/CVS format."

    |words firstWord info nm indexOfLastHash|

    words := aString asCollectionOfWords.
    words size < 2 ifTrue:[
        ^ nil
    ].
    firstWord := words first.

    info := self new.

    "/
    "/ supported formats:
    "/
    "/ $-Header:   pathName#rev $

    (firstWord = '$Header:') ifTrue:[
        nm := words second.
        indexOfLastHash := nm lastIndexOf:$#.
        indexOfLastHash ~= 0 ifTrue:[
            info fileName:((nm copyTo:(indexOfLastHash - 1)) asFilename baseName).
            info repositoryPathName:(nm copyTo:(indexOfLastHash - 1)).
            info revision:((nm copyFrom:indexOfLastHash + 1) asCollectionOfWords first).
        ].
        ^ info
    ].


    ^ nil

    "
     PerforceVersionInfo fromRCSString:'$Header: /cvs/stx/stx/libbasic3/PerforceSourceCodeManager.st,v 1.10 2011-04-20 10:49:45 cg Exp $'
    "

    "Modified: / 22-10-2008 / 20:17:00 / cg"
! !

!PerforceSourceCodeManager::PerforceVersionInfo methodsFor:'accessing'!

repositoryPathName
    ^ repositoryPathName
!

repositoryPathName:something
    repositoryPathName := something.
!

state
    ^ ''
!

timeZone
    ^ ''
!

timezone
    ^ ''

    "Created: / 22-10-2008 / 20:50:39 / cg"
! !

!PerforceSourceCodeManager::PerforceVersionInfo methodsFor:'queries'!

getVersionString

    |stream|

    stream := WriteStream on:''.
    stream nextPutAll:'$Header:'.
    stream space.
    stream nextPutAll:repositoryPathName.
    stream nextPut:$#.
    stream nextPutAll:revision printString.
    stream space.
    stream nextPut:$$.
    ^ stream contents
! !

!PerforceSourceCodeManager::WorkSpaceDefinition methodsFor:'accessing'!

client
    ^ client
!

client:something
    client := something.
!

host
    ^ host
!

host:something
    host := something.
!

localDir
    ^ localDir
!

localDir:something
    localDir := something.
!

moduleName
    ^ moduleName
!

moduleName:something
    moduleName := something.
!

owner
    ^ owner
!

owner:something
    owner := something.
!

repositoryDir
    ^ repositoryDir
!

repositoryDir:something
    repositoryDir := something.
!

root
    ^ root
!

root:something
    root := something.
!

workSpaceDefinitionFilename
    ^ workSpaceDefinitionFilename
!

workSpaceDefinitionFilename:something
    workSpaceDefinitionFilename := something.
!

workSpaceName
    ^ workSpaceName
!

workSpaceName:something
    workSpaceName := something.
! !

!PerforceSourceCodeManager::WorkSpaceDefinition methodsFor:'queries'!

getDepotPackageDirDorModule:modulePath classFileName:classFileName

    |foundView localDirComponents localComponentsModulIndex|

    foundView := self repositoryDir.
    (foundView endsWith:'...') ifTrue:[
        foundView := foundView copyTo:(foundView size - 3).
    ].
    localDirComponents := localDir components.
    localComponentsModulIndex := localDirComponents findLast:[:aComponent| aComponent = moduleName].
    localComponentsModulIndex = 0 ifTrue:[
        ^ nil
    ].
    localDirComponents from:localComponentsModulIndex to:localDirComponents size do:[:aComponent|
        aComponent ~= '...' ifTrue:[
            foundView := foundView, '/', aComponent.
        ].
    ].
    modulePath notNil ifTrue:[
        foundView := foundView, '/', modulePath.
    ].
    classFileName notNil ifTrue:[
        foundView := foundView, '/', classFileName.
    ].
    ^foundView
! !

!PerforceSourceCodeManager class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic3/PerforceSourceCodeManager.st,v 1.10 2011-04-20 10:49:45 cg Exp $'
! !

PerforceSourceCodeManager initialize!