RosemaryUserBackingImpl.mesa
Copyright Ó 1987 by Xerox Corporation. All rights reserved.
Jean-Marc Frailong December 28, 1987 9:57:44 am PST
Management of backing storage and plotting functions for RosemaryUser.
DIRECTORY Basics, Convert, Core, CoreClasses, CoreFlat, CoreOps, CoreProperties, FS, IO, List, PlotGraph, Ports, Real, RedBlackTree, RefTab, RefText, Rope, Rosemary, RosemaryUser;
RosemaryUserBackingImpl: CEDAR MONITOR
IMPORTS Basics, Convert, CoreFlat, CoreOps, CoreProperties, FS, IO, List, PlotGraph, Ports, Real, RedBlackTree, RefTab, RefText, Rope, Rosemary, RosemaryUser
EXPORTS RosemaryUser
~ BEGIN OPEN RosemaryUser;
Backup file management
Principles
Due to space & time constraints, backup file management is quite messy. The main ideas are:
- samples are kept in memory only if needed (i.e. if they are plotted). Samples are time-stamped with the MosSim step number. Relationship between `Eval time' and steps is achieved through an array in the handle that keeps track of the endpoints of each Eval. This permits to support time-logging or step-logging, as well as time-plotting or step-plotting.
NOTE: In the current version, samples are never removed from memory. This would be easy it it appears worthwile.
- two samples are always kept in memory per wire in order to allow collapsing identical values (c.f. LogData). The information is attached as data field to RoseWires and RoseInstances.
- samples on disk are chained backwards through disk pointers to accelerate recovery. Only deltas in file position and time are kept on disk, using a variable length encoding, to reduce storage. The exact format per sample is <DPos>, <DStep>, <level(s)> where
DPos = file position of sample - file position of previous sample for same object, 0 if this was the 1st sample for the object
DStep = step# for next sample - step# for this sample
level(s) = value of level, 1 per byte (this could be improved)
Both DPos and DStep are represented as 29-bit variable-length numbers (c.f. Write29Bits).
The current implementation has the following problems:
- It would be real fine to save the drive with which a wire has been driven, in order to distinguish X from Z (driven to garbage from tri-stated). Two problems for that: RoseWires that have LS attached do not carry the drive around (Rick says that can be twiddled around), and PlotGraph does not provide the capacity to display that information. The nice thing is that the cost in storage/disk is very small...
Types
Sample: TYPE = REF SampleRec;
SampleRec: TYPE = RECORD [
next: Sample ← NIL,
step: INTLAST[INT], -- MosSim step number at which this event occured
value: PACKED SEQUENCE size: CARDINAL OF Ports.Level
];
The object has the specified value in the range [sample.step..sample.next.step)
SampleList: TYPE = REF SampleListRec;
SampleListRec: TYPE ~ RECORD [
head: Sample, -- the head of the list. The tail is always LogData.current
beforeHeadPos: INT, -- the file position of the predecessor of head, <0 => no predecessor
inTable: BOOLFALSE -- used internally to RBT management, don't modify ...
];
The in-memory representation of a list of samples. The samples back in time may still be on disk, starting at beforeHeadPos. SampleLists are created only when necessary.
LogData: TYPE = REF LogDataRec;
LogDataRec: TYPE = RECORD [
lastFilePos: INT ← -1, -- the file position of the last sample written
list: SampleList ← NIL, -- if non-nil, the samples for this object are currently kept in memory
previous: Sample ← NIL, -- the previous sample
currentTime: INT ← -1, -- time of current sample
current: Sample ← NIL -- the sample currently taken, not guaranteed if time=lastUpdateTime
];
A LogData is attached to all RoseWires and to RoseInstances that require logging. The following assertions must hold:
- current.next = NIL
- current.step = value of MosSimStep at last call to Update
- current will never be modified once step of Update call > current.step
- previous is the sample that was valid just before current. It is necessary to allow collapsing curent with a previous value. previous has not yet been written to disk!
- if previous#NIL, then previous.next=current
- if list#NIL, then samples are kept in memory. Then, either list.head=previous=NIL, or previous may be reached by following next links from list.head (possibly 0 times!).
Backing store physical access -- all procs require backing store lock
LockBackingStore: ENTRY PROC [h: RoseDisplay] = {
UNTIL NOT h.psLock DO WAIT h.psWait ENDLOOP;
h.psLock ← TRUE;
};
UnlockBackingStore: ENTRY PROC [h: RoseDisplay] = {
h.psLock ← FALSE;
BROADCAST h.psWait;
};
WillWrite: PROC [handle: RoseDisplay, nBytes: NAT] ~ {
Warns of the intent of writing a certain number of bytes on file
to: REF TEXT = handle.wBuff;
IF to.maxLength-nBytes < to.length THEN FlushWBuff[handle, nBytes];
};
FlushWBuff: PROC [handle: RoseDisplay, nBytes: NAT] ~ {
Write current contents of wBuff on file & check there is room enough for nBytes
IO.PutBlock[handle.ps, handle.wBuff];
IF handle.wBuff.maxLength<nBytes THEN handle.wBuff ← RefText.New[nBytes];
handle.wBuff.length ← 0;
};
PutByte: PROC [handle: RoseDisplay, byte: BYTE] ~ INLINE {
handle.wBuff ← RefText.InlineAppendChar[handle.wBuff, VAL[byte]];
};
Write29Bits: PROC [handle: RoseDisplay, delta: INT32] ~ {
Write a 29-bits integer as 1, 2, 3 or 4 bytes according to size. This a hack to reduce the disk size of backing files...
The encoding scheme is (MSB always written first):
0XXXXXXX => delta IN [0..128)
10XXXXXX XXXXXXXX => delta IN [0..16384)
110XXXXX XXXXXXXX XXXXXXXX => delta IN [0..2097152)
111XXXXX XXXXXXXX XXXXXXXX XXXXXXXX => delta IN [0..536870912)
byte: CARD32 = 256;
limit1: CARD32 = 080H;
limit2: CARD32 = 040H*byte;
limit3: CARD32 = 020H*byte*byte;
limit4: CARD32 = 020H*byte*byte*byte;
v: Basics.LongNumber;
v.li ← delta;
SELECT v.lc FROM
<limit1 => { -- write single byte
IF Basics.BITAND[v.lo, 00080H]#0 THEN ERROR;
PutByte[handle, v.ll];
handle.filePos ← handle.filePos+1;
};
<limit2 => { -- write 2 bytes
IF Basics.BITAND[v.lo, 0C000H]#0 THEN ERROR;
v.lo ← Basics.BITOR[v.lo, 08000H];
IF Basics.BITAND[v.lo, 0C000H]#08000H THEN ERROR;
PutByte[handle, v.lh];
PutByte[handle, v.ll];
handle.filePos ← handle.filePos+2;
};
<limit3 => { -- write 3 bytes
IF Basics.BITAND[v.hi, 000E0H]#0 THEN ERROR;
v.hi ← Basics.BITOR[v.hi, 000C0H];
IF Basics.BITAND[v.hi, 000E0H]#000C0H THEN ERROR;
PutByte[handle, v.hl];
PutByte[handle, v.lh];
PutByte[handle, v.ll];
handle.filePos ← handle.filePos+3;
};
<limit4 => { -- write 4 bytes
IF Basics.BITAND[v.hi, 0E000H]#0 THEN ERROR;
v.hi ← Basics.BITOR[v.hi, 0E000H];
IF Basics.BITAND[v.hi, 0E000H]#0E000H THEN ERROR;
PutByte[handle, v.hh];
PutByte[handle, v.hl];
PutByte[handle, v.lh];
PutByte[handle, v.ll];
handle.filePos ← handle.filePos+4;
};
ENDCASE => ERROR; -- too large
};
Read29Bits: PROC [s: IO.STREAM] RETURNS [delta: INT32] ~ {
Read a 29-bits integer using the format emitted by Write29Bits
v: Basics.LongNumber;
v.lc ← 0;
v.ll ← IO.GetByte[s];
SELECT TRUE FROM
Basics.BITAND[v.lo, 00080H]=0 => { -- single byte
IF v.lc>=limit1 THEN ERROR;
};
Basics.BITAND[v.lo, 00040H]=0 => { -- 2 bytes
v.lo ← Basics.BITAND[Basics.BITSHIFT[v.lo, 8], 03F00H];
v.ll ← IO.GetByte[s];
IF v.lc>=limit2 THEN ERROR;
};
Basics.BITAND[v.lo, 00020H]=0 => { -- 3 bytes
v.hi ← Basics.BITAND[v.lo, 0001FH];
v.lh ← IO.GetByte[s];
v.ll ← IO.GetByte[s];
IF v.lc>=limit3 THEN ERROR;
};
ENDCASE => { -- 4 bytes
v.hi ← Basics.BITAND[Basics.BITSHIFT[v.lo, 8], 01F00H];
v.hl ← IO.GetByte[s];
v.lh ← IO.GetByte[s];
v.ll ← IO.GetByte[s];
IF v.lc>=limit4 THEN ERROR;
};
RETURN [delta: v.li];
};
WriteSample: PROC [handle: RoseDisplay, sample: Sample, prvPos: INT, nextStep: INT] RETURNS [pos: INT] ~ {
Write the specified sample at the current file position, using prvPos as backpointer, and return in pos the fileposition at which this sample was read. The initial and final file position are at EOF.
Must be called under backing store lock!
deltaPos: INT;
WillWrite[handle, 8+sample.size]; -- max number of bytes that will be written
pos ← handle.filePos;
IF prvPos<0 THEN deltaPos ← 0
ELSE {
deltaPos ← pos-prvPos;
IF deltaPos<=0 THEN ERROR; -- something is very wrong...
};
Write29Bits[handle, deltaPos];
Write29Bits[handle, nextStep - sample.step]; -- must be >=0 !!!
FOR i: NAT IN [0..sample.size) DO
PutByte[handle, ORD[sample.value[i]]];
ENDLOOP;
handle.filePos ← handle.filePos+sample.size;
};
ReadSample: PROC [s: IO.STREAM, pos: INT, into: Sample, nextStep: INT] RETURNS [prvPos: INT] ~ {
Read a sample from the specified location on the file. prvPos is the pointer to the previous sample in the chain. prv<0 means this is the 1st sample in chain. Refer to readSample for details.
Must be called under backing store lock!
deltaPos: INT;
IO.SetIndex[s, pos];
deltaPos ← Read29Bits[s];
IF deltaPos=0 THEN prvPos ← -1
ELSE {
prvPos ← pos - deltaPos;
IF prvPos<0 THEN ERROR; -- inconsistency in file management
};
into.step ← nextStep - Read29Bits[s];
FOR i: NAT IN [0..into.size) DO
into.value[i] ← VAL[IO.GetByte[s]];
ENDLOOP;
};
Backing store logical access -- all procs require backing store lock
RBTGetKey: RedBlackTree.GetKey ~ {
Get the key for a SampleList in the RedBlackTree: it's identity...
RETURN [data]; -- keys are same as data...
};
RBTCompare: RedBlackTree.Compare ~ {
Compare key & data in the RedBlackTree
list1: SampleList = NARROW [k];
list2: SampleList = NARROW [data];
RETURN [Basics.CompareInt[list1.beforeHeadPos, list2.beforeHeadPos]];
};
EnterSourceInRBT: PROC [table: RedBlackTree.Table, source: REF ANY, min: INT ← 0] RETURNS [newTable: RedBlackTree.Table] ~ {
Add the specified roseValues/roseInstance to the table so that they will be fetched from disk up to the required minimum time. Just some sugar on top of EnterLogDataInRBT.
min is expressed in steps.
Must be called under backing store lock!
EnterLogDataInRBT: PROC [data: LogData] ~ {
IF data#NIL THEN { -- nothing ever logged for this guy...
list: SampleList ← data.list;
IF list=NIL THEN { -- must create list head
list ← NEW [SampleListRec ← [
head: IF data.previous#NIL THEN data.previous ELSE data.current,
beforeHeadPos: data.lastFilePos,
inTable: FALSE]];
data.list ← list;
};
IF list.beforeHeadPos<0 OR list.head.step<=min THEN RETURN; -- nothing to fetch
IF newTable=NIL THEN newTable ← RedBlackTree.Create[RBTGetKey, RBTCompare];
IF NOT list.inTable THEN { -- may not insert twice in a RedBlackTree
RedBlackTree.Insert[newTable, list, list];
list.inTable ← TRUE;
};
};
};
newTable ← table;
WITH source SELECT FROM
rvl: Rosemary.RoseValues => UNTIL rvl=NIL DO -- this is for a CoreFlat wire
EnterLogDataInRBT[NARROW [rvl.first.roseWire.data]];
rvl ← rvl.rest; -- advance list pointer
ENDLOOP;
roseInstance: Rosemary.RoseCellInstance => EnterLogDataInRBT[NARROW [roseInstance.data]];
ENDCASE => ERROR;
};
ReadSamplesUsingRBT: PROC [handle: RoseDisplay, table: RedBlackTree.Table, min: INT] ~ {
Read all the samples described in the RBT, going backwards & in order through the file.
min is expressed in steps.
Must be called under backing store lock!
stream: IO.STREAM = handle.ps;
FlushWBuff[handle, 0]; -- ensure we are really at end of file and the buffer is empty
IF table#NIL THEN WHILE RedBlackTree.Size[table]#0 DO
list: SampleList ← NARROW [RedBlackTree.LookupLargest[table]];
node: RedBlackTree.Node ← RedBlackTree.Delete[table, list];
sample: Sample ← NEW [SampleRec[list.head.size]];
list.beforeHeadPos ← ReadSample[stream, list.beforeHeadPos, sample, list.head.step];
sample.next ← list.head; list.head ← sample; -- insert as head of list
IF sample.step>min AND list.beforeHeadPos>=0 THEN RedBlackTree.InsertNode[table, node, list] -- this one must still go on...
ELSE list.inTable ← FALSE; -- it's no more there...
ENDLOOP;
IO.SetIndex[stream, handle.filePos]; -- go back to end of file
};
Time management
Principles:
The timeSteps array (2-level due to stupid 32K array restriction) is a mapping from time value to last step number for that time value. The logic has a deep built-in assumption that time 0 starts at step 0. TimeSteps entries are valid only in the range [0..handle.lastValidTime].
The samples in ]timeSteps[t-1]..timeSteps[t]] are in the time slot t.
Only procedures in this section should refer to handle.timeSteps
LogTime: PROC [handle: RoseDisplay, time: INT] ~ {
Note time as new lastValidTime & add item to timeSteps array
index: NAT ← time/timeBlock;
offset: NAT ← time MOD timeBlock;
block: TimeSteps ← handle.timeSteps[index];
handle.lastValidTime ← time;
IF block=NIL THEN {
IF offset#0 THEN ERROR; -- we missed a time value !!!
block ← NEW [TimeStepsRep ← ALL[-1]];
handle.timeSteps[index] ← block;
};
block[offset] ← handle.simulation.mosSimTime;
};
LastStep: PROC [handle: RoseDisplay, time: INT] RETURNS [lastStep: INT] ~ {
Return the last step number in [time..time+1)
SELECT TRUE FROM
time<0 => lastStep ← 0;
time>handle.lastValidTime => lastStep ← handle.simulation.mosSimTime;
ENDCASE => { -- normal case
index: NAT ← time/timeBlock;
offset: NAT ← time MOD timeBlock;
lastStep ← handle.timeSteps[index][offset];
};
};
FirstStep: PROC [handle: RoseDisplay, time: INT] RETURNS [firstStep: INT] ~ {
Return the first step number in [time..time+1)
time ← time-1;
SELECT TRUE FROM
time<0 => firstStep ← 0;
time>handle.lastValidTime => firstStep ← LAST[INT]; -- get lost ...
ENDCASE => { -- normal case
index: NAT ← time/timeBlock;
offset: NAT ← time MOD timeBlock;
firstStep ← handle.timeSteps[index][offset]+1;
};
};
Sampling
LSToSample: PROC [ls: Ports.LevelSequence, sample: Sample] ~ {
Copy the value of the LevelSequence into the sample's data field
IF ls.size#sample.size THEN ERROR; -- Client programming error or Rosemary bug
FOR i: NAT IN [0.. ls.size) DO sample.value[i] ← ls[i] ENDLOOP;
};
NewLogData: PROC [nbits: NAT] RETURNS [data: LogData] ~ {
All is initialized properly except for the bits of data.current. current.time is forced to 0 since NewLogData is called only at Init time.
data ← NEW [LogDataRec];
data.lastFilePos ← -1;
data.list ← NIL; -- not kept in memory (yet...)
data.previous ← NIL; -- no previous sample
data.currentTime ← -1;
data.current ← NEW[SampleRec[nbits]];
data.current.next ← NIL;
data.current.step ← 0;
};
InitializeDeltas: PUBLIC PROC [handle: RoseDisplay] = {
EraseWireData: RefTab.EachPairAction = {
Create the Wire data and initialize it properly...
wire: Rosemary.RoseWire ← NARROW[val];
atomic: BOOL = wire.currentValue=NIL;
data: LogData ← NewLogData[IF atomic THEN 1 ELSE wire.currentValue.size];
IF atomic THEN data.current.value[0] ← wire.wireLevel
ELSE LSToSample[wire.currentValue, data.current];
wire.data ← data;
};
EraseInstanceData: RefTab.EachPairAction ~ {
Initializing instance data is tricky since InitializeDeltas is called after Rosemary.Initialize. The technique is to store (a copy) of the returned LS as data field of the RoseCellInstance and to do the conversion here...
roseInstance: Rosemary.RoseCellInstance ← NARROW [val];
ls: Ports.LevelSequence = NARROW [roseInstance.data];
IF ls#NIL THEN { -- make into a LogData
data: LogData ← NewLogData[ls.size];
LSToSample[ls, data.current];
roseInstance.data ← data;
};
};
LockBackingStore[handle]; -- Don't forget it here...
LogTime[handle, 0];
IF handle.wBuff=NIL THEN handle.wBuff ← RefText.New[4096];
handle.wBuff.length ← 0; -- erase the buffer as it may contain garbage
IF handle.ps=NIL THEN handle.ps ← FS.StreamOpen["///Temp/RoseBackingStore.bin", $create]
ELSE IO.SetLength[handle.ps, 0]; -- completely erase the file if already there...
handle.filePos ← 0;
[] ← RefTab.Pairs[x: handle.simulation.coreToRoseWires, action: EraseWireData];
[] ← RefTab.Pairs[x: handle.simulation.coreToRoseInstances, action: EraseInstanceData];
UnlockBackingStore[handle]; -- we don't want to hold onto it during plotting !
IF handle.plot#NIL AND handle.plot.data#NIL THEN PlotGraph.RefreshPlot[plot: handle.plot, eraseFirst: TRUE];
};
CollapseSample: PROC [handle: RoseDisplay, data: LogData] ~ {
Must be called under backing store lock ... File pointer is assumed to be at EOF.
This procedure is not concerned with time/step stamping.
nbits: NAT = data.current.size;
DifferSample: PROC [s1, s2: Sample] RETURNS [BOOL] ~ {
Returns TRUE iff the two samples have different value fields (size must be same!)
FOR i: CARDINAL IN [0..s1.size) DO
IF s1.value[i]#s2.value[i] THEN RETURN [TRUE]
ENDLOOP;
RETURN [FALSE];
};
SELECT TRUE FROM
data.previous=NIL => { -- this the 1st sample, make it previous & allocate new current
data.previous ← data.current;
data.current ← NEW[SampleRec[nbits]];
data.previous.next ← data.current;
data.current.next ← NIL; -- just to make sure...
};
DifferSample[data.previous, data.current] => { -- commit current sample
data.lastFilePos ← WriteSample[handle, data.previous, data.lastFilePos, data.current.step];
data.current.next ← IF data.list=NIL THEN data.previous ELSE NEW[SampleRec[nbits]];
data.previous ← data.current; data.current ← data.previous.next; -- update data
data.current.next ← NIL; -- necessary if data.previous was reused
};
ENDCASE => NULL; -- collapse current with previous
};
RecordDelta: PUBLIC PROC [handle: RoseDisplay, wire: Rosemary.RoseWire, time: INT] ~ {
Maintain the wire data field when the wire is updated.
IF handle.recordDeltas THEN { -- otherwise, nop...
data: LogData = NARROW [wire.data];
nbits: NAT = data.current.size;
mosSimTime: INT = handle.simulation.mosSimTime;
mustCollapse: BOOL = IF handle.recordSteps THEN mosSimTime#data.current.step ELSE time#data.currentTime;
LockBackingStore[handle]; -- let's be paranoid...
At this point, we assume the file pointer to be at EOF
IF mustCollapse THEN { -- this is a different Eval
CollapseSample[handle, data];
data.currentTime ← time; -- this is the new time for the curent sample
data.current.step ← mosSimTime; -- this is the new step for the curent sample
};
IF wire.currentValue=NIL THEN data.current.value[0] ← wire.wireLevel
ELSE LSToSample[wire.currentValue, data.current];
UnlockBackingStore[handle];
};
IF handle.traceChanges THEN { -- debug output
wireKey: CoreFlat.FlatWire ← NEW[CoreFlat.FlatWireRec ← wire.wire];
UpdateDisplay[handle];
IO.PutF[handle.tsout, "%g←%g ", IO.rope[CoreFlat.WirePathRope[handle.cellType, wireKey^]], IO.rope[Ports.LevelSequenceToRope[Rosemary.WireValue[ handle.simulation, wireKey]]]];
};
};
RecordStateSample: PUBLIC PROC [handle: RoseDisplay, roseInstance: Rosemary.RoseCellInstance, value: Ports.LevelSequence, time: INT] ~ {
Maintain the wire data field when the rose instance is updated. This looks a lot like RecordDelta...
IF value#NIL AND handle.recordDeltas THEN {
data: LogData = NARROW [roseInstance.data];
mosSimTime: INT = handle.simulation.mosSimTime;
mustCollapse: BOOL = IF handle.recordSteps THEN mosSimTime#data.current.step ELSE time#data.currentTime;
IF data=NIL THEN ERROR; -- InitProc should be returning an LS first !!!
LockBackingStore[handle]; -- let's be paranoid...
At this point, we assume the file pointer to be at EOF
IF mustCollapse THEN { -- this is a different Eval
CollapseSample[handle, data];
data.currentTime ← time; -- this is the new time for the curent sample
data.current.step ← mosSimTime; -- this is the new step for the curent sample
};
LSToSample[value, data.current];
UnlockBackingStore[handle];
};
IF handle.traceChanges THEN { -- cell has changed state
UpdateDisplay[handle];
IO.PutF[handle.tsout, "<%g> ", IO.rope[CoreFlat.CellTypePathRope[handle.cellType, roseInstance.instance]]];
};
};
Plotting
Types
Known misfeatures and how to improve on them:
- PlotGraph almost always calls the GraphEnumerateProc with bounds=infinite (on fact, due to a PlotGraph bug, empty). As a result, when a new wire is displayed, it is always read back to the origin of times. It is not possible from the client code to infer the correct bounds (gathering them from the viewer will hamper IP generation). This should be fixed in PlotGraph (anyway, there are other things to be fixed there...).
- It would be more efficient to add multiple wires to the plot at once than one at a time because refreshing requires reading the disk. Either have AddWiresToPlot instead of AddWireToPlot, or (better) leave the responsability of refreshing to the client.
- It would be faster is InitPlotGraphData could avoid rewinding back to the beginning of times. This could be achieved by adding a "currentTime" field to the pgd, but this raises serious questions when the simulation is re-initialized because we then must invalidate all pgd's.
PlotGraphData: TYPE ~ REF PlotGraphDataRec;
PlotGraphDataRec: TYPE ~ RECORD [
source: REF ANYNIL, -- either RoseValues or RoseCellInstance
bits: Ports.LevelSequence ← NIL, -- computed values will go in there
clientData: REF ANYNIL, -- only for RoseCellInstances
ropeProc: StateToRopeProc, -- only if display style is hexaV
parts: SEQUENCE size: CARDINAL OF Sample -- basic information for reconstitution
];
This is the data structure that permits to recompute values of flatwires at each time
roseGraphClass: PlotGraph.GraphClass ← NEW[PlotGraph.GraphClassRec ← [
enumerate: RoseGraphEnumerate]];
Value recovery and assembly
NewPlotGraphData: PROC [source: REF ANY, clientData: REF ANY, ropeProc: StateToRopeProc] RETURNS [pgd: PlotGraphData] ~ {
Create the PlotGraphData with the right sizes for the RoseValues. The contents of parts are left to NIL. The bits field initialization is deferreed for roseInstances to InitPlotGraphData.
partCount: NAT ← 0;
bits: Ports.LevelSequence ← NIL;
WITH source SELECT FROM
rvl: Rosemary.RoseValues => { -- this plot is for a CoreFlat wire
bitCount: NAT ← 0;
UNTIL rvl=NIL DO
val: Rosemary.RoseValue = rvl.first;
bitCount ← bitCount+val.fieldWidth;
partCount ← partCount + 1;
rvl ← rvl.rest;
ENDLOOP;
bits ← NEW[Ports.LevelSequenceRec[bitCount]];
};
roseInstance: Rosemary.RoseCellInstance => { -- this plot is for an unexpanded cell
The bits LS is not setup yet as we don't know the size...
It will be setup the 1st time we find a non-NIL sample on the instance...
partCount ← 1;
};
ENDCASE => ERROR; -- internal bug, invalid argument
pgd ← NEW[PlotGraphDataRec[partCount]];
pgd.source ← source;
pgd.clientData ← clientData;
pgd.ropeProc ← ropeProc;
pgd.bits ← bits;
};
InitPlotGraphData: PROC [handle: RoseDisplay, pgd: PlotGraphData, minStep: INT] RETURNS [effectiveStep: INT ← 0] ~ {
Initialize pgd parts so that a first sample is valid at the required step number.
Assumes that the corresponding values have been made resident early enough using EnterSourceInRBT/ReadSamplesUsingRBT.
Returns the step at which the value is correct (may be >minStep, LAST[INT] means no value may be established).
Must be called under backing store lock!
WITH pgd.source SELECT FROM
rvl: Rosemary.RoseValues => { -- this is a wire plot
FOR part: NAT IN [0..pgd.size) DO -- go up the sample chain up to minStep
data: LogData = NARROW[rvl.first.roseWire.data];
sample: Sample;
IF data=NIL OR data.list=NIL THEN RETURN [LAST[INT]]; -- not initialized !
sample ← data.list.head; -- cannot be NIL !
IF sample.step<=minStep THEN { -- try going forwards
UNTIL sample.next=NIL OR sample.next.step>minStep DO
sample ← sample.next;
ENDLOOP;
};
effectiveStep ← MAX[effectiveStep, sample.step];
pgd.parts[part] ← sample;
rvl ← rvl.rest;
ENDLOOP;
};
roseInstance: Rosemary.RoseCellInstance => { -- this is a cell state plot
The bits field of pgd is initialized here if we have the information.
data: LogData = NARROW[roseInstance.data];
sample: Sample;
IF data=NIL OR data.list=NIL THEN RETURN [LAST[INT]]; -- no info available
sample ← data.list.head; -- cannot be NIL !
IF pgd.bits=NIL THEN pgd.bits ← NEW[Ports.LevelSequenceRec[sample.size]];
IF sample.step<=minStep THEN { -- try going forwards
UNTIL sample.next=NIL OR sample.next.step>minStep DO
sample ← sample.next;
ENDLOOP;
};
effectiveStep ← sample.step;
pgd.parts[0] ← sample; -- there is exactly 1 part in a cell state pgd
};
ENDCASE => ERROR;
};
AssemblePlotGraphDataBits: PROC [pgd: PlotGraphData] RETURNS [nextStep: INT] ~ {
Assemble the bits for the current step, and position everything for the next step. Returns LAST[INT] if the computed value is the last one. pgd.bits must have been initialized.
Must be called under backing store lock!
firstFreeBit: NAT ← 0;
bits: Ports.LevelSequence ← pgd.bits;
nextStep ← LAST[INT];
FOR i: NAT IN [0..pgd.size) DO -- build up the bits
sample: Sample = pgd.parts[i];
FOR bit: NAT IN [0..sample.size) DO bits[firstFreeBit+bit] ← sample.value[bit] ENDLOOP;
firstFreeBit ← firstFreeBit+sample.size;
IF sample.next#NIL THEN nextStep ← MIN[sample.next.step, nextStep];
ENDLOOP;
IF nextStep=LAST[INT] THEN RETURN; -- nothing more to do...
FOR i: NAT IN [0..pgd.size) DO -- advance samples for nextTime
sample: Sample = pgd.parts[i];
IF sample.next#NIL AND sample.next.step=nextStep THEN pgd.parts[i] ← sample.next;
ENDLOOP;
};
GetValueAt: PROC [handle: RoseDisplay, pgd: PlotGraphData, time: INT] RETURNS [ls: Ports.LevelSequence ← NIL] ~ {
Update the pgd to get a decent value in bits for time, return NIL if it's impossible.
atStep: INT ← LastStep[handle, time]; -- convert to step specification
possibleStep: INT;
LockBackingStore[handle]; -- critical here...
possibleStep ← InitPlotGraphData[handle, pgd, atStep];
IF possibleStep>atStep THEN { -- try from disk...
table: RedBlackTree.Table ← EnterSourceInRBT[NIL, pgd.source, atStep];
IF table#NIL THEN ReadSamplesUsingRBT[handle, table, atStep];
possibleStep ← InitPlotGraphData[handle, pgd, atStep];
IF possibleStep>atStep THEN RETURN [NIL]; -- we lost the battle...
};
IF possibleStep<=atStep THEN {
[] ← AssemblePlotGraphDataBits[pgd];
ls ← NEW [Ports.LevelSequenceRec[pgd.bits.size]];
Ports.CopyLS[from: pgd.bits, to: ls];
};
UnlockBackingStore[handle]; -- may now safely release
};
WireTimeValue: PUBLIC PROC [handle: RoseDisplay, flatWire: CoreFlat.FlatWire, time: INT] RETURNS [value: Ports.LevelSequence] = {
Return the value of a wire at a given time. Will return NIL if no value may be established for the required time.
roseValues: Rosemary.RoseValues ← Rosemary.GetValues[handle.simulation, flatWire];
value ← GetValueAt[handle, NewPlotGraphData[roseValues, NIL, NIL], time];
};
StateTimeValue: PUBLIC PROC [handle: RoseDisplay, flatCell: CoreFlat.FlatCellType, time: INT] RETURNS [value: Ports.LevelSequence] = {
Return the value of a wire at a given time. Will return NIL if no value may be established for the required time.
roseInstance: Rosemary.RoseCellInstance = NARROW [ RefTab.Fetch[handle.simulation.coreToRoseInstances, flatCell].val];
IF roseInstance=NIL THEN ERROR Rosemary.NotInstantiated[];
value ← GetValueAt[handle, NewPlotGraphData[roseInstance, NIL, NIL], time];
};
Client plotting interface
DisplayPortLeafWires: PUBLIC PROC [root: Core.CellType, flatCell: CoreFlat.FlatCellTypeRec ← CoreFlat.rootCellType] RETURNS [displayWires: CoreFlat.FlatWires] = {
CompareFlatWires: List.CompareProc = {
flat1: CoreFlat.FlatWire ← NARROW[ref1];
flat2: CoreFlat.FlatWire ← NARROW[ref2];
IF flat1.flatCell.path.length>flat2.flatCell.path.length THEN RETURN [greater];
IF flat1.flatCell.path.length<flat2.flatCell.path.length THEN RETURN [less];
FOR i: CoreFlat.InstancePathIndex IN [0..flat1.flatCell.path.length) DO
one: BOOL ← flat1.flatCell.path.bits[i];
other: BOOL ← flat2.flatCell.path.bits[i];
SELECT TRUE FROM
one AND (NOT other) => RETURN [greater];
(NOT one) AND other => RETURN [less];
ENDCASE;
ENDLOOP;
IF flat1.flatCell.recastCount>flat2.flatCell.recastCount THEN RETURN [greater];
IF flat1.flatCell.recastCount<flat2.flatCell.recastCount THEN RETURN [less];
RETURN[Rope.Compare[CoreOps.GetFullWireName[cell.public, flat1.wire], CoreOps.GetFullWireName[cell.public, flat2.wire]]];
};
FindLeaves: CoreOps.EachWireProc = {
IF Ports.WirePortType[cell, wire].levelType#composite THEN {
subWires ← FALSE;
displayWires ← CONS[NEW[CoreFlat.FlatWireRec ← [flatCell: flatCell, wireRoot: public, wire: wire]], displayWires];
};
};
cell: Core.CellType ← CoreFlat.ResolveFlatCellType[root, flatCell].cellType;
IF CoreOps.VisitWire[cell.public, FindLeaves] THEN ERROR;
TRUSTED {displayWires ← LOOPHOLE[List.Sort[LOOPHOLE[displayWires], CompareFlatWires]]};
};
LSToRope: StateToRopeProc ~ {
This is restricted version of Ports.LSToRope that does not expand partial X's down to bit level. This is better for plotting as it guarantees that the resulting rope has a constant size.
rope ← Ports.LSToRope[value];
size: NAT = value.size;
scratch: REF TEXT ← RefText.New[(size+3)/4];
bitsInDigit: NAT;
digitBitCount: NAT ← 0;
someX: BOOLFALSE;
digitVal: CARDINAL ← 0;
bitsInDigit ← IF size MOD 4 = 0 THEN 4 ELSE size MOD 4;
bitsInDigit ← ((size+3) MOD 4) + 1;
FOR bit: NAT IN [0..size) DO
SELECT value[bit] FROM
H => digitVal ← 2*digitVal + 1;
L => digitVal ← 2*digitVal;
ENDCASE => someX ← TRUE; -- don't care about digitVal now...
digitBitCount ← digitBitCount + 1;
IF digitBitCount=bitsInDigit THEN {
IF someX THEN scratch ← RefText.InlineAppendChar[scratch, 'X]
ELSE scratch ← Convert.AppendCard[to: scratch, from: digitVal, base: 16, showRadix: FALSE];
bitsInDigit ← 4;
digitBitCount ← 0;
someX ← FALSE;
digitVal ← 0;
};
ENDLOOP;
rope ← Rope.FromRefText[scratch];
};
AddGraph: PROC [handle: RoseDisplay, pgd: PlotGraphData, name: ROPE, style: PlotGraph.DrawingStyle, maxChars: NAT ← 8] ~ {
Add a graph to the plot
plot: PlotGraph.Plot ← handle.plot;
graph: PlotGraph.Graph ← NEW[PlotGraph.GraphRec ← [
class: roseGraphClass,
data: pgd]];
axis: PlotGraph.Axis ← NEW[PlotGraph.AxisRec ← [
graphs: LIST [graph],
bounds: [0.0, 0.0, 10.0, 6.0],
name: name,
style: style,
maxChars: maxChars,
axisData: [X: [ticks: 1.0, visible: TRUE], Y: [ticks: 1.0, visible: TRUE]]
]];
IF plot=NIL OR plot.data=NIL THEN { -- don't forget the plot might have been destroyed
plot ← handle.plot ← PlotGraph.CreatePlot[handle.name];
PlotGraph.LockPlot[plot];
plot.lowerBounds ← [0.0, 0.0];
plot.upperBounds ← [Real.Float[handle.lastValidTime], 5.0];
plot.data ← handle;
}
ELSE PlotGraph.LockPlot[plot];
IF plot.axis#NIL THEN axis.bounds ← plot.axis.first.bounds;
plot.axis ← CONS[axis, plot.axis];
PlotGraph.UnlockPlot[plot];
PlotGraph.RefreshPlot[plot: plot, eraseFirst: TRUE];
};
AddWireToPlot: PUBLIC PROC [handle: RoseDisplay, wire: CoreFlat.FlatWire] RETURNS [msg: ROPENIL] = {
For reasons of efficiency, this procedure should NOT refresh the plot because refreshing the plot forces reading the backing store, and the more there is to do at once the better...
roseValues: Rosemary.RoseValues ← Rosemary.GetValues[handle.simulation, wire ! Rosemary.NotInstantiated => GOTO NoSuchWire];
pgd: PlotGraphData ← NewPlotGraphData[roseValues, NIL, LSToRope];
name: ROPE ← CoreFlat.WirePathRope[handle.cellType, wire^];
IF Rope.Equal[Rope.Substr[name, 0, 7], "public."] THEN name ← Rope.Substr[name, 7];
IF pgd.bits.size=1 THEN AddGraph[handle, pgd, name, analog]
ELSE AddGraph[handle, pgd, name, hexaV, (pgd.bits.size+3)/4];
EXITS
NoSuchWire => msg ← "Not stored as a Rosemary wire";
};
stateToMaxCharsProcProp: PUBLIC ATOM ← $RoseStateToMaxCharsProc;
stateToRopeProcProp: PUBLIC ATOM ← $RoseStateToRopeProc;
AddStateToPlot: PUBLIC PROC [handle: RoseDisplay, flatCell: CoreFlat.FlatCellType, data: REF ANYNIL] RETURNS [msg: ROPENIL] = {
For reasons of efficiency, this procedure should NOT refresh the plot because refreshing the plot forces reading the backing store, and the more there is to do at once the better...
flat: CoreFlat.FlatCellType ← NEW[CoreFlat.FlatCellTypeRec ← flatCell^];
cellType: Core.CellType ← NIL;
cellInstance: CoreClasses.CellInstance ← NIL;
roseInstance: Rosemary.RoseCellInstance ← NIL;
IF CoreFlat.BelowCutSet[handle.cellType, flatCell^, handle.cutSet] THEN RETURN [msg: "Below simulation cutset"];
[,cellInstance, cellType] ← CoreFlat.ResolveFlatCellType[handle.cellType, flat^];
UNTIL CoreFlat.CutSetMemberResolved[flat^, cellInstance, cellType, handle.cutSet] DO
cellType ← CoreOps.Recast[cellType];
flat.recastCount ← flat.recastCount + 1;
ENDLOOP;
roseInstance ← NARROW [ RefTab.Fetch[handle.simulation.coreToRoseInstances, flat].val];
IF roseInstance#NIL THEN {
charsProc: REF StateToMaxCharsProc ← NARROW [CoreProperties.InheritCellTypeProp[cellType, stateToMaxCharsProcProp]];
ropeProc: REF StateToRopeProc ← NARROW [CoreProperties.InheritCellTypeProp[cellType, stateToRopeProcProp]];
name: ROPE ← CoreFlat.CellTypePathRope[handle.cellType, flat^];
pgd: PlotGraphData ← NewPlotGraphData[roseInstance, data, IF ropeProc=NIL THEN LSToRope ELSE ropeProc^];
AddGraph[handle, pgd, name, hexaV, IF charsProc=NIL THEN (pgd.bits.size+3)/4 ELSE charsProc^[roseInstance.state, data]];
}
ELSE msg ← "Not stored as a Rosemary cell instance";
};
RemoveFromPlot: PROC [handle: RoseDisplay, source: REF ANY, clientData: REF ANY] RETURNS [found: BOOLFALSE] ~ {
plot: PlotGraph.Plot ← handle.plot;
trail: PlotGraph.AxisList ← NIL;
IF plot=NIL OR plot.data=NIL THEN RETURN;
PlotGraph.LockPlot[plot];
FOR axis: PlotGraph.AxisList ← plot.axis, axis.rest UNTIL axis=NIL DO
pgd: PlotGraphData ← NARROW[axis.first.graphs.first.data];
IF pgd.source=source AND pgd.clientData=clientData THEN {
IF trail=NIL THEN plot.axis ← axis.rest ELSE trail.rest ← axis.rest; -- excise guilty axis
found ← TRUE;
EXIT;
};
trail ← axis;
ENDLOOP;
PlotGraph.UnlockPlot[plot];
IF found THEN PlotGraph.RefreshPlot[plot: plot, eraseFirst: TRUE];
};
RemoveWireFromPlot: PUBLIC PROC [handle: RoseDisplay, wire: CoreFlat.FlatWire] RETURNS [found: BOOLFALSE] = {
roseValues: Rosemary.RoseValues ← Rosemary.GetValues[handle.simulation, wire ! Rosemary.NotInstantiated => GOTO NoSuchWire];
found ← RemoveFromPlot[handle, roseValues, NIL];
EXITS
NoSuchWire => NULL;
};
RemoveStateFromPlot: PUBLIC PROC [handle: RoseDisplay, flatCell: CoreFlat.FlatCellType, data: REF ANYNIL] RETURNS [found: BOOLFALSE] = {
roseInstance: Rosemary.RoseCellInstance = NARROW [ RefTab.Fetch[handle.simulation.coreToRoseInstances, flatCell].val];
IF roseInstance#NIL THEN found ← RemoveFromPlot[handle, roseInstance, data];
};
PlotGraph service
DeltaFinished: PUBLIC PROC [handle: RoseDisplay, time: INT] = {
plot: PlotGraph.Plot ← handle.plot;
LogTime[handle, time];
IF plot#NIL AND plot.data#NIL THEN { -- the plot viewer might have been destroyed !
oldUpper: REAL = plot.upperBounds.x-1.0;
newUpper: REAL = Real.Float[time];
plot.upperBounds.x ← newUpper;
PlotGraph.RefreshPlot[plot: plot, within: [oldUpper, 0.0, newUpper-oldUpper, 6.0]];
};
};
PGDStepProc: TYPE ~ PROC [pgd: PlotGraphData, rTime: REAL, notLast: BOOL];
EnumeratePGD: PROC [handle: RoseDisplay, pgd: PlotGraphData, from: REAL, to: REAL, eachStep: PGDStepProc, showSteps: BOOL] ~ {
Enumerate the items in the pgd in the time interval [from..to] (those are the plot bounds), call eachTime for each sample
The details shown on the plot are specified by handle.plotStyle:
allSteps => everything is shown in full detail, may be unreadable, fractional time
waveSteps => show steps only if showSteps is TRUE (waveforms), fractional time
noSteps => never show steps, force all display point on integer time boundaries
Must be called under backing store lock
firstCur, lastCur, step: INT; -- steps for current time: firstCur<=step<=lastCur, in fromTime
firstLogged: INT; -- first time time at which we succeed to get a sample
fromTime: INT ← Real.Floor[MAX[from, 0.0]]; -- we should start roughly from here
fractional: BOOL; -- TRUE means time is fractional, FALSE time is forced to INT
firstCur ← FirstStep[handle, fromTime]; -- first step in fromTime
lastCur ← LastStep[handle, fromTime]; -- last step in fromTime
step ← firstCur;
firstLogged ← InitPlotGraphData[handle, pgd, firstCur];
IF firstLogged>firstCur THEN { -- read more data from disk
table: RedBlackTree.Table ← NIL;
plot: PlotGraph.Plot = handle.plot;
FOR al: PlotGraph.AxisList ← plot.axis, al.rest UNTIL al=NIL DO -- pass over all axis
FOR gl: PlotGraph.GraphList ← al.first.graphs, gl.rest UNTIL gl=NIL DO -- and all graphs
thisPGD: PlotGraphData = NARROW [gl.first.data];
table ← EnterSourceInRBT[table, thisPGD.source, firstCur]; -- collect source values
ENDLOOP;
ENDLOOP;
IF table#NIL THEN ReadSamplesUsingRBT[handle, table, firstCur];
firstLogged ← InitPlotGraphData[handle, pgd, firstCur];
};
-- At this point, firstLogged contains the 1st really available point of data.
SELECT handle.plotStyle FROM
allSteps => {showSteps ← TRUE; fractional ← TRUE};
waveSteps => {fractional ← TRUE};
noSteps => {showSteps ← FALSE; fractional ← FALSE};
ENDCASE => ERROR;
IF step<=handle.simulation.mosSimTime THEN DO
nextStep: INT = AssemblePlotGraphDataBits[pgd];
rTime: REAL;
UNTIL step<=lastCur DO -- advance `fromTime' till it reaches step
fromTime ← fromTime+1;
firstCur ← lastCur+1;
lastCur ← LastStep[handle, fromTime];
ENDLOOP;
IF showSteps OR nextStep>lastCur THEN { -- show step, or last of time slot
rTime ← Real.Float[fromTime];
IF fractional THEN rTime ← rTime - (step-lastCur)/Real.Float[lastCur-firstCur+1];
IF rTime<to THEN eachStep[pgd, rTime, TRUE] ELSE GO TO EndOfWindow;
};
step ← nextStep;
IF step>handle.simulation.mosSimTime THEN GO TO EndOfWindow;
REPEAT
EndOfWindow => eachStep[pgd, to, FALSE];
ENDLOOP;
};
RoseGraphEnumerate: PlotGraph.GraphEnumerateProc = {
[plot: Plot, graph: Graph, bounds: Rectangle, eachPoint: PointProc, data: REF ANY]
ENABLE ABORTED => GOTO Aborted; -- in order to help debug...
handle: RoseDisplay ← NARROW [plot.data];
pgd: PlotGraphData ← NARROW [graph.data];
low: REAL = MAX [bounds.x, 0];
high: REAL = handle.lastValidTime+1; -- bounds.w is incorrect in PlotGraph
LockBackingStore[handle]; -- critical here...
WITH pgd.source SELECT FROM
rvl: Rosemary.RoseValues => { -- this plot is for a CoreFlat wire
value: REAL; notFirst: BOOLFALSE;
EachAnalogStep: PGDStepProc ~ {
IF notFirst THEN [] ← eachPoint[x: rTime, y: value]
ELSE notFirst ← TRUE;
IF notLast THEN {
value ← SELECT pgd.bits[0] FROM L => 0.0, X => 2.5, H => 5.0, ENDCASE => ERROR;
[] ← eachPoint[x: rTime, y: value]
};
};
EachWireStep: PGDStepProc ~ {
value: ROPE = pgd.ropeProc[NIL, pgd.bits, pgd.clientData];
[] ← eachPoint[x: rTime, y: 0.0, rope: value]
};
IF pgd.bits.size=1 THEN EnumeratePGD[handle, pgd, low, high, EachAnalogStep, TRUE]
ELSE EnumeratePGD[handle, pgd, low, high, EachWireStep, FALSE];
};
roseInstance: Rosemary.RoseCellInstance => { -- this plot is for an unexpanded cell
EachStateStep: PGDStepProc ~ {
value: ROPE = pgd.ropeProc[roseInstance.state, pgd.bits, pgd.clientData];
[] ← eachPoint[x: rTime, y: 0.0, rope: value]
};
EnumeratePGD[handle, pgd, low, high, EachStateStep, FALSE];
};
ENDCASE => ERROR;
UnlockBackingStore[handle]; -- may now safely release
EXITS
Aborted => UnlockBackingStore[NARROW [plot.data]];
};
Odds and ends
Types
Entry: TYPE ~ REF EntryRep;
LevelSeen: TYPE ~ RECORD [wasH, wasL: BOOL];
EntryRep: TYPE ~ RECORD [
pos: INT ← -1,
roseWire: Rosemary.RoseWire, -- to print the wire name in case of error
sample: Sample, -- to read the sample
seen: PACKED SEQUENCE size: CARDINAL OF LevelSeen
];
Coverage checking
MergeSample: PROC [entry: Entry, sample: Sample] RETURNS [allSeen: BOOLTRUE] ~ {
Add information from sample into entry, return TRUE iff the result has allSeen.
FOR i: CARDINAL IN [0..entry.size) DO
SELECT sample.value[i] FROM
H => {
entry.seen[i].wasH ← TRUE;
allSeen ← allSeen AND entry.seen[i].wasL;
};
L => {
entry.seen[i].wasL ← TRUE;
allSeen ← allSeen AND entry.seen[i].wasH;
};
ENDCASE => allSeen ← allSeen AND entry.seen[i].wasH AND entry.seen[i].wasL;
ENDLOOP;
};
GetEntryKey: RedBlackTree.GetKey ~ {
Get the key for a SampleList in the RedBlackTree: it's identity...
RETURN [data]; -- keys are same as data...
};
CompareEntries: RedBlackTree.Compare ~ {
Compare key & data in the RedBlackTree
e1: Entry = NARROW [k];
e2: Entry = NARROW [data];
RETURN [Basics.CompareInt[e1.pos, e2.pos]];
};
CheckCoverage: PUBLIC PROC [handle: RoseDisplay] RETURNS [ok: BOOL] ~ {
Returns TRUE iff all nodes in the simulation reach the H and L levels. Nodes that do not are printed on the simulation log. All information is recovered from the backing file.
The algorithm is:
- build an RBT containing all of the simulations roseWires
- perform an algorithm similar to ReadSamplesUsingRBT:
- when a wire has been both H and L, remove it from RBT
- when a wire reaches the starting point and it has not been through both values, log a message & remove it from RBT
InsertInRBT: RefTab.EachPairAction ~ {
wire: Rosemary.RoseWire = NARROW[val];
data: LogData = NARROW [wire.data];
nBits: CARDINAL = data.current.size;
entry: Entry ← NEW [EntryRep[nBits]];
entry.pos ← data.lastFilePos;
entry.roseWire ← wire;
entry.sample ← NEW [SampleRec[nBits]];
FOR i: CARDINAL IN [0..nBits) DO entry.seen[i] ← [FALSE, FALSE] ENDLOOP;
IF MergeSample[entry, data.current] THEN RETURN; -- all bits have seen H and L
IF data.previous#NIL AND MergeSample[entry, data.previous] THEN RETURN; -- H,L seen
SELECT TRUE FROM
entry.pos<0 => ReportEntry[entry]; -- we've seen all about it, and it fails
RedBlackTree.LookupNode[table, entry]=NIL => RedBlackTree.Insert[table, entry, entry];
ENDCASE => NULL; -- discard the entry, it's already in the RBT somehow ...
};
ReportEntry: PROC [entry: Entry] ~ {
Report on the Rosemary typescript information about this wire not seing H and L
The algorithm to find the correct flat wire for structured wires follows exactly the method used in RosemaryImpl.InitWire.
ReportAtomic: PROC [wire: Core.Wire] ~ {
msg: ROPE;
h, l: BOOL;
[wasH: h, wasL: l] ← entry.seen[bit];
bit ← bit+1;
SELECT TRUE FROM
h AND l => RETURN; -- good bit
h => msg ← "L";
l => msg ← "H";
ENDCASE => msg ← "H nor L";
flatWire.wire ← wire;
handle.tsout.PutF["Wire %g does not go through %g\n", IO.rope[CoreFlat.WirePathRope[handle.cellType, flatWire]], IO.rope[msg]];
ok ← FALSE; -- at least one bit in error
};
flatWire: CoreFlat.FlatWireRec ← entry.roseWire.wire;
wireSize: NAT = CoreOps.WireBits[flatWire.wire];
bit: NAT ← 0;
IF entry.roseWire.currentValue=NIL AND entry.roseWire.wireDrive=infinite THEN RETURN;
IF wireSize#entry.size THEN ERROR; -- we're in BIG trouble
IF wireSize>1 THEN CoreOps.VisitRootAtomics[flatWire.wire, ReportAtomic]
ELSE ReportAtomic[flatWire.wire];
};
table: RedBlackTree.Table ← RedBlackTree.Create[GetEntryKey, CompareEntries];
LockBackingStore[handle]; -- the whole procedure assumes the backing store does not change
FlushWBuff[handle, 0]; -- ensure we are really at end of file and the buffer is empty
ok ← TRUE; -- until proven false ...
[] ← RefTab.Pairs[x: handle.simulation.coreToRoseWires, action: InsertInRBT]; -- build RBT
WHILE RedBlackTree.Size[table]#0 DO -- Read the backing file backwards
entry: Entry ← NARROW [RedBlackTree.LookupLargest[table]];
node: RedBlackTree.Node ← RedBlackTree.Delete[table, entry];
entry.pos ← ReadSample[handle.ps, entry.pos, entry.sample, 0]; -- step is ignored
IF MergeSample[entry, entry.sample] THEN LOOP; -- entry has seen H and L, discard
IF entry.pos>=0 THEN RedBlackTree.InsertNode[table, node, entry] -- keep entry active
ELSE ReportEntry[entry]; -- no more samples, but disagreement
ENDLOOP;
IO.SetIndex[handle.ps, handle.filePos]; -- go back to end of file
UnlockBackingStore[handle];
};
END.