[squeak-dev] The Inbox: Files-eem.195.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jul 14 14:15:41 UTC 2022


A new version of Files was added to project The Inbox:
http://source.squeak.org/inbox/Files-eem.195.mcz

==================== Summary ====================

Name: Files-eem.195
Author: eem
Time: 13 July 2022, 9:09:36.427827 pm
UUID: 7ccbfb5c-e5d3-4911-9497-09fdc484d09c
Ancestors: Files-eem.194

Occasionally FileDirectory>>exists fails.  The old implementation seems unreliable, but it's also slow.  So if possible, implement it above primLookupEntryIn:name:


Old:
| foo bar baz |
foo := FileDirectory on: '/no/where/at/all'.
bar := FileDirectory on: '/Users/eliot/Desktop/not there'.
baz := FileDirectory default.
[foo exists. bar exists. baz exists] bench '8,070 per second. 124 microseconds per run. 0 % GC time.' 

New:
| foo bar baz |
foo := FileDirectory on: '/no/where/at/all'.
bar := FileDirectory on: '/Users/eliot/Desktop/not there'.
baz := FileDirectory default.
[foo exists. bar exists. baz exists] bench '73,700 per second. 13.6 microseconds per run. 0.64 % GC time.'

=============== Diff against Files-eem.194 ===============

Item was removed:
- (PackageInfo named: 'Files') preamble: '"Migrate stdio handles and files from StandardFileStream to FileStream. Turn off encoding and reuse the streams if they are in use in the image for backwards compatibility."
- (StandardFileStream classPool at: #StdioHandles) ifNotNil: [ :handleArray |
- 	FileStream classPool at: #TheStdioHandles put: handleArray ].
- (StandardFileStream instVarNamed: #stdioFiles) ifNotNil: [ :stdioFiles |
- 	FileStream classPool
- 		at: #StdioFiles put: stdioFiles;
- 		at: #EncodeAndDecodeStdioFiles put: false ].
- Smalltalk
- 	removeFromStartUpList: StandardFileStream;
- 	removeFromShutDownList: StandardFileStream'!

Item was removed:
- SystemOrganization addCategory: #'Files-Directories'!
- SystemOrganization addCategory: #'Files-Exceptions'!
- SystemOrganization addCategory: #'Files-Kernel'!
- SystemOrganization addCategory: #'Files-System'!

Item was removed:
- FileDirectory subclass: #AcornFileDirectory
- 	instanceVariableNames: ''
- 	classVariableNames: 'LegalCharMap'
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!

Item was removed:
- ----- Method: AcornFileDirectory class>>currentDirectoryNickname (in category 'platform specific') -----
- currentDirectoryNickname
- 	"Answer the nick-name for the current directory (e.g. '.' on Unix and Windows).
- 	 Who knows what this is on Acorn?"
- 	^nil!

Item was removed:
- ----- Method: AcornFileDirectory class>>initialize (in category 'class initialization') -----
- initialize
- "Set up the legal chars map for filenames. May need extending for unicode etc.
- Basic rule is that any char legal for use in filenames will have a non-nil entry in this array; except for space, this is the same character. Space is transcoded to a char 160 to be a 'hard space' "
- "AcornFileDirectory initialize"
- 	LegalCharMap := Array new: 256.
- 	Character alphabet do:[:c|
- 		| aVal |
- 		LegalCharMap at: c asciiValue +1  put: c.
- 		LegalCharMap at: (aVal := c asUppercase) asciiValue +1 put: aVal].
- 	'`!!()-_=+[{]};~,./1234567890' do:[:c|
- 			LegalCharMap at: c asciiValue + 1 put: c].
- 	LegalCharMap at: Character space asciiValue +1 put: (Character value:160 "hardspace").
- 	LegalCharMap at: 161 put: (Character value:160 "hardspace")."secondary mapping to keep it in strings"!

Item was removed:
- ----- Method: AcornFileDirectory class>>isActiveDirectoryClass (in category 'platform specific') -----
- isActiveDirectoryClass
- 	"Does this class claim to be that properly active subclass of FileDirectory  
- 	for the current platform? On Acorn, the test is whether platformName 
- 	is 'RiscOS' (on newer VMs) or if the primPathNameDelimiter is $. (on
- 	older ones), which is what we would like to use for a dirsep if only it
- 	would work out. See pathNameDelimiter for more woeful details - then
- 	just get on and enjoy Squeak"
- 
- 	^ Smalltalk platformName = 'RiscOS'
- 		or: [self primPathNameDelimiter = $.]!

Item was removed:
- ----- Method: AcornFileDirectory class>>isCaseSensitive (in category 'platform specific') -----
- isCaseSensitive
- 	"Risc OS ignores the case of file names"
- 	^ false!

Item was removed:
- ----- Method: AcornFileDirectory class>>maxFileNameLength (in category 'platform specific') -----
- maxFileNameLength
- 
- 	^ 255
- !

Item was removed:
- ----- Method: AcornFileDirectory class>>parentDirectoryNickname (in category 'platform specific') -----
- parentDirectoryNickname
- 	"Answer the nick-name for the parent directory (e.g. '..' on Unix and Windows).
- 	 Acorn chose to use the much more sensible ^; after all it points upwards..."
- 	^$^!

Item was removed:
- ----- Method: AcornFileDirectory class>>pathNameDelimiter (in category 'platform specific') -----
- pathNameDelimiter
- "Acorn RiscOS uses a dot as the directory separator and has no real concept of filename extensions. We tried to make code handle this, but there are just too many uses of dot as a filename extension - so fake it out by pretending to use a slash. The file prims do conversions instead.
- Sad, but pragmatic"
- 	^ $/
- !

Item was removed:
- ----- Method: AcornFileDirectory>>checkName:fixErrors: (in category 'file name utilities') -----
- checkName: aFileName fixErrors: fixing
- 	"Check if the file name contains any invalid characters"
- 	| fName hasBadChars correctedName |
- 	fName := super checkName: aFileName fixErrors: fixing.
- 	correctedName := String streamContents:[:s|
- 								fName do:[:c|
- 									| newChar |
- 									(newChar := LegalCharMap at: c asciiValue +1) ifNotNil:[s nextPut: newChar]]]. 
- 	hasBadChars := fName ~= correctedName.
- 	(hasBadChars and:[fixing not]) ifTrue:[^self error:'Invalid file name'].
- 	hasBadChars ifFalse:[^ fName].
- 	^ correctedName!

Item was removed:
- ----- Method: AcornFileDirectory>>directoryContentsFor:do: (in category 'private') -----
- directoryContentsFor: fullPath do: aBlock
- 	"Evaluate aBlock with the directory entries for the files and directories in 
- 	the directory with the given path. See primLookupEntryIn:index: for 
- 	further details."
- 	"FileDirectory default directoryContentsFor: '' do: [ :each | Transcript show: each; cr ]"
- 
- 	| extraPath extraPathFullName needsExtraPath |
- 	fullPath isNullPath ifFalse: [ ^super directoryContentsFor: fullPath do: aBlock ].
- 
- 	"For Acorn we also make sure that at least the parent of the current dir 
- 	is added - sometimes this is in a filing system that has not been (or 
- 	cannot be) polled for disc root names"
- 	extraPath := self class default containingDirectory.
- 	extraPathFullName := extraPath fullName.
- 	needsExtraPath := true.
- 	super directoryContentsFor: fullPath do: [ :entry |
- 		needsExtraPath := needsExtraPath and: [ (extraPathFullName beginsWith: entry name) not ].
- 		aBlock value: entry ].
- 
- 	needsExtraPath ifFalse: [ ^self ].
- 	"Only add the extra path if we haven't already got the root of the current dir in the list"
- 	aBlock value: (
- 		DirectoryEntryDirectory
- 			directory: self
- 			name: extraPathFullName
- 			creationTime: 0
- 			modificationTime: 0
- 			fileSize: 0)!

Item was removed:
- ----- Method: AcornFileDirectory>>directoryExists: (in category 'testing') -----
- directoryExists: filenameOrPath
- "if the path is a root,we have to treat it carefully"
- 	(filenameOrPath endsWith: '$') ifTrue:[^(FileDirectory on: filenameOrPath) exists].
- 	^(self directoryNamed: filenameOrPath ) exists!

Item was removed:
- ----- Method: AcornFileDirectory>>fullPathFor: (in category 'file name utilities') -----
- fullPathFor: path
- 	"if the arg is an empty string, just return my path name converted via the language stuff. 
- If the arg seems to be a  rooted path, return it raw, assuming it is already ok.
- Otherwise cons up a path"
- 	path isEmpty ifTrue:[^pathName asSqueakPathName].
- 	((path includes: $$ ) or:[path includes: $:]) ifTrue:[^path].
- 	^pathName asSqueakPathName, self slash, path!

Item was removed:
- ----- Method: AcornFileDirectory>>pathParts (in category 'path access') -----
- pathParts
- 	"Return the path from the root of the file system to this directory as an 
- 	array of directory names.
- 	This version tries to cope with the RISC OS' strange filename formatting; 
- 	filesystem::discname/$/path/to/file
- 	where the $ needs to be considered part of the filingsystem-discname atom."
- 	| pathList |
- 	pathList := super pathParts.
- 	(pathList indexOf: '$') = 2
- 		ifTrue: ["if the second atom is root ($) then stick $ on the first atom 
- 				and drop the second. Yuck"
- 			^ pathList species
- 				streamContents: [:a | 
- 					a nextPut: (pathList at: 1), '/$'.
- 					3 to: pathList size do: [:i | a
- 								nextPut: (pathList at: i)]]].
- 	^ pathList!

Item was removed:
- Object subclass: #AsyncFile
- 	instanceVariableNames: 'name writeable semaphore fileHandle'
- 	classVariableNames: 'Busy ErrorCode'
- 	poolDictionaries: ''
- 	category: 'Files-Kernel'!
- 
- !AsyncFile commentStamp: '<historical>' prior: 0!
- An asynchronous file allows simple file read and write operations to be performed in parallel with other processing. This is useful in multimedia applications that need to stream large amounts of sound or image data from or to a file while doing other work.
- !

Item was removed:
- ----- Method: AsyncFile class>>initialize (in category 'class initialization') -----
- initialize
- 	"AsyncFile initialize"
- 
- 	"Possible abnormal I/O completion results."
- 	Busy := -1.
- 	ErrorCode := -2.
- !

Item was removed:
- ----- Method: AsyncFile>>close (in category 'file open/close') -----
- close
- 
- 	fileHandle ifNil: [^ self].  "already closed"
- 	self primClose: fileHandle.
- 	Smalltalk unregisterExternalObject: semaphore.
- 	semaphore := nil.
- 	fileHandle := nil.
- !

Item was removed:
- ----- Method: AsyncFile>>fileHandle (in category 'accessing') -----
- fileHandle
- 	^ fileHandle!

Item was removed:
- ----- Method: AsyncFile>>open:forWrite: (in category 'file open/close') -----
- open: fullFileName forWrite: aBoolean
- 	"Open a file of the given name, and return a handle for that file. Answer the receiver if the primitive succeeds, nil otherwise.
- 	If openForWrite is true, then:
- 		if there is no existing file with this name, then create one
- 		else open the existing file in read-write mode
- 	otherwise:
- 		if there is an existing file with this name, then open it read-only
- 		else answer nil."
- 	"Note: if an exisiting file is opened for writing, it is NOT truncated. If truncation is desired, the file should be deleted before being opened as an asynchronous file."
- 	"Note: On some platforms (e.g., Mac), a file can only have one writer at a time."
- 
- 	name := fullFileName.
- 	writeable := aBoolean.
- 	^Smalltalk newExternalSemaphoreDo: [ :newSemaphore :index |
- 		fileHandle := self primOpen: name asVmPathName forWrite: writeable semaIndex: index.
- 		fileHandle
- 			ifNotNil: [
- 				semaphore := newSemaphore.
- 				self ]
- 			ifNil: [
- 				Smalltalk unregisterExternalObject: newSemaphore.
- 				nil ] ]!

Item was removed:
- ----- Method: AsyncFile>>primClose: (in category 'primitives') -----
- primClose: fHandle
- 	"Close this file. Do nothing if primitive fails."
- 
- 	<primitive: 'primitiveAsyncFileClose' module: 'AsynchFilePlugin'>
- !

Item was removed:
- ----- Method: AsyncFile>>primOpen:forWrite:semaIndex: (in category 'primitives') -----
- primOpen: fileName forWrite: openForWrite semaIndex: semaIndex
- 	"Open a file of the given name, and return a handle for that file. Answer the receiver if the primitive succeeds, nil otherwise."
- 
- 	<primitive: 'primitiveAsyncFileOpen' module: 'AsynchFilePlugin'>
- 	^ nil
- !

Item was removed:
- ----- Method: AsyncFile>>primReadResult:intoBuffer:at:count: (in category 'primitives') -----
- primReadResult: fHandle intoBuffer: buffer at: startIndex count: count
- 	"Copy the result of the last read operation into the given buffer starting at the given index. The buffer may be any sort of bytes or words object, excluding CompiledMethods. Answer the number of bytes read. A negative result means:
- 		-1 the last operation is still in progress
- 		-2 the last operation encountered an error"
- 
- 	<primitive: 'primitiveAsyncFileReadResult' module: 'AsynchFilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: AsyncFile>>primReadStart:fPosition:count: (in category 'primitives') -----
- primReadStart: fHandle fPosition: fPosition count: count
- 	"Start a read operation of count bytes starting at the given offset in the given file."
- 
- 	<primitive: 'primitiveAsyncFileReadStart' module: 'AsynchFilePlugin'>
- 	self error: 'READ THE COMMENT FOR THIS METHOD.'
- 
- "NOTE: This method will fail if there is insufficient C heap to allocate an internal buffer of the required size (the value of count).  If you are trying to read a movie file, then the buffer size will be height*width*2 bytes.  Each Squeak image retains a value to be used for this allocation, and it it initially set to 0.  If you are wish to play a 640x480 movie, you need room for a buffer of 640*480*2 = 614400 bytes.  You should execute the following...
- 
- 	Smalltalk extraVMMemory 2555000.
- 
- Then save-and-quit, restart, and try to open the movie file again.  If you are using Async files in another way, find out the value of count when this failure occurs (call it NNNN), and instead of the above, execute...
- 
- 	Smalltalk extraVMMemory: Smalltalk extraVMMemory + NNNN
- 
- then save-and-quit, restart, and try again.
- "
- 
- !

Item was removed:
- ----- Method: AsyncFile>>primWriteResult: (in category 'primitives') -----
- primWriteResult: fHandle
- 	"Answer the number of bytes written. A negative result means:
- 		-1 the last operation is still in progress
- 		-2 the last operation encountered an error"
- 
- 	<primitive: 'primitiveAsyncFileWriteResult' module: 'AsynchFilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: AsyncFile>>primWriteStart:fPosition:fromBuffer:at:count: (in category 'primitives') -----
- primWriteStart: fHandle fPosition: fPosition fromBuffer: buffer at: startIndex count: count
- 	"Start a write operation of count bytes starting at the given index in the given buffer. The buffer may be any sort of bytes or words object, excluding CompiledMethods. The contents of the buffer are copied into an internal buffer immediately, so the buffer can be reused after the write operation has been started. Fail if there is insufficient C heap to allocate an internal buffer of the requested size."
- 
- 	<primitive: 'primitiveAsyncFileWriteStart' module: 'AsynchFilePlugin'>
- 	writeable ifFalse: [^ self error: 'attempt to write a file opened read-only'].
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: AsyncFile>>readByteCount:fromFilePosition:onCompletionDo: (in category 'reading') -----
- readByteCount: byteCount fromFilePosition: fPosition onCompletionDo: aBlock
- 	"Start a read operation to read byteCount's from the given position in this file. and fork a process to await its completion. When the operation completes, evaluate the given block. Note that, since the completion block may run asynchronous, the client may need to use a SharedQueue or a semaphore for synchronization."
- 
- 	| buffer |
- 	buffer := String new: byteCount.
- 	self primReadStart: fileHandle fPosition: fPosition count: byteCount.
- 	"here's the process that awaits the results:"
- 	[| n |
- 		[	semaphore wait.
- 		  	n := self primReadResult: fileHandle intoBuffer: buffer at: 1 count: byteCount.
- 		  	n = Busy.
- 		] whileTrue.  "loop while busy in case the semaphore had excess signals"
- 		n = ErrorCode ifTrue: [^ self error: 'asynchronous read operation failed'].
- 		aBlock value: buffer.
- 	] forkAt: Processor userInterruptPriority.
- !

Item was removed:
- ----- Method: AsyncFile>>test:fileName: (in category 'tests') -----
- test: byteCount fileName: fileName
- 	"AsyncFile new test: 10000 fileName: 'testData'"
- 
- 	| buf1 buf2 bytesWritten bytesRead |
- 	buf1 := String new: byteCount withAll: $x.
- 	buf2 := String new: byteCount.
- 	self open: ( FileDirectory default fullNameFor: fileName) forWrite: true.
- 	self primWriteStart: fileHandle
- 		fPosition: 0
- 		fromBuffer: buf1
- 		at: 1
- 		count: byteCount.
- 	semaphore wait.
- 	bytesWritten := self primWriteResult: fileHandle.
- 	self close.
- 	
- 	self open: ( FileDirectory default fullNameFor: fileName) forWrite: false.
- 	self primReadStart: fileHandle fPosition: 0 count: byteCount.
- 	semaphore wait.
- 	bytesRead :=
- 		self primReadResult: fileHandle
- 			intoBuffer: buf2
- 			at: 1
- 			count: byteCount.
- 	self close.
- 
- 	buf1 = buf2 ifFalse: [self error: 'buffers do not match'].
- 	^ 'wrote ', bytesWritten printString, ' bytes; ',
- 	   'read ', bytesRead printString, ' bytes'
- !

Item was removed:
- ----- Method: AsyncFile>>waitForCompletion (in category 'private') -----
- waitForCompletion
- 	semaphore wait!

Item was removed:
- ----- Method: AsyncFile>>writeBuffer:atFilePosition:onCompletionDo: (in category 'private') -----
- writeBuffer: buffer atFilePosition: fPosition onCompletionDo: aBlock
- 	"Start an operation to write the contents of the buffer at given position in this file, and fork a process to await its completion. When the write completes, evaluate the given block. Note that, since the completion block runs asynchronously, the client may need to use a SharedQueue or a semaphore for synchronization."
- 
- 	self primWriteStart: fileHandle
- 		fPosition: fPosition
- 		fromBuffer: buffer
- 		at: 1
- 		count: buffer size.
- 	"here's the process that awaits the results:"
- 	[| n |
- 		[	semaphore wait.
- 		  	n := self primWriteResult: fileHandle.
- 		  	n = Busy.
- 		] whileTrue.  "loop while busy in case the semaphore had excess signals"
- 		n = ErrorCode ifTrue: [^ self error: 'asynchronous write operation failed'].
- 		n = buffer size ifFalse: [^ self error: 'did not write the entire buffer'].
- 		aBlock value.
- 	] forkAt: Processor userInterruptPriority.
- !

Item was removed:
- FileStreamException subclass: #CannotDeleteFileException
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Exceptions'!

Item was removed:
- Exception subclass: #CurrentReadOnlySourceFiles
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-System'!
- 
- !CurrentReadOnlySourceFiles commentStamp: 'ul 3/17/2011 01:17' prior: 0!
- I'm useful to avoid the creation of several read-only copies of the source files. Use me instead of SourceFiles in your code when you need a read-only copy, like here:
- 
- CurrentReadOnlySourceFiles at: 1.
- 
- To reuse the source files, surround your code the following way:
- 
- CurrentReadOnlySourceFiles cacheDuring: [
- 	<your code here using CurrentReadOnlySourceFiles> ]
- 
- Note that it's still better performance wise to store the source files in a variable in your code if you need them more than once, than throwing many exceptions.!

Item was removed:
- ----- Method: CurrentReadOnlySourceFiles class>>at: (in category 'act like SourceFiles') -----
- at: sourceFileIndex
- 
- 	^self signal at: sourceFileIndex!

Item was removed:
- ----- Method: CurrentReadOnlySourceFiles class>>cacheDuring: (in category 'caching') -----
- cacheDuring: aBlock
- 	"Cache the read only source files on the first request and use them on subsequent requests during the evaluation of aBlock."
- 	
- 	| currentReadOnlySouceFiles |
- 	currentReadOnlySouceFiles := nil.
- 	^aBlock
- 		on: self
- 		do: [ :exception |
- 			exception resume: (currentReadOnlySouceFiles ifNil: [
- 				currentReadOnlySouceFiles := exception defaultAction ]) ]!

Item was removed:
- ----- Method: CurrentReadOnlySourceFiles>>defaultAction (in category 'handling') -----
- defaultAction
- 	"Return a read-only copy of SourceFiles."
- 
- 	^SourceFiles collect: [ :each |
- 		each ifNotNil: [
- 			[ each readOnlyCopy ]
- 				on: FileDoesNotExistException
- 				do: [ :ex | nil "file does not exist happens in secure mode" ] ] ]!

Item was removed:
- Object subclass: #DirectoryEntry
- 	instanceVariableNames: 'directory name creationTime modificationTime fileSize attributes'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!
- 
- !DirectoryEntry commentStamp: '<historical>' prior: 0!
- an entry in a directory; a reference to either a file or a directory.!

Item was removed:
- ----- Method: DirectoryEntry class>>directory:name:creationTime:modificationTime:fileSize: (in category 'instance creation') -----
- directory: aFileDirectoryOrServerDirectory name: name0 creationTime: creationTime modificationTime: modificationTime fileSize: fileSize 
- 	^ self new 
- 		setDirectory: aFileDirectoryOrServerDirectory
- 		name: name0
- 		creationTime: creationTime
- 		modificationTime: modificationTime
- 		fileSize: fileSize!

Item was removed:
- ----- Method: DirectoryEntry class>>fromArray:directory: (in category 'instance creation') -----
- fromArray: array directory: aFileDirectoryOrServerDirectory 
- 	| entryType |
- 	entryType := (array at: 4) 
- 		ifTrue: [ DirectoryEntryDirectory ]
- 		ifFalse: [ DirectoryEntryFile ].
- 	^ entryType 
- 		directory: aFileDirectoryOrServerDirectory
- 		name: (array at: 1)
- 		creationTime: (array at: 2)
- 		modificationTime: (array at: 3)
- 		fileSize: (array at: 5)!

Item was removed:
- ----- Method: DirectoryEntry>>= (in category 'testing') -----
- = aDirectoryEntry 
- 	"Answer whether I am equivalent in all of my file-system attributes."
- 	super = aDirectoryEntry ifTrue: [^ true].
- 	self species = aDirectoryEntry species ifFalse: [^ false].
- 	^ self containingDirectory = aDirectoryEntry containingDirectory
- 		and: [self name = aDirectoryEntry name
- 				and: [self modificationTime = aDirectoryEntry modificationTime
- 						and: [self fileSize = aDirectoryEntry fileSize]]]!

Item was removed:
- ----- Method: DirectoryEntry>>asDirectoryEntry (in category 'converting') -----
- asDirectoryEntry
- 	^ self!

Item was removed:
- ----- Method: DirectoryEntry>>at: (in category 'access') -----
- at: index
- 	"compatibility interface"
- 	self deprecated: 'old-style access to DirectoryEntry'.
- 	index = 1 ifTrue: [ ^self name ].
- 	index = 2 ifTrue: [ ^self creationTime ].
- 	index = 3 ifTrue: [ ^self modificationTime ].
- 	index = 4 ifTrue:[ ^self isDirectory ].
- 	index = 5 ifTrue:[ ^self fileSize ].
- 	self error: 'invalid index specified'.
- !

Item was removed:
- ----- Method: DirectoryEntry>>attributeNamed:ifAbsent: (in category 'access') -----
- attributeNamed: aString ifAbsent: oneArgBlock 
- 	"Answer the value of attribute named aString.  If no attribute by that name has ever been set, answer oneArgBlock value."
- 	^ self attributes 
- 		at: aString
- 		ifAbsent: oneArgBlock!

Item was removed:
- ----- Method: DirectoryEntry>>attributeNamed:put: (in category 'access') -----
- attributeNamed: aString put: anObject
- 	"Set the value of attribute named aString.  This is provided for extension by third-party developers."
- 	^ self attributes 
- 		at: aString
- 		put: anObject!

Item was removed:
- ----- Method: DirectoryEntry>>attributes (in category 'private-initialization') -----
- attributes
- 	^ attributes ifNil: [ attributes := Dictionary new ]!

Item was removed:
- ----- Method: DirectoryEntry>>baseName (in category 'access') -----
- baseName
- 	^ FileDirectory baseNameFor: self name!

Item was removed:
- ----- Method: DirectoryEntry>>containingDirectory (in category 'access') -----
- containingDirectory
- 	"Answer the FileDirectory in which I reside."
- 	^ directory!

Item was removed:
- ----- Method: DirectoryEntry>>convertFromSystemName (in category 'multilingual system') -----
- convertFromSystemName
- 
- 	name := name vmPathToSqueakPath!

Item was removed:
- ----- Method: DirectoryEntry>>copyTo: (in category 'file operations') -----
- copyTo: fileOrServerDirectory 
- 	"Copy me to fileOrServerDirectory."
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DirectoryEntry>>creationDateAndTime (in category 'access') -----
- creationDateAndTime
- 	"The DateAndTime my entry in the file system was created."
- 	^DateAndTime fromSeconds: creationTime!

Item was removed:
- ----- Method: DirectoryEntry>>creationTime (in category 'access') -----
- creationTime
- 	"The time the entry was created, as an Integer number of seconds offset from the DateAndTime epoch."
- 	^creationTime!

Item was removed:
- ----- Method: DirectoryEntry>>delete (in category 'file operations') -----
- delete
- 	"Physically remove from the disk."
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DirectoryEntry>>directorySize (in category 'access') -----
- directorySize
- 	"Size of all files in that directory and all its sub-directories."
- 	
- 	^ 0!

Item was removed:
- ----- Method: DirectoryEntry>>directorySizeString (in category 'access') -----
- directorySizeString
- 
- 	^ self directorySize asBytesDescription	
- 	!

Item was removed:
- ----- Method: DirectoryEntry>>directoryTreeDo: (in category 'enumeration') -----
- directoryTreeDo: oneArgBlock
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DirectoryEntry>>exists (in category 'testing') -----
- exists
- 	^ (self containingDirectory
- 		entryAt: self name
- 		ifAbsent: [ nil ]) notNil!

Item was removed:
- ----- Method: DirectoryEntry>>extension (in category 'access') -----
- extension
- 	^ FileDirectory extensionFor: self name!

Item was removed:
- ----- Method: DirectoryEntry>>fileSize (in category 'access') -----
- fileSize
- 	"size of the entry, if it's a file"
- 	^fileSize!

Item was removed:
- ----- Method: DirectoryEntry>>fileSizeString (in category 'access') -----
- fileSizeString
- 	"Answer my file size as an easy-to-read String."
- 	^ self fileSize asBytesDescription!

Item was removed:
- ----- Method: DirectoryEntry>>fullName (in category 'access') -----
- fullName
- 	"The fully-qualified name.
- 	 Since this method falls into the equality test, make it safe when directory is nil."
- 	^ directory 
- 		ifNotNil: [ directory fullNameFor: self name ] 
- 		ifNil: [ self name ]!

Item was removed:
- ----- Method: DirectoryEntry>>hash (in category 'testing') -----
- hash
- 	"Hashing on directory + name should be sufficient."
- 	^ (self containingDirectory hash hashMultiply + self name hash) hashMultiply!

Item was removed:
- ----- Method: DirectoryEntry>>isDirectory (in category 'access') -----
- isDirectory
- 	"whether this entry represents a directory"
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DirectoryEntry>>modificationDateAndTime (in category 'access') -----
- modificationDateAndTime
- 	"The DateAndTime my entry in the file system was last modified."
- 	^ DateAndTime fromSeconds: modificationTime!

Item was removed:
- ----- Method: DirectoryEntry>>modificationTime (in category 'access') -----
- modificationTime
- 	"time the entry was last modified"
- 	^modificationTime!

Item was removed:
- ----- Method: DirectoryEntry>>name (in category 'access') -----
- name
- 	"name of the entry"
- 	^name!

Item was removed:
- ----- Method: DirectoryEntry>>printOn: (in category 'access') -----
- printOn: aStream 
- 	super printOn: aStream.
- 	aStream
- 		space ;
- 		nextPutAll: self name!

Item was removed:
- ----- Method: DirectoryEntry>>services (in category 'services') -----
- services
- 	"Answer the same collection of SimpleServiceEntry's accessed by the FileList."
- 	^ FileServices itemsForFile: self fullName!

Item was removed:
- ----- Method: DirectoryEntry>>setDirectory: (in category 'private-initialization') -----
- setDirectory: aFileOrServerDirectory 
- 	"Set only my (containing) directory.  This is only needed because I couldn't factor ServerDirectory class>>#parseFTPEntry: to the instance-side (because HTTPClient utility uses it).  Therefore, they pass a nil and then set my 'directory' immediately after.."
- 	directory := aFileOrServerDirectory!

Item was removed:
- ----- Method: DirectoryEntry>>setDirectory:name:creationTime:modificationTime:fileSize: (in category 'private-initialization') -----
- setDirectory: aFileDirectoryOrServerDirectory name: name0  creationTime: creationTime0  modificationTime: modificationTime0 fileSize: fileSize0
- 	directory := aFileDirectoryOrServerDirectory.
- 	name := name0.
- 	creationTime := creationTime0.
- 	modificationTime := modificationTime0.
- 	fileSize := fileSize0!

Item was removed:
- ----- Method: DirectoryEntry>>size (in category 'access') -----
- size
- 	"For API compatibility with byte objects (for streaming api)."
- 	^ self fileSize!

Item was removed:
- ----- Method: DirectoryEntry>>splitNameVersionExtension (in category 'access') -----
- splitNameVersionExtension
- 	" answer an array with the root name, version # and extension."
- 	^ self directory splitNameVersionExtensionFor: self name!

Item was removed:
- DirectoryEntry subclass: #DirectoryEntryDirectory
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!
- 
- !DirectoryEntryDirectory commentStamp: 'cmm 9/13/2007 12:24' prior: 0!
- an entry in a directory; a reference to a directory.!

Item was removed:
- ----- Method: DirectoryEntryDirectory>>/ (in category 'access') -----
- / aString 
- 	^ self asFileDirectory / aString!

Item was removed:
- ----- Method: DirectoryEntryDirectory>>asFileDirectory (in category 'convert') -----
- asFileDirectory
- 	"Answer a FileDirectory representing the same directory I represent."
- 
- 	^directory on: (directory fullNameFor: name)!

Item was removed:
- ----- Method: DirectoryEntryDirectory>>assureAbsence (in category 'file operations') -----
- assureAbsence
- 	self asFileDirectory assureAbsence!

Item was removed:
- ----- Method: DirectoryEntryDirectory>>copyHere: (in category 'file operations') -----
- copyHere: aDirectoryEntryFile
- 	"Copy aDirectoryFileEntry, which represents a file, to the directory I represent."
- 	^ self asFileDirectory copyHere: aDirectoryEntryFile!

Item was removed:
- ----- Method: DirectoryEntryDirectory>>delete (in category 'file operations') -----
- delete
- 	self asFileDirectory recursiveDelete!

Item was removed:
- ----- Method: DirectoryEntryDirectory>>directorySize (in category 'access') -----
- directorySize
- 
- 	| size |
- 	size := 0.
- 	self asFileDirectory entriesDo: [ :entry |
- 		entry isDirectory
- 			ifTrue: [ size := size + entry directorySize ]
- 			ifFalse:[ size := size + entry fileSize ] ].
- 	^size!

Item was removed:
- ----- Method: DirectoryEntryDirectory>>directoryTreeDo: (in category 'enumeration') -----
- directoryTreeDo: oneArgBlock
- 	self asFileDirectory directoryTreeDo: oneArgBlock!

Item was removed:
- ----- Method: DirectoryEntryDirectory>>isDirectory (in category 'testing') -----
- isDirectory
- 	"whether this entry represents a directory, it does."
- 	^ true!

Item was removed:
- DirectoryEntry subclass: #DirectoryEntryFile
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!

Item was removed:
- ----- Method: DirectoryEntryFile>>contentsFrom:to: (in category 'contents') -----
- contentsFrom: startPosition to: endPosition 
- 	"Answer my contents from startPosition to endPosition."
- 	^ FileStream 
- 		detectFile: self readStream
- 		do: 
- 			[ : stream | 
- 			stream
- 				position: startPosition ;
- 				next: endPosition - startPosition + 1 ]!

Item was removed:
- ----- Method: DirectoryEntryFile>>contentsTo: (in category 'contents') -----
- contentsTo: endPosition 
- 	"Answer my contents up to endPosition."
- 	^ self 
- 		contentsFrom: 0
- 		to: endPosition!

Item was removed:
- ----- Method: DirectoryEntryFile>>copyTo: (in category 'file operations') -----
- copyTo: targetDirectory 
- 	"Make a copy of me in targetDirectory.  targetDirectory can be a FileDirectory, ServerDirectory or a DirectoryEntryDirectory.  If a file with my name already exists in targetDirectory, signal a FileExistsException."
- 	^ targetDirectory copyHere: self!

Item was removed:
- ----- Method: DirectoryEntryFile>>delete (in category 'file operations') -----
- delete
- 	directory deleteFileNamed: self name!

Item was removed:
- ----- Method: DirectoryEntryFile>>directoryTreeDo: (in category 'enumeration') -----
- directoryTreeDo: oneArgBlock
- 	oneArgBlock value: (OrderedCollection with: self)!

Item was removed:
- ----- Method: DirectoryEntryFile>>isDirectory (in category 'testing') -----
- isDirectory
- 	"whether this entry represents a directory, it does not."
- 	^ false!

Item was removed:
- ----- Method: DirectoryEntryFile>>readStream (in category 'stream access') -----
- readStream
- 	"Answer a FileStream on my contents that can be read, but not written."
- 	^ directory readOnlyFileNamed: self name!

Item was removed:
- ----- Method: DirectoryEntryFile>>readStreamDo: (in category 'stream access') -----
- readStreamDo: aBlock 
- 	"Open a read stream on my contents and answer the value of aBlock with it, ensuring the stream is closed."
- 	^ FileStream
- 		detectFile: self readStream
- 		do: aBlock!

Item was removed:
- ----- Method: DirectoryEntryFile>>readWriteStream (in category 'stream access') -----
- readWriteStream
- 	"Answer a FileStream on my contents that can be read and written."
- 	^ directory fileNamed: self name!

Item was removed:
- ----- Method: DirectoryEntryFile>>readWriteStreamDo: (in category 'stream access') -----
- readWriteStreamDo: aBlock 
- 	"Open a read-write stream on my contents and answer the value of aBlock with it, ensuring the stream is closed."
- 	^ FileStream
- 		detectFile: self readWriteStream
- 		do: aBlock!

Item was removed:
- FileDirectory subclass: #DosFileDirectory
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!
- 
- !DosFileDirectory commentStamp: '<historical>' prior: 0!
- I represent a DOS or Windows FileDirectory.
- !

Item was removed:
- ----- Method: DosFileDirectory class>>isCaseSensitive (in category 'platform specific') -----
- isCaseSensitive
- 	"Return true if file names are treated case sensitive"
- 	^false!

Item was removed:
- ----- Method: DosFileDirectory class>>isDrive: (in category 'platform specific') -----
- isDrive: fullName
- 	"Answer whether the given full name describes a 'drive', e.g., one of the root directories of a Win32 file system. We allow two forms here - the classic one where a drive is specified by a letter followed by a colon, e.g., 'C:', 'D:' etc. and the network share form starting with double-backslashes e.g., '\\server'."
- 	^ (fullName size = 2 and: [fullName first isLetter and: [fullName last = $:]])
- 		or: [(fullName beginsWith: '\\') and: [(fullName occurrencesOf: $\) = 2]]!

Item was removed:
- ----- Method: DosFileDirectory class>>maxFileNameLength (in category 'platform specific') -----
- maxFileNameLength
- 
- 	^ 255
- !

Item was removed:
- ----- Method: DosFileDirectory class>>pathNameDelimiter (in category 'platform specific') -----
- pathNameDelimiter
- 
- 	^ $\
- !

Item was removed:
- ----- Method: DosFileDirectory class>>splitName:to: (in category 'platform specific') -----
- splitName: fullName to: pathAndNameBlock
- 	"Take the file name and convert it to the path name of a directory and a local file name within that directory. 
- 	IMPORTANT NOTE: For 'drives', e.g., roots of the file system on Windows we treat the full name of that 'drive' as the local name rather than the path. This is because conceptually, all of these 'drives' hang off the virtual root of the entire Squeak file system, specified by FileDirectory root. In order to be consistent with, e.g., 
- 
- 		DosFileDirectory localNameFor: 'C:\Windows' -> 'Windows'
- 		DosFileDirectory dirPathFor: 'C:\Windows' -> 'C:'
- 
- 	we expect the following to be true:
- 
- 		DosFileDirectory localNameFor: 'C:' -> 'C:'
- 		DosFileDirectory dirPathFor: 'C:'. -> ''
- 		DosFileDirectory localNameFor: '\\server' -> '\\server'.
- 		DosFileDirectory dirPathFor: '\\server' -> ''.
- 
- 	so that in turn the following relations hold:
- 
- 		| fd |
- 		fd := DosFileDirectory on: 'C:\Windows'.
- 		fd containingDirectory includes: fd localName.
- 		fd := DosFileDirectory on: 'C:'.
- 		fd containingDirectory includes: fd localName.
- 		fd := DosFileDirectory on: '\\server'.
- 		fd containingDirectory includes: fd localName.
- 	"
- 	(self isDrive: fullName)
- 		ifTrue: [^ pathAndNameBlock value:''  value: fullName].
- 	^ super splitName: fullName to: pathAndNameBlock!

Item was removed:
- ----- Method: DosFileDirectory>>checkName:fixErrors: (in category 'file name utilities') -----
- checkName: aFileName fixErrors: fixing
- 	"Check if the file name contains any invalid characters"
- 	| fName badChars hasBadChars |
- 	fName := super checkName: aFileName fixErrors: fixing.
- 	badChars := #( $: $< $> $| $/ $\ $? $* $") asSet.
- 	hasBadChars := fName includesAnyOf: badChars.
- 	(hasBadChars and:[fixing not]) ifTrue:[^self error:'Invalid file name'].
- 	hasBadChars ifFalse:[^ fName].
- 	^ fName collect:
- 		[:char | (badChars includes: char) 
- 				ifTrue:[$#] 
- 				ifFalse:[char]]!

Item was removed:
- ----- Method: DosFileDirectory>>driveName (in category 'path access') -----
- driveName
- 
-    "return a possible drive letter and colon at the start of a Path name, empty string otherwise"
- 
-    | firstTwoChars |
- 
-    ( pathName asSqueakPathName size >= 2 ) ifTrue: [
-       firstTwoChars := (pathName asSqueakPathName copyFrom: 1 to: 2).
-       (self class isDrive: firstTwoChars) ifTrue: [^firstTwoChars]
-    ].
-    ^''!

Item was removed:
- ----- Method: DosFileDirectory>>fullNameFor: (in category 'path access') -----
- fullNameFor: fileName
- 	"Return a corrected, fully-qualified name for the given file name. If the given name is already a full path (i.e., it contains a delimiter character), assume it is already a fully-qualified name. Otherwise, prefix it with the path to this directory. In either case, correct the local part of the file name."
- 	fileName ifNil:[^fileName].
- 	"Check for fully qualified names"
- 	((fileName size >= 2 and: [fileName first isLetter and: [fileName second = $:]])
- 		or: [(fileName beginsWith: '\\') and: [(fileName occurrencesOf: $\) >= 2]])
- 			ifTrue:[^fileName].
- 	^super fullNameFor: fileName!

Item was removed:
- ----- Method: DosFileDirectory>>fullPathFor: (in category 'path access') -----
- fullPathFor: path
- 	"Return the fully-qualified path name for the given file."
- 	path isEmpty ifTrue:[^pathName asSqueakPathName].
- 	(path at: 1) = $\ ifTrue:[
- 		(path size >= 2 and:[(path at: 2) = $\]) ifTrue:[^path]. "e.g., \\pipe\"
- 		^self driveName , path "e.g., \windows\"].
- 	(path size >= 2 and:[(path at: 2) = $: and:[path first isLetter]])
- 		ifTrue:[^path]. "e.g., c:"
- 	^pathName asSqueakPathName, self slash, path!

Item was removed:
- ----- Method: DosFileDirectory>>relativeNameFor: (in category 'path access') -----
- relativeNameFor: path
- 	"Return the full name for path, assuming that path is a name relative to me."
- 	path isEmpty ifTrue:[^pathName asSqueakPathName].
- 	(path at: 1) = $\ ifTrue:[
- 		(path size >= 2 and:[(path at: 2) = $\]) ifTrue:[^super relativeNameFor: path allButFirst ]. "e.g., \\pipe\"
- 		^super relativeNameFor: path "e.g., \windows\"].
- 	(path size >= 2 and:[(path at: 2) = $: and:[path first isLetter]])
- 		ifTrue:[^super relativeNameFor: (path copyFrom: 3 to: path size) ]. "e.g., c:"
- 	^pathName asSqueakPathName, self slash, path!

Item was removed:
- ----- Method: DosFileDirectory>>relativeNameIfAbsoluteFor: (in category 'path access') -----
- relativeNameIfAbsoluteFor: aFileName
- 	"Answer either the relative name for aFileName, if aFileName names a file in me or
- 	 subdirectories, or aFileName's absolute path if it isn't in me or subdirectories.
- 	 P.S. Ths is what I'd expect relativeNameFor: to do, but it is taken and means
- 	 exactly the opposite, i.e. the absolute path for a relative name."
- 	| fullNameSize fullName fileNameSize |
- 	(aFileName isEmpty or: [aFileName first ~= self driveName first]) ifTrue:
- 		[self error: 'this method expects an absolute filename'].
- 	fullNameSize := (fullName := self fullName) size.
- 	fileNameSize := aFileName size.
- 	^(aFileName beginsWith: fullName)
- 		ifTrue: [(fileNameSize = fullNameSize
- 				or: [fileNameSize - 1 = fullNameSize
- 					and: [(aFileName at: fileNameSize) = self pathNameDelimiter]])
- 					ifTrue: [self class currentDirectoryNickname]
- 					ifFalse: [aFileName copyFrom: fullNameSize + 2 to: fileNameSize]]
- 		ifFalse: [aFileName]
- 
- 	"SourceFiles asArray collect: [:sf| FileDirectory default relativeNameIfAbsoluteFor: sf fullName]"
- 	"FileDirectory default relativeNameIfAbsoluteFor: FileDirectory default fullName" "should be dot"
- 	"FileDirectory default relativeNameIfAbsoluteFor: FileDirectory default fullName, FileDirectory default slash" "should also be dot"!

Item was removed:
- ----- Method: DosFileDirectory>>setPathName: (in category 'private') -----
- setPathName: pathString
- 	"Ensure pathString is absolute - relative directories aren't supported on all platforms."
- 
- 	(pathString isEmpty
- 		or: [pathString first = $\
- 			or: [pathString size >= 2 and: [pathString second = $: and: [pathString first isLetter]]]])
- 				ifTrue: [^ super setPathName: pathString].
- 
- 	self error: 'Fully qualified path expected'!

Item was removed:
- SourceFileArray subclass: #ExpandedSourceFileArray
- 	instanceVariableNames: 'files'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-System'!
- 
- !ExpandedSourceFileArray commentStamp: 'dtl 12/22/2009 23:09' prior: 0!
- This is a variation on StandardSourceFileArray that provides a larger maximum changes file size.
- 
- The available address space for source pointers in a traditional CompiledMethod is 16r1000000 through 16r4FFFFFF. StandardSourceFileArray maps positions in the sources file to address range 16r1000000 through 16r1FFFFFF and 16r3000000 through 16r3FFFFFF, and positions in the changes file to address range 16r2000000 through 16r2FFFFFF and 16r4000000 through 16r4FFFFFF. This permits a maximum file size of 16r2000000 (32MB) for both the sources file and the changes file. 
- 
- This implementation extends the source pointer address space using bit 25 of the source pointer to identify the external sources and changes files, with the remaining high order bits treated as address extension. This limits the number of external file references to two (the traditional sources and changes files). If additional external file references are needed in the future, some higher order bits in the source pointer address space should be allocated for that purpose.
- 
- The use of bit 25 of the source pointer for file references permits backward compatibility with StandardSourceFileArray, with essentially unlimited address space expansion for the sources and changes files.
- !

Item was removed:
- ----- Method: ExpandedSourceFileArray class>>new: (in category 'initialize-release') -----
- new: nFiles
- 	^self new initialize: nFiles.!

Item was removed:
- ----- Method: ExpandedSourceFileArray>>at: (in category 'accessing') -----
- at: index
- 	^files at: index!

Item was removed:
- ----- Method: ExpandedSourceFileArray>>at:put: (in category 'accessing') -----
- at: index put: aFile
- 	^files at: index put: aFile!

Item was removed:
- ----- Method: ExpandedSourceFileArray>>checkOKToAdd:at: (in category 'sourcePointer conversion') -----
- checkOKToAdd: size at: filePosition
- 	"No check is required"
- 
- 	^ self!

Item was removed:
- ----- Method: ExpandedSourceFileArray>>fileIndexFromSourcePointer: (in category 'sourcePointer conversion') -----
- fileIndexFromSourcePointer: anInteger
- 	"Return the index of the source file which contains the source chunk addressed by anInteger"
- 
- 	(anInteger bitAnd: 16r1000000) ~= 0
- 		ifTrue: [^1 "sources file"]
- 		ifFalse: [anInteger >= 16r1000000
- 			ifTrue: [^2 "changes file"]
- 			ifFalse: [^0 "compatibility with StandardSourceFileArray"]]!

Item was removed:
- ----- Method: ExpandedSourceFileArray>>filePositionFromSourcePointer: (in category 'sourcePointer conversion') -----
- filePositionFromSourcePointer: anInteger 
- 	"Return the position of the source chunk addressed by anInteger"
- 
- 	| hi lo |
- 	hi := anInteger // 33554432.
- 	lo := anInteger \\ 16777216.
- 	((anInteger bitAnd: 16777216) ~= 0
- 			or: [anInteger < 16777216 "compatibility with StandardSourceFileArray"])
- 		ifTrue: [^ hi * 16777216 + lo"sources file"]
- 		ifFalse: [^ hi - 1 * 16777216 + lo"changes file"]!

Item was removed:
- ----- Method: ExpandedSourceFileArray>>initialize (in category 'initialize-release') -----
- initialize
- 	files := Array new: 2.
- 	files at: 1 put: (SourceFiles at: 1).
- 	files at: 2 put: (SourceFiles at: 2)!

Item was removed:
- ----- Method: ExpandedSourceFileArray>>initialize: (in category 'initialize-release') -----
- initialize: nFiles
- 	files := Array new: nFiles!

Item was removed:
- ----- Method: ExpandedSourceFileArray>>size (in category 'accessing') -----
- size
- 	^files size!

Item was removed:
- ----- Method: ExpandedSourceFileArray>>sourcePointerFromFileIndex:andPosition: (in category 'sourcePointer conversion') -----
- sourcePointerFromFileIndex: index andPosition: position
- 	"Return a sourcePointer encoding the given file index and position"
- 
- 	| hi lo |
- 	(index = 1 or: [index = 2])
- 		ifFalse: [self error: 'invalid source file index'].
- 	position < 0 ifTrue: [self error: 'invalid source code pointer'].
- 	hi := position // 16r1000000 *2 + index.
- 	lo := position \\ 16r1000000.
- 	^ hi * 16r1000000 + lo
- !

Item was removed:
- Object subclass: #FileDirectory
- 	instanceVariableNames: 'pathName'
- 	classVariableNames: 'DefaultDirectory DirectoryClass StandardMIMEMappings'
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!
- 
- !FileDirectory commentStamp: '<historical>' prior: 0!
- A FileDirectory represents a folder or directory in the underlying platform's file system. It carries a fully-qualified path name for the directory it represents, and can enumerate the files and directories within that directory.
- 
- A FileDirectory can be thought of as a Dictionary whose keys are the local names of files in that directory, and whose values are directory "entries". Each entry is an array of five items:
- 
- 	<name> <creationTime> <modificationTime> <dirFlag> <fileSize>
- 
- The times are given in seconds, and can be converted to a time and date via Time>dateAndTimeFromSeconds:. See the comment in lookupEntry:... which provides primitive access to this information.
- !

Item was removed:
- ----- Method: FileDirectory class>>activeDirectoryClass (in category 'private') -----
- activeDirectoryClass
- 	"Return the concrete FileDirectory subclass for the platform on which we are currently running."
- 
- 	FileDirectory allSubclasses do: [:class |
- 		class isActiveDirectoryClass ifTrue: [^ class]].
- 
- 	"no responding subclass; use FileDirectory"
- 	^ FileDirectory
- !

Item was removed:
- ----- Method: FileDirectory class>>baseNameFor: (in category 'name utilities') -----
- baseNameFor: fileName
- 	"Return the given file name without its extension, if any. We have to remember that many (most?) OSs allow extension separators within directory names and so the leaf filename needs to be extracted, trimmed and rejoined. Yuck"
- 	"The test is 
- 		FileDirectory baseNameFor: ((FileDirectory default directoryNamed: 'foo.bar') fullNameFor:'blim.blam') 
- 		should end 'foo.bar/blim' (or as appropriate for your platform AND
- 		FileDirectory baseNameFor: ((FileDirectory default directoryNamed: 'foo.bar') fullNameFor:'blim')
- 		should be the same and NOT  'foo'
- 		Oh, and FileDirectory baseNameFor: 'foo.bar' should be 'foo' not '/foo' "
- 
- 	self splitName: fileName to: [:path : fn|
- 		| delim i leaf |
- 		delim := DirectoryClass extensionDelimiter.
- 		i := fn findLast: [:c | c = delim].
- 		leaf := i = 0
- 			ifTrue: [fn]
- 			ifFalse: [fn copyFrom: 1 to: i - 1].
- 		path isEmpty ifTrue:[^leaf].
- 		^path, self slash, leaf]
- !

Item was removed:
- ----- Method: FileDirectory class>>changeSuffix (in category 'name utilities') -----
- changeSuffix
- "if 'changes' is not suitable, override this message to return something that is ok"
- 	^'changes'!

Item was removed:
- ----- Method: FileDirectory class>>checkName:fixErrors: (in category 'name utilities') -----
- checkName: fileName fixErrors: flag
- 	"Check a string fileName for validity as a file name on the current default file system. Answer the original file name if it is valid. If the name is not valid (e.g., it is too long or contains illegal characters) and fixing is false, raise an error. If fixing is true, fix the name (usually by truncating and/or tranforming characters), and answer the corrected name. The default behavior is to truncate the name to 31 chars. Subclasses can do any kind of checking and correction appropriate to the underlying platform."
- 
- 	^ DefaultDirectory
- 		checkName: fileName
- 		fixErrors: flag
- !

Item was removed:
- ----- Method: FileDirectory class>>currentDirectoryNickname (in category 'platform specific') -----
- currentDirectoryNickname
- 	"Answer the nick-name for the current directory (e.g. '.' on Unix and Windows).
- 	 Answer the common default."
- 	^'.'!

Item was removed:
- ----- Method: FileDirectory class>>default (in category 'instance creation') -----
- default
- 	"Answer the default directory."
- 
- 	^ DefaultDirectory
- !

Item was removed:
- ----- Method: FileDirectory class>>deleteFilePath: (in category 'create/delete file') -----
- deleteFilePath: fullPathToAFile
- 	"Delete the file after finding its directory"
- 
- 	| dir |
- 	dir := self on: (self dirPathFor: fullPathToAFile).
- 	dir deleteFileNamed: (self localNameFor: fullPathToAFile).
- !

Item was removed:
- ----- Method: FileDirectory class>>dirPathFor: (in category 'name utilities') -----
- dirPathFor: fullName 
- 	"Return the directory part the given name."
- 	DirectoryClass
- 		splitName: fullName
- 		to: [:dirPath :localName | ^ dirPath]!

Item was removed:
- ----- Method: FileDirectory class>>directoryEntryFor: (in category 'name utilities') -----
- directoryEntryFor: filenameOrPath
- 	^self default directoryEntryFor: filenameOrPath!

Item was removed:
- ----- Method: FileDirectory class>>dot (in category 'platform specific') -----
- dot
- 	"Return a one-character string containing the filename extension delimiter for this platform (i.e., the local equivalent of 'dot')"
- 
- 	^ self extensionDelimiter asString
- !

Item was removed:
- ----- Method: FileDirectory class>>dropFilesAndDirectories: (in category 'dnd requests') -----
- dropFilesAndDirectories: numFiles
- 	"Answer a sequence of directories and/or streams for a drop event.
- 	 The collection may be empty."
- 	^(1 to: numFiles)
- 		collect:
- 			[:index |
- 			(self requestDropDirectory: index) ifNil:
- 				[FileStream requestDropStream: index]]
- 		thenSelect: [:directoryOrStreamOrNil| directoryOrStreamOrNil notNil]!

Item was removed:
- ----- Method: FileDirectory class>>extensionDelimiter (in category 'platform specific') -----
- extensionDelimiter
- 	"Return the character used to delimit filename extensions on this platform. Most platforms use the period (.) character."
- 
- 	^ $.
- !

Item was removed:
- ----- Method: FileDirectory class>>extensionFor: (in category 'name utilities') -----
- extensionFor: fileName
- 	"Return the extension of given file name, if any."
- 
- 	| delim i |
- 	delim := DirectoryClass extensionDelimiter.
- 	i := fileName findLast: [:c | c = delim].
- 	i = 0
- 		ifTrue: [^ '']
- 		ifFalse: [^ fileName copyFrom: i + 1 to: fileName size].
- !

Item was removed:
- ----- Method: FileDirectory class>>fileName:extension: (in category 'name utilities') -----
- fileName: fileName extension: fileExtension
- 	| extension |
- 	extension := FileDirectory dot , fileExtension.
- 	^(fileName endsWith: extension)
- 		ifTrue: [fileName]
- 		ifFalse: [fileName , extension].!

Item was removed:
- ----- Method: FileDirectory class>>fileReaderServicesForFile:suffix: (in category 'file reader services') -----
- fileReaderServicesForFile: fullName suffix: suffix
- 
- 	^ (self on: fullName) exists
- 		ifTrue: [self services]
- 		ifFalse: [#()].!

Item was removed:
- ----- Method: FileDirectory class>>forFileName: (in category 'instance creation') -----
- forFileName: aString
- 
- 	| path |
- 	path := self dirPathFor: aString.
- 	path isEmpty ifTrue: [^ self default].
- 	^ self on: path
- !

Item was removed:
- ----- Method: FileDirectory class>>imageSuffix (in category 'name utilities') -----
- imageSuffix
- "if 'image' is not suitable, override this message to return something that is ok"
- 	^'image'!

Item was removed:
- ----- Method: FileDirectory class>>initialize (in category 'class initialization') -----
- initialize
- 
- 	FileServices registerFileReader: self.!

Item was removed:
- ----- Method: FileDirectory class>>initializeStandardMIMETypes (in category 'class initialization') -----
- initializeStandardMIMETypes
- 	"FileDirectory initializeStandardMIMETypes"
- 	StandardMIMEMappings := Dictionary new.
- 	#(
- 		(gif		('image/gif'))
- 		(pdf	('application/pdf'))
- 		(aiff	('audio/aiff'))
- 		(bmp	('image/bmp'))
- 		(png	('image/png'))
- 		(swf	('application/x-shockwave-flash'))
- 		(htm	('text/html' 'text/plain'))
- 		(html	('text/html' 'text/plain'))
- 		(jpg	('image/jpeg'))
- 		(jpeg	('image/jpeg'))
- 		(mid	('audio/midi'))
- 		(midi	('audio/midi'))
- 		(mp3	('audio/mpeg'))
- 		(mpeg	('video/mpeg'))
- 		(mpg	('video/mpg'))
- 		(txt		('text/plain'))
- 		(text	('text/plain'))
- 		(mov	('video/quicktime'))
- 		(qt		('video/quicktime'))
- 		(tif		('image/tiff'))
- 		(tiff	('image/tiff'))
- 		(ttf		('application/x-truetypefont'))
- 		(wrl	('model/vrml'))
- 		(vrml	('model/vrml'))
- 		(wav	('audio/wav'))
- 	) do:[:spec|
- 		StandardMIMEMappings at: spec first asString put: spec last.
- 	].!

Item was removed:
- ----- Method: FileDirectory class>>isActiveDirectoryClass (in category 'private') -----
- isActiveDirectoryClass
- 	"Does this class claim to be that properly active subclass of FileDirectory for this platform?
- 	Default test is whether the primPathNameDelimiter matches the one for this class. Other tests are possible"
- 
- 	^self pathNameDelimiter = self primPathNameDelimiter
- !

Item was removed:
- ----- Method: FileDirectory class>>isCaseSensitive (in category 'platform specific') -----
- isCaseSensitive
- 	"Return true if file names are treated case sensitive"
- 	^true!

Item was removed:
- ----- Method: FileDirectory class>>isLegalFileName: (in category 'name utilities') -----
- isLegalFileName: fullName
- 	"Return true if the given string is a legal file name."
- 
- 	^ DefaultDirectory isLegalFileName: (self localNameFor: fullName)
- !

Item was removed:
- ----- Method: FileDirectory class>>localNameFor: (in category 'name utilities') -----
- localNameFor: fullName 
- 	"Return the local part the given name."
- 	DirectoryClass
- 		splitName: fullName
- 		to: [:dirPath :localName | ^ localName]!

Item was removed:
- ----- Method: FileDirectory class>>lookInUsualPlaces: (in category 'create/delete file') -----
- lookInUsualPlaces: fileName
- 	"Check the default directory, the imagePath, and the vmPath (and the vmPath's owner) for this file."
- 
- 	| vmp |
- 	(FileDirectory default fileExists: fileName)
- 		ifTrue: [^ FileDirectory default fileNamed: fileName].
- 
- 	((vmp := FileDirectory on: Smalltalk imagePath) fileExists: fileName)
- 		ifTrue: [^ vmp fileNamed: fileName].
- 
- 	((vmp := FileDirectory on: Smalltalk vmPath) fileExists: fileName)
- 		ifTrue: [^ vmp fileNamed: fileName].
- 
- 	((vmp := vmp containingDirectory) fileExists: fileName)
- 		ifTrue: [^ vmp fileNamed: fileName].
- 
- 	^ nil!

Item was removed:
- ----- Method: FileDirectory class>>makeAbsolute: (in category 'platform specific') -----
- makeAbsolute: path
- 	"Ensure that path looks like an absolute path"
- 	^path first = self pathNameDelimiter
- 		ifTrue: [ path ]
- 		ifFalse: [ self slash, path ]!

Item was removed:
- ----- Method: FileDirectory class>>makeRelative: (in category 'platform specific') -----
- makeRelative: path
- 	"Ensure that path looks like an relative path"
- 	^path first = self pathNameDelimiter
- 		ifTrue: [ path copyWithoutFirst ]
- 		ifFalse: [ path ]!

Item was removed:
- ----- Method: FileDirectory class>>maxFileNameLength (in category 'platform specific') -----
- maxFileNameLength
- 
- 	^ 31
- !

Item was removed:
- ----- Method: FileDirectory class>>on: (in category 'instance creation') -----
- on: pathString
- 	"Return a new file directory for the given path, of the appropriate FileDirectory subclass for the current OS platform."
- 
- 	| pathName |
- 	DirectoryClass ifNil: [self setDefaultDirectoryClass].
- 	"If path ends with a delimiter (: or /) then remove it"
- 	pathName := pathString.
- 	(pathName at: pathName size ifAbsent: nil) = self pathNameDelimiter ifTrue:
- 		[pathName := pathName allButLast].
- 	DirectoryClass parentDirectoryNickname ifNotNil:
- 		[:parentName|
- 		(pathName beginsWith: parentName) ifTrue:
- 			[pathName = parentName ifTrue:
- 				[^self default containingDirectory].
- 			 (pathName at: parentName size + 1 ifAbsent: nil) = self pathNameDelimiter ifTrue:
- 				[^self default containingDirectory on: (pathName allButFirst: parentName size + 1)]]].
- 	^DirectoryClass new setPathName: pathName!

Item was removed:
- ----- Method: FileDirectory class>>parentDirectoryNickname (in category 'platform specific') -----
- parentDirectoryNickname
- 	"Answer the nick-name for the parent directory (e.g. '..' on Unix and Windows).
- 	 Answer the common default."
- 	^'..'!

Item was removed:
- ----- Method: FileDirectory class>>pathNameDelimiter (in category 'platform specific') -----
- pathNameDelimiter
- "return the active directory class's directory seperator character"
- 	^ DirectoryClass pathNameDelimiter!

Item was removed:
- ----- Method: FileDirectory class>>primPathNameDelimiter (in category 'private') -----
- primPathNameDelimiter
- 	"Return the path delimiter for the underlying platform's file system."
- 
-  	<primitive: 'primitiveDirectoryDelimitor' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: FileDirectory class>>requestDropDirectory: (in category 'dnd requests') -----
- requestDropDirectory: dropIndex
- 
- 	^(FileStream primDropRequestFileName: dropIndex) ifNotNil:
- 		[:dropFileName| | potentialDirectory | 
- 		potentialDirectory := self on: dropFileName.
- 		potentialDirectory exists ifTrue: [potentialDirectory]]!

Item was removed:
- ----- Method: FileDirectory class>>root (in category 'instance creation') -----
- root
- 	"Answer the root directory."
- 
- 	^ self on: ''
- !

Item was removed:
- ----- Method: FileDirectory class>>services (in category 'file reader services') -----
- services
- 
- 	^ (self class selectors copyWithout: #services)
- 		select: [:symbol | symbol beginsWith: #service]
- 		thenCollect: [:selector | self perform: selector]!

Item was removed:
- ----- Method: FileDirectory class>>setDefaultDirectoryClass (in category 'system start up') -----
- setDefaultDirectoryClass
- 	"Initialize the default directory class to suit this platform. This method is called when the image starts up - it needs to be right at the front of the list of the startup sequence"
- 
- 	DirectoryClass := self activeDirectoryClass
- !

Item was removed:
- ----- Method: FileDirectory class>>shutDown (in category 'system start up') -----
- shutDown
- 
- 	Smalltalk closeSourceFiles.
- !

Item was removed:
- ----- Method: FileDirectory class>>slash (in category 'platform specific') -----
- slash
- 	^ self pathNameDelimiter asString!

Item was removed:
- ----- Method: FileDirectory class>>splitName:to: (in category 'name utilities') -----
- splitName: fullName to: pathAndNameBlock
- 	"Take the file name and convert it to the path name of a directory and a local file name within that directory. FileName must be of the form: <dirPath><delimiter><localName>, where <dirPath><delimiter> is optional. The <dirPath> part may contain delimiters."
- 
- 	| delimiter i dirName localName |
- 	delimiter := self pathNameDelimiter.
- 	(i := fullName findLast: [:c | c = delimiter]) = 0
- 		ifTrue:
- 			[dirName := String new.
- 			localName := fullName]
- 		ifFalse:
- 			[dirName := fullName copyFrom: 1 to: (i - 1 max: 1).
- 			localName := fullName copyFrom: i + 1 to: fullName size].
- 
- 	^ pathAndNameBlock value: dirName value: localName!

Item was removed:
- ----- Method: FileDirectory class>>startUp (in category 'system start up') -----
- startUp
- 
- 	self startUpDefaultDirectory.
- 	Smalltalk openSourceFiles.!

Item was removed:
- ----- Method: FileDirectory class>>startUpDefaultDirectory (in category 'system start up') -----
- startUpDefaultDirectory
- 	"Establish the platform-specific FileDirectory subclass. Do any platform-specific startup."
- 
- 	self setDefaultDirectoryClass.
- 	self setDefaultDirectory: (self dirPathFor: Smalltalk imageName).
- 
- 	Preferences startInUntrustedDirectory 
- 		ifTrue:[	"The SecurityManager may override the default directory to prevent unwanted write access etc."
- 				self setDefaultDirectory: SecurityManager default untrustedUserDirectory.
- 				"Make sure we have a place to go to"
- 				DefaultDirectory assureExistence].
- 	
- 	(Smalltalk classNamed: #DoItFirst) ifNotNil: [ :doit | doit perform: #reevaluateCwd ].!

Item was removed:
- ----- Method: FileDirectory class>>urlForFileNamed: (in category 'name utilities') -----
- urlForFileNamed: aFilename 
- 	"Create a URL for the given fully qualified file name"
- 	"FileDirectory urlForFileNamed: 
- 	'C:\Home\andreasr\Squeak\DSqueak3\DSqueak3:=1.1\DSqueak3.1.image' "
- 	| path localName |
- 	DirectoryClass
- 		splitName: aFilename
- 		to: [:p :n | 
- 			path := p.
- 			localName := n].
- 	^ localName asUrlRelativeTo: (self on: path) url asUrl!

Item was removed:
- ----- Method: FileDirectory>>/ (in category 'path access') -----
- / aString 
- 	"Answer a FileDirectory on a subdirectory named aString, of the receiver.  If there is already a file named aString in the receiver directory, answer its Entry."
- 	| dir |
- 	dir := FileDirectory on: (self fullNameFor: aString).
- 	^ dir exists
- 		ifTrue: [ dir ]
- 		ifFalse:
- 			[ self
- 				entryAt: aString
- 				ifAbsent: [ dir ] ]!

Item was removed:
- ----- Method: FileDirectory>>= (in category 'comparing') -----
- = aDirectory
- 	"Compare two FileDirectory instances."
- 	
- 	^(aDirectory isKindOf: FileDirectory) and: [
- 		(pathName asString 
- 			compare: aDirectory pathName asString 
- 			caseSensitive: (self isCaseSensitive or: [ aDirectory isCaseSensitive ])) = 2 ]!

Item was removed:
- ----- Method: FileDirectory>>acceptsUploads (in category 'testing') -----
- acceptsUploads
- 	^true!

Item was removed:
- ----- Method: FileDirectory>>assureAbsence (in category 'file directory') -----
- assureAbsence
- 	self exists ifTrue: [ self recursiveDelete ]!

Item was removed:
- ----- Method: FileDirectory>>assureExistence (in category 'file directory') -----
- assureExistence
- 	"Make sure the current directory exists. If necessary, create all parts in between"
- 	self exists ifFalse:
- 		[ self containingDirectory
- 			 assureExistence ;
- 			 createDirectory: self localName.
- 		self exists ifFalse: [ Error signal: self fullName, ' could not be created.  Permissions?' ] ]!

Item was removed:
- ----- Method: FileDirectory>>assureExistenceOfPath: (in category 'file directory') -----
- assureExistenceOfPath: lPath
- 	"Make sure the local directory exists. If necessary, create all parts in between"
- 	| localPath |
- 	localPath := lPath.
- 	localPath isEmpty ifTrue: [ ^self ]. "Assumed to exist"
- 	self assureExistence.
- 	(self directoryExists: localPath) ifTrue: [^ self]. "exists"
- 	self createDirectory: localPath!

Item was removed:
- ----- Method: FileDirectory>>checkName:fixErrors: (in category 'file name utilities') -----
- checkName: aFileName fixErrors: fixing
- 	"Check a string aFileName for validity as a file name. Answer the original file name if it is valid. If the name is not valid (e.g., it is too long or contains illegal characters) and fixing is false, raise an error. If fixing is true, fix the name (usually by truncating and/or tranforming characters), and answer the corrected name. The default behavior is just to truncate the name to the maximum length for this platform. Subclasses can do any kind of checking and correction appropriate for their platform."
- 
- 	| maxLength |
- 	aFileName size = 0 ifTrue: [self error: 'zero length file name'].
- 	maxLength := self class maxFileNameLength.
- 	aFileName size > maxLength ifTrue: [
- 		fixing
- 			ifTrue: [^ aFileName contractTo: maxLength]
- 			ifFalse: [self error: 'file name is too long']].
- 
- 	^ aFileName
- !

Item was removed:
- ----- Method: FileDirectory>>containingDirectory (in category 'enumeration') -----
- containingDirectory
- 	"Return the directory containing this directory."
- 
- 	^ FileDirectory on: (FileDirectory dirPathFor: pathName asSqueakPathName)
- !

Item was removed:
- ----- Method: FileDirectory>>copyFile:toFile: (in category 'file operations') -----
- copyFile: fileStream1 toFile: fileStream2 
- 	| buffer |
- 	fileStream1 position: 0.
- 	fileStream2 truncate.
- 	buffer := String new: 50000.
- 	[ fileStream1 atEnd ] whileFalse: [ fileStream2 nextPutAll: (fileStream1 nextInto: buffer) ].
- 	fileStream2 position < fileStream1 size ifTrue: [ self error: 'File copy failed' ]!

Item was removed:
- ----- Method: FileDirectory>>copyFileNamed:toFileNamed: (in category 'file operations') -----
- copyFileNamed: fileName1 toFileNamed: fileName2
- 	"Copy the contents of the existing file with the first name into a new file with the second name. Both files are assumed to be in this directory."
- 	"FileDirectory default copyFileNamed: 'todo.txt' toFileNamed: 'todocopy.txt'"
- 
- 	| file1 file2 |
- 	file1 := (self readOnlyFileNamed: fileName1) binary.
- 	file2 := (self newFileNamed: fileName2) binary.
- 	self copyFile: file1 toFile: file2.
- 	file1 close.
- 	file2 close.
- !

Item was removed:
- ----- Method: FileDirectory>>copyFileWithoutOverwriteConfirmationNamed:toFileNamed: (in category 'file operations') -----
- copyFileWithoutOverwriteConfirmationNamed: fileName1 toFileNamed: fileName2
- 	"Copy the contents of the existing file with the first name into a file with the second name (which may or may not exist). If the second file exists, force an overwrite without confirming.  Both files are assumed to be in this directory."
- 	"FileDirectory default copyFileWithoutOverwriteConfirmationNamed: 'todo.txt' toFileNamed: 'todocopy.txt'"
- 
- 	| file1 file2 |
- 	fileName1 = fileName2 ifTrue: [^ self].
- 	file1 := (self readOnlyFileNamed: fileName1) binary.
- 	file2 := (self forceNewFileNamed: fileName2) binary.
- 	self copyFile: file1 toFile: file2.
- 	file1 close.
- 	file2 close.!

Item was removed:
- ----- Method: FileDirectory>>copyHere: (in category 'file operations') -----
- copyHere: aDirectoryEntryFile 
- 	"Copy aDirectoryEntryFile, which represents a file, to the directory I represent."
- 	aDirectoryEntryFile readStream in: 
- 		[ : readStream | 
- 		[ self 
- 			putFile: readStream
- 			named: aDirectoryEntryFile name ] ensure: [ readStream close ] ]!

Item was removed:
- ----- Method: FileDirectory>>createDirectory: (in category 'file operations') -----
- createDirectory: localFileName
- 	"Create a directory with the given name in this directory. Fail if the name is bad or if a file or directory with that name already exists."
- 
-  	self primCreateDirectory: (self fullNameFor: localFileName) asVmPathName
- !

Item was removed:
- ----- Method: FileDirectory>>deleteDirectory: (in category 'file operations') -----
- deleteDirectory: localDirName
- 	"Delete the directory with the given name in this directory. Fail if the path is bad or if a directory by that name does not exist."
- 
-  	self primDeleteDirectory: (self fullNameFor: localDirName) asVmPathName.
- !

Item was removed:
- ----- Method: FileDirectory>>deleteFileNamed: (in category 'file operations') -----
- deleteFileNamed: localFileName
- 	"Delete the file with the given name in this directory."
- 
- 	self deleteFileNamed: localFileName ifAbsent: [].
- !

Item was removed:
- ----- Method: FileDirectory>>deleteFileNamed:ifAbsent: (in category 'file operations') -----
- deleteFileNamed: localFileName ifAbsent: failBlock
- 	"Delete the file of the given name if it exists, else evaluate failBlock.
- 	If the first deletion attempt fails do a GC to force finalization of any lost references. ar 3/21/98 17:53"
- 	| fullName |
- 	fullName := self fullNameFor: localFileName.
- 	(StandardFileStream 
- 		retryWithGC:[self primDeleteFileNamed: (self fullNameFor: localFileName) asVmPathName]
- 		until:[:result| result notNil]
- 		forFileNamed: fullName) == nil
- 			ifTrue: [^failBlock value].
- !

Item was removed:
- ----- Method: FileDirectory>>deleteLocalFiles (in category 'file operations') -----
- deleteLocalFiles
- 	"Delete the local files in this directory."
- 
- 	self fileNames do:[:fn| self deleteFileNamed: fn ifAbsent: [(CannotDeleteFileException new
- 			messageText: 'Could not delete the old version of file ' , (self fullNameFor: fn)) signal]]
- !

Item was removed:
- ----- Method: FileDirectory>>directoryContentsFor: (in category 'private') -----
- directoryContentsFor: fullPath
- 	"Return a collection of directory entries for the files and directories in the directory with the given path. See primLookupEntryIn:index: for further details."
- 	"FileDirectory default directoryContentsFor: ''"
- 
- 	^Array new: 200 streamContents: [:stream |
- 		self directoryContentsFor: fullPath do: [:ea | stream nextPut: ea]].!

Item was removed:
- ----- Method: FileDirectory>>directoryContentsFor:do: (in category 'private') -----
- directoryContentsFor: fullPath do: aBlock
- 	"Do aBlock for the files and directories in the directory with the given path. See primLookupEntryIn:index: for further details."
- 	"FileDirectory default directoryContentsFor: '' do: [ :each | Transcript show: each; cr ]"
- 
- 	| vmPath entryArray index |
- 	vmPath := fullPath asVmPathName.
- 	index := 1.
- 	entryArray := (self primLookupEntryIn: vmPath index: index) ifNil: [ ^self ].
- 	#badDirectoryPath == entryArray ifTrue: [
- 		^(InvalidDirectoryError pathName: fullPath) signal ].
- 	[
- 		aBlock value: (DirectoryEntry fromArray: entryArray directory: self) convertFromSystemName.
- 		entryArray := (self primLookupEntryIn: vmPath index: (index := index + 1)) ifNil: [ ^self ] ] repeat!

Item was removed:
- ----- Method: FileDirectory>>directoryEntries (in category 'enumeration') -----
- directoryEntries
- 	"Return a collection of full entries for the subdirectories of this directory."
- 	"FileDirectory default directoryEntries"
- 
- 	^Array streamContents: [ :stream |
- 		self entriesDo: [ :entry |
- 			entry isDirectory ifTrue: [
- 				stream nextPut: entry ]]]!

Item was removed:
- ----- Method: FileDirectory>>directoryEntry (in category 'enumeration') -----
- directoryEntry
- 	^self containingDirectory entryAt: self localName!

Item was removed:
- ----- Method: FileDirectory>>directoryEntryFor: (in category 'enumeration') -----
- directoryEntryFor: filenameOrPath
- 	"Answer the directory entry for the given file or path."
- 	^ DirectoryClass
- 		splitName: filenameOrPath
- 		to:
- 			[ : filePath : name | | filename directory |
- 			filename := name.
- 			directory := filePath isEmpty
- 				ifTrue: [ self ]
- 				ifFalse: [ FileDirectory on: filePath ].
- 			 directory
- 				entryAt: filename
- 				ifAbsent: [ nil ] ]!

Item was removed:
- ----- Method: FileDirectory>>directoryEntryForName: (in category 'private') -----
- directoryEntryForName: aFileName
- 
- 	"Return a single DirectoryEntry for the given (non-path) entry name,
- 	 or nil if the entry could not be found.
- 	 Raises InvalidDirectoryError if this directory's path does not identify a directory."
- 
- 	| entryArray sysPath sysName |
- 
- 	sysPath := pathName asVmPathName.
- 	sysName := aFileName asVmPathName.
- 
- 	"New linear-time primitive."
- 	entryArray := self primLookupEntryIn: sysPath name: sysName.
- 	entryArray == #primFailed ifFalse:[
- 		^ entryArray ifNotNil: [(DirectoryEntry fromArray: entryArray directory: self) convertFromSystemName]
- 	].
- 
- 	"(InvalidDirectoryError pathName: pathName) signal.
- 	^nil"
- 
- 	"If the new primitive fails, use the old slow method. 
- 	 (This fallback can be changed to signal InvalidDirectoryError once
- 	  VM's with FilePlugin #primitiveDirectoryEntry have been distributed everywhere;
- 	  the new primitive was introduced 6/13/2007."
- 
- 	self isCaseSensitive 
- 		ifTrue: [ self entriesDo: [ :entry | entry name = aFileName ifTrue: [ ^entry ] ] ] 
- 		ifFalse: [ self entriesDo: [ :entry | (entry name sameAs: aFileName) ifTrue: [ ^entry ] ] ].
- 	^nil!

Item was removed:
- ----- Method: FileDirectory>>directoryExists: (in category 'testing') -----
- directoryExists: filenameOrPath
- 	"Answer true if a directory of the given name exists. The given name may be either a full path name or a local directory within this directory."
- 	"FileDirectory default directoryExists: FileDirectory default pathName"
- 
- 	| fName dir |
- 	DirectoryClass
- 		splitName: filenameOrPath
- 		to: [:filePath :name |
- 			fName := name.
- 			dir := filePath isEmpty
- 					ifTrue: [self]
- 					ifFalse: [FileDirectory on: filePath]].
- 
- 	^dir exists
- 	  and: [(dir directoryEntryForName: fName)
- 			ifNotNil: [:e| e isDirectory]
- 			ifNil: [false]]!

Item was removed:
- ----- Method: FileDirectory>>directoryNamed: (in category 'enumeration') -----
- directoryNamed: localFileName
- 	"Return the subdirectory of this directory with the given name."
- 
- 	^ FileDirectory on: (self fullNameFor: localFileName)
- !

Item was removed:
- ----- Method: FileDirectory>>directoryNames (in category 'enumeration') -----
- directoryNames
- 	"Return a collection of names for the subdirectories of this directory."
- 	"FileDirectory default directoryNames"
- 
- 	^Array streamContents: [ :stream |
- 		self entriesDo: [ :entry |
- 			entry isDirectory ifTrue: [
- 				stream nextPut: entry name ] ] ]!

Item was removed:
- ----- Method: FileDirectory>>directoryNamesMatching: (in category 'file name utilities') -----
- directoryNamesMatching: pat
- 	"
- 	FileDirectory default directoryNamesMatching: '*'
- 	FileDirectory default directoryNamesMatching: '*_segs'
- 	"
- 	
- 	| directories directoryNames |
- 	directories := OrderedCollection new.
- 	directoryNames := self directoryNames.
- 	(pat findTokens: ';', String crlf) do:
- 		[:tok | 
- 		directories addAll: (directoryNames select: [:name | tok match: name])].
- 	^directories!

Item was removed:
- ----- Method: FileDirectory>>directoryObject (in category 'squeaklets') -----
- directoryObject
- 
- 	^self!

Item was removed:
- ----- Method: FileDirectory>>directoryTreeDo: (in category 'enumeration') -----
- directoryTreeDo: oneArgBlock 
- 	"For each file and directory in my tree, value oneArgBlock with an OrderedCollection of the path of DirectoryEntry's leading to the current node.  The first element in the collection will be the DirectoryEntryDirectory for myself, the last is the currentNode (a DirectoryEntry)."
- 	|myEntry|
- 	myEntry := OrderedCollection with: self directoryEntry.
- 	oneArgBlock value: myEntry.
- 	self 
- 		directoryTreeDo: oneArgBlock
- 		entries: myEntry!

Item was removed:
- ----- Method: FileDirectory>>directoryTreeDo:entries: (in category 'enumeration') -----
- directoryTreeDo: oneArgBlock entries: entriesCollection 
- 	"Value oneArgBlock with the path (an OrderedCollection of FileDirectory's) to each DirectoryEntry and the DirectoryEntry itself."
- 
- 	self entriesDo:  [ :entry | 
- 		entriesCollection addLast: entry.
- 		oneArgBlock value: entriesCollection.
- 		entry isDirectory ifTrue: [
- 			entry asFileDirectory
- 				directoryTreeDo: oneArgBlock
- 				entries: entriesCollection ].
- 		entriesCollection removeLast ]!

Item was removed:
- ----- Method: FileDirectory>>downloadUrl (in category 'squeaklets') -----
- downloadUrl
- 	^''!

Item was removed:
- ----- Method: FileDirectory>>entries (in category 'enumeration') -----
- entries
- 	"Return a collection of DirectoryEntry's for the files and directories in this directory.  See primLookupEntryIn:index: for further details."
- 	"FileDirectory default entries"
- 	^ self directoryContentsFor: pathName
- !

Item was removed:
- ----- Method: FileDirectory>>entriesDo: (in category 'enumeration') -----
- entriesDo: aBlock
- 	"Evaluate aBlock with DirectoryEntry's for the files and directories in this directory.  See primLookupEntryIn:index: for further details."
- 	
- 	^self directoryContentsFor: pathName do: aBlock
- !

Item was removed:
- ----- Method: FileDirectory>>entryAt: (in category 'file status') -----
- entryAt: fileName  
- 	"find the entry with local name fileName"
- 
- 	^self entryAt: fileName ifAbsent: [ self error: 'file not in directory: ', fileName ].!

Item was removed:
- ----- Method: FileDirectory>>entryAt:ifAbsent: (in category 'file status') -----
- entryAt: fileName ifAbsent: aBlock
- 	"Find the entry with local name fileName and answer it.
- 	 If not found, answer the result of evaluating aBlock."
- 
- 	self exists ifFalse: [^aBlock value].
- 
- 	^(self directoryEntryForName: fileName) ifNil: [ aBlock value ]
- !

Item was removed:
- ----- Method: FileDirectory>>exists (in category 'testing') -----
- exists
- "Answer whether the directory exists"
- 
- 	| result |
- 	result := self primLookupEntryIn: pathName asVmPathName index: 1.
- 	^ result ~= #badDirectoryPath
- !

Item was removed:
- ----- Method: FileDirectory>>fileAndDirectoryNames (in category 'enumeration') -----
- fileAndDirectoryNames
- 	"FileDirectory default fileAndDirectoryNames"
- 	
- 	^Array streamContents: [ :stream |
- 		self entriesDo: [ :entry |
- 			stream nextPut: entry name ] ]!

Item was removed:
- ----- Method: FileDirectory>>fileEntries (in category 'enumeration') -----
- fileEntries
- 	"Return a collection of the full entries for the files (but not directories) in this directory."
- 	"FileDirectory default fileEntries"
- 
- 	^Array streamContents: [ :stream |
- 		self entriesDo: [ :entry |
- 			entry isDirectory ifFalse: [
- 				stream nextPut: entry ]]]!

Item was removed:
- ----- Method: FileDirectory>>fileExists: (in category 'testing') -----
- fileExists: filenameOrPath
- 	"Answer true if a file of the given name exists. The given name may be either a full path name or a local file within this directory."
- 	"FileDirectory default fileExists: Smalltalk sourcesName"
- 
- 	| fName dir |
- 	DirectoryClass
- 		splitName: filenameOrPath
- 		to: [:filePath :name |
- 			fName := name.
- 			dir := filePath isEmpty
- 					ifTrue: [self]
- 					ifFalse: [FileDirectory on: filePath]].
- 	
- 	^(dir directoryEntryForName: fName)
- 		ifNotNil: [:e| e isDirectory not]
- 		ifNil: [false]
- 		!

Item was removed:
- ----- Method: FileDirectory>>fileNamed: (in category 'file stream creation') -----
- fileNamed: localFileName
- 	"Open the file with the given name in this directory for writing."
- 
- 	^ FileStream concreteStream fileNamed: (self fullNameFor: localFileName)
- !

Item was removed:
- ----- Method: FileDirectory>>fileNamed:do: (in category 'file stream creation') -----
- fileNamed: localFileName do: aBlock
- 	"Open the file with the given name in this directory for writing and pass it as argument to aBlock."
- 
- 	^ FileStream concreteStream fileNamed: (self fullNameFor: localFileName) do: aBlock
- !

Item was removed:
- ----- Method: FileDirectory>>fileNames (in category 'enumeration') -----
- fileNames
- 	"Return a collection of names for the files (but not directories) in this directory."
- 	"FileDirectory default fileNames"
- 
- 	^Array streamContents: [ :stream |
- 		self entriesDo: [ :entry |
- 			entry isDirectory ifFalse: [
- 				stream nextPut: entry name ] ] ]!

Item was removed:
- ----- Method: FileDirectory>>fileNamesMatching: (in category 'file name utilities') -----
- fileNamesMatching: pat
- 	"
- 	FileDirectory default fileNamesMatching: '*'
- 	FileDirectory default fileNamesMatching: '*.image;*.changes'
- 	"
- 	
- 	| files fileNames |
- 	files := OrderedCollection new.
- 	fileNames := self fileNames.
- 	(pat findTokens: ';', String crlf) do:
- 		[:tok | 
- 		files addAll: (fileNames select: [:name | tok match: name])].
- 	^files!

Item was removed:
- ----- Method: FileDirectory>>fileOrDirectoryExists: (in category 'file operations') -----
- fileOrDirectoryExists: filenameOrPath
- 	"Answer true if either a file or a directory file of the given name exists. The given name may be either a full path name or a local name within this directory."
- 	"FileDirectory default fileOrDirectoryExists: Smalltalk sourcesName"
- 
- 	| fName dir |
- 	DirectoryClass splitName: filenameOrPath to:
- 		[:filePath :name |
- 			fName := name.
- 			filePath isEmpty
- 				ifTrue: [dir := self]
- 				ifFalse: [dir := FileDirectory on: filePath]].
- 
- 	^ (dir includesKey: fName) or: [ fName = '' and:[ dir entries size > 1]]!

Item was removed:
- ----- Method: FileDirectory>>filesContaining:caseSensitive: (in category 'searching') -----
- filesContaining: searchString caseSensitive: aBoolean
- 	| aList |
- 	"Search the contents of all files in the receiver and its subdirectories for the search string.  Return a list of paths found.  Make the search case sensitive if aBoolean is true."
- 
- 	aList := OrderedCollection new.
- 	self withAllFilesDo: [:stream |
- 			(stream contentsOfEntireFile includesSubstring: searchString caseSensitive: aBoolean)
- 				ifTrue:	[aList add: stream name]]
- 		andDirectoriesDo: [:d | d pathName].
- 	^ aList
- 
- "FileDirectory default filesContaining: 'includesSubstring:'  caseSensitive: true"!

Item was removed:
- ----- Method: FileDirectory>>forceNewFileNamed: (in category 'file stream creation') -----
- forceNewFileNamed: localFileName
- 	"Open the file with the given name in this directory for writing.  If it already exists, delete it first without asking."
- 
- 	^ FileStream concreteStream forceNewFileNamed: (self fullNameFor: localFileName)
- !

Item was removed:
- ----- Method: FileDirectory>>forceNewFileNamed:do: (in category 'file stream creation') -----
- forceNewFileNamed: localFileName do: aBlock
- 	"Open the file with the given name in this directory for writing.  If it already exists, delete it first without asking and pass it as argument to aBlock."
- 
- 	^ FileStream concreteStream forceNewFileNamed: (self fullNameFor: localFileName) do: aBlock
- !

Item was removed:
- ----- Method: FileDirectory>>fullName (in category 'enumeration') -----
- fullName
- 	"Return the full name of this directory."
- 
- 	^pathName asSqueakPathName
- !

Item was removed:
- ----- Method: FileDirectory>>fullNameFor: (in category 'file name utilities') -----
- fullNameFor: fileName
- 	"Return a corrected, fully-qualified name for the given file name. If the given name is already a full path (i.e., it contains a delimiter character), assume it is already a fully-qualified name. Otherwise, prefix it with the path to this directory. In either case, correct the local part of the file name."
- 	"Details: Note that path relative to a directory, such as '../../foo' are disallowed by this algorithm.  Also note that this method is tolerent of a nil argument -- is simply returns nil in this case."
- 
- 	| correctedLocalName prefix |
- 	fileName ifNil: [^ nil].
- 	DirectoryClass splitName: fileName to:
- 		[:filePath :localName |
- 			correctedLocalName := localName isEmpty 
- 				ifFalse: [self checkName: localName fixErrors: true]
- 				ifTrue: [localName].
- 			prefix := self fullPathFor: filePath].
- 	prefix isEmpty
- 		ifTrue: [^correctedLocalName].
- 	prefix last = self pathNameDelimiter
- 		ifTrue:[^ prefix, correctedLocalName]
- 		ifFalse:[^ prefix, self slash, correctedLocalName]!

Item was removed:
- ----- Method: FileDirectory>>fullNamesOfAllFilesInSubtree (in category 'enumeration') -----
- fullNamesOfAllFilesInSubtree
- 	"Answer a collection containing the full names of all the files in the subtree of the file system whose root is this directory."
- 
- 	| result todo dir |
- 	result := OrderedCollection new: 100.
- 	todo := OrderedCollection with: self.
- 	[todo size > 0] whileTrue: [
- 		dir := todo removeFirst.
- 		dir fileNames do: [:n | result add: (dir fullNameFor: n)].
- 		dir directoryNames do: [:n | todo add: (dir directoryNamed: n)]].
- 	^ result asArray
- !

Item was removed:
- ----- Method: FileDirectory>>fullPathFor: (in category 'path access') -----
- fullPathFor: path
- 	^path isEmpty ifTrue:[pathName asSqueakPathName] ifFalse:[path]!

Item was removed:
- ----- Method: FileDirectory>>getMacFileTypeAndCreator: (in category 'file operations') -----
- getMacFileTypeAndCreator: fileName 
- 	| results typeString creatorString |
- 	"get the Macintosh file type and creator info for the file with the given name. Fails if the file does not exist or if the type and creator type arguments are not strings of length 4. Does nothing on other platforms (where the underlying primitive is a noop)."
- 	"FileDirectory default getMacFileNamed: 'foo'"
- 
- 	typeString := ByteArray new: 4 withAll: ($? asInteger).
- 	creatorString := ByteArray new: 4 withAll: ($? asInteger).
- 	[self primGetMacFileNamed: (self fullNameFor: fileName) asVmPathName
- 		type: typeString
- 		creator: creatorString.] ensure: 
- 		[typeString := typeString asString. 
- 		creatorString := creatorString asString].
- 	results := Array with: typeString convertFromSystemString with: creatorString convertFromSystemString.
- 	^results
- !

Item was removed:
- ----- Method: FileDirectory>>hasEntries (in category 'private') -----
- hasEntries
- 	"Return true if this directory has entries or false."
- 	"FileDirectory default hasEntries"
- 
- 	^(self primLookupEntryIn: pathName asVmPathName index: 1) ~~ nil!

Item was removed:
- ----- Method: FileDirectory>>hasFiles (in category 'testing') -----
- hasFiles
- 	"Return true if we find an entry that is a file, false otherwise"
- 	"FileDirectory default hasFiles"
- 
- 	self entriesDo: [ :entry |entry isDirectory ifFalse: [^true] ] .
- 	^false!

Item was removed:
- ----- Method: FileDirectory>>hasSubDirectories (in category 'testing') -----
- hasSubDirectories
- 	"Return true if we find an entry that is a directory, false otherwise"
- 	"FileDirectory default hasSubDirectories"
- 
- 	self entriesDo: [ :entry |entry isDirectory ifTrue: [^true] ] .
- 	^false!

Item was removed:
- ----- Method: FileDirectory>>hash (in category 'comparing') -----
- hash
- 	"Hash is reimplemented because #= is reimplemented"
- 	^pathName asString asLowercase hash!

Item was removed:
- ----- Method: FileDirectory>>includesKey: (in category 'testing') -----
- includesKey: localName
- 	"Answer true if this directory includes a file or directory of the given name. Note that the name should be a local file name, in contrast with fileExists:, which takes either local or full-qualified file names."
- 	"(FileDirectory on: Smalltalk vmPath) includesKey: 'SqueakV2.sources'"
- 	^(self directoryEntryForName: localName) notNil!

Item was removed:
- ----- Method: FileDirectory>>isAFileNamed: (in category 'testing') -----
- isAFileNamed: fName
- 	^FileStream isAFileNamed: (self fullNameFor: fName)!

Item was removed:
- ----- Method: FileDirectory>>isCaseSensitive (in category 'testing') -----
- isCaseSensitive
- 	"Return true if file names are treated case sensitive"
- 	^self class isCaseSensitive!

Item was removed:
- ----- Method: FileDirectory>>isLegalFileName: (in category 'file name utilities') -----
- isLegalFileName: aString 
- 	"Answer true if the given string is a legal file name."
- 
- 	^ (self checkName: aString fixErrors: true) = aString
- !

Item was removed:
- ----- Method: FileDirectory>>isRemoteDirectory (in category 'testing') -----
- isRemoteDirectory
- 	"answer whatever the receiver is a remote directory"
- 	^ false!

Item was removed:
- ----- Method: FileDirectory>>isTypeFile (in category 'file name utilities') -----
- isTypeFile
- 	^true!

Item was removed:
- ----- Method: FileDirectory>>keysDo: (in category 'enumeration') -----
- keysDo: nameBlock
- 	"Evaluate the given block for each file or directory name in this directory."
- 
- 	^ self fileAndDirectoryNames do: nameBlock
- !

Item was removed:
- ----- Method: FileDirectory>>lastNameFor:extension: (in category 'file name utilities') -----
- lastNameFor: baseFileName extension: extension
- 	"Assumes a file name includes a version number encoded as '.' followed by digits 
- 	preceding the file extension.  Increment the version number and answer the new file name.
- 	If a version number is not found, set the version to 1 and answer a new file name"
- 
- 	| files splits |
- 
- 	files := self fileNamesMatching: (baseFileName,'*', self class dot, extension).
- 	splits := files 
- 			collect: [:file | self splitNameVersionExtensionFor: file]
- 			thenSelect: [:split | (split at: 1) = baseFileName].
- 	splits isEmpty ifTrue: [ ^nil ].
- 	^(baseFileName, '.', ((splits detectMax: [ :each | each at: 2]) at: 2) asString, self class dot, extension) asFileName!

Item was removed:
- ----- Method: FileDirectory>>localName (in category 'enumeration') -----
- localName
- 	"Return the local name of this directory."
- 
- 	^FileDirectory localNameFor: pathName asSqueakPathName!

Item was removed:
- ----- Method: FileDirectory>>localNameFor: (in category 'file directory') -----
- localNameFor: fullName
- 	"Return the local part the given name."
- 
- 	^self class localNameFor: fullName!

Item was removed:
- ----- Method: FileDirectory>>matchingEntries: (in category 'enumeration') -----
- matchingEntries: criteria
- 	"Ignore the filter criteria for now"
- 	^self entries!

Item was removed:
- ----- Method: FileDirectory>>mimeTypes (in category 'path access') -----
- mimeTypes
- 
- 	^ #('text/directory')!

Item was removed:
- ----- Method: FileDirectory>>mimeTypesFor: (in category 'file operations') -----
- mimeTypesFor: fileName
- 	"Return a list of MIME types applicable to the receiver. This default implementation uses the file name extension to figure out what we're looking at but specific subclasses may use other means of figuring out what the type of some file is. Some systems like the macintosh use meta data on the file to indicate data type"
- 
- 	| idx ext dot |
- 	ext := ''.
- 	dot := self class extensionDelimiter.
- 	idx := fileName findLast: [:ch| ch = dot].
- 	idx = 0 ifFalse: [ext := fileName copyFrom: idx+1 to: fileName size].
- 	^ StandardMIMEMappings at: ext asLowercase ifAbsent: [nil]!

Item was removed:
- ----- Method: FileDirectory>>name (in category 'path access') -----
- name
- 	"Compatibility with StandardFileStream >> #name to be used, for example, for drop event handling."
- 	
- 	^ self fullName!

Item was removed:
- ----- Method: FileDirectory>>newFileNamed: (in category 'file stream creation') -----
- newFileNamed: localFileName
- 	"Create a new file with the given name in this directory."
- 
- 	^ FileStream concreteStream newFileNamed: (self fullNameFor: localFileName)
- !

Item was removed:
- ----- Method: FileDirectory>>newFileNamed:do: (in category 'file stream creation') -----
- newFileNamed: localFileName do: aBlock
- 	"Create a new file with the given name in this directory and pass it as argument to aBlock."
- 
- 	^ FileStream concreteStream newFileNamed: (self fullNameFor: localFileName) do: aBlock
- !

Item was removed:
- ----- Method: FileDirectory>>nextNameFor:extension: (in category 'file name utilities') -----
- nextNameFor: baseFileName extension: extension
- 	"Assumes a file name includes a version number encoded as '.' followed by digits 
- 	preceding the file extension.  Increment the version number and answer the new file name.
- 	If a version number is not found, set the version to 1 and answer a new file name"
- 
- 	| files splits version |
- 
- 	files := self fileNamesMatching: (baseFileName,'*', self class dot, extension).
- 	splits := files 
- 			collect: [:file | self splitNameVersionExtensionFor: file]
- 			thenSelect:
- 					[:split |
- 					 self isCaseSensitive 
- 						ifTrue:[(split at: 1) = baseFileName]
- 						ifFalse:[(split at: 1) match: baseFileName]].
- 	version := splits isEmpty 
- 				ifTrue: [1]
- 				ifFalse: [((splits detectMax: [ :each | each at: 2 ]) at: 2) + 1].
- 	^ (baseFileName, '.', version asString, self class dot, extension) asFileName!

Item was removed:
- ----- Method: FileDirectory>>oldFileNamed: (in category 'file stream creation') -----
- oldFileNamed: localFileName
- 	"Open the existing file with the given name in this directory."
- 
- 	^ FileStream concreteStream oldFileNamed: (self fullNameFor: localFileName)
- !

Item was removed:
- ----- Method: FileDirectory>>oldFileNamed:do: (in category 'file stream creation') -----
- oldFileNamed: localFileName do: aBlock
- 	"Open the existing file with the given name in this directory and pass it as argument to aBlock."
- 
- 	^ FileStream concreteStream oldFileNamed: (self fullNameFor: localFileName) do: aBlock
- !

Item was removed:
- ----- Method: FileDirectory>>oldFileOrNoneNamed: (in category 'file stream creation') -----
- oldFileOrNoneNamed: localFileName
- 	"If the file exists, answer a read-only FileStream on it. If it doesn't, answer nil."
- 
- 	^ FileStream concreteStream oldFileOrNoneNamed: (self fullNameFor: localFileName)
- !

Item was removed:
- ----- Method: FileDirectory>>on: (in category 'path access') -----
- on: path
- 	"Answer another instance"
- 
- 	^self class on: (self fullPathFor: path)!

Item was removed:
- ----- Method: FileDirectory>>pathFromUrl: (in category 'path access') -----
- pathFromUrl: aFileUrl
- 	
- 	^String streamContents: [ :s | | first |
- 		first := false.
- 		aFileUrl path do: [ :p |
- 			first ifTrue: [ s nextPut: self pathNameDelimiter ].
- 			first := true.
- 			s nextPutAll: p ] ].!

Item was removed:
- ----- Method: FileDirectory>>pathName (in category 'path access') -----
- pathName
- 	"Return the path from the root of the file system to this directory."
- 
- 	^ pathName asSqueakPathName.
- 
- !

Item was removed:
- ----- Method: FileDirectory>>pathNameDelimiter (in category 'path access') -----
- pathNameDelimiter
- 	"Return the delimiter character for this kind of directory. This depends on the current platform."
- 
- 	^ self class pathNameDelimiter
- !

Item was removed:
- ----- Method: FileDirectory>>pathParts (in category 'path access') -----
- pathParts
- 	"Return the path from the root of the file system to this directory as an array of directory names."
- 
- 	^ pathName asSqueakPathName findTokens: self pathNameDelimiter asString!

Item was removed:
- ----- Method: FileDirectory>>primCreateDirectory: (in category 'private') -----
- primCreateDirectory: fullPath
- 	"Create a directory named by the given path. Fail if the path is bad or if a file or directory by that name already exists."
- 
-  	<primitive: 'primitiveDirectoryCreate' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: FileDirectory>>primDeleteDirectory: (in category 'private') -----
- primDeleteDirectory: fullPath
- 	"Delete the directory named by the given path. Fail if the path is bad or if a directory by that name does not exist."
- 
-  	<primitive: 'primitiveDirectoryDelete' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: FileDirectory>>primDeleteFileNamed: (in category 'private') -----
- primDeleteFileNamed: aFileName
- 	"Delete the file of the given name. Return self if the primitive succeeds, nil otherwise."
- 
- 	<primitive: 'primitiveFileDelete' module: 'FilePlugin'>
- 	^ nil
- !

Item was removed:
- ----- Method: FileDirectory>>primGetMacFileNamed:type:creator: (in category 'private') -----
- primGetMacFileNamed: fileName type: typeString creator: creatorString
- 	"Get the Macintosh file type and creator info for the file with the given name. Fails if the file does not exist or if the type and creator type arguments are not strings of length 4. This primitive is Mac specific; it is a noop on other platforms."
- 
-  	<primitive: 'primitiveDirectoryGetMacTypeAndCreator' module: 'FilePlugin'>
- 
- !

Item was removed:
- ----- Method: FileDirectory>>primLookupEntryIn:index: (in category 'private') -----
- primLookupEntryIn: fullPath index: index
- 	"Look up the index-th entry of the directory with the given fully-qualified path (i.e., starting from the root of the file hierarchy) and return an array containing:
- 
- 	<name> <creationTime> <modificationTime> <dirFlag> <fileSize>
- 
- 	The empty string enumerates the top-level files or drives. (For example, on Unix, the empty path enumerates the contents of '/'. On Macs and PCs, it enumerates the mounted volumes/drives.)
- 
- 	The creation and modification times are in seconds since the start of the Smalltalk time epoch. DirFlag is true if the entry is a directory. FileSize the file size in bytes or zero for directories. The primitive returns nil when index is past the end of the directory. It fails if the given path is bad."
- 
-  	<primitive: 'primitiveDirectoryLookup' module: 'FilePlugin'>
- 	^ #badDirectoryPath
- 
- !

Item was removed:
- ----- Method: FileDirectory>>primLookupEntryIn:name: (in category 'private') -----
- primLookupEntryIn: fullPath name: fName
- 
- 	"Look up <fName> (a simple file name) in the directory identified by <fullPath>
-  	 and return an array containing:
- 
- 	<fName> <creationTime> <modificationTime> <dirFlag> <fileSize>
- 
- 	On Unix, the empty path denotes '/'. 
-       On Macs and PCs, it is the container of the system volumes.)
- 
- 	The creation and modification times are in seconds since the start of the Smalltalk time epoch. DirFlag is true if the entry is a directory. FileSize the file size in bytes or zero for directories. The primitive returns nil when index is past the end of the directory. It fails if the given path is bad."
- 
-  	<primitive: 'primitiveDirectoryEntry' module: 'FilePlugin'>
- 
- 	^ #primFailed		"to distinguish from nil"
- 
- !

Item was removed:
- ----- Method: FileDirectory>>primRename:to: (in category 'private') -----
- primRename: oldFileFullName to: newFileFullName 
- 	"Rename the file of the given name to the new name. Fail if there is no file of the old name or if there is an existing file with the new name.
- 	Changed to return nil instead of failing ar 3/21/98 18:04"
- 
- 	<primitive: 'primitiveFileRename' module: 'FilePlugin'>
- 	^nil!

Item was removed:
- ----- Method: FileDirectory>>primSetMacFileNamed:type:creator: (in category 'private') -----
- primSetMacFileNamed: fileName type: typeString creator: creatorString
- 	"Set the Macintosh file type and creator info for the file with the given name. Fails if the file does not exist or if the type and creator type arguments are not strings of length 4. This primitive is Mac specific; it is a noop on other platforms."
- 
-  	<primitive: 'primitiveDirectorySetMacTypeAndCreator' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: FileDirectory>>printOn: (in category 'printing') -----
- printOn: aStream 
- 	"Refer to the comment in Object|printOn:."
- 
- 	aStream nextPutAll: self class name.
- 	aStream nextPutAll: ' on '.
- 	pathName asSqueakPathName printOn: aStream.
- !

Item was removed:
- ----- Method: FileDirectory>>putFile:named: (in category 'file operations') -----
- putFile: file1 named: destinationFileName
- 	"Copy the contents of the existing fileStream into the file destinationFileName in this directory.  fileStream can be anywhere in the fileSystem."
- 
- 	| file2 |
- 	file1 binary.
- 	(file2 := self newFileNamed: destinationFileName) ifNil: [^ false].
- 	file2 binary.
- 	self copyFile: file1 toFile: file2.
- 	file1 close.
- 	file2 close.
- 	^ true
- !

Item was removed:
- ----- Method: FileDirectory>>putFile:named:retry: (in category 'file operations') -----
- putFile: file1 named: destinationFileName retry: aBool
- 	"Copy the contents of the existing fileStream into the file destinationFileName in this directory.  fileStream can be anywhere in the fileSystem.  No retrying for local file systems."
- 
- 	^ self putFile: file1 named: destinationFileName
- !

Item was removed:
- ----- Method: FileDirectory>>readOnlyFileNamed: (in category 'file stream creation') -----
- readOnlyFileNamed: localFileName
- 	"Open the existing file with the given name in this directory for read-only access."
- 
- 	^ FileStream concreteStream readOnlyFileNamed: (self fullNameFor: localFileName)
- !

Item was removed:
- ----- Method: FileDirectory>>readOnlyFileNamed:do: (in category 'file stream creation') -----
- readOnlyFileNamed: localFileName do: aBlock
- 	"Open the existing file with the given name in this directory for read-only access and pass it as argument to aBlock."
- 
- 	^ FileStream concreteStream readOnlyFileNamed: (self fullNameFor: localFileName) do: aBlock
- !

Item was removed:
- ----- Method: FileDirectory>>realUrl (in category 'file name utilities') -----
- realUrl
- 	"Senders expect url without trailing slash - #url returns slash"
- 	| url |
- 	url := self url.
- 	url last = $/ ifTrue:[^url copyFrom: 1 to: url size-1].
- 	^url!

Item was removed:
- ----- Method: FileDirectory>>recursiveDelete (in category 'file operations') -----
- recursiveDelete
- 	"Delete the this directory, recursing down its tree."
- 	self directoryNames
- 		do: [:dn | (self directoryNamed: dn) recursiveDelete].
- 	self deleteLocalFiles.
- 	"should really be some exception handling for directory deletion, but no 
- 	support for it yet"
- 	self containingDirectory deleteDirectory: self localName!

Item was removed:
- ----- Method: FileDirectory>>relativeNameFor: (in category 'file name utilities') -----
- relativeNameFor: aFileName
- 	"Return the full name for aFileName, assuming that aFileName is a name relative to me."
- 	aFileName isEmpty ifTrue: [ ^pathName asSqueakPathName].
- 	^aFileName first = self pathNameDelimiter
- 		ifTrue: [ pathName asSqueakPathName, aFileName ]
- 		ifFalse: [ pathName asSqueakPathName, self slash, aFileName ]
- !

Item was removed:
- ----- Method: FileDirectory>>relativeNameIfAbsoluteFor: (in category 'file name utilities') -----
- relativeNameIfAbsoluteFor: aFileName
- 	"Answer either the relative name for aFileName, if aFileName names a file in me or
- 	 subdirectories, or aFileName's absolute path if it isn't in me or subdirectories.
- 	 P.S. Ths is what I'd expect relativeNameFor: to do, but it is taken and means
- 	 exactly the opposite, i.e. the absolute path for a relative name."
- 	| fullNameSize fullName fileNameSize |
- 	(aFileName isEmpty or: [aFileName first ~= self pathNameDelimiter]) ifTrue:
- 		[self error: 'this method expects an absolute filename'].
- 	fullNameSize := (fullName := self fullName) size.
- 	fileNameSize := aFileName size.
- 	^(aFileName beginsWith: fullName)
- 		ifTrue: [(fileNameSize = fullNameSize
- 				or: [fileNameSize - 1 = fullNameSize
- 					and: [(aFileName at: fileNameSize) = self pathNameDelimiter]])
- 					ifTrue: [self class currentDirectoryNickname]
- 					ifFalse: [aFileName copyFrom: fullNameSize + 2 to: fileNameSize]]
- 		ifFalse: [aFileName]
- 
- 	"SourceFiles asArray collect: [:sf| FileDirectory default relativeNameIfAbsoluteFor: sf fullName]"
- 	"FileDirectory default relativeNameIfAbsoluteFor: FileDirectory default fullName" "should be dot"
- 	"FileDirectory default relativeNameIfAbsoluteFor: FileDirectory default fullName, FileDirectory default slash" "should also be dot"!

Item was removed:
- ----- Method: FileDirectory>>rename:toBe: (in category 'file operations') -----
- rename: oldFileName toBe: newFileName 
- 	"Rename the file of the given name to the new name. Fail if there is no file of the old name or if there is an existing file with the new name."
- 	"Modified for retry after GC ar 3/21/98 18:09"
- 	| replaceIt oldName newName |
- 	oldName := self fullNameFor: oldFileName.
- 	newName := self fullNameFor: newFileName.
- 	((self fileExists: oldFileName) or: [ (self directoryExists: oldFileName) ]) ifFalse: [ ^ self error: 'Attempt to rename a non-existent file or directory.' ].
- 	(self fileExists: newFileName) ifTrue:
- 		[replaceIt := (ReplaceExistingFileException fileName: newFileName) signal.
- 		replaceIt ifTrue: [ self deleteFileNamed: newFileName ]	ifFalse: [ ^ self ]].
- 	(self directoryExists: newFileName) ifTrue: [ FileExistsException signal: newFileName, ' already exists.' ].
- 	(StandardFileStream
- 		retryWithGC:
- 			[ self
- 				primRename: oldName asVmPathName
- 				to: newName asVmPathName ]
- 		until: [ : result | result notNil ]
- 		forFileNamed: oldName) ~~ nil ifTrue: [ ^ self ].
- 	^ self error: 'Failed to rename file'!

Item was removed:
- ----- Method: FileDirectory>>setMacFileNamed:type:creator: (in category 'file operations') -----
- setMacFileNamed: fileName type: typeString creator: creatorString
- 	"Set the Macintosh file type and creator info for the file with the given name. Fails if the file does not exist or if the type and creator type arguments are not strings of length 4. Does nothing on other platforms (where the underlying primitive is a noop)."
- 	"FileDirectory default setMacFileNamed: 'foo' type: 'TEXT' creator: 'ttxt'"
- 
-  	self primSetMacFileNamed: (self fullNameFor: fileName) asVmPathName
- 		type: typeString convertToSystemString
- 		creator: creatorString convertToSystemString.
- !

Item was removed:
- ----- Method: FileDirectory>>setPathName: (in category 'private') -----
- setPathName: pathString
- 
- 	pathName := FilePath pathName: pathString.
- !

Item was removed:
- ----- Method: FileDirectory>>slash (in category 'path access') -----
- slash
- 	^self class slash!

Item was removed:
- ----- Method: FileDirectory>>sleep (in category 'file directory') -----
- sleep
- 	"Leave the FileList window.  Do nothing.  Disk directories do not have to be shut down."
- !

Item was removed:
- ----- Method: FileDirectory>>splitNameVersionExtensionFor: (in category 'file name utilities') -----
- splitNameVersionExtensionFor: fileName
- 	" answer an array with the root name, version # and extension.
- 	See comment in nextSequentialNameFor: for more details"
- 
- 	| baseName version extension i j |
- 
- 	baseName := self class baseNameFor: fileName.
- 	extension := self class extensionFor: fileName.
- 	i := j := baseName findLast: [:c | c isDigit not].
- 	i = 0
- 		ifTrue: [version := 0]
- 		ifFalse:
- 			[(baseName at: i) = $.
- 				ifTrue:
- 					[version := (baseName copyFrom: i+1 to: baseName size) asNumber.
- 					j := j - 1]
- 				ifFalse: [version := 0].
- 			baseName := baseName copyFrom: 1 to: j].
- 	^ Array with: baseName with: version with: extension!

Item was removed:
- ----- Method: FileDirectory>>statsForDirectoryTree: (in category 'enumeration') -----
- statsForDirectoryTree: rootedPathName
- 	"Return the size statistics for the entire directory tree starting at the given root. The result is a three element array of the form: (<number of folders><number of files><total bytes in all files>). This method also serves as an example of how recursively enumerate a directory tree."
- 	"FileDirectory default statsForDirectoryTree: '\smalltalk'"
- 
- 	| dirs files bytes todo entries p |
- 	dirs := files := bytes := 0.
- 	todo := OrderedCollection with: rootedPathName.
- 	[todo isEmpty] whileFalse: [
- 		p := todo removeFirst.
- 		entries := self directoryContentsFor: p.
- 		entries do: [:entry |
- 			entry isDirectory
- 				ifTrue: [
- 					todo addLast: p , self pathNameDelimiter asString , entry name.
- 					dirs := dirs + 1]
- 				ifFalse: [
- 					files := files + 1.
- 					bytes := bytes + entry fileSize]]].
- 	^ Array with: dirs with: files with: bytes
- !

Item was removed:
- ----- Method: FileDirectory>>storeServerEntryOn: (in category 'private') -----
- storeServerEntryOn: stream
- 	
- 	stream
- 		nextPutAll: 'name:'; tab; nextPutAll: self localName; cr;
- 		nextPutAll: 'directory:'; tab; nextPutAll: self pathName; cr;
- 		nextPutAll: 'type:'; tab; nextPutAll: 'file'; cr!

Item was removed:
- ----- Method: FileDirectory>>upLoadProject:named:resourceUrl:retry: (in category 'file operations') -----
- upLoadProject: projectFile named: destinationFileName resourceUrl: resUrl retry: aBool
- 	"Copy the contents of the existing fileStream into the file destinationFileName in this directory.  fileStream can be anywhere in the fileSystem.  No retrying for local file systems."
- 
- 	| result |
- 	result := self putFile: projectFile named: destinationFileName.
- 	[self
- 		setMacFileNamed: destinationFileName
- 		type: 'SOBJ'
- 		creator: 'FAST']
- 		on: Error
- 		do: [ "ignore" ].
- 	^result!

Item was removed:
- ----- Method: FileDirectory>>updateProjectInfoFor: (in category 'squeaklets') -----
- updateProjectInfoFor: aProject
- 
- 	"only swiki servers for now"!

Item was removed:
- ----- Method: FileDirectory>>wakeUp (in category 'file directory') -----
- wakeUp
- 	"Entering a FileList window.  Do nothing.  Disk directories do not have to be awakened."
- !

Item was removed:
- ----- Method: FileDirectory>>withAllFilesDo:andDirectoriesDo: (in category 'searching') -----
- withAllFilesDo: fileStreamBlock andDirectoriesDo: directoryBlock
- 
- 	"For the receiver and all it's subdirectories evaluate directoryBlock.
- 	For a read only file stream on each file within the receiver 
- 	and it's subdirectories evaluate fileStreamBlock."
- 
- 	| todo dir |
- 
- 	todo := OrderedCollection with: self.
- 	[todo size > 0] whileTrue: [
- 		dir := todo removeFirst.
- 		directoryBlock value: dir.
- 		dir fileNames do: [: n | 
- 			fileStreamBlock value: 
- 				(FileStream readOnlyFileNamed: (dir fullNameFor: n))].
- 		dir directoryNames do: [: n | 
- 			todo add: (dir directoryNamed: n)]]
- 
- !

Item was removed:
- ----- Method: FileDirectory>>withAllSubdirectoriesCollect: (in category 'enumeration') -----
- withAllSubdirectoriesCollect: aBlock
- 	"Evaluate aBlock with each of the directories in the subtree of the file system whose root is this directory.
- 	Answer the results of these evaluations."
- 
- 	| result todo dir |
- 	result := OrderedCollection new: 100.
- 	todo := OrderedCollection with: self.
- 	[todo size > 0] whileTrue: [
- 		dir := todo removeFirst.
- 		result add: (aBlock value: dir).
- 		dir directoryNames do: [:n | todo add: (dir directoryNamed: n)]].
- 	^ result
- !

Item was removed:
- ----- Method: FileDirectory>>writeProject:inFileNamed:fromDirectory: (in category 'squeaklets') -----
- writeProject: aProject inFileNamed: fileNameString fromDirectory: localDirectory 
- 	"write aProject (a file version can be found in the file named fileNameString in localDirectory)"
- 	aProject
- 		writeFileNamed: fileNameString
- 		fromDirectory: localDirectory
- 		toServer: self!

Item was removed:
- ----- Method: FileDirectory>>writeSourceCodeFrom:baseName:isSt:useHtml: (in category 'utilities') -----
- writeSourceCodeFrom: sourceStream baseName: baseName isSt: stOrCsFlag useHtml: useHtml
- 	"Write the source code from sourceStream into a file. The stream's content format is indicated via stOrCsFlag and useHtml. We must ensure that a text converter for code is used to not differ from the system's current text converter. See #Locale."
- 
- 	| extension |
- 	extension := FileDirectory dot, (useHtml
- 		ifTrue: ['html']
- 		ifFalse: [stOrCsFlag
- 			ifTrue: [FileStream st] ifFalse: [FileStream cs]]).
- 	self
- 		newFileNamed: baseName, extension
- 		do: [:targetStream |			
- 			targetStream
- 				nextPutUTF8BOM; "Backwards compatibililty."
- 				setConverterForCode;
- 				nextPutAll: sourceStream contents]!

Item was removed:
- FileStreamException subclass: #FileDoesNotExistException
- 	instanceVariableNames: 'readOnly'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Exceptions'!

Item was removed:
- ----- Method: FileDoesNotExistException class>>example (in category 'examples') -----
- example
- 	"FileDoesNotExistException example"
- 
- 	| result |
- 	result := [(StandardFileStream readOnlyFileNamed: 'error42.log') contentsOfEntireFile]
- 		on: FileDoesNotExistException
- 		do: [:ex | 'No error log'].
- 	Transcript show: result; cr!

Item was removed:
- ----- Method: FileDoesNotExistException>>readOnly (in category 'accessing') -----
- readOnly
- 	^readOnly == true!

Item was removed:
- ----- Method: FileDoesNotExistException>>readOnly: (in category 'accessing') -----
- readOnly: aBoolean
- 	readOnly := aBoolean!

Item was removed:
- FileStreamException subclass: #FileExistsException
- 	instanceVariableNames: 'fileClass'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Exceptions'!

Item was removed:
- ----- Method: FileExistsException class>>fileName:fileClass: (in category 'exceptionInstantiator') -----
- fileName: aFileName fileClass: aClass 
- 	^ self new
- 		fileName: aFileName;
- 		fileClass: aClass!

Item was removed:
- ----- Method: FileExistsException>>fileClass (in category 'accessing') -----
- fileClass
- 	^ fileClass ifNil: [StandardFileStream]!

Item was removed:
- ----- Method: FileExistsException>>fileClass: (in category 'accessing') -----
- fileClass: aClass
- 	fileClass := aClass!

Item was removed:
- Object subclass: #FilePath
- 	instanceVariableNames: 'squeakPathName vmPathName converter'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!
- 
- !FilePath commentStamp: 'yo 10/19/2004 21:36' prior: 0!
- This class absorb the difference of internal and external representation of the file path.  The idea is to keep the internal one as much as possible, and only when it goes to a primitive, the encoded file path, i.e. the native platform representation is passsed to the primitive.
- 
- 	The converter used is obtained by "LanguageEnvironment defaultFileNameConverter".
- !

Item was removed:
- ----- Method: FilePath class>>classVersion (in category 'accessing') -----
- classVersion
- 
- 	^ 1.
- !

Item was removed:
- ----- Method: FilePath class>>pathName: (in category 'instance creation') -----
- pathName: pathName
- 
- 	^ self pathName: pathName isEncoded: false.
- !

Item was removed:
- ----- Method: FilePath class>>pathName:isEncoded: (in category 'instance creation') -----
- pathName: pathName isEncoded: aBoolean
- 
- 	^ (self new) pathName: pathName isEncoded: aBoolean; yourself.
- !

Item was removed:
- ----- Method: FilePath>>asSqueakPathName (in category 'conversion') -----
- asSqueakPathName
- 
- 	^ self pathName.
- !

Item was removed:
- ----- Method: FilePath>>asString (in category 'conversion') -----
- asString
- 	^self asSqueakPathName!

Item was removed:
- ----- Method: FilePath>>asVmPathName (in category 'conversion') -----
- asVmPathName
- 
- 	^ vmPathName.
- !

Item was removed:
- ----- Method: FilePath>>convertToCurrentVersion:refStream: (in category 'file in/out') -----
- convertToCurrentVersion: varDict refStream: smartRefStrm
- 	"If we're reading in an old version with a system path instance variable, convert it to a vm path."
- 
- 	varDict at: 'systemPathName' ifPresent: [ :x | 
- 		vmPathName := x.
- 	].
- 	^super convertToCurrentVersion: varDict refStream: smartRefStrm.
- !

Item was removed:
- ----- Method: FilePath>>converter: (in category 'conversion') -----
- converter: aTextConverter
- 
- 	converter class ~= aTextConverter class ifTrue: [
- 		converter := aTextConverter.
- 		vmPathName := squeakPathName convertToWithConverter: converter
- 	].
- !

Item was removed:
- ----- Method: FilePath>>copySystemToVm (in category 'file in/out') -----
- copySystemToVm
- 
- 	(self class instVarNames includes: 'systemPathName') ifTrue: [
- 		vmPathName := self instVarNamed: 'systemPathName'.
- 	].
- 
- !

Item was removed:
- ----- Method: FilePath>>isNullPath (in category 'testing') -----
- isNullPath
- 	"an empty path is used to represent the root path(s) when calling the primitive to list directory entries. Some users need to check for this and this is cleaner than grabbing the pathname and assuming it is a plain String"
- 	^self pathName isEmpty!

Item was removed:
- ----- Method: FilePath>>pathName (in category 'conversion') -----
- pathName
- 
- 	^ squeakPathName.
- !

Item was removed:
- ----- Method: FilePath>>pathName:isEncoded: (in category 'conversion') -----
- pathName: p isEncoded: isEncoded
- 
- 	converter := Locale currentPlatform fileNameConverter.
- 	isEncoded ifTrue: [
- 		squeakPathName := p convertFromWithConverter: converter.
- 		vmPathName := p.
- 	] ifFalse: [
- 		squeakPathName := p isOctetString ifTrue: [p asOctetString] ifFalse: [p].
- 		vmPathName := squeakPathName convertToWithConverter: converter.
- 	].
- !

Item was removed:
- ----- Method: FilePath>>printOn: (in category 'conversion') -----
- printOn: aStream
- 
- 	aStream nextPutAll: 'FilePath('''.
- 	aStream nextPutAll: squeakPathName.
- 	aStream nextPutAll: ''')'.
- !

Item was removed:
- ReadWriteStream subclass: #FileStream
- 	instanceVariableNames: 'rwmode'
- 	classVariableNames: 'EncodeAndDecodeStdioFiles Stderr Stdin StdioFiles Stdout TheStdioHandles'
- 	poolDictionaries: ''
- 	category: 'Files-Kernel'!
- 
- !FileStream commentStamp: '<historical>' prior: 0!
- I represent a Stream that accesses a FilePage from a File. One use for my instance is to access larger "virtual Strings" than can be stored contiguously in main memory. I restrict the objects stored and retrieved to be Integers or Characters. An end of file pointer terminates reading; it can be extended by writing past it, or the file can be explicitly truncated.
- 	
- To use the file system for most applications, you typically create a FileStream. This is done by sending a message to a FileDirectory (file:, oldFile:, newFile:, rename:newName:) which creates an instance of me. Accesses to the file are then done via my instance.
- 
- *** On DOS, files cannot be shortened!!  ***  To overwrite a file with a shorter one, first delete the old file (FileDirectory deleteFilePath: 'Hard Disk:aFolder:dataFolder:foo') or (aFileDirectory deleteFileNamed: 'foo').  Then write your new shorter version.!

Item was removed:
- ----- Method: FileStream class>>changes (in category 'file reader services') -----
- changes
- 
- 	^'changes' shallowCopy!

Item was removed:
- ----- Method: FileStream class>>concreteStream (in category 'concrete classes') -----
- concreteStream
- 	"Who should we really direct class queries to?  "
- 	^ MultiByteFileStream.
- !

Item was removed:
- ----- Method: FileStream class>>cs (in category 'file reader services') -----
- cs
- 
- 	^'cs' shallowCopy!

Item was removed:
- ----- Method: FileStream class>>detectFile:do: (in category 'instance creation') -----
- detectFile: aBlockOrFileStream do: anotherBlock
- 
- 	^aBlockOrFileStream value "Assume that FileStreams return self for #value."
- 		ifNotNil: [ :file | [ anotherBlock value: file ] ensure: [ file close ] ]!

Item was removed:
- ----- Method: FileStream class>>encodeAndDecodeStdioFiles (in category 'stdio') -----
- encodeAndDecodeStdioFiles
- 	
- 	<preference: 'Encode and decode the contents of stdio files.'
- 		category: 'Files'
- 		description: 'If true, then the contents of stdin, stdout and stderr are encoded/decoded using the system default text converter.'
- 		type: #Boolean>
- 	^EncodeAndDecodeStdioFiles ifNil: [ true ]!

Item was removed:
- ----- Method: FileStream class>>encodeAndDecodeStdioFiles: (in category 'stdio') -----
- encodeAndDecodeStdioFiles: aBoolean
- 	
- 	EncodeAndDecodeStdioFiles := aBoolean.
- 	self updateStdioFiles!

Item was removed:
- ----- Method: FileStream class>>fileNamed: (in category 'instance creation') -----
- fileNamed: fileName 
- 	^ self concreteStream fileNamed: (self fullName: fileName)!

Item was removed:
- ----- Method: FileStream class>>fileNamed:do: (in category 'instance creation') -----
- fileNamed: fileName do: aBlock
- 	"Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})).  It's time Squeak had it, too.''
- 	
- 	Returns the result of aBlock."
- 	
- 	^self detectFile: (self fileNamed: fileName) do: aBlock!

Item was removed:
- ----- Method: FileStream class>>fileReaderServicesForFile:suffix: (in category 'file reader services') -----
- fileReaderServicesForFile: fullName suffix: suffix
- 	"Answer services for the given file"
- 
- 	"Check whether the given path points to a directory or file."
- 	(FileDirectory default directoryExists: fullName) ifTrue: [^ #()].
- 		
- 	^ self servicesWithSuffixes
- 		select: [:spec | spec key anySatisfy: [:pattern | suffix = '*' or: [pattern match: suffix]]]
- 		thenCollect: [:spec | spec value]!

Item was removed:
- ----- Method: FileStream class>>flushAndVoidStdioFiles (in category 'stdio') -----
- flushAndVoidStdioFiles
- 
- 	StdioFiles ifNotNil: [
- 		StdioFiles do: [ :file |
- 			file ifNotNil: [ 
- 				file isReadOnly ifFalse: [
- 					[ file flush ]
- 						on: Error
- 						do: [ :ex | "care less" ] ] ] ].
- 		self voidStdioFiles ]!

Item was removed:
- ----- Method: FileStream class>>forceNewFileNamed: (in category 'instance creation') -----
- forceNewFileNamed: fileName
-  	"Create a new file with the given name, and answer a stream opened for writing on that file. If the file already exists, delete it without asking before creating the new file."
- 
- 	^self concreteStream forceNewFileNamed: fileName!

Item was removed:
- ----- Method: FileStream class>>forceNewFileNamed:do: (in category 'instance creation') -----
- forceNewFileNamed: fileName do: aBlock
- 	"Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})).  It's time Squeak had it, too.''
- 	
- 	Returns the result of aBlock."
- 	
- 	^self detectFile: (self forceNewFileNamed: fileName) do: aBlock!

Item was removed:
- ----- Method: FileStream class>>fullName: (in category 'instance creation') -----
- fullName: fileName
- 	^ FileDirectory default fullNameFor: fileName!

Item was removed:
- ----- Method: FileStream class>>initialize (in category 'initialize-release') -----
- initialize
- 
- 	FileServices registerFileReader: self.
- 	EncodeAndDecodeStdioFiles := true.
- 	TheStdioHandles := Array new: 3.
- 	Smalltalk
- 		addToStartUpList: self after: SecurityManager; "the intent being before: AutoStart"
- 		addToShutDownList: self after: SecurityManager!

Item was removed:
- ----- Method: FileStream class>>isAFileNamed: (in category 'instance creation') -----
- isAFileNamed: fName
- 	"return whether a file exists with the given name"
- 	^self concreteStream isAFileNamed: (self fullName: fName)!

Item was removed:
- ----- Method: FileStream class>>isSourceFileSuffix: (in category 'file reader services') -----
- isSourceFileSuffix: suffix
- 
- 	^ FileStream sourceFileSuffixes includes: suffix
- !

Item was removed:
- ----- Method: FileStream class>>multiCs (in category 'file reader services') -----
- multiCs
- 
- 	^'mcs' shallowCopy!

Item was removed:
- ----- Method: FileStream class>>multiSt (in category 'file reader services') -----
- multiSt
- 
- 	^'mst' shallowCopy!

Item was removed:
- ----- Method: FileStream class>>new (in category 'stdio') -----
- new
- 
- 	^self basicNew initialize!

Item was removed:
- ----- Method: FileStream class>>newFileNamed: (in category 'instance creation') -----
- newFileNamed: fileName 
- 	^ self concreteStream newFileNamed: (self fullName: fileName)!

Item was removed:
- ----- Method: FileStream class>>newFileNamed:do: (in category 'instance creation') -----
- newFileNamed: fileName do: aBlock
- 	"Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})).  It's time Squeak had it, too.''
- 	
- 	Returns the result of aBlock."
- 	
- 	^self detectFile: (self newFileNamed: fileName) do: aBlock!

Item was removed:
- ----- Method: FileStream class>>newForStdio (in category 'stdio') -----
- newForStdio
- 	"This is a hook for subclasses to initialize themselves properly."
- 
- 	^self new!

Item was removed:
- ----- Method: FileStream class>>oldFileNamed: (in category 'instance creation') -----
- oldFileNamed: fileName 
- 	^ self concreteStream oldFileNamed: (self fullName: fileName)!

Item was removed:
- ----- Method: FileStream class>>oldFileNamed:do: (in category 'instance creation') -----
- oldFileNamed: fileName do: aBlock
- 	"Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})).  It's time Squeak had it, too.''
- 	
- 	Returns the result of aBlock."
- 	
- 	^self detectFile: (self oldFileNamed: fileName) do: aBlock!

Item was removed:
- ----- Method: FileStream class>>oldFileOrNoneNamed: (in category 'instance creation') -----
- oldFileOrNoneNamed: fileName
- 	"If the file exists, answer a read-only FileStream on it. If it doesn't, answer nil."
- 
- 	| fullName |
- 	fullName := self fullName: fileName.
- 	(self concreteStream isAFileNamed: fullName)
- 		ifTrue: [^ self concreteStream readOnlyFileNamed: fullName]
- 		ifFalse: [^ nil].
- !

Item was removed:
- ----- Method: FileStream class>>primDropRequestFileName: (in category 'dnd requests') -----
- primDropRequestFileName: dropIndex
- 	"Primitive. Return the file name for some file that was just dropped onto Squeak.
- 	Fail if dropIndex is out of range or the primitive is not supported."
- 	<primitive: 'primitiveDropRequestFileName' module:'DropPlugin'>
- 	^nil!

Item was removed:
- ----- Method: FileStream class>>readOnlyFileNamed: (in category 'instance creation') -----
- readOnlyFileNamed: fileName 
- 	^ self concreteStream readOnlyFileNamed: (self fullName: fileName)!

Item was removed:
- ----- Method: FileStream class>>readOnlyFileNamed:do: (in category 'instance creation') -----
- readOnlyFileNamed: fileName do: aBlock
- 	"Avi Bryant says, ''This idiom is quite common in other languages that make heavy use of closures (i.e. Lisp (with-file 'foo' (f) ...) and Ruby (File.open('foo'){|f|...})).  It's time Squeak had it, too.''
- 	
- 	Returns the result of aBlock."
- 	
- 	^self detectFile: (self readOnlyFileNamed: fileName) do: aBlock!

Item was removed:
- ----- Method: FileStream class>>removeLineFeeds: (in category 'file reader services') -----
- removeLineFeeds: fullName
- 	| fileContents |
- 	fileContents := ((FileStream readOnlyFileNamed: fullName) wantsLineEndConversion: true) contentsOfEntireFile.
- 	(FileStream newFileNamed: fullName) 
- 		nextPutAll: fileContents;
- 		close.!

Item was removed:
- ----- Method: FileStream class>>requestDropStream: (in category 'dnd requests') -----
- requestDropStream: dropIndex
- 	"Request a read-only stream for some file that was dropped onto Squeak"
- 	^self concreteStream new requestDropStream: dropIndex.!

Item was removed:
- ----- Method: FileStream class>>serviceFileIn (in category 'file reader services') -----
- serviceFileIn
- 	"Answer a service for filing in an entire file"
- 
- 	^ SimpleServiceEntry 
- 		provider: self 
- 		label: 'fileIn entire file' translatedNoop
- 		selector: #fileIn:
- 		description: 'file in the entire contents of the file, which is expected to contain Smalltalk code in fileout ("chunk") format' translatedNoop
- 		buttonLabel: 'filein' translatedNoop!

Item was removed:
- ----- Method: FileStream class>>serviceFileInSuffixes (in category 'file reader services') -----
- serviceFileInSuffixes
- 
- 	^ self sourceFileSuffixes!

Item was removed:
- ----- Method: FileStream class>>serviceRemoveLineFeeds (in category 'file reader services') -----
- serviceRemoveLineFeeds
- 	"Answer a service for removing linefeeds from a file"
- 
- 	^ FileModifyingSimpleServiceEntry
- 		provider: self 
- 		label: 'remove line feeds' translatedNoop
- 		selector: #removeLineFeeds:	
- 		description: 'remove line feeds in file' translatedNoop
- 		buttonLabel: 'remove lfs' translatedNoop!

Item was removed:
- ----- Method: FileStream class>>serviceRemoveLineFeedsSuffixes (in category 'file reader services') -----
- serviceRemoveLineFeedsSuffixes
- 
- 	^ self sourceFileSuffixes!

Item was removed:
- ----- Method: FileStream class>>services (in category 'file reader services') -----
- services
- 
- 	^ (((self class selectors copyWithout: #services)
- 		select: [:symbol | symbol beginsWith: #service])
- 		reject: [:symbol | symbol endsWith: #Suffixes])
- 		collect: [:selector | self perform: selector]!

Item was removed:
- ----- Method: FileStream class>>servicesWithSuffixes (in category 'file reader services') -----
- servicesWithSuffixes
- 
- 	^ (((self class selectors copyWithout: #services)
- 		select: [:symbol | symbol beginsWith: #service])
- 		reject: [:symbol | symbol endsWith: #Suffixes])
- 		collect: [:selector | 
- 			(self perform: (selector, #Suffixes) asSymbol) -> (self perform: selector)]!

Item was removed:
- ----- Method: FileStream class>>shutDown: (in category 'system startup') -----
- shutDown: quitting
- 
- 	quitting ifTrue: [ self flushAndVoidStdioFiles ]!

Item was removed:
- ----- Method: FileStream class>>sourceFileSuffixes (in category 'file reader services') -----
- sourceFileSuffixes
- 
- 	^ {FileStream st. FileStream sources. FileStream changes. FileStream cs. FileStream multiSt. FileStream multiCs} asSet asArray!

Item was removed:
- ----- Method: FileStream class>>sources (in category 'file reader services') -----
- sources
- 
- 	^'sources' shallowCopy!

Item was removed:
- ----- Method: FileStream class>>st (in category 'file reader services') -----
- st
- 
- 	^'st' shallowCopy!

Item was removed:
- ----- Method: FileStream class>>standardIOStreamNamed:forWrite: (in category 'stdio') -----
- standardIOStreamNamed: moniker forWrite: forWrite
- 	
- 	| index |
- 	index := #(stdin stdout stderr) identityIndexOf: moniker.
- 	^((StdioFiles ifNil: [ StdioFiles := Array new: 3 ]) at: index)
- 		ifNil: [
- 			StdioFiles
- 				at: index 
- 				put: (
- 					(TheStdioHandles at: index)
- 						ifNil: [ ^self error: moniker, ' is unavailable' ]
- 						ifNotNil: [ :handle |
- 							self stdioStreamClass newForStdio
- 								openOnHandle: handle
- 								name: moniker
- 								forWrite: forWrite ]) ]
- !

Item was removed:
- ----- Method: FileStream class>>startUp: (in category 'system startup') -----
- startUp: resuming
- 	
- 	resuming ifTrue: [
- 		self voidStdioFiles.
- 		[ TheStdioHandles := self stdioHandles ]
- 			on: Error
- 			do: [:ex|
- 				TheStdioHandles isArray ifFalse: [
- 					TheStdioHandles := Array new: 3 ] ].
- 		(Smalltalk classNamed: 'TranscriptStream')
- 			ifNotNil: [ :t | "Reestablish dependency for stdout Transcript view"
- 				t redirectToStdOut: t redirectToStdOut ] ]
- !

Item was removed:
- ----- Method: FileStream class>>stderr (in category 'stdio') -----
- stderr
- 
- 	^Stderr ifNil: [ Stderr := self standardIOStreamNamed: #stderr forWrite: true ]!

Item was removed:
- ----- Method: FileStream class>>stdin (in category 'stdio') -----
- stdin
- 
- 	^Stdin ifNil: [ Stdin := self standardIOStreamNamed: #stdin forWrite: false ]!

Item was removed:
- ----- Method: FileStream class>>stdioHandles (in category 'stdio') -----
- stdioHandles
- 	<primitive: 'primitiveFileStdioHandles' module: 'FilePlugin' error: ec>
- 	self primitiveFailed!

Item was removed:
- ----- Method: FileStream class>>stdioStreamClass (in category 'stdio') -----
- stdioStreamClass
- 
- 	^self encodeAndDecodeStdioFiles
- 		ifTrue: [ MultiByteFileStream ]
- 		ifFalse: [ StandardFileStream ]!

Item was removed:
- ----- Method: FileStream class>>stdout (in category 'stdio') -----
- stdout
- 
- 	^Stdout ifNil: [ Stdout := self standardIOStreamNamed: #stdout forWrite: true ]!

Item was removed:
- ----- Method: FileStream class>>unload (in category 'class initialization') -----
- unload
- 
- 	FileServices unregisterFileReader: self !

Item was removed:
- ----- Method: FileStream class>>updateStdioFiles (in category 'stdio') -----
- updateStdioFiles
- 	"Make sure that all existing stdio files are instances of #stdioStreamClass."
- 
- 	StdioFiles ifNil: [ ^self ].
- 	Stdin := Stdout := Stderr := nil.
- 	StdioFiles := StdioFiles collect: [ :file |
- 		file ifNotNil: [
- 			file class == self stdioStreamClass
- 				ifTrue: [ file ]
- 				ifFalse: [
- 					self stdioStreamClass newForStdio
- 						copyFrom: file;
- 						yourself ] ] ]
- !

Item was removed:
- ----- Method: FileStream class>>voidStdioFiles (in category 'stdio') -----
- voidStdioFiles
- 
- 	 Stdin := Stdout := Stderr := StdioFiles := nil!

Item was removed:
- ----- Method: FileStream class>>writeSourceCodeFrom:baseName:isSt:useHtml: (in category 'file reader services') -----
- writeSourceCodeFrom: aStream baseName: baseName isSt: stOrCsFlag useHtml: useHtml
- 	"Write the source code from aStream into a file. 
- 	Uses ChangeSet defaultChangeSetDirectory for consistency."
- 
- 	^(ChangeSet defaultChangeSetDirectory)
- 		writeSourceCodeFrom: aStream 
- 		baseName: baseName 
- 		isSt: stOrCsFlag 
- 		useHtml: useHtml!

Item was removed:
- ----- Method: FileStream>>asBinaryOrTextStream (in category 'converting') -----
- asBinaryOrTextStream
- 	"I can switch between binary and text data"
- 
- 	^ self!

Item was removed:
- ----- Method: FileStream>>ascii (in category 'file modes') -----
- ascii
- 	"Set this file to ascii (text) mode."
- 
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: FileStream>>atEnd (in category 'testing') -----
- atEnd
- 	"Answer true if the current position is >= the end of file position.
- 	 1/31/96 sw: subclassResponsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>binary (in category 'file modes') -----
- binary
- 	"Set this file to binary mode."
- 
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: FileStream>>close (in category 'file open/close') -----
- close
- 	"Close this file."
- 
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: FileStream>>closed (in category 'file open/close') -----
- closed
- 	"Answer true if this file is closed."
- 
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: FileStream>>contents (in category 'accessing') -----
- contents
- 	"Return the contents of the receiver. Do not close or otherwise touch the receiver. Return data in whatever mode the receiver is in (e.g., binary or text)."
- 	| s savePos |
- 	savePos := self position.
- 	self position: 0.
- 	s := self next: self size.
- 	self position: savePos.
- 	^s!

Item was removed:
- ----- Method: FileStream>>contentsOfEntireFile (in category 'accessing') -----
- contentsOfEntireFile
- 	"Read all of the contents of the receiver."
- 
- 	| s binary |
- 	self readOnly.
- 	binary := self isBinary.
- 	self reset.	"erases knowledge of whether it is binary"
- 	binary ifTrue: [self binary].
- 	s := self next: self size.
- 	self close.
- 	^s!

Item was removed:
- ----- Method: FileStream>>dataIsValid (in category 'remote file compatibility') -----
- dataIsValid
- 
- 	self flag: #bob.		"we needed this if a remote stream, but could be local as well"!

Item was removed:
- ----- Method: FileStream>>directoryEntry (in category 'accessing') -----
- directoryEntry
- 	^self directory entryAt: self localName!

Item was removed:
- ----- Method: FileStream>>file (in category 'file accessing') -----
- file
- 	"Answer the file for the page the receiver is streaming over.
- 	 1/31/96 sw: made subclass responsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>fileIn (in category 'fileIn/Out') -----
- fileIn
- 	"Guarantee that the receiver is readOnly before fileIn for efficiency and
- 	to eliminate remote sharing conflicts."
- 
- 	self readOnly.
- 	self fileInAnnouncing: 'Loading ', self localName!

Item was removed:
- ----- Method: FileStream>>fileInObjectAndCode (in category 'fileIn/Out') -----
- fileInObjectAndCode
- 	"Read the file directly, do not use an RWBinaryOrTextStream."
- 
- 	self text.
- 	^ super fileInObjectAndCode
- !

Item was removed:
- ----- Method: FileStream>>flush (in category 'file open/close') -----
- flush
- 	"When writing, flush the current buffer out to disk."
- 
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: FileStream>>localName (in category 'file accessing') -----
- localName
- 
- 	^ FileDirectory localNameFor: self name
- !

Item was removed:
- ----- Method: FileStream>>longPrintOn: (in category 'printing') -----
- longPrintOn: aStream
- 	"Do nothing, so it will print short.  Called to print the error file.  If the error was in a file operation, we can't read the contents of that file.  Just print its name instead."
- !

Item was removed:
- ----- Method: FileStream>>longPrintOn:limitedTo:indent: (in category 'printing') -----
- longPrintOn: aStream limitedTo: sizeLimit indent: indent
- 
- 	"Do nothing, so it will print short.  Called to print the error file.  If the error was in a file operation, we can't read the contents of that file.  Just print its name instead."
- 
- 	aStream cr!

Item was removed:
- ----- Method: FileStream>>mimeTypes (in category 'accessing') -----
- mimeTypes
- 	^FileDirectory default mimeTypesFor: self name.!

Item was removed:
- ----- Method: FileStream>>name (in category 'file accessing') -----
- name
- 	"Answer the name of the file for the page the receiver is streaming over.  1/31/96 sw: made subclassResponsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>next (in category 'accessing') -----
- next
- 
- 	(position >= readLimit and: [self atEnd])
- 		ifTrue: [^nil]
- 		ifFalse: [^collection at: (position := position + 1)]!

Item was removed:
- ----- Method: FileStream>>next: (in category 'accessing') -----
- next: anInteger
- 
- 	| newCollection howManyRead increment |
- 	newCollection := self collectionSpecies new: anInteger.
- 	howManyRead := 0.
- 	[howManyRead < anInteger] whileTrue:
- 		[self atEnd ifTrue:
- 			[(howManyRead + 1) to: anInteger do: [:i | newCollection at: i put: (self next)].
- 			^newCollection].
- 		increment := (readLimit - position) min: (anInteger - howManyRead).
- 		newCollection replaceFrom: (howManyRead + 1)
- 			to: (howManyRead := howManyRead + increment)
- 			with: collection
- 			startingAt: (position + 1).
- 		position := position + increment].
- 	^newCollection!

Item was removed:
- ----- Method: FileStream>>nextPut: (in category 'accessing') -----
- nextPut: aByte
- 	"1/31/96 sw: subclassResponsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>nextPutAll: (in category 'accessing') -----
- nextPutAll: aCollection
- 	"1/31/96 sw: made subclass responsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>position (in category 'positioning') -----
- position
- 	"Answer the current character position in the file.
- 	 1/31/96 sw: subclassResponsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>position: (in category 'positioning') -----
- position: pos
- 	"Set the current character position in the file to pos.
- 	 1/31/96 sw: made subclassResponsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>printOn: (in category 'printing') -----
- printOn: aStream
- 
- 	super printOn: aStream.
- 	aStream nextPutAll: ' on '.
- 	self file printOn: aStream!

Item was removed:
- ----- Method: FileStream>>readOnly (in category 'file modes') -----
- readOnly
- 	"Set this file's mode to read-only."
- 
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: FileStream>>readOnlyStream (in category 'file modes') -----
- readOnlyStream
- 	^self readOnly!

Item was removed:
- ----- Method: FileStream>>readWrite (in category 'file modes') -----
- readWrite
- 	"Set this file's mode to read-write."
- 
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: FileStream>>reopen (in category 'file open/close') -----
- reopen
- 	"Ensure that the receiver is open, re-open it if necessary."
- 	"Details: Files that were open when a snapshot occurs are no longer valid when the snapshot is resumed. This operation re-opens the file if that has happened."
- 
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: FileStream>>reset (in category 'positioning') -----
- reset
- 	"Set the current character position to the beginning of the file.
- 	 1/31/96 sw: subclassResponsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>setToEnd (in category 'positioning') -----
- setToEnd
- 	"Set the current character position to the end of the File. The same as
- 	self position: self size.  1/31/96 sw: made subclassResponsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>size (in category 'accessing') -----
- size
- 	"Answer the size of the file in characters.
- 	 1/31/96 sw: made subclass responsibility"
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>skip: (in category 'positioning') -----
- skip: n
- 	"Set the character position to n characters from the current position.
- 	Error if not enough characters left in the file
- 	1/31/96 sw: made subclassResponsibility."
-  
- 	self subclassResponsibility!

Item was removed:
- ----- Method: FileStream>>sync (in category 'file open/close') -----
- sync
- 	"sync the current buffer out to disk."
- 
- 	self subclassResponsibility
- !

Item was removed:
- ----- Method: FileStream>>text (in category 'file modes') -----
- text
- 	"Set this file to text (ascii) mode."
- 
- 	self ascii.
- !

Item was removed:
- ----- Method: FileStream>>truncate: (in category 'positioning') -----
- truncate: pos
- 	"Truncate file to pos"
- 
- 	self subclassResponsibility!

Item was removed:
- Error subclass: #FileStreamException
- 	instanceVariableNames: 'fileName'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Exceptions'!

Item was removed:
- ----- Method: FileStreamException class>>fileName: (in category 'exceptionInstantiator') -----
- fileName: aFileName
- 	^self new fileName: aFileName!

Item was removed:
- ----- Method: FileStreamException>>fileName (in category 'exceptionDescription') -----
- fileName
- 	^fileName!

Item was removed:
- ----- Method: FileStreamException>>fileName: (in category 'exceptionBuilder') -----
- fileName: aFileName
- 	fileName := aFileName!

Item was removed:
- ----- Method: FileStreamException>>isResumable (in category 'exceptionDescription') -----
- isResumable
- 	"Determine whether an exception is resumable."
- 
- 	^true!

Item was removed:
- ----- Method: FileStreamException>>messageText (in category 'exceptionDescription') -----
- messageText
- 	
- 	"Return an exception's message text."
- 
- 	^messageText == nil
- 		ifTrue: [fileName printString]
- 		ifFalse: [messageText]!

Item was removed:
- FileStreamException subclass: #FileWriteError
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Exceptions'!

Item was removed:
- ----- Method: Integer>>asBytesDescription (in category '*files') -----
- asBytesDescription
- 	"Answer a terse, easily-readable representation of this Integer as a number of bytes.  Useful for file-browsers."
- 	| sign abs suffixes units |
- 	sign := self negative ifTrue: ['-'] ifFalse: [String empty].
- 	abs := self abs.
- 	suffixes := { '' "bytes".  'k'"ilobytes". 'M'"egabytes". 'G'"igabytes". 'T'"erabytes". 'P'"etabytes". 'E'"xabytes". 'Z'"ettabytes". 'Y'"ottabytes"}.
- 	1 to: suffixes size do:
- 		[ : index |
- 		units := 1000 raisedTo: index.
- 		units>abs ifTrue: [ ^ sign,(abs/(units/1000)) rounded asString,(suffixes at: index) ] ].
- 	^ sign,(abs/units) rounded,'Y'!

Item was removed:
- Error subclass: #InvalidDirectoryError
- 	instanceVariableNames: 'pathName'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Exceptions'!

Item was removed:
- ----- Method: InvalidDirectoryError class>>pathName: (in category 'exceptionInstantiator') -----
- pathName: badPathName
- 	^self new pathName: badPathName!

Item was removed:
- ----- Method: InvalidDirectoryError>>defaultAction (in category 'handling') -----
- defaultAction
- 	"Return an empty list as the default action of signaling the occurance of an invalid directory."
- 	^#()!

Item was removed:
- ----- Method: InvalidDirectoryError>>pathName (in category 'accessing') -----
- pathName
- 	^pathName!

Item was removed:
- ----- Method: InvalidDirectoryError>>pathName: (in category 'accessing') -----
- pathName: badPathName
- 	pathName := badPathName!

Item was removed:
- FileDirectory subclass: #MacFileDirectory
- 	instanceVariableNames: ''
- 	classVariableNames: 'TypeToMimeMappings'
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!
- 
- !MacFileDirectory commentStamp: '<historical>' prior: 0!
- I represent a Macintosh FileDirectory.
- !

Item was removed:
- ----- Method: MacFileDirectory class>>initializeTypeToMimeMappings (in category 'class initialization') -----
- initializeTypeToMimeMappings
- 	"MacFileDirectory initializeTypeToMimeMappings"
- 	TypeToMimeMappings := Dictionary new.
- 	#(
- 		"format"
- 		"(abcd		('image/gif'))"
- 	) do:[:spec|
- 		TypeToMimeMappings at: spec first asString put: spec last.
- 	].
- !

Item was removed:
- ----- Method: MacFileDirectory class>>isAbsolute: (in category 'class initialization') -----
- isAbsolute: fileName
- 	"Return true if the given fileName is absolute. The rules are:
- 
- If a path begins with a colon, it is relative.
- Otherwise,
-   If it contains a colon anywhere, it is absolute and the first component is the volume name.
-   Otherwise,
-     It is relative."
- 
- 	^fileName first ~= $:
- 		and: [ fileName includes: $: ]!

Item was removed:
- ----- Method: MacFileDirectory class>>isActiveDirectoryClass (in category 'platform specific') -----
- isActiveDirectoryClass
- 	^ super isActiveDirectoryClass
- 		and: [(Smalltalk getSystemAttribute: 1201) isNil
- 				or: [(Smalltalk getSystemAttribute: 1201) asNumber <= 31]]!

Item was removed:
- ----- Method: MacFileDirectory class>>isCaseSensitive (in category 'platform specific') -----
- isCaseSensitive
- 	"Mac OS ignores the case of file names"
- 	^ false!

Item was removed:
- ----- Method: MacFileDirectory class>>makeAbsolute: (in category 'platform specific') -----
- makeAbsolute: path
- 	"Ensure that path looks like an absolute path"
- 	| absolutePath |
- 	(self isAbsolute: path)
- 		ifTrue: [ ^path ].
- 	"If a path begins with a colon, it is relative."
- 	absolutePath := (path first = $:)
- 		ifTrue: [ path copyWithoutFirst ]
- 		ifFalse: [ path ].
- 	(self isAbsolute: absolutePath)
- 		ifTrue: [ ^absolutePath ].
- 	"Otherwise, if it contains a colon anywhere, it is absolute and the first component is the volume name."
- 	^absolutePath, ':'!

Item was removed:
- ----- Method: MacFileDirectory class>>makeRelative: (in category 'platform specific') -----
- makeRelative: path
- 	"Ensure that path looks like an relative path"
- 	^path first = $:
- 		ifTrue: [ path ]
- 		ifFalse: [ ':', path ]!

Item was removed:
- ----- Method: MacFileDirectory class>>maxFileNameLength (in category 'platform specific') -----
- maxFileNameLength
- 
- 	^31!

Item was removed:
- ----- Method: MacFileDirectory class>>pathNameDelimiter (in category 'platform specific') -----
- pathNameDelimiter
- 
- 	^ $:
- !

Item was removed:
- ----- Method: MacFileDirectory>>fullNameFor: (in category 'file name utilities') -----
- fullNameFor: fileName
- 	"Return a corrected, fully-qualified name for the given file name. If the given name is already a full path (i.e., it contains a delimiter character), assume it is already a fully-qualified name. Otherwise, prefix it with the path to this directory. In either case, correct the local part of the file name."
- 	"Details: Note that path relative to a directory, such as '../../foo' are disallowed by this algorithm.  Also note that this method is tolerent of a nil argument -- is simply returns nil in this case."
- 	"Fix by hmm: for a file in the root directory of a volume on MacOS, the filePath (name of the directory) is not  recognizable as an absolute path anymore (it has no delimiters). Therefore, the original fileName is tested for absoluteness, and the filePath is only made absolute if the original fileName was not absolute"
- 
- 	| correctedLocalName prefix |
- 	fileName isEmptyOrNil ifTrue: [^ fileName].
- 	DirectoryClass splitName: fileName to:
- 		[:filePath :localName |
- 			correctedLocalName := localName isEmpty 
- 				ifFalse: [self checkName: localName fixErrors: true]
- 				ifTrue: [localName].
- 			prefix := (DirectoryClass isAbsolute: fileName)
- 						ifTrue: [filePath]
- 						ifFalse: [self fullPathFor: filePath]].
- 	prefix isEmpty
- 		ifTrue: [^correctedLocalName].
- 	prefix last = self pathNameDelimiter
- 		ifTrue:[^ prefix, correctedLocalName]
- 		ifFalse:[^ prefix, self slash, correctedLocalName]!

Item was removed:
- ----- Method: MacFileDirectory>>fullPathFor: (in category 'file operations') -----
- fullPathFor: path
- 	"Return the fully-qualified path name for the given file."
- 	path isEmptyOrNil ifTrue: [^ pathName asSqueakPathName].
- 	(self class isAbsolute: path) ifTrue: [^ path].
- 	pathName asSqueakPathName = ''			"Root dir?"
- 		ifTrue: [ ^path].
- 	^(path first = $:)
- 		ifTrue: [ pathName asSqueakPathName, path ]
- 		ifFalse: [pathName asSqueakPathName, ':' , path]!

Item was removed:
- ----- Method: MacFileDirectory>>mimeTypesFor: (in category 'file operations') -----
- mimeTypesFor: fileName
- 	"Return a list of MIME types applicable to the receiver. This default implementation uses the file name extension to figure out what we're looking at but specific subclasses may use other means of figuring out what the type of some file is. Some systems like the macintosh use meta data on the file to indicate data type"
- 	| typeCreator type | 
- 	typeCreator := self getMacFileTypeAndCreator: ((self fullNameFor: fileName)).
- 	type := (typeCreator at: 1) asLowercase.
- 	^TypeToMimeMappings at: type ifAbsent:[super mimeTypesFor: fileName]!

Item was removed:
- MacFileDirectory subclass: #MacHFSPlusFileDirectory
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!

Item was removed:
- ----- Method: MacHFSPlusFileDirectory class>>isActiveDirectoryClass (in category 'platform specific') -----
- isActiveDirectoryClass
- 	"Ok, lets see if we support HFS Plus file names, the long ones"
- 
- 	^ (self pathNameDelimiter = self primPathNameDelimiter) and: [(Smalltalk  getSystemAttribute: 1201) notNil and: [(Smalltalk getSystemAttribute: 1201) asNumber > 31]]!

Item was removed:
- ----- Method: MacHFSPlusFileDirectory class>>maxFileNameLength (in category 'platform specific') -----
- maxFileNameLength
- 
- 	^ 255!

Item was removed:
- Object subclass: #RemoteString
- 	instanceVariableNames: 'sourceFileNumber filePositionHi'
- 	classVariableNames: 'CurrentTextAttStructure CurrentTextAttVersion TextAttributeStructureVersions'
- 	poolDictionaries: ''
- 	category: 'Files-System'!
- 
- !RemoteString commentStamp: '<historical>' prior: 0!
- My instances provide an external file reference to a piece of text.  It may be the sourceCode of a method, or the class comments of a class.
- 
- The changes file or file-in file usually has a chunk that is just the source string of a method:
- 
- max: aNumber
- 	^ self > aNumber ifTrue: [self] ifFalse: [aNumber]!!
- 
- I can return either a String or a Text.  Some a chunk is followed by a second chunk (beginning with ]style[) containing style information.  The encoding is like this:
- 
- max: aNumber
- 	^ self > aNumber ifTrue: [self] ifFalse: [aNumber]!!
- ]style[(14 50 312)f1,f1b,f1LInteger +;i!!
- 
- Allowed TextAttributes are TextFontChange, TextEmphasis, TextColor, TextDoIt, TextKern, TextLink, TextURL.  TextFontReference and TextAnchor are not supported.
- 
- See PositionableStream nextChunkText and RunArray class scanFrom:.!

Item was removed:
- ----- Method: RemoteString class>>currentTextAttVersion (in category 'accessing') -----
- currentTextAttVersion
- 	"The current configuration of the TextAttributes classes has a structures array describing the inst vars of the classes (SmartRefStream instVarInfo:).  Return tag that indexes the TextAttributeStructureVersions dictionary (4 random characters)."
- 
- 	^ CurrentTextAttVersion
- 	"Be sure to run makeNewTextAttVersion when any TextAttributes class changes inst vars"!

Item was removed:
- ----- Method: RemoteString class>>initialize (in category 'class initialization') -----
- initialize
- 	"Derive the current TextAttributes classes object structure"
- 
- 	self new makeNewTextAttVersion!

Item was removed:
- ----- Method: RemoteString class>>newFileNumber:position: (in category 'instance creation') -----
- newFileNumber: sourceIndex position: anInteger 
- 	"Answer an instance of me for a file indexed by sourceIndex, at the 
- 	position anInteger. Assume that the string is already stored on the file 
- 	and the instance will be used to access it."
- 
- 	^self new fileNumber: sourceIndex position: anInteger!

Item was removed:
- ----- Method: RemoteString class>>newString:onFileNumber: (in category 'instance creation') -----
- newString: aString onFileNumber: sourceIndex 
- 	"Answer an instance of me for string, aString, on file indexed by 
- 	sourceIndex. Put the string on the file and create the remote reference."
- 
- 	^self new string: aString onFileNumber: sourceIndex!

Item was removed:
- ----- Method: RemoteString class>>newString:onFileNumber:toFile: (in category 'instance creation') -----
- newString: aString onFileNumber: sourceIndex toFile: aFileStream
- 	"Answer an instance of me for string, aString, on file indexed by 
- 	sourceIndex. Put the string on the file, aFileStream, and create the 
- 	remote reference. Assume that the index corresponds properly to 
- 	aFileStream."
- 
- 	^self new string: aString onFileNumber: sourceIndex toFile: aFileStream!

Item was removed:
- ----- Method: RemoteString class>>structureAt: (in category 'accessing') -----
- structureAt: styleVersion
- 
- 	^ TextAttributeStructureVersions at: styleVersion ifAbsent: [nil]!

Item was removed:
- ----- Method: RemoteString>>checkSum: (in category 'private') -----
- checkSum: aString
- 	"Construct a checksum of the string.  A three byte number represented as Base64 characters."
- 	| sum shift bytes |
- 	sum := aString size.
- 	shift := 0.
- 	aString do: [:char |
- 		(shift := shift + 7) > 16 ifTrue: [shift := shift - 17].
- 			"shift by 7 to keep a change of adjacent chars from xoring to same value"
- 		sum := sum bitXor: (char asInteger bitShift: shift)
- 	].
- 	bytes := ByteArray new: 3.
- 	sum := sum + 16r10000000000.
- 	1 to: 3 do: [:ind | bytes at: ind put: (sum digitAt: ind)].
- 	^bytes base64Encoded!

Item was removed:
- ----- Method: RemoteString>>fileNumber:position: (in category 'private') -----
- fileNumber: fileNumber position: position 
- 
- 	sourceFileNumber := fileNumber.
- 	filePositionHi := position!

Item was removed:
- ----- Method: RemoteString>>fileStream (in category 'accessing') -----
- fileStream 
- 	"Answer the file stream with position set at the beginning of my string"
- 
- 	| theFile |
- 	(sourceFileNumber == nil or: [(SourceFiles at: sourceFileNumber) == nil]) ifTrue: [^ nil].
- 	theFile := SourceFiles at: sourceFileNumber.
- 	theFile position: filePositionHi.
- 	^ theFile!

Item was removed:
- ----- Method: RemoteString>>last (in category 'accessing') -----
- last
- 	^self string ifNotNil: [ :s | s last ]!

Item was removed:
- ----- Method: RemoteString>>makeNewTextAttVersion (in category 'private') -----
- makeNewTextAttVersion
- 	"Create a new TextAttributes version because some inst var has changed.  If no change, don't make a new one."
- 	"Don't delete this method even though it has no callers!!!!!!!!!!"
- 
- | obj struct tag |
- "Note that TextFontReference and TextAnchor are forbidden."
- obj := #(RunArray TextDoIt TextLink TextURL TextColor TextEmphasis TextFontChange TextKern TextLinkToImplementors 3 'a string') collect: [:each | | cls | 
- 		cls := Smalltalk at: each ifAbsent: [nil].
- 		cls ifNil: [each] ifNotNil: [cls new]].
- struct := (SmartRefStream on: (RWBinaryOrTextStream on: String new)) instVarInfo: obj.
- tag := self checkSum: struct printString.
- TextAttributeStructureVersions ifNil: [TextAttributeStructureVersions := Dictionary new].
- (struct = CurrentTextAttStructure) & (tag = CurrentTextAttVersion) 
- 	ifTrue: [^ false].
- CurrentTextAttStructure := struct.
- CurrentTextAttVersion := tag.
- TextAttributeStructureVersions at: tag put: struct.
- ^ true!

Item was removed:
- ----- Method: RemoteString>>position (in category 'accessing') -----
- position 
- 	"Answer the location of the string on a file."
- 
- 	^ filePositionHi!

Item was removed:
- ----- Method: RemoteString>>setSourcePointer: (in category 'accessing') -----
- setSourcePointer: aSourcePointer
- 	sourceFileNumber := SourceFiles fileIndexFromSourcePointer: aSourcePointer.
- 	filePositionHi := SourceFiles filePositionFromSourcePointer: aSourcePointer!

Item was removed:
- ----- Method: RemoteString>>sourceFileNumber (in category 'accessing') -----
- sourceFileNumber
- 	"Answer the index of the file on which the string is stored."
- 
- 	^sourceFileNumber!

Item was removed:
- ----- Method: RemoteString>>sourcePointer (in category 'accessing') -----
- sourcePointer
- 	sourceFileNumber ifNil: [^ 0].
- 	^SourceFiles sourcePointerFromFileIndex: sourceFileNumber andPosition: filePositionHi!

Item was removed:
- ----- Method: RemoteString>>string (in category 'accessing') -----
- string 
- 	"Answer the receiver's string if remote files are enabled."
- 	| theFile |
- 	(sourceFileNumber == nil or: [(SourceFiles at: sourceFileNumber) == nil]) ifTrue: [^''].
- 	theFile := SourceFiles at: sourceFileNumber.
- 	theFile position: filePositionHi.
- 	^ theFile nextChunk!

Item was removed:
- ----- Method: RemoteString>>string:onFileNumber: (in category 'private') -----
- string: aString onFileNumber: fileNumber
- 	"Store this as my string if source files exist."
- 	(SourceFiles at: fileNumber) ifNotNil: [:theFile |
- 		theFile isReadOnly ifTrue: [^ nil].
- 		theFile setToEnd; cr.
- 		self string: aString onFileNumber: fileNumber toFile: theFile].!

Item was removed:
- ----- Method: RemoteString>>string:onFileNumber:toFile: (in category 'private') -----
- string: aStringOrText onFileNumber: fileNumber toFile: aFileStream 
- 	"Store this as the receiver's text if source files exist. If aStringOrText is a Text, store a marker with the string part, and then store the runs of TextAttributes in the next chunk."
- 
- 	| position |
- 	position := aFileStream position.
- 	self fileNumber: fileNumber position: position.
- 	aFileStream nextChunkPutWithStyle: aStringOrText
- 	"^ self		(important)"!

Item was removed:
- ----- Method: RemoteString>>text (in category 'accessing') -----
- text 
- 	"Answer the receiver's string asText if remote files are enabled."
- 
- 	| theFile |
- 	theFile := (CurrentReadOnlySourceFiles at: (sourceFileNumber ifNil: [ ^nil ])) ifNil: [ ^nil ].
- 	theFile size <= filePositionHi ifTrue: [ 
- 		 "SourceFiles might have been appended to since theFile was opened. Flush the written data and reopen theFile to make it see the changes."
- 		(SourceFiles at: sourceFileNumber) flush.
- 		theFile reopen. "Currently the only way to re-read the size field of a read-only file on unix..." ].
- 	theFile size < filePositionHi ifTrue: [
- 		self error: 'RemoteString past end of file' ].
- 	^theFile
- 		position: filePositionHi;
- 		nextChunkText!

Item was removed:
- FileStreamException subclass: #ReplaceExistingFileException
- 	instanceVariableNames: 'fileClass'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Exceptions'!

Item was removed:
- ----- Method: ReplaceExistingFileException>>messageText (in category 'exceptionDescription') -----
- messageText
- 	^ fileName , ' already exists'.!

Item was removed:
- SequenceableCollection subclass: #SourceFileArray
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-System'!
- 
- !SourceFileArray commentStamp: '<historical>' prior: 0!
- This class is an abstract superclass for source code access mechanisms. It defines the messages that need to be understood by those subclasses that store and retrieve source chunks on files, over the network or in databases.
- The first concrete subclass, StandardSourceFileArray, supports access to the traditional sources and changes files. Other subclasses might implement multiple source files for different applications, or access to a network source server.!

Item was removed:
- ----- Method: SourceFileArray class>>concreteClass (in category 'initialize-release') -----
- concreteClass
- 
- 	^ ExpandedSourceFileArray!

Item was removed:
- ----- Method: SourceFileArray class>>install (in category 'initialize-release') -----
- install
- 	"Replace SourceFiles by an instance of me with the standard sources and changes files.
- 	This only works if SourceFiles is either an Array or an instance of this class"
- 
- 	"SourceFileArray install"
- 
- 	^ SourceFiles := self concreteClass new!

Item was removed:
- ----- Method: SourceFileArray>>at: (in category 'accessing') -----
- at: index
- 	self subclassResponsibility!

Item was removed:
- ----- Method: SourceFileArray>>at:put: (in category 'accessing') -----
- at: index put: aFileStream
- 	self subclassResponsibility!

Item was removed:
- ----- Method: SourceFileArray>>checkOKToAdd:at: (in category 'sourcePointer conversion') -----
- checkOKToAdd: size at: filePosition
- 	"Issue several warnings as the end of the changes file approaches its limit,
- 	and finally halt with an error when the end is reached."
- 
- 	^ self subclassResponsibility!

Item was removed:
- ----- Method: SourceFileArray>>fileIndexAndPositionFromSourcePointer:do: (in category 'sourcePointer conversion') -----
- fileIndexAndPositionFromSourcePointer: sourcePointer do: aBlock
- 
- 	^aBlock
- 		value: (self fileIndexFromSourcePointer: sourcePointer)
- 		value: (self filePositionFromSourcePointer: sourcePointer)!

Item was removed:
- ----- Method: SourceFileArray>>fileIndexFromSourcePointer: (in category 'sourcePointer conversion') -----
- fileIndexFromSourcePointer: anInteger
- 	"Return the index of a source file corresponding to the given source pointer."
- 	self subclassResponsibility!

Item was removed:
- ----- Method: SourceFileArray>>filePositionFromSourcePointer: (in category 'sourcePointer conversion') -----
- filePositionFromSourcePointer: anInteger
- 	"Return the position within a source file for the given source pointer."
- 	self subclassResponsibility!

Item was removed:
- ----- Method: SourceFileArray>>sourcePointerFromFileIndex:andPosition: (in category 'sourcePointer conversion') -----
- sourcePointerFromFileIndex: index andPosition: position
- 	"Return a sourcePointer encoding the given file index and position"
- 	self subclassResponsibility!

Item was removed:
- FileStream subclass: #StandardFileStream
- 	instanceVariableNames: 'name fileID buffer1 lastWritten'
- 	classVariableNames: 'Registry'
- 	poolDictionaries: ''
- 	category: 'Files-Kernel'!
- 
- !StandardFileStream commentStamp: 'ul 12/6/2009 05:13' prior: 0!
- Provides a simple, platform-independent, interface to a file system. The instance variable rwmode, inherited from class PositionableStream, here is used to hold a Boolean -- true means opened for read-write, false means opened for read-only.  2/12/96 sw
- 
- I implement a simple read buffering scheme with the variables defined in PositionableStream (which are unused in me otherwise) in the following way:
- 	collection	<ByteString> or <ByteArray>	This is the buffer.
- 	position	<Integer>	The relative position in the buffer. Greater or equal to zero.
- 	readLimit	<Integer>	The number of bytes buffered. Greater or equal to zero.
- Read buffering is enabled with #enableReadBuffering, disabled with #disableReadBuffering and it is enabled by default. The buffer is filled when a read attempt of an unbuffered absolute position is requested, or when a negative repositioning is made (with #position: with an argument < than the current absolute position) to an absolute position which is not buffered. In the first case, the buffer is positioned to the given absolute position. In the latter case the repositioning is made to the requested absolute position minus fourth of the buffer size. This means that further small negative repositionings won't result in buffer flushing. This is really useful when filing in code.
- The read buffer is flushed (#flushReadBuffer) whenever a write attempt is made.
- The buffer state is valid if and only if collection is not nil and position < readLimit.!

Item was removed:
- ----- Method: StandardFileStream class>>fileNamed: (in category 'file creation') -----
- fileNamed: fileName
- 	"Open a file with the given name for reading and writing. If the name has no directory part, then the file will be created in the default directory. If the file already exists, its prior contents may be modified or replaced, but the file will not be truncated on close."
- 
- 	^ self new open: (self fullName: fileName) forWrite: true
- !

Item was removed:
- ----- Method: StandardFileStream class>>forceNewFileNamed: (in category 'file creation') -----
- forceNewFileNamed: fileName 
- 	"Create a new file with the given name, and answer a stream opened 
- 	for writing on that file. If the file already exists, delete it without 
- 	asking before creating the new file."
- 	| dir localName fullName f |
- 	fullName := self fullName: fileName.
- 	(self isAFileNamed: fullName)
- 		ifFalse: 
- 			[f := self new open: fullName forWrite: true.
- 			^ f
- 				ifNil: ["Failed to open the file"
- 					(FileDoesNotExistException fileName: fullName) signal]].
- 	dir := FileDirectory forFileName: fullName.
- 	localName := FileDirectory localNameFor: fullName.
- 	dir
- 		deleteFileNamed: localName
- 		ifAbsent: [(CannotDeleteFileException new
- 			messageText: 'Could not delete the old version of file ' , fullName) signal].
- 	f := self new open: fullName forWrite: true.
- 	^ f
- 		ifNil: ["Failed to open the file"
- 			(FileDoesNotExistException fileName: fullName) signal]!

Item was removed:
- ----- Method: StandardFileStream class>>isAFileNamed: (in category 'file creation') -----
- isAFileNamed: fileName
- 	"Answer true if a file of the given name exists."
- 
- 	^ FileDirectory default fileExists: fileName!

Item was removed:
- ----- Method: StandardFileStream class>>newFileNamed: (in category 'file creation') -----
- newFileNamed: fileName
-  	"Create a new file with the given name, and answer a stream opened for writing on that file. If the file already exists, ask the user what to do."
- 
- 	| fullName |
- 	fullName := self fullName: fileName.
- 
- 	^(self isAFileNamed: fullName)
- 		ifTrue: ["file already exists:"
- 			(FileExistsException fileName: fullName fileClass: self) signal]
- 		ifFalse: [self new open: fullName forWrite: true]
- 
- !

Item was removed:
- ----- Method: StandardFileStream class>>oldFileNamed: (in category 'file creation') -----
- oldFileNamed: fileName
- 	"Open an existing file with the given name for reading and writing. If the name has no directory part, then the file will be created in the default directory. If the file already exists, its prior contents may be modified or replaced, but the file will not be truncated on close."
- 
- 	| fullName |
- 	fullName := self fullName: fileName.
- 
- 	^(self isAFileNamed: fullName)
- 		ifTrue: [self new open: fullName forWrite: true]
- 		ifFalse: ["File does not exist..."
- 			(FileDoesNotExistException fileName: fullName) signal]!

Item was removed:
- ----- Method: StandardFileStream class>>readOnlyFileNamed: (in category 'file creation') -----
- readOnlyFileNamed: fileName 
- 	"Open an existing file with the given name for reading."
- 
- 	| fullName f |
- 	fullName := self fullName: fileName.
- 	f := self new open: fullName forWrite: false.
- 	^ f
- 		ifNil: ["File does not exist..."
- 			((FileDoesNotExistException fileName: fullName) readOnly: true) signal].
- 
- 	"StandardFileStream readOnlyFileNamed: 'kjsd.txt' "!

Item was removed:
- ----- Method: StandardFileStream class>>register: (in category 'registry') -----
- register: anObject
- 	
- 	^self registry add: anObject!

Item was removed:
- ----- Method: StandardFileStream class>>registry (in category 'registry') -----
- registry
- 	
- 	^Registry ifNil: [ Registry := WeakRegistry new ]!

Item was removed:
- ----- Method: StandardFileStream class>>retryWithGC:until:forFileNamed: (in category 'registry') -----
- retryWithGC: execBlock until: testBlock forFileNamed: fullName
- 	"Re-implemented to only force GC if a file with the given name exists"
- 	| blockValue foundIt |
- 	blockValue := execBlock value.
- 	(testBlock value: blockValue) ifTrue:[^blockValue].
- 	"See if we have a file with the given name"
- 	foundIt := Registry keys "hold on strongly for now" 
- 		anySatisfy:[:file| file name sameAs: fullName].
- 	foundIt ifFalse:[^blockValue].
- 	Smalltalk garbageCollectMost.
- 	blockValue := execBlock value.
- 	(testBlock value: blockValue) ifTrue:[^blockValue].
- 	Smalltalk garbageCollect.
- 	^execBlock value.!

Item was removed:
- ----- Method: StandardFileStream class>>unregister: (in category 'registry') -----
- unregister: anObject
- 	
- 	^self registry remove: anObject ifAbsent: nil!

Item was removed:
- ----- Method: StandardFileStream>><< (in category 'printing') -----
- << aCollection
- 	aCollection putOn: self!

Item was removed:
- ----- Method: StandardFileStream>>actAsExecutor (in category 'finalization') -----
- actAsExecutor
- 	super actAsExecutor.
- 	name := nil.!

Item was removed:
- ----- Method: StandardFileStream>>ascii (in category 'properties-setting') -----
- ascii
- 	"Read and/or write in ASCII mode."
- 	buffer1
- 		ifNil: [ buffer1 := ByteString new: 1 ]
- 		ifNotNil: [ ByteString adoptInstance: buffer1 ].
- 	collection ifNotNil: [ ByteString adoptInstance: collection ].
- 	lastWritten ifNotNil:
- 		[ lastWritten isInteger ifTrue: [ lastWritten := lastWritten asCharacter ] ]!

Item was removed:
- ----- Method: StandardFileStream>>atEnd (in category 'read, write, position') -----
- atEnd
- 	"Answer whether the receiver is at its end.  "
- 	
- 	collection ifNotNil: [
- 		position < readLimit ifTrue: [ ^false ] ].
- 	^self primAtEnd: fileID!

Item was removed:
- ----- Method: StandardFileStream>>basicNext (in category 'read, write, position') -----
- basicNext
- 	"Answer the next byte from this file, or nil if at the end of the file."
- 	
- 	| count |
- 	<primitive: 65>
- 	collection ifNotNil: [
- 		position < readLimit 
- 			ifFalse: [ 
- 				readLimit := self primRead: fileID into: collection startingAt: 1 count: collection size.
- 				position := 0.
- 				readLimit = 0 ifTrue: [ ^nil ] ].
- 		^collection at: (position := position + 1) ].	
- 	count := self primRead: fileID into: buffer1 startingAt: 1 count: 1.
- 	count = 1
- 		ifTrue: [ ^buffer1 at: 1 ]
- 		ifFalse: [ ^nil ]!

Item was removed:
- ----- Method: StandardFileStream>>binary (in category 'properties-setting') -----
- binary
- 	"Read and/or write in binary mode."
- 	buffer1
- 		ifNil: [ buffer1 := ByteArray new: 1 ]
- 		ifNotNil: [ ByteArray adoptInstance: buffer1 ].
- 	collection ifNotNil: [ ByteArray adoptInstance: collection ].
- 	lastWritten ifNotNil:
- 		[ lastWritten isCharacter ifTrue: [ lastWritten := lastWritten asInteger ] ]!

Item was removed:
- ----- Method: StandardFileStream>>close (in category 'open/close') -----
- close
- 	"Close this file."
- 
- 	fileID ifNotNil: [
- 		collection ifNotNil: [
- 			readLimit := position := 0 ].
- 		self primClose: fileID.
- 		self unregister.
- 		fileID := nil].
- !

Item was removed:
- ----- Method: StandardFileStream>>closed (in category 'open/close') -----
- closed
- 	"Answer true if this file is closed."
- 
- 	^ fileID == nil or: [ (self primSizeNoError: fileID) == nil ]
- !

Item was removed:
- ----- Method: StandardFileStream>>collectionSpecies (in category 'private') -----
- collectionSpecies
- 	"Answer the species of collection into which the receiver can stream"
- 	
- 	^buffer1 species!

Item was removed:
- ----- Method: StandardFileStream>>directory (in category 'access') -----
- directory
- 	"Return the directory containing this file."
- 
- 	^ FileDirectory forFileName: self fullName
- !

Item was removed:
- ----- Method: StandardFileStream>>directoryUrl (in category 'access') -----
- directoryUrl
- 
- 	^ self directory url!

Item was removed:
- ----- Method: StandardFileStream>>disableReadBuffering (in category 'private') -----
- disableReadBuffering
- 
- 	collection ifNotNil: [
- 		position < readLimit
- 			ifTrue: [
- 				| currentPosition |
- 				currentPosition := self position.
- 				collection := readLimit := position := nil.
- 				self position: currentPosition ]
- 			ifFalse: [
- 				collection := readLimit := position := nil ] ]
- 		!

Item was removed:
- ----- Method: StandardFileStream>>enableReadBuffering (in category 'private') -----
- enableReadBuffering
- 
- 	collection ifNil: [
- 		buffer1 ifNotNil: [
- 			collection := self collectionSpecies new: 2048 ] ].
- 	readLimit := position := 0!

Item was removed:
- ----- Method: StandardFileStream>>ensureOpen (in category 'open/close') -----
- ensureOpen
- 	"Make sure that this file really is open."
- 
- 	self closed ifTrue: [^ self reopen].
- 	(self primSizeNoError: fileID) ifNotNil: [^ self].
- 	self reopen.
- !

Item was removed:
- ----- Method: StandardFileStream>>file (in category 'access') -----
- file
- 	"Answer the object representing the receiver's file.  Need for compatibility with some calls -- check senders.  2/14/96 sw"
- 
- 	^ self!

Item was removed:
- ----- Method: StandardFileStream>>finalize (in category 'finalization') -----
- finalize
- 	self primCloseNoError: fileID.!

Item was removed:
- ----- Method: StandardFileStream>>findString: (in category 'read, write, position') -----
- findString: string
- 	"Fast version of #upToAll: to find a String in a file starting from the beginning.
- 	Returns the position and also sets the position there.
- 	If string is not found 0 is returned and position is unchanged."
- 
- 	| pos buffer count oldPos sz |
- 	oldPos := self position.
- 	self reset.
- 	sz := self size.
- 	pos := 0.
- 	buffer := String new: 2000.
- 	[ buffer := self nextInto: buffer.
- 	(count := buffer findString: string) > 0
- 		ifTrue: ["Found the string part way into buffer"
- 			self position: pos.
- 			self next: count - 1.
- 			^self position ].
- 	pos := ((pos + 2000 - string size) min: sz).
- 	self position: pos.
- 	pos = sz] whileFalse.
- 	"Never found it, and hit end of file"
- 	self position: oldPos.
- 	^0!

Item was removed:
- ----- Method: StandardFileStream>>findStringFromEnd: (in category 'read, write, position') -----
- findStringFromEnd: string
- 	"Fast version to find a String in a file starting from the end.
- 	Returns the position and also sets the position there.
- 	If string is not found 0 is returned and position is unchanged."
- 
- 	| pos buffer count oldPos |
- 	oldPos := self position.
- 	self setToEnd.
- 	pos := self position.
- 	[ pos := ((pos - 2000 + string size) max: 0).  "the [+ string size] allows for the case where the end of the search string is at the beginning of the current buffer"
- 	self position: pos.
- 	buffer := self next: 2000.
- 	(count := buffer findString: string) > 0
- 		ifTrue: ["Found the string part way into buffer"
- 			self position: pos.
- 			self next: count-1.  "use next instead of position:, so that CrLfFileStream can do its magic if it is being used"
- 			^self position].
- 	pos = 0] whileFalse.
- 	"Never found it, and hit beginning of file"
- 	self position: oldPos.
- 	^0!

Item was removed:
- ----- Method: StandardFileStream>>flush (in category 'read, write, position') -----
- flush
- 	"Flush pending changes"
- 	^self primFlush: fileID!

Item was removed:
- ----- Method: StandardFileStream>>flushReadBuffer (in category 'private') -----
- flushReadBuffer
- 
- 	collection ifNotNil: [
- 		position < readLimit ifTrue: [
- 			| currentPosition |
- 			currentPosition := self position.
- 			position := readLimit := 0.
- 			self primSetPosition: fileID to: currentPosition ] ]!

Item was removed:
- ----- Method: StandardFileStream>>fullName (in category 'access') -----
- fullName
- 	"Answer this file's full path name."
- 
- 	^ name
- !

Item was removed:
- ----- Method: StandardFileStream>>getFileType (in category 'properties-setting') -----
- getFileType
- 	"On the Macintosh, get the file type and creator of this file. On other platforms, do nothing."
- 
- 	^FileDirectory default
- 		getMacFileTypeAndCreator: self fullName
- 		
- !

Item was removed:
- ----- Method: StandardFileStream>>insertLineFeeds (in category 'properties-setting') -----
- insertLineFeeds
- 	"(FileStream oldFileNamed: 'BBfix2.st') insertLineFeeds"
- 	| s crLf f |
- 	crLf := String crlf.
- 	s := self next: self size.
- 	self close.
- 	f := FileStream newFileNamed: self name.
- 	s linesDo: [:line | f nextPutAll: line; nextPutAll: crLf].
- 	f close!

Item was removed:
- ----- Method: StandardFileStream>>isBinary (in category 'properties-setting') -----
- isBinary
- 	^buffer1 isString not!

Item was removed:
- ----- Method: StandardFileStream>>isDirectory (in category 'access') -----
- isDirectory
- 	"Answer whether the receiver represents a directory.  For the post-transition case, uncertain what to do.  2/14/96 sw"
- 	^ false!

Item was removed:
- ----- Method: StandardFileStream>>isReadOnly (in category 'properties-setting') -----
- isReadOnly
- 
- 	^ rwmode not
- !

Item was removed:
- ----- Method: StandardFileStream>>localName (in category 'access') -----
- localName
- 	^ name ifNotNil: [(name findTokens: FileDirectory pathNameDelimiter asString) last]!

Item was removed:
- ----- Method: StandardFileStream>>name (in category 'access') -----
- name
- 	"Answer this file's full path name."
- 
- 	^ name
- !

Item was removed:
- ----- Method: StandardFileStream>>next (in category 'read, write, position') -----
- next
- 	"Answer the next byte from this file, or nil if at the end of the file."
- 
- 	^ self basicNext!

Item was removed:
- ----- Method: StandardFileStream>>next: (in category 'read, write, position') -----
- next: n
- 	"Return a string with the next n characters of the filestream in it.  1/31/96 sw"
- 	^ self nextInto: (self collectionSpecies new: n)!

Item was removed:
- ----- Method: StandardFileStream>>next:putAll:startingAt: (in category 'read, write, position') -----
- next: anInteger putAll: aString startingAt: startIndex
- 	"Store the next anInteger elements from the given collection."
- 	rwmode ifFalse: [^ self error: 'Cannot write a read-only file'].
- 	anInteger > 0 ifFalse: [ ^aString ].
- 	collection ifNotNil: [
- 		position < readLimit ifTrue: [ self flushReadBuffer ] ].	
- 	self primWrite: fileID from: aString startingAt: startIndex count: anInteger.
- 	^aString!

Item was removed:
- ----- Method: StandardFileStream>>nextPut: (in category 'read, write, position') -----
- nextPut: element
- 	"Write the given element (character or integer) to this file."
- 
- 	rwmode ifFalse: [^ self error: 'Cannot write a read-only file'].
- 	collection ifNotNil:
- 		[position < readLimit ifTrue: [ self flushReadBuffer ] ].
- 	buffer1 at: 1 put: element.
- 	self primWrite: fileID from: buffer1 startingAt: 1 count: 1.
- 	lastWritten := element.
- 	^ element
- !

Item was removed:
- ----- Method: StandardFileStream>>nextPutAll: (in category 'read, write, position') -----
- nextPutAll: aCollection
- 	"Write all the elements of the given collection (a String or IntegerArray of some kind) to this file."
- 	| size |
- 	rwmode ifFalse: [^ self error: 'Cannot write a read-only file'].
- 	collection ifNotNil:
- 		[position < readLimit ifTrue: [ self flushReadBuffer]].
- 	(size := aCollection basicSize) > 0 ifTrue:
- 		[self primWrite: fileID from: aCollection startingAt: 1 count: size.
- 		 lastWritten := aCollection at: size].
- 	^ aCollection!

Item was removed:
- ----- Method: StandardFileStream>>nextWordsInto: (in category 'read, write, position') -----
- nextWordsInto: aBitmap
- 	"Note: The file primitives automatically adjust for word based objects."
- 
- 	self next: aBitmap basicSize into: aBitmap startingAt: 1.
- 	aBitmap restoreEndianness.
- 	^ aBitmap!

Item was removed:
- ----- Method: StandardFileStream>>open (in category 'open/close') -----
- open
- 	"For compatibility with a few existing things.  2/14/96 sw"
- 
- 	^ self reopen!

Item was removed:
- ----- Method: StandardFileStream>>open:forWrite: (in category 'open/close') -----
- open: fileName forWrite: writeMode 
- 	"Open the file with the given name. If writeMode is true, allow writing, otherwise open the file in read-only mode."
- 	"Changed to do a GC and retry before failing ar 3/21/98 17:25"
- 	| f newFileID |
- 	f := fileName asVmPathName.
- 	
- 	fileID := nil.
- 	fileID := [StandardFileStream
- 		retryWithGC:
- 			[newFileID := nil.
- 			newFileID := self primOpen: f writable: writeMode] 
- 		until: [:id | id notNil] 
- 		forFileNamed: fileName]
- 			ifCurtailed:
- 				[newFileID ifNotNil: [self primClose: newFileID]].
- 	fileID ifNil: [^ nil].  "allows sender to detect failure"
- 	name := fileName.
- 	self register.
- 	rwmode := writeMode.
- 	buffer1 := String new: 1.
- 	self enableReadBuffering.!

Item was removed:
- ----- Method: StandardFileStream>>openOnHandle:name:forWrite: (in category 'open/close') -----
- openOnHandle: aFileID name: streamName forWrite: writeMode
- 	"Initialize the file with the given handle. If writeMode is true then
- 	 allow writing, otherwise put the file in read-only mode.
- 	 N.B. Do _not_ register the stream.  We do not want it to be
- 	 closed implicitly (e.g. on GC).  There may be multiple instances
- 	 accessing the same stream.  The stream is not a file."
- 	fileID := aFileID.
- 	name := streamName.
- 	rwmode := writeMode.
- 	buffer1 := String new: 1.
- 	self enableReadBuffering!

Item was removed:
- ----- Method: StandardFileStream>>openReadOnly (in category 'open/close') -----
- openReadOnly
- 	"Open the receiver as a read-only file.  1/31/96 sw"
- 
- 	^ self open: name forWrite: false!

Item was removed:
- ----- Method: StandardFileStream>>padToEndWith: (in category 'read, write, position') -----
- padToEndWith: aChar
- 	"On the Mac, files do not truncate.  One can delete the old file and write a new one, but sometime deletion fails (file still open? file stale?).  This is a sad compromise.  Just let the file be the same length but pad it with a harmless character."
- 
- 	| pad |
- 	self atEnd ifTrue: [^ self].
- 	pad := self isBinary 
- 		ifTrue: [aChar asCharacter asciiValue]	"ok for char or number"
- 		ifFalse: [aChar asCharacter].
- 	self nextPutAll: (self collectionSpecies new: ((self size - self position) min: 20000) 
- 							withAll: pad).!

Item was removed:
- ----- Method: StandardFileStream>>peek (in category 'read, write, position') -----
- peek
- 	"Answer what would be returned if the message next were sent to the receiver. If the receiver is at the end, answer nil."
- 	
- 	| next |
- 	next := self basicNext ifNil: [ ^nil ].
- 	collection ifNotNil: [
- 		"#basicNext ensures that this is enough"
- 		position := position - 1.
- 		^next ].
- 	self skip: -1.
- 	^next!

Item was removed:
- ----- Method: StandardFileStream>>peekFor: (in category 'access') -----
- peekFor: item 
- 	"Answer false and do not advance if the next element is not equal to item, or if this stream is at the end.  If the next element is equal to item, then advance over it and return true"
- 
- 	"self atEnd ifTrue: [^ false]. -- SFStream will give nil"
- 	(self next ifNil: [ ^false ]) = item ifTrue: [ ^true ].
- 	self skip: -1.
- 	^ false!

Item was removed:
- ----- Method: StandardFileStream>>peekLast (in category 'read, write, position') -----
- peekLast
- 	"Answer the item just put at the end of the stream, if any."
- 
- 	^lastWritten!

Item was removed:
- ----- Method: StandardFileStream>>position (in category 'read, write, position') -----
- position
- 	"Return the receiver's current file position.  2/12/96 sw"
- 
- 	collection ifNotNil: [
- 		position < readLimit ifTrue: [
- 			^(self primGetPosition: fileID) - readLimit + position ] ].
- 	^self primGetPosition: fileID!

Item was removed:
- ----- Method: StandardFileStream>>position: (in category 'read, write, position') -----
- position: pos
- 	"Set the receiver's position as indicated.  2/12/96 sw"
- 
- 	collection ifNotNil: [
- 		position < readLimit ifTrue: [
- 			| newPosition |
- 			newPosition := pos - (self primGetPosition: fileID) + readLimit.
- 			newPosition < 0 ifTrue: [
- 					| offsetPos |
- 					self primSetPosition: fileID to: (offsetPos := pos - (collection size // 4) max: 0).
- 					readLimit := self primRead: fileID into: collection startingAt: 1 count: collection size.
- 					position := pos - offsetPos.
- 					^self ].
- 			newPosition < readLimit 
- 				ifTrue: [
- 					position := newPosition.
- 					^self ]
- 				ifFalse: [
- 					readLimit := position := 0 ] ] ].
- 	^self primSetPosition: fileID to: pos!

Item was removed:
- ----- Method: StandardFileStream>>primAtEnd: (in category 'primitives') -----
- primAtEnd: id
- 	"Answer true if the file position is at the end of the file."
- 
- 	<primitive: 'primitiveFileAtEnd' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: StandardFileStream>>primClose: (in category 'primitives') -----
- primClose: id
- 	"Close this file."
- 
- 	<primitive: 'primitiveFileClose' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: StandardFileStream>>primCloseNoError: (in category 'primitives') -----
- primCloseNoError: id
- 	"Close this file. Don't raise an error if the primitive fails."
- 
- 	<primitive: 'primitiveFileClose' module: 'FilePlugin'>
- !

Item was removed:
- ----- Method: StandardFileStream>>primDropRequestFileHandle: (in category 'dnd requests') -----
- primDropRequestFileHandle: dropIndex
- 	"Primitive. Return the (read-only) file handle for some file that was just dropped onto Squeak.
- 	Fail if dropIndex is out of range or the primitive is not supported."
- 	<primitive: 'primitiveDropRequestFileHandle' module:'DropPlugin'>
- 	^nil!

Item was removed:
- ----- Method: StandardFileStream>>primFlush: (in category 'primitives') -----
- primFlush: id
- 	"Flush pending changes to the disk"
- 	| p |
- 	<primitive: 'primitiveFileFlush' module: 'FilePlugin'>
- 	"In some OS's seeking to 0 and back will do a flush"
- 	p := self position.
- 	self position: 0; position: p!

Item was removed:
- ----- Method: StandardFileStream>>primGetPosition: (in category 'primitives') -----
- primGetPosition: id
- 	"Get this files current position."
- 
- 	<primitive: 'primitiveFileGetPosition' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: StandardFileStream>>primOpen:writable: (in category 'primitives') -----
- primOpen: fileName writable: writableFlag
- 	"Open a file of the given name, and return the file ID obtained.
- 	If writableFlag is true, then
- 		if there is none with this name, then create one
- 		else prepare to overwrite the existing from the beginning
- 	otherwise
- 		if the file exists, open it read-only
- 		else return nil"
- 
- 	<primitive: 'primitiveFileOpen' module: 'FilePlugin'>
- 	^ nil
- !

Item was removed:
- ----- Method: StandardFileStream>>primRead:into:startingAt:count: (in category 'primitives') -----
- primRead: id into: byteArray startingAt: startIndex count: count
- 	"Read up to count bytes of data from this file into the given string or byte array starting at the given index. Answer the number of bytes actually read."
- 
- 	<primitive: 'primitiveFileRead' module: 'FilePlugin'>
- 	self closed ifTrue: [^ self error: 'File is closed'].
- 	self error: 'File read failed'.
- !

Item was removed:
- ----- Method: StandardFileStream>>primSetPosition:to: (in category 'primitives') -----
- primSetPosition: id to: anInteger
- 	"Set this file to the given position."
- 
- 	<primitive: 'primitiveFileSetPosition' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: StandardFileStream>>primSize: (in category 'primitives') -----
- primSize: id
- 	"Answer the size of this file."
- 
- 	<primitive: 'primitiveFileSize' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: StandardFileStream>>primSizeNoError: (in category 'primitives') -----
- primSizeNoError: id
- 	"Answer the size of this file. Answer nil if the primitive fails; this indicates that the file handle has become stale."
- 
- 	<primitive: 'primitiveFileSize' module: 'FilePlugin'>
- 	^ nil
- !

Item was removed:
- ----- Method: StandardFileStream>>primSync: (in category 'primitives') -----
- primSync: id
- 	"Call fsync to really, really, flush pending changes to the disk"
- 	| p |
- 	<primitive: 'primitiveFileSync' module: 'FilePlugin'>
- 	"In some OS's seeking to 0 and back will do a flush. Maybe that will help if we dont have the primitives"
- 	p := self position.
- 	self position: 0; position: p!

Item was removed:
- ----- Method: StandardFileStream>>primTruncate:to: (in category 'primitives') -----
- primTruncate: id to: anInteger
- 	"Truncate this file to the given position."
- 
- 	<primitive: 'primitiveFileTruncate' module: 'FilePlugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: StandardFileStream>>primWrite:from:startingAt:count: (in category 'primitives') -----
- primWrite: id from: stringOrByteArray startingAt: startIndex count: count
- 	"Write count bytes onto this file from the given string or byte array starting at the given index. Answer the number of bytes written."
- 
- 	<primitive: 'primitiveFileWrite' module: 'FilePlugin'>
- 	(FileWriteError fileName: name)
- 		signal: (self closed
- 			ifTrue: [ 'File ', name, ' is closed' ]
- 			ifFalse: [ 'File ', name, ' write failed' ])!

Item was removed:
- ----- Method: StandardFileStream>>printOn: (in category 'access') -----
- printOn: aStream
- 	"Put a printed version of the receiver onto aStream.  1/31/96 sw"
- 
- 	aStream nextPutAll: self class name; nextPutAll: ': '; print: name!

Item was removed:
- ----- Method: StandardFileStream>>readInto:startingAt:count: (in category 'read, write, position') -----
- readInto: byteArray startingAt: startIndex count: count
- 	"Read into the given array as specified, and return the count
- 	actually transferred.  index and count are in units of bytes or
- 	longs depending on whether the array is Bitmap, String or ByteArray"
- 	
- 	| nRead newN newStartIndex |
- 	collection 
- 		ifNil: [ 
- 			newN := count.
- 			newStartIndex := startIndex ]
- 		ifNotNil: [
- 			byteArray class isBytes 
- 				ifFalse: [ 
- 					position < readLimit ifTrue: [ self flushReadBuffer ].
- 					newN := count.
- 					newStartIndex := startIndex ]
- 				ifTrue: [
- 					| available |
- 					(available := readLimit - position) > 0 
- 						ifFalse: [ available := 0 ]
- 						ifTrue: [
- 							| bufferedCount |
- 							bufferedCount := count min: available.
- 							byteArray
- 								replaceFrom: startIndex
- 								to: startIndex + bufferedCount - 1
- 								with: collection
- 								startingAt: position + 1.
- 							position := position + bufferedCount.
- 							bufferedCount = count ifTrue: [ ^count ] ].
- 					newN := count - available.
- 					newStartIndex := startIndex + available ] ].
- 	nRead := self primRead: fileID into: byteArray startingAt: newStartIndex count: newN.
- 	^nRead + (count - newN)!

Item was removed:
- ----- Method: StandardFileStream>>readOnly (in category 'properties-setting') -----
- readOnly
- 	"Make this file read-only."
- 
- 	rwmode := false.
- !

Item was removed:
- ----- Method: StandardFileStream>>readOnlyCopy (in category 'read, write, position') -----
- readOnlyCopy
- 	self flush.	"Some linux open a truncated readOnlyCopy. Force it to take latest bytes written into account."
- 	^ self class readOnlyFileNamed: self name.
- !

Item was removed:
- ----- Method: StandardFileStream>>readWrite (in category 'properties-setting') -----
- readWrite
- 	"Make this file writable."
- 
- 	rwmode := true.
- !

Item was removed:
- ----- Method: StandardFileStream>>register (in category 'registry') -----
- register
- 	^self class register: self!

Item was removed:
- ----- Method: StandardFileStream>>reopen (in category 'open/close') -----
- reopen
- 	"Close and reopen this file. The file position is reset to zero."
- 	"Details: Files that were open when a snapshot occurs are no longer valid when the snapshot is resumed. This operation re-opens the file if that has happened."
- 
- 	fileID ifNotNil: [
- 		collection ifNotNil: [
- 			position < readLimit ifTrue: [
- 				self flushReadBuffer ] ].
- 		self primCloseNoError: fileID ].
- 	self open: name forWrite: rwmode.
- !

Item was removed:
- ----- Method: StandardFileStream>>requestDropStream: (in category 'dnd requests') -----
- requestDropStream: dropIndex
- 	"Answer a read-only stream for some file the user has just dropped onto Squeak,
- 	 or nil if dropIndex does not refer to a file."
- 	^(self class primDropRequestFileName: dropIndex) ifNotNil:
- 		[:rawName|
- 		name := rawName vmPathToSqueakPath.
- 		fileID := self primDropRequestFileHandle: dropIndex.
- 		fileID ifNotNil:
- 			[self register.
- 			rwmode := false.
- 			buffer1 := String new: 1.
- 			self enableReadBuffering.
- 			self]]!

Item was removed:
- ----- Method: StandardFileStream>>reset (in category 'access') -----
- reset
- 	self ensureOpen.
- 	self position: 0.!

Item was removed:
- ----- Method: StandardFileStream>>setFileTypeToObject (in category 'properties-setting') -----
- setFileTypeToObject
- 	"On the Macintosh, set the file type and creator of this file to be a Squeak object file. On other platforms, do nothing. Setting the file type allows Squeak object files to be sent as email attachments and launched by double-clicking. On other platforms, similar behavior is achieved by creating the file with the '.sqo' file name extension."
- 
- 	FileDirectory default
- 		setMacFileNamed: self fullName
- 		type: 'SOBJ'
- 		creator: 'FAST'.
- !

Item was removed:
- ----- Method: StandardFileStream>>setToEnd (in category 'read, write, position') -----
- setToEnd
- 	"Set the position of the receiver to the end of file.  1/31/96 sw"
- 
- 	self position: self size!

Item was removed:
- ----- Method: StandardFileStream>>size (in category 'access') -----
- size
- 	"Answer the size of the file in characters.  2/12/96 sw"
- 
- 	^ self primSize: fileID!

Item was removed:
- ----- Method: StandardFileStream>>skip: (in category 'read, write, position') -----
- skip: n
- 	"Set the character position to n characters from the current position.
- 	Error if not enough characters left in the file.  1/31/96 sw"
- 
- 	collection ifNotNil: [
- 		position < readLimit ifTrue: [
- 			| newPosition |
- 			((newPosition := position + n) >= 0 and: [ newPosition < readLimit ])
- 				ifTrue: [ 
- 					position := newPosition.
- 					^self ] ] ].
- 	self position: self position + n!

Item was removed:
- ----- Method: StandardFileStream>>sync (in category 'read, write, position') -----
- sync
- 	"Really, really, flush pending changes"
- 	^self flush; primSync: fileID!

Item was removed:
- ----- Method: StandardFileStream>>truncate (in category 'read, write, position') -----
- truncate
- 	"Truncate to zero"
- 
- 	^ self truncate: 0!

Item was removed:
- ----- Method: StandardFileStream>>truncate: (in category 'read, write, position') -----
- truncate: pos
- 	"Truncate to this position"
- 
- 	self position: pos.
- 	^self primTruncate: fileID to: pos!

Item was removed:
- ----- Method: StandardFileStream>>unregister (in category 'registry') -----
- unregister
- 	^self class unregister: self!

Item was removed:
- ----- Method: StandardFileStream>>upTo: (in category 'read, write, position') -----
- upTo: delimiter
- 
- 	| pos |
- 	collection ifNotNil: [
- 		(position < readLimit and: [
- 			(pos := collection indexOf: delimiter startingAt: position + 1) <= readLimit and: [
- 				pos > 0 ] ]) ifTrue: [
- 					^collection copyFrom: position + 1 to: (position := pos) - 1 ] ].
- 	^self collectionSpecies streamContents: [ :stream |
- 		| buffer bytesRead |
- 		buffer := collection 
- 			ifNil: [ self collectionSpecies new: 2000 ]
- 			ifNotNil: [
- 				position < readLimit ifTrue: [
- 					stream next: readLimit - position putAll: collection startingAt: position + 1.
- 					position := readLimit ].
- 				collection ].
- 		[
- 			bytesRead := self readInto: buffer startingAt: 1 count: buffer size.
- 			((pos := buffer indexOf: delimiter startingAt: 1) = 0 or: [ pos > bytesRead ])
- 				ifTrue: [ 
- 					stream next: bytesRead putAll: buffer startingAt: 1.
- 					bytesRead > 0 "Try again if we could read something last time." ]
- 				ifFalse: [
- 					stream next: pos - 1 putAll: buffer startingAt: 1.
- 					collection 
- 						ifNil: [ self skip: pos - bytesRead ]
- 						ifNotNil: [
- 							position := pos.
- 							readLimit := bytesRead ].
- 					false "Found the delimiter." ] ] whileTrue ]!

Item was removed:
- ----- Method: StandardFileStream>>upToAnyOf:do: (in category 'read, write, position') -----
- upToAnyOf: delimiters do: aBlock
- 
- 	| pos |
- 	collection ifNotNil: [
- 		(position < readLimit and: [
- 			(pos := collection indexOfAnyOf: delimiters startingAt: position + 1) <= readLimit and: [
- 				pos > 0 ] ]) ifTrue: [
- 					| result |
- 					result := collection copyFrom: position + 1 to: (position := pos) - 1 .
- 					aBlock value: (collection at: position).
- 					^result ] ].
- 	^self collectionSpecies streamContents: [ :stream |
- 		| buffer bytesRead |
- 		buffer := collection 
- 			ifNil: [ self collectionSpecies new: 2000 ]
- 			ifNotNil: [
- 				position < readLimit ifTrue: [
- 					stream next: readLimit - position putAll: collection startingAt: position + 1.
- 					position := readLimit ].
- 				collection ].
- 		[
- 			bytesRead := self readInto: buffer startingAt: 1 count: buffer size.
- 			((pos := buffer indexOfAnyOf: delimiters startingAt: 1) = 0 or: [ pos > bytesRead ])
- 				ifTrue: [ 
- 					stream next: bytesRead putAll: buffer startingAt: 1.
- 					bytesRead > 0 "Try again if we could read something last time." ]
- 				ifFalse: [
- 					stream next: pos - 1 putAll: buffer startingAt: 1.
- 					collection 
- 						ifNil: [ self skip: pos - bytesRead ]
- 						ifNotNil: [
- 							position := pos.
- 							readLimit := bytesRead ].
- 					false "Found the delimiter." ] ] whileTrue.
- 		bytesRead = 0 ifFalse: [
- 			aBlock value: (buffer at: pos) ] ]!

Item was removed:
- ----- Method: StandardFileStream>>upToEnd (in category 'read, write, position') -----
- upToEnd
- 	"Answer a subcollection from the current access position through the last element of the receiver."
- 
- 	^self next: self size - self position!

Item was removed:
- ----- Method: StandardFileStream>>update: (in category 'updating') -----
- update: aParameter
- 	super update: aParameter.
- 	aParameter == #appendEntry 
- 		ifTrue: [self flush]. "Transcript is being redirected to this steam, stdout"
- 	!

Item was removed:
- ----- Method: StandardFileStream>>verbatim: (in category 'read, write, position') -----
- verbatim: aString
- 	"A version of nextPutAll that can be called knowing it won't call nextPut: "
- 
- 	^ self nextPutAll: aString
- !

Item was removed:
- SourceFileArray subclass: #StandardSourceFileArray
- 	instanceVariableNames: 'files'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-System'!
- 
- !StandardSourceFileArray commentStamp: '<historical>' prior: 0!
- This class implements the source file management behavior of traditional Squeak, with a sources file and a changes file. File positions are mapped such that those files can be up to 32MBytes in size.
- 
- Structure:
-  files		Array -- storing the actual source files
- !

Item was removed:
- ----- Method: StandardSourceFileArray class>>new: (in category 'initialize-release') -----
- new: nFiles
- 	^self new initialize: nFiles.!

Item was removed:
- ----- Method: StandardSourceFileArray>>at: (in category 'accessing') -----
- at: index
- 	^files at: index!

Item was removed:
- ----- Method: StandardSourceFileArray>>at:put: (in category 'accessing') -----
- at: index put: aFile
- 	^files at: index put: aFile!

Item was removed:
- ----- Method: StandardSourceFileArray>>checkOKToAdd:at: (in category 'sourcePointer conversion') -----
- checkOKToAdd: size at: filePosition
- 	"Issue several warnings as the end of the changes file approaches its limit,
- 	and finally halt with an error when the end is reached."
- 
- 	| fileSizeLimit margin |
- 	fileSizeLimit := 16r2000000.
- 	3 to: 1 by: -1 do:
- 		[:i | margin := i*100000.
- 		(filePosition + size + margin) > fileSizeLimit
- 			ifTrue: [(filePosition + margin) > fileSizeLimit ifFalse:
- 						[self inform: 'WARNING: your changes file is within
- ' , margin printString , ' characters of its size limit.
- You should take action soon to reduce its size.
- You may proceed.']]
- 			ifFalse: [^ self]].
- 	(filePosition + size > fileSizeLimit) ifFalse: [^ self].
- 	self error: 'You have reached the size limit of the changes file.
- You must take action now to reduce it.
- Close this error.  Do not attempt to proceed.'!

Item was removed:
- ----- Method: StandardSourceFileArray>>fileIndexFromSourcePointer: (in category 'sourcePointer conversion') -----
- fileIndexFromSourcePointer: anInteger
- 	"Return the index of the source file which contains the source chunk addressed by anInteger"
- 	"This implements the recent 32M source file algorithm"
- 
- 	| hi |
- 	hi := anInteger // 16r1000000.
- 	^hi < 3
- 		ifTrue: [hi]
- 		ifFalse: [hi - 2]!

Item was removed:
- ----- Method: StandardSourceFileArray>>filePositionFromSourcePointer: (in category 'sourcePointer conversion') -----
- filePositionFromSourcePointer: anInteger
- 	"Return the position of the source chunk addressed by anInteger"
- 	"This implements the recent 32M source file algorithm"
- 
- 	| hi lo |
- 	hi := anInteger // 16r1000000.
- 	lo := anInteger \\ 16r1000000.
- 	^hi < 3
- 		ifTrue: [lo]
- 		ifFalse: [lo + 16r1000000]!

Item was removed:
- ----- Method: StandardSourceFileArray>>initialize (in category 'initialize-release') -----
- initialize
- 	files := Array new: 2.
- 	files at: 1 put: (SourceFiles at: 1).
- 	files at: 2 put: (SourceFiles at: 2)!

Item was removed:
- ----- Method: StandardSourceFileArray>>initialize: (in category 'initialize-release') -----
- initialize: nFiles
- 	files := Array new: nFiles!

Item was removed:
- ----- Method: StandardSourceFileArray>>size (in category 'accessing') -----
- size
- 	^files size!

Item was removed:
- ----- Method: StandardSourceFileArray>>sourcePointerFromFileIndex:andPosition: (in category 'sourcePointer conversion') -----
- sourcePointerFromFileIndex: index andPosition: position
- 	| hi lo |
- 	"Return a source pointer according to the new 32M algorithm"
- 	((index between: 1 and: 2) and: [position between: 0 and: 16r1FFFFFF])
- 		ifFalse: [self error: 'invalid source code pointer'].
- 	hi := index.
- 	lo := position.
- 	lo >= 16r1000000 ifTrue: [
- 		hi := hi+2.
- 		lo := lo - 16r1000000].
- 	^hi * 16r1000000 + lo!

Item was removed:
- ----- Method: String>>asDirectoryEntry (in category '*files') -----
- asDirectoryEntry
- 	^ FileDirectory directoryEntryFor: self!

Item was removed:
- FileDirectory subclass: #UnixFileDirectory
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Files-Directories'!
- 
- !UnixFileDirectory commentStamp: 'tpr 12/26/2017 13:44' prior: 0!
- I represent a Unix FileDirectory.
- 
- It is worth noting that the various enumeration methods do *not* include the parent and local directory pseudo-names '.' and '..'. They are filtered out in the primitive that reads the directory entries.
- !

Item was removed:
- ----- Method: UnixFileDirectory class>>maxFileNameLength (in category 'platform specific') -----
- maxFileNameLength
- 
- 	^ 255!

Item was removed:
- ----- Method: UnixFileDirectory class>>pathNameDelimiter (in category 'platform specific') -----
- pathNameDelimiter
- 
- 	^ $/
- !

Item was removed:
- ----- Method: UnixFileDirectory>>checkName:fixErrors: (in category 'file names') -----
- checkName: aFileName fixErrors: fixing
- 	"Check if the file name contains any invalid characters"
- 	| fName |
- 	fName := super checkName: aFileName fixErrors: fixing.
- 	(fName includes: self class pathNameDelimiter) ifFalse:
- 		[^fName].
- 	^fixing
- 		ifTrue: [fName copyReplaceAll: (String with: self class pathNameDelimiter) with: '#']
- 		ifFalse: [self error:'Invalid file name']!

Item was removed:
- ----- Method: UnixFileDirectory>>directoryExists: (in category 'testing') -----
- directoryExists: filenameOrPath
- 	"Answers true if the directory exists.  Overrides to handle the root directory /
- 	 and relative paths."
- 	| fName dir |
- 
- 	filenameOrPath = '/' ifTrue:
- 		[^true].
- 
- 	DirectoryClass
- 		splitName: filenameOrPath
- 		to: [:filePath :name |
- 			fName := name.
- 			dir := filePath isEmpty
- 					ifTrue: [self]
- 					ifFalse:
- 						[FileDirectory on: (filePath first = $/
- 											ifTrue: [filePath]
- 											ifFalse: [self fullName, '/', filePath])]].
- 
- 	^dir exists
- 	  and: [(dir directoryEntryForName: fName)
- 			ifNotNil: [:e| e isDirectory]
- 			ifNil: [false]]!

Item was removed:
- ----- Method: UnixFileDirectory>>fileOrDirectoryExists: (in category 'testing') -----
- fileOrDirectoryExists: filenameOrPath
- 	"Answer true if either a file or a directory file of the given name exists. The given name
- 	 may be either a full path name or a local name within this directory. Overrides to handle
- 	 the root directory / and relative paths."
- 	| fName dir |
- 
- 	filenameOrPath = '/' ifTrue:
- 		[^true].
- 
- 	DirectoryClass
- 		splitName: filenameOrPath
- 		to: [:filePath :name |
- 			fName := name.
- 			dir := filePath isEmpty
- 					ifTrue: [self]
- 					ifFalse:
- 						[FileDirectory on: (filePath first = $/
- 											ifTrue: [filePath]
- 											ifFalse: [self fullName, '/', filePath])]].
- 
- 	^dir exists
- 	  and: [(dir includesKey: fName) or: [fName isEmpty and: [dir entries size > 1]]]!

Item was removed:
- ----- Method: UnixFileDirectory>>fullPathFor: (in category 'file names') -----
- fullPathFor: path
- 	"Return the fully-qualified path name for the given file."
- 	path isEmpty ifTrue: [^ pathName asSqueakPathName].
- 	path first = $/ ifTrue: [^ path].
- 	^ pathName asSqueakPathName = '/'			"Only root dir ends with a slash"
- 		ifTrue: ['/' , path]
- 		ifFalse: [pathName asSqueakPathName , '/' , path]!

Item was removed:
- ----- Method: UnixFileDirectory>>pathFromUrl: (in category 'file names') -----
- pathFromUrl: aFileUrl
- 	^'/', (super pathFromUrl: aFileUrl)!

Item was removed:
- ----- Method: UnixFileDirectory>>setPathName: (in category 'private') -----
- setPathName: pathString
- 	"Unix path names start with a leading delimiter character."
- 
- 	(pathString isEmpty or: [pathString first ~= self pathNameDelimiter])
- 		ifTrue: [pathName := FilePath pathName: (self pathNameDelimiter asString, pathString)]
- 		ifFalse: [pathName := FilePath pathName: pathString].
- !

Item was removed:
- (PackageInfo named: 'Files') postscript: '| handleArray |
- handleArray := StandardFileStream classPool at: #StdioHandles.
- (handleArray isNil or: [ handleArray allSatisfy: [ :each | each isNil ] ])	
- 	ifTrue: [ StandardFileStream startUp: true ]'!



More information about the Squeak-dev mailing list