CVSSourceCodeManager.st
branchjv
changeset 4166 66a7a47f9253
parent 4114 400f59aa641f
parent 4157 3eb587af122a
child 4168 2ec8d1bba408
--- a/CVSSourceCodeManager.st	Wed Sep 07 16:04:00 2016 +0100
+++ b/CVSSourceCodeManager.st	Mon Nov 28 17:11:46 2016 +0000
@@ -23,6 +23,13 @@
 	category:'System-SourceCodeManagement'
 !
 
+VersionInfo subclass:#CVSVersionInfo
+	instanceVariableNames:'repositoryPathName timeZone changedLinesInfo'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:CVSSourceCodeManager
+!
+
 !CVSSourceCodeManager class methodsFor:'documentation'!
 
 copyright
@@ -1324,7 +1331,7 @@
     "read and parse a single revision info-entry from the cvs log output.
      Return nil on end.
 
-     The returned information is a structure (IdentityDictionary)
+     The returned information is a CVSVersionInfo object (used to be an IdentityDictionary)
      filled with:
               #revision              -> the revision string
               #author                -> who checked that revision into the repository
@@ -1348,7 +1355,7 @@
     ].
     revLine2 := inStream nextLine.
     (revLine1 notNil and:[revLine2 notNil]) ifTrue:[
-        record := IdentityDictionary new.
+        record := CVSVersionInfo "IdentityDictionary" new.
         record at:#revision put:(revLine1 asCollectionOfWords at:2).
         "/ decompose date/author/state etc.
         (revLine2 asCollectionOfSubstringsSeparatedBy:$;) do:[:info |
@@ -1367,8 +1374,8 @@
             ].
         ].
 
-        "first revision does not hav a 'lines:' entry"
-        (record includesKey:#numberOfChangedLines) ifFalse:[
+        "first revision does not have a 'lines:' entry"
+        (record at:#numberOfChangedLines ifAbsent:[nil]) isNil ifTrue:[
             record at:#numberOfChangedLines put:''
         ].
 
@@ -3141,104 +3148,6 @@
 
 !CVSSourceCodeManager class methodsFor:'source code administration'!
 
-annotationsFor:clsOrNil fileName:classFileName directory:packageDir module:moduleDir
-    "return info about who changed what and when.
-     Return nil on failure.
-
-     The returned information is a structure entry for each line
-            #revision           -> version of last change
-            #author             -> author 
-            #date               -> change date 
-        "
-
-    |tempDir fullName modulePath inStream inHeaderInfo line info msg|
-
-    tempDir := self createTempDirectory:nil forModule:nil.
-    tempDir isNil ifTrue:[
-        ('CVSSourceCodeManager [error]: no tempDir - cannot extract log') errorPrintCR.
-        ^ nil.
-    ].
-
-    [
-        |cmd revArg|
-
-        modulePath :=  moduleDir , '/' , packageDir. 
-        fullName :=  modulePath , '/' , classFileName.
-
-        self createEntryFor:fullName 
-             module:moduleDir
-             in:(tempDir construct:modulePath) 
-             revision:'1.1' 
-             date:'dummy' 
-             special:''
-             overwrite:false.
-
-        msg := 'Fetching annotation log '.
-        clsOrNil isNil ifTrue:[
-            msg := msg , 'in ' , fullName.
-        ] ifFalse:[
-            msg := msg , 'of ', clsOrNil name.
-        ].
-        self activityNotification:msg,'...'.
-
-        inStream := self 
-                        executeCVSCommand:('annotate ' , fullName) 
-                        module:moduleDir 
-                        inDirectory:tempDir 
-                        log:true 
-                        pipe:true.
-
-        inStream isNil ifTrue:[
-            ('CVSSourceCodeManager [error]: cannot open pipe to cvs annotate ', fullName) errorPrintCR.
-            ^ nil
-        ].
-
-        "/
-        "/ read the commands pipe output and extract the info
-        "/
-        info := IdentityDictionary new.
-        inHeaderInfo := true.
-        [inHeaderInfo and:[inStream atEnd not]] whileTrue:[
-            line:= inStream nextLine.
-            ((line ? '') startsWith:'*******') ifTrue:[
-                inHeaderInfo := false.
-            ]
-        ].
-
-        "/
-        "/ continue to read the commands pipe output 
-        "/ and extract change info records
-        "/
-        [inStream atEnd] whileFalse:[
-            line := inStream nextLine.
-Transcript showCR:line.
-        ].
-    ] ensure:[
-        inStream notNil ifTrue:[inStream close].
-
-        tempDir notNil ifTrue:[
-            OperatingSystem accessDeniedErrorSignal handle:[:ex |
-                ('CVSSourceCodeManager [warning]: could not remove tempDir ', tempDir pathName) infoPrintCR.
-            ] do:[
-                tempDir recursiveRemove
-            ].
-        ].
-        self activityNotification:nil.
-    ].
-    ^ info
-
-    "
-     SourceCodeManager 
-        annotationsFor:Array 
-        fileName:'Array.st' directory:'libbasic' module:'stx'
-    "
-    "
-     SourceCodeManager 
-        annotationsFor:MenuPanel 
-        fileName:'MenuPanel.st' directory:'libwidg2' module:'stx'
-    "
-!
-
 checkForExistingContainer:fileName inModule:moduleDir directory:packageDir
     "check for a container to exist"
 
@@ -4006,108 +3915,6 @@
     "
 !
 
-diffListFor:clsOrNil fileName:classFileName directory:packageDir module:moduleDir revision1:rev1 revision2:rev2
-    "return diff info. This is supposed to return a standard diff-like
-     list of lines, representing the diffs between two revisions.
-     experimental (for ownershipGraph)"
-
-    ^  self
-        diffListFor:clsOrNil fileName:classFileName directory:packageDir module:moduleDir revision1:rev1 revision2:rev2 
-        cache:true
-!
-
-diffListFor:clsOrNil fileName:classFileNameArg directory:packageDir module:moduleDir revision1:rev1 revision2:rev2 cache:cacheIt
-    "return diff info. This is supposed to return a standard diff-like
-     list of lines, representing the diffs between two revisions.
-     experimental (for ownershipGraph)"
-
-    |tempDir fullName modulePath inStream list msg cacheDir cachedFile classFileName|
-
-    clsOrNil notNil ifTrue:[
-        modulePath :=  clsOrNil package copyReplaceAll:$: with:$/.
-        fullName :=  modulePath , '/' , (classFileName := clsOrNil getClassFilename).
-    ] ifFalse:[
-        modulePath :=  moduleDir , '/' , packageDir. 
-        fullName :=  modulePath , '/' , (classFileName := classFileNameArg).
-    ].
-
-   (cacheIt) ifTrue:[
-        (cacheDir := self sourceCacheDirectory) isNil ifTrue:[
-            ('CVSSourceCodeManager [warning]: no source cache directory') infoPrintCR.
-        ] ifFalse:[
-            (cacheDir / modulePath / '.diffs') exists ifFalse:[
-                (cacheDir / modulePath / '.diffs') makeDirectory.
-            ].
-            cachedFile := cacheDir / modulePath / '.diffs' / (classFileName,'_',rev1,'_',rev2).
-            cachedFile exists ifTrue:[
-                ^ cachedFile contents
-            ].
-        ].
-    ].
-
-    tempDir := self createTempDirectory:nil forModule:nil.
-    tempDir isNil ifTrue:[
-        ('CVSSourceCodeManager [error]: no tempDir - cannot extract status') errorPrintCR.
-        ^ nil.
-    ].
-
-    [
-        self createEntryFor:fullName 
-             module:moduleDir
-             in:(tempDir construct:modulePath) 
-             revision:'1.1' 
-             date:'dummy' 
-             special:''
-             overwrite:false.
-
-        msg := 'CVS: Fetching diff list of '.
-        clsOrNil isNil ifTrue:[
-            msg := msg , fullName.
-        ] ifFalse:[
-            msg := msg , clsOrNil name.
-        ].
-        msg := msg , ' ' , rev1 , ' vs. ' , rev2.
-        self activityNotification:msg.
-
-        inStream := self 
-                        executeCVSCommand:('diff -w -r%1 -r%2 %3' bindWith:rev1 with:rev2 with:fullName) 
-                        module:moduleDir 
-                        inDirectory:tempDir 
-                        log:true 
-                        pipe:true.
-
-        inStream isNil ifTrue:[
-            ('CVSSourceCodeManager [error]: cannot open pipe to cvs diff ', fullName) errorPrintCR.
-            ^ nil
-        ].
-
-        "/
-        "/ read the commands pipe output and extract the container info
-        "/
-        [ inStream nextLine startsWith:'diff -'] whileFalse.
-
-        list := inStream contents.
-    ] ensure:[
-        inStream notNil ifTrue:[inStream close].
-        tempDir recursiveRemove
-    ].
-    list := list reject:[:line | line startsWith:'\ '].
-
-    cachedFile notNil ifTrue:[
-        cachedFile contents:list.
-    ].
-    ^ list
-
-    "
-     SourceCodeManager statusOf:Array 
-     SourceCodeManager statusOf:Array fileName:'Array.st' directory:'libbasic' module:'stx'  
-     SourceCodeManager statusOf:Filename fileName:'Filename.st' directory:'libbasic' module:'stx'  
-     SourceCodeManager statusOf:NewSystemBrowser fileName:'NewSystemBrowser.st' directory:'libtool' module:'stx'  
-    "
-
-    "Modified: / 29-08-2006 / 13:18:00 / cg"
-!
-
 getExistingContainersInModule:aModule directory:aPackage
     "return a list of existing containers."
 
@@ -4146,27 +3953,6 @@
     "
 !
 
-initialRevisionStringFor:aClass inModule:moduleDir directory:packageDir container:fileName
-    "return a string usable as initial revision string"
-
-    |cvsRoot fullName|
-
-    cvsRoot := self getCVSROOTForModule:moduleDir.
-    cvsRoot := self repositoryTopDirectoryFromCVSRoot:cvsRoot.
-    packageDir isEmptyOrNil ifTrue:[
-        fullName := (cvsRoot , '/' , moduleDir)
-    ] ifFalse:[
-        fullName := (cvsRoot , '/' , moduleDir , '/' , packageDir)
-    ].        
-    ^ self
-        initialRCSRevisionStringFor:aClass 
-        in:fullName
-        container:fileName
-
-    "Modified: / 16-01-1998 / 17:34:13 / stefan"
-    "Created: / 23-08-2006 / 14:05:46 / cg"
-!
-
 listDirectories:cvsPath
     "return a list of all directories in cvsPath.
      cvsPath is the path relative to the cvs root"
@@ -4821,7 +4607,7 @@
 
      The returned information is a structure (IdentityDictionary)
      filled with:
-            #container          -> the RCS/CVS container file name 
+            #container          -> the CVS container file name 
             #cvsRoot            -> the CVS root (repository) 
             #filename           -> the actual source file name
             #newestRevision     -> the revisionString of the newest revision
@@ -4843,7 +4629,7 @@
               #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
+              #numberOfChangedLines  -> the number of changed lines w.r.t the previous (as string with +n -n)
               #logMessage            -> the checkIn log message
 
             revisions are ordered newest first 
@@ -5049,7 +4835,7 @@
     "
      The returned information is a list of structures (IdentityDictionary)
      each filled with:
-            #container          -> the RCS/CVS container file name 
+            #container          -> the CVS container file name 
             #cvsRoot            -> the CVS root (repository) 
             #filename           -> the actual source file name
             #newestRevision     -> the revisionString of the newest revision
@@ -5071,7 +4857,7 @@
               #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
+              #numberOfChangedLines  -> the number of changed lines w.r.t the previous (as string with +n -n)
               #logMessage            -> the checkIn log message
 
             revisions are ordered newest first 
@@ -5721,6 +5507,255 @@
     "Modified: / 29-08-2006 / 13:18:00 / cg"
 ! !
 
+!CVSSourceCodeManager class methodsFor:'source code utilities'!
+
+annotationsFor:clsOrNil fileName:classFileName directory:packageDir module:moduleDir
+    "return info about who changed what and when.
+     Return nil on failure.
+
+     The returned information is a structure entry for each line
+            #revision           -> version of last change
+            #author             -> author 
+            #date               -> change date 
+        "
+
+    |tempDir fullName modulePath inStream inHeaderInfo line info msg|
+
+    tempDir := self createTempDirectory:nil forModule:nil.
+    tempDir isNil ifTrue:[
+        ('CVSSourceCodeManager [error]: no tempDir - cannot extract log') errorPrintCR.
+        ^ nil.
+    ].
+
+    [
+        |cmd revArg|
+
+        modulePath :=  moduleDir , '/' , packageDir. 
+        fullName :=  modulePath , '/' , classFileName.
+
+        self createEntryFor:fullName 
+             module:moduleDir
+             in:(tempDir construct:modulePath) 
+             revision:'1.1' 
+             date:'dummy' 
+             special:''
+             overwrite:false.
+
+        msg := 'Fetching annotation log '.
+        clsOrNil isNil ifTrue:[
+            msg := msg , 'in ' , fullName.
+        ] ifFalse:[
+            msg := msg , 'of ', clsOrNil name.
+        ].
+        self activityNotification:msg,'...'.
+
+        inStream := self 
+                        executeCVSCommand:('annotate ' , fullName) 
+                        module:moduleDir 
+                        inDirectory:tempDir 
+                        log:true 
+                        pipe:true.
+
+        inStream isNil ifTrue:[
+            ('CVSSourceCodeManager [error]: cannot open pipe to cvs annotate ', fullName) errorPrintCR.
+            ^ nil
+        ].
+
+        "/
+        "/ read the commands pipe output and extract the info
+        "/
+        info := IdentityDictionary new.
+        inHeaderInfo := true.
+        [inHeaderInfo and:[inStream atEnd not]] whileTrue:[
+            line:= inStream nextLine.
+            ((line ? '') startsWith:'*******') ifTrue:[
+                inHeaderInfo := false.
+            ]
+        ].
+
+        "/
+        "/ continue to read the commands pipe output 
+        "/ and extract change info records
+        "/
+        [inStream atEnd] whileFalse:[
+            line := inStream nextLine.
+Transcript showCR:line.
+        ].
+    ] ensure:[
+        inStream notNil ifTrue:[inStream close].
+
+        tempDir notNil ifTrue:[
+            OperatingSystem accessDeniedErrorSignal handle:[:ex |
+                ('CVSSourceCodeManager [warning]: could not remove tempDir ', tempDir pathName) infoPrintCR.
+            ] do:[
+                tempDir recursiveRemove
+            ].
+        ].
+        self activityNotification:nil.
+    ].
+    ^ info
+
+    "
+     SourceCodeManager 
+        annotationsFor:Array 
+        fileName:'Array.st' directory:'libbasic' module:'stx'
+    "
+    "
+     SourceCodeManager 
+        annotationsFor:MenuPanel 
+        fileName:'MenuPanel.st' directory:'libwidg2' module:'stx'
+    "
+!
+
+diffListFor:clsOrNil fileName:classFileNameArg directory:packageDir module:moduleDir revision1:rev1 revision2:rev2 cache:cacheIt
+    "return diff info. This is supposed to return a standard diff-like
+     list of lines, representing the diffs between two revisions.
+     experimental (for ownershipGraph).
+     Here we ask cvs to give us the diff list"
+
+    |tempDir fullName modulePath inStream list msg cacheDir cachedFile classFileName diffDir|
+
+    clsOrNil notNil ifTrue:[
+        modulePath :=  clsOrNil package copyReplaceAll:$: with:$/.
+        fullName :=  modulePath , '/' , (classFileName := clsOrNil getClassFilename).
+    ] ifFalse:[
+        modulePath :=  moduleDir , '/' , packageDir. 
+        fullName :=  modulePath , '/' , (classFileName := classFileNameArg).
+    ].
+
+   (cacheIt) ifTrue:[
+        (cacheDir := self sourceCacheDirectory) isNil ifTrue:[
+            ('CVSSourceCodeManager [warning]: no source cache directory') infoPrintCR.
+        ] ifFalse:[
+            diffDir := (cacheDir / modulePath / '.diffs').
+            diffDir exists ifFalse:[
+                diffDir makeDirectory.
+            ].
+            cachedFile := diffDir / (classFileName,'_',rev1,'_',rev2).
+            cachedFile exists ifTrue:[
+                ^ cachedFile contents
+            ].
+        ].
+    ].
+
+    tempDir := self createTempDirectory:nil forModule:nil.
+    tempDir isNil ifTrue:[
+        ('CVSSourceCodeManager [error]: no tempDir - cannot extract status') errorPrintCR.
+        ^ nil.
+    ].
+
+    [
+        self createEntryFor:fullName 
+             module:moduleDir
+             in:(tempDir construct:modulePath) 
+             revision:'1.1' 
+             date:'dummy' 
+             special:''
+             overwrite:false.
+
+        msg := 'CVS: Fetching diff list of '.
+        clsOrNil isNil ifTrue:[
+            msg := msg , fullName.
+        ] ifFalse:[
+            msg := msg , clsOrNil name.
+        ].
+        msg := msg , ' ' , rev1 , ' vs. ' , rev2.
+        self activityNotification:msg.
+
+        inStream := self 
+                        executeCVSCommand:('diff -w -r%1 -r%2 %3' bindWith:rev1 with:rev2 with:fullName) 
+                        module:moduleDir 
+                        inDirectory:tempDir 
+                        log:true 
+                        pipe:true.
+
+        inStream isNil ifTrue:[
+            ('CVSSourceCodeManager [error]: cannot open pipe to cvs diff ', fullName) errorPrintCR.
+            ^ nil
+        ].
+
+        "/
+        "/ read the command's pipe output, skipping some administrative info
+        "/
+        [ inStream nextLine startsWith:'diff -'] whileFalse.
+
+        list := inStream contents.
+    ] ensure:[
+        inStream notNil ifTrue:[inStream close].
+        tempDir recursiveRemove
+    ].
+    list := list reject:[:line | line startsWith:'\ '].
+
+    cachedFile notNil ifTrue:[
+        cachedFile contents:list.
+    ].
+    ^ list
+
+    "
+     SourceCodeManager statusOf:Array 
+     SourceCodeManager statusOf:Array fileName:'Array.st' directory:'libbasic' module:'stx'  
+     SourceCodeManager statusOf:Filename fileName:'Filename.st' directory:'libbasic' module:'stx'  
+     SourceCodeManager statusOf:NewSystemBrowser fileName:'NewSystemBrowser.st' directory:'libtool' module:'stx'  
+    "
+
+    "Modified: / 29-08-2006 / 13:18:00 / cg"
+!
+
+initialRCSRevisionStringFor:aClass in:dir container:fileName
+    "return a string usable as initial revision string"
+
+    "/ do not make the string below into one string;
+    "/ RCS would expand it into a wrong rev-string
+
+    |nm oldRev idx special|
+
+    nm := fileName.
+    (nm endsWith:',v') ifTrue:[
+        nm := nm copyButLast:2
+    ].
+    (nm endsWith:'.st') ifFalse:[
+        nm := nm , '.st'
+    ].
+
+    oldRev := aClass revisionString.
+    special := ''.
+
+    oldRev notNil ifTrue:[
+        idx := oldRev lastIndexOf:$[.
+        idx ~~ 0 ifTrue:[
+            idx := oldRev indexOf:$[ startingAt:idx+1.
+            idx ~~ 0 ifTrue:[
+                special := ' ' , (oldRev copyFrom:idx).
+            ]
+        ]
+    ].
+
+
+    ^ '$' , 'Header: ' , dir , '/' , fileName , ',v $'
+      , special
+
+    "Modified: 17.9.1996 / 15:57:15 / cg"
+    "Created: 14.2.1997 / 20:59:28 / cg"
+!
+
+initialRevisionStringFor:aClass inModule:moduleDir directory:packageDir container:fileName
+    "return a string usable as initial revision string"
+
+    |cvsRoot fullName|
+
+    cvsRoot := self getCVSROOTForModule:moduleDir.
+    cvsRoot := self repositoryTopDirectoryFromCVSRoot:cvsRoot.
+    packageDir isEmptyOrNil ifTrue:[
+        fullName := (cvsRoot , '/' , moduleDir)
+    ] ifFalse:[
+        fullName := (cvsRoot , '/' , moduleDir , '/' , packageDir)
+    ].        
+    ^ self initialRCSRevisionStringFor:aClass in:fullName container:fileName
+
+    "Modified: / 16-01-1998 / 17:34:13 / stefan"
+    "Created: / 23-08-2006 / 14:05:46 / cg"
+! !
+
 !CVSSourceCodeManager class methodsFor:'testing'!
 
 isCVS
@@ -5729,6 +5764,179 @@
     "Created: / 16-08-2006 / 10:58:19 / cg"
 ! !
 
+!CVSSourceCodeManager::CVSVersionInfo class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2009 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    In ancient times, Class used to return a Dictionary when asked for versionInfo.
+    This has been replaced by instances of VersionInfo and subclasses.
+
+    CVSVersionInfo adds some CVS specific data.
+
+    [author:]
+        cg (cg@AQUA-DUO)
+"
+!
+
+version
+    ^ '$Header$'
+!
+
+version_CVS
+    ^ '$Header$'
+! !
+
+!CVSSourceCodeManager::CVSVersionInfo 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 nextWord info nm s fn revString d |
+
+    s := aString readStream.
+    s skipSeparators.
+    firstWord := s upToSeparator.
+
+    info := self new.
+
+    "/
+    "/ supported formats:
+    "/
+    "/ $-Header:   pathName rev date time user state $
+    "/ $-Revision: rev $
+    "/ $-Id:       fileName rev date time user state $
+    "/
+    (firstWord = '$Header:' or:[firstWord = 'Header:']) ifTrue:[
+        d := firstWord first.
+        s skipSeparators.
+        nm := s throughAll:',v '.
+        nm := nm withoutSeparators.
+        info repositoryPathName:nm.
+        info fileName:(nm asFilename baseName copyButLast:2).
+        words := s upToEnd asCollectionOfWords readStream.
+
+        words atEnd ifFalse:[
+            nextWord := words next.
+            nextWord first ~= d ifTrue:[
+                info revision:nextWord.
+                nextWord := words next.
+                (nextWord notNil and:[nextWord first ~= d]) ifTrue:[
+                    info date:nextWord.
+                    info time:words next.
+                    nextWord := words next.
+                    (nextWord notNil and:[nextWord startsWithAnyOf:'+-']) ifTrue:[
+                        info timezone:nextWord.
+                        nextWord := words next.
+                    ].
+                    info user:nextWord.
+                    info state:words next.
+                ]
+            ].
+        ].
+        ^ info
+    ].
+
+    (firstWord = '$Revision:' or:[firstWord = 'Revision:']) ifTrue:[
+        info revision:(s upToEnd asCollectionOfWords first).
+        ^ info
+    ].
+
+    (firstWord = '$Id:' or:[firstWord = 'Id:']) ifTrue:[
+        "/commented out by Jan Vrany, 2009/10/20
+        "/according to http://svnbook.red-bean.com/en/1.5/svn.advanced.props.special.keywords.html
+        "/svn has no support for $ Header $ expansion. Therefore
+        "/libsvn uses $Id$ instead.
+        "/self halt:'no longer supported'.        
+        words := s upToEnd asCollectionOfWords readStream.
+        info fileName:(fn := words next).
+        (fn endsWith:',v') ifFalse:[
+            "/ not a CVS version
+            ^ nil
+        ].
+        info revision:(revString := words next).
+
+        "/ do not use matchesRegex:'[0-9]+\.[0-9]+.*') here: regex is an optional package
+        ((revString conform:[:c | c isDigit or:[c == $.]])
+        and:[revString includes:$.]) ifFalse:[
+            "/ not a CVS version
+            ^ nil
+        ].
+        info date:(words next).
+        info time:(words next).
+        info user:(words next).
+        info state:(words next).
+        ^ info
+    ].
+
+    ^ nil
+
+    "
+     CVSVersionInfo fromRCSString:('$' , 'Revision: 1.122 $')
+     CVSVersionInfo fromRCSString:(CVSSourceCodeManager version)
+     CVSVersionInfo fromRCSString:(SVNSourceCodeManager version_CVS)
+    "
+
+    "Modified (comment): / 11-10-2011 / 23:41:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 22-11-2011 / 16:15:49 / cg"
+    "Modified (format): / 24-11-2011 / 10:56:51 / cg"
+! !
+
+!CVSSourceCodeManager::CVSVersionInfo methodsFor:'accessing'!
+
+changedLinesInfo
+    ^ changedLinesInfo
+!
+
+changedLinesInfo:aString
+    changedLinesInfo := aString.
+!
+
+repositoryPathName
+    ^ repositoryPathName
+!
+
+repositoryPathName:something
+    repositoryPathName := something.
+!
+
+timeZone
+    ^ timeZone
+!
+
+timeZone:something
+    timeZone := something.
+!
+
+timezone
+    ^ timeZone
+
+    "Created: / 22-10-2008 / 20:50:39 / cg"
+!
+
+timezone:something
+    timeZone := something.
+
+    "Created: / 22-10-2008 / 20:50:32 / cg"
+! !
+
 !CVSSourceCodeManager class methodsFor:'documentation'!
 
 version