Use cvs rlog and cvs rls to avoid temp directory creation
authorStefan Vogel <sv@exept.de>
Wed, 22 Feb 2006 23:07:08 +0100
changeset 1457 8383e94050aa
parent 1456 673e4fc61c36
child 1458 ed654d80997f
Use cvs rlog and cvs rls to avoid temp directory creation Fetch symbolic name info.
CVSSourceCodeManager.st
--- a/CVSSourceCodeManager.st	Wed Feb 22 23:04:23 2006 +0100
+++ b/CVSSourceCodeManager.st	Wed Feb 22 23:07:08 2006 +0100
@@ -849,7 +849,17 @@
         pipe:false
 !
 
-executeCVSCommand:cvsCommand module:moduleName inDirectory:dirArg log:doLog errorTo:errorStream
+executeCVSCommand:cvsCommand module:moduleName inDirectory:dirArg log:doLog errorTo:errorStream 
+    ^ self 
+        executeCVSCommand:cvsCommand
+        module:moduleName
+        inDirectory:dirArg
+        log:doLog
+        outputTo:nil
+        errorTo:errorStream
+!
+
+executeCVSCommand:cvsCommand module:moduleName inDirectory:dirArg log:doLog outputTo:outStream errorTo:errorStream
     "execute command and prepend cvs command name and global options.
      execute command in the dirArg directory.
      The doLog argument, if false supresses a logEntry to be added 
@@ -857,8 +867,10 @@
 
     |command cvsRoot rslt ok pathOfDir p dir|
 
-    dir := dirArg asFilename.
-    pathOfDir := dir pathName.
+    dirArg notNil ifTrue:[
+        dir := dirArg asFilename.
+        pathOfDir := dir pathName.
+    ].
 
     cvsRoot := self getCVSROOTForModule:moduleName.
 
@@ -886,7 +898,7 @@
     Processor isDispatching ifFalse:[
         rslt := ok := OperatingSystem executeCommand:command 
                                 inputFrom:nil 
-                                outputTo:nil 
+                                outputTo:outStream 
                                 errorTo:errorStream 
                                 auxFrom:nil
                                 inDirectory:pathOfDir
@@ -896,7 +908,7 @@
         p := [
             rslt := ok := OperatingSystem executeCommand:command
                                 inputFrom:nil 
-                                outputTo:nil 
+                                outputTo:outStream 
                                 errorTo:errorStream 
                                 auxFrom:nil
                                 inDirectory:pathOfDir
@@ -926,10 +938,11 @@
      The doLog argument, if false supresses a logEntry to be added 
      in the cvs log file (used when reading / extracting history)"
 
-    |command cvsRoot rslt ok pathOfDir p dir|
-
-    dir := dirArg asFilename.
-    pathOfDir := dir pathName.
+    |command cvsRoot rslt ok pathOfDir p|
+
+    dirArg notNil ifTrue:[    
+        pathOfDir := dirArg asFilename pathName.
+    ].
 
     cvsRoot := self getCVSROOTForModule:moduleName.
 
@@ -1033,6 +1046,78 @@
     "Modified: / 18.1.2000 / 20:21:32 / cg"
 !
 
+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 revLine2 record s line atEnd|
+
+    atEnd := false.
+
+    revLine1 := inStream nextLine.
+    [revLine1 notNil and:[(revLine1 startsWith:'revision ') not]]
+        whileTrue:[inStream atEnd ifTrue:[
+                    revLine1 := nil
+                   ] ifFalse:[
+                    revLine1 := inStream nextLine.
+                  ]
+    ].
+    revLine2 := inStream nextLine.
+    (revLine1 notNil and:[revLine2 notNil]) ifTrue:[
+        record := IdentityDictionary new.
+        record at:#revision put:(revLine1 asCollectionOfWords at:2).
+        "/ decompose date/author/state etc.
+        (revLine2 asCollectionOfSubstringsSeparatedBy:$;) do:[:info |
+            |subEntry|
+            subEntry := info withoutSeparators.
+            #('date:'   #date
+              'author:' #author 
+              'state:'  #state 
+              'lines:'  #numberOfChangedLines
+             ) pairWiseDo:[:word :key |
+                s := subEntry restAfter:word withoutSeparators:true.
+                s notNil ifTrue:[record at:key put:s.].                        
+            ].
+        ].
+
+        "first revision does not hav a 'lines:' entry"
+        (record includesKey:#numberOfChangedLines) ifFalse:[
+            record at:#numberOfChangedLines put:''
+        ].
+
+        s := nil.
+        line := inStream nextLine.
+        [atEnd or:[line isNil or:[line startsWith:'--------']]] whileFalse:[
+            (line startsWith:'==========') ifTrue:[
+                atEnd := true.
+            ] ifFalse:[
+                (line withoutSpaces = '.') ifTrue:[
+                    line := '*** empty log message ***'
+                ].
+                s isNil ifTrue:[
+                    s := line
+                ] ifFalse:[
+                    s := s , Character cr asString , line.
+                ].
+                line := inStream nextLine.
+            ]
+        ].
+        record at:#logMessage put:s.
+    ].
+    ^record.
+
+!
+
 releaseAndRemove:tempdir module:moduleDir outputTo:outputFilename
     "cleanup; release tree towards cvs and remove the temporary tree"
 
@@ -2559,11 +2644,11 @@
 
     |fullName ret cvsRoot cmd tempDir|
 
-    cvsRoot := self getCVSROOTForModule:moduleDir.
 
     fullName := moduleDir , '/' , packageDir , '/' , fileName.
 
     RemoteCVS ifFalse:[
+        cvsRoot := self getCVSROOTForModule:moduleDir.
         cvsRoot asFilename exists ifTrue:[
             "/
             "/ with local CVS - simply check if that file exists
@@ -3275,276 +3360,48 @@
     "Modified: / 18.1.2000 / 20:14:01 / cg"
 !
 
+deleteSymbolicName:symbolicName fileName:classFileName directory:packageDir module:moduleDir
+    "remove symbolicName from classFileName"
+
+    self setSymbolicName:symbolicName revision:0 overWrite:false fileName:classFileName directory:packageDir module:moduleDir
+
+    "
+        self deleteSymbolicName:'stable' fileName:'Array.st' directory:'libbasic' module:'stx'
+        self deleteSymbolicName:'testBLAbla' fileName:nil directory:'libbasic' module:'stx'
+    "
+!
+
 getExistingContainersInModule:aModule package:aPackage
-    "return a list of existing containers.
-     This does not work with remote-CVS"
-
-    |cvsRoot containers moduleDir packageDir tempdir cmdOut cmd dirName|
-
-    cvsRoot := self getCVSROOTForModule:aModule.
-    cvsRoot isNil ifTrue:[^ #() ].
-
-    dirName := aModule , '/' , aPackage.
-
-    self activityNotification:'getting list of containers in ' , dirName , ' ...'.
-
-    (RemoteCVS 
-    or:[cvsRoot asFilename exists not]) ifTrue:[
-        "/ remote CVS
-        "/ filter the output of the history command
-        "/ (sigh - there ought to be some cvs-command for that)
-        "/
-
-        tempdir := self createTempDirectory:nil forModule:nil.
-        tempdir isNil ifTrue:[
-            ('CVSSourceCodeManager [error]: no tempDir - cannot checkout') errorPrintCR.
-            ^ #()
-        ].
-
-        cmd := 'checkout ', dirName.
-        OperatingSystem isUNIXlike ifTrue:[
-            "/ can redirect output
-            cmdOut := Filename newTemporary.
-            cmdOut exists ifTrue:[
-                cmdOut remove.
-            ].
-            cmd := cmd , ' > ' , cmdOut name.
-        ].
-
-        (self 
-            executeCVSCommand:cmd 
-            module:aModule
-            inDirectory:tempdir name
-        ) ifFalse:[
-            'CVSSourceCodeManager [error]: failed to execute: ' errorPrint. cmd errorPrintCR.
-            cmdOut notNil ifTrue:[cmdOut remove].
-            tempdir recursiveRemove.
-            ^ #()
-        ].
-
-        cmdOut notNil ifTrue:[cmdOut remove].
-
-        packageDir := (tempdir construct:dirName).
-        (packageDir isDirectory) ifFalse:[
-            'CVSSourceCodeManager [error]: checkout failed (no dir)' errorPrintCR.
-            tempdir recursiveRemove.
-            ^ #()
-        ].
-
-        "/
-        "/ enumerate the checkedOut directory, looking for plain files
-        "/
-        containers := OrderedCollection new.
-        packageDir directoryContents do:[:aFilenameString |
-            |fn|
-
-            (packageDir construct:aFilenameString) isDirectory ifFalse:[
-                containers add:aFilenameString
-            ]
-        ].
-        tempdir recursiveRemove.
-    ] ifFalse:[
-        (cvsRoot := cvsRoot asFilename) exists ifFalse:[
-            ^ #()
-        ].
-        ((moduleDir := cvsRoot construct:aModule) exists
-        and:[moduleDir isDirectory]) ifFalse:[
-            self warn:'No such module'.
-            ^ #()
-        ].
-        ((packageDir := moduleDir construct:aPackage) exists
-        and:[packageDir isDirectory]) ifFalse:[
-            self warn:'No such package'.
-            ^ #()
-        ].
-
-        "/
-        "/ enumerate the package directory, looking for container files
-        "/ strip off the ,v ending.
-        "/
-        containers := OrderedCollection new.
-        packageDir directoryContents do:[:aFilenameString |
-            |fn|
-
-            (aFilenameString endsWith:',v') ifTrue:[
-                containers add:(aFilenameString copyWithoutLast:2)
-            ]
-        ].
-    ].
-    ^ containers sort
+    "return a list of existing containers."
+
+    ^ self listDirectories:aModule, '/', aPackage
 
     "
      CVSSourceCodeManager getExistingContainersInModule:'stx' package:'libhtml'
      CVSSourceCodeManager getExistingContainersInModule:'cg'  package:'java'
-     CVSSourceCodeManager getExistingContainersInModule:'sel' package:'bmti'
+     CVSSourceCodeManager getExistingContainersInModule:'exept' package:'osi'
     "
-
-    "Created: / 20.5.1998 / 19:48:59 / cg"
-    "Modified: / 20.5.1998 / 22:08:29 / cg"
 !
 
 getExistingModules
-    "return a list of existing modules.
-     This does not work with remote-CVS"
-
-    |cvsRoot modules inStream list|
-
-    cvsRoot := self getCVSROOTForModule:nil.
-    cvsRoot isNil ifTrue:[^ #() ].
-
-    self activityNotification:'getting list of modules...'.
-
-    (RemoteCVS 
-    or:[cvsRoot asFilename exists not]) ifTrue:[
-        "/ remote CVS
-        "/ filter the output of the history command
-        "/ (sigh - there ought to be some cvs-command for that)
-        "/
-        inStream := PipeStream readingFrom:'cvs -d ' , cvsRoot , ' history -x A'.
-        inStream isNil ifTrue:[
-            self warn:'This operation is not possible with this remoteCVS server'.
-            ^ #().
-        ].
-        list := inStream contents asStringCollection.
-        inStream close.
-
-        modules := Set new.
-        list do:[:line |
-            |idx items entry|
-
-            items := line asCollectionOfWords.
-            "/ #( 'A' '10/29' '17:47' '+0000' 'cg' '1.1' '.cvsignore' 'stx' '==' '~/work/stx' )
-            "/ fetch the word before '=='
-        
-            idx := items indexOf:'=='.
-            idx > 1 ifTrue:[
-                entry := items at:idx-1.
-
-                "/ extract the first directory component ...
-                idx := entry indexOf:$/.
-                idx ~~ 0 ifTrue:[
-                    entry := entry copyTo:idx-1
-                ].
-                modules add:entry.
-            ]
-        ].
-        modules := modules asArray
-    ] ifFalse:[
-        "/ local CVS
-        "/
-        "/ enumerate the root directory, looking for subdirs
-        "/ which contain a CVS subdir.
-        "/
-        (cvsRoot := cvsRoot asFilename) exists ifFalse:[
-            ^ #()
-        ].
-
-        modules := OrderedCollection new.
-        cvsRoot directoryContents do:[:aFilenameString |
-            |fn|
-
-            (aFilenameString endsWith:',v') ifFalse:[
-                (#('CVS' 'CVSROOT' 'Attic') includes:aFilenameString) ifFalse:[
-                    (fn := (cvsRoot construct:aFilenameString)) isDirectory ifTrue:[
-                        modules add:aFilenameString
-                    ]
-                ]
-            ]
-        ].
-    ].
-
-    ^ modules sort
+    "return a list of existing modules"
+
+    ^ self listDirectories:nil.
 
     "
      CVSSourceCodeManager getExistingModules
     "
-
-    "Created: / 20.5.1998 / 19:28:43 / cg"
-    "Modified: / 20.5.1998 / 22:07:07 / cg"
 !
 
 getExistingPackagesInModule:aModule
-    "return a list of existing packages.
-     This does not work with remote-CVS"
-
-    |cvsRoot packages moduleDir inStream list|
-
-    cvsRoot := self getCVSROOTForModule:aModule.
-
-    self activityNotification:'getting list of packages in ' , aModule , ' ...'.
-
-    (RemoteCVS 
-    or:[cvsRoot asFilename exists not]) ifTrue:[
-        "/ remote CVS
-        "/ filter the output of the history command
-        "/ (sigh - there ought to be some cvs-command for that)
-        "/
-        inStream := PipeStream readingFrom:'cvs -d ' , cvsRoot , ' history -x A'.
-        inStream isNil ifTrue:[
-            self warn:'This operation is not possible with this remoteCVS server'.
-            ^ #().
-        ].
-        list := inStream contents asStringCollection.
-        inStream close.
-
-        packages := Set new.
-        list do:[:line |
-            |items idx entry|
-
-            items := line asCollectionOfWords.
-            "/ #( 'A' '10/29' '17:47' '+0000' 'cg' '1.1' '.cvsignore' 'stx' '==' '~/work/stx' )
-            "/ fetch the word before '=='
-
-            idx := items indexOf:'=='.
-            idx > 1 ifTrue:[
-                entry := items at:idx-1.
-
-                "/ extract the first directory component ...
-                (entry startsWith:aModule) ifTrue:[
-                    idx := entry indexOf:$/.
-                    idx ~~ 0 ifTrue:[
-                        (entry copyTo:idx-1) = aModule ifTrue:[
-                            packages add:(entry copyFrom:idx+1).
-                        ]
-                    ].
-                ]
-            ]
-        ].
-        packages := packages asArray
-    ] ifFalse:[
-        "/ local CVS
-        "/
-        "/ enumerate the module directory, looking for subdirs
-        "/ which contain a CVS subdir.
-        "/
-
-        (cvsRoot := cvsRoot asFilename) exists ifFalse:[
-            ^ #()
-        ].
-        (moduleDir := cvsRoot construct:aModule) isDirectory ifFalse:[
-            self warn:'No such module'.
-            ^ #()
-        ].
-
-        packages := OrderedCollection new.
-        moduleDir directoryContents do:[:aFilenameString |
-            |fn|
-
-            (aFilenameString endsWith:',v') ifFalse:[
-                (#('CVS' 'CVSROOT' 'Attic') includes:aFilenameString) ifFalse:[
-                    (fn := (moduleDir construct:aFilenameString)) isDirectory ifTrue:[
-                        packages add:aFilenameString
-                    ]
-                ]
-            ]
-        ].
-    ].
-    ^ packages sort
+    "return a list of existing packages."
+
+    ^ self listDirectories:aModule.
 
     "
      CVSSourceCodeManager getExistingPackagesInModule:'stx'
      CVSSourceCodeManager getExistingPackagesInModule:'cg'
-     CVSSourceCodeManager getExistingPackagesInModule:'sel'
+     CVSSourceCodeManager getExistingPackagesInModule:'exept'
     "
 
     "Created: / 20.5.1998 / 19:28:43 / cg"
@@ -3567,99 +3424,113 @@
     "Modified: / 16.1.1998 / 17:34:13 / stefan"
 !
 
+listDirectories:cvsPath
+    "return a list of all directories in cvsPath.
+     cvsPath is the path relative to the cvs root"
+
+    |cvsRoot directories inStream line|
+
+    cvsRoot := self getCVSROOTForModule:nil.
+    cvsRoot isNil ifTrue:[^ #()].
+
+    self activityNotification:'getting list of directories...'.
+    directories := Set new.
+
+    [
+        inStream := self 
+                        executeCVSCommand:('rls -l ' , (cvsPath ? '')) 
+                        module:nil 
+                        inDirectory:nil 
+                        log:false 
+                        pipe:true.
+
+        inStream isNil ifTrue:[
+            self warn:'This operation is not possible with this remoteCVS server'.
+            ^ #().
+        ].
+
+        [line := inStream nextLine. line notNil] whileTrue:[
+            |idx|
+
+            "/ 'd--- 2005-06-02 17:21:20 +0200 Eigene Dateien'
+        
+            (line startsWith:$d) ifTrue:[
+                idx := 0.
+                4 timesRepeat:[
+                    idx := line indexOf:Character space startingAt:idx+1.
+                ].
+                directories add:(line copyFrom:idx+1) withoutSeparators
+            ]
+        ].
+    ] ensure:[
+        inStream notNil ifTrue:[
+            inStream close.
+        ]
+    ].
+
+    ^ directories asArray sort
+
+    "
+     CVSSourceCodeManager listDirectories:nil
+     CVSSourceCodeManager listDirectories:'stx'
+     CVSSourceCodeManager listDirectories:'stx/libbasic'
+    "
+!
+
 newestRevisionInFile:classFileName directory:packageDir module:moduleDir
     "return the newest revision found in a container.
-     Return nil on failure.
-     Uses 'cvs status', which is much faster than 'cvs log'"
-
-    |info|
-
-    info := self
-            statusOf:nil 
-            fileName:classFileName 
-            directory:packageDir 
-            module:moduleDir.
-
-    info isNil ifTrue:[^ nil].
-    ^ info at:#newestRevision ifAbsent:nil
+     Return nil on failure."
+
+    |tempDir fullName modulePath inStream line s|
+
+    modulePath :=  moduleDir , '/' , packageDir. 
+    fullName :=  modulePath , '/' , classFileName.
+
+    [
+        self activityNotification:'Fetching revision info for ', fullName.
+
+        inStream := self 
+                        executeCVSCommand:('rlog -h -N ' , fullName) 
+                        module:moduleDir 
+                        inDirectory:tempDir 
+                        log:true 
+                        pipe:true.
+
+        inStream isNil ifTrue:[
+            ('CVSSourceCodeManager [error]: cannot open pipe to cvs log ', fullName) errorPrintCR.
+            ^ nil
+        ].
+
+        "/
+        "/ read the commands pipe output and extract the container info
+        "/
+        [inStream atEnd] whileFalse:[
+            line:= inStream nextLine.
+            line notNil ifTrue:[
+                line := line withoutSeparators.
+            ].
+            line notEmpty ifTrue:[
+                s := line restAfter:'head:' withoutSeparators:true.
+                s notNil ifTrue:[ |i|
+                    i := s indexOfSeparator.
+                    i ~~ 0 ifTrue:[
+                        s := s copyTo:i-1
+                    ].
+                    ^ s
+                ].                        
+            ]
+        ].
+        ('CVSSourceCodeManager [warning]: no revision for ', fullName) errorPrintCR.
+    ] ensure:[
+        inStream notNil ifTrue:[inStream close].
+    ].
+    ^ nil
 
     "
      SourceCodeManager newestRevisionInFile:'Array.st' directory:'libbasic' module:'stx'       
     "
 !
 
-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 revLine2 record s line atEnd|
-
-    atEnd := false.
-
-    revLine1 := inStream nextLine.
-    [revLine1 notNil and:[(revLine1 startsWith:'revision ') not]]
-        whileTrue:[inStream atEnd ifTrue:[
-                    revLine1 := nil
-                   ] ifFalse:[
-                    revLine1 := inStream nextLine.
-                  ]
-    ].
-    revLine2 := inStream nextLine.
-    (revLine1 notNil and:[revLine2 notNil]) ifTrue:[
-        record := IdentityDictionary new.
-        record at:#revision put:(revLine1 asCollectionOfWords at:2).
-        "/ decompose date/author/state etc.
-        (revLine2 asCollectionOfSubstringsSeparatedBy:$;) do:[:info |
-            |subEntry|
-            subEntry := info withoutSeparators.
-            #('date:'   #date
-              'author:' #author 
-              'state:'  #state 
-              'lines:'  #numberOfChangedLines
-             ) pairWiseDo:[:word :key |
-                s := subEntry restAfter:word withoutSeparators:true.
-                s notNil ifTrue:[record at:key put:s.].                        
-            ].
-        ].
-
-        "first revision does not hav a 'lines:' entry"
-        (record includesKey:#numberOfChangedLines) ifFalse:[
-            record at:#numberOfChangedLines put:''
-        ].
-
-        s := nil.
-        line := inStream nextLine.
-        [atEnd or:[line isNil or:[line startsWith:'--------']]] whileFalse:[
-            (line startsWith:'==========') ifTrue:[
-                atEnd := true.
-            ] ifFalse:[
-                (line withoutSpaces = '.') ifTrue:[
-                    line := '*** empty log message ***'
-                ].
-                s isNil ifTrue:[
-                    s := line
-                ] ifFalse:[
-                    s := s , Character cr asString , line.
-                ].
-                line := inStream nextLine.
-            ]
-        ].
-        record at:#logMessage put:s.
-    ].
-    ^record.
-
-!
-
 removeContainerFor:aClass inModule:moduleDir package:packageDir container:fileName
     "remove a container"
 
@@ -4058,21 +3929,8 @@
 
     modulePath :=  moduleDir , '/' , packageDir. 
     fullName :=  modulePath , '/' , classFileName.
-    tempDir := self createTempDirectory:nil forModule:nil.
-    tempDir isNil ifTrue:[
-        ('CVSSourceCodeManager [error]: no tempDir - cannot extract log') errorPrintCR.
-        ^ nil.
-    ].
 
     [
-        self createEntryFor:fullName 
-             module:moduleDir
-             in:(tempDir construct:modulePath) 
-             revision:'1.1' 
-             date:'dummy' 
-             special:''
-             overwrite:false.
-
         revArg := ''.
         headerOnly := false.
         (firstRev notNil or:[lastRef notNil]) ifTrue:[
@@ -4104,7 +3962,7 @@
         self activityNotification:msg.
 
         inStream := self 
-                        executeCVSCommand:('log ' , revArg , ' ' , fullName) 
+                        executeCVSCommand:('rlog ' , revArg , ' ' , fullName) 
                         module:moduleDir 
                         inDirectory:tempDir 
                         log:true 
@@ -4191,11 +4049,6 @@
         ].
     ] ensure:[
         inStream notNil ifTrue:[inStream close].
-        OperatingSystem accessDeniedErrorSignal handle:[:ex |
-            ('CVSSourceCodeManager [warning]: could not remove tempDir ', tempDir pathName) infoPrintCR.
-        ] do:[
-            tempDir recursiveRemove
-        ].
     ].
     ^ info
 
@@ -4224,6 +4077,63 @@
         module:moduleDir
 !
 
+setSymbolicName:symbolicName revision:rev overWrite:overWriteBool fileName:filename directory:packageDir module:moduleDir
+    "set a symbolicName for revision rev.
+     If rev is nil, set it for the head (most recent) revision.
+     If rev is 0, delete the symbolic name.
+     If overWriteBool is true, the symbolicName will be changed, even if it has already been set.
+     If overWriteBool is false, an error will be raised if symbolicName has already been set.
+
+     If filename is nil, the symbolicName for a whole package is set"
+
+    |fullName modulePath inStream argumentString result tempDir errorStream outStream|
+
+    modulePath :=  moduleDir , '/' , packageDir.
+    filename notNil ifTrue:[
+        fullName :=  modulePath , '/' , filename.
+    ] ifFalse:[
+        fullName := modulePath.
+    ].
+
+    rev = 0 ifTrue:[
+        argumentString := ' -d '.
+    ] ifFalse:[
+        argumentString := ' -r ', (rev ? 'HEAD').
+        overWriteBool ifTrue:[
+            argumentString := argumentString, ' -F'
+        ].
+    ].
+
+    [
+        self activityNotification:'setting symbolic name ', fullName.
+
+        errorStream := '' writeStream.
+        outStream := '' writeStream.
+
+        result := self  executeCVSCommand:('rtag ' , argumentString, ' ', symbolicName, ' ', fullName) 
+                        module:moduleDir 
+                        inDirectory:tempDir 
+                        log:true
+                        outputTo:outStream
+                        errorTo:errorStream.
+        (result not or:[errorStream size ~~ 0]) ifTrue:[
+            SourceCodeManagerError raiseWith:errorStream contents errorString:' cvs tag failed: ', fullName.
+        ].
+        (outStream contents asStringCollection contains:[:eachLine| eachLine startsWithAnyOf:'WE']) ifTrue:[
+            SourceCodeManagerError raiseWith:outStream contents errorString:' cvs tag could not be set: ', fullName.
+        ].
+    ] ensure:[
+        inStream notNil ifTrue:[inStream close].
+    ].
+
+    "
+        self setSymbolicName:'stable' revision:nil overWrite:false fileName:'Array.st' directory:'libbasic' module:'stx'
+        self setSymbolicName:'stable' revision:nil overWrite:true fileName:'Array.st' directory:'libbasic' module:'stx'
+        self setSymbolicName:'stable' revision:nil overWrite:true fileName:nil directory:'libbasic' module:'stx'
+        self setSymbolicName:'stable' revision:'1.1' overWrite:true fileName:'Array.st' directory:'libbasic' module:'stx'
+    "
+!
+
 statusOf:clsOrNil fileName:classFileName directory:packageDir module:moduleDir
     "return info about the status repository container.
      Return nil on failure.
@@ -4327,7 +4237,7 @@
 !CVSSourceCodeManager class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/CVSSourceCodeManager.st,v 1.296 2006-02-01 22:16:35 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic3/CVSSourceCodeManager.st,v 1.297 2006-02-22 22:07:08 stefan Exp $'
 ! !
 
 CVSSourceCodeManager initialize!