DIRECTORY Atom USING [ GetPropFromList, PropList, PutPropOnList ], Real USING [ Fix, Float ], Rope USING [ ROPE ], CedarProcess USING [ DoWithPriority ], G3dVector USING [ Cross, Sub, Length, Normalize ], G3dMatrix USING [ Transform ], ThreeDBasics USING [ Context, Error, NatSequence, PairSequence, PtrPatch, PtrPatchSequence, Quad, RGB, SetPosition, ShadingSequence, ShapeClass, ShapeInstance, ShapeSequence, ShadingValue, Triple, TripleSequence, Vertex, VertexInfo, VertexInfoProc, VertexInfoSequence, VertexSequence ], SceneUtilities USING [ FindShape, NewShape ], ShapeTwiddle USING [ NatPair ]; ShapeTwiddleImpl: CEDAR PROGRAM IMPORTS Atom, CedarProcess, G3dMatrix, Real, SceneUtilities, ThreeDBasics, G3dVector EXPORTS ShapeTwiddle ~ BEGIN LORA: TYPE ~ LIST OF REF ANY; Context: TYPE ~ ThreeDBasics.Context; RGB: TYPE ~ ThreeDBasics.RGB; ShadingValue: TYPE ~ ThreeDBasics.ShadingValue; Vertex: TYPE ~ ThreeDBasics.Vertex; VertexSequence: TYPE ~ ThreeDBasics.VertexSequence; VertexInfo: TYPE ~ ThreeDBasics.VertexInfo; VertexInfoProc: TYPE ~ ThreeDBasics.VertexInfoProc; VertexInfoSequence: TYPE ~ ThreeDBasics.VertexInfoSequence; Triple: TYPE ~ ThreeDBasics.Triple; TripleSequence: TYPE ~ ThreeDBasics.TripleSequence; NatSequence: TYPE ~ ThreeDBasics.NatSequence; PairSequence: TYPE ~ ThreeDBasics.PairSequence; ShapeInstance: TYPE ~ ThreeDBasics.ShapeInstance; PtrPatch: TYPE ~ ThreeDBasics.PtrPatch; PtrPatchSequence: TYPE ~ ThreeDBasics.PtrPatchSequence; ShadingSequence: TYPE ~ ThreeDBasics.ShadingSequence; ShapeClass: TYPE ~ ThreeDBasics.ShapeClass; NatPair: TYPE ~ ShapeTwiddle.NatPair; -- RECORD [x, y: NAT]; GetProp: PROC [propList: Atom.PropList, prop: REF ANY] RETURNS [REF ANY] ~ Atom.GetPropFromList; PutProp: PROC [propList: Atom.PropList, prop: REF ANY, val: REF ANY] RETURNS [Atom.PropList] ~ Atom.PutPropOnList; DiffPosns: PROC[vtx1, vtx2: Vertex] RETURNS[Triple] ~ { RETURN[[vtx1.x - vtx2.x, vtx1.y - vtx2.y, vtx1.z - vtx2.z]]; -- object space }; ScaleShape: PUBLIC PROC [context: REF Context, name: Rope.ROPE, scale: REAL, xRatio, yRatio, zRatio: REAL _ 1.0, applyXfm: BOOLEAN _ FALSE] ~ { shape: REF ShapeInstance _ SceneUtilities.FindShape[ context, name ]; IF shape.positionInValid THEN ThreeDBasics.SetPosition[shape]; -- set position matrix FOR i: NAT IN [0..shape.vertex.length) DO OPEN shape.vertex[i]; tx, ty, tz: REAL; IF applyXfm THEN [ [tx, ty, tz] ] _ G3dMatrix.Transform[ [x, y, z], shape.position] ELSE { tx _ x; ty _ y; tz _ z; }; x _ tx * scale * xRatio; y _ ty * scale * yRatio; z _ tz * scale * zRatio; ENDLOOP; shape.boundingRadius _ shape.boundingRadius * scale * MAX[xRatio, yRatio, zRatio]; shape.shadingProps _ PutProp[ shape.shadingProps, $Scale, NEW[ ThreeDBasics.Quad _ [scale, xRatio, yRatio, zRatio] ] ]; }; ScaleTexture: PUBLIC PROC [context: REF Context, name: Rope.ROPE, scale: REAL, xRatio, yRatio, zRatio: REAL _ 1.0] ~ { shape: REF ShapeInstance _ SceneUtilities.FindShape[ context, name ]; auxData: REF _ GetProp[ shape.shadingProps, $AuxiliaryVtxData ]; WITH auxData SELECT FROM pairs: REF PairSequence => FOR i: NAT IN [0..pairs.length) DO pairs[i].x _ pairs[i].x * scale * xRatio; pairs[i].y _ pairs[i].y * scale * yRatio; ENDLOOP; triples: REF TripleSequence => FOR i: NAT IN [0..triples.length) DO triples[i].x _ triples[i].x * scale * xRatio; triples[i].y _ triples[i].y * scale * yRatio; triples[i].z _ triples[i].z * scale * zRatio; ENDLOOP; ENDCASE => SIGNAL ThreeDBasics.Error[[$Unimplemented, "Unrecognized coord type"]]; shape.shadingProps _ PutProp[ shape.shadingProps, $TextureScale, NEW[ ThreeDBasics.Quad _ [scale, xRatio, yRatio, zRatio] ] ]; }; SortPair: TYPE ~ RECORD [vtx, next: NAT]; SortSequence: TYPE ~ RECORD[SEQUENCE length: NAT OF REF SortPair]; CleanUp: PUBLIC PROC [context: REF Context, name: Rope.ROPE, deSeam: BOOLEAN _ FALSE, tolerance: REAL _ 0.0] ~ { currPos: NAT _ 0; shape: REF ShapeInstance _ SceneUtilities.FindShape[ context, name ]; surface: REF PtrPatchSequence _ NARROW[shape.surface]; table: REF NatSequence _ NEW[ NatSequence[shape.vertex.length] ]; buckets: REF SortSequence _ NEW[SortSequence[5 * shape.vertex.length / 4]]; nextBucket: NAT _ (shape.vertex.length / 4) + 1; newVtx: REF VertexSequence; newShade: REF ShadingSequence; Action: PROC ~ { IF deSeam THEN { minX, maxX, scale: REAL; [minX, maxX] _ Bounds[context, name]; scale _ (shape.vertex.length / 4) / (maxX - minX); IF 1.0 / scale < tolerance THEN SIGNAL ThreeDBasics.Error[[$Mismatch, "Tolerance too large"]]; FOR i: NAT IN [0..shape.vertex.length) DO -- bucket sort vertices index: NAT _ Real.Fix[ (shape.vertex[i].x - minX) * scale ]; IF buckets[index] # NIL THEN { buckets[nextBucket] _ NEW[SortPair]; buckets[nextBucket].next _ buckets[index].next; -- put on next-to-head of list buckets[index].next _ nextBucket; -- reset first pointer index _ nextBucket; nextBucket _ nextBucket + 1; } ELSE { buckets[index] _ NEW[SortPair]; -- bucket hit for first time buckets[index].next _ 0; }; buckets[index].vtx _ i; -- store vertex pointer ENDLOOP; FOR i: NAT IN [1..table.length) DO -- Coalesce nearby vertices vtx: REF Vertex _ shape.vertex[i]; xBucket: NAT _ MAX[ 1, MIN[shape.vertex.length-1, INTEGER[ Real.Fix[ (vtx.x - minX)*scale] ]] ]; table[i] _ i; -- set to identity value FOR j: NAT IN [xBucket-1 .. xBucket+1] DO -- search this and last and next buckets index: NAT _ j; WHILE buckets[index] # NIL DO k: NAT _ buckets[index].vtx; diff: REAL _ G3dVector.Length[ G3dVector.Sub[ -- check distance [vtx.x, vtx.y, vtx.z], [shape.vertex[k].x, shape.vertex[k].y, shape.vertex[k].z] ] ]; IF diff <= tolerance THEN IF k < table[i] THEN table[i] _ k; -- reset if smaller index _ buckets[index].next; IF index = 0 THEN EXIT; ENDLOOP; ENDLOOP; ENDLOOP; FOR i: NAT IN [0..shape.numSurfaces) DO -- retarget vertex pointers IF surface[i] # NIL THEN FOR j: NAT IN [0..surface[i].nVtces) DO surface[i].vtxPtr[j] _ table[surface[i].vtxPtr[j]]; ENDLOOP; ENDLOOP; IF shape.class.type = $ConvexPolygon THEN { FOR i: NAT IN [0..shape.numSurfaces) DO -- eliminate duplicated polygon vertices vtx: NAT _ 0; IF surface[i] # NIL THEN FOR j: NAT IN [0..surface[i].nVtces) DO k: NAT _ (j-1 + surface[i].nVtces) MOD surface[i].nVtces; IF surface[i].vtxPtr[j] # surface[i].vtxPtr[k] THEN { surface[i].vtxPtr[vtx] _ surface[i].vtxPtr[j]; vtx _ vtx + 1; }; ENDLOOP; surface[i].nVtces _ vtx; ENDLOOP; }; }; -- end deSeaming block FOR i: NAT IN [0..table.length) DO table[i] _ 0; ENDLOOP; FOR i: NAT IN [0..shape.numSurfaces) DO -- build vertex reference count IF surface[i] # NIL THEN FOR j: NAT IN [0..surface[i].nVtces) DO table[surface[i].vtxPtr[j]] _ table[surface[i].vtxPtr[j]] + 1; ENDLOOP; ENDLOOP; currPos _ 0; FOR i: NAT IN [0..table.length) DO -- collapse vertex array and keep audit trail IF table[i] # 0 THEN { shape.vertex[currPos] _ shape.vertex[i]; shape.shade[currPos] _ shape.shade[i]; table[i] _ currPos; currPos _ currPos + 1; }; ENDLOOP; newVtx _ NEW[ VertexSequence[currPos] ]; newVtx.length _ currPos; newShade _ NEW[ ShadingSequence[currPos] ]; newShade.length _ currPos; FOR i: NAT IN [0..currPos) DO -- copy into new sequences of proper length newVtx[i] _ shape.vertex[i]; newShade[i] _ shape.shade[i]; ENDLOOP; shape.vertex _ newVtx; shape.shade _ newShade; FOR i: NAT IN [0..shape.numSurfaces) DO -- retarget vertex pointers FOR j: NAT IN [0..surface[i].nVtces) DO surface[i].vtxPtr[j] _ table[surface[i].vtxPtr[j]]; ENDLOOP; ENDLOOP; }; CedarProcess.DoWithPriority[background, Action]; }; CopyShape: PUBLIC PROC [context: REF Context, dstName, srcName: Rope.ROPE] RETURNS[REF ShapeInstance] ~ { dstShape: REF ShapeInstance _ SceneUtilities.NewShape[dstName]; srcShape: REF ShapeInstance _ SceneUtilities.FindShape[ context, srcName ]; srcSurface: REF PtrPatchSequence _ NARROW[srcShape.surface]; dstSurface: REF PtrPatchSequence; currPos: NAT _ 0; shape: REF ShapeInstance _ SceneUtilities.NewShape[dstName]; dstShape.orientation _ srcShape.orientation; dstShape.location _ srcShape.location; dstShape.rotation _ srcShape.rotation; dstShape.axisBase _ srcShape.axisBase; dstShape.axisEnd _ srcShape.axisEnd; dstShape.centroid _ srcShape.centroid; dstShape.boundingRadius _ srcShape.boundingRadius; dstShape.vertex _ NEW[ThreeDBasics.VertexSequence[srcShape.vertex.length] ]; dstShape.vertex.length _ srcShape.vertex.length; FOR i: NAT IN [0..srcShape.vertex.length) DO dstShape.vertex[i] _ srcShape.vertex[i]; ENDLOOP; dstShape.shade _ NEW[ ShadingSequence[srcShape.shade.length] ]; dstShape.shade.length _ srcShape.shade.length; FOR i: NAT IN [0..srcShape.shade.length) DO dstShape.shade[i] _ srcShape.shade[i]; ENDLOOP; dstShape.surface _ NEW[ PtrPatchSequence[srcShape.numSurfaces] ]; dstSurface _ NARROW[dstShape.surface, REF PtrPatchSequence]; FOR i: NAT IN [0..srcShape.numSurfaces) DO dstSurface[i] _ srcSurface[i]; ENDLOOP; dstShape.numSurfaces _ srcShape.numSurfaces; dstShape.shadingProps _ srcShape.shadingProps; dstShape.props _ srcShape.props; RETURN[dstShape]; }; Combine: PUBLIC PROC [context: REF Context, dstName, src1, src2: Rope.ROPE] RETURNS[REF ShapeInstance] ~ { shape: REF ShapeInstance _ SceneUtilities.NewShape[dstName]; shape1: REF ShapeInstance _ SceneUtilities.FindShape[ context, src1 ]; shape2: REF ShapeInstance _ SceneUtilities.FindShape[ context, src2 ]; surface1: REF PtrPatchSequence _ NARROW[shape1.surface]; surface2: REF PtrPatchSequence _ NARROW[shape2.surface]; surface: REF PtrPatchSequence; shape.vertex _ NEW[ -- copy vertices ThreeDBasics.VertexSequence[shape1.vertex.length + shape2.vertex.length] ]; shape.vertex.length _ shape.vertex.maxLength; FOR i: NAT IN [0..shape1.vertex.length) DO shape.vertex[i] _ shape1.vertex[i]; [[shape.vertex[i].x, shape.vertex[i].y, shape.vertex[i].z]] _ G3dMatrix.Transform[ [shape.vertex[i].x, shape.vertex[i].y, shape.vertex[i].z], shape1.position ]; ENDLOOP; FOR i: NAT IN [0..shape2.vertex.length) DO shape.vertex[i+shape1.vertex.length] _ shape2.vertex[i]; [[shape.vertex[i].x, shape.vertex[i].y, shape.vertex[i].z]] _ G3dMatrix.Transform[ [shape.vertex[i].x, shape.vertex[i].y, shape.vertex[i].z], shape2.position ]; ENDLOOP; shape.shade _ NEW[ -- copy shading values ShadingSequence[shape1.shade.length + shape2.shade.length] ]; shape.shade.length _ shape.shade.maxLength; FOR i: NAT IN [0..shape1.shade.length) DO shape.shade[i] _ shape1.shade[i]; ENDLOOP; FOR i: NAT IN [0..shape2.shade.length) DO shape.shade[i+shape1.shade.length] _ shape2.shade[i]; ENDLOOP; shape.numSurfaces _ shape1.numSurfaces + shape2.numSurfaces; shape.surface _ NEW[ -- copy surfaces PtrPatchSequence[shape1.numSurfaces + shape2.numSurfaces] ]; surface _ NARROW[shape.surface, REF PtrPatchSequence]; FOR i: NAT IN [0..shape1.numSurfaces) DO surface[i] _ surface1[i]; ENDLOOP; FOR i: NAT IN [0..shape2.numSurfaces) DO base: NAT _ shape1.numSurfaces; surface[i+base] _ surface2[i]; FOR j: NAT IN [0..surface[i+base].nVtces) DO -- redirect vertex pointers surface[i+base].vtxPtr[j] _ surface[i+base].vtxPtr[j] + shape1.vertex.length ENDLOOP; ENDLOOP; shape.shadingProps _ shape1.shadingProps; shape.props _ shape1.props; RETURN[shape]; }; DeletePatches: PUBLIC PROC [context: REF Context, dstName, srcName: Rope.ROPE, patchList: LIST OF NatPair] RETURNS[REF ShapeInstance] ~ { currPos: NAT _ 0; oldShape: REF ShapeInstance _ SceneUtilities.FindShape[ context, srcName ]; shape: REF ShapeInstance _ CopyShape[context, dstName, srcName]; surface: REF PtrPatchSequence; surface _ NARROW[shape.surface, REF PtrPatchSequence]; FOR list: LIST OF NatPair _ patchList, list.rest UNTIL list = NIL DO FOR i: NAT IN [list.first.x..list.first.y] DO surface[i] _ NIL; ENDLOOP; ENDLOOP; FOR i: NAT IN [0..shape.numSurfaces) DO -- collapse array IF surface[i] # NIL THEN { surface[currPos] _ surface[i]; currPos _ currPos + 1; }; ENDLOOP; shape.numSurfaces _ currPos; RETURN[ shape ]; }; Bounds: PUBLIC PROC [context: REF Context, name: Rope.ROPE] RETURNS[xMin, xMax, yMin, yMax, zMin, zMax: REAL] ~ { shape: REF ShapeInstance _ SceneUtilities.FindShape[ context, name ]; xMin _ xMax _ shape.vertex[0].x; yMin _ yMax _ shape.vertex[0].y; zMin _ zMax _ 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].x < xMin THEN xMin _ shape.vertex[i].x ELSE IF shape.vertex[i].x > xMax THEN xMax _ shape.vertex[i].x; IF shape.vertex[i].y < yMin THEN yMin _ shape.vertex[i].y ELSE IF shape.vertex[i].y > yMax THEN yMax _ shape.vertex[i].y; IF shape.vertex[i].z < zMin THEN zMin _ shape.vertex[i].z ELSE IF shape.vertex[i].z > zMax THEN zMax _ shape.vertex[i].z; ENDLOOP; }; 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.maxLength < newPts.length + ptIndex -- then we expand as needed THEN { vertex2: REF VertexSequence; IF vertex.length * 2 > LAST[CARDINAL] THEN SIGNAL ThreeDBasics.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; }; vertex.length _ vertex.maxLength; 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; }; shade.length _ shade.maxLength; 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 ThreeDBasics.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; }; surface.length _ surface.maxLength; }; expand: PROC[shape: REF ShapeInstance, patch: REF PtrPatch, nPrSide: NAT] RETURNS [REF VertexInfoSequence, REF PtrPatchSequence]; subdivide: PROC [shape: REF ThreeDBasics.ShapeInstance, patch: REF PtrPatch] RETURNS [REF VertexInfoSequence, REF PtrPatchSequence]; patch: REF PtrPatchSequence _ NARROW[ shape.surface ]; vertex: REF ThreeDBasics.VertexSequence; shade: REF ShadingSequence; surface: REF PtrPatchSequence; patchInfo: REF ShadingSequence _ shape.shadingClass.patchShade; newPts: REF VertexInfoSequence; newPatches: REF PtrPatchSequence; ptIndex, patchIndex: INT _ 0; SELECT shape.class.type FROM $Bezier => { expand _ BezierParametricExpand; subdivide _ BezierSubdivideExpand; }; ENDCASE => SIGNAL ThreeDBasics.Error[[$Unimplemented, "Unknown surface type"]]; FOR pNum: NAT IN [0..shape.numSurfaces) DO IF fullExpand -- expand patch THEN [newPts, newPatches] _ expand[ shape, patch[pNum], Real.Fix[limit] ] ELSE [newPts, newPatches] _ subdivide[ shape, patch[pNum] ]; 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[ 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] _ NEW[ PtrPatch ]; 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.class.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; shape.shadingClass.patchShade _ NIL; shape.shadingInValid _ TRUE; shape.vtcesInValid _ TRUE; RETURN[shape]; }; ShapeExpand: PUBLIC PROC[ context: REF Context, name: Rope.ROPE, limitType: ATOM _ NIL, limit: REAL _ 0.0] RETURNS [REF ShapeInstance] ~ { shape: REF ShapeInstance _ SceneUtilities.FindShape[ context, name ]; RETURN[ ShapeDo[ context, shape, TRUE, limitType, limit ] ]; }; ShapeSubdivide: PUBLIC PROC[ context: REF Context, name: Rope.ROPE, limitType: ATOM _ NIL, limit: REAL _ 0.0] RETURNS [REF ShapeInstance] ~ { shape: REF ShapeInstance _ SceneUtilities.FindShape[ context, name ]; RETURN[ ShapeDo[ context, shape, FALSE, limitType, limit ] ]; }; BezierPtrPatchNormals: PROC[ shape: REF ShapeInstance, patch: REF PtrPatch] ~ { GetXProd: PROC[vertex: REF ThreeDBasics.VertexSequence, v1b, v1e, v2b, v2e: NAT] RETURNS[Triple] ~ { RETURN [ G3dVector.Normalize[ G3dVector.Cross[ -- in object space so do right-handed DiffPosns[ vertex[v1e]^, vertex[v1b]^ ], DiffPosns[ vertex[v2e]^, vertex[v2b]^ ] ] ] ]; }; vertex: REF ThreeDBasics.VertexSequence _ shape.vertex; shade: REF ThreeDBasics.ShadingSequence _ shape.shade; FOR i: INTEGER IN [0..4) DO FOR j: INTEGER IN [0..4) DO k: NAT _ patch.vtxPtr[j + i*4]; IF shade[k].xn = 0.0 AND shade[k].yn = 0.0 AND shade[k].zn = 0.0 THEN { -- untouched v1Beg: NAT _ 4*i + MAX[j-1, 0]; v1End: NAT _ 4*i + MIN[j+1, 3]; v2Beg: NAT _ 4*MAX[i-1, 0] + j; v2End: NAT _ 4*MIN[i+1, 3] + j; IF patch.vtxPtr[v1Beg] = patch.vtxPtr[v1End] THEN { -- try to fix coalesced points v1Beg _ 4*MAX[i-1, 0] + MAX[j-1, 0]; v1End _ 4*MIN[i+1, 3] + MIN[j+1, 3]; IF patch.vtxPtr[v1Beg] = patch.vtxPtr[v1End] THEN SIGNAL ThreeDBasics.Error[[$MisMatch, "DegeneratePatch"]]; }; IF patch.vtxPtr[v2Beg] = patch.vtxPtr[v2End] THEN { -- try to fix coalesced points v2Beg _ 4*MAX[i-1, 0] + MAX[j-1, 0]; v2End _ 4*MIN[i+1, 3] + MIN[j+1, 3]; IF patch.vtxPtr[v2Beg] = patch.vtxPtr[v2End] THEN SIGNAL ThreeDBasics.Error[[$MisMatch, "DegeneratePatch"]]; }; [[ shade[k].xn, shade[k].yn, shade[k].zn ]] _ GetXProd[ vertex, patch.vtxPtr[v1Beg], patch.vtxPtr[v1End], patch.vtxPtr[v2Beg], patch.vtxPtr[v2End] ]; }; ENDLOOP; ENDLOOP; }; ApplyCubicBasis: PROC[ v0, v1, v2, v3: REF VertexInfo, f0, f1, f2, f3: REAL ] RETURNS[vOut: REF VertexInfo] ~ { shape: REF ShapeInstance _ NARROW[ Atom.GetPropFromList[v0.props, $Shape] ]; lerpProc: VertexInfoProc _ IF shape # NIL THEN shape.shadingClass.lerpVtxAux ELSE NIL; vOut _ NEW[VertexInfo]; vOut.coord.x _ f0*v0.coord.x + f1*v1.coord.x + f2*v2.coord.x + f3*v3.coord.x; vOut.coord.y _ f0*v0.coord.y + f1*v1.coord.y + f2*v2.coord.y + f3*v3.coord.y; vOut.coord.z _ f0*v0.coord.z + f1*v1.coord.z + f2*v2.coord.z + f3*v3.coord.z; vOut.shade.xn _ f0*v0.shade.xn + f1*v1.shade.xn + f2*v2.shade.xn + f3*v3.shade.xn; vOut.shade.yn _ f0*v0.shade.yn + f1*v1.shade.yn + f2*v2.shade.yn + f3*v3.shade.yn; vOut.shade.zn _ f0*v0.shade.zn + f1*v1.shade.zn + f2*v2.shade.zn + f3*v3.shade.zn; vOut.shade.r _ f0*v0.shade.r + f1*v1.shade.r + f2*v2.shade.r + f3*v3.shade.r; vOut.shade.g _ f0*v0.shade.g + f1*v1.shade.g + f2*v2.shade.g + f3*v3.shade.g; vOut.shade.b _ f0*v0.shade.b + f1*v1.shade.b + f2*v2.shade.b + f3*v3.shade.b; IF lerpProc # NIL THEN { -- get auxiliary info from supplied proc data: LORA _ LIST[v0.aux, vOut.aux, NEW[REAL _ f0], NEW[REAL _ 0.0]]; vOut.aux _ NIL; vOut^ _ lerpProc[ NIL, vOut^, data]; data _ LIST[ v1.aux, vOut.aux, NEW[REAL _ f1], NEW[REAL _ 1.0]]; vOut.aux _ NIL; vOut^ _ lerpProc[ NIL, vOut^, data]; data _ LIST[ v2.aux, vOut.aux, NEW[REAL _ f2], NEW[REAL _ 1.0]]; vOut.aux _ NIL; vOut^ _ lerpProc[ NIL, vOut^, data]; data _ LIST[ v3.aux, vOut.aux, NEW[REAL _ f3], NEW[REAL _ 1.0]]; vOut.aux _ NIL; vOut^ _ lerpProc[ NIL, vOut^, data]; } ELSE vOut.aux _ v0.aux; }; BezierParametricExpand: PROC[shape: REF ShapeInstance, patch: REF PtrPatch, nPrSide: NAT] RETURNS [REF VertexInfoSequence, REF PtrPatchSequence] ~ { vertex: REF ThreeDBasics.VertexSequence _ shape.vertex; shade: REF ThreeDBasics.ShadingSequence _ shape.shade; RowEval: PROC[ v0, v1, v2, v3: REF VertexInfo, numPts: NAT ] RETURNS [pt: REF VertexInfoSequence] ~ { pt _ NEW[ VertexInfoSequence[numPts] ]; pt.length _ numPts; FOR i: NAT IN [0..numPts) DO t: REAL _ Real.Float[i] / (numPts-1); t2: REAL _ t * t; t3: REAL _ t2 * t; f0: REAL _ -1.0*t3 + 3.0*t2 - 3.0*t + 1; f1: REAL _ 3.0*t3 - 6.0*t2 + 3.0*t; f2: REAL _ -3.0*t3 + 3.0*t2; f3: REAL _ 1.0*t3; pt[i] _ ApplyCubicBasis[v0, v1, v2, v3, f0, f1, f2, f3]; ENDLOOP; }; row: ARRAY [0..4) OF REF VertexInfoSequence; colA, colB: REF VertexInfoSequence; vtxCnt, ptchCnt: NAT _ 0; nVtces: NAT _ (nPrSide+1) * (nPrSide+1); outVtx: REF VertexInfoSequence _ NEW[ VertexInfoSequence[nVtces] ]; outPatch: REF PtrPatchSequence _ NEW[ PtrPatchSequence[nPrSide*nPrSide] ]; ctlPtRow: ARRAY [0..4) OF REF VertexInfo; outputType: ATOM _ NARROW[ Atom.GetPropFromList[ patch.props, $InterimPatchType ] ]; IF outputType = NIL THEN outputType _ $ConvexPolygon; BezierPtrPatchNormals[shape, patch]; FOR i: NAT IN [0..4) DO FOR j: NAT IN [0..4) DO IF ctlPtRow[j] = NIL THEN ctlPtRow[j] _ NEW[ VertexInfo ]; ctlPtRow[j].coord _ vertex[patch.vtxPtr[i*4 + j]]^; ctlPtRow[j].shade _ shade[patch.vtxPtr[i*4 + j]]^; ENDLOOP; row[i] _ RowEval[ ctlPtRow[0], ctlPtRow[1], ctlPtRow[2], ctlPtRow[3], nPrSide+1 ]; ENDLOOP; colA _ RowEval[ row[0][0], row[1][0], row[2][0], row[3][0], nPrSide+1 ]; FOR i: NAT IN [0..nPrSide] DO outVtx[i+vtxCnt] _ colA[i]; ENDLOOP; -- store vertices vtxCnt _ vtxCnt + nPrSide+1; FOR i: NAT IN [1..nPrSide] DO colB _ RowEval[ row[0][i], row[1][i], row[2][i], row[3][i], nPrSide+1 ]; FOR j: NAT IN [0..nPrSide] DO outVtx[j+vtxCnt] _ colB[j]; ENDLOOP; -- store vertices vtxCnt _ vtxCnt + nPrSide+1; FOR j: NAT IN [1..nPrSide] DO IF outPatch[ptchCnt] = NIL THEN outPatch[ptchCnt] _ NEW[PtrPatch]; outPatch[ptchCnt].vtxPtr _ NEW[NatSequence[4]]; outPatch[ptchCnt].vtxPtr[0] _ (nPrSide+1) * (i-1) + j-1; outPatch[ptchCnt].vtxPtr[1] _ (nPrSide+1) * (i-1) + j; outPatch[ptchCnt].vtxPtr[2] _ (nPrSide+1) * i + j; outPatch[ptchCnt].vtxPtr[3] _ (nPrSide+1) * i + j-1; outPatch[ptchCnt].type _ outputType; outPatch[ptchCnt].oneSided _ patch.oneSided; outPatch[ptchCnt].nVtces _ 4; outPatch[ptchCnt].clipState _ patch.clipState; outPatch[ptchCnt].props _ patch.props; ptchCnt _ ptchCnt + 1; ENDLOOP; colA _ colB; ENDLOOP; outVtx.length _ nVtces; outPatch.length _ nPrSide*nPrSide; RETURN[ outVtx, outPatch ]; }; BezierCurveDivide: PUBLIC PROC[v0, v1, v2, v3: REF VertexInfo] RETURNS[pt: REF VertexInfoSequence] ~ { tempPt: REF VertexInfo; pt _ NEW[ VertexInfoSequence[7] ]; pt.length _ 7; pt[0] _ NEW[ VertexInfo _ v0^ ]; pt[6] _ NEW[ VertexInfo _ v3^ ]; pt[1] _ VtxShapeMidPt[v0, v1]; pt[5] _ VtxShapeMidPt[v2, v3]; tempPt _ VtxShapeMidPt[v1, v2]; pt[2] _ VtxShapeMidPt[pt[1], tempPt]; pt[4] _ VtxShapeMidPt[tempPt, pt[5]]; pt[3] _ VtxShapeMidPt[pt[2], pt[4]]; }; VtxShapeMidPt: PROC[v0, v1: REF VertexInfo] RETURNS[REF VertexInfo] ~ { shape: REF ShapeInstance _ NARROW[ Atom.GetPropFromList[v0.props, $Shape] ]; lerpProc: VertexInfoProc _ IF shape # NIL THEN shape.shadingClass.lerpVtxAux ELSE NIL; v: REF VertexInfo _ NEW[VertexInfo]; v.coord.x _ (v0.coord.x + v1.coord.x) / 2; v.coord.y _ (v0.coord.y + v1.coord.y) / 2; v.coord.z _ (v0.coord.z + v1.coord.z) / 2; v.shade.r _ (v0.shade.r + v1.shade.r) / 2; v.shade.g _ (v0.shade.g + v1.shade.g) / 2; v.shade.b _ (v0.shade.b + v1.shade.b) / 2; IF lerpProc # NIL THEN { -- get auxiliary info from supplied proc data: LORA _ LIST[ v0.aux, v1.aux, NEW[REAL _ .5], NEW[REAL _ .5] ]; v^ _ lerpProc[ NIL, v^, data]; } ELSE v.aux _ v0.aux; v.props _ v0.props; RETURN[v]; }; BezierSubdivideExpand: PROC [shape: REF ThreeDBasics.ShapeInstance, patch: REF PtrPatch] RETURNS [REF VertexInfoSequence, REF PtrPatchSequence] ~{ vertex: REF ThreeDBasics.VertexSequence _shape.vertex; shade: REF ThreeDBasics.ShadingSequence _ shape.shade; outVtx: REF VertexInfoSequence _ NEW [ VertexInfoSequence [7*7] ]; outPatch: REF PtrPatchSequence _ NEW[PtrPatchSequence [4]]; row: ARRAY [0..4) OF REF VertexInfoSequence; ctlPtRow: ARRAY [0..4) OF REF VertexInfo; FOR i: NAT IN [0..4) DO FOR j: NAT IN [0..4) DO IF ctlPtRow[j] = NIL THEN ctlPtRow[j] _ NEW[ VertexInfo ]; ctlPtRow[j].coord _ vertex[patch.vtxPtr[i*4 + j]]^; ctlPtRow[j].shade _ shade[patch.vtxPtr[i*4 + j]]^; ENDLOOP; row[i] _ BezierCurveDivide[ ctlPtRow[0], ctlPtRow[1], ctlPtRow[2], ctlPtRow[3] ]; ENDLOOP; FOR i: NAT IN [0..7) DO vtces: REF VertexInfoSequence _ BezierCurveDivide[ row[0][i], row[1][i], row[2][i], row[3][i] ]; FOR j: NAT IN [0..7) DO outVtx[i*7 + j] _ NEW[ VertexInfo _ vtces[j]^ ]; ENDLOOP; ENDLOOP; FOR i: NAT IN [0..4) DO base: NAT _ (i / 2) * 21 + (i MOD 2) * 3; -- {0, 3, 21, 24}, least corners of 7x7 array IF outPatch[i] = NIL THEN outPatch[i] _ NEW[PtrPatch]; outPatch[i].vtxPtr _ NEW [NatSequence[16]]; outPatch[i].type _ patch.type; outPatch[i].oneSided _ patch.oneSided; outPatch[i].nVtces _ 16; outPatch[i].clipState _ patch.clipState; outPatch[i].props _ patch.props; FOR j: NAT IN [0..4) DO FOR k: NAT IN [0..4) DO outPatch[i].vtxPtr[(3-j)*4+k] _ base + 7*j + k; -- count along rows, jump by 7 to next row ENDLOOP; ENDLOOP; ENDLOOP; outVtx.length _ 7*7; outPatch.length _ 4; RETURN[outVtx, outPatch]; }; END. lShapeTwiddleImpl.mesa Last Edited by: Crow, April 8, 1988 1:38:51 pm PDT Types Renamed Procedures Utility Procedures Shape Manipulations delete excess vertices, join identical ones, etc. Procedures for expansion of/to polygons Expands a whole shape, calling procedures supplied by the surface type Subdivide a whole shape once, calling procedures supplied by the surface type Get normals at control points, given by cross product of vectors formed from adjacent control points (limited to patch bounds, of course) Get special output type for weird things like displacement mapping Get normals at control points Expand patch by evaluating control point rows, then spitting out polygons columnwise DeCasteljau subdivision algorithm PROC[v0, v1: REF VertexInfo] RETURNS[REF VertexInfo] Expand patch by evaluating control point rows, then spitting out polygons columnwise ΚΠ˜head™J™2defaultšΟk ˜ Jšœ œ.˜P˜—šΟb™JšΟnœœ!œœœœœ.˜uJš‘œœ!œœœœ œ&˜x—š ™š‘ œœœ ˜7Jšœ8Ÿ˜MJ˜——š ™š‘ œœœ œœ œ*œœœ˜ŸLšœœ;˜ELšœœ!Ÿ˜Wšœœœœ˜*Lšœ˜Lšœ œ˜šœ ˜ LšœC˜GLšœ$˜(—L˜L˜L˜Lšœ˜—Lšœ6œ˜R˜L˜Lšœ7˜:L˜—L˜—š‘ œœœ œœ œ-œ ˜‰Lšœœ;˜EJšœ œ4˜@šœ œ˜š œœœœœœ˜>O˜WLšœ˜—š œ œœœœœ˜DO˜^O˜-Lšœ˜—OšœœA˜R—˜L˜#Lšœ7˜:L˜—L˜Lšœ œœ œ˜)Lš œœœœ œœœ ˜B—š‘œ œ œœ œœœ ˜{LšŸ1™1Lšœ œ˜Lšœœ;˜ELšœ œœ˜6Lšœœœ%˜ALšœ œœ,˜KLšœ œ!˜0Lšœœ˜Lšœ œ˜š‘œœ˜šœœ˜Lšœœ˜L˜%L˜3šœ˜Lšœœ8˜C—š œœœœŸ˜ELšœœ4˜>šœœ˜šœ˜Lšœœ ˜$Lšœ/Ÿ"˜QLšœ&Ÿ˜Lšœ˜—Lšœ˜—L˜ š œœœœŸ-˜Sšœœœ˜L˜(L˜&L˜L˜L˜—Lšœ˜—Lšœ œ8˜DLšœ œ;˜Iš œœœœŸ+˜LL˜L˜Lšœ˜—Lšœ œ˜L˜š œœœœŸ˜Ešœœœ˜'L˜3Lšœ˜—Lšœ˜—L˜—L˜0L˜—š ‘ œ œ œ!œœœ˜vJšœ œ2˜?Pšœ œ>˜KLšœ œœ˜˜KJšœœ6˜@Lšœ œ˜Pšœ œœ˜6š œœœ œœ˜Dšœœœ˜-Pšœ œ˜Pšœ˜—Pšœ˜—š œœœœŸ˜:šœœœ˜P˜L˜L˜—Pšœ˜—P˜Jšœ ˜P˜—š ‘œ œ œœ œ%œ˜tJšœœ;˜EL˜ L˜ L˜!š œœœœŸ!˜Yšœ˜Jšœ˜Jšœœœ˜?—šœ˜Jšœ˜Jšœœœ˜?—šœ˜Jšœ˜Jšœœœ˜?—Jšœ˜—P˜——š '™'š‘œœ œœœœ œœœ˜’š‘œœ Ÿ1˜Hšœ œŸ=˜QOšœ œ5˜Fšœœ-Ÿ˜Ošœ˜Ošœ œ˜šœœœ˜&OšœœV˜a—Ošœ œ(˜5š œœœœŸ˜<šœ œ˜Ošœœ˜-Ošœœ ˜!—Ošœ˜—O˜O˜——O˜!—šœ œŸ=˜POšœ œ6˜Fšœœ)Ÿ˜Kšœ˜Ošœœœ%˜Fš œœœœŸ˜;šœ œ˜Ošœ œ˜1Ošœœ˜&—Ošœ˜—O˜O˜——O˜—šœ œŸ=˜ROšœ œ;˜Mšœœ1Ÿ˜Sšœ˜Ošœ œ˜šœœœ˜"OšœœV˜a—Ošœ œ'˜5š œœœœŸ˜=šœœ˜Ošœœ˜1Ošœœ ˜$—Ošœ˜—O˜O˜——O˜#—P˜—Ošœœœœœœœœ˜…Oš œ œ œ$œ  œœœ˜‹Ošœœœ˜6Ošœœ˜(Ošœœ˜Ošœ œ˜Jšœ œ1˜?Ošœœ˜Ošœ œ˜!Ošœœ˜šœ˜˜ O˜ O˜"O˜—Ošœœ>˜O—O˜šœœœ˜*šœŸ˜.OšœE˜IOšœ8˜<—OšœŸ'˜=š œœœœŸ#˜LOšœœ ˜"O˜%Ošœœ˜4O˜$šœ œœ˜O˜O˜,Ošœ˜—Ošœ œ%Ÿ)˜`Ošœ Ÿ"˜BO˜O˜O˜#Jšœ œ˜$Ošœ˜Ošœ˜Ošœ˜O˜—š‘ œœœ œœœœ œœœ˜›O™FJšœœ;˜EOšœœ˜šœœœ ˜Lšœœ&œœ ˜PLšœœ ˜(Lšœœ˜$Lšœœ˜Lšœœ ˜L˜8Ošœ˜—O˜—Lšœœœœ˜,Lšœ œ˜#Ošœœ˜Ošœœ˜(Ošœœœ˜COšœ œœ&˜Jšœ œœœ ˜)O™B—Ošœ œœ;˜Tšœœœ˜6O™—˜$L™T—šœœœ˜šœœœœ˜Lšœœœœ˜:L˜3L˜2Lšœ˜—L˜VLšœ˜—L˜HLš œœœœœŸ˜VL˜šœœœ˜L˜HLš œœœœ œŸ˜VL˜šœœœ˜Jšœœœœ ˜BLšœœ˜/L˜8L˜6L˜2L˜4L˜$L˜,L˜L˜.L˜&L˜Lšœ˜—L˜ Lšœ˜ —O˜O˜"Ošœ˜O˜—š ‘œ œœ œœ˜oJ™!Jšœœ ˜Jšœœ,˜4Jšœœ!œ˜DJ˜@J˜J˜NJ˜$Jšœ ˜—š Πbn œœ œ œœ˜GJšœ œ œœ ™4Jšœœœ+˜LLš œœ œœœœ˜VJšœœœ ˜$J˜*L˜*L˜*L˜*L˜*L˜*šœ œ˜šœŸ(˜1Oš œœœœœœœ ˜DOšœœ ˜O˜—Ošœ˜—J˜Jšœ˜ J˜—š œœ œ$œœœœ˜˜Jšœœ+˜6Jšœœ,˜6Jšœœœ˜BJšœ œœ˜;Lšœœœœ˜,šœ œœœ ˜)J˜L™T—šœœœ˜šœœœœ˜Lšœœœœ˜:L˜3L˜2Lšœ˜—L˜QLšœ˜—šœœœ˜šœœ)˜3J˜*J˜—šœœœœ˜Lšœœ˜2Lšœ˜—Jšœ˜—šœœœ˜Jšœœœ Ÿ.˜XJšœœœœ ˜6Jšœœ˜+L˜J˜&J˜J˜(J˜ šœœœ˜šœœœ˜Jšœ/Ÿ+˜ZJšœ˜—Jšœ˜—Jšœ˜—O˜O˜Jšœ˜J˜—O™—Jšœ˜—…—iz‡Ά