ShapeTwiddleImpl.mesa
Last Edited by: Crow, May 3, 1989 2:35:45 pm PDT
DIRECTORY Atom, CedarProcess, G3dMatrix, G3dRender, G3dVector, Real, Rope, ShapeTwiddle;
ShapeTwiddleImpl: CEDAR PROGRAM
IMPORTS Atom, CedarProcess, G3dMatrix, G3dRender, G3dVector, Real
EXPORTS ShapeTwiddle
~ BEGIN
Types
LORA:     TYPE ~ LIST OF REF ANY;
Context:     TYPE ~ G3dRender.Context;
RGB:      TYPE ~ G3dRender.RGB;
CtlPoint:    TYPE ~ G3dRender.CtlPoint;
CtlPointSequence: TYPE ~ G3dRender.CtlPointSequence;
CtlPtInfo:    TYPE ~ G3dRender.CtlPtInfo;
CtlPtInfoProc:  TYPE ~ G3dRender.CtlPtInfoProc;
CtlPtInfoSequence: TYPE ~ G3dRender.CtlPtInfoSequence;
Triple:    TYPE ~ G3dRender.Triple;
TripleSequence: TYPE ~ G3dRender.TripleSequence;
NatSequence: TYPE ~ G3dRender.NatSequence;
PairSequence: TYPE ~ G3dRender.PairSequence;
Shape:    TYPE ~ G3dRender.Shape;
Patch:     TYPE ~ G3dRender.Patch;
PatchSequence:  TYPE ~ G3dRender.PatchSequence;
ShapeClass:   TYPE ~ G3dRender.ShapeClass;
NatPair:  TYPE ~ ShapeTwiddle.NatPair;  -- RECORD [x, y: NAT];
Renamed Procedures
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;
Utility Procedures
DiffPosns: PROC[vtx1, vtx2: CtlPoint] RETURNS[Triple] ~ {
RETURN[[vtx1.x - vtx2.x, vtx1.y - vtx2.y, vtx1.z - vtx2.z]];  -- object space
};
Shape Manipulations
ScaleShape: PUBLIC PROC [context: Context, name: Rope.ROPE, scale: REAL,
        xRatio, yRatio, zRatio: REAL ← 1.0, applyXfm: BOOLEANFALSE] ~ {
shape: Shape ← G3dRender.FindShape[ context, name ];
FOR i: NAT IN [0..shape.vertices.length) DO
OPEN shape.vertices[i];
tx, ty, tz: REAL;
IF applyXfm
THEN [ [tx, ty, tz] ] ← G3dMatrix.Transform[ [x, y, z], shape.matrix]
ELSE { tx ← x; ty ← y; tz ← z; };
x ← tx * scale * xRatio;
y ← ty * scale * yRatio;
z ← tz * scale * zRatio;
ENDLOOP;
shape.sphereExtent.radius ← shape.sphereExtent.radius * scale * MAX[xRatio, yRatio, zRatio];
};
ScaleTexture: PUBLIC PROC [context: Context, name: Rope.ROPE, scale: REAL,
        xRatio, yRatio: REAL ← 1.0] ~ {
shape: Shape ← G3dRender.FindShape[ context, name ];
FOR i: NAT IN [0..shape.vertices.length) DO
shape.vertices[i].texture.x ← shape.vertices[i].texture.x * scale * xRatio;
shape.vertices[i].texture.y ← shape.vertices[i].texture.y * scale * yRatio;
ENDLOOP;
G3dRender.RenderDataFrom[shape].patch ← NIL;
};
SortPair: TYPE ~ RECORD [vtx, next: NAT];
SortSequence: TYPE ~ RECORD[SEQUENCE length: NAT OF REF SortPair];
CleanUp: PUBLIC PROC [context: Context, name: Rope.ROPE, deSeam: BOOLEANFALSE,
  tolerance: REAL ← 0.0] ~ { 
delete excess vertices, join identical ones, etc.
currPos: NAT ← 0;
shape: Shape ← G3dRender.FindShape[ context, name ];
table: NatSequence ← NEW[ NatSequence[shape.vertices.length] ];
buckets: REF SortSequence ← NEW[SortSequence[5 * shape.vertices.length / 4]];
nextBucket: NAT ← (shape.vertices.length / 4) + 1;
newVtx: VertexSequence;
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 G3dRender.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 CtlPoint ← shape.vertex[i];
xBucket: NATMAX[
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[ CtlPointSequence[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.vertexnewVtx;
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: Context, dstName, srcName: Rope.ROPE]
RETURNS[Shape] ~ {
dstShape: Shape ← G3dRender.NewShape[dstName];
srcShape: Shape ← G3dRender.FindShape[ context, srcName ];
srcSurface: PatchSequence ← NARROW[srcShape.surface];
dstSurface: PatchSequence;
currPos: NAT ← 0;
shape: Shape ← G3dRender.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[G3dRender.CtlPointSequence[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: Context, dstName, src1, src2: Rope.ROPE]
RETURNS[Shape] ~ {
shape: Shape ← G3dRender.NewShape[dstName];
shape1: Shape ← G3dRender.FindShape[ context, src1 ];
shape2: Shape ← G3dRender.FindShape[ context, src2 ];
surface1: REF PtrPatchSequence ← NARROW[shape1.surface];
surface2: REF PtrPatchSequence ← NARROW[shape2.surface];
surface: REF PtrPatchSequence;
shape.vertex ← NEW[     -- copy vertices
G3dRender.CtlPointSequence[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: Context, dstName, srcName: Rope.ROPE,
   patchList: LIST OF NatPair]
RETURNS[Shape] ~ {
currPos: NAT ← 0;
oldShape: Shape ← G3dRender.FindShape[ context, srcName ];
shape: Shape ← 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: Context, name: Rope.ROPE]
RETURNS
[xMin, xMax, yMin, yMax, zMin, zMax: REAL] ~ {
shape: Shape ← G3dRender.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;
};
Procedures for expansion of/to polygons
ShapeDo: PROC[ context: Context, shape: Shape, fullExpand: BOOLEAN,
     limitType: ATOM, limit: REAL]
   RETURNS [Shape] ~ {
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[ CtlPointSequence[newPts.length * shape.numSurfaces] ]
ELSE IF vertex.maxLength < newPts.length + ptIndex  -- then we expand as needed
THEN {
vertex2: CtlPointSequence;
IF vertex.length * 2 > LAST[CARDINAL]
THEN SIGNAL G3dRender.Error[$Unimplemented,
          "Sequence too long (Dragon needed)"];
vertex2 ← NEW[ CtlPointSequence[vertex.length*2] ];
FOR i: NAT IN [0..vertex.length) DO     -- copy old sequence
IF vertex[i] # NIL
THEN vertex2[i] ← NEW[ CtlPoint ← vertex[i]^ ]
ELSE vertex2[i] ← NEW[ CtlPoint ];
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: 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 G3dRender.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: Shape, patch: REF PtrPatch, nPrSide: NAT]
   RETURNS [ CtlPtInfoSequence, PatchSequence];
subdivide: PROC [shape: Shape, patch: REF PtrPatch]
   RETURNS [CtlPtInfoSequence, REF PtrPatchSequence];
patch: REF PtrPatchSequence ← NARROW[ shape.surface ];
vertex: CtlPointSequence;
shade: ShadingSequence;
surface: REF PtrPatchSequence;
patchInfo: ShadingSequence ← shape.shadingClass.patchShade;
newPts: CtlPtInfoSequence;
newPatches: PatchSequence;
ptIndex, patchIndex: INT ← 0;
SELECT shape.class.type FROM
$Bezier => {
expand ← BezierParametricExpand;
subdivide ← BezierSubdivideExpand;
};
ENDCASE => SIGNAL G3dRender.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[ CtlPoint ];
vertex[i+ptIndex]^ ← newPts[i].coord;
shade[i+ptIndex] ← NEW[ G3dRender.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: Context, name: Rope.ROPE,
         limitType: ATOMNIL, limit: REAL ← 0.0]
     RETURNS [Shape] ~ {
Expands a whole shape, calling procedures supplied by the surface type
shape: Shape ← G3dRender.FindShape[ context, name ];
RETURN[ ShapeDo[ context, shape, TRUE, limitType, limit ] ];
};
ShapeSubdivide: PUBLIC PROC[ context: Context, name: Rope.ROPE,
          limitType: ATOMNIL, limit: REAL ← 0.0]
      RETURNS [Shape] ~ {
Subdivide a whole shape once, calling procedures supplied by the surface type
shape: Shape ← G3dRender.FindShape[ context, name ];
RETURN[ ShapeDo[ context, shape, FALSE, limitType, limit ] ];
};
BezierPtrPatchNormals: PROC[ shape: Shape, patch: REF PtrPatch] ~ {
Get normals at control points, given by cross product of vectors formed from adjacent control points (limited to patch bounds, of course)
GetXProd: PROC[vertex: REF G3dRender.CtlPointSequence, 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: CtlPointSequence ← shape.vertex;
shade: 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 G3dRender.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 G3dRender.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 CtlPtInfo, f0, f1, f2, f3: REAL ]
      RETURNS[vOut: REF CtlPtInfo] ~ {
shape: Shape ← NARROW[ Atom.GetPropFromList[v0.props, $Shape] ];
lerpProc: CtlPtInfoProc ← IF shape # NIL THEN shape.shadingClass.lerpVtxAux ELSE NIL;
vOut ← NEW[CtlPtInfo];
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: LORALIST[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: Shape, patch: REF PtrPatch, nPrSide: NAT]
        RETURNS [REF CtlPtInfoSequence, REF PtrPatchSequence] ~ {
vertex: REF G3dRender.CtlPointSequence ← shape.vertex;
shade: REF G3dRender.ShadingSequence ← shape.shade;
RowEval: PROC[ v0, v1, v2, v3: REF CtlPtInfo, numPts: NAT ]
   RETURNS [pt: REF CtlPtInfoSequence] ~ {
pt ← NEW[ CtlPtInfoSequence[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 CtlPtInfoSequence;
colA, colB: REF CtlPtInfoSequence;
vtxCnt, ptchCnt: NAT ← 0;
nVtces: NAT ← (nPrSide+1) * (nPrSide+1);
outVtx: REF CtlPtInfoSequence ← NEW[ CtlPtInfoSequence[nVtces] ];
outPatch: REF PtrPatchSequence ← NEW[ PtrPatchSequence[nPrSide*nPrSide] ];
ctlPtRow: ARRAY [0..4) OF REF CtlPtInfo;
Get special output type for weird things like displacement mapping
outputType: ATOMNARROW[ Atom.GetPropFromList[ patch.props, $InterimPatchType ] ];
IF outputType = NIL THEN outputType ← $ConvexPolygon;
Get normals at control points
BezierPtrPatchNormals[shape, patch];
Expand patch by evaluating control point rows, then spitting out polygons columnwise
FOR i: NAT IN [0..4) DO
FOR j: NAT IN [0..4) DO
IF ctlPtRow[j] = NIL THEN ctlPtRow[j] ← NEW[ CtlPtInfo ];
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 CtlPtInfo]
       RETURNS
[pt: REF CtlPtInfoSequence] ~ {
DeCasteljau subdivision algorithm
tempPt: REF CtlPtInfo;
pt ← NEW[ CtlPtInfoSequence[7] ]; pt.length ← 7;
pt[0] ← NEW[ CtlPtInfo ← v0^ ]; pt[6] ← NEW[ CtlPtInfo ← 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 CtlPtInfo] RETURNS[REF CtlPtInfo] ~ {
PROC[v0, v1: REF CtlPtInfo] RETURNS[REF CtlPtInfo]
shape: ShapeNARROW[ Atom.GetPropFromList[v0.props, $Shape] ];
lerpProc: CtlPtInfoProc ← IF shape # NIL THEN shape.shadingClass.lerpVtxAux ELSE NIL;
v: REF CtlPtInfo ← NEW[CtlPtInfo];
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: LORALIST[ 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: Shape, patch: REF PtrPatch]
     RETURNS [REF CtlPtInfoSequence, REF PtrPatchSequence] ~{
vertex: REF G3dRender.CtlPointSequence ←shape.vertex;
shade: REF G3dRender.ShadingSequence ← shape.shade;
outVtx: REF CtlPtInfoSequence ← NEW [ CtlPtInfoSequence [7*7] ];
outPatch: REF PtrPatchSequence ← NEW[PtrPatchSequence [4]];
row: ARRAY [0..4) OF REF CtlPtInfoSequence;
ctlPtRow: ARRAY [0..4) OF REF CtlPtInfo;
Expand patch by evaluating control point rows, then spitting out polygons columnwise
FOR i: NAT IN [0..4) DO
FOR j: NAT IN [0..4) DO
IF ctlPtRow[j] = NIL THEN ctlPtRow[j] ← NEW[ CtlPtInfo ];
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 CtlPtInfoSequence ← 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[ CtlPtInfo ← 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.