FileOperation.st
changeset 7637 ee7ed843e5ba
parent 7634 f3ff12d68382
child 8289 8dcce3984b27
--- a/FileOperation.st	Wed Feb 07 22:12:26 2007 +0100
+++ b/FileOperation.st	Thu Feb 08 15:39:01 2007 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 2003 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -26,7 +26,7 @@
 !
 
 FileOperation::Copy subclass:#CopyCorrupted
-	instanceVariableNames:'copiedFiles newFiles'
+	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:FileOperation
@@ -72,7 +72,7 @@
 copyright
 "
  COPYRIGHT (c) 2003 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -86,17 +86,17 @@
 !FileOperation class methodsFor:'instance creation'!
 
 copyCorruptedFile:aSourceFile to:aDestFile
-    ^ CopyCorrupted 
-        copyFile:aSourceFile to:aDestFile
+    ^ CopyCorrupted
+	copyFile:aSourceFile to:aDestFile
 
     "Created: / 07-02-2007 / 18:41:24 / cg"
 !
 
 copyFile:aSourceFile to:aDestFile withOverWriteWarning:overWriteWarningBoolean copyFileIfSame:copyIfSameBoolean
-    ^ Copy 
-        copyFile:aSourceFile to:aDestFile 
-        withOverWriteWarning:overWriteWarningBoolean 
-        copyFileIfSame:copyIfSameBoolean
+    ^ Copy
+	copyFile:aSourceFile to:aDestFile
+	withOverWriteWarning:overWriteWarningBoolean
+	copyFileIfSame:copyIfSameBoolean
 !
 
 copyFiles:aColOfSourceFiles to:aDirectory
@@ -179,12 +179,12 @@
 
 checkDirectoryExists:aDirectory
     aDirectory exists ifFalse:[
-        Dialog warn:('Non-existing Directory: %1' bindWith:aDirectory asString). 
-        ^ false
+	Dialog warn:('Non-existing Directory: %1' bindWith:aDirectory asString).
+	^ false
     ].
     aDirectory isDirectory ifFalse:[
-        Dialog warn:('Not a Directory: %1' bindWith:aDirectory asString). 
-        ^ false
+	Dialog warn:('Not a Directory: %1' bindWith:aDirectory asString).
+	^ false
     ].
     ^ true
 
@@ -202,7 +202,7 @@
     "return true, if the file should be moved/copied.
      If oldFile exists, ask user.
      If withRemoveIfSame is true, two additional possible values are returned:
-        #removeSource and #removeDestination.
+	#removeSource and #removeDestination.
     "
 
     |msg oldSize newSize sameContents resources sourceType destType|
@@ -214,53 +214,53 @@
     sameContents := false.
 
     newFile isDirectory ifTrue:[
-        oldFile isDirectory ifTrue:[
-            "/ could (should?) recursively look for same contents here...
-        ].
+	oldFile isDirectory ifTrue:[
+	    "/ could (should?) recursively look for same contents here...
+	].
     ] ifFalse:[
-        oldFile isDirectory ifFalse:[
-            sameContents := oldSize = newSize and:[oldFile sameContentsAs:newFile].
-        ]
+	oldFile isDirectory ifFalse:[
+	    sameContents := oldSize = newSize and:[oldFile sameContentsAs:newFile].
+	]
     ].
 
     "/ for now:
     oldFile isDirectory ~~ newFile isDirectory ifTrue:[
-        Dialog warn:(resources string:'Will not overwrite directory with file and vice versa.').
-        ^  false.
+	Dialog warn:(resources string:'Will not overwrite directory with file and vice versa.').
+	^  false.
     ].
 
     sourceType := newFile isDirectory ifTrue:'directory' ifFalse:'file'.
     destType := oldFile isDirectory ifTrue:'directory' ifFalse:'file'.
 
     sameContents ifTrue:[
-        msg := 'Overwrite existing destination %7:\\  %1\    size: %3 of %2\\with source (same contents):\\  %4\    size: %6 of %5'.
+	msg := 'Overwrite existing destination %7:\\  %1\    size: %3 of %2\\with source (same contents):\\  %4\    size: %6 of %5'.
     ] ifFalse:[
-        msg := 'Overwrite existing destination %7:\\  %1\    size: %3 of %2\\with source:\\  %4\    size: %6 of %5'.
+	msg := 'Overwrite existing destination %7:\\  %1\    size: %3 of %2\\with source:\\  %4\    size: %6 of %5'.
     ].
 
     resources := AbstractFileBrowser classResources.
-    msg := resources 
-            stringWithCRs:msg
-            withArgs:(Array
-                with:newFile asString allBold
-                with:(newFile modificationTime printStringFormat:'%(Day)-%(mon)-%(year) %h:%m:%s')
-                with:newSize
-                with:oldFile asString allBold 
-                with:(oldFile modificationTime printStringFormat:'%(Day)-%(mon)-%(year) %h:%m:%s')
-                with:oldSize
-                with:destType).
+    msg := resources
+	    stringWithCRs:msg
+	    withArgs:(Array
+		with:newFile asString allBold
+		with:(newFile modificationTime printStringFormat:'%(Day)-%(mon)-%(year) %h:%m:%s')
+		with:newSize
+		with:oldFile asString allBold
+		with:(oldFile modificationTime printStringFormat:'%(Day)-%(mon)-%(year) %h:%m:%s')
+		with:oldSize
+		with:destType).
 
     (sameContents and:[withRemoveIfSame]) ifTrue:[
-        ^ OptionBox  
-                  request:msg
-                  label:(resources string:'Overwrite existing file')
-                  image:(YesNoBox iconBitmap)
-                  buttonLabels:(resources array:( #('No' 'Remove Source' 'Remove Destination' 'Yes' ) , (withCancel ifTrue:[#('Cancel')] ifFalse:[#()])))
-                  values:#( false #removeSource #removeDestination true )
-                  default:#removeSource
-                  onCancel:nil.
+	^ OptionBox
+		  request:msg
+		  label:(resources string:'Overwrite existing file')
+		  image:(YesNoBox iconBitmap)
+		  buttonLabels:(resources array:( #('No' 'Remove Source' 'Remove Destination' 'Yes' ) , (withCancel ifTrue:[#('Cancel')] ifFalse:[#()])))
+		  values:#( false #removeSource #removeDestination true )
+		  default:#removeSource
+		  onCancel:nil.
     ] ifFalse:[
-        ^ Dialog confirm:msg withCancel:withCancel.
+	^ Dialog confirm:msg withCancel:withCancel.
     ].
 ! !
 
@@ -330,14 +330,14 @@
 
 collectionOfCopiedFiles
     copiedFiles isNil ifTrue:[
-        copiedFiles := OrderedCollection new.
+	copiedFiles := OrderedCollection new.
     ].
     ^ copiedFiles
 !
 
 collectionOfNewFiles
     newFiles isNil ifTrue:[
-        newFiles := OrderedCollection new.
+	newFiles := OrderedCollection new.
     ].
     ^ newFiles
 ! !
@@ -353,10 +353,10 @@
 !
 
 copyFiles:aColOfSourceFiles to:aDirectory
-    ^ self copyFiles:aColOfSourceFiles to:aDirectory withOverWriteWarning:true. 
+    ^ self copyFiles:aColOfSourceFiles to:aDirectory withOverWriteWarning:true.
 !
 
-copyFiles:aColOfSourceFiles to:aDirectory withOverWriteWarning:overWriteWarning 
+copyFiles:aColOfSourceFiles to:aDirectory withOverWriteWarning:overWriteWarning
     ^ self copyFiles:aColOfSourceFiles to:aDirectory withOverWriteWarning:overWriteWarning copyFileIfSame:true.
 ! !
 
@@ -364,9 +364,9 @@
 
 basicCopy:aSourceFile to:newFile
     aSourceFile isDirectory ifTrue:[
-        OperatingSystem recursiveCopyDirectory:(aSourceFile pathName) to:(newFile pathName).
+	OperatingSystem recursiveCopyDirectory:(aSourceFile pathName) to:(newFile pathName).
     ] ifFalse:[
-        aSourceFile copyTo:newFile.
+	aSourceFile copyTo:newFile.
     ].
 
     "Created: / 07-02-2007 / 18:35:52 / cg"
@@ -376,45 +376,45 @@
     |newFile fileString targetDirectory suffix|
 
     aDestFile isDirectory ifTrue:[
-        targetDirectory := aDestFile.
-        newFile := aDestFile construct:(aSourceFile baseName).
+	targetDirectory := aDestFile.
+	newFile := aDestFile construct:(aSourceFile baseName).
     ] ifFalse:[
-        targetDirectory := aDestFile directory.
-        newFile := aDestFile.
+	targetDirectory := aDestFile directory.
+	newFile := aDestFile.
     ].
 
     "/ do not copy if destination directory doest exist.
     (self checkDirectoryExists:targetDirectory) ifFalse:[
-        result := false.
-        ^ self
+	result := false.
+	^ self
     ].
     (newFile exists) ifTrue:[
-        ((newFile asString = aSourceFile asString) and:[copyIfSameBoolean]) ifTrue:[
-            [newFile exists] whileTrue:[
-                suffix := newFile suffix.
-                fileString := newFile baseName withoutSuffix, self class suffixForCopyOverExistingFile, '.', suffix.
-                newFile := targetDirectory construct:fileString.
-            ].
-        ] ifFalse:[
-            overWriteWarningBoolean ifTrue:[
-                (self fileExistsDialogForNewFile:newFile oldFile:aSourceFile withCancel:false withRemoveIfSame:false) ifFalse:[ 
-                    result := false.
-                    ^ self.
-                ]
-            ] ifFalse:[
-                    result := false.
-                    ^ self.
-            ]
-        ].
+	((newFile asString = aSourceFile asString) and:[copyIfSameBoolean]) ifTrue:[
+	    [newFile exists] whileTrue:[
+		suffix := newFile suffix.
+		fileString := newFile baseName withoutSuffix, self class suffixForCopyOverExistingFile, '.', suffix.
+		newFile := targetDirectory construct:fileString.
+	    ].
+	] ifFalse:[
+	    overWriteWarningBoolean ifTrue:[
+		(self fileExistsDialogForNewFile:newFile oldFile:aSourceFile withCancel:false withRemoveIfSame:false) ifFalse:[
+		    result := false.
+		    ^ self.
+		]
+	    ] ifFalse:[
+		    result := false.
+		    ^ self.
+	    ]
+	].
     ].
     Error handle:[:ex|
-        "was not able to copy it"
-        WarningBox warn:'on copy file - ', ex errorString.
-        self errorString:('on copy file - ', ex description asString).
-        result := false.
-        ^ self
+	"was not able to copy it"
+	WarningBox warn:'on copy file - ', ex errorString.
+	self errorString:('on copy file - ', ex description asString).
+	result := false.
+	^ self
     ] do:[
-        self basicCopy:aSourceFile to:newFile.
+	self basicCopy:aSourceFile to:newFile.
     ].
     DirectoryContents flushCachedDirectoryFor:(aSourceFile directory).
     result := true.
@@ -427,57 +427,57 @@
 
     "/ do not copy if destination directory doest exist.
     (self checkDirectoryExists:aDirectory) ifFalse:[
-        result := false.
-        ^ self
+	result := false.
+	^ self
     ].
 
     aColOfSourceFiles do:[:filename |
-        newFile := aDirectory construct:(filename baseName).
-        doCopy := true.
-        (newFile exists) ifTrue:[
-            ((newFile asString = filename asString) and:[copy]) ifTrue:[
-                [newFile exists] whileTrue:[
-                    suffix := newFile suffix.
-                    fileString := newFile withoutSuffix baseName, self class suffixForCopyOverExistingFile.
-                    suffix notEmpty ifTrue:[
-                        fileString := fileString, '.', suffix.
-                    ].
-                    newFile := aDirectory construct:fileString.
-                ].
-            ] ifFalse:[
-                overWriteWarning ifTrue:[
-                    doCopy := (self fileExistsDialogForNewFile:newFile oldFile:filename withCancel:(aColOfSourceFiles size > 1) withRemoveIfSame:false).
-                    doCopy isNil ifTrue:[
-                        " abort pressed "
-                        result := false.
-                        ^ self.
-                    ]
-                ]
-            ].
-        ].
-        doCopy ifTrue:[
-            Error handle:[:ex|
-                |msg|
+	newFile := aDirectory construct:(filename baseName).
+	doCopy := true.
+	(newFile exists) ifTrue:[
+	    ((newFile asString = filename asString) and:[copy]) ifTrue:[
+		[newFile exists] whileTrue:[
+		    suffix := newFile suffix.
+		    fileString := newFile withoutSuffix baseName, self class suffixForCopyOverExistingFile.
+		    suffix notEmpty ifTrue:[
+			fileString := fileString, '.', suffix.
+		    ].
+		    newFile := aDirectory construct:fileString.
+		].
+	    ] ifFalse:[
+		overWriteWarning ifTrue:[
+		    doCopy := (self fileExistsDialogForNewFile:newFile oldFile:filename withCancel:(aColOfSourceFiles size > 1) withRemoveIfSame:false).
+		    doCopy isNil ifTrue:[
+			" abort pressed "
+			result := false.
+			^ self.
+		    ]
+		]
+	    ].
+	].
+	doCopy ifTrue:[
+	    Error handle:[:ex|
+		|msg|
 
-                msg := 'on copy file - ', ex description asString.
-                "was not able to copy it"
-                result := false.
-                self errorString:msg.
-                ( Dialog 
-                    confirm:('Error ',msg) 
-                    title:'Copy'
-                    yesLabel:'Continue' 
-                    noLabel:'Abort') ifTrue:[
-                        ex proceed.
-                    ] ifFalse:[
-                        ^ self.
-                    ].
-            ] do:[
-                self basicCopy:filename to:newFile
-            ].
-            self collectionOfCopiedFiles add:filename.
-            self collectionOfNewFiles add:newFile.
-        ]
+		msg := 'on copy file - ', ex description asString.
+		"was not able to copy it"
+		result := false.
+		self errorString:msg.
+		( Dialog
+		    confirm:('Error ',msg)
+		    title:'Copy'
+		    yesLabel:'Continue'
+		    noLabel:'Abort') ifTrue:[
+			ex proceed.
+		    ] ifFalse:[
+			^ self.
+		    ].
+	    ] do:[
+		self basicCopy:filename to:newFile
+	    ].
+	    self collectionOfCopiedFiles add:filename.
+	    self collectionOfNewFiles add:newFile.
+	]
     ].
     DirectoryContents flushCachedDirectoryFor:aDirectory.
     result := true.
@@ -489,12 +489,12 @@
 
 basicCopy:aSourceFile to:newFile
     aSourceFile isDirectory ifTrue:[
-        newFile makeDirectory.
-        aSourceFile directoryContentsDo:[:eachFileOrDirectory |
-            self basicCopy:(aSourceFile construct:eachFileOrDirectory) to:(newFile construct:eachFileOrDirectory)
-        ].
+	newFile makeDirectory.
+	aSourceFile directoryContentsDo:[:eachFileOrDirectory |
+	    self basicCopy:(aSourceFile construct:eachFileOrDirectory) to:(newFile construct:eachFileOrDirectory)
+	].
     ] ifFalse:[
-        self basicCopyFile:aSourceFile to:newFile.
+	self basicCopyFile:aSourceFile to:newFile.
     ].
 
     "Created: / 07-02-2007 / 18:39:03 / cg"
@@ -517,104 +517,104 @@
     out := destFile writeStream binary.
 
     doWrite := [:n |
-                nWritten := out nextPutBytes:n from:buffer startingAt:1.
-                offset := offset + nWritten.
-                nWritten ~= n ifTrue:[
-                    self error:'Write error'.
-                ].
-               ].
+		nWritten := out nextPutBytes:n from:buffer startingAt:1.
+		offset := offset + nWritten.
+		nWritten ~= n ifTrue:[
+		    self error:'Write error'.
+		].
+	       ].
 
     doRead := [:n |
-                ReadError handle:[:ex |
-                    nRead := 0.
-                    in position:offset.
-                ] do:[
-                    nRead := in nextBytes:n into:buffer startingAt:1.
-                ].
-               ].
+		ReadError handle:[:ex |
+		    nRead := 0.
+		    in position:offset.
+		] do:[
+		    nRead := in nextBytes:n into:buffer startingAt:1.
+		].
+	       ].
 
     [
-        [offset < fileSize] whileTrue:[
-            doRead value:(bufferSize min:(fileSize - offset)).
-            nRead > 0 ifTrue:[
-                lostStart notNil ifTrue:[
-                    Transcript showCR:'CORRUPT: ',(lostStart printString),' .. ',(lostEnd printString).
-                    lostStart := nil.
-                ].
-                doWrite value:nRead.
-            ].
+	[offset < fileSize] whileTrue:[
+	    doRead value:(bufferSize min:(fileSize - offset)).
+	    nRead > 0 ifTrue:[
+		lostStart notNil ifTrue:[
+		    Transcript showCR:'CORRUPT: ',(lostStart printString),' .. ',(lostEnd printString).
+		    lostStart := nil.
+		].
+		doWrite value:nRead.
+	    ].
 
-            nRead == (bufferSize min:(fileSize - offset)) ifTrue:[
-                bufferSize < buffer size ifTrue:[
-                    bufferSize := bufferSize * 2.
-                ].
-            ] ifFalse:[
-                nRead == 0 ifTrue:[
-                    "/ try reading single blocks for a while...
-                    nSingle := 512.
-                    [
-                        nSingle > 0
-                        and:[ 
-                            doRead value:256.
-                            nRead > 0]
-                    ] whileTrue:[
-                        lostStart notNil ifTrue:[
-                            Transcript showCR:'CORRUPT: ',(lostStart printString),' .. ',(lostEnd printString).
-                            lostStart := nil.
-                        ].
+	    nRead == (bufferSize min:(fileSize - offset)) ifTrue:[
+		bufferSize < buffer size ifTrue:[
+		    bufferSize := bufferSize * 2.
+		].
+	    ] ifFalse:[
+		nRead == 0 ifTrue:[
+		    "/ try reading single blocks for a while...
+		    nSingle := 512.
+		    [
+			nSingle > 0
+			and:[
+			    doRead value:256.
+			    nRead > 0]
+		    ] whileTrue:[
+			lostStart notNil ifTrue:[
+			    Transcript showCR:'CORRUPT: ',(lostStart printString),' .. ',(lostEnd printString).
+			    lostStart := nil.
+			].
 Transcript showCR:'single block at ',offset printString.
-                        doWrite value:nRead.
-                        nSingle := nSingle - 1.
-                    ].
+			doWrite value:nRead.
+			nSingle := nSingle - 1.
+		    ].
 
-                    nRead == 0 ifTrue:[
-                        in2 := sourceFile readStream binary.
-                        Error handle:[:ex |
-                        ] do:[
-                            in2 position:0.
-                            in2 nextBytes:buffer size into:buffer startingAt:1.
-                        ].
-                        seekFailed := false.
-                        Error handle:[:ex |
-                            seekFailed := true.
-                        ] do:[
-                            in2 position:offset.
-                        ].
-                        seekFailed ifTrue:[
-                            buffer from:1 to:256 put:0.
-                            Transcript showCR:'bad seek at ',offset printString.
-                            doWrite value:256.
-                        ] ifFalse:[
-                            in close.
-                            in := in2.
-                            doRead value:256.
-                            nRead > 0 ifTrue:[
+		    nRead == 0 ifTrue:[
+			in2 := sourceFile readStream binary.
+			Error handle:[:ex |
+			] do:[
+			    in2 position:0.
+			    in2 nextBytes:buffer size into:buffer startingAt:1.
+			].
+			seekFailed := false.
+			Error handle:[:ex |
+			    seekFailed := true.
+			] do:[
+			    in2 position:offset.
+			].
+			seekFailed ifTrue:[
+			    buffer from:1 to:256 put:0.
+			    Transcript showCR:'bad seek at ',offset printString.
+			    doWrite value:256.
+			] ifFalse:[
+			    in close.
+			    in := in2.
+			    doRead value:256.
+			    nRead > 0 ifTrue:[
 Transcript showCR:'single after reopen at ',offset printString.
-                                doWrite value:nRead.
-                            ] ifFalse:[
-                                lostStart isNil ifTrue:[
-                                    lostStart := lostEnd := offset.
-                                ] ifFalse:[
-                                    lostEnd := offset.
-                                ].
-                                buffer from:1 to:256 put:0.
+				doWrite value:nRead.
+			    ] ifFalse:[
+				lostStart isNil ifTrue:[
+				    lostStart := lostEnd := offset.
+				] ifFalse:[
+				    lostEnd := offset.
+				].
+				buffer from:1 to:256 put:0.
 Transcript showCR:'bad at ',offset printString.
-                                doWrite value:256.
-                                bufferSize := 256.
-                            ].
-                        ]
-                    ]
-                ].
-            ].
-            Transcript showCR:offset.
-        ].
+				doWrite value:256.
+				bufferSize := 256.
+			    ].
+			]
+		    ]
+		].
+	    ].
+	    Transcript showCR:offset.
+	].
     ] ensure:[
-        in close.
-        out close.
+	in close.
+	out close.
     ].
     lostStart notNil ifTrue:[
-        Transcript showCR:'CORRUPT: ',(lostStart printString),' .. ',(lostEnd printString).
-        lostStart := nil.
+	Transcript showCR:'CORRUPT: ',(lostStart printString),' .. ',(lostEnd printString).
+	lostStart := nil.
     ].
 
     "Created: / 07-02-2007 / 18:40:32 / cg"
@@ -691,7 +691,7 @@
 "/    LastCreatedDirectory notNil ifTrue:[
 "/        defaultDirectory := LastCreatedDirectory baseName.
 "/    ].
-    
+
     ^ self createDirectoryIn:startDirectory initialAnswer:defaultDirectory
 !
 
@@ -723,34 +723,34 @@
     startBaseName := startDirectory baseName.
     initialAnswer := initialAnswerArg.
     (startDirectory construct:initialAnswer) exists ifTrue:[
-        initialAnswer := nil.
+	initialAnswer := nil.
     ].
     newName := Dialog
-                    request:(resources string:'Create New Directory in %1:' with:startBaseName allBold)
-                    initialAnswer:initialAnswer
-                    okLabel:(resources string:'Create')
-                    title:(resources string:'Create Directory')
-                    onCancel:[
-                        self result:false. 
-                        ^ self
-                    ].
+		    request:(resources string:'Create New Directory in %1:' with:startBaseName allBold)
+		    initialAnswer:initialAnswer
+		    okLabel:(resources string:'Create')
+		    title:(resources string:'Create Directory')
+		    onCancel:[
+			self result:false.
+			^ self
+		    ].
     newName isEmpty ifTrue:[
-        self result:false. 
-        ^ self
+	self result:false.
+	^ self
     ].
     newDir := startDirectory construct:newName.
     newDir exists ifTrue:[
-        Dialog warn:(newName, ' already exists.').
-        result := false.
-        ^ self
+	Dialog warn:(newName, ' already exists.').
+	result := false.
+	^ self
     ].
 
     newDir makeDirectory ifFalse:[
-        msg := errorString := ('cannot create directory '', newName,'' !!') , '(', (OperatingSystem lastErrorString) , ')'.
-        errorString := msg.
-        Dialog warn:errorString.
-        result := false.
-        ^ self
+	msg := errorString := ('cannot create directory '', newName,'' !!') , '(', (OperatingSystem lastErrorString) , ')'.
+	errorString := msg.
+	Dialog warn:errorString.
+	result := false.
+	^ self
     ].
     self createdFile:newDir.
     LastCreatedDirectory := newDir.
@@ -767,52 +767,52 @@
     resources := AbstractFileBrowser classResources.
 
     aFile isDirectory ifTrue:[
-        directory := aFile
+	directory := aFile
     ] ifFalse:[
-        directory := aFile directory.
-        file := aFile
+	directory := aFile directory.
+	file := aFile
     ].
     LastCreatedFile isNil ifTrue:[
-        defaultFile := aFile baseName.
+	defaultFile := aFile baseName.
     ] ifFalse:[
-        defaultFile := LastCreatedFile baseName.
+	defaultFile := LastCreatedFile baseName.
     ].
     newName := Dialog
-                    request:(resources string:'Create New File in %1:' with:directory baseName allBold)
-                    initialAnswer:defaultFile
-                    okLabel:(resources string:'Create')
-                    title:(resources string:'Create File')
-                    onCancel:[
-                        self result:false. 
-                        ^ self
-                    ].
+		    request:(resources string:'Create New File in %1:' with:directory baseName allBold)
+		    initialAnswer:defaultFile
+		    okLabel:(resources string:'Create')
+		    title:(resources string:'Create File')
+		    onCancel:[
+			self result:false.
+			^ self
+		    ].
     newName isEmpty ifTrue:[
-        self result:false. 
+	self result:false.
     ] ifFalse:[
-        | newFile |
-        newFile := directory construct:newName.
-        newFile exists ifTrue:[
-            (Dialog 
-                confirm:(newName, ' already exists truncate ?')
-                yesLabel:('Truncate')
-                noLabel:('Cancel'))
-            ifFalse:[
-                self result:false. 
-                ^ self
-            ].
-        ].
-        FileStream openErrorSignal handle:[:ex|
-            msg := ('Cannot create file '', newName,'' !!') , '(' , (FileStream lastErrorString) , ')'.
-            errorString := msg.
-            self result:false. 
-            ^ Dialog warn:errorString
-        ] do:[    
-            aStream := newFile newReadWriteStream.
-        ].
-        aStream close.
-        self createdFile:newFile.
-        LastCreatedFile := newFile.
-        self result:true. 
+	| newFile |
+	newFile := directory construct:newName.
+	newFile exists ifTrue:[
+	    (Dialog
+		confirm:(newName, ' already exists truncate ?')
+		yesLabel:('Truncate')
+		noLabel:('Cancel'))
+	    ifFalse:[
+		self result:false.
+		^ self
+	    ].
+	].
+	FileStream openErrorSignal handle:[:ex|
+	    msg := ('Cannot create file '', newName,'' !!') , '(' , (FileStream lastErrorString) , ')'.
+	    errorString := msg.
+	    self result:false.
+	    ^ Dialog warn:errorString
+	] do:[
+	    aStream := newFile newReadWriteStream.
+	].
+	aStream close.
+	self createdFile:newFile.
+	LastCreatedFile := newFile.
+	self result:true.
     ].
 !
 
@@ -825,11 +825,11 @@
     resources := AbstractFileBrowser classResources.
 
     aFile isDirectory ifTrue:[
-        newPath := aFile asValue.
-        oldPath := aFile asValue.
+	newPath := aFile asValue.
+	oldPath := aFile asValue.
     ] ifFalse:[
-        newPath := aFile directory asValue.
-        oldPath := aFile asValue.
+	newPath := aFile directory asValue.
+	oldPath := aFile asValue.
     ].
 
     box := Dialog new.
@@ -844,14 +844,14 @@
     box addAbortAndOkButtons.
 
     aFile isDirectory ifFalse:[
-        box focusOnField:if1.
+	box focusOnField:if1.
     ].
     box showAtPointer.
 
     box accepted ifFalse:[
-        self result:false.
+	self result:false.
     ] ifTrue:[
-        self doCreateLinkFrom:(oldPath value) to:(newPath value) soft:symbolic.
+	self doCreateLinkFrom:(oldPath value) to:(newPath value) soft:symbolic.
     ].
 !
 
@@ -865,57 +865,57 @@
     resources := AbstractFileBrowser classResources.
 
     (oldPath size == 0) ifTrue:[
-        self operationError:'Missing source'.
-        ^ self.
+	self operationError:'Missing source'.
+	^ self.
     ].
     (newPath size == 0) ifTrue:[
-        self operationError:'Missing link name (target)'.
-        ^ self.
+	self operationError:'Missing link name (target)'.
+	^ self.
     ].
 
     newPathFile := newPath asFilename.
     oldPathFile := oldPath asFilename.
 
     newPathFile exists ifTrue:[
-        newPathFile isDirectory ifTrue:[
-            newPathFile := newPathFile construct:(oldPathFile baseName).
-            newPath := newPathFile name.
-        ].
+	newPathFile isDirectory ifTrue:[
+	    newPathFile := newPathFile construct:(oldPathFile baseName).
+	    newPath := newPathFile name.
+	].
     ].
 
     newPathFile exists ifTrue:[
-        self operationError:(resources string:'%1 already exists' with:newPath allBold).
-        ^ self.
+	self operationError:(resources string:'%1 already exists' with:newPath allBold).
+	^ self.
     ].
     oldPathFile exists ifFalse:[
-        symbolic ifTrue:[
-            oldPathFile isAbsolute ifTrue:[
-                self operationError:(resources string:'%1 does not exist' with:oldPath allBold).
-                ^ self.
-            ].
-            (newPathFile directory construct:oldPath) exists ifFalse:[
-                Dialog warn:(resources string:'%1 does not exist (Warning only)' with:oldPath allBold).
-            ].
-        ] ifFalse:[
-            self operationError:(resources string:'%1 does not exist' with:oldPath allBold).
-            ^ self.
-        ].
+	symbolic ifTrue:[
+	    oldPathFile isAbsolute ifTrue:[
+		self operationError:(resources string:'%1 does not exist' with:oldPath allBold).
+		^ self.
+	    ].
+	    (newPathFile directory construct:oldPath) exists ifFalse:[
+		Dialog warn:(resources string:'%1 does not exist (Warning only)' with:oldPath allBold).
+	    ].
+	] ifFalse:[
+	    self operationError:(resources string:'%1 does not exist' with:oldPath allBold).
+	    ^ self.
+	].
     ].
     ((symbolic not) and:[oldPathFile isDirectory]) ifTrue:[
-        self operationError:(resources string:'%1 is a directory' with:oldPath allBold).
-        ^ self.
+	self operationError:(resources string:'%1 is a directory' with:oldPath allBold).
+	^ self.
     ].
     ErrorSignal handle:[:ex |
-        err := ex errorString.
-        self operationError:err.
+	err := ex errorString.
+	self operationError:err.
     ] do:[
-        symbolic ifTrue:[
-            OperatingSystem createSymbolicLinkFrom:oldPath to:newPath.
-        ] ifFalse:[
-            OperatingSystem createHardLinkFrom:oldPath to:newPath
-        ].
-        self createdFile:newPathFile.
-        self result:true.
+	symbolic ifTrue:[
+	    OperatingSystem createSymbolicLinkFrom:oldPath to:newPath.
+	] ifFalse:[
+	    OperatingSystem createHardLinkFrom:oldPath to:newPath
+	].
+	self createdFile:newPathFile.
+	self result:true.
     ].
 ! !
 
@@ -961,25 +961,25 @@
     | file isDirectory |
 
     aFileOrDirectory notNil ifTrue:[
-        file := aFileOrDirectory asFilename.
+	file := aFileOrDirectory asFilename.
 
-        isDirectory := file isDirectory.
+	isDirectory := file isDirectory.
 
-        Error handle:[:ex|
-            "was not able to remove it"
-            Dialog warn:(ex description).
-            self errorString:(ex description).
-            result := false.
-            ^ self.
-        ] do:[
-            isDirectory ifTrue:[
-                file recursiveRemove
-            ] ifFalse:[
-                self eraseFilesContentsBeforeRemoving:file.
-                file remove
-            ].
-        ].
-        "/ flush parent directory or directory
+	Error handle:[:ex|
+	    "was not able to remove it"
+	    Dialog warn:(ex description).
+	    self errorString:(ex description).
+	    result := false.
+	    ^ self.
+	] do:[
+	    isDirectory ifTrue:[
+		file recursiveRemove
+	    ] ifFalse:[
+		self eraseFilesContentsBeforeRemoving:file.
+		file remove
+	    ].
+	].
+	"/ flush parent directory or directory
     ].
     DirectoryContents flushCachedDirectoryFor:(file directory).
     result := true.
@@ -996,96 +996,96 @@
 
     nFilesToDelete := colOfFiles size.
     colOfFiles do:[:filenameOrString |
-        |filename doDelete skip|
+	|filename doDelete skip|
 
-        filename := filenameOrString asFilename.
+	filename := filenameOrString asFilename.
 
-        skip := false.
-        fileTypeString := ''.
-        filename isSymbolicLink ifTrue:[
-            fileTypeString := 'symbolic link '.
-        ] ifFalse:[        
-            filename exists ifFalse:[ 
-                (Dialog 
-                    confirm:('%1 does not exist.' bindWith:filename asString allBold)
-                    yesLabel:(resources string:'Proceed')
-                    noLabel:(resources string:'Cancel')) 
-                ifFalse:[
-                    ^ self.
-                ].
-                skip := true.
-            ]
-        ].
-        skip ifFalse:[
-            ask ifTrue:[
-                nFilesToDelete = 1 ifTrue:[
-                    labels := #('No' 'Yes').
-                    values := #(#no #yes).
-                ] ifFalse:[
-                    labels := #('Cancel' 'No' 'Yes' 'Yes to All' ).
-                    values := #(#cancel #no #yes #yesToAll).
-                ].
-                msg := self isErase ifTrue:'Really erase' ifFalse:'Really delete'.
-                msg := msg ,
-                       (nFilesToDelete = 1 
-                            ifTrue:'\\%1%2 ?' 
-                            ifFalse:'\\%1%2 \\(%3 files alltogether)').
-                answer := Dialog 
-                    confirmWithCancel:(resources 
-                                        stringWithCRs:msg 
-                                        with:fileTypeString
-                                        with:(filename asString allBold)
-                                        with:nFilesToDelete)
-                    labels:(resources array:labels)
-                    values:values
-                    default:(values indexOf:#yes).
-            ] ifFalse:[
-                answer := #yesToAll.
-            ].
+	skip := false.
+	fileTypeString := ''.
+	filename isSymbolicLink ifTrue:[
+	    fileTypeString := 'symbolic link '.
+	] ifFalse:[
+	    filename exists ifFalse:[
+		(Dialog
+		    confirm:('%1 does not exist.' bindWith:filename asString allBold)
+		    yesLabel:(resources string:'Proceed')
+		    noLabel:(resources string:'Cancel'))
+		ifFalse:[
+		    ^ self.
+		].
+		skip := true.
+	    ]
+	].
+	skip ifFalse:[
+	    ask ifTrue:[
+		nFilesToDelete = 1 ifTrue:[
+		    labels := #('No' 'Yes').
+		    values := #(#no #yes).
+		] ifFalse:[
+		    labels := #('Cancel' 'No' 'Yes' 'Yes to All' ).
+		    values := #(#cancel #no #yes #yesToAll).
+		].
+		msg := self isErase ifTrue:'Really erase' ifFalse:'Really delete'.
+		msg := msg ,
+		       (nFilesToDelete = 1
+			    ifTrue:'\\%1%2 ?'
+			    ifFalse:'\\%1%2 \\(%3 files alltogether)').
+		answer := Dialog
+		    confirmWithCancel:(resources
+					stringWithCRs:msg
+					with:fileTypeString
+					with:(filename asString allBold)
+					with:nFilesToDelete)
+		    labels:(resources array:labels)
+		    values:values
+		    default:(values indexOf:#yes).
+	    ] ifFalse:[
+		answer := #yesToAll.
+	    ].
 
-            answer == #cancel ifTrue:[
-                ^ self.
-            ].
+	    answer == #cancel ifTrue:[
+		^ self.
+	    ].
 
-            answer == #yesToAll ifTrue:[
-                ask := false.
-                answer := #yes.
-            ].
+	    answer == #yesToAll ifTrue:[
+		ask := false.
+		answer := #yes.
+	    ].
 
-            answer == #yes ifTrue:[
-                doDelete := true.
-                filename isSymbolicLink ifFalse:[
-                    dontAskForNonEmptyDirectory ifFalse:[
-                        filename isNonEmptyDirectory ifTrue:[
-                            colOfFiles size == 1 ifTrue:[
-                                lbls := #('Cancel' 'Remove').
-                                vals := #(false true).
-                            ] ifFalse:[
-                                lbls := #('Cancel All' 'Keep' 'Remove' 'Remove All').
-                                vals := #(nil false true #removeAll).
-                            ].
-                            doDelete := Dialog
-                                        confirmWithCancel:(resources 
-                                                            stringWithCRs:'Directory ''%1'' is not empty\remove anyway ?' 
-                                                            with:filename pathName allBold) 
-                                        labels:( resources array:lbls )
-                                        values:vals 
-                                        default:(vals indexOf:true).
-                            doDelete == nil ifTrue:[
-                                ^ self
-                            ].
-                            doDelete == #removeAll ifTrue:[
-                                dontAskForNonEmptyDirectory := true.
-                                doDelete := true.
-                            ].
-                        ].
-                    ].
-                ].
-                doDelete ifTrue:[
-                    self deleteFile:filename.
-                ]
-            ].
-        ].
+	    answer == #yes ifTrue:[
+		doDelete := true.
+		filename isSymbolicLink ifFalse:[
+		    dontAskForNonEmptyDirectory ifFalse:[
+			filename isNonEmptyDirectory ifTrue:[
+			    colOfFiles size == 1 ifTrue:[
+				lbls := #('Cancel' 'Remove').
+				vals := #(false true).
+			    ] ifFalse:[
+				lbls := #('Cancel All' 'Keep' 'Remove' 'Remove All').
+				vals := #(nil false true #removeAll).
+			    ].
+			    doDelete := Dialog
+					confirmWithCancel:(resources
+							    stringWithCRs:'Directory ''%1'' is not empty\remove anyway ?'
+							    with:filename pathName allBold)
+					labels:( resources array:lbls )
+					values:vals
+					default:(vals indexOf:true).
+			    doDelete == nil ifTrue:[
+				^ self
+			    ].
+			    doDelete == #removeAll ifTrue:[
+				dontAskForNonEmptyDirectory := true.
+				doDelete := true.
+			    ].
+			].
+		    ].
+		].
+		doDelete ifTrue:[
+		    self deleteFile:filename.
+		]
+	    ].
+	].
     ].
 
     "Modified: / 05-09-2006 / 11:52:35 / cg"
@@ -1110,15 +1110,15 @@
     fileSize := file fileSize.
     writeStream := file asFilename readWriteStream.
 
-    remaining := fileSize.    
+    remaining := fileSize.
     bufferSize := 8192.
     buffer := ByteArray new:bufferSize.
     [remaining > 0] whileTrue:[
-        nWritten := writeStream 
-            nextPutBytes:(bufferSize min:remaining)
-            from:buffer
-            startingAt:1.
-        remaining := remaining - nWritten.
+	nWritten := writeStream
+	    nextPutBytes:(bufferSize min:remaining)
+	    from:buffer
+	    startingAt:1.
+	remaining := remaining - nWritten.
     ].
     writeStream close.
 
@@ -1191,7 +1191,7 @@
 
 collectionOfMovedFiles
     movedFiles isNil ifTrue:[
-        movedFiles := OrderedCollection new.
+	movedFiles := OrderedCollection new.
     ].
     ^ movedFiles
 ! !
@@ -1226,57 +1226,57 @@
 
     targetIsDirectory := aDestFile isDirectory.
     targetIsDirectory ifTrue:[
-        targetDirectory := aDestFile.
-        newFile := aDestFile construct:(aSourceFile baseName).
+	targetDirectory := aDestFile.
+	newFile := aDestFile construct:(aSourceFile baseName).
     ] ifFalse:[
-        targetDirectory := aDestFile directory.
-        newFile := aDestFile.
+	targetDirectory := aDestFile directory.
+	newFile := aDestFile.
     ].
     "/ do not copy if destination directory doest exist.
     targetDirectory exists ifFalse:[
-        Dialog warn:'Cannot move to non-existing directory ', targetDirectory asString. 
-        result := false.
-        ^ self
+	Dialog warn:'Cannot move to non-existing directory ', targetDirectory asString.
+	result := false.
+	^ self
     ].
     (newFile exists) ifTrue:[
-        ((newFile asString = aSourceFile asString) and:[move]) ifTrue:[
-            [newFile exists] whileTrue:[
-                suffix := newFile suffix.
-                fileString := newFile baseName withoutSuffix, self class suffixForCopyOverExistingFile, '.', suffix.
-                newFile := targetDirectory construct:fileString.
-            ].
-        ] ifFalse:[
-            overWriteWarning ifTrue:[
-                doMove := self fileExistsDialogForNewFile:newFile oldFile:aSourceFile withCancel:false withRemoveIfSame:true.
-                doMove == #removeSource ifTrue:[ 
-                    self halt.
-                    result := false.
-                    ^ self.
-                ].
-                doMove == #removeDestination ifTrue:[ 
-                    self halt.
-                    result := false.
-                    ^ self.
-                ].
-                doMove == true ifFalse:[ 
-                    result := false.
-                    ^ self.
-                ].
+	((newFile asString = aSourceFile asString) and:[move]) ifTrue:[
+	    [newFile exists] whileTrue:[
+		suffix := newFile suffix.
+		fileString := newFile baseName withoutSuffix, self class suffixForCopyOverExistingFile, '.', suffix.
+		newFile := targetDirectory construct:fileString.
+	    ].
+	] ifFalse:[
+	    overWriteWarning ifTrue:[
+		doMove := self fileExistsDialogForNewFile:newFile oldFile:aSourceFile withCancel:false withRemoveIfSame:true.
+		doMove == #removeSource ifTrue:[
+		    self halt.
+		    result := false.
+		    ^ self.
+		].
+		doMove == #removeDestination ifTrue:[
+		    self halt.
+		    result := false.
+		    ^ self.
+		].
+		doMove == true ifFalse:[
+		    result := false.
+		    ^ self.
+		].
 
-            ] ifFalse:[
-                result := false.
-                ^ self.
-            ]
-        ].
+	    ] ifFalse:[
+		result := false.
+		^ self.
+	    ]
+	].
     ].
     Error handle:[:ex|
-        "was not able to copy it"
-        WarningBox warn:'Error in copy file Operation: ', ex errorString.
-        self errorString:('Error in copy file Operation- ', ex description asString).
-        result := false.
-        ^ self
+	"was not able to copy it"
+	WarningBox warn:'Error in copy file Operation: ', ex errorString.
+	self errorString:('Error in copy file Operation- ', ex description asString).
+	result := false.
+	^ self
     ] do:[
-        aSourceFile moveTo:newFile.
+	aSourceFile moveTo:newFile.
     ].
     DirectoryContents flushCachedDirectoryFor:(aSourceFile directory).
     result := true.
@@ -1287,89 +1287,89 @@
     |newFile suffix fileString doMove doRemoveSource doRemoveDestination|
 
     aDirectory exists ifFalse:[
-        (Dialog confirm:(FileBrowser classResources 
-                            stringWithCRs:'Non-existing directory "%1" .\Create ?' 
-                            with:aDirectory asString allBold)) ifFalse:[
-            result := false.
-            ^ self
-        ].
-        aDirectory makeDirectory.
-        aDirectory exists ifFalse:[
-            Dialog warn:(FileBrowser classResources 
-                                stringWithCRs:'Cannot create directory "%1" !!\Create ?.' 
-                                with:aDirectory asString allBold).
-            result := false.
-            ^ self
-        ]
+	(Dialog confirm:(FileBrowser classResources
+			    stringWithCRs:'Non-existing directory "%1" .\Create ?'
+			    with:aDirectory asString allBold)) ifFalse:[
+	    result := false.
+	    ^ self
+	].
+	aDirectory makeDirectory.
+	aDirectory exists ifFalse:[
+	    Dialog warn:(FileBrowser classResources
+				stringWithCRs:'Cannot create directory "%1" !!\Create ?.'
+				with:aDirectory asString allBold).
+	    result := false.
+	    ^ self
+	]
     ].
     (aDirectory isDirectory) ifFalse:[
-        Dialog warn:('Destination %1 is not a directory.' bindWith:aDirectory asString allBold).
-        result := false.
-        ^ self
+	Dialog warn:('Destination %1 is not a directory.' bindWith:aDirectory asString allBold).
+	result := false.
+	^ self
     ].
     aColOfSourceFiles do:[: filename |
-        newFile := aDirectory construct:filename baseName.
+	newFile := aDirectory construct:filename baseName.
 
-        doMove := true.
-        doRemoveSource := false.
-        doRemoveDestination := false.
+	doMove := true.
+	doRemoveSource := false.
+	doRemoveDestination := false.
 
-        (newFile exists) ifTrue:[
-            ((newFile asString = filename asString) and:[move]) ifTrue:[
-                [newFile exists] whileTrue:[
-                    suffix := newFile suffix.
-                    fileString := newFile withoutSuffix baseName , self class suffixForCopyOverExistingFile, '.', suffix.
-                    newFile := aDirectory construct:fileString.
-                ].
-            ] ifFalse:[
-                overWriteWarning ifTrue:[
-                    doMove := self fileExistsDialogForNewFile:newFile oldFile:filename withCancel:(aColOfSourceFiles size > 1) withRemoveIfSame:true.
-                    doMove isNil ifTrue:[   "/ cancel
-                        result := false.
-                        ^ self.
-                    ].
-                    (doMove == #removeSource) ifTrue:[
-                        doRemoveSource := true.
-                        doMove := false
-                    ] ifFalse:[ 
-                        (doMove == #removeDestination) ifTrue:[
-                            doRemoveDestination := true.
-                            doMove := false
-                        ]
-                    ]
-                ]
-            ].
-        ].
+	(newFile exists) ifTrue:[
+	    ((newFile asString = filename asString) and:[move]) ifTrue:[
+		[newFile exists] whileTrue:[
+		    suffix := newFile suffix.
+		    fileString := newFile withoutSuffix baseName , self class suffixForCopyOverExistingFile, '.', suffix.
+		    newFile := aDirectory construct:fileString.
+		].
+	    ] ifFalse:[
+		overWriteWarning ifTrue:[
+		    doMove := self fileExistsDialogForNewFile:newFile oldFile:filename withCancel:(aColOfSourceFiles size > 1) withRemoveIfSame:true.
+		    doMove isNil ifTrue:[   "/ cancel
+			result := false.
+			^ self.
+		    ].
+		    (doMove == #removeSource) ifTrue:[
+			doRemoveSource := true.
+			doMove := false
+		    ] ifFalse:[
+			(doMove == #removeDestination) ifTrue:[
+			    doRemoveDestination := true.
+			    doMove := false
+			]
+		    ]
+		]
+	    ].
+	].
 
-        (doMove or:[doRemoveSource or:[doRemoveDestination]]) ifTrue:[
-            Error handle:[:ex|
-                "was not able to copy it"
-                |descriptionString|
+	(doMove or:[doRemoveSource or:[doRemoveDestination]]) ifTrue:[
+	    Error handle:[:ex|
+		"was not able to copy it"
+		|descriptionString|
 
-                result := false.
-                descriptionString := ex description asString.
-                self errorString:(' Error in Move-File Operation:', descriptionString).
-                ( Dialog 
-                    confirm:(' Error in Move-File Operation: ', descriptionString) 
-                    title:'Move'
-                    yesLabel:'Continue' 
-                    noLabel:'Abort'
-                ) ifFalse:[
-                    ^ self.
-                ].
-            ] do:[
-                doRemoveSource ifTrue:[
-                    filename remove
-                ] ifFalse:[
-                    doRemoveDestination ifTrue:[
-                        newFile remove
-                    ] ifFalse:[
-                        filename moveTo:newFile.
-                    ]
-                ]
-            ].
-            self collectionOfMovedFiles add:filename
-        ]
+		result := false.
+		descriptionString := ex description asString.
+		self errorString:(' Error in Move-File Operation:', descriptionString).
+		( Dialog
+		    confirm:(' Error in Move-File Operation: ', descriptionString)
+		    title:'Move'
+		    yesLabel:'Continue'
+		    noLabel:'Abort'
+		) ifFalse:[
+		    ^ self.
+		].
+	    ] do:[
+		doRemoveSource ifTrue:[
+		    filename remove
+		] ifFalse:[
+		    doRemoveDestination ifTrue:[
+			newFile remove
+		    ] ifFalse:[
+			filename moveTo:newFile.
+		    ]
+		]
+	    ].
+	    self collectionOfMovedFiles add:filename
+	]
     ].
     DirectoryContents flushCachedDirectoryFor:aDirectory.
     result := true.
@@ -1385,7 +1385,7 @@
     ^ instance
 !
 
-renameFiles:aColOfFiles 
+renameFiles:aColOfFiles
     |instance|
 
     instance := self new.
@@ -1397,7 +1397,7 @@
 
 renamedFiles
     renamedFiles isNil ifTrue:[
-        renamedFiles := OrderedCollection new.
+	renamedFiles := OrderedCollection new.
     ].
     ^ renamedFiles
 ! !
@@ -1410,65 +1410,65 @@
     |newFile msg resources sameFile|
 
     (oldFile isNil or:[newName isNil]) ifTrue:[
-        result := false.
-        ^ self.
+	result := false.
+	^ self.
     ].
     (oldFile asString isBlank or:[newName isBlank]) ifTrue:[
-        result := false.
-        ^ self.
+	result := false.
+	^ self.
     ].
     newName asFilename isAbsolute ifTrue:[
-        newFile := newName asFilename.
+	newFile := newName asFilename.
     ] ifFalse:[
-        (oldFile baseName = newName) ifTrue:[
-            result := false
-        ].
-        newFile := oldFile directory construct:newName.
+	(oldFile baseName = newName) ifTrue:[
+	    result := false
+	].
+	newFile := oldFile directory construct:newName.
     ].
 
     oldFile pathName = newFile pathName ifTrue:[
-        ^ self.
+	^ self.
     ].
     Filename isCaseSensitive ifFalse:[
-        sameFile := (oldFile pathName sameAs: newFile pathName)
+	sameFile := (oldFile pathName sameAs: newFile pathName)
     ] ifTrue:[
-        sameFile := false
+	sameFile := false
     ].
 
     resources := Dialog classResources.
 
     OperatingSystem errorSignal handle:[:ex|
-        msg := resources 
-                stringWithCRs:'Cannot rename file %1 to %2 !!\\(%3)' 
-                with:oldFile baseName 
-                with:newName 
-                with:(OperatingSystem lastErrorString).
-        Dialog warn:msg.
-        result := false.
-        ^ self.
+	msg := resources
+		stringWithCRs:'Cannot rename file %1 to %2 !!\\(%3)'
+		with:oldFile baseName
+		with:newName
+		with:(OperatingSystem lastErrorString).
+	Dialog warn:msg.
+	result := false.
+	^ self.
     ] do:[
-        sameFile ifFalse:[
-            newFile exists ifTrue:[
-                (newFile sameContentsAs:oldFile) ifTrue:[
-                    msg := '%1 exists [with same contents] - rename (i.e. overwrite) anyway ?'
-                ] ifFalse:[
-                    msg := '%1 exists - rename (i.e. overwrite) anyway ?'
-                ].
-                (Dialog confirmWithCancel:(resources string:msg with:newName allBold) default:false) ifFalse:[
-                    result := false.
-                    ^ self.
-                ]
-            ].
-        ].
-        oldFile renameTo:newFile.
-        self renamedFiles add:newFile.
+	sameFile ifFalse:[
+	    newFile exists ifTrue:[
+		(newFile sameContentsAs:oldFile) ifTrue:[
+		    msg := '%1 exists [with same contents] - rename (i.e. overwrite) anyway ?'
+		] ifFalse:[
+		    msg := '%1 exists - rename (i.e. overwrite) anyway ?'
+		].
+		(Dialog confirmWithCancel:(resources string:msg with:newName allBold) default:false) ifFalse:[
+		    result := false.
+		    ^ self.
+		]
+	    ].
+	].
+	oldFile renameTo:newFile.
+	self renamedFiles add:newFile.
     ].
     result := true.
 
     "Modified: / 21-09-2006 / 18:32:12 / cg"
 !
 
-renameFiles:aColOfFiles 
+renameFiles:aColOfFiles
     |resources queryBox b lastNewName lastOldName initialText oldName newName renameAll doRename|
 
     resources := AbstractFileBrowser classResources.
@@ -1478,38 +1478,38 @@
     queryBox okText:(resources string:'Rename').
 
     aColOfFiles size > 1 ifTrue:[
-        b := queryBox addAbortButtonLabelled:(resources string:'Cancel All').
-        b action:[^ self].
-        queryBox addButton:(Button label:(resources string:'Rename All') action:[renameAll := true. queryBox okPressed]) before:(queryBox okButton).
+	b := queryBox addAbortButtonLabelled:(resources string:'Cancel All').
+	b action:[^ self].
+	queryBox addButton:(Button label:(resources string:'Rename All') action:[renameAll := true. queryBox okPressed]) before:(queryBox okButton).
     ].
     aColOfFiles do:[:oldFile |
-        oldName := oldFile baseName asString.
-        lastNewName notNil ifTrue:[
-            initialText := FileBrowser goodRenameDefaultForFile:oldName lastOld:lastOldName lastNew:lastNewName.
-        ].
-        doRename := false.
-        (renameAll and:[initialText notNil]) ifTrue:[
-            doRename := true.
-            newName := initialText.
-        ] ifFalse:[
-            queryBox title:(resources string:'Rename %1 to:' with:(oldName allBold)).
-            queryBox initialText:(initialText ? oldName).
-            queryBox action:[:newEnteredName | newName := newEnteredName. doRename := true.].
-            queryBox show "showAtPointer".
-            "/ queryBox accepted ifFalse:[self halt].
-        ].
-        doRename ifTrue:[
-            (self renameFile:oldFile to:newName asString) ifTrue:[
-                result := true
-            ].
-            lastOldName := oldName.
-            lastNewName := newName.
-        ].
+	oldName := oldFile baseName asString.
+	lastNewName notNil ifTrue:[
+	    initialText := FileBrowser goodRenameDefaultForFile:oldName lastOld:lastOldName lastNew:lastNewName.
+	].
+	doRename := false.
+	(renameAll and:[initialText notNil]) ifTrue:[
+	    doRename := true.
+	    newName := initialText.
+	] ifFalse:[
+	    queryBox title:(resources string:'Rename %1 to:' with:(oldName allBold)).
+	    queryBox initialText:(initialText ? oldName).
+	    queryBox action:[:newEnteredName | newName := newEnteredName. doRename := true.].
+	    queryBox show "showAtPointer".
+	    "/ queryBox accepted ifFalse:[self halt].
+	].
+	doRename ifTrue:[
+	    (self renameFile:oldFile to:newName asString) ifTrue:[
+		result := true
+	    ].
+	    lastOldName := oldName.
+	    lastNewName := newName.
+	].
     ]
 ! !
 
 !FileOperation class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/FileOperation.st,v 1.77 2007-02-07 21:12:05 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/FileOperation.st,v 1.78 2007-02-08 14:39:01 cg Exp $'
 ! !