IO.mesa
Copyright Ó 1985, 1986, 1987, 1991 by Xerox Corporation. All rights reserved.
MBrown on September 20, 1983 11:53 pm
Andrew Birrell on June 6, 1983 10:34 am
Paul Rovner on May 23, 1983 9:31 am
Teitelman on January 12, 1983 3:01 pm
Russ Atkinson (RRA) February 2, 1985 12:38:05 pm PST
Beach, February 27, 1985 10:20:51 am PST
Michael Plass, November 22, 1991 3:31 pm PST
Doug Wyatt, August 16, 1991 12:48 pm PDT
This interface defines STREAM, the Cedar byte stream abstraction. It defines the generic operations on streams and procs for implementing a new stream class. It also contains create procs for creating certain types of streams (for instance, stream to/from rope), procs for performing output conversion and writing the results to a stream, procs for reading from a stream and performing input conversion.
This interface is structured for reference use, and does not contain complete documentation. The Convert, IOUtils, and IOClasses interfaces contain related procedures. See IODoc.tioga for complete documentation.
DIRECTORY
Ascii USING [CR, SP, TAB, LF, BS, ControlA, ControlX, FF, NUL, ESC, DEL, BEL],
Atom USING [PropList],
Basics USING [FWORD, HWORD, UnsafeBlock],
BasicTime USING [GMT, Now, Unpacked],
Rope USING [ROPE, UncheckedFlat];
IO: CEDAR DEFINITIONS
IMPORTS BasicTime
= BEGIN
ROPE: TYPE = Rope.ROPE;
UnsafeBlock: TYPE = Basics.UnsafeBlock;
An UnsafeBlock describes a sequence of bytes residing in virtual memory.
If you interpret base as a POINTER TO PACKED ARRAY OF CHAR, then the byte
sequence described by an UnsafeBlock is base[
startIndex .. startIndex+count).
STREAM: TYPE = REF STREAMRecord;
STREAMRecord should be regarded as opaque by most clients.
Its representation is defined below in the section "Private details".
StreamVariety: TYPE = {input, output, inputOutput};
Generic stream operations and errors
Calling an undefined stream operation raises ERROR Error[$NotImplementedForThisStream, self]. Calling an operation other than Reset or Close on a closed stream raises ERROR Error[$StreamClosed, self]; calling Reset or Close on a closed stream does nothing.
Errors
EndOfStream: ERROR [stream: STREAM];
Error: ERROR [ec: ErrorCode, stream: STREAM, details: LIST OF REF ¬ NIL, msg: ROPE ¬ NIL];
ErrorCode: TYPE = MACHINE DEPENDENT {
Null,
not raised by any proc
NotImplementedForThisStream,
this operation is not implemented by this stream
StreamClosed,
this stream is closed (operation might have been valid before close)
Failure,
from any operation; consult details for more detailed information
IllegalBackup,
detected an attempt to Backup a different character than came from GetChar
BufferOverflow,
attempt to Backup too far
BadIndex,
bad index to SetIndex (e.g. past end of file)
SyntaxError,
in formatted input tokenizing or conversion
Overflow,
in formatted input conversion
PFInvalidCode,
IOUtils.Set/Get PFCodeProc.. char not IN ['A..'Z] or ['a..'z]
PFInvalidPFProcs,
IOUtils.Set/Get PFCodeProc.. pfProcs = NIL
PFCantBindConversionProc,
PutF.. stream (and its backing streams) does not define code proc
PFFormatSyntaxError,
PutF.. not enough or too many '%s, no code following '%
PFTypeMismatch,
PutF.. the PFCodeProc is not prepared for the supplied Value type
PFUnprintableValue,
PutF.. the PFCodeProc is not able to print the particular value (e.g. overflow in real -> int conversion)
(BYTE.LAST)
};
AtomFromErrorCode: PROC [ErrorCode] RETURNS [ATOM];
ErrorCodeFromAtom: PROC [ATOM] RETURNS [ErrorCode];
Rubout: ERROR [stream: STREAM]; -- Formerly EditedStream.Rubout;
Some interactive streams raise Rubout (and discard buffered input characters) when suitable user input (e.g., DEL) occurs.
Timeout: SIGNAL [which: REF, codes: LIST OF ATOM, msg: ROPE];
This is primarily for network streams. Refer to the NetworkStream interface for details.
General information
GetInfo: PROC [stream: STREAM] RETURNS [variety: StreamVariety, class: ATOM];
Input Operations (defined for input and inputOutput streams)
GetChar: PROC [self: STREAM] RETURNS [CHAR];
! EndOfStream (end of input sequence has been reached)
InlineGetChar: PROC [self: STREAM] RETURNS [CHAR] ~ INLINE {
i: NAT ~ self.bufferIndex;
IF i < self.bufferInputLength
THEN { self.bufferIndex ¬ i+1; RETURN[QFetch[self.buffer, i]] }
ELSE RETURN[self.streamProcs.getChar[self]];
};
GetBlock: PROC [self: STREAM, block: REF TEXT, startIndex: NAT ¬ 0, count: NAT ¬ NAT.LAST] RETURNS [nBytesRead: NAT];
! RuntimeError.BoundsFault (block.startIndex > block.maxLength)
Gets characters from the stream until count characters have been read, or the block is full, or the stream ends; stores the characters in block, starting at startIndex; when done, sets block.length ¬ startIndex+nBytesRead (<=block.maxLength); block[startIndex..block.length) contains the new characters. GetBlock never raises EndOfStream.
UnsafeGetBlock: UNSAFE PROC [self: STREAM, block: UnsafeBlock] RETURNS [nBytesRead: INT];
! RuntimeError.BoundsFault (block.startIndex < 0 OR block.count < 0)
Analogous to GetBlock. Never raises EndOfStream.
EndOf: PROC [self: STREAM] RETURNS [BOOL];
Tests for the input stream being at its end.
InlineEndOf: PROC [self: STREAM] RETURNS [BOOL] ~ INLINE {
RETURN[(self.bufferIndex >= self.bufferInputLength) AND self.streamProcs.endOf[self]];
};
CharsAvail: PROC [self: STREAM, wait: BOOL ¬ FALSE] RETURNS [INT];
Predicts the real-time response of the stream to later requests. Returns the number of times GetChar can be called quickly (without waiting for user input or for network transmission). If EndOf[stream] then CharsAvail[stream]#0, since GetChar would raise EndOfStream quickly! If wait, does not return until it can return a nonzero value.
Backup: PROC [self: STREAM, char: CHAR];
! Error[self, IllegalBackup] (char is not the last byte read).
Undoes the effect of the most recent GetChar, which returned the value char.
PeekChar: PROC [self: STREAM] RETURNS [CHAR];
Short for GetChar followed by Backup.
InlinePeekChar: PROC [self: STREAM] RETURNS [CHAR] ~ INLINE {
i: NAT ~ self.bufferIndex;
IF i < self.bufferInputLength
THEN RETURN[QFetch[self.buffer, i]]
ELSE RETURN[PeekChar[self]];
};
Output Operations (defined for output and inputOutput streams)
PutChar: PROC [self: STREAM, char: CHAR];
Puts one character to the stream
InlinePutChar: PROC [self: STREAM, char: CHAR] ~ INLINE {
i: NAT ~ self.bufferIndex;
IF i < self.bufferOutputLength
THEN { self.bufferIndex ¬ i+1; self.buffer[i] ¬ char }
ELSE self.streamProcs.putChar[self, char];
};
PutBlock: PROC [self: STREAM, block: REF READONLY TEXT, startIndex: NAT ¬ 0, count: NAT ¬ NAT.LAST];
Effect is like: If startIndex+count > block.maxLength, then set count ¬ block.length-startIndex. Then perform PutChar for each byte in block[startIndex .. startIndex+count).
UnsafePutBlock: PROC [self: STREAM, block: UnsafeBlock];
! RuntimeError.BoundsFault (block.startIndex < 0 OR block.count < 0)
Analogous to PutBlock.
Flush: PROC [self: STREAM];
Causes characters that have been output to stream, but not yet sent (because of buffering) to be sent
EraseChar: PROC [self: STREAM, char: CHAR];
Erases char, which was last char put to self. For instance, erases character from display. For most stream classes, implemented as on a teletype by printing '\\ followed by char.
Control Operations (defined for all streams)
Reset: PROC [self: STREAM];
For input streams, has the effect of flushing all pending input, so that self.CharsAvail[] = 0. For output and input/output streams, has some class-specific effect.
Close: PROC [self: STREAM, abort: BOOL ¬ FALSE];
Makes stream unusable for further operations; any stream operation except Flush, Reset, and Close will raise ERROR Error[self, StreamClosed].
Special Control Operations (defined for file-like streams)
GetIndex: PROC [self: STREAM] RETURNS [index: INT];
SetIndex: PROC [self: STREAM, index: INT];
GetLength: PROC [self: STREAM] RETURNS [length: INT];
SetLength: PROC [self: STREAM, length: INT];
Stream classes that interface to other data types
ROPE
RIS: PROC [rope: ROPE, oldStream: STREAM ¬ NIL] RETURNS [stream: STREAM];
The rope input stream behaves much like a file input stream: GetIndex, SetIndex, and GetLength are all defined. Gets chars from client's rope. If oldStream is non-NIL it is reused rather than allocating space for a new stream.
ROS: PROC [oldStream: STREAM ¬ NIL] RETURNS [stream: STREAM];
The rope output stream behaves much like an append-only file stream: GetIndex and GetLength are defined. The sequence output so far is available as a rope. Closing the stream releases a REF TEXT buffer to the scratch TEXT pool.
RopeFromROS: PROC [self: STREAM, close: BOOL ¬ TRUE] RETURNS [ROPE];
Applies only to the result of a ROS call. Returns the entire output sequence as a rope. If close, then close self.
REF TEXT
TIS: PROC [text: REF READONLY TEXT, oldStream: STREAM ¬ NIL] RETURNS [stream: STREAM];
The text input stream behaves much like a file input stream: GetIndex, SetIndex, and GetLength are all defined. Gets chars from user's user's REF TEXT. If oldStream is non-NIL, it is reused rather than allocating space for a new stream. The user should not modify the text after passing it to TIS until the stream is closed.
TOS: PROC [text: REF TEXT ¬ NIL, oldStream: STREAM ¬ NIL] RETURNS [stream: STREAM];
The text output stream behaves much like an append-only file stream: GetIndex and GetLength are defined. If text = NIL then TOS allocates one. Sets text.length ¬ 0. PutChar appends characters to text using RefText.InlineAppendChar. The user should not modify the text after passing it to TOS until the stream is closed.
TextFromTOS: PROC [self: STREAM] RETURNS [REF TEXT];
Applies only to the result of a TOS call. Returns the entire output sequence as a ref text. Does not close the stream, so may be called repeatedly, but same ref text may be returned several times (and is mutable).
Null
noWhereStream: STREAM;
output stream that simply discards its characters.
noInputStream: STREAM;
input stream for which CharsAvail is INT.LAST, EndOf is TRUE.
Printing
atom: PROC [v: ATOM] RETURNS [Value] = INLINE {RETURN[[atom[v]]]};
bool: PROC [v: BOOL] RETURNS [Value] = INLINE {RETURN[[boolean[v]]]};
card: PROC [v: CARD] RETURNS [Value] = INLINE {RETURN[[cardinal[v]]]};
char: PROC [v: CHAR] RETURNS [Value] = INLINE {RETURN[[character[v]]]};
dcard: PROC [v: DCARD] RETURNS [Value];
dint: PROC [v: DINT] RETURNS [Value];
dreal: PROC [v: DREAL] RETURNS [Value];
int: PROC [v: INT] RETURNS [Value] = INLINE {RETURN[[integer[v]]]};
real: PROC [v: REAL] RETURNS [Value] = INLINE {RETURN[[real[v]]]};
refAny: PROC [v: REF READONLY ANY] RETURNS [Value] = INLINE {RETURN[[refAny[v]]]};
rope: PROC [v: ROPE] RETURNS [Value] = INLINE {RETURN[[rope[v]]]};
text: PROC [v: REF READONLY TEXT] RETURNS [Value] = INLINE {RETURN[[text[v]]]};
time: PROC [v: BasicTime.GMT ¬ BasicTime.Now[]] RETURNS [Value] = INLINE {RETURN[[time[v]]]};
IO.time[] gives the current time.
Put: PROC [stream: STREAM, v1, v2: Value, v3: Value ¬ [null[]]];
Put1: PROC [stream: STREAM, value: Value];
PutR: PROC [v1, v2: Value, v3: Value ¬ [null[]]] RETURNS [ROPE];
PutR1: PROC [value: Value] RETURNS [ROPE];
PutL: PROC [stream: STREAM, list: LIST OF Value];
PutLR: PROC [list: LIST OF Value] RETURNS [ROPE];
Suffix "R" means "ToRope", "L" means "FromList", and "LR" means "FromListToRope".
Put is a convenience procedure that gives the effect of (1) calling the appropriate procedure from the Convert interface to turn the Value into a character string, and (2) sending this character string down the stream. Put is relatively efficient but provides no formatting options. Use PutF, or call Convert, to get other effects.
PutF: PROC [stream: STREAM, format: ROPE ¬ NIL, v1, v2: Value, v3: Value ¬ [null[]]];
PutF1: PROC [stream: STREAM, format: ROPE ¬ NIL, value: Value];
PutFR: PROC [format: ROPE ¬ NIL, v1, v2: Value, v3: Value ¬ [null[]]] RETURNS [ROPE];
PutFR1: PROC [format: ROPE ¬ NIL, value: Value] RETURNS [ROPE];
PutFL: PROC [stream: STREAM, format: ROPE ¬ NIL, list: LIST OF Value];
PutFLR: PROC [format: ROPE ¬ NIL, list: LIST OF Value] RETURNS [ROPE];
PutF is similar in spirit to the FORTRAN format interpreter. A call to PutF specifies a format (a ROPE containing text and conversion specifications) and a sequence of Cedar values. PutF replaces each conversion specification in the format with a printed representation of the corresponding Cedar value. Examples (see IODoc.tioga for a full explanation):
IO.PutFR["This is %g in a 5 position field: |%5g|", IO.rope["an integer"], IO.int[17]] =
"This is an integer in a 5 position field: | 17|"
IO.PutFR["This is %g in a 5 position field: |%05g|", IO.rope["an integer"], IO.int[17]] =
"This is an integer in a 5 position field: |00017|"
IO.PutFR["This is %g in a 5 position field: |%-5g|", IO.rope["an integer"], IO.int[17]] =
"This is an integer in a 5 position field: |17 |"
IO.PutFR["This is a floating point number: |%5.2f|", IO.real[1.2345]] =
"This is a floating point number: | 1.23|"
Though %g usually suffices, other specifications are occasionally useful:
%b: Print number in octal, with trailing 'B.
%x: Print number in hex, with trailing 'H.
%e: Analogous to FORTRAN E format. Example: "%10.2e".
%f: Analogous to FORTRAN F format. Example: "%-8.3f" (left-justified).
%r: Print the number as a time interval in seconds, with format HH:MM:SS.
%l: For Viewer streams, change looks for subsequent output.
%q: Print the literal representation of the rope, i.e., with escape sequences.
Scanning
Scanning routines that return a result are generally provided in two versions. The first version takes a REF TEXT buffer as a parameter, and may return its result in this buffer, but will allocate a larger one if the buffer fills up. Hence if each token is smaller than the buffer, only a single allocation is required to scan a sequence of tokens. The second version returns its result in a ROPE; hence at least one byte of storage is allocated for each byte of token scanned. In either case, a token cannot exceed NAT.LAST bytes in length.
Scanning according to Cedar syntax
TokenKind: TYPE = MACHINE DEPENDENT {
tokenERROR, -- token.error describes the scanning error
tokenID, -- an identifier or reserved word
tokenDECIMAL, -- a whole number literal expressed in decimal
tokenOCTAL, -- a whole number literal expressed in octal
tokenHEX, -- a whole number literal expressed in hexidecimal
tokenREAL, -- a REAL literal
tokenROPE, -- a ROPE, REF TEXT, or STRING literal
tokenCHAR, -- a CHAR literal
tokenATOM, -- an ATOM literal
tokenSINGLE, -- a single-character token
tokenDOUBLE, -- a double-character token
tokenCOMMENT, -- a comment
tokenEOF, -- the end-of-file marker
(BYTE.LAST) -- room for extensions
};
AtomFromTokenKind: PROC [TokenKind] RETURNS [ATOM];
TokenKindFromAtom: PROC [ATOM] RETURNS [TokenKind];
TokenError: TYPE = MACHINE DEPENDENT {
none, -- no error
extendedChar, -- error following backslash in char or string literal
numericLiteral, charLiteral, stringLiteral, atomLiteral, -- error in parsing indicated type
singleChar, -- first non-whitespace char is not legal as first char of token
(BYTE.LAST) -- room for extensions
};
AtomFromTokenError: PROC [TokenError] RETURNS [ATOM];
TokenErrorFromAtom: PROC [ATOM] RETURNS [TokenError];
GetCedarToken: PROC [stream: STREAM, buffer: REF TEXT, flushComments: BOOL ¬ TRUE]
RETURNS [tokenKind: TokenKind, token: REF TEXT, charsSkipped: INT, error: TokenError];
! (none)
Consumes chars from stream, looking for next Cedar token. Returns the kind of token found, the characters of the token, and the number of white space characters discarded before reaching the token. If flushComments then the characters of a comment are treated as white space. The error returned is # none only for tokenKind = tokenERROR.
GetCedarTokenRope: PROC [stream: STREAM, flushComments: BOOL ¬ TRUE]
RETURNS [tokenKind: TokenKind, token: ROPE, charsSkipped: INT];
! EndOfStream
! Error[SyntaxError]
Calls GetCedarToken. If token returned is tokenEOF or tokenERROR, raises an appropriate signal. Otherwise converts the token into a ROPE and returns it.
GetInt: PROC [stream: STREAM] RETURNS [INT];
GetCard: PROC [stream: STREAM] RETURNS [CARD];
GetReal: PROC [stream: STREAM] RETURNS [REAL];
GetDReal: PROC [stream: STREAM] RETURNS [DREAL];
GetBool: PROC [stream: STREAM] RETURNS [BOOL];
GetAtom: PROC [stream: STREAM] RETURNS [ATOM];
GetRopeLiteral: PROC [stream: STREAM] RETURNS [ROPE];
GetCharLiteral: PROC [stream: STREAM] RETURNS [CHAR];
GetID: PROC [stream: STREAM] RETURNS [ROPE];
These convenience procedures generally call GetCedarToken (with flushComments = TRUE), check that the tokenKind is as expected, and convert the token to a Cedar value of the indicated type. They raise EndOfStream if the tokenKind is tokenEOF, raise Error[SyntaxError] if the tokenKind is not the one expected (including tokenERROR), and raise Error[Overflow] if there is an overflow in a conversion.
GetTime: PROC [stream: STREAM] RETURNS [BasicTime.GMT];
GetUnpackedTime: PROC [stream: STREAM] RETURNS [BasicTime.Unpacked];
GetTime and GetUnpackedTime do not follow the simple pattern just described because there is no standard Cedar syntax for time. They consume whatever looks like a time.
GetRefAny: PROC [stream: STREAM] RETURNS [REF ANY];
Calls GetCedarToken to parse input stream, then converts the resulting token to a REF to a value of the appropriate type. GetRefAny recognizes no tokens of type tokenDOUBLE, and only a few tokens of type tokenSINGLE:
'( starts a list (LIST OF REF ANY), ') terminates a list,
'+, '- are unary operators that may precede a numeric literal,
', is ignored between elements of a list,
'^ is always ignored.
GetRefAnyLine: PROC [stream: STREAM] RETURNS [LIST OF REF ANY];
Calls GetRefAny repeatedly until the token found is (1) not an element of a list, and (2) is immediately followed by a NL. Creates a LIST OF REF ANY to hold the sequence of values returned, and returns this list. Is intended for use in command interpreters.
Simple stream scanning
SkipWhitespace: PROC [stream: STREAM, flushComments: BOOL ¬ TRUE]
RETURNS [charsSkipped: INT];
The effect is to read and discard characters from stream until a non-whitespace character is read (and put back using Backup). If flushComments, treats comments as whitespace. Returns the number of characters skipped.
GetToken: PROC [stream: STREAM, breakProc: BreakProc ¬ TokenProc, buffer: REF TEXT]
RETURNS [token: REF TEXT, charsSkipped: INT];
! EndOfStream (stream.EndOf[] AND token.IsEmpty[] when GetToken is about to return)
The result token is the first sequence of characters in stream that is either a run of consecutive other characters, or a single break character. All chars preceding token, and token itself, are removed from stream. Raises EndOfStream if token would be empty and stream is empty. charsSkipped is the number of chars skipped before reaching the first char of the token.
CharClass: TYPE = {break, sepr, other};
BreakProc: TYPE = PROC [char: CHAR] RETURNS [CharClass];
TokenProc: BreakProc;
Is equivalent to {RETURN[SELECT char FROM
IN [NUL .. SP], ',, ':, '; => sepr,
'[, '], '(, '), '{, '}, '", '+, '-, '*, '/, '@, '¬ => break,
ENDCASE => other]};
s.GetToken[breakProc: TokenProc] approximates the behavior of the Cedar scanner, but discards commas, colons, and semicolons, does not handle real numbers, rope literals, two-character operators, etc.
IDProc: BreakProc;
Is equivalent to {RETURN[SELECT char FROM
IN [NUL .. SP], ',, ':, '; => sepr,
ENDCASE => other]};
s.GetToken[IDProc] does not recognize single-character tokens, hence accepts "/indigo/cedar/top/io.df" or "Rovner.pa" as a single token.
GetTokenRope: PROC [stream: STREAM, breakProc: BreakProc ¬ TokenProc]
RETURNS [token: ROPE, charsSkipped: INT];
! EndOfStream (stream.EndOf[] AND token.IsEmpty[] when GetTokenRope is about to return)
Calls GetToken, converts token to ROPE, returns it.
GetLine: PROC [stream: STREAM, buffer: REF TEXT] RETURNS [line: REF TEXT];
! EndOfStream (stream.EndOf[] when GetLine is called)
The result line is the sequence of characters in stream preceding the next NL or end of stream. If the line is terminated with NL, the NL is removed from stream but not included in line. Raises EndOfStream if the input stream is empty on entry.
GetLineRope: PROC [stream: STREAM] RETURNS [line: ROPE];
! EndOfStream (stream.EndOf[] when GetLineRope is called)
Calls GetLine, converts line to ROPE, returns it.
Other Get/Put operations
GetRope: PROC [self: STREAM, len: INT ¬ INT.LAST, demand: BOOL ¬ FALSE] RETURNS [ROPE];
Gets len characters from the stream and returns them in a ROPE. If the stream ends before len characters have been read, the effect depends on demand: if demand=FALSE, GetRope just returns a shorter rope; if demand=TRUE, GetRope raises EndOfStream.
If self is a RIS, returns a Rope.Substr of the underlying rope rather than copying.
PutRope: PROC [self: STREAM, r: ROPE, start: INT ¬ 0, len: INT ¬ INT.LAST];
Puts onto the stream the characters of the specified substring of r.
Does not emit escape sequences for non-printing characters (compare PutF["%q", [rope[r]]]).
If self is a ROS, may Rope.Concat to the underlying rope rather than copying.
GetText: PROC [self: STREAM, len: NAT, buffer: REF TEXT ¬ NIL] RETURNS [REF TEXT];
Gets len characters from the stream and returns them in characters [0..len) of a REF TEXT; the result has text.length=len. Uses buffer if it is long enough, otherwise allocates a new TEXT. If the stream ends before len characters have been read, GetText raises EndOfStream.
PutText: PROC [self: STREAM, t: REF READONLY TEXT];
A convenience, equivalent to { IF t#NIL THEN PutBlock[self, t] }.
GetByte: PROC [self: STREAM] RETURNS [BYTE]
~ INLINE { RETURN [ORD[GetChar[self]]] };
InlineGetByte: PROC [self: STREAM] RETURNS [BYTE]
~ INLINE { RETURN [ORD[InlineGetChar[self]]] };
PutByte: PROC [self: STREAM, byte: BYTE]
~ INLINE { PutChar[self, VAL[byte]] };
InlinePutByte: PROC [self: STREAM, byte: BYTE]
~ INLINE { InlinePutChar[self, VAL[byte]] };
GetHWord: PROC [self: STREAM] RETURNS [hword: Basics.HWORD];
PutHWord: PROC [self: STREAM, hword: Basics.HWORD];
GetFWord: PROC [self: STREAM] RETURNS [fword: Basics.FWORD];
PutFWord: PROC [self: STREAM, fword: Basics.FWORD];
ASCII Character constants
BS: CHAR = Ascii.BS; -- '\b
TAB: CHAR = Ascii.TAB; -- '\t
LF: CHAR = Ascii.LF; -- '\l
FF: CHAR = Ascii.FF; -- '\f
CR: CHAR = Ascii.CR; -- '\r
NUL: CHAR = Ascii.NUL;
ControlA: CHAR = Ascii.ControlA;
BEL: CHAR = Ascii.BEL;
ControlX: CHAR = Ascii.ControlX;
ESC: CHAR = Ascii.ESC;
SP: CHAR = Ascii.SP;
DEL: CHAR = Ascii.DEL;
Implementing a stream class
The following procedures are used to implement a stream class. Few stream implementations require access to such aspects of the stream representation as the stream property list, the stream procs property list, and the backing stream, except through the CreateStreamProcs and CreateStream procedures below. When such access is necessary, consult the IOUtils interface for relevant procedures.
GetCharProc: TYPE ~ PROC [self: STREAM] RETURNS [CHAR];
GetBlockProc: TYPE ~ PROC [self: STREAM, block: REF TEXT, startIndex: NAT, count: NAT]
RETURNS [nBytesRead: NAT];
UnsafeGetBlockProc: TYPE ~ UNSAFE PROC [self: STREAM, block: UnsafeBlock]
RETURNS [nBytesRead: INT];
EndOfProc: TYPE ~ PROC [self: STREAM] RETURNS [BOOL];
CharsAvailProc: TYPE ~ PROC [self: STREAM, wait: BOOL] RETURNS [INT];
BackupProc: TYPE ~ PROC [self: STREAM, char: CHAR];
PutCharProc: TYPE ~ PROC [self: STREAM, char: CHAR];
PutBlockProc: TYPE ~ PROC [self: STREAM, block: REF READONLY TEXT, startIndex: NAT, count: NAT];
UnsafePutBlockProc: TYPE ~ PROC [self: STREAM, block: UnsafeBlock];
FlushProc: TYPE ~ PROC [self: STREAM];
ResetProc: TYPE ~ PROC [self: STREAM];
CloseProc: TYPE ~ PROC [self: STREAM, abort: BOOL];
GetIndexProc: TYPE ~ PROC [self: STREAM] RETURNS [INT];
SetIndexProc: TYPE ~ PROC [self: STREAM, index: INT];
GetLengthProc: TYPE ~ PROC [self: STREAM] RETURNS [INT];
SetLengthProc: TYPE ~ PROC [self: STREAM, length: INT];
EraseCharProc: TYPE ~ PROC [self: STREAM, char: CHAR];
CreateStreamProcs: PROC [
variety: StreamVariety,
class: ATOM,
getChar: GetCharProc ¬ NIL,
getBlock: GetBlockProc ¬ NIL,
unsafeGetBlock: UnsafeGetBlockProc ¬ NIL,
endOf: EndOfProc ¬ NIL,
charsAvail: CharsAvailProc ¬ NIL,
backup: BackupProc ¬ NIL,
putChar: PutCharProc ¬ NIL,
putBlock: PutBlockProc ¬ NIL,
unsafePutBlock: UnsafePutBlockProc ¬ NIL,
flush: FlushProc ¬ NIL,
reset: ResetProc ¬ NIL,
close: CloseProc ¬ NIL,
getIndex: GetIndexProc ¬ NIL,
setIndex: SetIndexProc ¬ NIL,
getLength: GetLengthProc ¬ NIL,
setLength: SetLengthProc ¬ NIL,
eraseChar: EraseCharProc ¬ NIL
]
RETURNS [REF StreamProcs];
CreateStream: PROC [streamProcs: REF StreamProcs, streamData: REF ANY,
backingStream: STREAM ¬ NIL] RETURNS [stream: STREAM];
Private details
STREAMRecord: TYPE = RECORD [
streamProcs: REF StreamProcs, -- the stream procedures
streamData: REF ANY ¬ NIL, -- instance data, type is specific to the stream class
propList: Atom.PropList ¬ NIL, -- instance data, type is independent of the stream class
backingStream: STREAM ¬ NIL, -- distinguished instance data, used to "layer" streams
The following are used by the inline versions of GetChar, PeekChar, EndOf, and PutChar. They are optional in that impementations may default these fields, which will cause the operations to go though the class. If the implementation chooses to provide the buffer, its streamProcs must maintain the appropriate invariants.
buffer: REF TEXT ¬ NIL,
bufferInputLength: NAT ¬ 0,
bufferOutputLength: NAT ¬ 0,
bufferIndex: NAT ¬ 0
];
StreamProcs: TYPE = PRIVATE RECORD [
getChar: GetCharProc,
getBlock: GetBlockProc,
unsafeGetBlock: UnsafeGetBlockProc,
endOf: EndOfProc,
charsAvail: CharsAvailProc,
backup: BackupProc,
putChar: PutCharProc,
putBlock: PutBlockProc,
unsafePutBlock: UnsafePutBlockProc,
flush: FlushProc,
reset: ResetProc,
close: CloseProc,
getIndex: GetIndexProc,
setIndex: SetIndexProc,
getLength: GetLengthProc,
setLength: SetLengthProc,
eraseChar: EraseCharProc,
propList: Atom.PropList,
variety: StreamVariety,
class: ATOM
];
Value: TYPE = RECORD [
SELECT type: ValueType FROM
null => NULL,
atom => [value: ATOM],
boolean => [value: BOOL],
character => [value: CHAR],
cardinal => [value: CARD],
integer => [value: INT],
dint => [value: REF DINT], -- indirection keeps size of IO.Value small
dcard => [value: REF DCARD],
real => [value: REAL],
dreal => [value: REF DREAL],
refAny => [value: REF READONLY ANY],
rope => [value: ROPE],
text => [value: REF READONLY TEXT],
time => [value: BasicTime.GMT],
ENDCASE
];
ValueType: TYPE = {null, atom, boolean, character, cardinal, integer, dint, dcard, real, dreal, refAny, rope, text, time};
QFetch: PRIVATE PROC [buffer: REF READONLY TEXT, i: NAT] RETURNS [CHAR] ~ INLINE {
quick fetch from buffer for hack purposes, no checking
TRUSTED { RETURN [LOOPHOLE[buffer, Rope.UncheckedFlat][i]] };
};
END.