G3dIOImpl.mesa
Copyright Ó 1985, 1992 by Xerox Corporation. All rights reserved.
Bloomenthal, July 22, 1992 1:49 pm PDT
Glassner, July 5, 1989 6:38:15 pm PDT
Ken Fishkin, August 20, 1992 4:23 pm PDT
DIRECTORY CedarProcess, Convert, FileNames, G2dBasic, G3dBasic, G3dIO, G3dMatrix, FS, IO, Process, Rope, Tioga, TiogaAccess;
G3dIOImpl: CEDAR MONITOR
IMPORTS CedarProcess, Convert, FileNames, FS, IO, Process, Rope, TiogaAccess
EXPORTS G3dIO
~ BEGIN
Type Declarations
IntegerSequence:   TYPE ~ G3dBasic.IntegerSequence;
IntegerSequenceRep: TYPE ~ G3dBasic.IntegerSequenceRep;
NatSequence :   TYPE ~ G3dBasic.NatSequence;
NatSequenceRep:   TYPE ~ G3dBasic.NatSequenceRep;
Pair:      TYPE ~ G3dBasic.Pair;
PairSequence:   TYPE ~ G3dBasic.PairSequence;
PairSequenceRep:  TYPE ~ G3dBasic.PairSequenceRep;
Quad:      TYPE ~ G3dBasic.Quad;
RealSequence:   TYPE ~ G3dBasic.RealSequence;
RealSequenceRep:  TYPE ~ G3dBasic.RealSequenceRep;
SurfaceSequence:  TYPE ~ G3dBasic.SurfaceSequence;
Triple:     TYPE ~ G3dBasic.Triple;
TripleSequence:   TYPE ~ G3dBasic.TripleSequence;
TripleSequenceRep:  TYPE ~ G3dBasic.TripleSequenceRep;
SurfaceSequenceRep: TYPE ~ G3dBasic.SurfaceSequenceRep;
ErrorType:    TYPE ~ G3dIO.ErrorType;
FieldRep:     TYPE ~ G3dIO.FieldRep;
FieldSequence:   TYPE ~ G3dIO.FieldSequence;
FieldSequenceRep:  TYPE ~ G3dIO.FieldSequenceRep;
FieldType:    TYPE ~ G3dIO.FieldType;
Line:      TYPE ~ G3dIO.Line;
LineRep:     TYPE ~ G3dIO.LineRep;
Matrix:     TYPE ~ G3dMatrix.Matrix;
STREAM:     TYPE ~ IO.STREAM;
ROPE:      TYPE ~ Rope.ROPE;
Writer:     TYPE ~ TiogaAccess.Writer;
Errors
Error: PUBLIC ERROR [reason, lineText: ROPE, lineNumber: NAT] = CODE;
Private Support Procedures
ErrorReport: PUBLIC PROC [errorType: ErrorType, line: Line ¬ NIL, keyWord: ROPE ¬ NIL] ~ {
lineNumber: INTEGER ¬ IF errorType # notFound THEN LineNumber[line] ELSE 0;
text: ROPE ¬ IF errorType # notFound THEN line.rope ELSE NIL;
reason: ROPE ¬ SELECT errorType FROM
notFound => Rope.Concat["KeyWord not found: ", keyWord],
format => IO.PutFR["Bad format, line %g: %g", IO.int[lineNumber], IO.rope[line.rope]],
convert => IO.PutFR["Bad conversion, line %g: %g", IO.int[lineNumber], IO.rope[line.rope]],
ENDCASE => NIL;
Error[reason, text, lineNumber];
};
GetNonBlankLine: PROC [stream: STREAM, line: Line ¬ NIL] RETURNS [Line] ~ {
DO
line ¬ GetLine[stream, line];
IF line.type # blank THEN EXIT;
ENDLOOP;
RETURN[line];
};
GetLineAfterKey: PROC [
stream: STREAM,
keyWord: ROPE,
circularSearch: BOOL ¬ FALSE,
line: Line ¬ NIL]
RETURNS [Line]
~ {
[] ¬ FindKeyWord[stream, keyWord, circularSearch, , line];
RETURN[GetLine[stream, line]];
};
BlankLine: PROC [line: ROPE] RETURNS [BOOL] ~ {
RETURN[Rope.SkipOver[line, 0, " \t"] = Rope.Length[line]];
};
Equal: PROC [r1, r2: ROPE] RETURNS [BOOL] ~ {RETURN[Rope.Equal[r1, r2, FALSE]]};
Support Procedures
nScratchLines: NAT ~ 40;
scratchLines: ARRAY [0..nScratchLines) OF Line ¬ ALL[NIL];
ObtainLine: PUBLIC ENTRY PROC RETURNS [line: Line] ~ {
FOR i: NAT IN [0..nScratchLines) DO
line: Line ~ scratchLines[i];
IF line # NIL THEN {
scratchLines[i] ¬ NIL;
line.index ¬ line.length ¬ 0;
line.rope ¬ NIL;
line.stream ¬ NIL;
RETURN[line];
};
ENDLOOP;
RETURN[NEW[LineRep]];
};
ReleaseLine: PUBLIC ENTRY PROC [line: Line] ~ {
FOR i: NAT IN [0..nScratchLines) DO
IF scratchLines[i] = NIL THEN {
scratchLines[i] ¬ line;
RETURN;
};
ENDLOOP;
};
LineNumber: PUBLIC PROC [line: Line] RETURNS [nLine: INTEGER ¬ 0] ~ {
index: INT ¬ IO.GetIndex[line.stream];
IF line = NIL OR line.stream = NIL THEN RETURN[-1];
IO.SetIndex[line.stream, 0];
DO
test: ROPE ¬ IO.GetLineRope[line.stream ! IO.EndOfStream, IO.Error => {nLine ¬ -1; EXIT}];
IF Rope.Equal[line.rope, test] THEN EXIT;
nLine ¬ nLine+1;
ENDLOOP;
IO.SetIndex[line.stream, index];
};
NextKeyWord: PUBLIC PROC [
stream: STREAM,
circularSearch: BOOL ¬ FALSE,
maxNLinesToTest: CARDINAL ¬ LAST[CARDINAL]]
RETURNS [key: ROPE]
~ {
Return the next keyWord. The file index points to the beginning of the key line.
line: Line ¬ ObtainLine[];
nTested: CARDINAL ¬ 0;
loopIndex: INT;
length: INTEGER;
eof, startedAtZero: BOOL ¬ FALSE;
sIndexStart: INT ¬ IO.GetIndex[stream];
DO
loopIndex ¬ IO.GetIndex[stream];
IF nTested >= maxNLinesToTest OR (startedAtZero AND loopIndex > sIndexStart)
THEN GOTO notFound;
line ¬ GetLine[stream, line ! IO.EndOfStream, IO.Error => {eof ¬ TRUE; CONTINUE}];
nTested ¬ nTested+1;
IF eof THEN {
IF NOT circularSearch OR startedAtZero THEN GOTO notFound;
IO.SetIndex[stream, 0];
startedAtZero ¬ TRUE;
LOOP;
};
IF line.type = blank THEN LOOP;
length ¬ Rope.Length[key ¬ GetWord[line]];
IF Rope.Fetch[key, length-1] = '~ THEN {key ¬ Rope.Substr[key, 0, length-1]; EXIT};
IF Equal[GetWord[line], "~"] THEN EXIT;
REPEAT
notFound => {
IO.SetIndex[stream, sIndexStart];
ErrorReport[notFound, NIL, "no keyWord"];
};
ENDLOOP;
ReleaseLine[line];
IO.SetIndex[stream, loopIndex];
};
FindKeyWord: PUBLIC PROC [
stream: STREAM,
keyWord: ROPE,
circularSearch: BOOL ¬ FALSE,
maxNLinesToTest: CARDINAL ¬ LAST[CARDINAL],
line: Line ¬ NIL]
RETURNS [Line]
~ {
Return the line beginning with keyWord followed by "~". line is returned with its index set
to after the "~". The file index points to the beginning of the line following the key line.
word: ROPE;
nTested: CARDINAL ¬ 0;
length: INTEGER ¬ Rope.Length[keyWord];
eof, startedAtZero: BOOL ¬ FALSE;
sIndexStart: INT ¬ IO.GetIndex[stream];
DO
IF nTested = maxNLinesToTest OR (startedAtZero AND IO.GetIndex[stream] > sIndexStart)
THEN GOTO notFound;
line ¬ GetLine[stream, line ! IO.EndOfStream, IO.Error => {eof ¬ TRUE; CONTINUE}];
nTested ¬ nTested+1;
IF eof THEN {
IF NOT circularSearch OR startedAtZero THEN GOTO notFound;
IO.SetIndex[stream, 0];
startedAtZero ¬ TRUE;
LOOP;
};
SELECT Rope.Length[word ¬ GetWord[line]] FROM
length => {
IF NOT Equal[keyWord, word] THEN LOOP;
IF Equal[GetWord[line], "~"] THEN EXIT;
};
length+1 => {
IF NOT Equal[keyWord, Rope.Substr[word, 0, length]] THEN LOOP;
IF Rope.Fetch[word, length] = '~ THEN EXIT;
};
ENDCASE => NULL;
REPEAT
notFound => {
IO.SetIndex[stream, sIndexStart];
ErrorReport[notFound, NIL, keyWord];
};
ENDLOOP;
RETURN[line];
};
InitializeFields: PUBLIC PROC [keyLine: Line] RETURNS [fields: FieldSequence] ~ {
Allocate fields, set their id's and types, but not their sequences.
nFields: INTEGER ¬ 0;
fields ¬ NEW[FieldSequenceRep[(NWordsInRope[keyLine.rope]-1)/2]]; -- allocate fields
FOR n: NAT IN[0..fields.maxLength) DO      -- set id and type of each field
rope: ROPE ¬ GetWord[keyLine];
length: INTEGER ¬ Rope.Length[rope];
IF rope = NIL OR Rope.Equal[Rope.Substr[rope, 0, 2], "--"] THEN EXIT;
IF Rope.Equal[rope, ","] THEN length ¬ Rope.Length[rope ¬ GetWord[keyLine]];
IF Rope.Fetch[rope, length-1] = ':
THEN length ¬ length-1
ELSE IF NOT Rope.Equal[GetWord[keyLine], ":"] THEN ErrorReport[format, keyLine];
fields[n] ¬ NEW[FieldRep];
nFields ¬ nFields+1;
fields[n].id ¬ Rope.Substr[rope, 0, length];
rope ¬ GetWord[keyLine];
length ¬ Rope.Length[rope];
IF Rope.Fetch[rope, length-1] = ', THEN rope ¬ Rope.Substr[rope, 0, length-1];
fields[n].type ¬ SELECT TRUE FROM
Equal[rope, "integer"] => integer,
Equal[rope, "real"]  => real,
Equal[rope, "pair"]  => pair,
Equal[rope, "triple"]  => triple,
Equal[rope, "nats"]  => nats,
ENDCASE => none;
ENDLOOP;
fields.length ¬ nFields;
};
NumberOfLinesToConvert: PUBLIC PROC [stream: STREAM] RETURNS [INTEGER] ~ {
GoodLine: PROC RETURNS [BOOL] ~ {
DO
line ¬ GetNonBlankLine[stream, line];
SELECT line.type FROM
key => RETURN[FALSE];
comment => LOOP;
ENDCASE => {
rope: ROPE ¬ GetWord[line];
RETURN[rope = NIL OR NOT Equal["~", rope]];
};
ENDLOOP;
};
line: Line ¬ ObtainLine[];
nLines: INTEGER ¬ 0;
sIndexSave: INT ¬ IO.GetIndex[stream];      -- start data conversion from here
DO
IF GoodLine[ ! IO.EndOfStream => GOTO eof]
THEN nLines ¬ nLines+1
ELSE EXIT;
REPEAT
eof => NULL;
ENDLOOP;
IO.SetIndex[stream, sIndexSave];        -- reset for upcoming conversions
ReleaseLine[line];
RETURN[nLines];
};
NWordsInRope: PUBLIC PROC [line: ROPE] RETURNS [INTEGER] ~ {
nWords, index: INTEGER ¬ 0;
length: INTEGER ¬ Rope.Length[line];
IF line = NIL THEN RETURN[0];
index ¬ Rope.SkipOver[line, 0, " \t"];
WHILE index < length DO
nWords ¬ nWords+1;
index ¬ Rope.SkipOver[line, Rope.SkipTo[line, index, " \t"], " \t"];
ENDLOOP;
RETURN[nWords];
};
Get Procedures
GetStream: PUBLIC PROC [fileName: ROPE] RETURNS [stream: STREAM] ~ {
stream ¬ FS.StreamOpen[FileNames.ResolveRelativePath[fileName]
! FS.Error => CONTINUE];
};
GetLine: PUBLIC PROC [stream: STREAM, line: Line ¬ NIL] RETURNS [Line] ~ {
Process.CheckForAbort[];
IF line = NIL THEN line ¬ ObtainLine[];
line.rope ¬ NIL;
line.index ¬ 0;
line.type ¬ blank;
line.rope ¬ IO.GetLineRope[stream];
line.length ¬ Rope.Length[line.rope];
line.stream ¬ stream;
IF NOT BlankLine[line.rope] THEN {
rope: ROPE ¬ GetWord[line];
IF Rope.Equal["--", Rope.Substr[rope, 0, 2]]
THEN line.type ¬ comment
ELSE IF Rope.Fetch[rope, Rope.Length[rope]-1] = '~
THEN line.type ¬ key
ELSE line.type ¬ IF Equal["~", GetWord[line]] THEN key ELSE data;
line.index ¬ 0;
};
RETURN[line];
};
GetDataLine: PUBLIC PROC [stream: STREAM, line: Line ¬ NIL] RETURNS [Line] ~ {
DO
line ¬ GetLine[stream, line];
IF line.type = data THEN RETURN[line];
ENDLOOP;
};
GetWord: PUBLIC PROC [line: Line] RETURNS [word: ROPE] ~ {
Return the next whitespace-delimited word in line.
index: INTEGER;
IF line = NIL THEN RETURN[NIL];
IF line.rope = NIL OR line.length = 0 OR line.index = line.length THEN RETURN[NIL];
IF line.index = 0 THEN line.index ¬ Rope.SkipOver[line.rope, 0, " \t"];
index ¬ Rope.SkipTo[line.rope, line.index, " \t"];
word ¬ Rope.Substr[line.rope, line.index, index-line.index];
line.index ¬ Rope.SkipOver[line.rope, index, " \t"];
};
GetInteger: PUBLIC PROC [line: Line] RETURNS [INTEGER] ~ {
word: ROPE ¬ GetWord[line];
IF word = NIL THEN ErrorReport[format, line];
RETURN[Convert.IntFromRope[word ! Convert.Error => ErrorReport[convert, line]]];
};
GetReal: PUBLIC PROC [line: Line] RETURNS [REAL] ~ {
word: ROPE ¬ GetWord[line];
IF word = NIL THEN ErrorReport[format, line];
RETURN[Convert.RealFromRope[word ! Convert.Error => ErrorReport[convert, line]]];
};
GetPair: PUBLIC PROC [line: Line] RETURNS [Pair] ~ {
p: ARRAY [0..2) OF REAL;
FOR n: NAT IN[0..2) DO
word: ROPE ¬ GetWord[line];
IF word = NIL THEN ErrorReport[format, line];
p[n] ¬ Convert.RealFromRope[word ! Convert.Error => ErrorReport[convert, line]];
ENDLOOP;
RETURN[[p[0], p[1]]];
};
GetTriple: PUBLIC PROC [line: Line] RETURNS [Triple] ~ {
p: ARRAY [0..3) OF REAL;
FOR n: NAT IN[0..3) DO
word: ROPE ¬ GetWord[line];
IF word = NIL THEN ErrorReport[format, line];
p[n] ¬ Convert.RealFromRope[word ! Convert.Error => ErrorReport[convert, line]];
ENDLOOP;
RETURN[[p[0], p[1], p[2]]];
};
GetNats: PUBLIC PROC [line: Line] RETURNS [nats: NatSequence] ~ {
maxLength: NAT ← NWordsInRope[Rope.Substr[line.rope, line.index, line.length-line.index]];
maxLength: NAT ¬ NWordsInRope[Rope.Substr[line.rope, line.index]];
nats ¬ NEW[NatSequenceRep[maxLength]];
FOR n: NAT IN [0..maxLength) DO
word: ROPE ¬ GetWord[line];
IF Rope.Length[word] > 1 AND Rope.Equal[Rope.Substr[word, 0, 2], "--"] THEN EXIT;
nats[n] ¬ Convert.IntFromRope[word ! Convert.Error => ErrorReport[convert, line]];
nats.length ¬ nats.length+1;
ENDLOOP;
};
Read Procedures
maxNTriples: CARDINAL ~ G2dBasic.maxNTriples;
ReadRope: PUBLIC PROC [stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE]
RETURNS [rope: ROPE] ~ {
line: Line ¬ FindKeyWord[stream, keyWord, circularSearch, , ObtainLine[]];
rope ¬ Rope.Substr[line.rope, line.index, Rope.Length[line.rope]-line.index];
ReleaseLine[line];
};
ReadInteger: PUBLIC PROC [stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE]
RETURNS [n: INTEGER] ~ {
line: Line ¬ ObtainLine[];
n ¬ GetInteger[GetLineAfterKey[stream, keyWord, circularSearch, line]];
ReleaseLine[line];
};
ReadReal: PUBLIC PROC [stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE]
RETURNS [r: REAL] ~ {
line: Line ¬ ObtainLine[];
r ¬ GetReal[GetLineAfterKey[stream, keyWord, circularSearch, line]];
ReleaseLine[line];
};
ReadPair: PUBLIC PROC [stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE]
RETURNS [p: Pair] ~ {
line: Line ¬ ObtainLine[];
p ¬ GetPair[GetLineAfterKey[stream, keyWord, circularSearch, line]];
ReleaseLine[line];
};
ReadTriple: PUBLIC PROC [stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE]
RETURNS [t: Triple] ~ {
line: Line ¬ ObtainLine[];
t ¬ GetTriple[GetLineAfterKey[stream, keyWord, circularSearch, line]];
ReleaseLine[line];
};
ReadIntegerSequence: PUBLIC PROC [
stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE, nElements: INT ¬ 0]
RETURNS [IntegerSequence]
~ {
line: Line ¬ FindKeyWord[stream, keyWord, circularSearch, , ObtainLine[]];
nLines: INT ¬ IF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
integers: IntegerSequence ¬ NEW[IntegerSequenceRep[nLines]];
integers.length ¬ nLines;
FOR n: INT IN [0..nLines) DO
line ¬ GetDataLine[stream, line ! IO.EndOfStream => GOTO eof];
integers[n] ¬ GetInteger[line];
REPEAT eof => NULL;
ENDLOOP;
ReleaseLine[line];
RETURN[integers];
};
ReadRealSequence: PUBLIC PROC [
stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE, nElements: INT ¬ 0]
RETURNS [RealSequence]
~ {
line: Line ¬ FindKeyWord[stream, keyWord, circularSearch, , ObtainLine[]];
nLines: INT ¬ IF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
reals: RealSequence ¬ NEW[RealSequenceRep[nLines]];
reals.length ¬ nLines;
FOR n: INT IN [0..nLines) DO
line ¬ GetDataLine[stream ! IO.EndOfStream => GOTO eof];
reals[n] ¬ GetReal[line];
REPEAT eof => NULL;
ENDLOOP;
ReleaseLine[line];
RETURN[reals];
};
ReadPairSequence: PUBLIC PROC [
stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE, nElements: INT ¬ 0]
RETURNS [PairSequence]
~ {
line: Line ¬ FindKeyWord[stream, keyWord, circularSearch, , ObtainLine[]];
nLines: INT ¬ IF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
pairs: PairSequence ¬ NEW[PairSequenceRep[nLines]];
pairs.length ¬ nLines;
FOR n: INT IN [0..nLines) DO
line ¬ GetDataLine[stream, line ! IO.EndOfStream => GOTO eof];
pairs[n] ¬ GetPair[line];
REPEAT eof => NULL;
ENDLOOP;
ReleaseLine[line];
RETURN[pairs];
};
ReadTripleSequence: PUBLIC PROC [
stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE, nElements: INT ¬ 0]
RETURNS [TripleSequence]
~ {
line: Line ¬ FindKeyWord[stream, keyWord, circularSearch, , ObtainLine[]];
indexed: BOOL ¬ Rope.Find[line.rope, "index",, FALSE] # -1;
nLines: INT ¬ MIN[maxNTriples, IF nElements # 0
THEN nElements ELSE NumberOfLinesToConvert[stream]];
triples: TripleSequence ¬ NEW[TripleSequenceRep[nLines]];
triples.length ¬ nLines;
FOR n: INT IN [0..nLines) DO
line ¬ GetDataLine[stream, line ! IO.EndOfStream => GOTO eof];
IF indexed THEN [] ¬ GetWord[line];
triples[n] ¬ GetTriple[line];
REPEAT eof => NULL;
ENDLOOP;
ReleaseLine[line];
RETURN[triples];
};
ReadSurfaceSequence: PUBLIC PROC [
stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE, nElements: INT ¬ 0]
RETURNS [SurfaceSequence]
~ {
line: Line ¬ FindKeyWord[stream, keyWord, circularSearch, , ObtainLine[]];
indexed: BOOL ¬ Rope.Find[line.rope, "index",, FALSE] # -1;
nLines: INT ¬ IF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
nats: SurfaceSequence ¬ NEW[SurfaceSequenceRep[nLines]];
nats.length ¬ nLines;
FOR n: INT IN [0..nLines) DO
line ¬ GetDataLine[stream, line];
IF indexed THEN [] ¬ GetWord[line];
nats[n].vertices ¬ GetNats[line];
ENDLOOP;
ReleaseLine[line];
RETURN[nats];
};
ReadFields: PUBLIC PROC [
stream: STREAM, keyWord: ROPE, circularSearch: BOOL ¬ FALSE, nElements: INT ¬ 0]
RETURNS [fields: FieldSequence]
~ {
SkipTriple: PROC [l: Line] ~ {[] ¬ GetWord[l]; [] ¬ GetWord[l]; [] ¬ GetWord[l]};
line: Line ¬ FindKeyWord[stream, keyWord, circularSearch, , ObtainLine[]]; -- keyword line
f: FieldSequence ¬ fields ¬ InitializeFields[line];
nLines: INTEGER ¬ IF nElements#0 THEN nElements ELSE NumberOfLinesToConvert[stream];
nTripleLines: INTEGER ¬ MIN[maxNTriples, nLines];
FOR n: INT IN [0..fields.length) DO       -- allocate sequences
fields[n].sequence ¬ SELECT fields[n].type FROM
integer => NEW[IntegerSequenceRep[nLines]],
real  => NEW[RealSequenceRep[nLines]],
pair  => NEW[PairSequenceRep[nLines]],
triple  => NEW[TripleSequenceRep[nTripleLines]],
nats  => NEW[SurfaceSequenceRep[nLines]],
ENDCASE => NIL;
ENDLOOP;
FOR n: NAT IN[0..fields.length) DO       -- assign sequence length
SELECT fields[n].type FROM
integer => NARROW[fields[n].sequence, IntegerSequence].length ¬ nLines;
real => NARROW[fields[n].sequence, RealSequence].length ¬ nLines;
pair => NARROW[fields[n].sequence, PairSequence].length ¬ nLines;
triple => NARROW[fields[n].sequence, TripleSequence].length ¬ nTripleLines;
nats => NARROW[fields[n].sequence, SurfaceSequence].length ¬ nLines;
ENDCASE => NULL;
ENDLOOP;
FOR n: NAT IN [0..nLines) DO         -- line by line data conversions
CedarProcess.CheckAbort[];
line ¬ GetDataLine[stream, line ! IO.EndOfStream => GOTO eof];
FOR nn: NAT IN [0..fields.length) DO
SELECT fields[nn].type FROM
integer => {
s: IntegerSequence ¬ NARROW[fields[nn].sequence];
s[n] ¬ GetInteger[line];
};
real => {
s: RealSequence ¬ NARROW[fields[nn].sequence];
s[n] ¬ GetReal[line];
};
pair => {
s: PairSequence ¬ NARROW[fields[nn].sequence];
s[n] ¬ GetPair[line];
};
triple => {
s: TripleSequence ¬ NARROW[fields[nn].sequence];
IF n < maxNTriples THEN s[n] ¬ GetTriple[line] ELSE SkipTriple[line];
};
nats => {
s: SurfaceSequence ¬ NARROW[fields[nn].sequence];
s[n].vertices ¬ GetNats[line];
};
ENDCASE => NULL;
ENDLOOP;
REPEAT
eof => NULL;
ENDLOOP;
ReleaseLine[line];
};
ReadMatrix: PUBLIC PROC [stream: STREAM] RETURNS [m: Matrix] ~ {
NB: note that G3dMatrices are 4 by 4 by definition.
m ← NEW[G3dMatrix.MatrixRep];
FOR row: INT IN [0 .. 4) DO
FOR col: INT IN [0 .. 4) DO
m[row][col] ← IO.GetReal[stream];
ENDLOOP;
ENDLOOP;
};
Write Procedures
WritePair: PUBLIC PROC [stream: STREAM, p: Pair] ~ {
WriteJustified[stream, p.x];
WriteJustified[stream, p.y];
IO.PutRope[stream, "\t"];
};
WriteTriple: PUBLIC PROC [stream: STREAM, t: Triple] ~ {
WriteJustified[stream, t.x];
WriteJustified[stream, t.y];
WriteJustified[stream, t.z];
IO.PutRope[stream, "\t"];
};
WriteJustified: PUBLIC PROC [stream: STREAM, r: REAL] ~ {
IF r >= 0.0 THEN IO.PutRope[stream, " "];
IO.PutF1[stream, "%6.5f ", IO.real[r]]
};
WriteFields: PUBLIC PROC [stream: STREAM, keyWord: ROPE, fields: FieldSequence] ~ {
RopeFromFieldType: PROC [type: FieldType] RETURNS [ROPE] ~ {
RETURN [SELECT type FROM
integer => "integer",
real  => "real",
pair  => "pair",
triple  => "triple",
nats  => "nats",
ENDCASE => NIL];
};
IF fields # NIL THEN {
nElements: INTEGER ¬ 0;
IO.PutF1[stream, "\n%g~ ", IO.rope[keyWord]];
FOR n: NAT IN [0..fields.length) DO
nElements ¬ MAX[nElements, SELECT fields[n].type FROM
integer => NARROW[fields[n].sequence, IntegerSequence].length,
real =>  NARROW[fields[n].sequence, RealSequence].length,
pair =>  NARROW[fields[n].sequence, PairSequence].length,
triple =>  NARROW[fields[n].sequence, TripleSequence].length,
nats =>  NARROW[fields[n].sequence, SurfaceSequence].length,
ENDCASE => nElements];
ENDLOOP;
FOR n: NAT IN [0..fields.length) DO
IO.PutF[stream, "%g: %g ",
IO.rope[fields[n].id], IO.rope[RopeFromFieldType[fields[n].type]]];
ENDLOOP;
IO.PutRope[stream, "\n\n"];
FOR n: NAT IN [0..nElements) DO
FOR nn: NAT IN [0..fields.length) DO
SELECT fields[nn].type FROM
integer => {
s: IntegerSequence ¬ NARROW[fields[nn].sequence];
IO.PutF1[stream, "%5g ", IO.int[INT[s[n]]]];
};
real => {
s: RealSequence ¬ NARROW[fields[nn].sequence];
IO.PutF1[stream, "%9g ", IO.real[s[n]]];
};
pair => {
s: PairSequence ¬ NARROW[fields[nn].sequence];
IO.PutF[stream, "%9g %9g\t\t ", IO.real[s[n].x], IO.real[s[n].y]];
};
triple => {
s: TripleSequence ¬ NARROW[fields[nn].sequence];
IO.PutF[stream, "%9g %9g %9g\t\t ", IO.real[s[n].x], IO.real[s[n].y], IO.real[s[n].z]];
};
nats => {
t: SurfaceSequence ¬ NARROW[fields[nn].sequence];
s: NatSequence ¬ t[n].vertices;
FOR nnn: NAT IN [0..s.length) DO
IO.PutF1[stream, "%5g ", IO.int[INT[s[nnn]]]];
ENDLOOP;
};
ENDCASE => NULL;
ENDLOOP;
IO.PutRope[stream, "\n"];
ENDLOOP;
};
};
WriteMatrix: PUBLIC PROC [stream: STREAM, m: Matrix] ~ {
NB: note that G3dMatrices are 4 by 4 by definition.
FOR row: INT IN [0 .. 4) DO
FOR col: INT IN [0 .. 4) DO
IO.PutF1[stream," %g", IO.real[m[row][col]]];
ENDLOOP;
IO.PutRope[stream,"\n"];
ENDLOOP;
};
Points/Polys Procedures
ReadPointsPolygons: PUBLIC PROC [fileName: ROPE]
RETURNS [points: TripleSequence, polygons: SurfaceSequence, errorMessage: ROPE]
~ {
stream: IO.STREAM ¬ NIL;
points ¬ NIL;
polygons ¬ NIL;
IF (stream ¬ FS.StreamOpen[fileName ! FS.Error => CONTINUE]) = NIL THEN {
errorMessage ¬ "Can't open file.";
RETURN;
};
points ¬ ReadTripleSequence[stream, "Vertices", TRUE];
polygons ¬ ReadSurfaceSequence[stream, "Polygons", TRUE];
IO.Close[stream];
};
WritePointsPolygons: PUBLIC PROC [
fileName: ROPE,
points: TripleSequence,
polygons: SurfaceSequence]
~ {
stream: STREAM ¬ FS.StreamOpen[fileName, $create];
IO.PutRope[stream, "Vertices~ xyzCoords: triple\n\n"];
FOR n: NAT IN [0..points.length) DO
WriteTriple[stream, points[n]];
IO.PutRope[stream, "\n"];
ENDLOOP;
IO.PutRope[stream, "\n\nPolygons~ vertices: nats\n\n"];
FOR n: NAT IN [0..polygons.length) DO
nats: NatSequence ~ polygons[n].vertices;
FOR i: NAT IN [0..nats.length) DO
IO.PutF1[stream, "%g\t", IO.int[nats[i]]];
ENDLOOP;
IO.PutRope[stream, "\n"];
ENDLOOP;
IO.Close[stream];
};
Printing Procedures
PrintPair: PUBLIC PROC [stream: STREAM, pair: Pair, name: ROPE ¬ NIL] ~ {
IF stream = NIL THEN RETURN;
IF name = NIL THEN stream.PutF["%f\t%f\n", IO.real[pair.x], IO.real[pair.y]]
ELSE stream.PutF["%g\t[%6.3f\t%6.3f]\n", IO.rope[name], IO.real[pair.x], IO.real[pair.y]];
};
PrintTriple: PUBLIC PROC [stream: STREAM, triple: Triple, name: ROPE ¬ NIL] ~ {
IF stream = NIL THEN RETURN;
IF name = NIL
THEN IO.PutF[stream, "%f\t%f\t%f\n", IO.real[triple.x], IO.real[triple.y], IO.real[triple.z]]
ELSE IO.PutFL[stream, "%g\t[%6.3f\t%6.3f\t%6.3f]\n",
LIST[IO.rope[name], IO.real[triple.x], IO.real[triple.y], IO.real[triple.z]]];
};
PrintQuad: PUBLIC PROC [stream: STREAM, quad: Quad, name: ROPE ¬ NIL] ~ {
IF stream = NIL THEN RETURN;
IF name # NIL
THEN IO.PutFL[stream, "%g: [%f\t%f\t%f\t%f]\n",
LIST[IO.rope[name], IO.real[quad.x], IO.real[quad.y], IO.real[quad.z], IO.real[quad.w]]]
ELSE IO.PutFL[stream, "%6.3f\t%6.3f\t%6.3f\t%6.3f\n",
LIST[IO.real[quad.x], IO.real[quad.y], IO.real[quad.z], IO.real[quad.w]]];
};
PrintMatrix: PUBLIC PROC [stream: STREAM, matrix: Matrix, name: ROPE ¬ NIL] ~ {
IF stream = NIL OR matrix = NIL THEN RETURN;
IF name # NIL THEN IO.PutF1[stream, "%g\n", IO.rope[name]];
FOR i: NAT IN [0..3] DO
IO.PutFL[stream, "%6.3f\t%6.3f\t%6.3f\t%6.3f\n",
LIST[IO.real[matrix[i][0]], IO.real[matrix[i][1]], IO.real[matrix[i][2]], IO.real[matrix[i][3]]]];
ENDLOOP;
};
TiogaAccess
WriteCreate: PUBLIC PROC [title: ROPE] RETURNS [w: Writer] ~ {
w ¬ TiogaAccess.Create[];
WriteNode[w, title, "bi", TRUE];
TiogaAccess.Nest[w, 1];
WriteNode[w, IO.PutFR1["Created %g", IO.time[]], "i", TRUE, $code];
WriteNode[w, "", "", TRUE];
};
WriteNode: PUBLIC PROC [
w: Writer,
node: ROPE,
looks: ROPE ¬ NIL,
comment: BOOL ¬ FALSE,
format: ATOM ¬ NIL]
~ {
tc: TiogaAccess.TiogaChar ¬ [0, '\000, ALL[FALSE], NIL, comment, FALSE, 0, NIL];
FOR n: INT IN [0..Rope.Length[looks]) DO-- set the looks
c: CHAR ¬ Rope.Fetch[looks, n];
IF c IN Tioga.Look THEN tc.looks[c] ¬ TRUE;
ENDLOOP;
tc.format ¬ format;
FOR n: INT IN [0..Rope.Length[node]) DO  -- write the node
tc.char ¬ Rope.Fetch[node, n];
TiogaAccess.Put[w, tc];
ENDLOOP;
tc.endOfNode ¬ TRUE;
TiogaAccess.Put[w, tc];
};
WritePartialNode: PUBLIC PROC [
w: Writer,
node: ROPE,
looks: ROPE ¬ NIL,
comment: BOOL ¬ FALSE]
~ {
tc: TiogaAccess.TiogaChar ¬ [0, '\000, ALL[FALSE], NIL, comment, FALSE, 0, NIL];
FOR n: INT IN [0..Rope.Length[looks]) DO-- set the looks
c: CHAR ¬ Rope.Fetch[looks, n];
IF c IN Tioga.Look THEN tc.looks[c] ¬ TRUE;
ENDLOOP;
FOR n: INT IN [0..Rope.Length[node]) DO  -- write the node
tc.char ¬ Rope.Fetch[node, n];
TiogaAccess.Put[w, tc];
ENDLOOP;
};
WriteKey: PUBLIC PROC [w: Writer, key: ROPE, val1, val2, val3: IO.Value ¬ [null[]]] ~ {
WritePartialNode[w, key, "b"];
SELECT TRUE FROM
val1 # [null[]] AND val2 # [null[]] AND val3 # [null[]] =>
WritePartialNode[w, IO.PutFR[" %g %g %g ", val1, val2, val3]];
val1 # [null[]] AND val2 # [null[]] =>
WritePartialNode[w, IO.PutFR[" %g %g ", val1, val2]];
val1 # [null[]] =>
WritePartialNode[w, IO.PutFR1[" %g ", val1]];
ENDCASE;
WriteNodeEnd[w];
};
WriteNodeEnd: PUBLIC PROC [w: Writer] ~ {
tc: TiogaAccess.TiogaChar ¬ [0, '\000, ALL[FALSE], NIL, FALSE, FALSE, 0, NIL];
tc.endOfNode ¬ TRUE;
TiogaAccess.Put[w, tc];
};
END.
..
Old Code
VertexValidities:  TYPE ~ RECORD [normal, color, texture, transmittance: BOOLFALSE];
VertexProc:   TYPE ~ PROC [
vertexIndex, nVertices:  CARDINAL,
point, normal, color:  Triple ← [0.0, 0.0, 0.0],
texture:      Pair ← [0.0, 0.0],
transmittance:    REAL ← 1.0,
validities:      VertexValidities ← []]
RETURNS [continue:   BOOLTRUE];
Return FALSE if the client's vertex array or sequence is about to overflow.
ShapeRep:   TYPE ~ RECORD [
type:       {patch, poly} ← poly,  -- patch or polygon?
insideVisible:    BOOLFALSE,    -- true iff backfacing visible
vertexValidities:    VertexValidities ← [],  -- what's in the file for a vertex?
polygons:      SurfaceSequence ← NIL,    -- the polygons
faceNormals:     TripleSequence ← NIL,  -- polygon normals
faceColors:     TripleSequence ← NIL,  -- polygon colors
faceTransmits:   RealSequence ← NIL,  -- polygon transmits
props:       PropList ← NIL    -- for unconventional file formats
];
ShapeFromStream: PUBLIC PROC [
stream: STREAM,
vertexProc: VertexProc,
checkNVertices: BOOLFALSE]
RETURNS [s: Shape]
~ {
Get ready:
AddToMap: PROC [index: CARDINAL, number: INTEGER] ~ {
IF map = NIL THEN map ← NEW[IntegerSequenceRep[100]];
IF index >= map.maxLength THEN map ←
G2dBasic.LengthenIntegerSequence[map, MAX[1.3, REAL[index+1]/map.maxLength]];
map[index] ← number;
map.length ← MAX[map.length, index+1];
};
Eq: PROC [r1, r2: ROPE] RETURNS [BOOL] ~ {RETURN[Rope.Equal[r1, r2, FALSE]]};
CheckHeader: PROC [key: ROPE] ~ { -- hint about shape type, nVertices, nPolygons?
streamIndex: INTIO.GetIndex[stream]; -- need to reset if key found
header: Line ← ObtainLine[];
IF (header ← FindKeyWord[stream, key,, 10 ! Error => CONTINUE]) # NIL THEN {
rope, previous: ROPE;
DO
ENABLE Convert.Error => CONTINUE;
Seq: PROC [r:ROPE] RETURNS [b:BOOL] ~ {b𡤎q[Rope.Substr[rope,,Rope.Size[r]],r]};
IF (rope ← GetWord[header]) = NIL THEN EXIT;
SELECT TRUE FROM
Seq["Polygon"]   => s.type ← poly;
Seq["Bezier"]    => s.type ← patch;
Seq["InsideVisible"]  => s.insideVisible ← TRUE;
Seq["CountFromOne"] => countFromOne ← TRUE;
Seq["vertices"]   => nVertices ← Convert.IntFromRope[previous];
Seq["polygons"]    => nPolygons ← Convert.IntFromRope[previous];
Seq["patches"]    => nPolygons ← Convert.IntFromRope[previous];
ENDCASE;
previous ← rope;
ENDLOOP;
IO.SetIndex[stream, streamIndex];
};
ReleaseLine[header];
};
line: Line;
fields: FieldSequence;
vertexOverflow, countFromOne: BOOLFALSE;
map, ids: IntegerSequence ← NIL;
nVertices, nPolygons, vertexIndex: CARDINAL ← 0;
IF stream = NIL THEN RETURN;
s ← NEW[ShapeRep];
CheckHeader["ShapeHeader"];
CheckHeader["SurfaceType"];
Read Vertices:
line ← FindKeyWord[stream, "Vertices", FALSE,, ObtainLine[]];
IF nVertices = 0 AND checkNVertices THEN nVertices ← NumberOfLinesToConvert[stream];
fields ← InitializeFields[line];
ids ← NEW[IntegerSequenceRep[fields.length]];
FOR n: NAT IN [0..fields.length) DO  -- what's a vertex?
SELECT TRUE FROM
Eq[fields[n].id, "normalVec"]  => s.vertexValidities.normal ← TRUE;
Eq[fields[n].id, "rgbColor"]   => s.vertexValidities.color ← TRUE;
Eq[fields[n].id, "textureCoords"] => s.vertexValidities.texture ← TRUE;
ENDCASE;
ENDLOOP;
FOR n: NAT IN [0..fields.length) DO
ids[n] ← SELECT TRUE FROM
Eq[fields[n].id, "index"]   => 0,
Eq[fields[n].id, "xyzCoords"]  => 1,
Eq[fields[n].id, "normalVec"]  => 2,
Eq[fields[n].id, "rgbColor"]   => 3,
Eq[fields[n].id, "textureCoords"] => 4,
Eq[fields[n].id, "transmittance"] => 5,
ENDCASE => -1;
ENDLOOP;
DO
streamIndex: INTIO.GetIndex[stream]; -- need to reset if line is a key
line ← GetLine[stream, line ! IO.EndOfStream => GOTO eof];
SELECT line.type FROM
data => {
transmittance: REAL;
texture: Pair;
point, normal, color: Triple;
FOR n: NAT IN [0..fields.length) DO
SELECT ids[n] FROM
0 => AddToMap[GetInteger[line], vertexIndex];
1 => point   ← GetTriple[line];
2 => normal  ← GetTriple[line];
3 => color   ← GetTriple[line];
4 => texture  ← GetPair[line];
5 => transmittance ← GetReal[line];
ENDCASE;
ENDLOOP;
IF NOT vertexProc[vertexIndex, nVertices, point, normal, color, texture, transmittance, s.vertexValidities] THEN {
vertexOverflow ← TRUE;
EXIT;
};
vertexIndex ← vertexIndex+1;
};
key => {
IO.SetIndex[stream, streamIndex];
EXIT;
};
ENDCASE;
REPEAT
eof => NULL;
ENDLOOP;
ReleaseLine[line];
Read Polygons:
fields ← ReadFields[stream, IF s.type = poly THEN "Polygons" ELSE "Patches",, nPolygons];
FOR n: NAT IN [0..fields.length) DO
PutProp: PROC ~ {s.props ← Atom.PutPropOnList[
s.props, Convert.AtomFromRope[fields[n].id], fields[n].sequence]};
SELECT fields[n].type FROM
integer =>
IF NOT Eq[fields[n].id, "index"] THEN PutProp[]; -- (ignore indices)
real =>
IF Eq[fields[n].id, "transmittance"]
THEN s.faceTransmits ← NARROW[fields[n].sequence]
ELSE PutProp[];
triple =>
SELECT TRUE FROM
Eq[fields[n].id, "rgbColor"] => s.faceColors ← NARROW[fields[n].sequence];
Eq[fields[n].id, "normalVec"] => s.faceNormals ← NARROW[fields[n].sequence];
ENDCASE => PutProp[];
nats =>
IF Eq[fields[n].id, "vertices"]
THEN s.polygons ← NARROW[fields[n].sequence]
ELSE PutProp[];
ENDCASE =>
PutProp[];
ENDLOOP;
Tests:
IF vertexOverflow THEN {   -- cull smashed polygons
n: NAT ← 0;
DO
poly: NatSequence ← s.polygons[n];
FOR nn: NAT IN [0..poly.length) DO
IF poly[nn] >= vertexIndex THEN { -- overwrite this polygon
s.polygons.length ← s.polygons.length-1;
IF n # s.polygons.length THEN s.polygons[n] ← s.polygons[s.polygons.length];
EXIT;
};
REPEAT
FINISHED => n ← n+1;
ENDLOOP;
IF n >= s.polygons.length THEN RETURN;
ENDLOOP;
};
SELECT TRUE FROM
map # NIL =>   -- take care of strangely indexed vertices:
FOR n: NAT IN [0..s.polygons.length) DO
poly: NatSequence ← s.polygons[n];
FOR nn: NAT IN [0..poly.length) DO
poly[nn] ← map[poly[nn]];
ENDLOOP;
ENDLOOP;
countFromOne =>
FOR n: NAT IN [0..s.polygons.length) DO
poly: NatSequence ← s.polygons[n];
FOR nn: NAT IN [0..poly.length) DO
poly[nn] ← poly[nn]-1;  -- vertices are indexed from 0
ENDLOOP;
ENDLOOP;
ENDCASE;
FOR n: NAT IN [0..s.polygons.length) DO-- check polygon validity:
poly: NatSequence ← s.polygons[n];
FOR nn: NAT IN [0..poly.length) DO
IF poly[nn] >= vertexIndex THEN
Error[IO.PutFR["polygon %g refers to non-existent vertex", IO.int[n]]];
ENDLOOP;
ENDLOOP;
};
NumberOfLinesToConvert: PROC [stream: STREAM, nElementsPerLine: INTEGER]
RETURNS [INTEGER] ~ {
nElements: INTEGER ← 0;
indexSave: INTIO.GetIndex[stream];      -- start data conversion from here
DO
line: ROPEIO.GetLineRope[stream ! IO.EndOfStream, IO.Error => GOTO eof];
index: INTEGER ← Rope.SkipOver[line, 0, " \t"];
IF index = Rope.Length[line] THEN LOOP;    -- blank line?
SELECT Rope.Fetch[line, index] FROM
'-, '. => IF Rope.Fetch[line, index+1] NOT IN ['0..'9] THEN EXIT;
'0, '1, '2, '3, '4, '5, '6, '7, '8, '9 => NULL;
ENDCASE => EXIT;
IF NWordsInRope[line] # nElementsPerLine THEN EXIT;
nElements ← nElements+1;
REPEAT
eof => NULL;
ENDLOOP;
IO.SetIndex[stream, indexSave];        -- reset for upcoming conversions
RETURN[nElements];
};
NumberOfLinesToConvert: PROC [stream: STREAM, nElementsPerLine: INTEGER]
RETURNS [INTEGER] ~ {
WordType: TYPE ~ {number, none, other};
TestWord: PROC RETURNS [WordType] ~ {
WHILE index < refText.length DO
c: CHAR ← refText[index];
index ← index+1;
SELECT c FROM
Ascii.SP, Ascii.TAB => EXIT;
'., '0, '1, '2, '3, '4, '5, '6, '7, '8, '9 => NULL;
ENDCASE => RETURN[other];
ENDLOOP;
RETURN[number];
};
SkipWhiteAndTestWord: PROC RETURNS [WordType] ~ {
c: CHAR;
DO
IF index = refText.length THEN RETURN[none];
c ← refText[index];
index ← index+1;
IF c # Ascii.SP AND c # Ascii.TAB THEN EXIT;
ENDLOOP;
RETURN[SELECT c FROM
'., '-, '0, '1, '2, '3, '4, '5, '6, '7, '8, '9 => TestWord[],
ENDCASE => other
];
};
GoodLine: PROC RETURNS [BOOL] ~ {
nNumbersInLine: INTEGER ← 0;
index ← refText.length ← 0;
[] ← Rope.AppendChars[refText, GetNonBlankLine[stream].rope];
DO
SELECT SkipWhiteAndTestWord[] FROM
none => RETURN[nNumbersInLine = nElementsPerLine];
number => nNumbersInLine ← nNumbersInLine+1;
ENDCASE => RETURN[FALSE];
ENDLOOP;
};
sIndexSave: INTIO.GetIndex[stream];      -- start data conversion from here
index, nLines: INTEGER ← 0;
refText: TEXT ← RefText.ObtainScratch[1000];
DO
IF GoodLine[ ! IO.EndOfStream => GOTO eof]
THEN nLines ← nLines+1
ELSE EXIT;
REPEAT
eof => NULL;
ENDLOOP;
RefText.ReleaseScratch[refText];
IO.SetIndex[stream, sIndexSave];        -- reset for upcoming conversions
RETURN[nLines];
};
NatLine: PROC [line: Line] RETURNS [BOOL] ~ {
DO
word: ROPE ← GetWord[line];
IF word = NIL THEN RETURN[TRUE];
refText ← Rope.ToRefText[GetWord[line]];
FOR n: NAT IN [0..refText.length) DO
IF refText[n] NOT IN ['0..'9] THEN RETURN[FALSE];
ENDLOOP;
ENDLOOP;
};