|
|
6.67 FileDescriptor
- Defined in namespace Smalltalk
- Category: Streams-Files
- My instances are what conventional programmers think of as files.
My instance creation methods accept the name of a disk file (or any named
file object, such as /dev/rmt0 on UNIX or MTA0: on VMS).
6.67.1 FileDescriptor class: initialization
- initialize
- Initialize the receiver's class variables
- update: aspect
- Close open files before quitting
6.67.2 FileDescriptor class: instance creation
- append
- Open for writing. The file is created if it does not exist. The stream is positioned at the end of the file.
- create
- Open for reading and writing. The file is created if it does not exist, otherwise it is truncated. The stream is positioned at the beginning of the file.
- on: fd
- Open a FileDescriptor on the given file descriptor. Read-write access is assumed.
- open: fileName
- Open fileName in read-write mode - fail if the file cannot be opened. Else answer a new FileStream. The file will be automatically closed upon GC if the object is not referenced anymore, but you should close it with #close anyway. To keep a file open, send it #removeToBeFinalized
- open: fileName mode: fileMode
- Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and fail if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any standard C non-binary fopen mode. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized
- open: fileName mode: fileMode ifFail: aBlock
- Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and evaluate aBlock if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized
- popen: commandName dir: direction
- Open a pipe on the given command and fail if the file cannot be opened. Else answer a new FileStream. The pipe will not be automatically closed upon GC, even if the object is not referenced anymore, because when you close a pipe you have to wait for the associated process to terminate. To enforce automatic closing of the pipe, send it #addToBeFinalized. direction is returned by #read or #write ('r' or 'w') and is interpreted from the point of view of Smalltalk: reading means Smalltalk reads the standard output of the command, writing means Smalltalk writes the standard input of the command. The other channel (stdin when reading, stdout when writing) is the same as GST's, unless commandName alters it.
- popen: commandName dir: direction ifFail: aBlock
- Open a pipe on the given command and evaluate aBlock file cannot be opened. Else answer a new FileStream. The pipe will not be automatically closed upon GC, even if the object is not referenced anymore, because when you close a pipe you have to wait for the associated process to terminate. To enforce automatic closing of the pipe, send it #addToBeFinalized. direction is interpreted from the point of view of Smalltalk: reading means that Smalltalk reads the standard output of the command, writing means that Smalltalk writes the standard input of the command
- read
- Open text file for reading. The stream is positioned at the beginning of the file.
- readWrite
- Open for reading and writing. The stream is positioned at the beginning of the file.
- write
- Truncate file to zero length or create text file for writing. The stream is positioned at the beginning of the file.
6.67.3 FileDescriptor: accessing
- canRead
- Answer whether the file is open and we can read from it
- canWrite
- Answer whether the file is open and we can write from it
- ensureReadable
- If the file is open, wait until data can be read from it. The wait allows other Processes to run.
- ensureWriteable
- If the file is open, wait until we can write to it. The wait allows other Processes to run.
- exceptionalCondition
- Answer whether the file is open and an exceptional condition (such as presence of out of band data) has occurred on it
- fd
- Return the OS file descriptor of the file
- isOpen
- Answer whether the file is still open
- isPipe
- Answer whether the file is a pipe or an actual disk file
- name
- Return the name of the file
- waitForException
- If the file is open, wait until an exceptional condition (such as presence of out of band data) has occurred on it. The wait allows other Processes to run.
6.67.4 FileDescriptor: basic
- close
- Close the file
- contents
- Answer the whole contents of the file
- copyFrom: from to: to
- Answer the contents of the file between the two given positions
- finalize
- Close the file if it is still open by the time the object becomes garbage.
- invalidate
- Invalidate a file descriptor
- next
- Return the next character in the file, or nil at eof
- nextByte
- Return the next byte in the file, or nil at eof
- nextPut: aCharacter
- Store aCharacter on the file
- nextPutByte: anInteger
- Store the byte, anInteger, on the file
- nextPutByteArray: aByteArray
- Store aByteArray on the file
- position
- Answer the zero-based position from the start of the file
- position: n
- Set the file pointer to the zero-based position n
- reset
- Reset the stream to its beginning
- size
- Return the current size of the file, in bytes
- truncate
- Truncate the file at the current position
6.67.5 FileDescriptor: built ins
- fileOp: ioFuncIndex
- Private - Used to limit the number of primitives used by FileStreams
- fileOp: ioFuncIndex ifFail: aBlock
- Private - Used to limit the number of primitives used by FileStreams.
- fileOp: ioFuncIndex with: arg1
- Private - Used to limit the number of primitives used by FileStreams
- fileOp: ioFuncIndex with: arg1 ifFail: aBlock
- Private - Used to limit the number of primitives used by FileStreams.
- fileOp: ioFuncIndex with: arg1 with: arg2
- Private - Used to limit the number of primitives used by FileStreams
- fileOp: ioFuncIndex with: arg1 with: arg2 ifFail: aBlock
- Private - Used to limit the number of primitives used by FileStreams.
- fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3
- Private - Used to limit the number of primitives used by FileStreams
- fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 ifFail: aBlock
- Private - Used to limit the number of primitives used by FileStreams.
6.67.6 FileDescriptor: class type methods
- isBinary
- We answer characters, so answer false
- isExternalStream
- We stream on an external entity (a file), so answer true
- isText
- We answer characters, so answer true
6.67.7 FileDescriptor: initialize-release
- initialize
- Initialize the receiver's instance variables
- newBuffer
- Private - Answer a String to be used as the receiver's buffer
- nextHunk
- Answer the next buffers worth of stuff in the Stream represented by the receiver. Do at most one actual input operation.
6.67.8 FileDescriptor: low-level access
- read: byteArray
- Ignoring any buffering, try to fill byteArray with the contents of the file
- read: byteArray from: position to: end
- Ignoring any buffering, try to fill the given range of byteArray with the contents of the file
- read: byteArray numBytes: anInteger
- Ignoring any buffering, try to fill anInteger bytes of byteArray with the contents of the file
- write: byteArray
- Ignoring any buffering, try to write the contents of byteArray in the file
- write: byteArray from: position to: end
- Ignoring any buffering, try to write to the file the given range of byteArray, starting at index position.
- write: byteArray numBytes: anInteger
- Ignoring any buffering, try to write to the file the first anInteger bytes of byteArray
6.67.9 FileDescriptor: overriding inherited methods
- isEmpty
- Answer whether the receiver is empty
- next: anInteger
- Return the next 'anInteger' characters from the stream, as a String.
- nextByteArray: anInteger
- Return the next 'anInteger' bytes from the stream, as a ByteArray.
- nextPutAll: aCollection
- Put all the characters in aCollection in the file
- reverseContents
- Return the contents of the file from the last byte to the first
- setToEnd
- Reset the file pointer to the end of the file
- skip: anInteger
- Skip anInteger bytes in the file
6.67.10 FileDescriptor: printing
- printOn: aStream
- Print a representation of the receiver on aStream
6.67.11 FileDescriptor: testing
- atEnd
- Answer whether data has come to an end
|