<> <> <> DIRECTORY Atom USING [ GetPropFromList, PutPropOnList, PropList, DottedPair, DottedPairNode ], Real USING [ RoundC, Fix, FixI, FixC ], RealFns USING [ SqRt ], Basics USING [ BITOR, BITAND ], BasicTime USING [ PulsesToSeconds, GetClockPulses ], Rope USING [ ROPE, Cat , Find, Equal], Convert USING [ RopeFromReal, AtomFromRope ], IO USING [ Close, STREAM, PutRope ], FS USING [ StreamOpen ], Imager USING [ Context, MaskVectorI, SetStrokeWidth ], QuickViewer USING [ DrawInViewer ], Pixels USING [ GetSampleSet, SampleSet ], ScanConvert USING [ PutLine, justNoticeable ], Vector3d USING [ Dot, Triple, Quad, Normalize, Cross, Add ], Plane3d USING [ DistanceToPt ], ThreeDBasics USING [ AllOut, ClipState, Context, FacingDir, IntegerSequence, NatSequence, NatTable, NoneOut, OutCode, RealSequence, RGB, ShadingSequence, ShadingValue, ShapeInstance, ShapeSequence, ShapeProc, SixSides, Triple, TripleSequence, Vertex, VertexInfo, VertexInfoProc, VertexInfoSequence, VertexSequence ], ThreeDMisc USING [ CombineBoxes, GetMappedColor, GetBackgroundColor, SetRGBColor ], ThreeDScenes USING [ Error, GetShading, GetVtxShades, PutShading, ShadeVtx, XfmPtToDisplay, XfmToDisplay, XfmToEyeSpace ], Tilers USING [ PolygonTiler ], ThreeDSurfaces USING [ Patch, PatchProcs, PtrPatchSequence, PtrPatch, PatchSequence, SortSequence, ShapePatch ], ThreeDIO USING [ Error, Field, FieldSequence, ReadFields, WriteFields, ReadRope, ReadVertexInfoSequence, WriteVertexInfoSequence ]; ThreeDSurfacesImpl: CEDAR MONITOR IMPORTS Atom, BasicTime, Convert, Real, RealFns, Rope, IO, Basics, ThreeDScenes, Tilers, Vector3d, Plane3d, QuickViewer, ScanConvert, ThreeDMisc, Pixels, Imager, ThreeDIO, FS EXPORTS ThreeDSurfaces = BEGIN <> Context: TYPE ~ ThreeDBasics.Context; RGB: TYPE ~ ThreeDBasics.RGB; -- [ r, g, b: REAL]; SixSides: TYPE ~ ThreeDBasics.SixSides; Triple: TYPE ~ ThreeDBasics.Triple; TripleSequence: TYPE ~ ThreeDBasics.TripleSequence; NatSequence: TYPE ~ ThreeDBasics.NatSequence; IntegerSequence: TYPE ~ ThreeDBasics.IntegerSequence; RealSequence: TYPE ~ ThreeDBasics.RealSequence; SampleSet: TYPE ~ Pixels.SampleSet; ShapeInstance: TYPE ~ ThreeDBasics.ShapeInstance; FacingDir: TYPE ~ ThreeDBasics.FacingDir; Patch: TYPE ~ ThreeDSurfaces.Patch; PatchSequence: TYPE ~ ThreeDSurfaces.PatchSequence; PtrPatch: TYPE ~ ThreeDSurfaces.PtrPatch; PtrPatchSequence: TYPE ~ ThreeDSurfaces.PtrPatchSequence; ShapePatch: TYPE ~ ThreeDSurfaces.ShapePatch; Vertex: TYPE ~ ThreeDBasics.Vertex; VertexSequence: TYPE ~ ThreeDBasics.VertexSequence; VertexInfo: TYPE ~ ThreeDBasics.VertexInfo; VertexInfoSequence: TYPE ~ ThreeDBasics.VertexInfoSequence; ShadingValue: TYPE ~ ThreeDBasics.ShadingValue; ShadingSequence: TYPE ~ ThreeDBasics.ShadingSequence; ShapeProc: TYPE ~ ThreeDBasics.ShapeProc; -- PROC[ Context, ShapeInstance ] <> <> patchCache: REF PatchSequence _ NEW[ PatchSequence[16] ]; -- temps for clipping, etc. patchCacheLength: NAT _ 16; patchCachePtr: NAT _ 0; -- place to return next free record pixelBytes: SampleSet _ Pixels.GetSampleSet[1]; -- cache for pixel size nullPtr: INT ~ 0; -- handy name for zero in sort sequences <> Sqr: PROCEDURE [number: REAL] RETURNS [REAL] ~ INLINE { RETURN[number * number]; }; Sgn: PROCEDURE [number: REAL] RETURNS [REAL] ~ INLINE { IF number < 0. THEN RETURN[-1.] ELSE RETURN[1.]; }; ElapsedTime: PROC[startTime: REAL] RETURNS[Rope.ROPE] ~ { timeX10: REAL _ 10.0 * (BasicTime.PulsesToSeconds[BasicTime.GetClockPulses[]] - startTime); RETURN[ Rope.Cat[ Convert.RopeFromReal[ Real.FixC[timeX10] / 10.0 ], " secs. " ] ]; }; CurrentTime: PROC[] RETURNS[REAL] ~ { RETURN[ BasicTime.PulsesToSeconds[BasicTime.GetClockPulses[]] ]; }; GetPatch: PUBLIC ENTRY PROC[size: NAT] RETURNS[REF Patch] ~ { ENABLE UNWIND => NULL; p: REF Patch; IF patchCachePtr = 0 THEN p _ NEW[Patch[size]] ELSE { patchCachePtr _ patchCachePtr - 1; p _ patchCache[patchCachePtr]; patchCache[patchCachePtr] _ NIL; IF p.maxLength < size THEN p _ NEW[Patch[size]]; }; RETURN[ p ]; }; ReleasePatch: PUBLIC ENTRY PROC[p: REF Patch] ~ { ENABLE UNWIND => NULL; IF p = NIL THEN RETURN[]; IF patchCachePtr = patchCacheLength THEN { patchCache _ NEW[ PatchSequence[patchCacheLength + 2] ]; patchCacheLength _ patchCacheLength + 2; patchCachePtr _ 0; }; patchCache[patchCachePtr] _ p; patchCachePtr _ patchCachePtr + 1; }; DiffPosns: PROC[vtx1, vtx2: REF Vertex] RETURNS[Triple] ~ { RETURN[[vtx1.x - vtx2.x, vtx1.y - vtx2.y, vtx1.z - vtx2.z]] }; HoldEverything: PROCEDURE [] ~ { ERROR ABORTED; }; ShapetoColorBytes: PROC [context: REF Context, s: REF ShapeInstance] RETURNS[SampleSet] ~ { ref: REF ANY _ ThreeDScenes.GetShading[ s, $Color]; r, g, b: REAL; addOn: NAT _ 0; IF context.alphaBuffer THEN addOn _ addOn + 1; IF context.depthBuffer THEN addOn _ addOn + 1; IF ref # NIL THEN [r, g, b] _ NARROW[ ref, REF RGB]^ -- shape color ELSE IF context.renderMode # $Interpress THEN r _ g _ b _ 1.0 ELSE r _ g _ b _ 0.0; SELECT context.renderMode FROM -- convert color to byte sequence $Bitmap => { clr: RGB _ ThreeDMisc.GetBackgroundColor[context]; IF (clr.R + clr.G + clr.B) / 3 > 0.5 THEN pixelBytes[0] _ 255 ELSE pixelBytes[0] _ 0; -- ensure contrast with backgrnd }; $Dithered, $PseudoColor => { IF pixelBytes.length < 1+addOn THEN pixelBytes _ Pixels.GetSampleSet[1+addOn]; pixelBytes[0] _ ThreeDMisc.GetMappedColor[context, [r, g, b] ]; IF addOn > 0 THEN pixelBytes[1] _ 0; IF addOn > 1 THEN pixelBytes[2] _ 0; }; $Grey => { IF pixelBytes.length < 1+addOn THEN pixelBytes _ Pixels.GetSampleSet[1+addOn]; pixelBytes[0] _ Real.RoundC[255.0 * (r + g + b)/3 ]; IF addOn > 0 THEN pixelBytes[1] _ 0; IF addOn > 1 THEN pixelBytes[2] _ 0; }; $FullColor, $Dorado24, $Interpress => { IF pixelBytes.length < 3+addOn THEN pixelBytes _ Pixels.GetSampleSet[3+addOn]; pixelBytes[0] _ Real.RoundC[255.0 * r]; pixelBytes[1] _ Real.RoundC[255.0 * g]; pixelBytes[2] _ Real.RoundC[255.0 * b]; IF addOn > 0 THEN pixelBytes[3] _ 0; IF addOn > 1 THEN pixelBytes[4] _ 0; }; ENDCASE => SIGNAL ThreeDScenes.Error[[$Unimplemented, "Unknown renderMode"]]; RETURN[pixelBytes]; }; ShapePatchToPatch: PUBLIC PROC[context: REF Context, sPatch: REF ThreeDSurfaces.ShapePatch] RETURNS [patch: REF Patch] ~ { ptrPatch: REF PtrPatch _ NARROW[sPatch.shape.surface, REF PtrPatchSequence][sPatch.patch]; vertex: REF ThreeDBasics.VertexSequence _ sPatch.shape.vertex; shade: REF ThreeDBasics.ShadingSequence _ sPatch.shape.shade; shadingType: REF ANY _ ThreeDScenes.GetShading[ sPatch.shape, $Type ]; auxProc: REF ThreeDBasics.VertexInfoProc _ NARROW[ ThreeDScenes.GetShading[ sPatch.shape, $AuxLoad ] ]; faceted: BOOLEAN _ shadingType = $Faceted; lines: BOOLEAN _ shadingType = $Lines; patchInfo: REF ThreeDBasics.ShadingSequence _ NARROW[ ThreeDScenes.GetShading[ sPatch.shape, $PatchColors ] ]; coloredPatches: BOOLEAN _ IF patchInfo # NIL AND NOT faceted THEN ThreeDScenes.GetShading[ sPatch.shape, $PatchColorsInFile ] # NIL ELSE FALSE; IF ptrPatch.clipState = out THEN RETURN[NIL]; -- reject if outside frame patch _ GetPatch[2 * ptrPatch.nVtces]; -- get temp patch, released by OutputPatch patch.nVtces _ ptrPatch.nVtces; patch.clipState _ ptrPatch.clipState; patch.type _ ptrPatch.type; patch.oneSided _ ptrPatch.oneSided; patch.dir _ ptrPatch.dir; patch.props _ NIL; FOR list: Atom.PropList _ sPatch.shape.shadingProps, list.rest UNTIL list = NIL DO element: Atom.DottedPair _ NEW[Atom.DottedPairNode _ list.first^]; -- copy shading props patch.props _ CONS[element, patch.props]; ENDLOOP; patch.props _ Atom.PutPropOnList[ patch.props, $Shape, sPatch.shape ]; -- put on shape info FOR i: NAT IN [0..ptrPatch.nVtces) DO j: NAT _ ptrPatch.vtxPtr[i]; patch[i].coord _ vertex[j]^; patch[i].shade _ shade[j]^; IF auxProc # NIL THEN { data: LIST OF REF ANY _ LIST[ sPatch.shape.auxInfo, NEW[INTEGER _ j] ]; patch[i] _ auxProc^[context, NEW[ VertexInfo _ patch[i] ], data]^; }; IF lines THEN { -- lines use unshaded values patch[i].shade.er _ patch[i].shade.r; patch[i].shade.eg _ patch[i].shade.g; patch[i].shade.eb _ patch[i].shade.b; } ELSE IF patchInfo # NIL THEN -- shades for individual patches IF faceted THEN patch[i].shade _ patchInfo[sPatch.patch]^ ELSE IF coloredPatches THEN { patch[i].shade.er _ patch[i].shade.er * patchInfo[sPatch.patch].r; patch[i].shade.eg _ patch[i].shade.eg * patchInfo[sPatch.patch].g; patch[i].shade.eb _ patch[i].shade.eb * patchInfo[sPatch.patch].b; patch[i].shade.et _ patch[i].shade.et * patchInfo[sPatch.patch].t; IF context.alphaBuffer THEN { -- possible pixel by pixel shading patch[i].shade.r _ shade[j].r * patchInfo[sPatch.patch].r; patch[i].shade.g _ shade[j].g * patchInfo[sPatch.patch].g; patch[i].shade.b _ shade[j].b * patchInfo[sPatch.patch].b; patch[i].shade.t _ shade[j].t * patchInfo[sPatch.patch].t; }; }; ENDLOOP; }; <> ReadShape: PUBLIC PROC[shape: REF ShapeInstance, fileName: Rope.ROPE] ~ { stream: IO.STREAM _ FS.StreamOpen[ fileName: fileName ]; firstVtxNo: NAT _ 0; -- some files count from 0 some from 1 surfaceInfo: Rope.ROPE; <> surfaceInfo _ ThreeDIO.ReadRope[ stream, "SurfaceType", TRUE ! ThreeDIO.Error => CONTINUE ]; shape.type _ $ConvexPolygon; -- defaults shape.insideVisible _ FALSE; IF Rope.Find[surfaceInfo, "polygon", 0, FALSE] >= 0 THEN shape.type _ $ConvexPolygon; IF Rope.Find[surfaceInfo, "bezier", 0, FALSE] >= 0 THEN shape.type _ $Bezier; IF Rope.Find[surfaceInfo, "Inside", 0, FALSE] >= 0 THEN shape.insideVisible _ TRUE; IF Rope.Find[surfaceInfo, "CountFromOne", 0, FALSE] >= 0 THEN firstVtxNo _ 1; <<>> <> { vertices: REF VertexInfoSequence _ ThreeDIO.ReadVertexInfoSequence[stream, "Vertices"]; normalsRead, colorsRead, txtrRead, transRead: INT _ 0; auxInfo: REF TripleSequence _ NIL; shape.vertex _ NEW[ ThreeDBasics.VertexSequence[vertices.length] ]; shape.shade _ NEW[ ThreeDBasics.ShadingSequence[vertices.length] ]; IF vertices[0].aux # NIL THEN { auxInfo _ NEW[ TripleSequence[vertices.length] ]; auxInfo.length _ vertices.length; shape.auxInfo _ auxInfo; }; FOR i: NAT IN [0..vertices.length) DO shape.vertex[i] _ NEW[ ThreeDBasics.Vertex _ vertices[i].coord ]; shape.shade[i] _ NEW[ ThreeDBasics.ShadingValue _ vertices[i].shade ]; IF shape.shade[i].xn # 0.0 OR shape.shade[i].yn # 0.0 OR shape.shade[i].zn # 0.0 THEN normalsRead _ normalsRead + 1; IF shape.shade[i].r # 0.7 OR shape.shade[i].r # 0.7 OR shape.shade[i].r # 0.7 THEN colorsRead _ colorsRead + 1; IF shape.shade[i].t # 0.0 THEN transRead _ transRead + 1; IF vertices[i].aux # NIL THEN { auxInfo[i] _ NARROW[vertices[i].aux, REF Triple]^; txtrRead _ txtrRead + 1; }; ENDLOOP; IF normalsRead > vertices.length / 2 THEN ThreeDScenes.PutShading[ shape, $VertexNormalsInFile, $DoIt ]; IF colorsRead > vertices.length / 2 THEN ThreeDScenes.PutShading[ shape, $VertexColorsInFile, $DoIt ]; IF transRead > vertices.length / 2 THEN ThreeDScenes.PutShading[ shape, $VertexTransInFile, $DoIt ]; IF txtrRead > vertices.length / 2 THEN ThreeDScenes.PutShading[ shape, $VertexTextureInFile, $DoIt ]; ThreeDScenes.PutShading[shape, $Type, $Smooth ]; }; <> { keyWord: Rope.ROPE _ IF shape.type = $ConvexPolygon THEN "Polygons" ELSE "Patches"; fields: REF ThreeDIO.FieldSequence _ ThreeDIO.ReadFields[stream, keyWord]; GetPatchInfo: PROC[shape: REF ShapeInstance] RETURNS[p: REF ShadingSequence] ~ { p _ NARROW[ ThreeDScenes.GetShading[ shape, $PatchColors ] ]; IF p = NIL THEN { p _ NEW[ThreeDBasics.ShadingSequence[shape.numSurfaces] ]; FOR i: NAT IN [0..shape.numSurfaces) DO p[i] _ NEW[ThreeDBasics.ShadingValue]; ENDLOOP; }; }; shape.numSurfaces _ 0; FOR n: NAT IN [0..fields.length) DO patchInfo: REF ThreeDBasics.ShadingSequence; SELECT fields[n].type FROM integer => { intSeq: REF IntegerSequence _ NARROW[fields[n].sequence]; shape.numSurfaces _ intSeq.length; SELECT TRUE FROM Rope.Equal[fields[n].id, "index", FALSE] => {}; ENDCASE => { key: ATOM _ Convert.AtomFromRope[fields[n].id]; -- put on proplist ThreeDScenes.PutShading[ shape, key, intSeq ]; }; }; real => { realSeq: REF RealSequence _ NARROW[fields[n].sequence]; shape.numSurfaces _ realSeq.length; patchInfo _ GetPatchInfo[shape]; SELECT TRUE FROM Rope.Equal[fields[n].id, "trans", FALSE] => FOR i: NAT IN [0..realSeq.length) DO patchInfo[i].t _ realSeq[i]; ENDLOOP; ENDCASE => { key: ATOM _ Convert.AtomFromRope[fields[n].id]; -- put on proplist ThreeDScenes.PutShading[ shape, key, realSeq ]; }; }; triple => { tripleSeq: REF TripleSequence _ NARROW[fields[n].sequence]; shape.numSurfaces _ tripleSeq.length; patchInfo _ GetPatchInfo[shape]; SELECT TRUE FROM Rope.Equal[fields[n].id, "color", FALSE] => { FOR i: NAT IN [0..tripleSeq.length) DO patchInfo[i].r _ tripleSeq[i].x; patchInfo[i].g _ tripleSeq[i].y; patchInfo[i].b _ tripleSeq[i].z; ENDLOOP; ThreeDScenes.PutShading[ shape, $PatchColors, patchInfo ]; ThreeDScenes.PutShading[ shape, $PatchColorsInFile, $DoIt ]; ThreeDScenes.PutShading[shape, $Type, $Faceted ]; }; Rope.Equal[fields[n].id, "normal", FALSE] => { FOR i: NAT IN [0..tripleSeq.length) DO patchInfo[i].xn _ tripleSeq[i].x; patchInfo[i].yn _ tripleSeq[i].y; patchInfo[i].zn _ tripleSeq[i].z; ENDLOOP; ThreeDScenes.PutShading[ shape, $PatchColors, patchInfo ]; ThreeDScenes.PutShading[ shape, $PatchNormalsInFile, $DoIt ]; ThreeDScenes.PutShading[shape, $Type, $Faceted ]; }; ENDCASE => { key: ATOM _ Convert.AtomFromRope[fields[n].id]; -- put on proplist ThreeDScenes.PutShading[ shape, key, tripleSeq ]; }; }; nats => { -- get the surface elements surface: REF PtrPatchSequence; surfels: REF ThreeDBasics.NatTable _ NARROW[fields[n].sequence]; shape.numSurfaces _ surfels.length; shape.surface _ NEW[ PtrPatchSequence[shape.numSurfaces] ]; surface _ NARROW[shape.surface, REF PtrPatchSequence]; FOR i: NAT IN [0..shape.numSurfaces) DO IF surface[i] = NIL THEN surface[i] _ NEW[PtrPatch]; surface[i].vtxPtr _ NEW[NatSequence[surfels[i].length]]; surface[i].nVtces _ surfels[i].length; surface[i].type _ shape.type; surface[i].oneSided _ NOT shape.insideVisible; FOR j: NAT IN [0..surfels[i].length) DO surface[i].vtxPtr[j] _ surfels[i][j] - firstVtxNo; -- counting from zero ENDLOOP; ENDLOOP; }; ENDCASE => { key: ATOM _ Convert.AtomFromRope[fields[n].id]; -- put on proplist ThreeDScenes.PutShading[ shape, key, fields[n].sequence ]; }; ENDLOOP; IF ThreeDScenes.GetShading[ shape, $VertexNormalsInFile ] = NIL THEN GetVtxNormals[shape ! ThreeDScenes.Error => IF reason.code = $MisMatch THEN CONTINUE]; IF ThreeDScenes.GetShading[ shape, $PatchNormalsInFile ] = NIL AND ThreeDScenes.GetShading[ shape, $PatchColorsInFile ] # NIL THEN GetPolyNormals[shape ! ThreeDScenes.Error => IF reason.code = $MisMatch THEN CONTINUE]; }; <> { min, max: Triple; min _ max _ [shape.vertex[0].x, shape.vertex[0].y, shape.vertex[0].z]; FOR i: NAT IN (0..shape.vertex.length) DO -- get min and max in x, y, and z IF shape.vertex[i] # NIL THEN { IF shape.vertex[i].x < min.x THEN min.x _ shape.vertex[i].x ELSE IF shape.vertex[i].x > max.x THEN max.x _ shape.vertex[i].x; IF shape.vertex[i].y < min.y THEN min.y _ shape.vertex[i].y ELSE IF shape.vertex[i].y > max.y THEN max.y _ shape.vertex[i].y; IF shape.vertex[i].z < min.z THEN min.z _ shape.vertex[i].z ELSE IF shape.vertex[i].z > max.z THEN max.z _ shape.vertex[i].z; }; ENDLOOP; shape.centroid.x _ (min.x + max.x) / 2; -- get middle point in each coordinate shape.centroid.y _ (min.y + max.y) / 2; shape.centroid.z _ (min.z + max.z) / 2; shape.boundingRadius _ 0.; FOR i: NAT IN [0..shape.vertex.length) DO -- find radius radius: REAL _ RealFns.SqRt[ Sqr[shape.vertex[i].x - shape.centroid.x] + Sqr[shape.vertex[i].y - shape.centroid.y] + Sqr[shape.vertex[i].z - shape.centroid.z] ]; IF radius > shape.boundingRadius THEN shape.boundingRadius _ radius; ENDLOOP; }; }; CloneShape: PUBLIC PROC[newshape, oldShape: REF ShapeInstance] ~ { -- copy shape data newSurface, oldSurface: REF PtrPatchSequence; newshape.type _ oldShape.type; newshape.insideVisible _ oldShape.insideVisible; newshape.centroid _ oldShape.centroid; newshape.boundingRadius _ oldShape.boundingRadius; newshape.vertex _ NEW[ VertexSequence[oldShape.vertex.length] ]; newshape.shade _ NEW[ ShadingSequence[oldShape.shade.length] ]; FOR i: NAT IN [0..oldShape.vertex.length) DO -- copy vertices and shades newshape.vertex[i] _ NEW [ Vertex _ oldShape.vertex[i]^ ]; newshape.shade[i] _ NEW [ ShadingValue _ oldShape.shade[i]^ ]; ENDLOOP; newshape.numSurfaces _ oldShape.numSurfaces; newshape.surface _ NEW[ PtrPatchSequence[oldShape.numSurfaces] ]; newSurface _ NARROW[newshape.surface, REF PtrPatchSequence]; oldSurface _ NARROW[oldShape.surface, REF PtrPatchSequence]; FOR i: NAT IN [0..oldShape.numSurfaces) DO -- copy surface IF newSurface[i] = NIL THEN newSurface[i] _ NEW[PtrPatch]; newSurface[i].vtxPtr _ NEW[NatSequence[oldSurface[i].nVtces]]; newSurface[i].nVtces _ oldSurface[i].nVtces; newSurface[i].type _ oldSurface[i].type; newSurface[i].oneSided _ oldSurface[i].oneSided; FOR j: NAT IN [0..oldSurface[i].nVtces) DO newSurface[i].vtxPtr[j] _ oldSurface[i].vtxPtr[j]; ENDLOOP; ENDLOOP; newshape.shadingProps _ NIL; -- copy shading props FOR list: Atom.PropList _ oldShape.shadingProps, list.rest UNTIL list = NIL DO element: Atom.DottedPair _ NEW[Atom.DottedPairNode _ list.first^]; newshape.shadingProps _ CONS[element, newshape.shadingProps]; ENDLOOP; newshape.props _ NIL; -- copy general props FOR list: Atom.PropList _ oldShape.props, list.rest UNTIL list = NIL DO element: Atom.DottedPair _ NEW[Atom.DottedPairNode _ list.first^]; newshape.props _ CONS[element, newshape.props]; ENDLOOP; IF ThreeDScenes.GetShading[ newshape, $PatchColors ] # NIL THEN { -- copy facet info polyShades: REF ShadingSequence _ NARROW[ ThreeDScenes.GetShading[ newshape, $PatchColors ] ]; newpolyShades: REF ShadingSequence _ NEW[ ShadingSequence[ polyShades.length ] ]; FOR i: NAT IN [0..polyShades.length) DO newpolyShades[i] _ NEW[ShadingValue _ polyShades[i]^ ]; ENDLOOP; ThreeDScenes.PutShading[ newshape, $PatchColors, newpolyShades ] }; }; WriteShape: PUBLIC PROC[shape: REF ShapeInstance, fileName: Rope.ROPE, xyz: BOOL _ TRUE, normal, color, trans, texture, polyClr: BOOL _ FALSE] ~ { stream: IO.STREAM _ FS.StreamOpen[Rope.Cat[fileName, ".shape"], $create]; numFields: NAT _ 0; fields: REF ThreeDIO.FieldSequence _ NEW[ThreeDIO.FieldSequence[1]]; vertices: REF VertexInfoSequence _ NEW[ VertexInfoSequence[shape.vertex.length] ]; auxInfo: REF TripleSequence _ NARROW[shape.auxInfo]; surfaceType: Rope.ROPE _ IF shape.type = $ConvexPolygon THEN "Polygons" ELSE "Patches"; insideVisible: Rope.ROPE _ IF shape.insideVisible THEN " InsideVisible" ELSE NIL; <
> stream.PutRope[ Rope.Cat[fileName, ".shape\n\n"] ]; -- write title on first line stream.PutRope[ Rope.Cat["SurfaceType ~ ", surfaceType, insideVisible, "\n\n"] ]; -- surface <> FOR i: NAT IN [0..shape.vertex.length) DO vertices[i] _ NEW[VertexInfo]; vertices[i].coord _ shape.vertex[i]^; vertices[i].shade _ shape.shade[i]^; IF auxInfo # NIL THEN vertices[i].aux _ NEW[ Triple _ auxInfo[i] ]; ENDLOOP; ThreeDIO.WriteVertexInfoSequence[ stream, "Vertices", vertices, xyz, normal, color, trans, texture ]; <> IF polyClr THEN { color: REF ShadingSequence _ NARROW[ ThreeDScenes.GetShading[shape, $PatchColors ] ]; tripleSeq: REF TripleSequence _ NEW[ TripleSequence[color.length] ]; tripleSeq.length _ color.length; FOR i: NAT IN [0..color.length) DO tripleSeq[i].x _ color[i].r; tripleSeq[i].y _ color[i].g; tripleSeq[i].z _ color[i].b; ENDLOOP; fields _ NEW[ThreeDIO.FieldSequence[2]]; fields[0] _ NEW[ThreeDIO.Field]; fields[0].sequence _ tripleSeq; fields[0].type _ triple; fields[0].id _ "rgbColor"; numFields _ 1; }; { surfels: REF ThreeDBasics.NatTable _ NEW[ThreeDBasics.NatTable[shape.numSurfaces] ]; patches: REF PtrPatchSequence _ NARROW[shape.surface, REF PtrPatchSequence]; FOR i: NAT IN [0..shape.numSurfaces) DO surfels[i] _ NEW[ NatSequence[patches[i].nVtces] ]; FOR j: NAT IN [0..patches[i].nVtces) DO surfels[i][j] _ patches[i].vtxPtr[j]; ENDLOOP; surfels[i].length _ patches[i].nVtces; ENDLOOP; surfels.length _ shape.numSurfaces; fields[numFields] _ NEW[ThreeDIO.Field]; fields[numFields].sequence _ surfels; fields[numFields].type _ nats; fields[numFields].id _ "vertices"; fields.length _ numFields + 1; }; ThreeDIO.WriteFields[stream, surfaceType, fields]; IO.Close[stream]; }; <> ClipPoly: PUBLIC PROC[ context: REF Context, poly: REF Patch] RETURNS [REF Patch] ~ { Clip: PROC[side: SixSides, pIn, pOut: REF Patch] RETURNS [REF Patch, REF Patch] = { Dist: PROC[side: SixSides, vtx: Vertex] RETURNS [REAL] = { -- + inside, - outside RETURN[ Plane3d.DistanceToPt[ [vtx.ex, vtx.ey, vtx.ez], context.clippingPlanes[side] ] ]; }; lastDist, dist: REAL; outCnt, last: NAT; IF pIn.nVtces < 3 THEN RETURN[ pIn, pOut ]; -- return if degenerate outCnt _ 0; IF pIn.type # $Path THEN { lastDist _ Dist[side, pIn.vtx[pIn.nVtces - 1].coord]; last _ pIn.nVtces - 1; }; IF pOut.maxLength < 2 * pIn.nVtces THEN pOut _ NEW[Patch[2 * pIn.nVtces]]; FOR i: NAT IN [0..pIn.nVtces) DO a, b: REAL; dist _ Dist[side, pIn.vtx[i].coord]; IF (i # 0 OR pIn.type # $Path) AND lastDist * dist < 0. THEN { <> b _ dist / (dist - lastDist); a _ 1.0 - b; pOut.vtx[outCnt].coord.x _ pIn.vtx[i].coord.x * a + pIn.vtx[last].coord.x * b; pOut.vtx[outCnt].coord.y _ pIn.vtx[i].coord.y * a + pIn.vtx[last].coord.y * b; pOut.vtx[outCnt].coord.z _ pIn.vtx[i].coord.z * a + pIn.vtx[last].coord.z * b; pOut.vtx[outCnt].coord.ex _ pIn.vtx[i].coord.ex * a + pIn.vtx[last].coord.ex * b; pOut.vtx[outCnt].coord.ey _ pIn.vtx[i].coord.ey * a + pIn.vtx[last].coord.ey * b; pOut.vtx[outCnt].coord.ez _ pIn.vtx[i].coord.ez * a + pIn.vtx[last].coord.ez * b; pOut.vtx[outCnt].shade.exn _ pIn.vtx[i].shade.exn*a + pIn.vtx[last].shade.exn*b; pOut.vtx[outCnt].shade.eyn _ pIn.vtx[i].shade.eyn*a + pIn.vtx[last].shade.eyn*b; pOut.vtx[outCnt].shade.ezn _ pIn.vtx[i].shade.ezn*a + pIn.vtx[last].shade.ezn*b; pOut.vtx[outCnt].shade.r _ pIn.vtx[i].shade.r * a + pIn.vtx[last].shade.r * b; pOut.vtx[outCnt].shade.g _ pIn.vtx[i].shade.g * a + pIn.vtx[last].shade.g * b; pOut.vtx[outCnt].shade.b _ pIn.vtx[i].shade.b * a + pIn.vtx[last].shade.b * b; pOut.vtx[outCnt].shade.t _ pIn.vtx[i].shade.t * a + pIn.vtx[last].shade.t * b; pOut.vtx[outCnt].shade.er _ pIn.vtx[i].shade.er * a + pIn.vtx[last].shade.er * b; pOut.vtx[outCnt].shade.eg _ pIn.vtx[i].shade.eg * a + pIn.vtx[last].shade.eg * b; pOut.vtx[outCnt].shade.eb _ pIn.vtx[i].shade.eb * a + pIn.vtx[last].shade.eb * b; pOut.vtx[outCnt].shade.et _ pIn.vtx[i].shade.et * a + pIn.vtx[last].shade.et * b; IF lerpProc # NIL THEN { data: LIST OF REF ANY _ LIST[ pIn.vtx[i].aux, pIn.vtx[last].aux, NEW[REAL _ a], NEW[REAL _ b] ]; pOut.vtx[outCnt] _ lerpProc[ context, NEW[VertexInfo _ pOut.vtx[outCnt]], data ]^; } ELSE pOut.vtx[outCnt].aux _ pIn.vtx[i].aux; outCnt _ outCnt + 1; }; IF dist >= 0. THEN { -- put out point if inside pOut.vtx[outCnt].coord.x _ pIn.vtx[i].coord.x; pOut.vtx[outCnt].coord.y _ pIn.vtx[i].coord.y; pOut.vtx[outCnt].coord.z _ pIn.vtx[i].coord.z; pOut.vtx[outCnt].coord.ex _ pIn.vtx[i].coord.ex; pOut.vtx[outCnt].coord.ey _ pIn.vtx[i].coord.ey; pOut.vtx[outCnt].coord.ez _ pIn.vtx[i].coord.ez; pOut.vtx[outCnt].shade.exn _ pIn.vtx[i].shade.exn; pOut.vtx[outCnt].shade.eyn _ pIn.vtx[i].shade.eyn; pOut.vtx[outCnt].shade.ezn _ pIn.vtx[i].shade.ezn; pOut.vtx[outCnt].shade.r _ pIn.vtx[i].shade.r; pOut.vtx[outCnt].shade.g _ pIn.vtx[i].shade.g; pOut.vtx[outCnt].shade.b _ pIn.vtx[i].shade.b; pOut.vtx[outCnt].shade.t _ pIn.vtx[i].shade.t; pOut.vtx[outCnt].shade.er _ pIn.vtx[i].shade.er; pOut.vtx[outCnt].shade.eg _ pIn.vtx[i].shade.eg; pOut.vtx[outCnt].shade.eb _ pIn.vtx[i].shade.eb; pOut.vtx[outCnt].shade.et _ pIn.vtx[i].shade.et; pOut.vtx[outCnt].aux _ pIn.vtx[i].aux; outCnt _ outCnt + 1; }; lastDist _ dist; last _ i; ENDLOOP; pOut.type _ pIn.type; pOut.oneSided _ pIn.oneSided; pOut.dir _ pIn.dir; pOut.nVtces _ outCnt; pOut.props _ pIn.props; RETURN [ pOut, pIn ]; }; -- end Clip Proc ref: REF ANY _ Atom.GetPropFromList[poly.props, $AuxLerp]; lerpProc: ThreeDBasics.VertexInfoProc _ NIL; orOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.NoneOut; poly2: REF Patch _ GetPatch[2 * poly.nVtces]; -- get temp patch, released below IF poly.type # $ConvexPolygon AND poly.type # $Path THEN SIGNAL ThreeDScenes.Error[[$Unimplemented, "Not clippable"]]; IF ref # NIL -- get proc for interpolating auxiliary vtx info THEN lerpProc _ NARROW[ref, REF ThreeDBasics.VertexInfoProc]^; FOR i: NAT IN [0..poly.nVtces) DO orOfCodes _ LOOPHOLE[ Basics.BITOR[LOOPHOLE[orOfCodes], LOOPHOLE[poly.vtx[i].coord.clip]], ThreeDBasics.OutCode]; ENDLOOP; IF orOfCodes.near THEN [poly, poly2] _ Clip[ Near, poly, poly2]; IF orOfCodes.far THEN [poly, poly2] _ Clip[ Far, poly, poly2]; IF orOfCodes.left THEN [poly, poly2] _ Clip[ Left, poly, poly2]; IF orOfCodes.right THEN [poly, poly2] _ Clip[ Right, poly, poly2]; IF orOfCodes.bottom THEN [poly, poly2] _ Clip[Bottom, poly, poly2]; IF orOfCodes.top THEN [poly, poly2] _ Clip[ Top, poly, poly2]; ReleasePatch[poly2]; -- done with temp patch RETURN[ poly ]; }; GetPatchClipState: PUBLIC PROC[ patch: REF Patch] ~ { orOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.NoneOut; andOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.AllOut; FOR i: NAT IN [0..patch.nVtces) DO orOfCodes _ LOOPHOLE[ Basics.BITOR[ LOOPHOLE[orOfCodes], LOOPHOLE[patch[i].coord.clip]], ThreeDBasics.OutCode]; andOfCodes _ LOOPHOLE[ Basics.BITAND[LOOPHOLE[andOfCodes], LOOPHOLE[patch[i].coord.clip]], ThreeDBasics.OutCode]; ENDLOOP; IF andOfCodes # ThreeDBasics.NoneOut THEN patch.clipState _ out ELSE IF orOfCodes = ThreeDBasics.NoneOut THEN patch.clipState _ in ELSE patch.clipState _ clipped; }; GetPtrPatchClipState: PROC[ shape: REF ShapeInstance, patch: REF PtrPatch] ~ { orOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.NoneOut; andOfCodes: ThreeDBasics.OutCode _ ThreeDBasics.AllOut; FOR j: NAT IN [0..patch.nVtces) DO k: NAT _ patch.vtxPtr[j]; orOfCodes _ LOOPHOLE[ Basics.BITOR[ LOOPHOLE[orOfCodes], LOOPHOLE[shape.vertex[k].clip]], ThreeDBasics.OutCode]; andOfCodes _ LOOPHOLE[ Basics.BITAND[LOOPHOLE[andOfCodes], LOOPHOLE[shape.vertex[k].clip]], ThreeDBasics.OutCode]; ENDLOOP; IF andOfCodes # ThreeDBasics.NoneOut THEN patch.clipState _ out ELSE IF orOfCodes = ThreeDBasics.NoneOut THEN patch.clipState _ in ELSE patch.clipState _ clipped; }; <> ShapeDo: PROC[ context: REF Context, shape: REF ShapeInstance, fullExpand: BOOLEAN, limitType: ATOM, limit: REAL] RETURNS [REF ShapeInstance] ~ { MakeRoom: PROC [] ~ { -- ensure enough space for storing expanded shape IF vertex = NIL -- first we attempt to guess at how much space will be needed THEN vertex _ NEW[ VertexSequence[newPts.length * shape.numSurfaces] ] ELSE IF vertex.length < newPts.length + ptIndex -- then we expand as needed THEN { vertex2: REF VertexSequence; IF vertex.length * 2 > LAST[NAT] THEN SIGNAL ThreeDScenes.Error[[$Unimplemented, "Sequence too long (Dragon needed)"]]; vertex2 _ NEW[ VertexSequence[vertex.length*2] ]; FOR i: NAT IN [0..vertex.length) DO -- copy old sequence IF vertex[i] # NIL THEN vertex2[i] _ NEW[ Vertex _ vertex[i]^ ] ELSE vertex2[i] _ NEW[ Vertex ]; ENDLOOP; vertex _ vertex2; }; IF shade = NIL -- first we attempt to guess at how much space will be needed THEN shade _ NEW[ ShadingSequence[newPts.length * shape.numSurfaces] ] ELSE IF shade.length < newPts.length + ptIndex -- then we expand as needed THEN { shade2: REF ShadingSequence _ NEW[ ShadingSequence[vertex.length*2] ]; FOR i: NAT IN [0..shade.length) DO -- copy old sequence IF shade[i] # NIL THEN shade2[i] _ NEW[ ShadingValue _ shade[i]^ ] ELSE shade2[i] _ NEW[ ShadingValue ]; ENDLOOP; shade _ shade2; }; IF surface = NIL -- first we attempt to guess at how much space will be needed THEN surface _ NEW[ PtrPatchSequence[newPatches.length * shape.numSurfaces] ] ELSE IF surface.length < newPatches.length + patchIndex -- then we expand as needed THEN { surface2: REF PtrPatchSequence; IF surface.length * 2 > LAST[NAT] THEN SIGNAL ThreeDScenes.Error[[$Unimplemented, "Sequence too long (Dragon needed)"]]; surface2 _ NEW[ PtrPatchSequence[surface.length*2] ]; FOR i: NAT IN [0..surface.length) DO -- copy old sequence IF surface[i] # NIL THEN surface2[i] _ NEW[ PtrPatch _ surface[i]^ ] ELSE surface2[i] _ NEW[ PtrPatch ]; ENDLOOP; surface _ surface2; }; }; patch: REF PtrPatchSequence _ NARROW[ shape.surface ]; vertex: REF ThreeDBasics.VertexSequence; shade: REF ThreeDBasics.ShadingSequence; surface: REF PtrPatchSequence; patchInfo: REF ThreeDBasics.ShadingSequence _ NARROW[ ThreeDScenes.GetShading[ shape, $PatchColors ] ]; newPts: REF ThreeDBasics.VertexInfoSequence; newPatches: REF PtrPatchSequence; ptIndex, patchIndex: INT _ 0; class: REF ThreeDSurfaces.PatchProcs _ NARROW[ Atom.GetPropFromList[context.props, patch[0].type] ]; IF class = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No class registered"]]; IF fullExpand AND class.expand = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No expand Proc"]]; IF NOT fullExpand AND class.subdivide = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No subdivide Proc"]]; FOR pNum: NAT IN [0..shape.numSurfaces) DO IF fullExpand -- expand patch THEN [newPts, newPatches] _ class.expand[shape, patch[pNum], limitType, limit] ELSE [newPts, newPatches] _ class.subdivide[shape, patch[pNum], limitType, limit]; MakeRoom[]; -- get storage space for expanded shape FOR i: NAT IN [0..newPts.length) DO -- copy the vertices into the whole vertex[i+ptIndex] _ NEW[ ThreeDBasics.Vertex ]; vertex[i+ptIndex]^ _ newPts[i].coord; shade[i+ptIndex] _ NEW[ ThreeDBasics.ShadingValue ]; shade[i+ptIndex]^ _ newPts[i].shade; IF patchInfo # NIL THEN { shade[i+ptIndex].r _ shade[i+ptIndex].r * patchInfo[pNum].r; shade[i+ptIndex].g _ shade[i+ptIndex].g * patchInfo[pNum].g; shade[i+ptIndex].b _ shade[i+ptIndex].b * patchInfo[pNum].b; }; ENDLOOP; FOR i: NAT IN [0..newPatches.length) DO -- copy the polygons into the whole surface[i+patchIndex].vtxPtr _ NEW[ NatSequence[newPatches[i].nVtces] ]; FOR j: NAT IN [0..newPatches[i].nVtces) DO surface[i+patchIndex].vtxPtr[j] _ newPatches[i].vtxPtr[j] + ptIndex; ENDLOOP; surface[i+patchIndex].type _ newPatches[i].type; surface[i+patchIndex].oneSided _ newPatches[i].oneSided; surface[i+patchIndex].dir _ newPatches[i].dir; surface[i+patchIndex].nVtces _ newPatches[i].nVtces; surface[i+patchIndex].clipState _ newPatches[i].clipState; surface[i+patchIndex].props _ newPatches[i].props; ENDLOOP; ptIndex _ ptIndex + newPts.length; -- update the indices patchIndex _ patchIndex + newPatches.length; ENDLOOP; IF fullExpand THEN shape.type _ $ConvexPolygon; -- set type to polygons if fully expanded shape.vertex _ vertex; -- point the shape at the new data shape.shade _ shade; shape.surface _ surface; shape.numSurfaces _ surface.length; ThreeDScenes.PutShading[ shape, $PatchColors, NIL ]; shape.shadingInValid _ TRUE; shape.vtcesInValid _ TRUE; RETURN[shape]; }; ShapeExpand: PUBLIC PROC[ context: REF Context, shape: REF ShapeInstance, limitType: ATOM _ NIL, limit: REAL _ 0.0] RETURNS [REF ShapeInstance] ~ { <> RETURN[ ShapeDo[ context, shape, TRUE, limitType, limit ] ]; }; ShapeSubdivide: PUBLIC PROC[ context: REF Context, shape: REF ShapeInstance, limitType: ATOM _ NIL, limit: REAL _ 0.0] RETURNS [REF ShapeInstance] ~ { <> RETURN[ ShapeDo[ context, shape, FALSE, limitType, limit ] ]; }; ExpandToLines: PROC[ context: REF Context, patch: REF Patch, action: PROC[context: REF Context, patch: REF Patch] ] ~ { <> class: REF ThreeDSurfaces.PatchProcs _ NARROW[ Atom.GetPropFromList[context.props, patch.type] ]; IF class = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No class registered"]]; class.displayLines[context, patch, NIL, 0.0, action]; -- expand to default limit and display << PROC[ context: REF Context, patch: REF Patch, limitType: ATOM, limit: REAL, action: PROC];>> }; limitInPixels: REAL _ 2.0; ExpandToConvexPolys: PROC[ context: REF Context, patch: REF Patch, action: PROC[context: REF Context, patch: REF Patch] ] ~ { <> class: REF ThreeDSurfaces.PatchProcs _ NARROW[ Atom.GetPropFromList[context.props, patch.type] ]; IF class = NIL THEN ERROR ThreeDScenes.Error[[$MisMatch, "No class registered"]]; IF context.alphaBuffer THEN class.display[context, patch, NIL, 0.0, action] -- expand to maximum and display ELSE class.display[context, patch, NIL, limitInPixels, action]; -- expand for quick display << PROC[ context: REF Context, patch: REF Patch, limitType: ATOM, limit: REAL, action: PROC];>> }; RegisterSurfaceType: PUBLIC PROC[ context: REF Context, type: ATOM, procs: REF ThreeDSurfaces.PatchProcs ] ~ { context.props _ Atom.PutPropOnList[context.props, type, procs]; }; <> BackFacing: PUBLIC PROC[ poly: REF Patch, useEyeSpace: BOOLEAN _ FALSE] RETURNS [FacingDir] ~ { <> SELECT poly.type FROM $ConvexPolygon => IF useEyeSpace THEN { <> this: VertexInfo _ poly.vtx[0]; next: VertexInfo _ poly.vtx[1]; last: VertexInfo _ poly.vtx[2]; <> direction: Triple _ Vector3d.Normalize[Vector3d.Cross[ [next.coord.ex - this.coord.ex, next.coord.ey - this.coord.ey, next.coord.ez - this.coord.ez], [last.coord.ex - this.coord.ex, last.coord.ey - this.coord.ey, last.coord.ez - this.coord.ez] ] ]; dotDir: REAL _ Vector3d.Dot[[this.coord.ex, this.coord.ey, this.coord.ez] , direction]; IF dotDir > 0.0 THEN RETURN[back] ELSE IF dotDir < 0.0 THEN RETURN[front]; } ELSE { -- do check in image space, rejecting eensy polygon edges s: REAL _ 1.0 / ScanConvert.justNoticeable; -- scales visible feature size to 1 FOR i: NAT IN [0..poly.nVtces) DO this: VertexInfo _ poly.vtx[i]; next: VertexInfo _ poly.vtx[(i+1) MOD poly.nVtces]; last: VertexInfo _ poly.vtx[(i+poly.nVtces-1) MOD poly.nVtces]; zNorm: INT _ -- integer computation of z-coord of normal ( Real.Fix[s*next.coord.sx - s*this.coord.sx] ) * ( Real.Fix[s*last.coord.sy - s*this.coord.sy] ) - ( Real.Fix[s*next.coord.sy - s*this.coord.sy] ) * ( Real.Fix[s*last.coord.sx - s*this.coord.sx] ); IF zNorm > 0 THEN RETURN[ back ] ELSE IF zNorm < 0 THEN RETURN[ front ]; ENDLOOP; SIGNAL ThreeDScenes.Error[[$Condition, "Edges too small for stable arithmetic"]]; }; $Bezier => { <