<> <> <> <> DIRECTORY Ascii, Convert, Imager, IO, Rope, ThreeDIO, Vector3d; ThreeDIOImpl: CEDAR PROGRAM IMPORTS Convert, IO, Rope EXPORTS ThreeDIO ~ BEGIN OPEN ThreeDIO; <> Error: PUBLIC ERROR [reason: ROPE] = CODE; ErrorType: TYPE ~ {notFound, format, convert}; <> ErrorReport: PROC [errorType: ErrorType, line: Line _ NIL, keyword: ROPE _ NIL] ~ { 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: BOOL _ FALSE] 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: 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 RETURN[nLines]; }; InitializeFields: PROC [keyLine: Line] RETURNS [fields: REF FieldSequence] ~ { <> 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; }; <> 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] ~ { <> 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: BOOL _ FALSE] RETURNS [key: ROPE] ~ { <> <<>> line: Line; loopIndex: INT; length: INTEGER; eof, startedAtZero: BOOL _ FALSE; sIndexStart: INT _ IO.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: BOOL _ FALSE] RETURNS [line: Line] ~ { <> <> <<>> word: ROPE; length: INTEGER _ Rope.Length[keyword]; eof, startedAtZero: BOOL _ FALSE; sIndexStart: INT _ IO.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: BOOL _ FALSE] 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: BOOL _ FALSE] RETURNS [INTEGER] ~ { RETURN[GetInteger[GetLineAfterKey[stream, keyword, circularSearch]]]; }; ReadReal: PUBLIC PROC [stream: STREAM, keyword: ROPE, circularSearch: BOOL _ FALSE] RETURNS [REAL] ~ { RETURN[GetReal[GetLineAfterKey[stream, keyword, circularSearch]]]; }; ReadTriple: PUBLIC PROC [stream: STREAM, keyword: ROPE, circularSearch: BOOL _ FALSE] RETURNS [Triple] ~ { RETURN[GetTriple[GetLineAfterKey[stream, keyword, circularSearch]]]; }; ReadIntegerSequence: PUBLIC PROC [ stream: STREAM, keyword: ROPE, circularSearch: BOOL _ FALSE, nElements: INT _ 0] RETURNS [REF IntegerSequence] ~ { line: Line _ FindKeyword[stream, keyword, circularSearch]; nLines: INT _ IF 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: BOOL _ FALSE, nElements: INT _ 0] RETURNS [REF RealSequence] ~ { line: Line _ FindKeyword[stream, keyword, circularSearch]; nLines: INT _ IF 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: BOOL _ FALSE, nElements: INT _ 0] RETURNS [REF TripleSequence] ~ { line: Line _ FindKeyword[stream, keyword, circularSearch]; nLines: INT _ IF 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: BOOL _ FALSE, nElements: INT _ 0] RETURNS [REF NatTable] ~ { line: Line _ FindKeyword[stream, keyword, circularSearch]; nLines: INT _ IF 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: BOOL _ FALSE, 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: BOOL _ FALSE, 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; }; <> WriteVertexInfoSequence: PUBLIC PROC [ stream: STREAM, keyword: ROPE, vertexInfo: REF VertexInfoSequence, xyz, normal, color, trans, texture: BOOL _ TRUE] ~ { 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. <<>> <> <> <> <> <<>> <> < GOTO eof];>> <> <> <> < EXIT;>> <<'., '0, '1, '2, '3, '4, '5, '6, '7, '8, '9 => NULL;>> < RETURN[other];>> <> <> <<};>> <> <> <> <> <> <> <> <> <> <<'., '-, '0, '1, '2, '3, '4, '5, '6, '7, '8, '9 => TestWord[],>> < other>> <<];>> <<};>> <> <> <> <<[] _ Rope.AppendChars[refText, GetNonBlankLine[stream].rope];>> <> <