<> <> <> DIRECTORY BIC, BitOps, CoreClasses, CoreCreate, CoreIO, CoreFlat, CoreProperties, IO, Ports, Rope, Rosemary, TerminalIO; BICImpl: CEDAR PROGRAM IMPORTS BitOps, CoreClasses, CoreCreate, CoreIO, CoreFlat, CoreProperties, IO, Ports, Rosemary, TerminalIO EXPORTS BIC = BEGIN OPEN CoreCreate; BICName: ROPE = Rosemary.Register[roseClassName: "BIC", init: BICInit, evalSimple: BICSimple, scheduleIfClockEval: TRUE]; InitializeTester: PUBLIC PROC [tester: CellType] = { Ports.InitTesterDrives[tester, drive, "nEClock", "Clock", "ChipCKIn", "ExtCKIn", "ChipCKOut", "ExtCKOut", "LocCKOut", "nDInB", "nBInB"]; Ports.InitTesterDrives[tester, expect, "nRqOutB", "nDOutB", "nBOutB", "nOrOutB"]; Ports.InitTesterDrives[tester, drive, "DInH", "BInH", "RqIn", "OrInH", "nSStop", "DOEn", "Name", "DBusIn", "Send"]; Ports.InitTesterDrives[tester, expect, "DOutH", "BOutH", "DBusOut", "DCS"]; [] _ Rosemary.SetFixedWire[FindWire[tester.public, "Vdd"], H]; [] _ Rosemary.SetFixedWire[FindWire[tester.public, "CKRecAdj"], H]; [] _ Rosemary.SetFixedWire[FindWire[tester.public, "RecAdj"], H]; [] _ Rosemary.SetFixedWire[FindWire[tester.public, "Gnd"], L]; [] _ Rosemary.SetFixedWire[FindWire[tester.public, "Gnd2V"], L]; }; DecorateCT: PROC [ct: CellType, v: NAT _ 0] = { CoreProperties.PutCellTypeProp[ct, $VersionNumber, NEW[NAT _ v]]; [] _ Rosemary.BindCellType[cellType: ct, roseClassName: BICName]; [] _ CoreFlat.CellTypeCutLabels[ct, "BIC"]; <<-- new syntax>> Ports.SetPorts[ct.public, LIST["Vdd", "CKRecAdj", "RecAdj", "Gnd", "Gnd2V", "nEClock", "Clock", "ChipCKIn", "ExtCKIn", "ChipCKOut", "ExtCKOut", "LocCKOut", "nDInB", "nBInB", "DInH", "BInH", "RqIn", "OrInH", "DOutH", "BOutH", "nSStop", "DOEn", "Name", "DBusIn", "Send", "DBusOut", "DCS"], ls]; Ports.SetPorts[ct.public, LIST["nRqOutB", "nDOutB", "nBOutB", "nOrOutB"], ls, separate]; }; CreateBIC: PUBLIC PROC [fromFile: BOOL _ FALSE, v: NAT _ 0] RETURNS [ct: CellType ] = { IF fromFile THEN ct _ CoreIO.RestoreCellType["BIC", NIL] ELSE { <<-- this public conforms to BICForSim.icon in BIC.dale>> public: Wire _ WireList[LIST[ <<-- power>> "Vdd", "Gnd", "Gnd2V", "CKRecAdj", "RecAdj", <<-- clocks>> "nEClock", "Clock", "ChipCKIn", "ExtCKIn", "ChipCKOut", "ExtCKOut", "LocCKOut", <<-- board side>> Seq["nDInB", 3], Seq["nBInB", 24], Seq["nRqOutB", 2], Seq["nDOutB", 3], Seq["nBOutB", 24], "nOrOutB", <<-- hybrid side>> Seq["DInH", 3], Seq["BInH", 24], Seq["RqIn", 2], Seq["OrInH", 4], Seq["DOutH", 3], Seq["BOutH", 24], <<-- DBus et al.>> "nSStop", "DOEn", Seq["Name", 3], Seq["DBusIn", 7], Seq["Send", 4], "DBusOut", Seq["DCS", 3] ]]; ct _ CoreClasses.CreateUnspecified[public, BICName]; }; CoreProperties.PutCellTypeProp[ct, $VersionNumber, NEW[NAT _ v]]; [] _ Rosemary.BindCellType[cellType: ct, roseClassName: BICName]; [] _ CoreFlat.CellTypeCutLabels[ct, "BIC"]; <<-- new syntax>> Ports.SetPorts[ct.public, LIST["Vdd", "CKRecAdj", "RecAdj", "Gnd", "Gnd2V", "nEClock", "Clock", "ChipCKIn", "ExtCKIn", "ChipCKOut", "ExtCKOut", "LocCKOut", "nDInB", "nBInB", "DInH", "BInH", "RqIn", "OrInH", "DOutH", "BOutH", "nSStop", "DOEn", "Name", "DBusIn", "Send", "DBusOut", "DCS"], ls]; Ports.SetPorts[ct.public, LIST["nRqOutB", "nDOutB", "nBOutB", "nOrOutB"], ls, separate]; }; BICState: TYPE = REF BICStateRec; BICStateRec: TYPE = RECORD[ ports: BIC.BICPorts _ NIL, resetM, normalM, freezeM, shiftM, normal, freeze, shift, reset: BOOL _ FALSE, <<-- from hybrid to board>> bMaster, bSlave: CARD _ 0, -- 24 orMaster, orSlave: BOOL _ FALSE, -- 1 rqMaster, rqSlave: CARD _ 0, -- 2 <<-- from board to hybrid>> nBMaster, nBSlave: CARD _ 0, -- 24 <> nRqFMaster, nRqFSlave: CARD _ 0, -- 2 <<-- control>> r1M, r2M, er1M, f1M, f2M, s1M, s2M, s3M, e1M, e2M: BOOL _ FALSE, r1S, r2S, er1S, f1S, f2S, s1S, s2S, s3S, e1S, e2S: BOOL _ FALSE, deviceIdM, deviceIdS: CARD _ 0, -- 8 bits chipIdM, chipIdS: CARD _ 0, -- 16 bits extCkM, extCkS: CARD _ 0, -- 4 bits intCkM, intCkS: CARD _ 0, -- 4 bits grantM, grantS: BOOL _ FALSE, version: NAT _ 0 ]; BICBind: PUBLIC PROC [public: Wire, p: Ports.Port] RETURNS [bicPorts: BIC.BICPorts] ~ { bicPorts _ NEW[BIC.BICPortsRec]; {OPEN bicPorts; [Vdd, Gnd, Gnd2V, CKRecAdj, RecAdj] _ Ports.BindPorts[public, p, "Vdd", "Gnd", "Gnd2V", "CKRecAdj", "RecAdj"]; [nEClock, Clock, ChipCKIn, ExtCKIn] _ Ports.BindPorts[public, p, "nEClock", "Clock", "ChipCKIn", "ExtCKIn"]; [ChipCKOut, ExtCKOut, LocCKOut] _ Ports.BindPorts[public, p, "ChipCKOut", "ExtCKOut", "LocCKOut"]; [nDInB, nBInB] _ Ports.BindPorts[public, p, "nDInB", "nBInB"]; [nRqOutB, nDOutB, nBOutB, nOrOutB] _ Ports.BindPorts[public, p, "nRqOutB", "nDOutB", "nBOutB", "nOrOutB"]; [DInH, BInH, RqIn, OrInH] _ Ports.BindPorts[public, p, "DInH", "BInH", "RqIn", "OrInH"]; [DOutH, BOutH] _ Ports.BindPorts[public, p, "DOutH", "BOutH"]; [nSStop, DOEn, Name, DBusIn, Send] _ Ports.BindPorts[public, p, "nSStop", "DOEn", "Name", "DBusIn", "Send"]; [DBusOut, DCS] _ Ports.BindPorts[public, p, "DBusOut", "DCS"]; }; }; BICInit: Rosemary.InitProc = { state: BICState _ NEW[BICStateRec]; state.ports _ BICBind[cellType.public, p]; {OPEN state.ports; Ports.PD[ChipCKOut, drive]; Ports.PD[ExtCKOut, drive]; Ports.PD[LocCKOut, drive]; Ports.PD[DOutH, drive]; Ports.PD[BOutH, drive]; Ports.PD[DBusOut, drive]; Ports.PD[DCS, drive]; state.version _ NARROW[CoreProperties.GetCellTypeProp[cellType, $VersionNumber], REF NAT]^; }; stateAny _ state; }; debug: BOOL _ FALSE; targetVersion: INT _ 0; BtoR: PROC [b: BOOL, nameIfTrue: ROPE] RETURNS [ROPE] ~ { RETURN[IF b THEN nameIfTrue ELSE " "]; }; LtoR: PROC [l: Ports.Level] RETURNS [ROPE] ~ { RETURN[SELECT l FROM L => "L", H => "H", ENDCASE => "X"]; }; AssertionFailed: SIGNAL [message: ROPE] = CODE; BICSimple: Rosemary.EvalProc = { ShiftOneLeft: PROC [from: CARD, size: NAT, lsb: BOOL] RETURNS [CARD] ~ { RETURN[BitOps.DShift[from, 1, size]+(IF lsb THEN 1 ELSE 0)]; }; Decoder: PROC [ad: CARD, en: BOOL, s: NAT] RETURNS [sel: CARD] ~ { sel _ IF ~en THEN 0 ELSE BitOps.TwoToThe[s-1-ad] }; Assert: PROC [condition: BOOL, message: ROPE _ NIL] = {IF NOT condition THEN SIGNAL AssertionFailed[message]}; MoreThanOne: PROC [a, b, c, d: BOOL _ FALSE] RETURNS [BOOL _ FALSE] ~ { BtoN: PROC [b: BOOL] RETURNS [NAT] ~ {RETURN[IF b THEN 1 ELSE 0]}; RETURN[BtoN[a]+BtoN[b]+BtoN[c]+BtoN[d]>1]; }; MyGB: PROC [p: Ports.Port] RETURNS [v: BOOL] ~ { SELECT Ports.GL[p] FROM L, X => v _ FALSE; -- a hack; see Rick for a real fix in Ports H => v _ TRUE; ENDCASE => ERROR; }; MyGBS: PROC [p: Ports.Port, i: NAT] RETURNS [v: BOOL] ~ { SELECT Ports.GLS[p, i] FROM L, X => v _ FALSE; -- a hack; see Rick for a real fix in Ports H => v _ TRUE; ENDCASE => ERROR; }; MyGDW: PROC [p: Ports.Port] RETURNS [v: BitOps.BitDWord] ~ { size: NAT _ Ports.Size[p]; IF NOT Ports.AnyX[p] THEN RETURN[Ports.GDW[p]]; v _ 0; FOR i: NAT IN [0..size) DO bit: BOOL _ SELECT Ports.GLS[p, i] FROM H => TRUE, ENDCASE => FALSE; v _ BitOps.IBID[bit, v, i, size]; ENDLOOP; }; MyNot: PROC [from: CARD, to: Ports.Port] ~ { Ports.PDW[to, BitOps.DNOT[from, Ports.Size[to]]]; }; <<-- address on 8 bits, id = cid[3] cs[2] rs[3]>> ExplodeAddress: PROC [id: CARD] RETURNS [cid, cs, rs: CARDINAL] ~ { IF id NOT IN [0..256) THEN ERROR; cid _ BitOps.ECFD[id, 0, 3, 8]; -- 3 high-order bits: compare to Name cs _ BitOps.ECFD[id, 3, 2, 8]; -- next 2 bits: this BIC or a client circuit rs _ BitOps.ECFD[id, 5, 3, 8]; -- 3 low-order bits: scan path in BIC }; <<-- set the drive according to the value>> OpenCollector: PROC [p: Ports.Port] ~ { FOR i: NAT IN [0..Ports.Size[p]) DO SELECT Ports.GLS[p, i] FROM L, X => Ports.PDS[p, i, drive]; H => Ports.PDS[p, i, driveWeak]; ENDCASE => ERROR; ENDLOOP; }; state: BICState _ NARROW[stateAny]; csOn: BOOL; ck: Ports.Level _ X; cid, cs, rs, csOt, selScanPath: CARD _ 0; <<-- structure of selScanPath>> ReadChipID: NAT = 128; AccessDP: NAT = 64; ReadExtCK: NAT = 32; ReadIntCK: NAT = 16; WriteExtCK: NAT = 8; WriteIntCK: NAT = 4; {OPEN Ports, state, state.ports; <<>> <<-- Unclocked stuff>> [cid, cs, rs] _ ExplodeAddress[deviceIdS]; csOn _ (cid=MyGDW[Name]) AND NOT MyGBS[DBusIn, BIC.DAddress] AND MyGBS[DBusIn, BIC.HybridSel]; csOt _ Decoder[ad: cs, en: csOn, s: 4]; selScanPath _ Decoder[ad: rs, en: csOt=8, s: 8]; <<>> <<-- Clocks: we ignore Clock and ExtCKIn>> Not[nEClock, LocCKOut]; Not[nEClock, ExtCKOut]; <<-- at the Rosemary level, the delay lines are invisible>> Copy[ChipCKIn, ChipCKOut]; ck _ GL[ChipCKIn]; <<-- ck is the current clock distributed inside the chip>> <<>> <<-- Using BIC.DShiftCK as clock>> <<-- DBus address register>> SELECT MyGBS[DBusIn, BIC.DShiftCK] FROM FALSE => { SELECT TRUE FROM MyGBS[DBusIn, BIC.DAddress] => deviceIdM _ ShiftOneLeft[deviceIdS, 8, MyGBS[DBusIn, BIC.DSerialIn]]; -- shift chipID ENDCASE => NULL; }; TRUE => deviceIdS _ deviceIdM; ENDCASE => ERROR; <<>> <<-- (0) ChipID shift register>> SELECT MyGBS[DBusIn, BIC.DShiftCK] FROM FALSE => { SELECT TRUE FROM MyGBS[DBusIn, BIC.DAddress] => chipIdM _ BIC.chipID+version; -- load chipID selScanPath=ReadChipID => chipIdM _ ShiftOneLeft[chipIdS, 16, MyGBS[DBusIn, BIC.DSerialIn]]; -- shift chipID ENDCASE => NULL; }; TRUE => chipIdS _ chipIdM; ENDCASE => ERROR; <<>> <<-- (2 and 4) External clock shift register>> SELECT MyGBS[DBusIn, BIC.DShiftCK] FROM FALSE => IF selScanPath=ReadExtCK OR selScanPath=WriteExtCK THEN extCkM _ ShiftOneLeft[extCkS, 4, MyGBS[DBusIn, BIC.DSerialIn]]; -- shift extCkM TRUE => extCkS _ extCkM; ENDCASE => ERROR; <<>> <<-- (3 and 5) Internal clock shift register>> SELECT MyGBS[DBusIn, BIC.DShiftCK] FROM FALSE => IF selScanPath=ReadIntCK OR selScanPath=WriteIntCK THEN intCkM _ ShiftOneLeft[intCkS, 4, MyGBS[DBusIn, BIC.DSerialIn]]; -- shift extCkM TRUE => intCkS _ intCkM; ENDCASE => ERROR; <<-- System clock: Control of slices>> IF NOT clockEval AND ck=L THEN { -- clock is low: sample the input in all masters f4: BOOL; grantM _ MyGDW[Send]#0; -- logical OR r1M _ MyGBS[DBusIn, BIC.nDReset]; r2M _ r1S; er1M _ MyGB[nSStop]; f1M _ MyGBS[DBusIn, BIC.nDFreeze]; f2M _ f1S; s1M _ NOT(MyGBS[DBusIn, BIC.DShiftCK] AND BitOps.EBFD[selScanPath, 1, 8]); -- AccessDP s2M _ s1S; s3M _ s2S; e1M _ MyGBS[DBusIn, BIC.DExecute]; e2M _ e1S; <<-- the order of evaluation is important>> f4 _ ~(er1S AND f2S); resetM _ r2S; freezeM _ ~(r2S AND f4 AND ~(~s2S AND s3S)); shiftM _ ~(~s2S AND s3S AND ~e2S) ; normalM _ ~(resetM AND freezeM AND shiftM); -- leave as last expression! <> orMaster _ MyGDW[OrInH]#0; -- a logical or4 ; SELECT TRUE FROM normal => { bMaster _ IF grantS THEN MyGDW[BInH] ELSE 0; rqMaster _ MyGDW[RqIn]; nBMaster _ MyGDW[nBInB]; nRqFMaster _ 3; -- because of unconnected 2V receivers }; reset => { bMaster _ 0; rqMaster _ 0; nBMaster _ 0FFFFFFFFH; nRqFMaster _ 3; }; shift => { -- MyGBS[DBusIn, BIC.DSerialIn] to Normal to Request to DPShiftOut; lsb to msb <<-- chain is the chain of flops whose outputs, inverted, will become BOutH; the 2 ghost flops do not come out;>> chain: CARD _ 0; -- 26 bits bMaster _ nBSlave; rqMaster _ nRqFSlave; chain _ BitOps.ILID[bSlave, chain, 2, 24, 26]; chain _ BitOps.ICID[rqSlave, chain, 0, 2, 26]; chain _ ShiftOneLeft[chain, 26, NOT MyGBS[DBusIn, BIC.DSerialIn]]; nBMaster _ BitOps.ELFD[chain, 2, 24, 26]; nRqFMaster _ BitOps.ECFD[chain, 0, 2, 26]; }; freeze => NULL; -- all flops keep their value except [orMaster, orSlave] ENDCASE => NULL; }; IF NOT clockEval AND ck=H THEN { -- clock is high: copy masters into slaves grantS _ grantM; r1S _ r1M; r2S _ r2M; er1S _ er1M; f1S _ f1M; f2S _ f2M; s1S _ s1M; s2S _ s2M; s3S _ s3M; e1S _ e1M; e2S _ e2M; normal _ NOT normalM; freeze _ NOT freezeM; shift _ NOT shiftM; reset _ NOT resetM; bSlave _ bMaster; rqSlave _ rqMaster; orSlave _ orMaster; nBSlave _ nBMaster; nRqFSlave _ nRqFMaster; <> }; <<-- Always copy slaves to outputs>> <<>> <<-- 2V outputs (remember to modify to express the wired or: value=0, drive changes)>> IF MyGB[DOEn] THEN Not[DInH, nDOutB] ELSE Set[nDOutB, H]; MyNot[bSlave, nBOutB]; PB[nOrOutB, ~ orSlave]; MyNot[rqSlave, nRqOutB]; <<-- 5V outputs>> Not[nDInB, DOutH]; MyNot[nBSlave, BOutH]; PDW[DCS, csOt MOD 8]; -- low-order three bits PB[DBusOut, SELECT selScanPath FROM 0 => FALSE, -- RAB of the value; port is tristate ReadChipID => BitOps.EBFD[chipIdS, 0, 16], -- ChipID AccessDP => NOT orSlave, -- DPShiftOut ReadExtCK => BitOps.EBFD[extCkS, 0, 4], -- ExtCkDelay ReadIntCK => BitOps.EBFD[intCkS, 0, 4], -- IntCkDelay WriteExtCK => BitOps.EBFD[extCkS, 0, 4], -- ExtDelayState WriteIntCK => BitOps.EBFD[intCkS, 0, 4], -- IntDelayState ENDCASE => ERROR ]; IF selScanPath=0 THEN PD[DBusOut, none]; -- tristate OpenCollector[nBOutB]; OpenCollector[nOrOutB]; OpenCollector[nRqOutB]; OpenCollector[nDOutB]; IF debug AND state.version=targetVersion THEN { TerminalIO.PutF["CK=%g %g ", IO.rope[LtoR[ck]], IO.rope[BtoR[clockEval, "clockEval"]]]; TerminalIO.PutF["mode= %g %g %g %g ", IO.rope[BtoR[normal, "normal"]], IO.rope[BtoR[reset, "reset"]], IO.rope[BtoR[shift, "shift"]], IO.rope[BtoR[freeze, "freeze"]]]; TerminalIO.PutF["\n"]; }; }}; END.