ThreeDIOImpl.mesa
Copyright © 1985 by Xerox Corporation. All rights reserved.
Bloomenthal, January 19, 1987 4:48:37 pm PST
Crow, October 14, 1986 6:03:27 pm PDT
DIRECTORY Ascii, Convert, Imager, IO, Rope, ThreeDIO, Vector3d;
ThreeDIOImpl: CEDAR PROGRAM
IMPORTS Convert, IO, Rope
EXPORTS ThreeDIO
~ BEGIN
OPEN ThreeDIO;
Type Declarations
Error:   PUBLIC ERROR [reason: ROPE] = CODE;
ErrorType: TYPE ~ {notFound, format, convert};
Private Support Procedures
ErrorReport: PROC [errorType: ErrorType, line: Line ← NIL, keyword: ROPENIL] ~ {
SELECT errorType FROM
notFound => Error[Rope.Concat["Keyword not found: ", keyword]];
format => Error[Rope.Concat["bad format in line: ", LineNumber[line]]];
convert => Error[Rope.Concat["bad conversion in line: ", LineNumber[line]]];
ENDCASE => NULL;
};
LineNumber: PROC [line: Line] RETURNS [ROPE] ~ {
testLine: ROPE;
nLine: INTEGER ← 0;
IF line = NIL THEN RETURN[NIL];
IO.SetIndex[line.stream, 0];
DO
testLine ← IO.GetLineRope[line.stream ! IO.EndOfStream, IO.Error => GOTO eof];
IF Rope.Equal[line.rope, testLine]
THEN RETURN[Rope.Cat[Convert.RopeFromInt[nLine], ": ", line.rope]];
nLine ← nLine+1;
REPEAT
eof => RETURN[line.rope];
ENDLOOP;
};
BlankLine: PROC [line: ROPE] RETURNS [BOOL] ~ {
RETURN [Rope.SkipOver[line, 0, " \t"] = Rope.Length[line]];
};
GetNonBlankLine: PROC [stream: STREAM] RETURNS [line: Line] ~ {
DO
line ← GetLine[stream];
IF NOT BlankLine[line.rope] THEN EXIT;
ENDLOOP;
};
GetDataLine: PROC [stream: STREAM] RETURNS [line: Line] ~ {
DO
line ← GetNonBlankLine[stream];
IF NOT Rope.Equal["--", Rope.Substr[GetWord[line], 0, 2]] THEN EXIT;
ENDLOOP;
line.index ← 0;
};
NWordsInRope: 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];
};
Equal: PROC [r1, r2: ROPE] RETURNS [BOOL] ~ {RETURN[Rope.Equal[r1, r2, FALSE]]};
GetLineAfterKey: PROC [stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE]
RETURNS [Line] ~ {
[] ← FindKeyword[stream, keyword, circularSearch];
RETURN[GetLine[stream]];
};
NumberOfLinesToConvert: PROC [stream: STREAM]
RETURNS [INTEGER] ~ {
GoodLine: PROC RETURNS [BOOL] ~ {
DO
line: Line ← GetNonBlankLine[stream];
rope: ROPE ← GetWord[line];
IF Rope.Equal["--", Rope.Substr[rope, 0, 2]] THEN LOOP; -- comment
IF Rope.Fetch[rope, Rope.Length[rope]-1] = '~    -- new keyline
THEN RETURN[FALSE];
RETURN[(rope ← GetWord[line]) = NIL OR NOT Equal["~", rope]];
ENDLOOP;
};
nLines: INTEGER ← 0;
sIndexSave: INTIO.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
RETURN[nLines];
};
InitializeFields: PROC [keyLine: Line] RETURNS [fields: REF FieldSequence] ~ {
Allocate fields, set their id's and types, but not their sequences.
nFields: INTEGER ← 0;
fields ← NEW[FieldSequence[(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[Field];
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, "triple"]  => triple,
Equal[rope, "nats"]  => nats,
ENDCASE => none;
ENDLOOP;
fields.length ← nFields;
};
Public Read Procedures
GetLine: PUBLIC PROC [stream: STREAM] RETURNS [line: Line] ~ {
line ← NEW[LineRec];
line.rope ← IO.GetLineRope[stream];
line.length ← Rope.Length[line.rope];
line.stream ← stream;
};
GetWord: PUBLIC PROC [line: Line] RETURNS [word: ROPE] ~ {
Return the next whitespace-delimited word in line.
index: INTEGER;
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]]];
};
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: REF NatSequence] ~ {
maxLength: NAT ← NWordsInRope[Rope.Substr[line.rope, line.index, line.length-line.index]];
nats ← NEW[NatSequence[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;
};
NextKeyword: PUBLIC PROC [stream: STREAM, circularSearch: BOOLFALSE]
RETURNS [key: ROPE] ~ {
Return the next keyword. The file index points to the beginning of the key line.
line: Line;
loopIndex: INT;
length: INTEGER;
eof, startedAtZero: BOOLFALSE;
sIndexStart: INTIO.GetIndex[stream];
DO
loopIndex ← IO.GetIndex[stream];
IF startedAtZero AND loopIndex > sIndexStart THEN GOTO notFound;
line ← GetLine[stream ! IO.EndOfStream, IO.Error => {eof ← TRUE; CONTINUE}];
IF eof THEN {
IF NOT circularSearch OR startedAtZero THEN GOTO notFound;
IO.SetIndex[stream, 0];
startedAtZero ← TRUE;
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;
IO.SetIndex[stream, loopIndex];
};
FindKeyword: PUBLIC PROC [stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE]
RETURNS [line: 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;
length: INTEGER ← Rope.Length[keyword];
eof, startedAtZero: BOOLFALSE;
sIndexStart: INTIO.GetIndex[stream];
DO
IF startedAtZero AND IO.GetIndex[stream] > sIndexStart THEN GOTO notFound;
line ← GetLine[stream ! IO.EndOfStream, IO.Error => {eof ← TRUE; CONTINUE}];
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;
};
ReadRope: PUBLIC PROC [stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE]
RETURNS [ROPE] ~ {
line: Line ← FindKeyword[stream, keyword, circularSearch];
RETURN[Rope.Substr[line.rope, line.index, Rope.Length[line.rope]-line.index]];
};
ReadInteger: PUBLIC PROC [stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE]
RETURNS [INTEGER] ~ {
RETURN[GetInteger[GetLineAfterKey[stream, keyword, circularSearch]]];
};
ReadReal: PUBLIC PROC [stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE]
RETURNS [REAL] ~ {
RETURN[GetReal[GetLineAfterKey[stream, keyword, circularSearch]]];
};
ReadTriple: PUBLIC PROC [stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE]
RETURNS [Triple] ~ {
RETURN[GetTriple[GetLineAfterKey[stream, keyword, circularSearch]]];
};
ReadIntegerSequence: PUBLIC PROC [
stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE, nElements: INT ← 0]
RETURNS [REF IntegerSequence]
~ {
line: Line ← FindKeyword[stream, keyword, circularSearch];
nLines: INTIF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
integers: REF IntegerSequence ← NEW[IntegerSequence[nLines]];
integers.length ← nLines;
FOR n: INT IN [0..nLines) DO
line ← GetDataLine[stream ! IO.EndOfStream => GOTO eof];
integers[n] ← GetInteger[line];
REPEAT eof => NULL;
ENDLOOP;
RETURN[integers];
};
ReadRealSequence: PUBLIC PROC [
stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE, nElements: INT ← 0]
RETURNS [REF RealSequence]
~ {
line: Line ← FindKeyword[stream, keyword, circularSearch];
nLines: INTIF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
reals: REF RealSequence ← NEW[RealSequence[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;
RETURN[reals];
};
ReadTripleSequence: PUBLIC PROC [
stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE, nElements: INT ← 0]
RETURNS [REF TripleSequence]
~ {
line: Line ← FindKeyword[stream, keyword, circularSearch];
nLines: INTIF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
triples: REF TripleSequence ← NEW[TripleSequence[nLines]];
triples.length ← nLines;
FOR n: INT IN [0..nLines) DO
line ← GetDataLine[stream ! IO.EndOfStream => GOTO eof];
triples[n] ← GetTriple[line];
REPEAT eof => NULL;
ENDLOOP;
RETURN[triples];
};
ReadNatTable: PUBLIC PROC [
stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE, nElements: INT ← 0]
RETURNS [REF NatTable]
~ {
line: Line ← FindKeyword[stream, keyword, circularSearch];
nLines: INTIF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
nats: REF NatTable ← NEW[NatTable[nLines]];
nats.length ← nLines;
FOR n: INT IN [0..nLines) DO
nats[n] ← GetNats[GetDataLine[stream]];
ENDLOOP;
RETURN[nats];
};
ReadVertexInfoSequence: PUBLIC PROC [
stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE, nElements: INT ← 0]
RETURNS [REF VertexInfoSequence]
~ {
fields: REF FieldSequence;
nLines: INTEGER;            -- number of lines to convert
vIS: REF VertexInfoSequence;
types: ARRAY [0..5) OF FieldType ← [triple, triple, triple, real, triple];
ids: ARRAY [0..5) OF ROPE
["xyzCoords", "normalVec", "rgbColor", "transmittance", "textureCoords"];
line: Line ← FindKeyword[stream, keyword, circularSearch];
IF NWordsInRope[line.rope] > 1
THEN fields ← InitializeFields[line]
ELSE {
fields ← NEW[FieldSequence[5]];
FOR n: NAT IN [0..5) DO
fields[n].id ← ids[n];
fields[n].type ← types[n];
ENDLOOP;
};
nLines ← IF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
vIS ← NEW[VertexInfoSequence[nLines]];
FOR n: INT IN [0..nLines) DO
vIS[n] ← NEW[VertexInfo];
line ← GetDataLine[stream];
FOR i: NAT IN [0..fields.length) DO
SELECT TRUE FROM
Equal[fields[i].id, "xyzCoords"] =>
[[vIS[n].coord.x, vIS[n].coord.y, vIS[n].coord.z]] ← GetTriple[line];
Equal[fields[i].id, "normalVec"] =>
[[vIS[n].shade.xn, vIS[n].shade.yn, vIS[n].shade.zn]] ← GetTriple[line];
Equal[fields[i].id, "rgbColor"] =>
[[vIS[n].shade.r, vIS[n].shade.g, vIS[n].shade.b]] ← GetTriple[line];
Equal[fields[i].id, "transmittance"] => vIS[n].shade.t ← GetReal[line];
Equal[fields[i].id, "textureCoords"] => vIS[n].aux ← NEW[Triple ← GetTriple[line] ];
ENDCASE => SELECT fields[i].type FROM
integer, real => [] ← GetWord[line];
triple => {[] ← GetWord[line]; [] ← GetWord[line]; [] ← GetWord[line]};
ENDCASE => NULL;
ENDLOOP;
ENDLOOP;
RETURN[vIS];
};
ReadFields: PUBLIC PROC [
stream: STREAM, keyword: ROPE, circularSearch: BOOLFALSE, nElements: INT ← 0]
RETURNS [fields: REF FieldSequence]
~ {
line: Line ← FindKeyword[stream, keyword, circularSearch]; -- the keyword line
nLines: INTEGER;            -- number of lines to convert
fields ← InitializeFields[line];
nLines ← IF nElements # 0 THEN nElements ELSE NumberOfLinesToConvert[stream];
FOR n: INT IN [0..fields.length) DO       -- allocate sequences
fields[n].sequence ← SELECT fields[n].type FROM
integer => NEW[IntegerSequence[nLines]],
real  => NEW[RealSequence[nLines]],
triple => NEW[TripleSequence[nLines]],
nats  => NEW[NatTable[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, REF IntegerSequence].length ← nLines;
real  => NARROW[fields[n].sequence, REF RealSequence].length ← nLines;
triple  => NARROW[fields[n].sequence, REF TripleSequence].length ← nLines;
nats  => NARROW[fields[n].sequence, REF NatTable].length ← nLines;
ENDCASE => NULL;
ENDLOOP;
FOR n: NAT IN [0..nLines) DO        -- line by line data conversions
line: Line ← GetDataLine[stream ! IO.EndOfStream => GOTO eof];
FOR nn: NAT IN [0..fields.length) DO
SELECT fields[nn].type FROM
integer => {
s: REF IntegerSequence ← NARROW[fields[nn].sequence];
s[n] ← GetInteger[line];
};
real => {
s: REF RealSequence ← NARROW[fields[nn].sequence];
s[n] ← GetReal[line];
};
triple => {
s: REF TripleSequence ← NARROW[fields[nn].sequence];
s[n] ← GetTriple[line];
};
nats => {
s: REF NatTable ← NARROW[fields[nn].sequence];
s[n] ← GetNats[line];
};
ENDCASE => NULL;
ENDLOOP;
REPEAT
eof => NULL;
ENDLOOP;
};
Public Write Procedures
WriteVertexInfoSequence: PUBLIC PROC [
stream: STREAM, keyword: ROPE, vertexInfo: REF VertexInfoSequence,
xyz, normal, color, trans, texture: BOOLTRUE] ~ {
IF vertexInfo # NIL THEN {
vi: REF VertexInfoSequence ← vertexInfo;
IO.PutF[stream, "%g~ ", IO.rope[keyword]];
IF xyz THEN IO.PutF[stream, "xyzCoords: triple"];
IF normal THEN IO.PutF[stream, ", normalVec: triple"];
IF color THEN IO.PutF[stream, ", rgbColor: triple"];
IF trans THEN IO.PutF[stream, ", transmittance: real"];
IF texture THEN IO.PutF[stream, ", textureCoords: triple"];
IO.PutF[stream, "\n\n"];
FOR n: NAT IN [0..vertexInfo.length) DO
IF xyz THEN IO.PutF[stream, "%9g %9g %9g\t\t",
IO.real[vi[n].coord.x], IO.real[vi[n].coord.y], IO.real[vi[n].coord.z]];
IF normal THEN IO.PutF[stream, "%9g %9g %9g\t\t",
IO.real[vi[n].shade.xn], IO.real[vi[n].shade.yn], IO.real[vi[n].shade.zn]];
IF color THEN IO.PutF[stream, "%9g %9g %9g\t\t",
IO.real[vi[n].shade.r], IO.real[vi[n].shade.g], IO.real[vi[n].shade.b]];
IF trans THEN IO.PutF[stream, "%9g\t\t", IO.real[vi[n].shade.t]];
IF texture THEN {
txtr: REF Triple ← NARROW[ vi[n].aux ];
IO.PutF[stream, "%9g %9g %9g", IO.real[txtr.x], IO.real[txtr.y], IO.real[txtr.z]];
};
IO.PutF[stream, "\n"];
ENDLOOP;
};
};
WriteFields: PUBLIC PROC [stream: STREAM, keyword: ROPE, fields: REF FieldSequence] ~ {
RopeFromFieldType: PROC [type: FieldType] RETURNS [ROPE] ~ {
RETURN [SELECT type FROM
integer => "integer",
real  => "real",
triple  => "triple",
nats  => "nats",
ENDCASE => NIL];
};
IF fields # NIL THEN {
nElements: INTEGER ← 0;
IO.PutF[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, REF IntegerSequence].length,
real =>  NARROW[fields[n].sequence, REF RealSequence].length,
triple =>  NARROW[fields[n].sequence, REF TripleSequence].length,
nats =>  NARROW[fields[n].sequence, REF NatTable].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.PutF[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: REF IntegerSequence ← NARROW[fields[nn].sequence];
IO.PutF[stream, "%5g ", IO.int[INT[s[n]]]];
};
real => {
s: REF RealSequence ← NARROW[fields[nn].sequence];
IO.PutF[stream, "%9g ", IO.real[s[n]]];
};
triple => {
s: REF 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: REF NatTable ← NARROW[fields[nn].sequence];
s: REF NatSequence ← t[n];
FOR nnn: NAT IN [0..s.length) DO
IO.PutF[stream, "%5g ", IO.int[INT[s[nnn]]]];
ENDLOOP;
};
ENDCASE => NULL;
ENDLOOP;
IO.PutF[stream, "\n"];
ENDLOOP;
};
};
END.
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: REF 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;
};