-- FILE: MarkImpl.mesa
-- Last edited by Ousterhout, August 30, 1983 11:48 am

DIRECTORY
    Flow,
    Globals,
    Hash,
    IO,
    Mark,
    Model,
    Parse,
    Printout,
    Rope;

MarkImpl: CEDAR PROGRAM
IMPORTS
    Flow,
    Globals,
    IO,
    Hash,
    Model,
    Parse,
    Printout,
    Rope
EXPORTS Mark =
BEGIN
OPEN Globals, Mark;

-- The following variables are used to pass information from
-- high-level command procedures to low-level search action
-- routines.

flag: {input, output, bus, precharged, watched};
value: REAL;
ivalue: INT;

-- The following variables are used to record statistics.

nodes0: INT ← 0;				-- number of nodes forced to zero.
nodes1: INT ← 0;				-- number of nodes forced to one.
dynamic: INT ← 0;				-- number of nodes marked dynamic.
simCount: INT ← 0;			-- counts calls to checkNode and findStrength.

-- The following flags determine whether or not we print out node
-- names whenever they get set to particular values or marked dynamic.

SeeSettings: PUBLIC BOOLEAN ← FALSE;
SeeAllSettings: PUBLIC BOOLEAN ← FALSE;
SeeDynamic: PUBLIC BOOLEAN ← FALSE;

-- The following stuff is used to cause a graceful abort in findStrength
-- when it's spending too long searching.

FSLimit: PUBLIC INT ← 1000;
fSCount: INT;


InputCmd: PUBLIC CmdProc  =
    BEGIN   
    flag ← input;
    WHILE args # NIL DO
        Hash.Enumerate[table: NodeTable, pattern: args.rope,
            proc: flagProc, errorStream: StdOut];
        args ← args.next;
        ENDLOOP;
    END;
    
OutputCmd: PUBLIC CmdProc  =
    BEGIN   
    flag ← output;
    WHILE args # NIL DO
        Hash.Enumerate[table: NodeTable, pattern: args.rope,
            proc: flagProc, errorStream: StdOut];
        args ← args.next;
        ENDLOOP;
    END;
    
BusCmd: PUBLIC CmdProc  =
    BEGIN   
    flag ← bus;
    WHILE args # NIL DO
        Hash.Enumerate[table: NodeTable, pattern: args.rope,
            proc: flagProc, errorStream: StdOut];
        args ← args.next;
        ENDLOOP;
    END;
    
PrechargedCmd: PUBLIC CmdProc  =
    BEGIN   
    flag ← precharged;
    WHILE args # NIL DO
        Hash.Enumerate[table: NodeTable, pattern: args.rope,
            proc: flagProc, errorStream: StdOut];
        args ← args.next;
        ENDLOOP;
    END;

WatchCmd: PUBLIC CmdProc =
    BEGIN
    flag ← watched;
    WHILE args # NIL DO
        Hash.Enumerate[table: NodeTable, pattern: args.rope,
            proc: flagProc, errorStream: StdOut];
        args ← args.next;
        ENDLOOP;
    END;

flagProc: Hash.EnumProc =
    BEGIN
    node: Node ← NARROW[entry.clientData];
    SELECT flag FROM
        input => node.input ← TRUE;
        output => node.output ← TRUE;
        bus => node.bus ← TRUE;
        watched => node.watched ← TRUE;
        precharged => 
            BEGIN
            node.precharged ← TRUE;
            node.bus ← TRUE;
            END;
        ENDCASE;
    END;


ResCmd: PUBLIC CmdProc =
    BEGIN
    ok: BOOLEAN;
    
    IF args = NIL THEN
        BEGIN
        IO.PutRope[StdOut, "No resistance value given.\n"];
        RETURN;
        END;
    [ok, value] ← Parse.Real[args];
    IF (NOT ok) OR (value < 0) THEN
        BEGIN
        IO.PutRope[StdOut, "Bad resistance value.\n"];
        RETURN;
        END;
    args ← args.next;
    
    WHILE args # NIL DO
        Hash.Enumerate[table: NodeTable, pattern: args.rope,
            proc: resProc, errorStream: StdOut];
        args ← args.next;
        ENDLOOP;
    END;
    
resProc: Hash.EnumProc =
    BEGIN
    node: Node ← NARROW[entry.clientData];
    node.res ← value;
    END;


CapCmd: PUBLIC CmdProc =
    BEGIN
    ok: BOOLEAN;
    
    IF args = NIL THEN
        BEGIN
        IO.PutRope[StdOut, "No capacitance value given.\n"];
        RETURN;
        END;
    [ok, value] ← Parse.Real[args];
    IF (NOT ok) OR (value < 0) THEN
        BEGIN
        IO.PutRope[StdOut, "Bad capacitance value.\n"];
        RETURN;
        END;
    args ← args.next;
    
    WHILE args # NIL DO
        Hash.Enumerate[table: NodeTable, pattern: args.rope,
            proc: capProc, errorStream: StdOut];
        args ← args.next;
        ENDLOOP;
    END;
    
capProc: Hash.EnumProc =
    BEGIN
    node: Node ← NARROW[entry.clientData];
    node.cap ← value;
    END;


SetNodeValue: PUBLIC PROC[node: Node, value: INT, propAnyway: BOOLEAN ← FALSE] =
    BEGIN
    p: Pointer;
    f: Fet;
    
    -- Make sure that there is no conflict in setting the node's
    -- value, then set the flags on the node.  If the level was
    -- already forced, then we can return immediately (this check
    -- prevents circular loops).
    
    IF value = 0 THEN
        BEGIN
        IF node.always1 THEN
            IO.PutF[StdOut, "Node forced to 1, then to 0 (0 wins): %s.\n",
                IO.rope[Printout.NodeRope[node]]];
        node.always1 ← FALSE;
        IF node.always0 AND NOT propAnyway THEN RETURN;
        node.always0 ← TRUE;
        nodes0 ← nodes0 + 1;
        END
    ELSE
        BEGIN
        IF node.always0 THEN
            IO.PutF[StdOut, "Node forced to 0, then to 1 (1 wins): %s.\n",
                IO.rope[Printout.NodeRope[node]]];
        node.always0 ← FALSE;
        IF node.always1  AND NOT propAnyway THEN RETURN;
        node.always1 ← TRUE;
        nodes1 ← nodes1 + 1;
        END;
    IF SeeAllSettings OR (SeeSettings AND
        ((Rope.Fetch[node.name, 0] < '0) OR (Rope.Fetch[node.name, 0] > '9))) THEN
        IO.PutF[StdOut, "Node %s forced to %d.\n",
            IO.rope[Printout.NodeRope[node]], IO.int[value]];
    
    -- Find all of the transistors connecting to this node, and take action
    -- (if necessary) to propagate the level setting.
    
    FOR p ← node.firstPointer,  p.next UNTIL p = NIL DO
        f ← p.fet;
        
        -- Where this node connects to sources or drains, check to
        -- see if level information will propagate to the next node over.
        
        IF (f.source = node) AND f.flowFromSource AND
            (f.onAlways OR f.forcedOn) THEN checkNode[f.drain];
        IF (f.drain = node) AND f.flowFromDrain AND
            (f.onAlways OR f.forcedOn) THEN checkNode[f.source];
        
        -- If the node connects to a transistor's gate and turns the
        -- transistor on, this may cause one of the nodes on either
        -- side to become fixed in value.  If the transistor is now
        -- turned off, then the source or drain may become fixed
        -- because of the reduced "competition" for that node.
        
        IF f.gate = node THEN
            BEGIN
            IF ((value=1) AND f.on1) OR ((value=0) AND f.on0) THEN
                f.forcedOn ← TRUE
            ELSE IF f.on1 OR f.on0 THEN f.forcedOff ← TRUE
            ELSE LOOP;
            IF f.flowFromDrain THEN checkNode[f.source];
            IF f.flowFromSource THEN checkNode[f.drain];
            END;
        ENDLOOP;
    END;
    
 
 checkNode: PROC[node: Node] =
     -- This procedure checks to see if a node is forced to a value,
     -- and sets it if necessary.  It operates in two stages.  First, it
     -- finds the strongest certain source of 0 or 1 for the node
     -- (certain sources are those connected to the node by transistors
     -- that are definitely turned on).  Then it finds the strongest
     -- possible source of the opposite value (a possible source is one
     -- connected to the node by transistors that aren't definitely
     -- turned off).  If the certain source is stronger than any possible
     -- opposition, then the node value is set.  If in the process of all
     -- this we discover that there are no transistors that can source
     -- information to the node, then the procedure is called recursively
     -- on all nodes that this node can source (this handles the case
     -- where the bottom transistor of a NAND gate turns off).
     
     BEGIN
     p: Pointer;
     f: Fet;
     other: Node;
     strength, strength2, value: INT;
     
     simCount ← simCount+1;
     
     -- Find strongest certain source of a 0 or 1.
     
     strength ← 0;
     FOR p ← node.firstPointer, p.next UNTIL p = NIL DO
         f ← p.fet;
         IF NOT (f.onAlways OR f.forcedOn) 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.always0 THEN
             BEGIN
             IF Model.TypeTable[f.type].strengthLo > strength THEN
                 BEGIN
                 value ← 0;
                 strength ← Model.TypeTable[f.type].strengthLo;
                 END; 
             END
         ELSE
             BEGIN
             IF Model.TypeTable[f.type].strengthHi > strength THEN
                 BEGIN
                 value ← 1;
                 strength ← Model.TypeTable[f.type].strengthHi;
                 END; 
             END;
         ENDLOOP;
     
     -- See if there is a potential source of the opposite signal that is
     -- at least as strong as the certain source.  If not, then it's OK to
     -- set the node's value.
     
     fSCount ← 0;
     IF strength > 0 THEN
         BEGIN
         strength2 ← findStrength[node: node, value: 1-value,
             beatThis: strength-1];
         IF strength > strength2 THEN SetNodeValue[node, value];
         END
     ELSE
     
         -- There's no certain source.  Now see if there is any possible
         -- source.  If not, mark all the transistors that flow away from
         -- this node as disconnected and call ourselves recursively to
         -- handle the nodes on the other side.
         
         IF (findStrength[node: node, value: 1, beatThis: 0] = 0) AND
             (findStrength[node: node, value: 0, beatThis: 0] = 0) THEN 
             BEGIN
             FOR p ← node.firstPointer, p.next UNTIL p=NIL DO
                 f ← p.fet;
                 IF f.source = node THEN
                     BEGIN
                     IF NOT f.flowFromSource THEN LOOP;
                     f.flowFromSource ← FALSE; 
                     checkNode[f.drain];
                     END
                 ELSE IF f.drain = node THEN
                     BEGIN
                     IF NOT f.flowFromDrain THEN LOOP;
                     f.flowFromDrain ← FALSE; 
                     checkNode[f.source];
                     END ;
                 ENDLOOP;
             END;
     END;
 

findStrength: PROC[node: Node, value: INT, beatThis: INT]
    RETURNS [INT] =
    -- This is a recursive local procedure that looks for the
    -- strongest possible source of a zero or one signal in a
    -- (potentially) connected piece of circuit.  Only sources
    -- stronger than beatThis are considered.  If a stronger
    -- source is found, it's strength is returned.  Otherwise
    -- beatThis is returned.  If a negative value is returned,
    -- it means that we looked and looked and eventually
    -- gave up without finishing all the possibilities.
    
    BEGIN
    p: Pointer;
    f: Fet;
    other: Node;
    strength, strength2: INT;
    
    simCount ← simCount+1;
    
    -- Abort gracefully if we can't finish the search with a 
    -- reasonable effort.
    
    fSCount ← fSCount + 1;
    IF fSCount >= FSLimit THEN
        BEGIN
        IO.PutF[StdOut, "Aborting simulation at %s:\n",
            IO.rope[Printout.NodeRope[node]]];
        IO.PutRope[StdOut, "    It's taking too long to find all the "];
        IO.PutRope[StdOut, "potential\n    signal sources.  You probably "];
        IO.PutRope[StdOut, "need to add more\n    flow control info.  "];
        IO.PutRope[StdOut, "A list of nodes in the\n    area follows:\n"];
        RETURN [-1];
        END;
    
    -- Use the inPath flag to avoid infinite recursion.
    
    node.inPath ← TRUE;
    
    -- Check all transistors whose sources or drains connect
    -- to this node to see if they could potnetially provide a
    -- strong enough source of the right value.  This may involve
    -- recursive calls.
    
    FOR p ← node.firstPointer, p.next UNTIL p=NIL DO
        f ← p.fet;
        IF f.forcedOff THEN LOOP;
        IF value = 0 THEN
            strength ← Model.TypeTable[f.type].strengthLo
        ELSE strength ← Model.TypeTable[f.type].strengthHi;
        IF strength <= beatThis 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 f.firstFlow # NIL THEN
            IF NOT Flow.Lock[fet: f, input: other] THEN LOOP;
        
        -- If an adjacent node is fixed in value, we know the
        -- strength right away:  it's the strength of the connecting
        -- transistor.  Otherwise we have to find the weakest
        -- transistor in the path to a driven node.  Be sure to
        -- consider only nodes driven to the right value.
        
        IF other.always1 OR other.always0 OR other.input THEN
            BEGIN
            IF value = 0 THEN
                BEGIN
                IF other.always1 THEN
                    BEGIN
                    IF f.firstFlow # NIL THEN Flow.Unlock[fet: f, input: other];
                    LOOP;
                    END;
                END
            ELSE IF other.always0 THEN
                BEGIN
                IF f.firstFlow # NIL THEN Flow.Unlock[fet: f, input: other];
                LOOP;
                END;
            END
        ELSE
            BEGIN
            IF other.inPath THEN
                BEGIN
                IF f.firstFlow # NIL THEN Flow.Unlock[fet: f, input: other];
                LOOP;
                END;
            strength2 ← findStrength[node: other, value: value, beatThis: beatThis];
            IF strength2 < 0 THEN
                BEGIN
                IO.PutF[StdOut, "    %s\n", IO.rope[Printout.NodeRope[node]]];
                node.inPath ← FALSE;
                IF f.firstFlow # NIL THEN Flow.Unlock[fet: f, input: other];
                RETURN [-1];
                END;
            IF strength2 < strength THEN strength ← strength2;
            IF f.firstFlow # NIL THEN Flow.Unlock[fet: f, input: other];
            END;
        IF strength > beatThis THEN beatThis ← strength;
        ENDLOOP;
    
    node.inPath ← FALSE;
    RETURN [beatThis];
    END;


SetCmd: PUBLIC CmdProc =
    BEGIN
    ok: BOOLEAN;
    
    IF args = NIL THEN
        BEGIN
        IO.PutRope[StdOut, "\"Set\" needs a 0/1 value and node names.\n"];
        RETURN;
        END;
    [ok, ivalue] ← Parse.Int[args];
    IF (NOT ok) OR (ivalue < 0) OR (ivalue > 1) THEN
        BEGIN
        IO.PutRope[StdOut, "Value must be 0 or 1.\n"];
        RETURN;
        END;
    args ← args.next;
    
    WHILE args # NIL DO
        Hash.Enumerate[table: NodeTable, pattern: args.rope,
            proc: setProc, errorStream: StdOut];
        args ← args.next;
        ENDLOOP;
    END;

setProc: Hash.EnumProc =
    BEGIN
    node: Node ← NARROW[entry.clientData];
    SetNodeValue[node, ivalue, TRUE];
    END;


Stats: PUBLIC PROC[] =
    BEGIN
    IO.PutF[StdOut, "Total nodes set to 0: %d.\n",
        IO.int[nodes0]];
    IO.PutF[StdOut, "Total nodes set to 1: %d.\n",
        IO.int[nodes1]];
    IO.PutF[StdOut, "Total nodes marked dynamic: %d.\n",
        IO.int[dynamic]];
    IO.PutF[StdOut, "Total number of recursive simulation calls: %d.\n",
        IO.int[simCount]];
    END;
    

MarkDynamic: PUBLIC PROC[] =
    BEGIN
    Hash.Enumerate[table: NodeTable, pattern: "*",  proc: markDynamicProc,
        errorStream: StdOut];
    END;
    
markDynamicProc: Hash.EnumProc =
    BEGIN
    p: Pointer;
    f: Fet;
    node: Node ← NARROW[entry.clientData];
    
    node.dynamic ← FALSE;
    IF node.input OR node.always0 OR node.always1 THEN RETURN;
    FOR p ← node.firstPointer, p.next UNTIL p = NIL DO
        f ← p.fet;
        IF f.source = node THEN
            BEGIN
            IF NOT f.flowFromDrain THEN LOOP;
            END
        ELSE IF f.drain = node THEN
            BEGIN
            IF NOT f.flowFromSource THEN LOOP;
            END
        ELSE LOOP;
        IF NOT f.forcedOff THEN RETURN;
        ENDLOOP;
    node.dynamic ← TRUE;
    dynamic ← dynamic + 1;
    IF SeeDynamic THEN IO.PutF[StdOut, "%s is dynamic.\n",
        IO.rope[Printout.NodeRope[node]]];
    END;
 
END.