#FEATURE by stefan expecco_head_5844
authorStefan Vogel <sv@exept.de>
Fri, 31 Mar 2017 15:57:47 +0200
changeset 4232 f02d9d68eabc
parent 4231 a30585392c57
child 4233 277b4ea21e4c
#FEATURE by stefan class: CVSSourceCodeManager class changed: #checkinClass:fileName:directory:module:source:logMessage:force: #checkinClass:fileName:directory:module:source:logMessage:force:asBranch: prepare for branch support (unfinished yet)
CVSSourceCodeManager.st
--- a/CVSSourceCodeManager.st	Sat Mar 18 19:01:30 2017 +0100
+++ b/CVSSourceCodeManager.st	Fri Mar 31 15:57:47 2017 +0200
@@ -2105,17 +2105,27 @@
 !
 
 checkinClass:cls fileName:classFileName directory:packageDir module:moduleDir source:sourceFileName logMessage:logMessage force:forceArg
+    ^ self checkinClass:cls fileName:classFileName directory:packageDir module:moduleDir source:sourceFileName logMessage:logMessage force:forceArg asBranch:nil
+
+    "Created: / 11-09-1996 / 16:16:11 / cg"
+    "Modified: / 31-07-2013 / 18:07:53 / cg"
+    "Modified: / 29-03-2017 / 18:21:23 / stefan"
+!
+
+checkinClass:cls fileName:classFileName directory:packageDir module:moduleDir source:sourceFileName logMessage:logMessage force:forceArg asBranch:branchTag
     "enter a classes source code (which has been already filed out into sourceFileName)
      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 revision newestRevision logTmp
-     cmdOut whatHappened s entry idx changeLog changesAsLogged l
+     Return true if ok, false if not.
+
+     If branchTag is notNil, the class is checked in on the branch if it already exists, or a branch for this tag is created.
+     (branch support does not work yet!!)"
+
+    |tempdir cmd checkoutName logMsg classRevision newestRevision cmdOut whatHappened s entry idx changeLog changesAsLogged l
      newRevision newString binRevision className msg answer didMerge
      modulePath time
      editor checkInRepaired checkInNew didAccept emphasizedText repairedText out
-     emSep comment force conflictResolvedManually revisionOption|
+     emSep force conflictResolvedManually revisionOption|
 
     force := forceArg.
 
@@ -2124,34 +2134,31 @@
         self reportError:'refuse to check in private classes.'.
         ^ false.
     ].
-    revision := "cls revision" cls revisionOfManager:self.
-    (revision notNil and:[revision endsWith:$m])
-    ifTrue:[
+    classRevision := cls revisionOfManager:self.
+    (classRevision notNil and:[classRevision endsWith:$m]) ifTrue:[
         "/ this class has already been checked in with a merge,
         "/ but not reloaded from the repository.
         "/ must use the original revision string.
-        revision := revision copyButLast:1.
+        classRevision := classRevision copyButLast:1.
     ].
-    (binRevision := cls binaryRevision) notNil ifTrue:[
-        revision ~= binRevision ifTrue:[
-            Transcript showCR:('CVSSourceCodeManager [info]: class ' , className , ' is based upon ' , binRevision , ' but has revision ' , (revision ? '?'))
-        ]
+    binRevision := cls binaryRevision.
+    (binRevision notNil and:[classRevision ~= binRevision]) ifTrue:[
+        Transcript showCR:('CVSSourceCodeManager [info]: class ' , className , ' is based upon ' , binRevision , ' but has revision ' , (classRevision ? '?'))
     ].
 
-    revision isNil ifTrue:[
-        revision := newestRevision := self newestRevisionOf:cls.
-        revision isNil ifTrue:[
+    classRevision isNil ifTrue:[
+        "there is no version method. Get the version from the repository"
+        classRevision := newestRevision := self newestRevisionOf:cls.
+        classRevision isNil ifTrue:[
             force ifTrue:[
-                revision := newestRevision := self newestRevisionInFile:classFileName directory:packageDir module:moduleDir.
-                revision isNil ifTrue:[
-                    revision := '1.0'   "/ initial checkin
-                ].
-            ] ifFalse:[
-                revision := '1.0'   "/ initial checkin
-            ]
+                classRevision := newestRevision := self newestRevisionInFile:classFileName directory:packageDir module:moduleDir.
+            ].
+            classRevision isNil ifTrue:[
+                classRevision := '1.0'   "/ initial checkin
+            ].
         ] ifFalse:[
-            revision == #deleted ifTrue:[
-                revision := '0'     "/ to force cvs-adding, which resurrects the file from the Attic
+            classRevision == #deleted ifTrue:[
+                classRevision := '0'     "/ to force cvs-adding, which resurrects the file from the Attic
             ].
         ].
     ].
@@ -2185,726 +2192,9 @@
         ('no tempDir - cannot checkin ' , className) errorPrintCR.
         ^ false
     ].
-    [
-        "/
-        "/ next, create CVS/Entries and CVS/Repository with version information of current version
-        "/
-        packageDir isEmptyOrNil ifTrue:[
-            modulePath := moduleDir
-        ] ifFalse:[
-            modulePath :=  moduleDir , '/' , packageDir.
-        ].
-        checkoutName :=  modulePath , '/' , classFileName.
-
-        "/
-        "/ correct our current time, so that converting it will give us UTC
-        "/
-        time := Timestamp now asUtcTimestamp subtractSeconds:1.
-
-        self createEntryFor:checkoutName
-             module:moduleDir
-             in:(tempdir construct:modulePath)
-             revision:revision
-             date:(self cvsTimeString:time)
-             special:''
-             overwrite:true.
-
-        "/
-        "/ copy-over our current version
-        "/
-        Error handle:[:ex|
-            self reportError:'cannot copy-over filedOut class source'.
-            ^ false.
-        ] do:[
-            sourceFileName asFilename copyTo:(tempdir construct:checkoutName).
-        ].
-
-        "/
-        "/ synchronize i.e. merge in any changes
-        "/
-        self activityNotification:'CVS: Merging ' , cls name , ' with repository version...'.
-
-        revisionOption := ''.
-        (revision asCollectionOfSubstringsSeparatedBy:$.) size > 2 ifTrue:[
-            "must be a branch, compare with branch revision"
-            revisionOption := '-r ', revision copyUpToLast:$..
-        ].
-
-        cmd := 'update %1 %4 %2 >"%3"'
-            bindWith:CVSUpdateOptions
-            with:classFileName
-            with:cmdOut name
-            with:revisionOption.
-
-        (self
-            executeCVSCommand:cmd
-            module:moduleDir
-            inDirectory:((tempdir construct:moduleDir) constructString:packageDir)
-        ) ifFalse:[
-            force ifFalse:[
-                (self checkForExistingContainer:classFileName inModule:moduleDir directory:packageDir) ifFalse:[
-                    "/ no container
-                    "/ someone fiddled around with repository ?
-                    (cls binaryRevision 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:moduleDir source:sourceFileName logMessage:logMsg force:force.
-                        ].
-                    ].
-                    (Dialog confirm:('There seems to be no source container for "%1"\(Either the source container was removed,\or your per-module repository setting is wrong,\or the CVS server is unreachable).\\Proceed?' bindWith:cls name allBold) withCRs)
-                    ifFalse:[
-                        ^ false
-                    ].
-                ].
-
-                "/ is the version correct ?
-                newestRevision isNil ifTrue:[
-                    newestRevision := self newestRevisionOf:cls.
-                    newestRevision isNil ifTrue:[
-                        (Dialog confirm:('The source container for ',cls name allBold,' seems corrupted. Proceed?' withCRs)) ifFalse:[
-                            ^ false
-                        ].
-                        ^ self
-                            checkinClass:cls fileName:classFileName directory:packageDir module:moduleDir
-                            source:sourceFileName logMessage:logMessage force:true.
-                    ].
-                ].
-"/            revision > newestRevision ifTrue:[
-"/                true "/ (Dialog confirm:('The version-info of ',cls name allBold,' is wrong \(The class version (',revision allBold,') is newer than the newest version in the repository (',newestRevision allBold,').\\Patch the version and retry checkin ?') withCRs)
-"/                ifTrue:[
-"/                    "/ newVersionString := self updatedRevisionStringOf:cls forRevision:newestRevision with:cls revisionString.
-"/                    "/ self updateVersionMethodOf:cls for:newVersionString.
-"/                    ^ self checkinClass:cls fileName:classFileName directory:packageDir module:moduleDir source:sourceFileName logMessage:logMsg force:force.
-"/                ].
-"/            ].
-"/
-"/            self reportError:('cannot merge current source with repository version (failed to execute: ',cmd,')').
-"/            ^ false.
-                "/ if we arrive here, proceed as if merged
-                whatHappened := 'M initial'
-            ].
-        ] ifTrue:[
-            "/
-            "/ check what happened - the contents of the cmdOut file may be:
-            "/   empty   -> nothing changed
-            "/   M xxx   -> merged-in changes from other users
-            "/   C xxx   -> a conflict occurred and the differences have been merged into the source
-            "/              needs special action
-            "/
-            (cmdOut exists and:[cmdOut fileSize > 0]) ifTrue:[
-                whatHappened := cmdOut contentsAsString.
-            ] ifFalse:[
-                self breakPoint:#cg.
-            ].
-        ].
-
-        (whatHappened isEmptyOrNil) ifTrue:[
-            "/
-            "/ no change
-            "/
-        Transcript showCR:'no change in ' , className , ' (repository unchanged)'.
-
-            force ifFalse:[
-"/            (ChangeSet current includesChangeForClass:cls) ifTrue:[
-"/                (self confirm:('Nothing changed in %1 (repository unchanged).\\Remove entries from changeSet ?' bindWith:className) withCRs) ifTrue:[
-"/                    ChangeSet current condenseChangesForClass:cls.
-"/                ].
-"/            ] ifFalse:[
-"/                self information:('Nothing changed in %1 (repository unchanged)' bindWith:className).
-"/            ].
-                self postCheckInClass:cls.
-            ] ifTrue:[
-                changeLog := self revisionLogOfContainer:classFileName directory:packageDir module:moduleDir.
-                (changeLog isNil or:[(changeLog at:#revisions) size ~~ 1]) ifTrue:[
-                    'CVSSourceCodeManager [error]: failed to update revisionString (no log)' errorPrintCR.
-                    self updateVersionMethodOf:cls for:'$' , 'Header' , '$'.  "/ concatenated to avoid RCS expansion
-                ] ifFalse:[
-                    entry := (changeLog at:#revisions) first.
-                    newString := self revisionStringFromLog:changeLog entry:entry forClass:cls.
-                    newString isEmptyOrNil ifTrue:[
-                        'CVSSourceCodeManager [error]: missng revisionString' errorPrintCR
-                    ] ifFalse:[
-                        self updateVersionMethodOf:cls for:newString.
-                        cls revision ~= newRevision ifTrue:[
-                            'CVSSourceCodeManager [error]: failed to update revisionString' errorPrintCR
-                        ] ifFalse:[
-                            ('CVSSourceCodeManager [info]: updated revisionString to:',newString) infoPrintCR
-                        ]
-                    ]
-                ]
-            ].
-
-            ^ true
-        ].
-        Verbose == true ifTrue:[
-            ('CVSMGR: result is: ' , whatHappened) infoPrintCR.
-        ].
-
-        force ifFalse:[
-            revision isNil ifTrue:[
-                changeLog := self revisionLogOf:cls.
-            ] ifFalse:[
-                changeLog := self revisionLogOf:cls fromRevision:(self revisionAfter:revision) toRevision:nil.
-            ].
-            changeLog notNil ifTrue:[
-                s := CharacterWriteStream on:''.
-                self writeRevisionLogMessagesFrom:changeLog withHeader:false to:s.
-                changesAsLogged := s contents.
-            ] ifFalse:[
-                "/ mhmh - that should not happen
-                changesAsLogged := ''.
-            ].
-        ].
-
-        didMerge := false.
-        conflictResolvedManually := checkInRepaired := checkInNew := false.
-
-        "/
-        "/ cvs above rel10 returns a multiline info ...
-        "/ we have to extract the one line which states what happened.
+    [ "ensure protected block"
         "/
-        whatHappened := whatHappened asCollectionOfLines asStringCollection.
-        whatHappened := whatHappened select:[:line |
-                            (line startsWith:'RCS file') not
-                            and:[(line startsWith:'retrieving') not
-                            and:[(line startsWith:'Merging') not
-                            and:[line size > 0]]]
-                        ].
-        whatHappened := whatHappened asString.
-
-        (force or:[(whatHappened startsWith:'M ') or:[whatHappened startsWith:'A ']]) ifTrue:[
-            "/
-            "/ merged in changes / resurrected
-            "/
-            (force
-            or:[changeLog isNil
-            or:[(changeLog at:#revisions ifAbsent:nil) isEmptyOrNil]]) ifTrue:[
-                "/
-                "/ pretty good - nothing has changed in the meanwhile
-                "/
-                Transcript showCR:('CVSSourceCodeManager [info]: checking in %1 (%2)...' bindWith:className with:modulePath).
-            ] ifFalse:[
-                |mySource mergedSource |
-
-                "/
-                "/ someone else has changed things in the meanwhile, but there is no conflict
-                "/ and version have been merged.
-                "/
-                didMerge := true.
-                changesAsLogged := changesAsLogged asCollectionOfLines.
-
-                s := CharacterWriteStream new.
-                self fileOutSourceCodeOf: cls on:s.
-                mySource := s contents asString.
-                mergedSource := (tempdir construct:checkoutName) readStream contents asString.
-
-                mySource = mergedSource ifTrue:[
-                    msg := 'The source of ' , className , ' has been changed in the meanwhile as listed below.
-
-I have merged your version with the newest repository version,
-and found no differences between the result and your current version
-(i.e. your version seemed up-to-date).'.
-
-                    self checkinTroubleDialog:'Merging versions'
-                                   message:msg
-                                   log:changesAsLogged
-                                   abortable:false
-                                   option:nil.
-                    didMerge := false.
-                ] ifFalse:[
-                    msg := 'The source of ' , className , ' has been changed in the meanwhile as listed below.
-
-If you continue, your new changes (based upon rev. ' , revision printString , ') will be MERGED
-into the newest revision. This will combine the other version with your changes
-into a new common revision which may be different from both.
-Although this is a nice feature, it may fail to create the expected result in certain situations.
-
-You should carefully check the result - by comparing the current version with the
-most recent version in the repository. If that does not contain an acceptable version,
-change methods as required and check in again.
-Be aware, that after that, the actual repository version is different from your current classes,
-and you should update your class from the repository.
-
-Continue ?'.
-
-                    answer := self checkinTroubleDialog:'Merging versions'
-                                   message:msg
-                                   log:changesAsLogged
-                                   abortable:true
-                                   option:'Stop - see first'
-                                   option2:'Do NOT Merge - Force my Code'.
-
-                    answer == #option2 ifTrue:[
-                        (Dialog confirm:'Are you certain that you want to suppress a merge and force your code to be checked in ?')
-                        ifTrue:[
-                            s := (tempdir construct:checkoutName) writeStream.
-                            self fileOutSourceCodeOf: cls on:s.
-                            s close.
-                            answer := true.
-                        ]
-                    ].
-
-                    answer ~~ true ifTrue:[
-                        answer == #option ifTrue:[
-                            DiffCodeView
-                                openOn:mySource
-                                label:'current version'
-                                and:mergedSource
-                                label:'merged version'.
-
-                        ].
-                        self reportError:'checkin aborted - (no merge; repository unchanged)'.
-                        ^ false.
-                    ].
-                ].
-
-"/                changesAsLogged := (changesAsLogged asStringCollection collect:[:line | line withTabsExpanded]) asString.
-"/                msg := 'The source of ' , className , ' has been changed in the meanwhile as follows:
-"/' , changesAsLogged , '
-"/
-"/If you continue, your new changes (based upon rev. ' , revision , ') will be MERGED
-"/into the newest revision. This will combine the other version with your changes
-"/into a new common revision which is different from both.
-"/Although convenient, it may fail to create the expected result in certain situations.
-"/
-"/You should carefully check the result - by comparing the current version with the
-"/most recent version in the repository. If that does not contain an acceptable version,
-"/change methods as required and check in again. Be aware, that the actual repository version
-"/is different from your current classes.
-"/
-"/Continue ?'.
-"/                (self confirm:msg) ifFalse:[
-"/                    Transcript showCR:'checkin aborted - (no merge; repository unchanged)'.
-"/                    ^ false.
-"/                ].
-                Transcript showCR:('CVSSourceCodeManager [info]: checking in %1 (%2) (merge)...' bindWith:className with:modulePath).
-            ]
-        ] ifFalse:[
-            (whatHappened startsWith:'C ') ifTrue:[
-                "/
-                "/ conflict; someone else checked in something in the meanwhile,
-                "/ and there is a conflict between this version and the checked in version.
-                "/
-
-                changesAsLogged := changesAsLogged asCollectionOfLines.
-
-                msg := 'The source of ' , className , ' has been changed in the meanwhile as listed below.
-
-Your new changes (based upon rev. ' , revision printString , ') CONFLICT with those changes.
-
-You should fix things by comparing your class with the most recent repository version
-and change your methods avoiding conflicts. Then checkin again.
-'.
-
-                answer := self checkinTroubleDialog:'Version conflict'
-                     message:msg
-                     log:changesAsLogged
-                     abortable:false
-                     option:'Show conflicts'
-                     option2:'Resolve conflicts'
-                     option3:'Do NOT Merge - Force my Code'.
-
-                answer == #option ifTrue:[
-                    "/
-                    "/ show conflicts in a 3-way DiffTextView ...
-                    "/
-                    Diff3TextView
-                        openOnMergedText:(tempdir construct:checkoutName) readStream contents
-                        label:'your version (checkin attempt)'
-                        label:'original (base version)'
-                        label:'newest repository version'.
-                ].
-
-                answer == #option2 ifTrue:[
-                    "/
-                    "/ allow checkin of repair version
-                    "/ this is error prone ...
-                    "/
-                    "/
-                    "/ show merged version in an editor ...
-                    "/ ... accept will check it in.
-                    "/
-                    emphasizedText := (tempdir construct:checkoutName) readStream contents.
-                    emSep := (Array with:(#color->Color black)
-                                 with:(#backgroundColor->Color green)).
-                    emphasizedText := Diff3TextView
-                                emphasizeMergedDiff3Text:emphasizedText
-                                emphasize1:(Array with:(#color->Color white)
-                                                  with:(#backgroundColor->Color blue))
-                                emphasize2:(Array with:(#color->Color white)
-                                                  with:(#backgroundColor->Color red))
-                                emphasizeSep:emSep.
-
-                    comment :=
-'"/ ***************************************************************
-"/ This text contains your current versions code (blue)
-"/ merged with the conflicting code as found in the repository (red) which resulted
-"/ from some other checkin.
-"/ Each such conflict is surrounded by green text (like this paragraph).
-"/
-"/ Please have a look at ALL the conflicts and fix things as appropriate.
-"/ Delete the green lines as a confirmation - I will not checkin the changed text,
-"/ unless no more green parts are present. This includes this comment at the top.
-"/ ***************************************************************
-'.
-                    comment := (Text string:comment emphasis:emSep) asStringCollection.
-                    emphasizedText := comment , emphasizedText.
-
-                    didAccept := false. checkInRepaired := true.
-                    [didAccept not and:[checkInRepaired]] whileTrue:[
-                        editor := RCSConflictEditTextView
-                                    setupWith:emphasizedText
-                                    title:'Resolve conflicts in ' , className , ', 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 notEmptyOrNil 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.
-                            ]
-                        ].
-
-                    ].
-
-                    checkInRepaired ifTrue:[
-                        [
-                            out := (tempdir construct:checkoutName) writeStream.
-                            out nextPutAll:(repairedText asString string).
-                            didAccept := true.
-                            out close.
-                        ] on:FileStream openErrorSignal do:[:ex|
-                            self warn:'could not write file ' , (tempdir constructString:checkoutName).
-                            checkInRepaired := false.
-                        ].
-                    ]
-                ].
-
-                answer == #option3 ifTrue:[
-                    "/
-                    "/ force checkin of new version
-                    "/
-                    "/
-                    "/ show merged version in an editor ...
-                    "/ ... accept will check it in.
-                    "/
-                    [
-                        out := (tempdir construct:checkoutName) writeStream.
-                        self fileOutSourceCodeOf: cls on:out.
-                        out close.
-                        didAccept := true.
-                        checkInNew := checkInRepaired := true.
-                    ] on:FileStream openErrorSignal do:[:ex|
-                        self warn:'could not write file ' , (tempdir constructString:checkoutName).
-                    ].
-                ].
-
-                checkInRepaired ifTrue:[
-                    checkInNew ifTrue:[
-                        Transcript showCR:('CVSSourceCodeManager [info]: checking in %1 (%2) (force)...' bindWith:className with:modulePath).
-                    ] ifFalse:[
-                        conflictResolvedManually := true.    "/ checkInRepaired and:[checkInNew not].
-                        Transcript showCR:('CVSSourceCodeManager [info]: checking in %1 (%2) (manually repaired)...' bindWith:className with:modulePath).
-                    ].
-                ] ifFalse:[
-                    Transcript showCR:'checkin of ' , className , ' aborted (conflicting changes; repository unchanged)'.
-                    self reportError:'checkin of ' , className , ' aborted (conflicting changes; repository unchanged)'.
-                    ^ false.
-                ].
-            ] ifFalse:[
-                ((whatHappened startsWith:'U ')
-                or:[ (whatHappened startsWith:'P ') ]) ifTrue:[
-                    "/
-                    "/ nothing changed here, but the repository already contains
-                    "/ a newer version.
-                    "/
-
-                    self information:'nothing changed in your ''' , className , ''';
-but repository already contains a newer version (repository unchanged).'.
-                    ^ true.
-                ] ifFalse:[
-                    "/
-                    "/ unexpected
-                    "/
-                    self warn:'unexpected message from CVS:
-' , whatHappened , '
-
-No checkin performed.'.
-                    self reportError:'*** cannot checkin ' , className , ' (unexpected CVS response; repository unchanged)'.
-                    ^ false.
-                ]
-            ]
-        ].
-
-
-        "/
-        "/ now check it in again
-        "/
-        self activityNotification:'CVS: Saving ' , cls name , ' in repository...'.
-
-        logMsg := logMsg replChar:$"  withString:'\"'.
-
-        OperatingSystem isUNIXlike ifFalse:[
-            "/ save the log message into another tempFile ...
-            logTmp := Filename newTemporaryIn:tempdir.
-            s := logTmp writeStream.
-            s nextPutAll:logMsg.
-            s close.
-
-            cmd := 'commit -F "', logTmp baseName, '" ', checkoutName, ' >', '"' , cmdOut name , '"'.
-        ] ifTrue:[
-            "/
-            "/ CVS up to V1.9.14 prints the 'new revision' to stderr,
-            "/ CVS V1.9.16 to stdout.
-            "/
-            cmd := 'commit -m "', logMsg, '" ', checkoutName, ' >', '"', cmdOut name, '"' , ' 2>&1'.
-        ].
-        (self
-            executeCVSCommand:cmd
-            module:moduleDir
-            inDirectory:tempdir name
-        ) ifFalse:[
-            (cmdOut exists and:[cmdOut fileSize > 0]) ifTrue:[
-                whatHappened := cmdOut contentsOfEntireFile asString.
-            ] ifFalse:[
-                whatHappened := '<< no message >>'
-            ].
-            self warn:'The following problem was reported by cvs:
-
-' , whatHappened , '
-
-The class has NOT been checked into the repository.'.
-
-            logTmp notNil ifTrue:[logTmp remove].
-            self reportError:'cannot checkin modified class source'.
-            ^ false.
-        ].
-        logTmp notNil ifTrue:[logTmp remove].
-        (cmdOut exists and:[cmdOut fileSize > 0]) ifTrue:[
-            whatHappened := cmdOut contentsOfEntireFile asString.
-        ] ifFalse:[
-            whatHappened := nil
-        ].
-    ] ensure:[
-        OsError handle:[:ex |
-            Dialog warn:('Warning: some problem encountered when trying to remove a temporary workfile:\\%1\\The checkin was successful, though.\Please remove those temporary files later.' withCRs
-                        bindWith:ex description).
-            ex proceed.
-        ] do:[
-            tempdir notNil ifTrue:[ tempdir recursiveRemove ].
-            cmdOut notNil ifTrue:[ cmdOut remove ].
-        ].
-    ].
-
-    "/
-    "/ fetch the new revision nr as found in the commit commands output
-    "/
-    (whatHappened isEmptyOrNil) ifTrue:[
-        'CVSSourceCodeManager [warning]: unexpected empty checkin command output' errorPrintCR.
-    ] ifFalse:[
-        whatHappened := whatHappened asCollectionOfLines asStringCollection.
-        idx := whatHappened indexOfLineStartingWith:'new revision:'.
-        idx == 0 ifTrue:[
-            'CVSSourceCodeManager [error]: unexpected checkin command output (no new-revision info)' errorPrintCR.
-        ] ifFalse:[
-            l := whatHappened at:idx.
-            newRevision := (l copyFrom:14 to:(l indexOf:$; startingAt:14)-1) withoutSpaces.
-        ]
-    ].
-
-    "/
-    "/ if there was no merge (i.e. the current version has been checked in unchanged):
-    "/   patch the classes revisionInfo (but keep binaryRevision unchanged) to the new revision
-    "/   this makes everyone here believe, that the incore version of the class is based upon
-    "/   the newly checked in version.
-    "/   (however, the binaryRevision must remain as it is - we will need it to fetch the sourceCode
-    "/    correctly for all unchanged methodss)
-    "/
-    "/ if there was a merge (i.e. the repository now contains a merge of the current and some
-    "/ other version):
-    "/    patch the classes revisionInfo (again, keep the binaryRevision) to the old revision
-    "/    and add a 'm' (for merged).
-    "/    If we later checkin again, the new checkin will be again based on the current revision
-    "/
-    newRevision notNil ifTrue:[
-        (didMerge or:[conflictResolvedManually]) ifFalse:[
-            "/ new code:
-            cls revisionString notEmptyOrNil ifTrue:[
-                newRevision isNil ifTrue:[
-                    'CVSSourceCodeManager [error]: got no valid revisionString (class checked in, but no valid revision returned)' errorPrintCR
-                ] ifFalse:[
-                    newString := self updatedRevisionStringOf:cls forRevision:newRevision andUser:OperatingSystem getLoginName with:cls revisionString.
-                    newString isNil ifTrue:[
-                        'CVSSourceCodeManager [error]: failed to update revisionString (class checked in, but no revision method)' errorPrintCR
-                    ] ifFalse:[
-                        self updateVersionMethodOf:cls for:newString.
-                        cls revision ~= newRevision ifTrue:[
-                            'CVSSourceCodeManager [error]: failed to update revisionString' errorPrintCR
-                        ].
-                    ].
-                ].
-                self activityNotification:'Done.'.
-            ] ifFalse:[
-                self activityNotification:'CVS: Fetch new revision number of ', cls name.
-
-                changeLog := self revisionLogOf:cls fromRevision:newRevision toRevision:newRevision.
-                (changeLog isNil or:[(changeLog at:#revisions) size ~~ 1]) ifTrue:[
-                    force ifTrue:[
-                        changeLog := self revisionLogOfContainer:classFileName directory:packageDir module:moduleDir.
-                    ].
-                ].
-                (changeLog isNil or:[(changeLog at:#revisions) size ~~ 1]) ifTrue:[
-                    'CVSSourceCodeManager [error]: failed to update revisionString (no log)' errorPrintCR.
-                    self updateVersionMethodOf:cls for:'$' , 'Header' , '$'.  "/ concatenated to avoid RCS expansion
-                ] ifFalse:[
-                    entry := (changeLog at:#revisions) first.
-                    newString := self revisionStringFromLog:changeLog entry:entry forClass:cls.
-                    self updateVersionMethodOf:cls for:newString.
-                    cls revision ~= newRevision ifTrue:[
-                        'CVSSourceCodeManager [error]: failed to update revisionString' errorPrintCR
-                    ]
-                ]
-            ]
-        ] ifTrue:[
-            "/ If the conflict was resolved manually, do NOT update the revision method
-            "/ (to get a new conflict in the next check-in)
-
-            "/ If there was a merge, update the revision method adding an 'm'"
-            didMerge ifTrue: [
-                newString := self updatedRevisionStringOf:cls forRevision:nil with:cls revisionString.
-                newString notNil ifTrue:[ self updateVersionMethodOf:cls for:newString ].
-            ]
-        ].
-    ].
-
-    Class addChangeRecordForClassCheckIn:cls.
-    self postCheckInClass:cls.
-
-    conflictResolvedManually ifTrue:[
-        (Dialog
-            confirm:'Now the repository contains a merge between your and the other changes.
-However, the class in your image does NOT contain the other changes.
-This will lead to more conflict-resolving whenever you check this class in again later,
-unless you load the newest (merged) version of the class from the repository.
-
-I recommend doing this as soon as possible via your browser''s checkout function.'
-            title:'Code Merged'
-            yesLabel:'OK' noLabel:'Update (Load Merged Code)'
-        ) ifFalse:[
-            self utilities
-                checkoutClass:cls
-                askForRevision:false
-                askForMerge:false
-                askForConfirmation:false.
-        ].
-    ].
-    ^ true
-
-    "
-     SourceCodeManager checkinClass:Array logMessage:'testing only'
-    "
-
-    "Created: / 11-09-1996 / 16:16:11 / cg"
-    "Modified: / 26-02-1998 / 17:34:16 / stefan"
-    "Modified: / 31-07-2013 / 18:07:53 / cg"
-!
-
-checkinClass:cls fileName:classFileName directory:packageDir module:moduleDir source:sourceFileName logMessage:logMessage force:forceArg asBranch:branchTag
-    "enter a classes source code (which has been already filed out into sourceFileName)
-     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 revision newestRevision logTmp
-     cmdOut whatHappened s entry idx changeLog changesAsLogged l
-     newRevision newString binRevision className msg answer didMerge
-     modulePath time
-     editor checkInRepaired checkInNew didAccept emphasizedText repairedText out
-     emSep comment force conflictResolvedManually revisionOption|
-
-    force := forceArg.
-
-    className := cls name.
-    cls isPrivate ifTrue:[
-        self reportError:'refuse to check in private classes.'.
-        ^ false.
-    ].
-    revision := cls revisionOfManager:self.
-    (revision notNil and:[revision endsWith:$m]) ifTrue:[
-        "/ this class has already been checked in with a merge,
-        "/ but not reloaded from the repository.
-        "/ must use the original revision string.
-        revision := revision copyButLast:1.
-    ].
-    binRevision := cls binaryRevision.
-    binRevision notNil ifTrue:[
-        revision ~= binRevision ifTrue:[
-            Transcript showCR:('CVSSourceCodeManager [info]: class ' , className , ' is based upon ' , binRevision , ' but has revision ' , (revision ? '?'))
-        ]
-    ].
-
-    revision isNil ifTrue:[
-        revision := newestRevision := self newestRevisionOf:cls.
-        revision isNil ifTrue:[
-            force ifTrue:[
-                revision := newestRevision := self newestRevisionInFile:classFileName directory:packageDir module:moduleDir.
-                revision isNil ifTrue:[
-                    revision := '1.0'   "/ initial checkin
-                ].
-            ] ifFalse:[
-                revision := '1.0'   "/ initial checkin
-            ]
-        ] ifFalse:[
-            revision == #deleted ifTrue:[
-                revision := '0'     "/ to force cvs-adding, which resurrects the file from the Attic
-            ].
-        ].
-    ].
-
-    logMessage isNil ifTrue:[
-        logMsg := ''.
-    ] ifFalse:[
-        logMsg := logMessage asSingleByteStringIfPossible.
-        logMsg isWideString ifTrue:[
-            self reportError:'cvs cannot handle unicode in logMessage'.
-            ^ false.
-        ].
-    ].
-
-    cmdOut := Filename newTemporary.
-    cmdOut exists ifTrue:[
-        cmdOut remove.
-    ].
-
-    "/
-    "/ in CVS, we have to checkout the file first, in order
-    "/ to get up-to-date CVS entries, and also to be able to merge in
-    "/ other users changes.
-    "/
-
-    "/
-    "/ first, create a temporary work tree
-    "/
-    tempdir := self createTempDirectory:nil forModule:nil.
-    tempdir isNil ifTrue:[
-        ('no tempDir - cannot checkin ' , className) errorPrintCR.
-        ^ false
-    ].
-    [
-        "/
-        "/ next, create CVS/Entries and CVS/Repository with version information of current version
+        "/ next, create CVS/Entries and CVS/Repository with revision information of current revision
         "/
         packageDir isEmptyOrNil ifTrue:[
             modulePath := moduleDir
@@ -2921,7 +2211,7 @@
         self createEntryFor:checkoutName
              module:moduleDir
              in:(tempdir construct:modulePath)
-             revision:revision
+             revision:classRevision
              date:(self cvsTimeString:time)
              special:''
              overwrite:true.
@@ -2945,17 +2235,17 @@
         branchTag notEmptyOrNil ifTrue:[
             revisionOption := '-r ', branchTag.
         ] ifFalse:[
-            (revision asCollectionOfSubstringsSeparatedBy:$.) size > 2 ifTrue:[
+            (classRevision occurrencesOf:$.) > 2 ifTrue:[
                 "must be a branch, compare with branch revision"
-                revisionOption := '-r ', revision copyUpToLast:$..
+                revisionOption := '-r ', classRevision copyUpToLast:$..
             ].
         ].
 
         cmd := 'update %1 %4 %2 >"%3"'
-            bindWith:CVSUpdateOptions
-            with:classFileName
-            with:cmdOut name
-            with:revisionOption.
+                    bindWith:CVSUpdateOptions
+                    with:classFileName
+                    with:cmdOut name
+                    with:revisionOption.
 
         (self
             executeCVSCommand:cmd
@@ -3044,7 +2334,7 @@
                     entry := (changeLog at:#revisions) first.
                     newString := self revisionStringFromLog:changeLog entry:entry forClass:cls.
                     newString isEmptyOrNil ifTrue:[
-                        'CVSSourceCodeManager [error]: missng revisionString' errorPrintCR
+                        'CVSSourceCodeManager [error]: missing revisionString' errorPrintCR
                     ] ifFalse:[
                         self updateVersionMethodOf:cls for:newString.
                         cls revision ~= newRevision ifTrue:[
@@ -3055,19 +2345,20 @@
                     ]
                 ]
             ].
-
             ^ true
         ].
+
         Verbose == true ifTrue:[
             ('CVSMGR: result is: ' , whatHappened) infoPrintCR.
         ].
 
         force ifFalse:[
-            revision isNil ifTrue:[
-                changeLog := self revisionLogOf:cls.
-            ] ifFalse:[
-                changeLog := self revisionLogOf:cls fromRevision:(self revisionAfter:revision) toRevision:nil.
+            |nextRevision|
+
+            classRevision notNil ifTrue:[
+                nextRevision := self revisionAfter:classRevision.
             ].
+            changeLog := self revisionLogOf:cls fromRevision:nextRevision toRevision:nil.
             changeLog notNil ifTrue:[
                 s := CharacterWriteStream on:''.
                 self writeRevisionLogMessagesFrom:changeLog withHeader:false to:s.
@@ -3085,12 +2376,11 @@
         "/ cvs above rel10 returns a multiline info ...
         "/ we have to extract the one line which states what happened.
         "/
-        whatHappened := whatHappened asCollectionOfLines asStringCollection.
-        whatHappened := whatHappened select:[:line |
-                            (line startsWith:'RCS file') not
-                            and:[(line startsWith:'retrieving') not
-                            and:[(line startsWith:'Merging') not
-                            and:[line size > 0]]]
+        whatHappened := whatHappened asCollectionOfLines reject:[:line |
+                            line isEmpty
+                            or:[(line startsWith:'RCS file')
+                            or:[(line startsWith:'retrieving')
+                            or:[(line startsWith:'Merging')]]]
                         ].
         whatHappened := whatHappened asString.
 
@@ -3099,8 +2389,8 @@
             "/ merged in changes / resurrected
             "/
             (force
-            or:[changeLog isNil
-            or:[(changeLog at:#revisions ifAbsent:nil) isEmptyOrNil]]) ifTrue:[
+             or:[changeLog isNil
+             or:[(changeLog at:#revisions ifAbsent:nil) isEmptyOrNil]]) ifTrue:[
                 "/
                 "/ pretty good - nothing has changed in the meanwhile
                 "/
@@ -3116,9 +2406,9 @@
                 changesAsLogged := changesAsLogged asCollectionOfLines.
 
                 s := CharacterWriteStream new.
-                self fileOutSourceCodeOf: cls on:s.
-                mySource := s contents asString.
-                mergedSource := (tempdir construct:checkoutName) readStream contents asString.
+                self fileOutSourceCodeOf:cls on:s.
+                mySource := s contents.
+                mergedSource := (tempdir construct:checkoutName) readStream contentsAsString.
 
                 mySource = mergedSource ifTrue:[
                     msg := 'The source of ' , className , ' has been changed in the meanwhile as listed below.
@@ -3136,7 +2426,7 @@
                 ] ifFalse:[
                     msg := 'The source of ' , className , ' has been changed in the meanwhile as listed below.
 
-If you continue, your new changes (based upon rev. ' , revision printString , ') will be MERGED
+If you continue, your new changes (based upon rev. ' , classRevision printString , ') will be MERGED
 into the newest revision. This will combine the other version with your changes
 into a new common revision which may be different from both.
 Although this is a nice feature, it may fail to create the expected result in certain situations.
@@ -3212,7 +2502,7 @@
 
                 msg := 'The source of ' , className , ' has been changed in the meanwhile as listed below.
 
-Your new changes (based upon rev. ' , revision printString , ') CONFLICT with those changes.
+Your new changes (based upon rev. ' , classRevision printString , ') CONFLICT with those changes.
 
 You should fix things by comparing your class with the most recent repository version
 and change your methods avoiding conflicts. Then checkin again.
@@ -3238,6 +2528,8 @@
                 ].
 
                 answer == #option2 ifTrue:[
+                    |diffComment|
+
                     "/
                     "/ allow checkin of repair version
                     "/ this is error prone ...
@@ -3257,7 +2549,7 @@
                                                   with:(#backgroundColor->Color red))
                                 emphasizeSep:emSep.
 
-                    comment :=
+                    diffComment :=
 '"/ ***************************************************************
 "/ This text contains your current versions code (blue)
 "/ merged with the conflicting code as found in the repository (red) which resulted
@@ -3269,8 +2561,8 @@
 "/ unless no more green parts are present. This includes this comment at the top.
 "/ ***************************************************************
 '.
-                    comment := (Text string:comment emphasis:emSep) asStringCollection.
-                    emphasizedText := comment , emphasizedText.
+                    diffComment := (Text string:diffComment emphasis:emSep) asStringCollection.
+                    emphasizedText := diffComment , emphasizedText.
 
                     didAccept := false. checkInRepaired := true.
                     [didAccept not and:[checkInRepaired]] whileTrue:[
@@ -3346,7 +2638,7 @@
                 ].
             ] ifFalse:[
                 ((whatHappened startsWith:'U ')
-                or:[ (whatHappened startsWith:'P ') ]) ifTrue:[
+                 or:[whatHappened startsWith:'P ']) ifTrue:[
                     "/
                     "/ nothing changed here, but the repository already contains
                     "/ a newer version.
@@ -3375,16 +2667,15 @@
         "/
         self activityNotification:'CVS: Saving ' , cls name , ' in repository...'.
 
-        logMsg := logMsg replChar:$"  withString:'\"'.
+        logMsg := logMsg replChar:$" withString:'\"'.
 
         OperatingSystem isUNIXlike ifFalse:[
             "/ save the log message into another tempFile ...
-            logTmp := Filename newTemporaryIn:tempdir.
-            s := logTmp writeStream.
+            s := FileStream newTemporaryIn:tempdir.
             s nextPutAll:logMsg.
             s close.
 
-            cmd := 'commit -F "', logTmp baseName, '" ', checkoutName, ' >', '"' , cmdOut name , '"'.
+            cmd := 'commit -F "', s fileName baseName, '" ', checkoutName, ' >', '"' , cmdOut name , '"'.
         ] ifTrue:[
             "/
             "/ CVS up to V1.9.14 prints the 'new revision' to stderr,
@@ -3398,7 +2689,7 @@
             inDirectory:tempdir name
         ) ifFalse:[
             (cmdOut exists and:[cmdOut fileSize > 0]) ifTrue:[
-                whatHappened := cmdOut contentsOfEntireFile asString.
+                whatHappened := cmdOut contentsAsString.
             ] ifFalse:[
                 whatHappened := '<< no message >>'
             ].
@@ -3408,13 +2699,11 @@
 
 The class has NOT been checked into the repository.'.
 
-            logTmp notNil ifTrue:[logTmp remove].
             self reportError:'cannot checkin modified class source'.
             ^ false.
         ].
-        logTmp notNil ifTrue:[logTmp remove].
         (cmdOut exists and:[cmdOut fileSize > 0]) ifTrue:[
-            whatHappened := cmdOut contentsOfEntireFile asString.
+            whatHappened := cmdOut contentsAsString.
         ] ifFalse:[
             whatHappened := nil
         ].
@@ -3435,7 +2724,7 @@
     (whatHappened isEmptyOrNil) ifTrue:[
         'CVSSourceCodeManager [warning]: unexpected empty checkin command output' errorPrintCR.
     ] ifFalse:[
-        whatHappened := whatHappened asCollectionOfLines asStringCollection.
+        whatHappened := whatHappened asCollectionOfLines.
         idx := whatHappened indexOfLineStartingWith:'new revision:'.
         idx == 0 ifTrue:[
             'CVSSourceCodeManager [error]: unexpected checkin command output (no new-revision info)' errorPrintCR.
@@ -3538,7 +2827,7 @@
     "
 
     "Created: / 13-03-2017 / 15:38:19 / stefan"
-    "Modified: / 14-03-2017 / 16:02:33 / stefan"
+    "Modified: / 31-03-2017 / 15:42:32 / stefan"
 !
 
 checkoutModule:aModule directory:aPackage andDo:aBlock