-- FILE: DelayImpl.mesa
-- Last edited by Ousterhout, October 4, 1983 4:23 pm
-- This file contains routines that figure out delays through the
-- circuit network, from when one node changes until everything
-- in the system is stable. Actually, the routines in this file just
-- compute stages (chains of transistors) that are affected, then
-- call routines in the model package to compute delays. The general
-- process is as follows:
-- When it is determined that a gate will rise or fall, and that this is
-- the worst rise or fall time seen so far for the gate, then delay
-- information has to be propagated. First, find all paths from the
-- transistor to a source of Ground or Vdd (busses and inputs are also
-- sources). Then for each source, find all paths from the other side
-- of the transistor to gates, busses, or outputs. Compute the delay
-- for each combination of source and target. If this results in a
-- new worst-case settling time for the target, repeat the process
-- recursively starting at the target. The search is depth-first, and has
-- to be in order to handle circularities cleanly.
DIRECTORY
Delay,
DPrint,
Flow,
Globals,
Hash,
IO,
Model,
Parse,
Printout,
Rope,
StagePool;
DelayImpl: CEDAR PROGRAM
IMPORTS
DPrint,
Globals,
Flow,
Hash,
IO,
Model,
Parse,
Printout,
Rope,
StagePool
EXPORTS Delay =
BEGIN
OPEN Delay, Globals;
-- Counter to keep us from looping infinitely during delay calculation:
delayCount: INT ← 0;
DelayLimit: PUBLIC INT ← 200000;
-- Counter to keep us from printing too many stage overflow messages:
stageOverflowCount: INT ← 0;
stageOverflowLimit: INT ← 10;
-- Flags telling what, if any, information to print out while calculating
-- delays:
Print: PUBLIC BOOLEAN ← FALSE;
PrintAll: PUBLIC BOOLEAN ← FALSE;
-- Threshold capacitance (in pfs) at which a node is considered to be a bus:
BusThreshold: PUBLIC REAL ← 2.0;
-- Counters used to gather statistics:
chaseVGCalls: INT ← 0;
chaseGatesCalls: INT ← 0;
chaseLoadsCalls: INT ← 0;
propagateCalls: INT ← 0;
feedbacks: INT ← 0;
-- Things that get passed between command-level routine and table
-- searching action routines:
hiTime, loTime: REAL;
chaseVG: PROC[stage: Stage] RETURNS [BOOLEAN] =
-- Stage describes the part of the stage seen so far. On entry, the
-- stage contains >= 1 entries in piece1, plus piece2Node[0] must be
-- initialized with the correct value for the first call to chaseGates.
-- The return value is TRUE if the procedure terminated normally,
-- and FALSE if it gave up because too many nodes had been searched.
-- This procedure continues searching for sources of Vdd or Ground,
-- calling itself recursively until all possible paths have been tried.
-- For each source of Vdd or Ground, chaseGates gets called.
BEGIN
p: Pointer;
f: Fet;
node, other: Node;
size: INT;
result: BOOLEAN;
{
chaseVGCalls ← chaseVGCalls + 1;
-- If we've already seen this node, return immediately.
size ← stage.piece1Size;
node ← stage.piece1Node[size-1];
IF node.inPath THEN RETURN [TRUE];
node.inPath ← TRUE;
IF Stop↑ OR (delayCount >= DelayLimit) THEN GOTO giveUp;
-- See if this node is highly capacitive (input or bus). If
-- it is, then chaseGates immediately.
IF node.bus OR node.input OR node.cap >= BusThreshold THEN
BEGIN
IF NOT node.always0 THEN
BEGIN
stage.piece2Size ← 1;
stage.rise ← TRUE;
IF NOT chaseGates[stage] THEN GOTO giveUp;
END;
IF NOT node.always1 THEN
BEGIN
stage.piece2Size ← 1;
stage.rise ← FALSE;
IF NOT chaseGates[stage] THEN GOTO giveUp;
END;
GOTO done;
END;
-- Scan all of the fets whose sources or drains connect to the
-- node, and either call chaseGates if the connect to Vdd or
-- Ground, or call this procedure recursively.
FOR p ← node.firstPointer, p.next UNTIL p = NIL DO
f ← p.fet;
-- Make sure that information can flow through this
-- transistor in the desired direction.
IF f.source = node THEN
BEGIN
other ← f.drain;
IF NOT f.flowFromDrain THEN LOOP;
END
ELSE IF f.drain = node THEN
BEGIN
other ← f.source;
IF NOT f.flowFromSource THEN LOOP;
END
ELSE LOOP;
IF f.forcedOff THEN LOOP;
IF f.firstFlow # NIL THEN IF NOT Flow.Lock[f, other] THEN LOOP;
-- Make sure that there's room in the delay stage for more info.
-- If not, it's an error (too many transistors in series).
IF size >= pieceLimit THEN
BEGIN
stageOverflowCount ← stageOverflowCount + 1;
IF f.firstFlow # NIL THEN Flow.Unlock[f, other];
IF stageOverflowCount > stageOverflowLimit THEN GOTO done;
IO.PutF[StdOut, "More than %d transistors in series, see %s.\n",
IO.int[pieceLimit], IO.rope[Printout.NodeRope[node]]];
IF stageOverflowCount = stageOverflowLimit THEN
IO.PutRope[StdOut, "No more messages of this kind will be printed....\n"];
GOTO done;
END;
-- Add more information to the delay stage.
stage.piece1Fet[size] ← f;
stage.piece1Node[size] ← other;
stage.piece1Size ← size + 1;
IF other = VddNode THEN
BEGIN
stage.piece2Size ← 1;
stage.rise ← TRUE;
result ← chaseGates[stage];
END
ELSE IF other = GroundNode THEN
BEGIN
stage.piece2Size ← 1;
stage.rise ← FALSE;
result ← chaseGates[stage];
END
ELSE result ← chaseVG[stage];
IF f.firstFlow # NIL THEN Flow.Unlock[f, other];
IF NOT result THEN GOTO giveUp;
ENDLOOP;
GOTO done;
EXITS
giveUp => BEGIN
IO.PutF[StdOut, "ChaseVG giving up at %s.\n",
IO.rope[Printout.NodeRope[node]]];
node.inPath ← FALSE;
RETURN [FALSE];
END;
done => BEGIN
node.inPath ← FALSE;
RETURN [TRUE];
END
}
END;
chaseGates: PROC[stage: Stage] RETURNS [BOOLEAN] =
-- Stage describes a partially-complete stage up to and including
-- the node from which this procedure is to continue chasing
-- gates. The return value is TRUE if the procedure terminated
-- normally, and FALSE if it gave up because too many nodes had
-- been searched. This procedure chases out gates and outputs
-- recursively, augmenting piece2 of the stage as it goes. When it
-- finds gates and outputs, it calculates delays and invokes Propagate
-- to propagate them. When this procedure is called, piece1 of the
-- stage must be complete (meaning 0 or more entries for fets and nodes).
BEGIN
p: Pointer;
f: Fet;
node, other: Node;
size: INT;
result: BOOLEAN;
{
chaseGatesCalls ← chaseGatesCalls + 1;
-- If this node is fixed in value, then return immediately: the delay
-- to here must be zero. If the node is already in the path we're
-- checking, then also return to avoid circular scans. In this case,
-- we've just discovered a static memory element (feedback). Before
-- returning, if this is a static memory element then record the delay.
-- All memory nodes found here are of the "OR" type.
size ← stage.piece2Size;
stage.piece2Fet[size-1] ← NIL; -- expected by the modelling routines.
node ← stage.piece2Node[size-1];
IF node.always0 OR node.always1 THEN RETURN [TRUE];
IF node.inPath THEN
BEGIN
feedbacks ← feedbacks + 1;
IF stage.prev.time >= DPrint.Threshold[memory] THEN
DPrint.Record[stage.prev, memory];
RETURN [TRUE];
END;
-- If this node is precharged, then there's no need to consider
-- rising transitions.
IF node.precharged AND stage.rise THEN RETURN [TRUE];
node.inPath ← TRUE;
IF Stop↑ OR (delayCount >= DelayLimit) THEN GOTO giveUp;
-- If the node is an input, then we can usually return right away
-- since its delay is fixed by the outside world. There are two
-- exceptions. If the node is also an output, then we still have to
-- calculate delays to it. Also, if this node is absolutely the only
-- entry in its stage so far, then this stage starts from the node;
-- in that case we are computing delays FROM the node, so we
-- skip the delay calculation and go on to search through transistors.
IF (stage.piece1Size # 0) OR (size # 1) THEN
BEGIN
IF node.input AND NOT node.output THEN GOTO done;
Model.Delay[stage];
IF stage.rise THEN
BEGIN
IF stage.time > node.hiTime THEN
BEGIN
node.hiTime ← stage.time;
Propagate[stage];
END;
END
ELSE IF stage.time > node.loTime THEN
BEGIN
node.loTime ← stage.time;
Propagate[stage];
END;
IF Stop↑ OR (delayCount > DelayLimit) THEN GOTO giveUp;
-- If this is a bus, then Propagate did everything that needs to be
-- done, and there's nothing left for us to do.
IF node.bus OR node.cap >= BusThreshold THEN GOTO done;
END;
-- Now go through all the fets that connect to this node. For each
-- non-load transistor, keep chasing gates on the other side, unless
-- the other side is an input or we're going the wrong way through
-- a transistor.
FOR p ← node.firstPointer, p.next UNTIL p = NIL DO
f ← p.fet;
IF f.forcedOff THEN LOOP;
IF f.source = node THEN
BEGIN
other ← f.drain;
IF NOT f.flowFromSource THEN LOOP;
END
ELSE IF f.drain = node THEN
BEGIN
other ← f.source;
IF NOT f.flowFromDrain THEN LOOP;
END
ELSE LOOP;
IF other.always1 OR other.always0 THEN LOOP;
IF f.firstFlow # NIL THEN IF NOT Flow.Lock[f, node] THEN LOOP;
-- Make sure that there's enough space in the stage for more
-- info. If not, then it's an error (too many transistors in series).
IF size >= pieceLimit THEN
BEGIN
IF f.firstFlow # NIL THEN Flow.Unlock[f, node];
stageOverflowCount ← stageOverflowCount + 1;
IF stageOverflowCount > stageOverflowLimit THEN GOTO done;
IO.PutF[StdOut, "More than %d transistors in series, see %s.\n",
IO.int[pieceLimit], IO.rope[Printout.NodeRope[node]]];
IF stageOverflowCount = stageOverflowLimit THEN
IO.PutRope[StdOut, "No more messages of this kind will be printed....\n"];
GOTO done;
END;
stage.piece2Fet[size-1] ← f;
stage.piece2Node[size] ← other;
stage.piece2Size ← size + 1;
result ← chaseGates[stage];
IF f.firstFlow # NIL THEN Flow.Unlock[f, node];
IF NOT result THEN GOTO giveUp;
ENDLOOP;
GOTO done;
EXITS
giveUp => BEGIN
IO.PutF[StdOut, "ChaseGates giving up at %s.\n",
IO.rope[Printout.NodeRope[node]]];
node.inPath ← FALSE;
RETURN [FALSE];
END;
done => BEGIN
node.inPath ← FALSE;
RETURN [TRUE];
END
}
END;
chaseLoads: PROC[node: Node, stage: Stage] =
-- This procedure is used to chase out loads that can drive
-- a stage when a transistor turns off. Node tells where to
-- start searching for loads, and stage is used when (if) a
-- load is found to record stage information. This procedure
-- searches out recursively from node to find all the loads
-- that can legally be reached from it. For each load found,
-- the stage is set up and chaseGates is processed to look for
-- things the load can drive.
-- Design note: when a given transistor turns off, we don't
-- find every possible load that is connected to the turned-off
-- fet though transistor channels (that might involve expensive
-- searches through pass transistor arrays). Instead, we only
-- look for loads that can be driven by the turned-off fet. This
-- will handle the common case of loads that are part of gates,
-- but might not handle other cases. Caveat emptor!
BEGIN
p: Pointer;
f: Fet;
other: Node;
chaseLoadsCalls ← chaseLoadsCalls + 1;
-- Make sure that we're not looping circularly. A circularity here
-- corresponds to an "AND" type of memory node: when this happens,
-- call the delay recorder.
IF node.always1 OR node.always0 THEN RETURN;
IF node.inPath THEN
BEGIN
feedbacks ← feedbacks + 1;
IF stage.prev.time >= DPrint.Threshold[memory] THEN
DPrint.Record[stage.prev, memory];
RETURN;
END;
-- See if this node has any loads attached to it. If so, then chase gates
-- from the load and return. A load is defined as a transistor that is
-- always on and connects to a node that is forced to a particular value.
FOR p ← node.firstPointer, p.next UNTIL p = NIL DO
f ← p.fet;
IF NOT (f.forcedOn OR f.onAlways) THEN LOOP;
IF f.source = node THEN
BEGIN
other ← f.drain;
IF NOT f.flowFromDrain THEN LOOP;
END
ELSE IF f.drain = node THEN
BEGIN
other ← f.source;
IF NOT f.flowFromSource THEN LOOP;
END
ELSE LOOP;
IF other.always1 THEN stage.rise ← TRUE
ELSE IF other.always0 THEN stage.rise ← FALSE
ELSE LOOP;
IF f.firstFlow # NIL THEN IF NOT Flow.Lock[f, other] THEN LOOP;
stage.piece1Size ← 0;
stage.piece2Size ← 2;
stage.piece2Node[0] ← other;
stage.piece2Node[1] ← node;
stage.piece2Fet[0] ← f;
[] ← chaseGates[stage];
IF f.firstFlow # NIL THEN Flow.Unlock[f, other];
RETURN;
ENDLOOP;
-- This node doesn't have any loads. In this case, continue
-- working outwards, looking recursively for loads. Note: the
-- inPath flag doesn't get set until here, because it must be
-- UNSET when we call chaseGates above (chaseGates will set
-- the flag for itself).
node.inPath ← TRUE;
FOR p ← node.firstPointer, p.next UNTIL p = NIL DO
f ← p.fet;
IF f.forcedOff THEN LOOP;
IF f.source = node THEN
BEGIN
other ← f.drain;
IF NOT f.flowFromSource THEN LOOP;
END
ELSE IF f.drain = node THEN
BEGIN
other ← f.source;
IF NOT f.flowFromDrain THEN LOOP;
END
ELSE LOOP;
IF f.firstFlow # NIL THEN
BEGIN
IF Flow.Lock[f, node] THEN
BEGIN
chaseLoads[other, stage];
Flow.Unlock[f, node];
END;
END
ELSE chaseLoads[other, stage];
ENDLOOP;
node.inPath ← FALSE;
RETURN;
END;
Propagate: PUBLIC PROC[prevStage: Stage] =
BEGIN
p: Pointer;
f: Fet;
node: Node;
stage: Stage;
result: BOOLEAN;
oldInPath: BOOLEAN;
propagateCalls ← propagateCalls + 1;
-- Quit if too many delays have been calculated. This probably means
-- that nodes aren't marked properly (user error), or else Crystal is messing
-- up.
delayCount ← delayCount + 1;
IF Stop↑ OR (delayCount >= DelayLimit) THEN
BEGIN
IF delayCount = DelayLimit THEN
BEGIN
IO.PutF[StdOut, "Aborting delay analysis: no solution after %d stages.\n",
IO.int[DelayLimit]];
IO.PutRope[StdOut, "Perhaps you forgot to mark some of the flow in"];
IO.PutRope[StdOut, " pass transistors?\n The information below may point"];
IO.PutRope[StdOut, " out the trouble spot.\n"];
END;
RETURN;
END;
node ← prevStage.piece2Node[prevStage.piece2Size - 1];
IF PrintAll OR (Print AND
((Rope.Fetch[node.name, 0] < '0) OR Rope.Fetch[node.name, 0] > '9)) THEN
IO.PutF[StdOut, "Delay at %s set to %6.1fns up, %6.1fns down.\n",
IO.rope[Printout.NodeRope[node]],
IO.real[node.hiTime], IO.real[node.loTime]];
-- Record delay information for posterity.
IF prevStage.time >= DPrint.Threshold[any] THEN
DPrint.Record[prevStage, any];
IF node.dynamic AND (prevStage.time >= DPrint.Threshold[memory]) THEN
DPrint.Record[prevStage, memory];
IF node.watched AND (prevStage.time >= DPrint.Threshold[watched]) THEN
DPrint.Record[prevStage, watched];
stage ← StagePool.New[];
stage.prev ← prevStage;
-- If this node is an input or bus, then call chaseGates immediately.
-- An empty piece1 is used to indicate the input status to the device
-- modellers.
IF node.input OR node.bus OR node.cap >= BusThreshold THEN
BEGIN
stage.piece1Size ← 0;
stage.piece2Size ← 1;
stage.piece2Node[0] ← node;
stage.rise ← prevStage.rise;
-- Be sure to clear the inPath flag here. This is necessary because when
-- this procedure is called from chaseGates with a bus, because the bus
-- is both the destination of one stage and the trigger of another. On the
-- other hand, be sure to restore the inPath flag before continuing in the
-- procedure.
oldInPath ← node.inPath;
node.inPath ← FALSE;
result ← chaseGates[stage];
node.inPath ← oldInPath;
IF NOT result THEN
BEGIN
StagePool.Free[stage];
RETURN;
END;
END;
-- Scan through all of the fets connecting to this node.
FOR p ← node.firstPointer, p.next UNTIL p = NIL DO
f ← p.fet;
IF f.gate # node THEN LOOP;
IF f.onAlways OR f.forcedOn OR f.forcedOff THEN LOOP;
-- If the signal change could potentially turn the transistor
-- on, then look first at the source side, then at the drain side.
-- For each side, if info could flow from that side then call
-- chaseVG to find the source. If the side connects directly
-- to a supply rail, then bypass the call to chaseVG and go
-- straight to chaseGates (this is a performance optimization and
-- isn't strictly necessary).
IF (prevStage.rise AND NOT f.on0)
OR ((NOT prevStage.rise) AND NOT f.on1) THEN
BEGIN
IF f.flowFromSource THEN
BEGIN
IF f.firstFlow # NIL THEN IF NOT Flow.Lock[f, f.source]
THEN GOTO skipSource;
stage.piece1Size ← 1;
stage.piece1Fet[0] ← f;
stage.piece1Node[0] ← f.source;
stage.piece2Size ← 1;
stage.piece2Node[0] ← f.drain;
IF f.source = GroundNode THEN
BEGIN
stage.rise ← FALSE;
result ← chaseGates[stage];
END
ELSE IF f.source = VddNode THEN
BEGIN
stage.rise ← TRUE;
result ← chaseGates[stage];
END
ELSE result ← chaseVG[stage];
IF f.firstFlow # NIL THEN Flow.Unlock[f, f.source];
IF NOT result THEN
BEGIN
StagePool.Free[stage];
RETURN;
END;
EXITS skipSource => NULL;
END;
IF f.flowFromDrain THEN
BEGIN
IF f.firstFlow # NIL THEN IF NOT Flow.Lock[f, f.drain]
THEN GOTO skipDrain;
stage.piece1Size ← 1;
stage.piece1Fet[0] ← f;
stage.piece1Node[0] ← f.drain;
stage.piece2Size ← 1;
stage.piece2Node[0] ← f.source;
IF f.drain = GroundNode THEN
BEGIN
stage.rise ← FALSE;
result ← chaseGates[stage];
END
ELSE IF f.drain = VddNode THEN
BEGIN
stage.rise ← TRUE;
result ← chaseGates[stage];
END
ELSE result ← chaseVG[stage];
IF f.firstFlow # NIL THEN Flow.Unlock[f, f.drain];
IF NOT result THEN
BEGIN
StagePool.Free[stage];
RETURN;
END;
EXITS skipDrain => NULL;
END;
END
-- This transition could only have turned the transistor off. In this
-- case, we scan out on each side of the transistor looking for a load
-- to take over now that the transistor is turned off. Be sure to mark
-- the node on the side of the transistor that we're NOT searching as
-- in the path. Otherwise, chaseLoads will consider pullup paths that
-- go back through the path we just turned off!
ELSE
BEGIN
IF f.flowFromSource THEN
BEGIN
oldInPath ← f.source.inPath;
f.source.inPath ← TRUE;
[] ← chaseLoads[f.drain, stage];
f.source.inPath ← oldInPath;
END;
IF f.flowFromDrain THEN
BEGIN
oldInPath ← f.drain.inPath;
f.drain.inPath ← TRUE;
[] ← chaseLoads[f.source, stage];
f.drain.inPath ← oldInPath;
END;
END;
ENDLOOP;
StagePool.Free[stage];
END;
DelayCmd: PUBLIC CmdProc =
BEGIN
nodeName: Rope.ROPE;
ok: BOOLEAN;
-- Parse the arguments.
IF args = NIL THEN GOTO noArgs;
nodeName ← args.rope;
args ← args.next;
IF args = NIL THEN GOTO noArgs;
[ok, hiTime] ← Parse.Real[args];
IF NOT ok THEN GOTO noArgs;
args ← args.next;
IF args = NIL THEN GOTO noArgs;
[ok, loTime] ← Parse.Real[args];
IF NOT ok THEN GOTO noArgs;
Hash.Enumerate[table: NodeTable, pattern: nodeName,
proc: delayProc, errorStream: StdOut];
EXITS noArgs =>
BEGIN
IO.PutRope[StdOut, "Delay requires three arguments:\n"];
IO.PutRope[StdOut, " node name, rise time, fall time.\n"];
END;
END;
delayProc: Hash.EnumProc =
BEGIN
node: Node ← NARROW[entry.clientData];
stage: Stage ← StagePool.New[];
stage.prev ← NIL;
stage.piece1Size ← 0;
stage.piece2Size ← 1;
stage.piece2Node[0] ← node;
stage.piece2Fet[0] ← NIL;
IF hiTime >= 0 THEN
BEGIN
stage.time ← hiTime;
stage.rise ← TRUE;
IF hiTime > node.hiTime THEN node.hiTime ← hiTime;
Propagate[stage];
END;
IF loTime >= 0 THEN
BEGIN
stage.time ← loTime;
stage.rise ← FALSE;
IF loTime > node.loTime THEN node.loTime ← loTime;
Propagate[stage];
END;
StagePool.Free[stage];
END;
Stats: PUBLIC PROC[] =
BEGIN
IO.PutF[StdOut, "Number of calls to chase Vdd or GND: %d.\n",
IO.int[chaseVGCalls]];
IO.PutF[StdOut, "Number of calls to chase gates: %d.\n",
IO.int[chaseGatesCalls]];
IO.PutF[StdOut, "Number of calls to chase loads: %d.\n",
IO.int[chaseLoadsCalls]];
IO.PutF[StdOut, "Number of calls to propagate delays: %d.\n",
IO.int[propagateCalls]];
IO.PutF[StdOut, "Number of delay feedback paths: %d.\n",
IO.int[feedbacks]];
END;
END.