#OTHER by stefan
authorStefan Vogel <sv@exept.de>
Fri, 30 Sep 2016 16:44:57 +0200
changeset 16876 0f63648af10e
parent 16875 7f9ac5b997bc
child 16877 06db0d151de3
#OTHER by stefan Use (*WriteStream on:'') instead of (*WriteStream on:String new)
PerforceSourceCodeManagerUtilities.st
--- a/PerforceSourceCodeManagerUtilities.st	Thu Sep 29 17:26:44 2016 +0200
+++ b/PerforceSourceCodeManagerUtilities.st	Fri Sep 30 16:44:57 2016 +0200
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -2473,111 +2475,111 @@
       localRevision resultSource definitionClass descriptionInfo resolveFiles depotPath localPath checkInDefinition fileStatDict|
 
     self temporaryWorkSpace isNil ifTrue:[
-	self perforceError raiseErrorString:('Error getting temporary workspace when try to merge or resolve conflicts for ', aNumber printString, '.').
-	^false.
+        self perforceError raiseErrorString:('Error getting temporary workspace when try to merge or resolve conflicts for ', aNumber printString, '.').
+        ^false.
     ].
     descriptionInfo := (self getChangeDespriptionInfoFor:aNumber printString).
     descriptionInfo isNil ifTrue:[
-	^false.
+        ^false.
     ].
     resolveFiles := descriptionInfo at:#Files ifAbsent:nil.
     resolveFiles isNil ifTrue:[
-	^false.
+        ^false.
     ].
     resolveFiles do:[:aFileLine|
-	depotPath := (aFileLine copyTo:((aFileLine lastIndexOf:$#) - 1 )) withoutTrailingSeparators.
-	localPath := self temporaryWorkSpace getLocalPathForDepotPath:depotPath.
-	fileStatDict := self temporaryWorkSpace getFileStatForPathname:localPath.
-	(fileStatDict includesKey:'unresolved') ifTrue:[
-	    definitionClass := Smalltalk at:(localPath asFilename withoutSuffix baseName asSymbol) ifAbsent:nil.
-	    checkInDefinition := PerforceSourceCodeManager getCheckInDefinitionForClass:definitionClass.
-	    localRevision := checkInDefinition getLocalRevisionNumber.
-	    tmpFilename := localPath asFilename.
-	    perforceCommand := ('resolve -af  "' , tmpFilename pathName, '"').
-	    outputStream := ReadWriteStream on:''.
-	    errorStream := ReadWriteStream on:''.
-	    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
-		inputFrom:nil outputTo:outputStream
-		errorTo:errorStream
-		logHeader:('resolving ', tmpFilename pathName, '.').
-	    result ifFalse:[
-		^ false
-	    ].
-	    "check for conflicts"
-	    changesAsLogged := StringCollection new.
-	    inStream := ReadStream on:(outputStream contents).
-
-	    [inStream atEnd not] whileTrue:[
-		line:= inStream nextLine.
-		line notNil ifTrue:[
-		    (line startsWith:'Diff chunks:') ifTrue:[
-			changesAsLogged add:line.
-			changesDict := Dictionary new.
-			chunksPart := line copyFrom:('Diff chunks:' size + 1).
-			(chunksPart asCollectionOfSubstringsSeparatedBy:$+) do:[:eachElement|
-			    words := eachElement asCollectionOfWords.
-			    changesDict at:words second asSymbol put:words first asNumber.
-			].
-		    ].
-		].
-	    ].
-	    s := WriteStream on:String new.
-	    PerforceSourceCodeManager fileOutSourceCodeOf:definitionClass on:s.
-	    mergedSource := tmpFilename readStream contents asString.
-	    mySource := s contents asString.
-	    resultSource := self askForMergedSource:mergedSource
-		    localSource:mySource
-		    changesDict:changesDict
-		    haveRevision:(fileStatDict at:'haveRev' ifAbsent:nil)
-		    changesAsLogged:changesAsLogged
-		    pathName:tmpFilename pathName
-		    definitionClass:definitionClass.
-	    resultSource isNil ifTrue:[
-		^false.
-	    ].
-	    "now we have a merge - lets get latest revision and write on it "
-	    perforceCommand := ('revert "' , tmpFilename pathName, '"').
-	    outputStream := ReadWriteStream on:''.
-	    errorStream := ReadWriteStream on:''.
-	    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
-		inputFrom:nil outputTo:outputStream
-		errorTo:errorStream
-		logHeader:('revert after resolving ', tmpFilename pathName, '.').
-	    result ifFalse:[
-		^ false
-	    ].
-
-	    tmpFilename remove.
-
-	    perforceCommand := ('sync -f "' , tmpFilename pathName, '"').
-	    outputStream := ReadWriteStream on:''.
-	    errorStream := ReadWriteStream on:''.
-	    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
-		inputFrom:nil outputTo:outputStream
-		errorTo:errorStream
-		logHeader:('sync after resolving ', tmpFilename pathName, '.').
-	    result ifFalse:[
-		^ false
-	    ].
-
-	    perforceCommand := ('edit -c ', aNumber printString, ' "' , tmpFilename pathName, '"').
-	    outputStream := ReadWriteStream on:''.
-	    errorStream := ReadWriteStream on:''.
-	    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
-		inputFrom:nil outputTo:outputStream
-		errorTo:errorStream
-		logHeader:('edit after resolving ', tmpFilename pathName, '.').
-	    result ifFalse:[
-		^ false
-	    ].
-
-	    "write my result"
-	    resultSource notNil ifTrue:[
-		s := tmpFilename writeStream.
-		s nextPutAll:resultSource.
-		s close.
-	    ].
-	].
+        depotPath := (aFileLine copyTo:((aFileLine lastIndexOf:$#) - 1 )) withoutTrailingSeparators.
+        localPath := self temporaryWorkSpace getLocalPathForDepotPath:depotPath.
+        fileStatDict := self temporaryWorkSpace getFileStatForPathname:localPath.
+        (fileStatDict includesKey:'unresolved') ifTrue:[
+            definitionClass := Smalltalk at:(localPath asFilename withoutSuffix baseName asSymbol) ifAbsent:nil.
+            checkInDefinition := PerforceSourceCodeManager getCheckInDefinitionForClass:definitionClass.
+            localRevision := checkInDefinition getLocalRevisionNumber.
+            tmpFilename := localPath asFilename.
+            perforceCommand := ('resolve -af  "' , tmpFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
+                inputFrom:nil outputTo:outputStream
+                errorTo:errorStream
+                logHeader:('resolving ', tmpFilename pathName, '.').
+            result ifFalse:[
+                ^ false
+            ].
+            "check for conflicts"
+            changesAsLogged := StringCollection new.
+            inStream := ReadStream on:(outputStream contents).
+
+            [inStream atEnd not] whileTrue:[
+                line:= inStream nextLine.
+                line notNil ifTrue:[
+                    (line startsWith:'Diff chunks:') ifTrue:[
+                        changesAsLogged add:line.
+                        changesDict := Dictionary new.
+                        chunksPart := line copyFrom:('Diff chunks:' size + 1).
+                        (chunksPart asCollectionOfSubstringsSeparatedBy:$+) do:[:eachElement|
+                            words := eachElement asCollectionOfWords.
+                            changesDict at:words second asSymbol put:words first asNumber.
+                        ].
+                    ].
+                ].
+            ].
+            s := WriteStream on:''.
+            PerforceSourceCodeManager fileOutSourceCodeOf:definitionClass on:s.
+            mergedSource := tmpFilename readStream contents asString.
+            mySource := s contents asString.
+            resultSource := self askForMergedSource:mergedSource
+                    localSource:mySource
+                    changesDict:changesDict
+                    haveRevision:(fileStatDict at:'haveRev' ifAbsent:nil)
+                    changesAsLogged:changesAsLogged
+                    pathName:tmpFilename pathName
+                    definitionClass:definitionClass.
+            resultSource isNil ifTrue:[
+                ^false.
+            ].
+            "now we have a merge - lets get latest revision and write on it "
+            perforceCommand := ('revert "' , tmpFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
+                inputFrom:nil outputTo:outputStream
+                errorTo:errorStream
+                logHeader:('revert after resolving ', tmpFilename pathName, '.').
+            result ifFalse:[
+                ^ false
+            ].
+
+            tmpFilename remove.
+
+            perforceCommand := ('sync -f "' , tmpFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
+                inputFrom:nil outputTo:outputStream
+                errorTo:errorStream
+                logHeader:('sync after resolving ', tmpFilename pathName, '.').
+            result ifFalse:[
+                ^ false
+            ].
+
+            perforceCommand := ('edit -c ', aNumber printString, ' "' , tmpFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
+                inputFrom:nil outputTo:outputStream
+                errorTo:errorStream
+                logHeader:('edit after resolving ', tmpFilename pathName, '.').
+            result ifFalse:[
+                ^ false
+            ].
+
+            "write my result"
+            resultSource notNil ifTrue:[
+                s := tmpFilename writeStream.
+                s nextPutAll:resultSource.
+                s close.
+            ].
+        ].
     ].
     ^true
 !