DIRECTORY BitOps, CDEnvironment, CDProperties, CDSequencer, Core, CoreClasses, CoreCreate, CoreFlat, CoreOps, CoreProperties, FileNames, FileViewerOps, FS, HashTable, IO, Logic, LogicUtils, Ports, Rope, RopeList, Rosemary, RosemaryUser, SinixOps, Sisyph, Static; LogicRosemaryImpl: CEDAR PROGRAM IMPORTS BitOps, CDEnvironment, CDProperties, CDSequencer, CoreClasses, CoreCreate, CoreFlat, CoreOps, CoreProperties, FileNames, FileViewerOps, FS, HashTable, IO, LogicUtils, Ports, Rope, RopeList, Rosemary, RosemaryUser, SinixOps, Sisyph, Static EXPORTS LogicUtils, Logic = BEGIN OPEN LogicUtils, CoreCreate; oracleBindings: HashTable.Table _ HashTable.Create[equal: HashTable.RopeEqual, hash: HashTable.HashRope]; SetOracleFileName: PUBLIC PROC [id, fileName: ROPE] ~ { [] _ HashTable.Store[oracleBindings, id, fileName]; }; GetOracleFileName: PUBLIC PROC [id: ROPE] RETURNS [fileName: ROPE]~ { ref: REF _ HashTable.Fetch[oracleBindings, id].value; RETURN[IF ref=NIL THEN id ELSE NARROW[ref]]; }; OracleName: IO.ROPE = Rosemary.Register[roseClassName: "Oracle", init: OracleInit, evalSimple: OracleSimple]; Oracle: PUBLIC PROC [in, out, name: ROPE, log: BOOL _ FALSE] RETURNS [ct: CellType] = { WireFromRope: PROC [descr, name: ROPE, driveLevel: Ports.Drive] RETURNS [wire: Wire] = { s: IO.STREAM = IO.RIS[IO.PutFR["(%s)", IO.rope[descr]]]; ref: REF ANY = IO.GetRefAny[s]; IO.Close[s]; wire _ WireFromRef[ref, driveLevel]; IF name#NIL THEN wire _ CoreOps.SetShortWireName[wire, name]; }; WireFromRef: PROC [ref: REF, driveLevel: Ports.Drive] RETURNS [wire: Wire] = { WireListFromRefList: PROC [lora: LIST OF REF ANY] RETURNS [wl: LIST OF WR] = { wl _ IF lora=NIL THEN NIL ELSE CONS[WireFromRef[lora.first, driveLevel], WireListFromRefList[lora.rest]]; }; WITH ref SELECT FROM refSize: REF INT => { size: INT = refSize^; wire _ CoreCreate.Seq[size: size]; IF size=0 THEN [] _ Ports.InitPort[wire: wire, levelType: l, driveType: aggregate, initDrive: driveLevel] ELSE [] _ Ports.InitPort[wire: wire, levelType: ls, driveType: seperate, initDrive: driveLevel]; CoreProperties.PutWireProp[wire, oracleValueProp, oracleValueProp]; --non-NIL }; lora: LIST OF REF ANY => wire _ CoreCreate.WireList[wrs: WireListFromRefList[lora]]; -- no l or ls ENDCASE => ERROR; }; inWire, outWire: Wire; IF out=NIL OR in=NIL OR name=NIL THEN Error["Missing parameter on oracle"]; inWire _ WireFromRope[in, "In", none]; -- also sets the ports outWire _ WireFromRope[out, "Out", force]; -- also sets the ports ct _ CoreClasses.CreateUnspecified[name: OracleName, public: Wires["CK", inWire, outWire]]; CoreProperties.PutCellTypeProp[ct, $oracle, name]; CoreProperties.PutCellTypeProp[ct, $log, NEW[BOOL _ log]]; [] _ Rosemary.BindCellType[cellType: ct, roseClassName: OracleName]; [] _ CoreFlat.CellTypeCutLabels[ct, logicCutSet, bottomCutSet]; Ports.InitPorts[ct, l, none, "CK"]; }; OracleState: TYPE = REF OracleStateRec; OracleStateRec: TYPE = RECORD [ oracleName: ROPE _ NIL, -- entry in `oracleBindings' table clk, in, out: NAT _ LAST[NAT], inWire, outWire: Wire, stopAfterOneRun: BOOL _ FALSE, maxNbCycle: INT _ 0, log: BOOL, prevClk: Ports.Level _ L, sLog: IO.STREAM _ NIL, cycle: INT _ -1 ]; OracleInit: Rosemary.InitProc = { state: OracleState = NEW[OracleStateRec]; clk, in, out: NAT _ LAST[NAT]; id: ROPE _ NARROW[CoreProperties.GetCellTypeProp[cellType, $oracle]]; log: BOOL _ NARROW[CoreProperties.GetCellTypeProp[cellType, $log], REF BOOL]^; path: LIST OF ROPE = LIST [CDEnvironment.GetWorkingDirectory[]]; state.oracleName _ FileNames.FileWithSearchRules[root: GetOracleFileName[id], defaultExtension: ".oracle", requireExtension: FALSE, requireExact: TRUE, searchRules: path].fullPath; [state.clk, state.in, state.out] _ Ports.PortIndexes[cellType.public, "CK", "In", "Out"]; state.inWire _ cellType.public[state.in]; state.outWire _ cellType.public[state.out]; [state.stopAfterOneRun, state.maxNbCycle] _ ParseFileAndDecorateWires[state.oracleName, state.inWire, state.outWire]; state.log _ log; state.prevClk _ L; IF log THEN state.sLog _ FS.StreamOpen[IO.PutFR["///Temp/%g.bugs", IO.rope[id]], $create]; state.cycle _ -1; stateAny _ state; }; Disagreement: SIGNAL [shouldBe, is: Ports.Level] = CODE; OracleSimple: Rosemary.EvalProc = { LogMismatch: PROC [sLog: IO.STREAM, shouldBe, is: Ports.Level, index: CARD] ~ { PortToRope: PROC [level: Ports.Level] RETURNS [r: ROPE] ~ { r _ SELECT level FROM L => "L", H => "H", X => "X", ENDCASE => ERROR; }; IO.PutF[sLog, "At %g should have been %g but was %g\n", IO.int[index], IO.rope[PortToRope[shouldBe]], IO.rope[PortToRope[is]]]; }; Mismatch: PROC [oracleName: ROPE, shouldBe, is: Ports.Level, index: CARD] ~ { IF state.log THEN LogMismatch[state.sLog, shouldBe, is, index] ELSE {PointAt[oracleName, index]; Disagreement[shouldBe, is]}; }; Compare: PROC [wire: Wire, cycle: CARD, p: Ports.Port] ~ { CompareLevel: PROC [shouldBe, is: Ports.Level, index: CARD] ~ { IF shouldBe#X AND shouldBe#is THEN Mismatch[state.oracleName, shouldBe, is, index]; }; CompareLS: PROC [shouldBe, is: Ports.LevelSequence, index: CARD] ~ { FOR i: NAT IN [0..shouldBe.size) DO CompareLevel[shouldBe[i], is[i], index] ENDLOOP; }; ref: REF _ CoreProperties.GetWireProp[wire, oracleValueProp]; IF ref=NIL THEN FOR i: NAT IN [0..wire.size) DO Compare[wire[i], cycle, p[i]] ENDLOOP ELSE { values: Values _ NARROW[ref]; IF wire.size=0 THEN CompareLevel[values[cycle].ls[0], p.l, values[cycle].filePosition] ELSE CompareLS[values[cycle].ls, p.ls, values[cycle].filePosition]; }; }; SetPort: PROC [wire: Wire, cycle: NAT, p: Ports.Port] ~ { ref: REF _ CoreProperties.GetWireProp[wire, oracleValueProp]; IF ref=NIL THEN FOR i: NAT IN [0..wire.size) DO SetPort[wire[i], cycle, p[i]] ENDLOOP ELSE { values: Values _ NARROW[ref]; IF wire.size=0 THEN { -- special case for atomic p.l _ values[cycle].ls[0]; p.d _ IF p.l=X THEN none ELSE drive; } ELSE { Ports.CopyLS[from: values[cycle].ls, to: p.ls]; FOR i: NAT IN [0..p.ls.size) DO p.ds[i] _ IF p.ls[i]=X THEN none ELSE drive; ENDLOOP; }; }; }; state: OracleState _ NARROW[stateAny]; curClk: Ports.Level = p[state.clk].l; IF state.prevClk=L AND curClk=H THEN { -- up-going transition state.cycle _ (state.cycle+1) MOD state.maxNbCycle; }; IF state.cycle=-1 THEN RETURN; FOR i: NAT IN [0..state.outWire.size) DO SetPort[state.outWire[i], state.cycle, p[state.out][i]]; ENDLOOP; IF state.prevClk=H AND curClk=L THEN { -- down-transition: check inputs FOR i: NAT IN [0..state.inWire.size) DO Compare[state.inWire[i], state.cycle, p[state.in][i]]; ENDLOOP; IF state.cycle=state.maxNbCycle-1 THEN SELECT TRUE FROM state.log AND state.stopAfterOneRun => { IO.Close[state.sLog]; Rosemary.Stop[msg: "Oracle completed; look at ///Temp/*.bugs"]}; state.log AND ~state.stopAfterOneRun => IO.PutF[state.sLog, "Processed the file entirely at cycle %g\n", IO.int[state.cycle]]; ~state.log AND state.stopAfterOneRun => Rosemary.Stop[msg: "Oracle completed successfully"]; ENDCASE => NULL; }; IF curClk#X THEN state.prevClk _ curClk; }; PointAt: PROC [oracleName: ROPE, index: CARD] = { FileViewerOps.OpenSource[fileName: oracleName, index: index, chars: 1]; }; Bug: ERROR [msg: ROPE] = CODE; CrashAndPointTo: PROC [oracleName, msg: ROPE, index: CARD] = { PointAt[oracleName, index]; Bug[msg]; }; oracleValueProp: ATOM = $OracleValueProp; -- of type Values Values: TYPE = REF ValuesRec; ValuesRec: TYPE = RECORD[seq: SEQUENCE size: NAT OF Value]; Value: TYPE = REF ValueRec; ValueRec: TYPE = RECORD[ ls: Ports.LevelSequence _ NIL, -- if atomic wire, use ls[0] filePosition: CARD _ 0 ]; ParseFileAndDecorateWires: PROC [oracleName: ROPE, in, out: Wire] RETURNS [stopAfterOneRun: BOOL _ FALSE, numberOfCycles: NAT _ 0] ~ { Absorb: PROC [source: IO.STREAM, c: CHAR, msg: ROPE] ~ { [] _ IO.SkipWhitespace[source]; IF IO.GetChar[source] # c THEN CrashAndPointTo[oracleName, msg, IO.GetIndex[source]-1]; }; CountBars: PROC [source: IO.STREAM] RETURNS [length: NAT _ 0] ~ { DO IF IO.GetChar[source ! IO.EndOfStream => GOTO Done] = '| THEN length _ length+1; REPEAT Done => NULL; ENDLOOP; }; GetLevel: PROC [] RETURNS [level: Ports.Level] ~ { SELECT IO.GetChar[source] FROM '0 => level _ L; '1 => level _ H; 'X, 'x => level _ X; ENDCASE => CrashAndPointTo[oracleName, "Not a valid level", IO.GetIndex[source]-1]; }; GetHexDigit: PROC [] RETURNS [h: Ports.LevelSequence] ~ { h _ NEW[Ports.LevelSequenceRec[4]]; SELECT IO.PeekChar[source] FROM '( => { [] _ IO.GetChar[source]; -- absorb the '( h[0] _ GetLevel[]; h[1] _ GetLevel[]; h[2] _ GetLevel[]; h[3] _ GetLevel[]; Absorb[source, '), "Missing )"]; }; ENDCASE => { c: CHAR; SELECT c _ IO.GetChar[source] FROM IN ['0 .. '9] => Ports.LCToLS[ORD[c]-ORD['0], h]; IN ['A .. 'F] => Ports.LCToLS[ORD[c]-ORD['A]+10, h]; 'X, 'x => Ports.SetLS[h, X]; ENDCASE => CrashAndPointTo[oracleName, "not a hex digit", IO.GetIndex[source]]; }; }; IsTerminator: PROC [c: CHAR] RETURNS [BOOL] ~ { RETURN [c IN [IO.NUL .. IO.SP] OR c='|]}; GetToken: PROC [nbBits: NAT] RETURNS [ls: Ports.LevelSequence]= { digitIndex: NAT _ 100; -- we can extend on the left with 100 zeros lsSize: NAT _ MAX[nbBits, 1]; -- atomic => 0, but represented as ls ls _ NEW[Ports.LevelSequenceRec[lsSize]]; [] _ IO.SkipWhitespace[source]; IF IsTerminator[IO.PeekChar[source]] THEN CrashAndPointTo[oracleName, "not a value", IO.GetIndex[source]]; WHILE NOT IsTerminator[IO.PeekChar[source]] DO h: Ports.LevelSequence _ GetHexDigit[]; FOR i: NAT IN [0..4) DO bigValue[digitIndex+i] _ h[i]; ENDLOOP; digitIndex _ digitIndex+4; ENDLOOP; FOR i: NAT IN [0..lsSize) DO ls[i] _ bigValue[digitIndex-lsSize+i]; ENDLOOP; Ports.SetLS[bigValue, L]; -- clean-up }; ParseOneLine: PROC [cycle: NAT] ~ { values: Values; val: Value; PutValuesOnLeavesLtoR: PROC [wire: Wire, level: NAT] ~ { ref: REF _ CoreProperties.GetWireProp[wire, oracleValueProp]; IF ref#NIL THEN { values _ NARROW[ref]; val _ NEW[ValueRec _ [ ls: GetToken[nbBits: wire.size], filePosition: IO.GetIndex[source]-1]]; values[cycle] _ val; } ELSE { IF level>0 THEN Absorb[source, '(, "Missing ("]; -- get the "(" FOR i: NAT IN [0..wire.size) DO PutValuesOnLeavesLtoR[wire[i], level+1] ENDLOOP; IF level>0 THEN Absorb[source, '), "Missing )"]; -- get the ")" }; }; PutValuesOnLeavesLtoR[out, 0]; -- read left side (stimuli) Absorb[source, '|, "Missing |"]; PutValuesOnLeavesLtoR[in, 0]; -- read right side (correct answers) }; InitValueSequences: PROC [wire: Wire, nb: NAT] ~ { IF CoreProperties.GetWireProp[wire, oracleValueProp]#NIL THEN CoreProperties.PutWireProp[wire, oracleValueProp, NEW[ValuesRec[nb]]] ELSE FOR i: NAT IN [0..wire.size) DO InitValueSequences[wire[i], nb] ENDLOOP; }; source: IO.STREAM _ FS.StreamOpen[oracleName]; bigValue: Ports.LevelSequence _ NEW[Ports.LevelSequenceRec[300]]; -- for parser numberOfCycles _ CountBars[source]; Ports.SetLS[bigValue, L]; IO.SetIndex[source, 0]; -- return to beginning of test InitValueSequences[in, numberOfCycles]; InitValueSequences[out, numberOfCycles]; FOR cycle: NAT IN [0..numberOfCycles) DO ParseOneLine[cycle] ENDLOOP; [] _ IO.SkipWhitespace[source]; SELECT TRUE FROM IO.EndOf[source] => stopAfterOneRun _ FALSE; IO.PeekChar[source]='. => stopAfterOneRun _ TRUE; ENDCASE => CrashAndPointTo[oracleName, "What is this???", IO.GetIndex[source]]; }; Wave: TYPE ~ REF WaveRec; WaveRec: TYPE ~ RECORD [index: NAT _ 0, ls: Ports.LevelSequence _ NIL]; WaveFormName: ROPE = Rosemary.Register[roseClassName: "WaveForm", init: WaveFormInit, evalSimple: WaveFormSimple]; WaveForm: PUBLIC PROC [val: ROPE, freq: NAT, firstEdge: INT] RETURNS [ct: CellType] ~ { Analyze: Rope.ActionType ~ { SELECT c FROM '0, 'L => ls[index] _ L; '1, 'H => ls[index] _ H; 'X, 'x => ls[index] _ X; ENDCASE => quit _ TRUE; IF quit THEN RETURN; index _ index+1; }; wave: Wave _ NEW[WaveRec]; index: NAT _ 0; ls: Ports.LevelSequence _ NEW[Ports.LevelSequenceRec[Rope.Length[val]]]; IF Rope.Length[val]=0 THEN LogicUtils.Error["The waveform value is missing"]; IF Rope.Map[base: val, action: Analyze] THEN LogicUtils.Error["The waveform value contains illegal characters"]; ct _ CoreClasses.CreateUnspecified[ name: WaveFormName, public: CoreCreate.Wires["RosemaryLogicTime", "Out"]]; CoreProperties.PutCellTypeProp[ct, $ls, ls]; CoreProperties.PutCellTypeProp[ct, $freq, NEW[NAT _ freq]]; CoreProperties.PutCellTypeProp[ct, $firstEdge, NEW[INT _ firstEdge]]; [] _ Rosemary.BindCellType[cellType: ct, roseClassName: WaveFormName]; [] _ CoreFlat.CellTypeCutLabels[ct, logicCutSet, bottomCutSet]; Ports.InitPorts[ct, l, drive, "Out"]; Ports.InitPorts[ct, l, none, "RosemaryLogicTime"]; }; WaveState: TYPE = REF WaveStateRec; WaveStateRec: TYPE = RECORD [ out, time: NAT _ LAST[NAT], index: NAT _ 0, ls: Ports.LevelSequence, freq: NAT _ 0, counter: INT _ 0, lastTime: Ports.Level _ H]; WaveFormInit: Rosemary.InitProc = { state: WaveState _ IF oldStateAny=NIL THEN NEW[WaveStateRec] ELSE NARROW[oldStateAny]; firstEdge: INT = NARROW[CoreProperties.GetCellTypeProp[cellType, $firstEdge], REF INT]^; [state.out, state.time] _ Ports.PortIndexes[cellType.public, "Out", "RosemaryLogicTime"]; state.index _ 0; state.ls _ NARROW[CoreProperties.GetCellTypeProp[cellType, $ls]]; state.freq _ NARROW[CoreProperties.GetCellTypeProp[cellType, $freq], REF NAT]^; state.counter _ 0-state.freq-firstEdge; state.lastTime _ p[state.time].l; stateAny _ state; }; WaveFormSimple: Rosemary.EvalProc = { state: WaveState _ NARROW[stateAny]; IF state.lastTime=p[state.time].l THEN RETURN; state.counter _ state.counter+1; IF state.counter>=state.freq THEN { state.counter _ 0; state.index _ state.index+1; IF state.index>=state.ls.size THEN state.index _ 0; }; p[state.out].l _ state.ls[state.index]; state.lastTime _ p[state.time].l; }; ClockGenName: ROPE = Rosemary.Register[roseClassName: "ClockGen", init: ClockGenInit, evalSimple: ClockGenSimple]; ClockGen: PUBLIC PROC [up, dn, firstEdge: INT, initLow: BOOL] RETURNS [ct: CellType] ~ { ct _ CoreClasses.CreateUnspecified[ name: ClockGenName, public: Wires["Clock", "RosemaryLogicTime"]]; CoreProperties.PutCellTypeProp[ct, $up, NEW[INT _ up]]; CoreProperties.PutCellTypeProp[ct, $dn, NEW[INT _ dn]]; CoreProperties.PutCellTypeProp[ct, $firstEdge, NEW[INT _ firstEdge]]; CoreProperties.PutCellTypeProp[ct, $initLow, NEW[BOOL _ initLow]]; CoreProperties.PutCellTypeProp[ct, $DAUserIgnoreForSelection, $Exists]; [] _ Rosemary.BindCellType[cellType: ct, roseClassName: ClockGenName]; [] _ CoreFlat.CellTypeCutLabels[ct, logicCutSet, bottomCutSet]; Ports.InitPorts[ct, l, driveStrong, "Clock"]; Ports.InitPorts[ct, l, none, "RosemaryLogicTime"]; }; ClockState: TYPE = REF ClockStateRec; ClockStateRec: TYPE = RECORD [ ck, time: NAT _ LAST[NAT], up, dn, firstEdge: INT, initLow: BOOL, counter: INT _ 0, lastTime: Ports.Level _ H]; ClockGenInit: Rosemary.InitProc = { state: ClockState _ NEW[ClockStateRec]; {OPEN state; infinity: INT _ LAST[INT]/4; -- to avoid overflow [ck, time] _ Ports.PortIndexes[cellType.public, "Clock", "RosemaryLogicTime"]; initLow _ NARROW[CoreProperties.GetCellTypeProp[cellType, $initLow], REF BOOL]^; up _ NARROW[CoreProperties.GetCellTypeProp[cellType, $up], REF INT]^; dn _ NARROW[CoreProperties.GetCellTypeProp[cellType, $dn], REF INT]^; firstEdge _ NARROW[CoreProperties.GetCellTypeProp[cellType, $firstEdge], REF INT]^; IF up=-1 THEN up _ infinity; IF dn=-1 THEN dn _ infinity; IF firstEdge=-1 THEN firstEdge _ infinity; lastTime _ p[time].l}; stateAny _ state; }; ClockGenSimple: Rosemary.EvalProc = { state: ClockState _ NARROW[stateAny]; {OPEN state; t0, normTime: INT; state: ClockState _ NARROW[stateAny]; IF p[time].l=X THEN {p[ck].l _ state.lastTime _ L; RETURN}; -- only at the beginning IF state.lastTime=p[time].l THEN RETURN; state.counter _ state.counter+1; t0 _ IF state.initLow THEN state.firstEdge+state.up ELSE state.firstEdge; normTime _ (state.counter-t0+state.up+state.dn) MOD (state.up+state.dn); p[ck].l _ SELECT TRUE FROM state.counter IF state.initLow THEN L ELSE H, normTime< state.dn => L, ENDCASE => H; state.lastTime _ p[time].l; }}; StopName: ROPE = Rosemary.Register[roseClassName: "Stop", init: StopInit, evalSimple: StopSimple]; Stop: PUBLIC PROC [] RETURNS [ct: CellType] ~ { ct _ CoreClasses.CreateUnspecified[ name: StopName, public: Wires["ShouldBeFalse", "RosemaryLogicTime"]]; [] _ Rosemary.BindCellType[cellType: ct, roseClassName: StopName]; [] _ CoreFlat.CellTypeCutLabels[ct, logicCutSet, bottomCutSet]; Ports.InitPorts[ct, l, none, "ShouldBeFalse", "RosemaryLogicTime"]; }; StopState: TYPE = REF StopStateRec; StopStateRec: TYPE = RECORD [ in, time: NAT _ LAST[NAT], lastTime: Ports.Level _ H]; StopInit: Rosemary.InitProc = { state: StopState _ NEW[StopStateRec]; [state.in, state.time] _ Ports.PortIndexes[cellType.public, "ShouldBeFalse", "RosemaryLogicTime"]; state.lastTime _ p[state.time].l; stateAny _ state; }; StopSimple: Rosemary.EvalProc = { state: StopState _ NARROW[stateAny]; {OPEN state; IF p[in].l#L AND p[time].l#lastTime THEN Rosemary.Stop[msg: "User-defined assertion is wrong", data: p, reason: $UserDefined]; lastTime _ p[time].l; }}; RomName: ROPE = Rosemary.Register[roseClassName: "Rom", init: RomInit, evalSimple: RomSimple]; RomRep: TYPE = ARRAY [0..10) OF INT; -- a hack Rom: PROC [n, b: NAT, v: RomRep] RETURNS [ct: CellType] ~ { a: NAT _ BitOps.NBits[n]; ct _ CoreClasses.CreateUnspecified[name: RomName, public: Wires[Seq["ad", a], Seq["out", b]]]; CoreProperties.PutCellTypeProp[ct, $value, NEW[RomRep _ v]]; [] _ Rosemary.BindCellType[cellType: ct, roseClassName: RomName]; [] _ CoreFlat.CellTypeCutLabels[ct, logicCutSet, bottomCutSet]; Ports.InitPorts[ct, ls, none, "ad"]; Ports.InitPorts[ct, ls, drive, "out"]; }; RomState: TYPE = REF RomStateRec; RomStateRec: TYPE = RECORD [ ad, out: NAT _ LAST[NAT], val: ARRAY [0..10) OF Ports.LevelSequence]; RomInit: Rosemary.InitProc = { state: RomState _ NEW[RomStateRec]; val: RomRep _ NARROW[CoreProperties.GetCellTypeProp[cellType, $value], REF RomRep]^; b: NAT; [state.ad, state.out] _ Ports.PortIndexes[cellType.public, "ad", "out"]; b _ p[state.out].ls.size; FOR i: NAT IN [0..10) DO state.val[i] _ NEW[Ports.LevelSequenceRec[b]]; Ports.LCToLS[val[i], state.val[i]]; ENDLOOP; stateAny _ state; }; RomSimple: Rosemary.EvalProc = { state: RomState _ NARROW[stateAny]; IF LogicUtils.HasX[p[state.ad].ls] THEN Ports.SetLS[p[state.out].ls, X] ELSE {ad: CARD _ Ports.LSToC[p[state.ad].ls]; Ports.CopyLS[from: state.val[ad], to: p[state.out].ls] }; }; logicCutSet: PUBLIC ROPE _ "Logic"; -- for standard cells macroCutSet: PUBLIC ROPE _ "LogicMacro"; -- for composite cells (e.g. adder, counter, ...) bottomCutSet: PUBLIC ROPE _ "LogicBottom"; -- for unspecified (e.g. clock, oracle, ...) RoseProbeProp: ATOM _ $RoseProbe; -- only value: $Yes SetObjectPort: PUBLIC PROC [cx: Sisyph.Context, initType: Ports.LevelType _ b, initDrive: Ports.Drive _ none] = { Sisyph.Eval[cx, "coreProps _ CoreProperties.PutProp[coreProps, $PortData, NEW[Ports.PortDataRec _ [ type: initType, drive: initDrive]]]"]; }; SetObjectTesterDrive: PUBLIC PROC [cx: Sisyph.Context, initDrive: Ports.Drive _ none] = { Sisyph.Eval[cx, "coreProps _ CoreProperties.PutProp[coreProps, $PortTesterDrive, NEW[Ports.Drive _ initDrive]]"]; }; LogicTest: RosemaryUser.TestProc ~ { logicTime: NAT _ Ports.PortIndex[cellType.public, "RosemaryLogicTime"]; memory: BOOL _ FALSE; IF CoreProperties.GetCellTypeProp[cellType, $Memory]#NIL THEN memory _ TRUE; p[logicTime].b _ TRUE; p[logicTime].d _ drive; DO p[logicTime].b _ NOT p[logicTime].b; Eval[memory]; ENDLOOP; }; ExtractSelectedObjAndRunRosemary: PROC [comm: CDSequencer.Command] = { globalNames: Sisyph.ROPES _ Sisyph.GetGlobalNames[Sisyph.Create[comm.design]]; UnnamedOrGlobal: PROC [wire: Wire] RETURNS [BOOL] ~ { name: ROPE = CoreOps.GetShortWireName[wire]; RETURN [name=NIL OR RopeList.Memb[globalNames, name]]; }; Unconnected: PROC [wire: Wire] RETURNS [BOOL] ~ { RETURN [CoreProperties.GetWireProp[wire, Static.staticCutSetProp]#NIL]; }; NotBus: PROC [wire: Wire] RETURNS [BOOL] ~ { FOR i: NAT IN [0..wire.size) DO -- Skipped if wire is atomic IF wire.elements[i].size#0 THEN RETURN[TRUE]; ENDLOOP; RETURN [FALSE]; }; WorthGraphing: CoreOps.EachWireProc ~ { SELECT TRUE FROM UnnamedOrGlobal[wire] => RETURN [subWires: FALSE]; -- don't even consider sons Unconnected[wire] => RETURN [subWires: FALSE]; -- don't even consider sons NotBus[wire] => RETURN [subWires: TRUE]; -- will have interesting sons ENDCASE => graphWires _ CONS[NEW [CoreFlat.FlatWireRec _ [wire: wire]], graphWires]; }; AtomicsInGraph: PROC [wire: Wire] ~ { graphWires _ CONS[NEW[CoreFlat.FlatWireRec _ [flatCell: CoreFlat.rootCellType, wire: wire]], graphWires]; }; logicVdd, logicGnd: NAT; graphWires: CoreFlat.FlatWires _ NIL; root, cellType: CellType; internal: Core.WireSeq; labels: LIST OF ROPE; [root: root, cell: cellType] _ SinixOps.SelectedCellType[comm.design, Sisyph.mode]; IF root=NIL THEN RETURN; -- Extraction ended in error, message already printed IF cellType.class#CoreClasses.recordCellClass THEN Error["I can't simulate this thing"]; internal _ NARROW[cellType.data, CoreClasses.RecordCellType].internal; [] _ CoreOps.VisitWireSeq[internal, WorthGraphing]; logicVdd _ CoreOps.GetWireIndex[cellType.public, "Vdd"]; -- -1 means not found logicGnd _ CoreOps.GetWireIndex[cellType.public, "Gnd"]; IF logicVdd#-1 THEN [] _ Rosemary.SetFixedWire[cellType.public[logicVdd], H]; IF logicGnd#-1 THEN [] _ Rosemary.SetFixedWire[cellType.public[logicGnd], L]; labels _ SELECT CoreProperties.GetCellTypeProp[from: cellType, prop: $Simulation] FROM $Fast => LIST[macroCutSet, logicCutSet], -- gate and macro level $Transistors => LIST[bottomCutSet], -- transistor level, except for oracles, ... ENDCASE => LIST[logicCutSet]; -- gate level CDProperties.PutDesignProp[comm.design, $DAUserRoseDisplay, RosemaryUser.TestProcedureViewer[ cellType: cellType, testButtons: LIST["Logic Test"], name: CoreOps.GetCellTypeName[cellType], displayWires: graphWires, graphWires: graphWires, cutSet: CoreFlat.CreateCutSet[labels: labels]].display]; }; myDefaultGlobalNames: Sisyph.ROPES = LIST ["Vdd", "Gnd", "RosemaryLogicTime"]; Sisyph.defaultGlobalNames _ myDefaultGlobalNames; CDSequencer.ImplementCommand[key: $CoreRosemaryExtractSelectedObjAndRunRosemary, proc: ExtractSelectedObjAndRunRosemary, queue: doQueue]; RosemaryUser.RegisterTestProc["Logic Test", LogicTest]; END. `LogicRosemaryImpl.mesa Copyright c 1986 by Xerox Corporation. All rights reserved. Created by: Louis Monier December 30, 1986 7:40:13 pm PST Last Edited by: Louis Monier April 27, 1987 12:22:55 pm PDT Pradeep Sindhu March 27, 1987 5:11:11 pm PST McCreight March 19, 1987 1:12:54 pm PST Hoel, February 20, 1987 6:11:31 pm PST Barth, February 20, 1987 5:27:10 pm PST This package provides the basic user-interface for interactive simulation using Rosemary, and a set of primitives: clock generator, oracle, rom, ... These primitives must be used for simulation only and do not produce any layout. Oracle -- oracle name -> file name; default is oracle name=file name -- called from the interpreter by a user to bind a new file to an oracle -- called from the interpreter by a user to find out which file is bound to an oracle -- syntax accepted: in _ " 0 2 32 (0 2) 1 (2 4 (3 3))" -- 0 means atomic wire -- 8 means a byte, ... -- (w1 w2 w3) means a composite wire made of ... -- I tag the wires which will receive sequences of values -- Wrong value during the simulation -- bit-wise comparison; if L or H, check; if X, ignore -- if L or H, drive; if X, tristate (drive_none) -- put values on "out" ports for current cycle -- compare values on "in" ports for cycle n used during simulation -- Parses the file and decorates every sub-wire of "In" and "Out" with the values -- Values are coded in hex, but digits are extended to accomodate X -- Hex digits are 0, 1, 2, ..., 9, A, B, C, D, E , F, X, or (b b b b) with b=0, 1, or X -- Examples of values: 37, FFEA7B, 7AXX2, 2BAD, XXXX -- If not enough digits are specified, the value is right-justified and the msb are zero-extended -- Atomic wires are restricted to 0, 1, X -- Parser always absorbs any white space before the token -- skip white space, then get a char and check it -- a hack to get the number of vectors -- parsed value is now left-justified in bigValue -- We know at this point how many tokens to find on a line -- Get the file and find the number of vectors -- Initialize values on In and Out wires -- Parse the file Waveform generator The waveform generator provides the capability to generate irregular level sequences for schematic-level Rosemary simulations. The icon (WaveForm.icon) has 3 parameters: - val: a rope of 0's, 1's and X's specifying the sequence of levels to be affected to the output port - freq: the requency of change (default is 2, the default period of the clock generator) - firstEdge: the instant in time of the first transition (default is 1, as for the clock generator) The output wire will stay at the first element of the level sequence until firstEdge, and then will progress circularly in the sequence every freq cycles (remember that the clock generator has a period of 2!). It should be noticed that the first value will be used up to firstEdge, and then for freq cycles more. Clock Generator Ports.InitPorts[ct, l, drive, "Clock"]; Assertion Checking Rom (only for simulation; at most 10 words) Utilities -- These cutsets are used by Rosemary -- These belong in Sch, but Sch must be redone, so in the mean time... -- Wires have no memory unless the $Memory property is set to $Yes (the only recognized value). -- a wire is innocent until proven guilty -- Let's make sure we have something to simulate -- Find out which wires to display: top-level only -- Prepare the cell for simulation -- Entry goes in Sisyph Menu Κ– "cedar" style˜codešœ™Kšœ Οmœ1™K˜—Kš’6™6šŸœžœžœ˜:šŸ œžœ$žœ˜?Kšžœ žœ žœ1˜SK˜—šŸ œžœ,žœ˜DKš žœžœžœžœ)žœ˜TK˜—Kšœžœ5˜=Kšžœžœžœžœžœžœžœž˜Ušžœ˜Kšœžœ˜Kšžœ žœC˜VKšžœ?˜CKšœ˜—K˜—Kš’0™0šŸœžœžœ˜9Kšœžœ5˜=Kšžœžœžœžœžœžœžœž˜Ušžœ˜Kšœžœ˜šžœ žœ’˜1Kšœ˜Kšœžœžœžœ˜$Kšœ˜—šžœ˜Kšœ/˜/šžœžœžœž˜Kšœ žœ žœžœ˜,Kšžœ˜—K˜—Kšœ˜—K˜—Kšœžœ ˜&Kšœ%˜%šžœžœ žœ’˜=Kšœžœ˜3Kšœ˜—Kšžœžœžœ˜Kš’.™.šžœžœžœž˜(Kšœ8˜8Kšžœ˜—šžœžœ žœ’ ˜GKš’+™+šžœžœžœž˜'Kšœ6˜6Kšžœ˜—šžœ žœ˜'šžœžœž˜šœ žœž˜)Kšžœ˜Kšœ@˜@—šœ žœ˜)Kšžœ?žœ˜V—šœ žœ˜)Kšœ4˜4—Kšžœžœ˜——Kšœ˜—Kšžœ žœ˜(Kšœ˜—K˜šŸœžœžœ žœ˜1KšœG˜GK˜—K˜KšŸœžœžœžœ˜šŸœžœžœ žœ˜>Kšœ˜Kšœ ˜ K˜—K˜Kšœžœ’˜;Kšœžœžœ ˜š œ žœžœžœžœžœ˜;Kšœ™—Kšœžœžœ ˜šœ žœžœ˜Kšœžœ’˜;Kšœžœ˜Kšœ˜—K˜Kš’Q™QKš’C™CKš’W™WKš’4™4Kš’a™aKš’)™)Kš’9™9šŸœžœžœžœžœžœžœ ˜†K™2š Ÿœžœ žœžœžœžœ˜8Kšœžœ˜šžœžœžœ˜Kšœ!žœ˜8—K˜—Kš’&™&š Ÿ œžœ žœžœžœ žœ ˜Aš žœžœžœžœžœ žœ˜SKšžœ žœ˜Kšžœ˜—Kšœ˜—šŸœžœžœ˜2šžœžœž˜Kšœ˜Kšœ˜Kšœ˜Kšžœ5žœ˜S—K˜—šŸ œžœžœ˜9Kšœžœ˜#šžœžœž˜šœ˜Kšœžœ’˜+Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ ˜ Kšœ˜—šžœ˜ Kšœžœ˜šžœžœž˜"Kšžœžœžœ ˜2Kšžœžœžœ ˜5Kšœ˜Kšžœ3žœ˜O—Kšœ˜——K˜—š Ÿ œžœžœžœžœ˜/Kšžœžœžœžœžœžœžœ˜)—šŸœžœ žœžœ˜AKšœ žœ’+˜BKšœžœžœ ’%˜CKšœžœ!˜)Kšœžœ˜Kšžœžœžœ,žœ˜jšžœžœžœž˜.Kšœ'˜'šžœžœžœž˜Kšœ˜Kšžœ˜—Kšœ˜Kšžœ˜—Kš’1™1šžœžœžœ ž˜Kšœ&˜&Kšžœ˜—Kšœ’ ˜%Kšœ˜—Kš’:™:šŸ œžœ žœ˜#Kšœ˜Kšœ ˜ šŸœžœžœ˜8Kšœžœ5˜=šžœžœžœ˜Kšœ žœ˜šœžœ ˜Kšœ!˜!Kšœžœ˜&—Kšœ˜Kšœ˜—šžœ˜Kšžœ žœ"’˜?Kš žœžœžœžœ)žœ˜PKšžœ žœ"’˜?Kšœ˜—K˜—Kšœ’˜:Kšœ ˜ Kšœ’$˜BK˜—šŸœžœžœ˜2šžœ3žœžœ˜>Kšœ2žœ˜E—Kš žœžœžœžœžœ!žœ˜MK˜—Kš’.™.Kšœžœžœžœ˜.Kšœ žœ’ ˜OKšœ#˜#Kšœ˜Kšžœ’˜6Kš’(™(Kšœ'˜'Kšœ(˜(Kš’™Kš žœžœžœžœžœ˜EKšœžœ˜šžœžœž˜Kšžœ$žœ˜,Kšžœ*žœ˜1Kšžœ3žœ˜O—K˜——™body™©Mšœe™eMšœX™XMšœc™c—MšœΈ™ΈM™Kšœžœžœ ˜Kš œ žœžœ žœ žœ˜GK˜KšŸ œžœ`˜rK˜šŸœžœžœžœžœ žœžœ˜WšŸœ˜šžœž˜ Kšœ˜Kšœ˜Kšœ˜Kšžœ žœ˜—Kšžœžœžœ˜Kšœ˜K˜—Kšœ žœ ˜Kšœžœ˜Kšœžœ+˜HKšžœžœ3˜MKšžœ&žœD˜pšœ#˜#Kšœ˜Kšœ6˜6—Kšœ,˜,Kšœ*žœžœ ˜;Kšœ/žœžœ˜EKšœF˜FKšœ?˜?Kšœ%˜%Kšœ2˜2K˜K˜—Kšœ žœžœ˜#šœžœžœ˜Kšœ žœžœžœ˜Kšœžœ˜Kšœ˜Kšœžœ˜Kšœ žœ˜Kšœ˜K˜—šŸ œ˜#Kš œžœ žœžœžœžœžœ˜VKš œ žœžœ7žœžœ˜XKšœY˜YK˜Kšœ žœ0˜AKšœ žœ2žœžœ˜OKšœ'˜'Kšœ!˜!Kšœ˜Kšœ˜K˜—šŸœ˜%Kšœžœ ˜$Kšžœ žœžœ˜.Kšœ ˜ šžœžœ˜#Kšœ˜K˜Kšžœžœ˜3K˜—Kšœ'˜'Kšœ!˜!Kšœ˜——™KšŸ œžœ`˜rš Ÿœžœžœžœ žœžœ˜Xšœ#˜#Kšœ˜Kšœ-˜-—Kšœ(žœžœ˜7Kšœ(žœžœ˜7Kšœ/žœžœ˜EKšœ-žœžœ ˜BKšœG˜GKšœF˜FKšœ?˜?Kšœ'™'Kšœ-˜-Kšœ2˜2K˜—Kšœ žœžœ˜%šœžœžœ˜Kšœ žœžœžœ˜Kšœžœ˜Kšœ žœ˜Kšœ žœ˜Kšœ˜—šŸ œ˜#Kšœžœ˜'šœžœ˜ Kšœ žœžœžœ’˜1KšœN˜NKšœ žœ5žœžœ˜PKšœžœ0žœžœ˜EKšœžœ0žœžœ˜EKšœ žœ7žœžœ˜SKšžœžœ˜Kšžœžœ˜Kšžœžœ˜*Kšœ˜—Kšœ˜Kšœ˜K˜—šŸœ˜%Kšœžœ ˜%Kšœžœ˜ Kšœžœ˜Kšœžœ ˜%Kšžœ žœ žœ’˜TKšžœžœžœ˜(Kšœ ˜ Kšœžœžœžœ˜IKšœ0žœ˜Hšœ žœžœž˜Kšœ!žœžœžœ˜@Kšœ˜Kšžœ˜ —Kšœ˜Kšœ˜——™KšŸœžœT˜bšŸœžœžœžœ˜/šœ#˜#Kšœ˜Kšœ5˜5—KšœB˜BKšœ?˜?KšœC˜CK˜—Kšœ žœžœ˜#šœžœžœ˜Kšœ žœžœžœ˜Kšœ˜—šŸœ˜Kšœžœ˜%Kšœb˜bKšœ!˜!Kšœ˜Kšœ˜K˜—šŸ œ˜!Kšœžœ ˜$Kšœžœ˜ Kšžœ žœžœV˜~Kšœ˜Kšœ˜——™+KšŸœžœQ˜^Kš œžœžœ žœžœ’ ˜.šŸœžœžœ žœ˜;Kšœžœ˜šœ1˜1Kšœ,˜,—Kšœ+žœ˜