class: PerforceSourceCodeManagerUtilities
authorClaus Gittinger <cg@exept.de>
Thu, 13 Jun 2013 17:27:17 +0200
changeset 12893 61328b650b79
parent 12892 1215124609dc
child 12894 29c0c38114f0
class: PerforceSourceCodeManagerUtilities added: #askForContainer:title:note:initialModule:initialPackage:initialFileName:forNewContainer: #checkInInfoDialogClass #defineSourceContainerForClass:usingManager:title:text:createDirectories:createContainer: changed: #checkinClass:withInfo:withCheck:usingManager:
PerforceSourceCodeManagerUtilities.st
--- a/PerforceSourceCodeManagerUtilities.st	Thu Jun 13 16:14:27 2013 +0200
+++ b/PerforceSourceCodeManagerUtilities.st	Thu Jun 13 17:27:17 2013 +0200
@@ -44,6 +44,11 @@
 
 !PerforceSourceCodeManagerUtilities class methodsFor:'class access'!
 
+checkInInfoDialogClass
+
+    ^P4CheckinInfoDialog
+!
+
 submitInfoDialogClass
 
     ^ SubmitInfoDialog
@@ -59,6 +64,188 @@
 
 !PerforceSourceCodeManagerUtilities methodsFor:'utilities-cvs'!
 
+askForContainer:boxText title:title note:notice initialModule:initialModule initialPackage:initialPackage initialFileName:initialFileName forNewContainer:forNewContainer
+    "open a dialog asking for a source container;
+     return a dictionary containing module, package and filename,
+     or nil if canceled."
+
+    |box y component answer
+     moduleHolder packageHolder fileNameHolder
+     module package fileName
+     knownContainers knownPackages packageUpdater
+     packageBoxComponent fileNameBoxComponent fileNameUpdater|
+
+    knownContainers := Set new.
+    Smalltalk allClassesDo:[:cls | |pckg|
+	pckg := cls package.
+	pckg size > 0 ifTrue:[
+	    knownContainers add:(pckg upTo:$:)
+	]
+    ].
+    knownContainers := knownContainers asOrderedCollection.
+    knownContainers := knownContainers select:[:module | module isBlank not].
+    knownContainers sort.
+
+    packageUpdater := [
+	|theModulePrefix|
+
+	theModulePrefix := moduleHolder value , ':'.
+
+	Cursor wait showWhile:[
+	    knownPackages := Set new.
+	    Smalltalk allClassesDo:[:cls | |pckg idx|
+		pckg := cls package.
+		pckg size > 0 ifTrue:[
+		    (pckg startsWith:theModulePrefix) ifTrue:[
+			idx := pckg indexOf:$:.
+			knownPackages add:(pckg copyFrom:idx + 1)
+		    ]
+		]
+	    ].
+	    knownPackages := knownPackages asOrderedCollection.
+	    knownPackages := knownPackages select:[:package | package isBlank not].
+	    knownPackages sort.
+	    packageBoxComponent list:knownPackages.
+	].
+    ].
+
+    fileNameUpdater := [
+	|module package files|
+
+	Cursor read showWhile:[
+	    module := moduleHolder value ? (PackageId noProjectID).
+	    package := packageHolder value ? (PackageId noProjectID).
+
+	    files := PerforceSourceCodeManager getExistingContainersInModule:module directory:package.
+	    files := files asOrderedCollection.
+	    files := files select:[:eachFile | eachFile asFilename hasSuffix:'st'].
+	    files sort.
+	    fileNameBoxComponent list:files.
+	].
+    ].
+
+    moduleHolder := initialModule asValue.
+    packageHolder := initialPackage asValue.
+    fileNameHolder := initialFileName asValue.
+
+    resources := self classResources.
+
+    "/
+    "/ open a dialog for this
+    "/
+    box := DialogBox new.
+    box label:title.
+
+    component := box addTextLabel:boxText withCRs.
+    component adjust:#left; borderWidth:0.
+    box addVerticalSpace.
+    box addVerticalSpace.
+
+    y := box yPosition.
+    component := box addTextLabel:(resources string:'Module:').
+    component width:0.4; adjust:#right.
+    box yPosition:y.
+    component := box addComboBoxOn:moduleHolder tabable:true.
+    component list:knownContainers.
+
+"/    component := box addInputFieldOn:moduleHolder tabable:true.
+    component width:0.6; left:0.4; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+
+    box addVerticalSpace.
+    y := box yPosition.
+    component := box addTextLabel:(resources string:'Package:').
+    component width:0.4; adjust:#right.
+    box yPosition:y.
+    packageBoxComponent := component := box addComboBoxOn:packageHolder tabable:true.
+"/    component := box addInputFieldOn:packageHolder tabable:true.
+    component width:0.6; left:0.4; "immediateAccept:true; "acceptOnLeave:true; cursorMovementWhenUpdating:#beginOfLine.
+    packageUpdater value.
+    moduleHolder onChangeEvaluate:packageUpdater.
+
+    box addVerticalSpace.
+    y := box yPosition.
+    component := box addTextLabel:(resources string:'Filename:').
+    component width:0.4; adjust:#right.
+    box yPosition:y.
+
+    forNewContainer ifTrue:[
+	component := box addInputFieldOn:fileNameHolder tabable:true.
+	component width:0.6; left:0.4; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+    ] ifFalse:[
+	fileNameBoxComponent := component := box addComboBoxOn:fileNameHolder tabable:true.
+	component width:0.6; left:0.4; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+	fileNameUpdater value.
+	packageHolder onChangeEvaluate:fileNameUpdater.
+    ].
+
+    box addVerticalSpace.
+
+    notice notNil ifTrue:[
+	component := box addTextLabel:notice.
+	component adjust:#left; borderWidth:0.
+    ].
+
+    box addVerticalSpace.
+    box addAbortAndOkButtons.
+
+    (YesToAllNotification notNil and:[YesToAllNotification isHandled]) ifTrue:[
+	component := Button label:'Yes to all'.
+	component action:[
+			    YesToAllNotification queryWith:true.
+			    box doAccept.
+			    box okPressed.
+			 ].
+	(DialogBox defaultOKButtonAtLeft) ifTrue:[
+	    box addButton:component after:nil.
+	] ifFalse:[
+	    box addButton:component before:nil.
+	].
+    ].
+    (AbortAllSignal isHandled) ifTrue:[
+	component := Button label:'Cancel all'.
+	component action:[
+			    box hide.
+			    AbortAllSignal raiseSignal.
+			 ].
+	(DialogBox defaultOKButtonAtLeft) ifTrue:[
+	    box addButton:component before:nil.
+	] ifFalse:[
+	    box addButton:component after:nil.
+	].
+    ].
+
+    (YesToAllQuery notNil and:[YesToAllQuery isHandled]) ifTrue:[
+	answer := YesToAllQuery query.
+    ].
+
+    answer isNil ifTrue:[
+	box showAtPointer.
+	answer := box accepted
+    ].
+
+    box destroy.
+    answer ifFalse:[
+	^ nil
+    ].
+
+    module := moduleHolder value withoutSpaces.
+    package := packageHolder value withoutSpaces.
+    fileName := fileNameHolder value withoutSpaces.
+    ^ Dictionary new
+	at:#module put:module;
+	at:#package put:package;
+	at:#fileName put:fileName;
+	yourself
+
+    "
+     self
+	askForContainer:'enter container' title:'container' note:'some note'
+	initialModule:'foo' initialPackage:'bar' initialFileName:'baz'
+    "
+
+    "Modified: / 23-08-2006 / 14:13:04 / cg"
+!
+
 checkinClass:aClass withInfo:aLogInfoOrNil withCheck:doCheckClass usingManager:managerOrNil
     "check a class into the source repository.
      If the argument, aLogInfoOrNil isNil, ask interactively for log-message.
@@ -66,101 +253,424 @@
 
     |logMessage checkinInfo mgr pri doSubmit|
 
+    resources := self classResources.
     doSubmit := false.
 
     aClass isLoaded ifFalse:[
-        self information:(resources string:'Cannot checkin unloaded classes (%1)' with:aClass name).
-        ^ false.
+	self information:(resources string:'Cannot checkin unloaded classes (%1)' with:aClass name).
+	^ false.
     ].
 
     mgr := managerOrNil.
     mgr isNil ifTrue:[
-        mgr := self sourceCodeManagerFor:aClass.
-        mgr isNil ifTrue:[
-            ^ false
-        ]
+	mgr := self sourceCodeManagerFor:aClass.
+	mgr isNil ifTrue:[
+	    ^ false
+	]
     ].
 
     self ensureCorrectVersionMethodsInClass:aClass usingManager:mgr.
     mgr supportsCheckinLogMessages ifTrue:[
-        (self 
-            getLogMessageForClassCheckinTakingDefaultsFromPreviousLogInfo:aLogInfoOrNil 
-            forClass:aClass
-            valuesInto:[:logMessageRet :checkinInfoRet |
-                logMessage := logMessageRet.
-                checkinInfo := checkinInfoRet.
-                checkinInfo notNil ifTrue:[
-                    doSubmit := checkinInfo submitHolder value.
-                ].
-            ]
-        ) ifFalse:[^ false].
+	(self
+	    getLogMessageForClassCheckinTakingDefaultsFromPreviousLogInfo:aLogInfoOrNil
+	    forClass:aClass
+	    valuesInto:[:logMessageRet :checkinInfoRet |
+		logMessage := logMessageRet.
+		checkinInfo := checkinInfoRet.
+		checkinInfo notNil ifTrue:[
+		    doSubmit := checkinInfo submitHolder value.
+		].
+	    ]
+	) ifFalse:[^ false].
     ].
 
     (self classIsNotYetInRepository:aClass withManager:mgr) ifTrue:[
-        (self createSourceContainerForClass:aClass usingManager:mgr) ifFalse:[
+	(self createSourceContainerForClass:aClass usingManager:mgr) ifFalse:[
 "/            self warn:'did not create a container for ''' , aClass name , ''''.
-            ^ false
-        ].
-        ^ true.
+	    ^ false
+	].
+	^ true.
     ].
 
     self activityNotification:(resources string:'checking in %1' with:aClass name).
     pri := Processor activePriority.
     Processor activeProcess withPriority:pri-1 to:pri
     do:[
-        |revision aborted|
-
-
-
-        aborted := false.
-        AbortOperationRequest handle:[:ex |
-            aborted := true.
-            ex return.
-        ] do:[
-            |checkinState cause|
-            checkinState := false.
-            cause := ''.
-            [
-                checkinState := mgr checkinClass:aClass logMessage:logMessage submit:doSubmit
-            ] on:SourceCodeManagerError do:[:ex| 
-self halt.
-                cause := ex description.
-                ex proceed.
-            ].
-
-            checkinState ifFalse:[
-                Transcript showCR:'checkin of ''' , aClass name , ''' failed - ', cause.
-                self warn:(resources stringWithCRs:'Checkin of "%1" failed\\' with:aClass name allBold),cause.
-                ^ false.
-            ].
-            checkinInfo notNil ifTrue:[
-                checkinInfo isStable ifTrue:[
-                    "set stable tag for class that has been checked in"
-                    self tagClass:aClass as:#stable.
-                ].
-                checkinInfo tagIt ifTrue:[
-                    "set an additional tag for class that has been checked in"
-                    self tagClass:aClass as:(checkinInfo tag).
-                ].
-            ].
-        ].
-        aborted ifTrue:[  |con|
-            Transcript showCR:'Checkin of ''' , aClass name , ''' aborted'.
-
-            AbortAllOperationWantedQuery query ifTrue:[
-                (Dialog 
-                    confirm:(resources stringWithCRs:'Checkin of "%1" aborted.\\Cancel all ?' with:aClass name)
-                    default:false)
-                ifTrue:[
-                    AbortAllOperationRequest raise.
-                ]
-            ].
-            ^ false.
-        ].
+	|revision aborted|
+
+
+
+	aborted := false.
+	AbortOperationRequest handle:[:ex |
+	    aborted := true.
+	    ex return.
+	] do:[
+	    |checkinState cause|
+	    checkinState := false.
+	    cause := ''.
+	    [
+		checkinState := mgr checkinClass:aClass logMessage:logMessage submit:doSubmit
+	    ] on:SourceCodeManagerError do:[:ex|
+		cause := ex description.
+		ex proceed.
+	    ].
+
+	    checkinState ifFalse:[
+		Transcript showCR:'checkin of ''' , aClass name , ''' failed - ', cause.
+		self warn:(resources stringWithCRs:'Checkin of "%1" failed\\' with:aClass name allBold),cause.
+		^ false.
+	    ].
+	    checkinInfo notNil ifTrue:[
+		checkinInfo isStable ifTrue:[
+		    "set stable tag for class that has been checked in"
+		    self tagClass:aClass as:#stable.
+		].
+		checkinInfo tagIt ifTrue:[
+		    "set an additional tag for class that has been checked in"
+		    self tagClass:aClass as:(checkinInfo tag).
+		].
+	    ].
+	].
+	aborted ifTrue:[  |con|
+	    Transcript showCR:'Checkin of ''' , aClass name , ''' aborted'.
+
+	    AbortAllOperationWantedQuery query ifTrue:[
+		(Dialog
+		    confirm:(resources stringWithCRs:'Checkin of "%1" aborted.\\Cancel all ?' with:aClass name)
+		    default:false)
+		ifTrue:[
+		    AbortAllOperationRequest raise.
+		]
+	    ].
+	    ^ false.
+	].
     ].
     ^ true
 
     "Created: / 21-12-2011 / 18:19:14 / cg"
+!
+
+defineSourceContainerForClass:aClass usingManager:mgr title:title text:boxText createDirectories:createDirs createContainer:createContainer
+    "let user specify the source-repository values for aClass"
+
+    |className
+     "oldModule oldPackage" oldFileName
+     module directory fileName nameSpace nameSpacePrefix
+     info project nm creatingNew msg
+     answer doCheckinWithoutAsking forceCheckIn rslt note
+     requiredPackage projectDefinitionClass packageId|
+
+    mgr isNil ifTrue:[^  false].
+
+    resources := self classResources.
+    aClass isLoaded ifFalse:[
+	self warn:(resources string:'Please load the %1-class first' with:aClass name).
+	^ false.
+    ].
+
+    className := aClass name.
+
+    aClass isProjectDefinition ifTrue:[
+	"/ no way - their package is already known and fix.
+	module := aClass module.
+	directory := aClass moduleDirectory.
+    ] ifFalse:[
+	"/
+	"/ defaults, if nothing at all is known
+	"/
+	projectDefinitionClass := aClass projectDefinitionClass.
+	projectDefinitionClass notNil ifTrue:[
+	    packageId := PackageId from:projectDefinitionClass package.
+	    module := packageId module.
+	    directory := packageId directory.
+	] ifFalse:[
+	    (module := LastModule) isNil ifTrue:[
+		module := (OperatingSystem getLoginName).
+	    ].
+	    (directory := LastPackage) isNil ifTrue:[
+		directory := 'private'.
+	    ].
+	].
+    ].
+
+    "/
+    "/ try to extract some useful defaults from the current project
+    "/
+    (Project notNil and:[(project := Project current) notNil]) ifTrue:[
+	directory isNil ifTrue:[
+	    (nm := project repositoryDirectory) isNil ifTrue:[
+		nm := project name
+	    ].
+	    directory := nm.
+	].
+	module isNil ifTrue:[
+	    (nm := project repositoryModule) notNil ifTrue:[
+		module := nm
+	    ]
+	].
+    ].
+
+    "/
+    "/ ask the sourceCodeManager if it knows anything about that class
+    "/ if so, take that as a default.
+    "/
+    info := mgr sourceInfoOfClass:aClass.
+    info notNil ifTrue:[
+	true "module ~= LastModule" ifTrue:[
+	    (info includesKey:#module) ifTrue:[
+		module := (info at:#module).
+	    ].
+	].
+"/        true "package ~= LastPackage" ifTrue:[
+"/            (info includesKey:#directory) ifTrue:[
+"/                package := (info at:#directory).
+"/            ].
+"/        ].
+	fileName := mgr containerFromSourceInfo:info.
+	(nameSpace := aClass nameSpace) ~~ Smalltalk ifTrue:[
+	    nameSpacePrefix := nameSpace name , '::'.
+	    (fileName startsWith:nameSpacePrefix) ifTrue:[
+		fileName := fileName copyFrom:(nameSpacePrefix size + 1).
+	    ]
+	].
+"/        (info includesKey:#fileName) ifTrue:[
+"/            fileName := (info at:#fileName).
+"/        ] ifFalse:[
+"/            (info includesKey:#expectedFileName) ifTrue:[
+"/                fileName := (info at:#expectedFileName).
+"/            ] ifFalse:[
+"/                (info includesKey:#classFileNameBase) ifTrue:[
+"/                    fileName := (info at:#classFileNameBase) , '.st'.
+"/                ]
+"/            ]
+"/        ]
+    ].
+
+    fileName isNil ifTrue:[
+	fileName := (Smalltalk fileNameForClass:aClass) , '.st'.
+    ].
+
+    OperatingSystem isMSDOSlike ifTrue:[
+	module replaceAll:$\ with:$/.
+	directory replaceAll:$\ with:$/.
+    ].
+
+    "/
+    "/ check for conflicts (i.e. if such a container already exists) ...
+    "/
+    doCheckinWithoutAsking := false.
+"/false ifTrue:[
+"/    (mgr checkForExistingContainer:fileName inModule:module directory:directory) ifTrue:[
+"/        answer := Dialog confirmWithCancel:(resources
+"/                            string:'About to change the source container.
+"/
+"/Notice: there is a container for %1 in:
+"/
+"/    %2 / %3 / %4
+"/
+"/Do you want to change it or check right into that container ?'
+"/                            with:className
+"/                            with:module
+"/                            with:directory
+"/                            with:fileName)
+"/                labels:(resources array:#('Cancel' 'Check in' 'Change')).
+"/        answer isNil ifTrue:[AbortSignal raise].
+"/        answer ifTrue:[
+"/            doCheckinWithoutAsking := false.
+"/            oldModule := module.
+"/            oldPackage := directory.
+"/            oldFileName := fileName
+"/        ] ifFalse:[
+"/            doCheckinWithoutAsking := true.
+"/            creatingNew := false.
+"/        ].
+"/    ].
+"/].
+    mgr isContainerBased ifTrue:[
+	doCheckinWithoutAsking ifFalse:[
+	    "/
+	    "/ open a dialog for this
+	    "/
+	    (mgr checkForExistingContainer:fileName inModule:module directory:directory) ifFalse:[
+		note := 'Notice: class seems to have no container yet.'.
+		creatingNew := true.
+	    ] ifTrue:[
+		creatingNew := false.
+	    ].
+
+	    rslt := self
+		    askForContainer:boxText title:title note:note
+		    initialModule:module initialPackage:directory initialFileName:fileName
+		    forNewContainer:true.
+
+	    rslt isNil ifTrue:[
+		^ false
+	    ].
+
+	    module := rslt at:#module.
+	    directory := rslt at:#package.
+	    fileName := rslt at:#fileName.
+	].
+	(fileName endsWith:',v') ifTrue:[
+	    fileName := fileName copyWithoutLast:2
+	].
+	(fileName endsWith:'.st') ifFalse:[
+	    fileName := fileName , '.st'
+	].
+
+    ].
+
+    "/ we require the packageID to be <module>:<container-dir>
+    "/ check for this ...
+
+    requiredPackage := ((module ? '') , ':' , (directory ? '')) asSymbol.
+    requiredPackage ~= aClass package ifTrue:[
+"/        doCheckinWithoutAsking ifFalse:[
+"/            (self confirm:'Change the classes packageID to: ''', requiredPackage , ''' ?')
+"/            ifFalse:[
+"/                ^ false
+"/            ]
+"/        ].
+	aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd | mthd setPackage:requiredPackage].
+	aClass package:requiredPackage.
+    ].
+
+    info := aClass revisionInfo.
+    info notNil ifTrue:[
+	(info repositoryPathName isNil) ifTrue:[
+	    info := nil
+	].
+"/        (info includesKey:#repositoryPathName) ifFalse:[
+"/            info := nil
+"/        ]
+    ].
+
+    info isNil ifTrue:[
+	true "doCheckinWithoutAsking" ifFalse:[
+	    answer := Dialog
+		 confirmWithCancel:(resources string:'%1 does not have any (usable) revision info (#version method)\\Shall I create one ?' with:className) withCRs
+		 labels:(resources array:#( 'Cancel' 'No' 'Yes')).
+	    answer isNil ifTrue:[^ false].
+	] ifTrue:[
+	    answer := true.
+	].
+	answer ifTrue:[
+	    mgr
+		updateVersionMethodOf:aClass
+		for:(mgr initialRevisionStringFor:aClass
+			 inModule:module
+			 directory:directory
+			 container:fileName).
+	].
+    ].
+
+    (self checkForExistingModule:module usingManager:mgr allowCreate:(createDirs or:[creatingNew]))
+	ifFalse:[^ false].
+    LastModule := module.
+
+    (self checkForExistingModule:module directory:directory usingManager:mgr allowCreate:(createDirs or:[creatingNew]))
+	ifFalse:[^ false].
+    LastPackage := directory.
+
+    "/
+    "/ check for the container itself
+    "/
+    (mgr isContainerBased not
+    or:[ mgr checkForExistingContainer:fileName inModule:module directory:directory ]) ifTrue:[
+"/            (oldModule notNil
+"/            and:[(oldModule ~= module)
+"/                 or:[oldPackage ~= package
+"/                 or:[oldFileName ~= fileName]]])
+"/            ifFalse:[
+"/                self warn:(resources string:'no change').
+"/                ^ false.
+"/            ].
+
+	mgr isContainerBased ifTrue:[
+	    creatingNew ifTrue:[
+		self warn:(resources string:'Container for %1 already exists in %2/%3.' with:fileName with:module with:directory) withCRs.
+	    ].
+
+	    doCheckinWithoutAsking ifFalse:[
+		(Dialog
+		    confirm:(resources string:'check %1 into the existing container
+
+    %2 / %3 / %4  ?'
+				    with:className
+				    with:module
+				    with:directory
+				    with:fileName) withCRs
+		    noLabel:'Cancel')
+		ifFalse:[
+		    ^ false.
+		].
+	    ].
+	].
+	oldFileName notNil ifTrue:[
+	    msg := ('forced checkin / source container change from ' , oldFileName).
+	] ifFalse:[
+	    msg := 'defined source container'
+	].
+
+	(forceCheckIn := doCheckinWithoutAsking) ifFalse:[
+	    (mgr
+		checkinClass:aClass
+		fileName:fileName
+		directory:directory
+		module:module
+		logMessage:msg)
+	    ifFalse:[
+		doCheckinWithoutAsking ifFalse:[
+		    (Dialog
+			confirm:'No easy merge seems possible; force checkin (no merge) ?'
+			noLabel:'Cancel')
+		    ifFalse:[
+			^ false.
+		    ].
+		].
+		forceCheckIn := true.
+	    ]
+	].
+	forceCheckIn ifTrue:[
+	    (mgr
+		checkinClass:aClass
+		fileName:fileName
+		directory:directory
+		module:module
+		logMessage:msg
+		force:true)
+	    ifFalse:[
+		self warn:(resources string:'Failed to check into existing container.').
+		^ false.
+	    ].
+	].
+	^ true
+    ] ifFalse:[
+	(createContainer or:[creatingNew]) ifFalse:[
+	    (Dialog
+		 confirm:(resources string:'No container exists for %1 in %2/%3\\create ?'
+				      with:fileName with:module with:directory) withCRs
+		 noLabel:'Cancel') ifFalse:[
+		^ false
+	    ]
+	]
+    ].
+
+    aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd | mthd setPackage:requiredPackage].
+    aClass package:requiredPackage.
+
+    (mgr
+	createContainerFor:aClass
+	inModule:module
+	package:directory
+	container:fileName
+    ) ifFalse:[
+	self warn:(resources string:'Failed to create container.').
+	^ false.
+    ].
+    ^ true
+
+    "Created: / 21-12-2011 / 18:34:02 / cg"
 ! !
 
 !PerforceSourceCodeManagerUtilities methodsFor:'utilities-p4'!
@@ -1337,84 +1847,88 @@
 
     |perforceCommand outputStream errorStream changeListFile result changeFileContents changeListFileStream firstIndex oldLogFileLines writeNextLine newLogFileLines currentTokenLineParts currentToken|
 
+    self temporaryWorkSpace isNil ifTrue:[
+	self perforceError raiseErrorString:('Error getting temporary workspace when change the change description for ', changeNumber printString, '.').
+	^false.
+    ].
     perforceCommand := 'change -o ', (changeNumber ? '').
-    outputStream := ReadWriteStream on:''.                                       
+    outputStream := ReadWriteStream on:''.
     errorStream := ReadWriteStream on:''.
     result := self temporaryWorkSpace executePerforceCommand:perforceCommand
-                        inDirectory:self tempDirectory
-                        inputFrom:nil
-                        outputTo:outputStream
-                        errorTo:errorStream
-                        logHeader:('get change desription for change ', changeNumber printString, '.').
+			inDirectory:self tempDirectory
+			inputFrom:nil
+			outputTo:outputStream
+			errorTo:errorStream
+			logHeader:('get change desription for change ', changeNumber printString, '.').
     result ifFalse:[
-        ^ false
+	^ false
     ].
     changeFileContents := outputStream contents.
     changeFileContents isEmptyOrNil ifTrue:[
-        ^false
+	^false
     ].
     changeListFile := self tempDirectory construct:'change'.
     changeListFileStream := changeListFile writeStream.
     changeFileContents := changeFileContents asStringCollection.
     firstIndex := changeFileContents indexOfLineStartingWith:'Description:'.
     firstIndex == 0 ifTrue:[
-        ^false
+	^false
     ].
     oldLogFileLines := StringCollection new.
     changeFileContents from:firstIndex do:[:aLine|
-        ((aLine size > 1) and:[aLine first ~= $# and:[aLine first isSeparator not]]) ifTrue:[
-            currentTokenLineParts := aLine asCollectionOfSubstringsSeparatedBy:$:.
-            currentTokenLineParts size > 1 ifTrue:[
-                currentToken := currentTokenLineParts first.
-            ].
-        ].
-        ((aLine size > 1) and:[aLine first isSeparator and:[currentToken = 'Description']]) ifTrue:[
-            oldLogFileLines add:(aLine copyFrom:2).
-        ].
+	((aLine size > 1) and:[aLine first ~= $# and:[aLine first isSeparator not]]) ifTrue:[
+	    currentTokenLineParts := aLine asCollectionOfSubstringsSeparatedBy:$:.
+	    currentTokenLineParts size > 1 ifTrue:[
+		currentToken := currentTokenLineParts first.
+	    ].
+	].
+	((aLine size > 1) and:[aLine first isSeparator and:[currentToken = 'Description']]) ifTrue:[
+	    oldLogFileLines add:(aLine copyFrom:2).
+	].
     ].
     newLogFileLines := StringCollection new.
     changeNumber isNil ifTrue:[
-        newLogFileLines := logLines.
+	newLogFileLines := logLines.
     ] ifFalse:[
-        (oldLogFileLines asString includesString:logLines asString) ifTrue:[
-            newLogFileLines := oldLogFileLines.
-        ] ifFalse:[
-            newLogFileLines := oldLogFileLines.
-            newLogFileLines addAll:logLines
-        ].
+	(oldLogFileLines asString includesString:logLines asString) ifTrue:[
+	    newLogFileLines := oldLogFileLines.
+	] ifFalse:[
+	    newLogFileLines := oldLogFileLines.
+	    newLogFileLines addAll:logLines
+	].
     ].
     writeNextLine := true.
     changeFileContents do:[:aLine|
-        writeNextLine ifFalse:[
-            (aLine notEmpty and:[aLine first isSeparator not]) ifTrue:[
-                writeNextLine := true.
-            ].
-        ].
-        writeNextLine ifTrue:[
-            (aLine startsWith:'Description:') ifTrue:[
-                changeListFileStream nextPutLine:aLine.
-                newLogFileLines do:[:logLine|
-                    changeListFileStream nextPut:Character tab.
-                    changeListFileStream nextPutLine:logLine.
-                ].
-                writeNextLine := false.
-            ] ifFalse:[
-                changeListFileStream nextPutLine:aLine
-            ].
-        ].
+	writeNextLine ifFalse:[
+	    (aLine notEmpty and:[aLine first isSeparator not]) ifTrue:[
+		writeNextLine := true.
+	    ].
+	].
+	writeNextLine ifTrue:[
+	    (aLine startsWith:'Description:') ifTrue:[
+		changeListFileStream nextPutLine:aLine.
+		newLogFileLines do:[:logLine|
+		    changeListFileStream nextPut:Character tab.
+		    changeListFileStream nextPutLine:logLine.
+		].
+		writeNextLine := false.
+	    ] ifFalse:[
+		changeListFileStream nextPutLine:aLine
+	    ].
+	].
     ].
     changeListFileStream close.
     perforceCommand := ('change -i < "', changeListFile pathName, '"').
     outputStream := ReadWriteStream on:''.
     errorStream := ReadWriteStream on:''.
     result := self temporaryWorkSpace executePerforceCommand:perforceCommand
-                        inDirectory:self tempDirectory
-                        inputFrom:nil
-                        outputTo:outputStream
-                        errorTo:errorStream
-                        logHeader:('write change desription for change ', changeNumber printString, '.').
+			inDirectory:self tempDirectory
+			inputFrom:nil
+			outputTo:outputStream
+			errorTo:errorStream
+			logHeader:('write change desription for change ', changeNumber printString, '.').
     result ifFalse:[
-        ^false
+	^false
     ].
     ^ true
 !
@@ -1430,148 +1944,186 @@
     perforceCommand := ('dirs "' ,depotPath , '"').
     outputStream := ReadWriteStream on:''.
     errorStream := ReadWriteStream on:''.
-    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
-        inputFrom:nil outputTo:outputStream 
-        errorTo:errorStream
-        logHeader:('dirs in checkForExistingContainer for ', depotPath, '.').
+    self getTemporaryWorkspaceFor:checkInDefinition.
+    self temporaryWorkSpace isNil ifTrue:[
+	self perforceError raiseErrorString:('Error getting temporary workspace when check for existing container ', checkInDefinition definitionObjectString, '.').
+	^false.
+    ].
+    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
+	inputFrom:nil outputTo:outputStream
+	errorTo:errorStream
+	logHeader:('dirs in checkForExistingContainer for ', depotPath, '.').
     result ifFalse:[
-        ^ false
+	^ false
     ].
     errorStream contents notEmpty ifTrue:[
-        ^false
+	^false
     ].
     ^ true
 !
 
 checkIn:checkInDefinition submit:doSubmit
 
-    | packagePath fullFilename s perforceCommand outputStream errorStream result tmpFilename fileNameAndRev tmpFilenameAndRev 
+    | packagePath fullFilename s perforceCommand outputStream errorStream result tmpFilename fileNameAndRev tmpFilenameAndRev
       haveChange nextVersionMethod diffOutput number baseRevision cls newestInRepository newVersionString openChangeNumber|
 
     self activityNotification:'checkin ' , checkInDefinition definitionObjectString , ' to perforce repository...'.
-    [                                 
-        cls := checkInDefinition definitionClass.
-        self getTemporaryWorkspaceFor:checkInDefinition.
-        self temporaryWorkSpace isNil ifTrue:[
-            self perforceError raiseErrorString:('Error getting temporary workspace when check in ', checkInDefinition definitionObjectString, '.').
-            ^false.
-        ].
-        baseRevision := checkInDefinition getLocalRevisionNumber.
-        newestInRepository := checkInDefinition getReposRevisionNumberBeforeCheckin.
-        baseRevision isNil ifTrue:[
-            self perforceError raiseErrorString:('No local revision for ', checkInDefinition definitionObjectString,' - should not happen here.').
-            ^false
-        ].
-        packagePath := Smalltalk packageDirectoryForPackageId:checkInDefinition package.
-        fullFilename := (packagePath construct:checkInDefinition packageDir) construct:checkInDefinition fileName.
-        tmpFilename := self getTemporaryFilenameFor:fullFilename pathName.
-        tmpFilename directory recursiveMakeDirectory.
-        checkInDefinition isClassCheckin ifTrue:[
-            baseRevision > newestInRepository ifTrue:[
-                openChangeNumber := self getOpenChangeFor:checkInDefinition.
-                openChangeNumber isNil ifTrue:[
-                    (Dialog confirm:('The version-info of ',checkInDefinition definitionObjectString allBold,' is wrong \(The class version (',baseRevision printString allBold,') is newer than the newest version in the repository (',newestInRepository printString allBold,').\\Patch the version and checkin ?') withCRs)
-                    ifTrue:[
-                        newVersionString := self updatedRevisionStringOf:cls 
-                                                    forRevision:newestInRepository printString with:(cls revisionStringOfManager:self).
-                        PerforceSourceCodeManager updateVersionMethod:(PerforceSourceCodeManager nameOfVersionMethodInClasses) 
-                            of:cls 
-                            for:newVersionString.
-
-                        cls updateVersionMethodFor:newVersionString.
-                    ].
-                ].
-            ].
-        ].
-        fileNameAndRev := checkInDefinition fileName, '#', baseRevision printString.
-        tmpFilenameAndRev := tmpFilename directory construct:fileNameAndRev.
-
-        openChangeNumber notNil ifTrue:[
-            s := tmpFilename writeStream.
-            checkInDefinition isClassCheckin ifTrue:[
-                PerforceSourceCodeManager fileOutSourceCodeOf:cls on:s.
-            ] ifFalse:[
-                self halt.
-                s nextPutAll:''.
-            ].
-            s close.
-            self changeChangeDescriptionTo:checkInDefinition logMessage asStringCollection changeNumber:openChangeNumber printString.
-            doSubmit ifTrue:[
-                self submitChangeNumber:openChangeNumber printString
-            ].
-            ^true
-        ].
-
-        perforceCommand := ('sync "' , tmpFilenameAndRev pathName, '"').
-        outputStream := ReadWriteStream on:''.
-        errorStream := ReadWriteStream on:''.
-        result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
-            inputFrom:nil outputTo:outputStream 
-            errorTo:errorStream
-            logHeader:('sync ', checkInDefinition definitionObjectString, ' to revision ', baseRevision printString, '.').
-        result ifFalse:[
-            ^ false
-        ].
-
-        number := self getChangeListNumber.
-        number isNil ifTrue:[
-            self perforceError raiseErrorString:('Error when getting a change list for ', checkInDefinition definitionObjectString, '.').
-            ^false
-        ].
-        perforceCommand := ('edit -c ' ,number 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 ', checkInDefinition definitionObjectString, '.').
-        result ifFalse:[
-            ^ false
-        ].
-        s := tmpFilename writeStream.
-        checkInDefinition isClassCheckin ifTrue:[
-            PerforceSourceCodeManager fileOutSourceCodeOf:cls on:s.
-        ] ifFalse:[
-            self halt.
-            s nextPutAll:''.
-        ].
-        s close.
-        perforceCommand := ('diff -db -dw -dl "' , tmpFilename pathName, '"').
-        outputStream := ReadWriteStream on:''.
-        errorStream := ReadWriteStream on:''.
-        result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
-            inputFrom:nil outputTo:outputStream 
-            errorTo:errorStream
-            logHeader:('diff ', checkInDefinition definitionObjectString, '.').
-        diffOutput := outputStream contents asStringCollection.
-        haveChange := diffOutput isEmptyOrNil or:[diffOutput notEmptyOrNil and:[diffOutput size > 1]].
-        haveChange ifFalse:[
-            self information:checkInDefinition definitionObjectString, ' not changed for revision ', baseRevision printString.
-            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 ', checkInDefinition definitionObjectString, '.').
-            ^true
-        ].
-        checkInDefinition isClassCheckin ifTrue:[
-            nextVersionMethod := self nextRevisionStringFor:checkInDefinition.
-            nextVersionMethod isNil ifTrue:[
-                self perforceError raiseErrorString:('Cant get next version method string for ', checkInDefinition definitionObjectString, ' revision ', baseRevision printString, '.').
-                ^false
-            ].
-            PerforceSourceCodeManager updateVersionMethod:(PerforceSourceCodeManager nameOfVersionMethodInClasses) 
-                    of:cls 
-                    for:nextVersionMethod.
-        ].
-        result := self changeChangeDescriptionTo:checkInDefinition logMessage asStringCollection changeNumber:number printString.
-        doSubmit ifTrue:[
-            result := self submitChangeNumber:number printString
-        ].
+    [
+	cls := checkInDefinition definitionClass.
+	self getTemporaryWorkspaceFor:checkInDefinition.
+	self temporaryWorkSpace isNil ifTrue:[
+	    self perforceError raiseErrorString:('Error getting temporary workspace when check in ', checkInDefinition definitionObjectString, '.').
+	    ^false.
+	].
+	baseRevision := checkInDefinition getLocalRevisionNumber.
+	newestInRepository := checkInDefinition getReposRevisionNumberBeforeCheckin.
+	(checkInDefinition isClassCheckin and:[baseRevision isNil]) ifTrue:[
+	    (Dialog confirm:('The version-info of ',checkInDefinition definitionObjectString allBold,' not exists. \Patch the version info?') withCRs)
+	    ifTrue:[
+		newVersionString := self updatedRevisionStringOf:cls
+					forRevision:newestInRepository printString with:(cls revisionStringOfManager:PerforceSourceCodeManager).
+		PerforceSourceCodeManager updateVersionMethod:(PerforceSourceCodeManager nameOfVersionMethodInClasses)
+			of:cls
+			for:newVersionString.
+		baseRevision := checkInDefinition getLocalRevisionNumber.
+		baseRevision notNil ifTrue:[
+			(Dialog confirm:('Check in ', checkInDefinition definitionObjectString allBold, 'based on version ', baseRevision printString, '?') withCRs)
+			ifFalse:[
+			    ^false.
+			].
+		].
+	    ] ifFalse:[
+		^false
+	    ].
+	].
+	packagePath := Smalltalk packageDirectoryForPackageId:checkInDefinition package.
+	fullFilename := (packagePath construct:checkInDefinition packageDir) construct:checkInDefinition fileName.
+	tmpFilename := self getTemporaryFilenameFor:fullFilename pathName.
+	tmpFilename directory recursiveMakeDirectory.
+	checkInDefinition isClassCheckin ifTrue:[
+	    baseRevision > newestInRepository ifTrue:[
+		openChangeNumber := self getOpenChangeFor:checkInDefinition.
+		openChangeNumber isNil ifTrue:[
+		    (Dialog confirm:('The version-info of ',checkInDefinition definitionObjectString allBold,' is wrong \(The class version (',baseRevision printString allBold,') is newer than the newest version in the repository (',newestInRepository printString allBold,').\\Patch the version and checkin ?') withCRs)
+		    ifTrue:[
+			newVersionString := self updatedRevisionStringOf:cls
+						    forRevision:newestInRepository printString with:(cls revisionStringOfManager:PerforceSourceCodeManager).
+			PerforceSourceCodeManager updateVersionMethod:(PerforceSourceCodeManager nameOfVersionMethodInClasses)
+			    of:cls
+			    for:newVersionString.
+
+			cls updateVersionMethodFor:newVersionString.
+		    ].
+		].
+	    ].
+	].
+	checkInDefinition isClassCheckin ifTrue:[
+	    fileNameAndRev := checkInDefinition fileName, '#', baseRevision printString.
+	] ifFalse:[
+	    fileNameAndRev := checkInDefinition fileName, '#', newestInRepository printString.
+	].
+	tmpFilenameAndRev := tmpFilename directory construct:fileNameAndRev.
+
+	openChangeNumber notNil ifTrue:[
+	    s := tmpFilename writeStream.
+	    checkInDefinition isClassCheckin ifTrue:[
+		PerforceSourceCodeManager fileOutSourceCodeOf:cls on:s.
+	    ] ifFalse:[
+		s nextPutAll:checkInDefinition fileContents.
+	    ].
+	    s close.
+	    self changeChangeDescriptionTo:checkInDefinition logMessage asStringCollection changeNumber:openChangeNumber printString.
+	    doSubmit ifTrue:[
+		self submitChangeNumber:openChangeNumber printString
+	    ].
+	    ^true
+	].
+	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:('sync ', checkInDefinition definitionObjectString, ' to revision ', baseRevision printString, '.').
+	result ifFalse:[
+	    ^ false
+	].
+	perforceCommand := ('sync -f "' , tmpFilenameAndRev pathName, '"').
+	outputStream := ReadWriteStream on:''.
+	errorStream := ReadWriteStream on:''.
+	result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
+	    inputFrom:nil outputTo:outputStream
+	    errorTo:errorStream
+	    logHeader:('sync ', checkInDefinition definitionObjectString, ' to revision ', baseRevision printString, '.').
+	result ifFalse:[
+	    ^ false
+	].
+
+	number := self getChangeListNumber.
+	number isNil ifTrue:[
+	    self perforceError raiseErrorString:('Error when getting a change list for ', checkInDefinition definitionObjectString, '.').
+	    ^false
+	].
+	perforceCommand := ('edit -c ' ,number 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 ', checkInDefinition definitionObjectString, '.').
+	result ifFalse:[
+	    ^ false
+	].
+	s := tmpFilename writeStream.
+	checkInDefinition isClassCheckin ifTrue:[
+	    PerforceSourceCodeManager fileOutSourceCodeOf:cls on:s.
+	] ifFalse:[
+	    s nextPutAll:checkInDefinition fileContents.
+	].
+	s close.
+	perforceCommand := ('diff -db -dw -dl "' , tmpFilename pathName, '"').
+	outputStream := ReadWriteStream on:''.
+	errorStream := ReadWriteStream on:''.
+	result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
+	    inputFrom:nil outputTo:outputStream
+	    errorTo:errorStream
+	    logHeader:('diff ', checkInDefinition definitionObjectString, '.').
+	diffOutput := outputStream contents asStringCollection.
+	haveChange := diffOutput isEmptyOrNil or:[diffOutput notEmptyOrNil and:[diffOutput size > 1]].
+	haveChange ifFalse:[
+	    self information:checkInDefinition definitionObjectString, ' not changed for revision ', baseRevision printString.
+	    newestInRepository ~= baseRevision ifTrue:[
+		newVersionString := self updatedRevisionStringOf:cls
+					    forRevision:newestInRepository printString with:(cls revisionStringOfManager:PerforceSourceCodeManager).
+		PerforceSourceCodeManager updateVersionMethod:(PerforceSourceCodeManager nameOfVersionMethodInClasses)
+			of:cls
+			for:newVersionString.
+	    ].
+	    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 ', checkInDefinition definitionObjectString, '.').
+	    ^true
+	].
+	checkInDefinition isClassCheckin ifTrue:[
+	    nextVersionMethod := self nextRevisionStringFor:checkInDefinition.
+	    nextVersionMethod isNil ifTrue:[
+		self perforceError raiseErrorString:('Cant get next version method string for ', checkInDefinition definitionObjectString, ' revision ', baseRevision printString, '.').
+		^false
+	    ].
+	    PerforceSourceCodeManager updateVersionMethod:(PerforceSourceCodeManager nameOfVersionMethodInClasses)
+		    of:cls
+		    for:nextVersionMethod.
+	].
+	result := self changeChangeDescriptionTo:checkInDefinition logMessage asStringCollection changeNumber:number printString.
+	doSubmit ifTrue:[
+	    result := self submitChangeNumber:number printString
+	].
     ] ensure:[
-        self activityNotification:''.
+	self activityNotification:''.
     ].
     ^result
 !
@@ -1668,17 +2220,19 @@
 
 deleteWorkSpaceFromServer
 
-    |perforceCommand outputStream errorStream result|
-
+    |perforceCommand outputStream errorStream result tmpWorkSpace|
+
+    tmpWorkSpace := self temporaryWorkSpace.
+    tmpWorkSpace isNil ifTrue:[ ^true].
     perforceCommand := ('client -df ', client).
     outputStream := ReadWriteStream on:''.
     errorStream := ReadWriteStream on:''.
-    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
-        inputFrom:nil outputTo:outputStream 
-        errorTo:errorStream
-        logHeader:('delete client ', client).
+    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root
+	inputFrom:nil outputTo:outputStream
+	errorTo:errorStream
+	logHeader:('delete client ', client).
     result ifFalse:[
-        ^ false
+	^ false
     ].
     ^true
 !
@@ -1687,49 +2241,53 @@
 
     |valuePairs startLineIndex keyEndIndex changeContents cmd outputStream errorStream result keyValues beginLine endLine keyName keyValue|
 
+    self temporaryWorkSpace isNil ifTrue:[
+	self perforceError raiseErrorString:('Error getting temporary workspace when try to get change description for ', changeNumber printString, '.').
+	^nil.
+    ].
     valuePairs := OrderedCollection new.
     cmd := 'change -o ', (changeNumber ? '').
-    outputStream := ReadWriteStream on:''.                                       
+    outputStream := ReadWriteStream on:''.
     errorStream := ReadWriteStream on:''.
     result := self temporaryWorkSpace executePerforceCommand:cmd
-                        inDirectory:self tempDirectory
-                        inputFrom:nil
-                        outputTo:outputStream
-                        errorTo:errorStream
-                        logHeader:('getting change description ', (changeNumber ? ''), '.').
+			inDirectory:self tempDirectory
+			inputFrom:nil
+			outputTo:outputStream
+			errorTo:errorStream
+			logHeader:('getting change description ', (changeNumber ? ''), '.').
     result ifFalse:[
-        ^ nil
+	^ nil
     ].
     changeContents := outputStream contents asStringCollection.
     changeContents doWithIndex:[:aLine :index|
-        startLineIndex isNil ifTrue:[
-            (aLine isEmpty or:[(aLine startsWith:$#) or:[aLine first isSeparator]]) ifFalse:[
-                keyEndIndex := aLine indexOf:$:.
-                keyEndIndex ~= 0 ifTrue:[
-                    startLineIndex := index.
-                    valuePairs add:(Array with:index with:nil with:(aLine copyTo:keyEndIndex - 1)).
-                ].
-            ].
-        ] ifFalse:[
-            (aLine isEmpty or:[aLine startsWith:$#]) ifTrue:[
-                valuePairs last at:2 put:index.
-                startLineIndex := nil.
-            ].
-        ].
+	startLineIndex isNil ifTrue:[
+	    (aLine isEmpty or:[(aLine startsWith:$#) or:[aLine first isSeparator]]) ifFalse:[
+		keyEndIndex := aLine indexOf:$:.
+		keyEndIndex ~= 0 ifTrue:[
+		    startLineIndex := index.
+		    valuePairs add:(Array with:index with:nil with:(aLine copyTo:keyEndIndex - 1)).
+		].
+	    ].
+	] ifFalse:[
+	    (aLine isEmpty or:[aLine startsWith:$#]) ifTrue:[
+		valuePairs last at:2 put:index.
+		startLineIndex := nil.
+	    ].
+	].
     ].
     keyValues := Dictionary new.
     valuePairs do:[:each|
-        beginLine := each first.
-        endLine := each second.
-        keyName := each last.
-        (beginLine == (endLine - 1)) ifTrue:[
-            keyValue := (changeContents at:beginLine) copyFrom:(keyName size + 2).
-            keyValue := (keyValue withoutLeadingSeparators withoutTrailingSeparators) asStringCollection.
-        ] ifFalse:[
-            keyValue := changeContents copyFrom:(beginLine + 1) to:(endLine - 1).
-            keyValue := keyValue collect:[:each | each withoutLeadingSeparators withoutTrailingSeparators].
-        ].
-        keyValues at:keyName put:keyValue.
+	beginLine := each first.
+	endLine := each second.
+	keyName := each last.
+	(beginLine == (endLine - 1)) ifTrue:[
+	    keyValue := (changeContents at:beginLine) copyFrom:(keyName size + 2).
+	    keyValue := (keyValue withoutLeadingSeparators withoutTrailingSeparators) asStringCollection.
+	] ifFalse:[
+	    keyValue := changeContents copyFrom:(beginLine + 1) to:(endLine - 1).
+	    keyValue := keyValue collect:[:each | each withoutLeadingSeparators withoutTrailingSeparators].
+	].
+	keyValues at:keyName put:keyValue.
     ].
     ^ keyValues.
 !
@@ -1756,26 +2314,30 @@
 
     |perforceCommand outputStream errorStream result pendingChangesOutput words numbers number|
 
+    self temporaryWorkSpace isNil ifTrue:[
+	self perforceError raiseErrorString:('Error getting temporary workspace when try to get change numbers.').
+	^nil.
+    ].
     perforceCommand := 'changes -s pending -u ', owner.
-    outputStream := ReadWriteStream on:''.                                       
+    outputStream := ReadWriteStream on:''.
     errorStream := ReadWriteStream on:''.
     result := self temporaryWorkSpace executePerforceCommand:perforceCommand
-                        inDirectory:self tempDirectory
-                        inputFrom:nil
-                        outputTo:outputStream
-                        errorTo:errorStream
-                        doLog:false.
+			inDirectory:self tempDirectory
+			inputFrom:nil
+			outputTo:outputStream
+			errorTo:errorStream
+			doLog:false.
     result ifFalse:[
-        ^ nil
+	^ nil
     ].
     numbers := OrderedCollection new.
     pendingChangesOutput := outputStream contents asStringCollection.
     pendingChangesOutput do:[:eachLine|
-        words := eachLine asCollectionOfWords.
-        words size > 1 ifTrue:[
-            number := Number readFrom:(ReadStream on:(words at:2)) onError:nil.
-            numbers add:number.                              
-        ].
+	words := eachLine asCollectionOfWords.
+	words size > 1 ifTrue:[
+	    number := Number readFrom:(ReadStream on:(words at:2)) onError:nil.
+	    numbers add:number.
+	].
     ].
     ^numbers
 !
@@ -1907,115 +2469,116 @@
 
 mergeOrResolveConflictsForChangeNumber:aNumber
 
-    | tmpFilename perforceCommand outputStream errorStream result s 
-      changesAsLogged inStream line changesDict chunksPart words mergedSource mySource 
+    | tmpFilename perforceCommand outputStream errorStream result s
+      changesAsLogged inStream line changesDict chunksPart words mergedSource mySource
       localRevision resultSource definitionClass descriptionInfo resolveFiles depotPath localPath checkInDefinition fileStatDict|
 
     self temporaryWorkSpace isNil ifTrue:[
-        ^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: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.
+	    ].
+	].
     ].
     ^true
 !
@@ -2434,42 +2997,47 @@
 
     |cmd outputStream errorStream result changeListDescription infoDialog logMsg|
 
+
+    self temporaryWorkSpace isNil ifTrue:[
+	self perforceError raiseErrorString:('Error getting temporary workspace when try to submot ', changeNumber printString, '.').
+	^false.
+    ].
     changeListDescription := self getChangeDespriptionInfoFor:changeNumber printString.
-    infoDialog := PerforceSourceCodeManager submitInfoDialogClass 
-            getCheckinInfoFor:'Perforce submit message check'                
-            initialAnswer:((changeListDescription at:#Description ifAbsent:'') copy)
-            withFileList:(changeListDescription at:#Files ifAbsent:'').
+    infoDialog := PerforceSourceCodeManager submitInfoDialogClass
+	    getCheckinInfoFor:'Perforce submit message check'
+	    initialAnswer:((changeListDescription at:#Description ifAbsent:'') copy)
+	    withFileList:(changeListDescription at:#Files ifAbsent:'').
     infoDialog notNil ifTrue:[
-        logMsg := infoDialog logMessage.
-        (changeListDescription at:#Description ifAbsent:'') ~= logMsg asStringCollection ifTrue:[
-            self changeChangeDescriptionTo:logMsg asStringCollection changeNumber:changeNumber printString
-        ].
+	logMsg := infoDialog logMessage.
+	(changeListDescription at:#Description ifAbsent:'') ~= logMsg asStringCollection ifTrue:[
+	    self changeChangeDescriptionTo:logMsg asStringCollection changeNumber:changeNumber printString
+	].
     ].
     cmd := ('submit -c ', changeNumber printString).
     outputStream := ReadWriteStream on:''.
     errorStream := ReadWriteStream on:''.
     result := self temporaryWorkSpace executePerforceCommand:cmd
-                        inDirectory:self tempDirectory
-                        inputFrom:nil
-                        outputTo:outputStream
-                        errorTo:errorStream
-                        doLog:false.                     
-    result ifFalse:[   
-        result := self mergeOrResolveConflictsForChangeNumber:changeNumber.
-        result ifTrue:[
-            cmd := ('submit -c ', changeNumber printString).
-            outputStream := ReadWriteStream on:''.
-            errorStream := ReadWriteStream on:''.
-            result := self temporaryWorkSpace executePerforceCommand:cmd
-                                inDirectory:self tempDirectory
-                                inputFrom:nil
-                                outputTo:outputStream
-                                errorTo:errorStream
-                                logHeader:('submit change ', changeNumber printString, ' after resolve.').
-            result ifFalse:[
-                ^ false
-            ].
-        ].
+			inDirectory:self tempDirectory
+			inputFrom:nil
+			outputTo:outputStream
+			errorTo:errorStream
+			doLog:false.
+    result ifFalse:[
+	result := self mergeOrResolveConflictsForChangeNumber:changeNumber.
+	result ifTrue:[
+	    cmd := ('submit -c ', changeNumber printString).
+	    outputStream := ReadWriteStream on:''.
+	    errorStream := ReadWriteStream on:''.
+	    result := self temporaryWorkSpace executePerforceCommand:cmd
+				inDirectory:self tempDirectory
+				inputFrom:nil
+				outputTo:outputStream
+				errorTo:errorStream
+				logHeader:('submit change ', changeNumber printString, ' after resolve.').
+	    result ifFalse:[
+		^ false
+	    ].
+	].
     ].
     ^true
 ! !
@@ -3024,14 +3592,15 @@
 
     myView := self getViewForPath:aFilename.
     self temporaryWorkSpace isNil ifTrue:[
-        ^nil
+	self perforceError raiseErrorString:('Error getting temporary workspace when try to get temporaryFilename.').
+	^nil.
     ].
     self temporaryWorkSpace views do:[:aView|
-        myView depot = aView depot ifTrue:[
-            checkInPart := PerforceSourceCodeManager getTrailungPathNameFrom:aFilename with:myView localPathName.
-            fullTempFilename := aView localPathName asFilename construct:checkInPart.
-            ^fullTempFilename
-        ].
+	myView depot = aView depot ifTrue:[
+	    checkInPart := PerforceSourceCodeManager getTrailungPathNameFrom:aFilename with:myView localPathName.
+	    fullTempFilename := aView localPathName asFilename construct:checkInPart.
+	    ^fullTempFilename
+	].
     ].
     ^nil
 !
@@ -3042,12 +3611,13 @@
 
     myView := self getViewForPackage:aPackage.
     self temporaryWorkSpace isNil ifTrue:[
-        ^nil
+	self perforceError raiseErrorString:('Error getting temporary workspace when try to get temporary view').
+	^nil.
     ].
     self temporaryWorkSpace views do:[:aView|
-        myView depot = aView depot ifTrue:[
-            ^ aView
-        ].
+	myView depot = aView depot ifTrue:[
+	    ^ aView
+	].
     ].
 !
 
@@ -3538,10 +4108,10 @@
 !PerforceSourceCodeManagerUtilities class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagerUtilities.st,v 1.4 2013-04-27 12:56:56 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagerUtilities.st,v 1.5 2013-06-13 15:27:17 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagerUtilities.st,v 1.4 2013-04-27 12:56:56 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagerUtilities.st,v 1.5 2013-06-13 15:27:17 cg Exp $'
 ! !