-- Wiring.mesa
-- last modified by C. Jacobi, January 26, 1983 9:51 am

DIRECTORY
 DoradoBoard,
 Environment USING [bytesPerWord],
 FileIO USING [Open, OpenFailed],
IO USING [BreakProc, Close, EndOf, GetChar, GetInt,
  GetRope, GetToken, SkipOver, STREAM, UnsafeGetBlock, WhiteSpace,
  PutFR, int,rope,PutRope,CreateViewerStreams],
 MessageWindow USING [Append],
 Rope USING [Concat, Equal, ROPE];

Wiring: CEDAR PROGRAM

IMPORTS FileIO, IO, MessageWindow, Rope, DoradoBoard
EXPORTS DoradoBoard =

BEGIN OPEN DoradoBoard;

------ global module values ------

crCount: INTEGER ← 0; -- klugey way to count double CR's
CR: CHAR = '\n;
SP: CHAR = ' ;


ReadASIFile: PROC [state: Board, boardName: Rope.ROPE] =
-- Initialize 'pads' array with information from .asi file.
TRUSTED BEGIN
 count: PadIndex;
 fileName: Rope.ROPE = Rope.Concat[boardName, ".asi"];
 state.padCount ← 0;
 state.asiFile ← FileIO.Open[fileName, read
  ! FileIO.OpenFailed => {state.asiFile ← NIL; CONTINUE}];
IF state.asiFile = NIL THEN {FileError[state,fileName, NeedFile]; RETURN};
IF GetCardinal[state] # ASISeal THEN
  {FileError[state, fileName, ASISealError]; RETURN};
 count ← GetCardinal[state];
 [] ← GetCardinal[state];
FOR i: CARDINAL IN [0 .. count) DO
  state.pads[i].p ← GetPoint[state];
  state.pads[i].con ← GetCardinal[state];
  state.pads[i].type ← ASItoFluke[ state.pads[i].p.x, state.pads[i].p.y];
  IF state.pads[i].con >= canonWithoutSegs THEN --if the pad is canonical, give it a SegTab
   BEGIN
   state.pads[i].segs ← NEW[SegTab];
   IF state.pads[i].con = canonWithSegs THEN FOR layer: WiringLayer IN WiringLayer DO
   state.pads[i].segs.l[layer] ← GetInt[state]; --get the filepos's for the segments on each layer
    ENDLOOP;
   state.pads[i].con ← i; --and point the pad to itself
   END
  ELSE BEGIN
   can: PadIndex ← state.pads[i].con; --canonical pad for the current pad
   state.pads[i].segs ← NIL; --no SegTab for this pad
   state.pads[i].con ← state.pads[can].con; --put this pad on the list for its canonical pad
   state.pads[can].con ← i;
   state.pads[can].segs.padCount ← state.pads[can].segs.padCount + 1;
   END
  ENDLOOP;
 state.padCount ← count;
END; -- of ReadASIFile --


GetCardinal: PUBLIC PROC [state: Board] RETURNS [v: CARDINAL] =
TRUSTED BEGIN
IF state.asiFile.UnsafeGetBlock[[base: @v, startIndex: 0,
  stopIndexPlusOne: SIZE[CARDINAL]*Environment.bytesPerWord]]
  # SIZE[CARDINAL]*Environment.bytesPerWord THEN ERROR;
END; -- of GetCardinal --


GetInt: PUBLIC PROC [state: Board] RETURNS [v: INT] =
TRUSTED BEGIN
IF state.asiFile.UnsafeGetBlock[[base: @v, startIndex: 0,
  stopIndexPlusOne: SIZE[INT]*Environment.bytesPerWord]]
  # SIZE[INT]*Environment.bytesPerWord THEN ERROR;
END; -- of GetInt --


GetPoint: PUBLIC PROC [state: Board] RETURNS [v: Point] =
TRUSTED BEGIN
IF state.asiFile.UnsafeGetBlock[[base: @v, startIndex: 0,
  stopIndexPlusOne: SIZE[Point]*Environment.bytesPerWord]]
  # SIZE[Point]*Environment.bytesPerWord THEN ERROR;
END; -- of GetPoint --


ReadBoardData: PUBLIC PROC [state: Board, boardName: Rope.ROPE] =
-- The purpose of this procedure is to read the portion of the ASI file that describes
--the pads, and to associate net names (from the associated .wl file) with each of the
--nets in the ASI file. Because ASI was allowed to reposition terminators in the course
--of laying out the board, this is nontrivial. First, the ASI file is read, then the .wl file
--is read one signal at a time. For each pad in a net in the .wl file, the corresponding
--canonical pad in the ASI file is found, and gets one vote. When all the pads in
--a net have been done, the canonical pad with the most votes gets the name from the .wl file
--if there is confusion, a message is output.
TRUSTED BEGIN
 ch: CHAR;
 fileHandle: IO.STREAM;
 votes, mismatches: CARDINAL ← 0;
 fileName: Rope.ROPE = Rope.Concat[boardName, ".wl"];

 ReadASIFile[state, boardName]; --read the ASI file
 fileHandle ← FileIO.Open[fileName, read !
  FileIO.OpenFailed => {fileHandle ← NIL; CONTINUE}];
IF fileHandle = NIL THEN {FileError[state, fileName, NeedFile]; RETURN};
IO.SkipOver[fileHandle, AtBreak]; -- skip over to @
IF IO.EndOf[fileHandle] THEN {FileError[state, fileName, EndOfFile]; RETURN};
 [] ← IO.GetChar[fileHandle]; -- get @
IO.SkipOver[fileHandle, IO.WhiteSpace]; -- skipping over first double CR after @
IO.SkipOver[fileHandle, EatDoubleCR]; -- skipping over 'CALIBRATE'
IO.SkipOver[fileHandle, IO.WhiteSpace];
UNTIL IO.EndOf[fileHandle] DO-- go through this loop once for each signal in the .wl file
  PollRec: TYPE = RECORD [
   index, votes: CARDINAL
   ];
  signal: Rope.ROPE;
  candidates, bestCandidate, highestVote: CARDINAL ← 0;
  maxCandidates: CARDINAL = 20;
  poll: ARRAY [0 .. maxCandidates) OF PollRec;

  IO.SkipOver[fileHandle, IO.WhiteSpace];
  signal ← NextSignal[fileHandle]; --this is the signal name
  IO.SkipOver[fileHandle, CrBreak];
  UNTIL IO.EndOf[fileHandle] DO-- go through this loop once per node
   asiIndex: CARDINAL;
   wl: Point;
   found: BOOL;
   [] ← IO.GetRope[fileHandle, IO.WhiteSpace];
   [] ← IO.GetToken[fileHandle]; -- get {
   wl.x ← IO.GetInt[fileHandle];
   IO.SkipOver[fileHandle, CommaBreak];
   wl.y ← IO.GetInt[fileHandle];
   [] ← IO.GetToken[fileHandle]; -- get }
   [found, asiIndex] ← Search[state,
    [x: 4200+25*wl.x, y: 14410-25*wl.y] -- .wl point transformed to .asi space --
    ]; --Search returns the index of the canonical pad for the pad with the given coordinates
   IF found THEN
    FOR i: CARDINAL IN [0 .. candidates) DO
    IF poll[i].index = asiIndex THEN
     {poll[i].votes ← poll[i].votes + 1; EXIT};
    REPEAT
     FINISHED => IF candidates < maxCandidates THEN
      BEGIN
      poll[candidates] ← [index: asiIndex, votes: 1];
      candidates ← candidates + 1;
      END;
    ENDLOOP
   ELSE mismatches ← mismatches+1;
   IF NOT IO.EndOf[fileHandle] THEN ch ← IO.GetChar[fileHandle];
   IF ch = CR THEN
    IF NOT IO.EndOf[fileHandle] THEN ch ← IO.GetChar[fileHandle];
   IF ch = CR THEN EXIT
   ELSE IO.SkipOver[fileHandle, IO.WhiteSpace];
   ENDLOOP;

  -- determine which pad should be given the signal name
  IF candidates>0 THEN
   BEGIN
   confusion: BOOLFALSE;
    FOR i: CARDINAL IN [0 .. candidates) DO {
    IF poll[i].votes = highestVote THEN confusion ← TRUE;
     IF poll[i].votes > highestVote THEN
     { [index: bestCandidate, votes: highestVote] ← poll[i]; confusion ←FALSE}; }
    ENDLOOP;
    IF confusion THEN
    BEGIN
    PutError[state,IO.PutFR[format: "*nConfusion about name %g for index %g ",
    v1: IO.rope[signal], v2: IO.int[bestCandidate]]];
    FOR i: CARDINAL IN [0..candidates) DO PutError[state,
     IO.PutFR[format: "*n*tindex: %g, votes: %g, x: %g, y: %g, count: %g",
     v1: IO.int[poll[i].index],
     v2: IO.int[poll[i].votes],
     v3: IO.int[state.pads[poll[i].index].p.x],
     v4: IO.int[state.pads[poll[i].index].p.y],
     v5: IO.int[state.pads[poll[i].index].segs.padCount]]]
     ENDLOOP;
    END;
    IF state.pads[bestCandidate].segs = NIL THEN
    state.pads[bestCandidate].segs ← NEW[SegTab ← []];
   state.pads[bestCandidate].segs.sigName ← signal;
   END;
  ENDLOOP; -- get next signal
IF mismatches>0 THEN
  PutError[state, IO.PutFR[format: "*n*nWire list and ASI file mismatched at %g pads.",v1: IO.int[mismatches]]];
IO.Close[fileHandle];
END; -- of ReadFile --

PutError: PROC[state: Board,r: Rope.ROPE] =
BEGIN
IF state.errorOutStream = NIL THEN [state.errorInStream, state.errorOutStream] ←
IO.CreateViewerStreams["DisplayBoardErrors"];
IO.PutRope[state.errorOutStream,r];
END;




Search: PROC [state: Board, target: Point] RETURNS [found: BOOLEAN, asiIndex: CARDINAL] =
-- Binary search procedure.
BEGIN
 lower: INTEGER ← 0;
 upper: INTEGER ← state.padCount-1;
WHILE lower <= upper DO
  i: INTEGER ← (lower+upper)/2;
  SELECT state.pads[i].p.x FROM
   <target.x => lower ← i+1;
   >target.x => upper ← i-1;
   ENDCASE => SELECT state.pads[i].p.y FROM
    <target.y => lower ← i+1;
    >target.y => upper ← i-1;
    ENDCASE =>
     RETURN[TRUE, GetCanonicalPad[state,i]];
  ENDLOOP;
RETURN[FALSE, 0];
END; -- of Search --


FileError: PUBLIC PROC [state: Board, file: Rope.ROPE, error: ErrorType] =
TRUSTED BEGIN
 PutError[state,"*n-- ERROR in file: "];
 PutError[state,file];
 PutError[state, SELECT error FROM
  ASISealError => " Unknown ASISeal",
  EndOfFile =>" (Internal error) Attempt to read beyond end of file",
  NeedFile =>" File needed on disk",
  IllegalFile =>" Illegal file name",
  InvalidSignal =>" Attempt to read invalid signal (or character)",
  ENDCASE => " (Internal error) Undetermined! "];

END; -- of FileError --

RemoveSignal: PUBLIC PROC [state: Board, signal: Rope.ROPE] RETURNS [BOOLEANTRUE] =
-- Remove a signal from the signalPads list.
TRUSTED BEGIN
  IF state.signalPads = NIL THEN RETURN[FALSE];
  IF Rope.Equal[state.pads[state.signalPads.first].segs.sigName, signal, FALSE] THEN
   BEGIN
   state.signalPads ← state.signalPads.rest; RETURN[TRUE];
   END;
  
  
  FOR s: SigPadList ← state.signalPads, s.rest WHILE s.rest # NIL DO
   IF Rope.Equal[state.pads[s.rest.first].segs.sigName, signal, FALSE] THEN
    BEGIN
    s.rest ← s.rest.rest;
    RETURN[TRUE];
    END;
   ENDLOOP;
RETURN[FALSE];
END; -- of RemoveSignal --




AddSignal: PUBLIC PROC [state: Board, signal: Rope.ROPE] RETURNS [BOOLEANTRUE] =
-- Add given signal (or the hit pad) to the signalPads list.
TRUSTED BEGIN
IF signal=NIL OR Rope.Equal[signal, "? ? ?"] THEN --use the hit pad if there is no valid signal name
  BEGIN
  IF state.hitPadIndex >=state.padCount THEN RETURN[FALSE];
  state.signalPads ← CONS[GetCanonicalPad[state,state.hitPadIndex], state.signalPads];
  RETURN[TRUE];
  END
ELSE --search for the name and put its pad on the signalPads list
  FOR count: CARDINAL IN [0 ..state.padCount) DO
   IF state.pads[count].segs # NIL AND
    Rope.Equal[state.pads[count].segs.sigName, signal, FALSE] THEN
    BEGIN
    state.signalPads ← CONS[count, state.signalPads];
    RETURN[TRUE];
    END;
   ENDLOOP;
RETURN[FALSE];
END; -- of AddSignal --


FindClosestPad: PUBLIC PROC [state: Board, p: Point]
RETURNS [pad: PadIndex, sigName: Rope.ROPE] =
TRUSTED BEGIN
 canon: PadIndex;
 x,y: INTEGER;
 sc,pin: INTEGER ← 0;
 pt: PadType;
 ty: Rope.ROPE;

 startIndex: PadIndex = MinPadGE[state: state, x: p.x];
 bestDist: INTLAST[INT];
IF state.padCount <= 0 THEN RETURN[0, NIL];
 pad ← 0; -- any legal pad
FOR i: PadIndex IN [startIndex..state.padCount) WHILE
  IntSquare[p.x-state.pads[i].p.x] -- best distance possible at this x -- < bestDist DO
  IF Distance[state.pads[i].p, p] < bestDist THEN
   BEGIN
   pad ← i;
   bestDist ← Distance[state.pads[i].p, p];
   END;
  ENDLOOP;
FOR i: PadIndex DECREASING IN [0..startIndex) WHILE
  IntSquare[p.x-state.pads[i].p.x] -- best distance possible at this x -- < bestDist DO
  IF Distance[state.pads[i].p, p] < bestDist THEN
   BEGIN
   pad ← i;
   bestDist ← Distance[state.pads[i].p, p];
   END;
  ENDLOOP;
 x ← state.pads[pad].p.x;
 y←state.pads[pad].p.y;
 pt ← state.pads[pad].type;

IF pt.t # noProbe THEN {sc←pt.n/128 + 1; pin ← pt.n MOD 128 + 1};
--format channel no. as ScanCard - Pin

 ty ← SELECT pt.t FROM
  noProbe => "noProbe",
  signal => "Signal",
  gnd => "Gnd",
  vdd => "Vdd",
  vee => "Vee",
  vtt => "Vtt",
  vcc => "Vcc",
  ENDCASE => "??";

 MessageWindow.Append [
  message: IO.PutFR[format: "Pad has ASI coordinates [x: %g, y: %g] (Fluke %g-%g {%g})",
   v1: IO.int[x], v2: IO.int[y], v3: IO.int[sc], v4: IO.int[pin], v5: IO.rope[ty]],
  clearFirst: TRUE
  ];
 canon ← GetCanonicalPad[state,pad];
 sigName ← IF state.pads[canon].segs.sigName # NIL THEN state.pads[canon].segs.sigName
  ELSE "? ? ?";
END; -- FindClosestPad --

GetCanonicalPad: PUBLIC PROC [state: Board, index: PadIndex] RETURNS [pindex: PadIndex] =
BEGIN
WHILE state.pads[index].segs = NIL DO index ← state.pads[index].con ENDLOOP;
RETURN[index];
END;

MinPadGE: PUBLIC PROC [state: Board, x: Mils] RETURNS [minIndex: PadIndex] =
-- Returns smallest index minIndex such that x<=state.pads[minIndex].p.x.
BEGIN
 upper: INTEGER ← state.padCount-1;
 lower: INTEGER ← 0;
WHILE lower <= upper DO
  i: INTEGER ← (lower+upper)/2;
  SELECT state.pads[i].p.x FROM
   <x => lower ← i+1;
   ENDCASE => upper ← i-1;
  ENDLOOP;
RETURN[lower];
END; -- of MinPadGE --


IntSquare: PROC [x: INT] RETURNS [INT] = INLINE {RETURN[x*x]};

Distance: PROC [first, second: Point] RETURNS [distance: INT] =
INLINE {RETURN[IntSquare[second.x - first.x] + IntSquare[second.y - first.y]]};


NextSignal: PROC [fileHandle: IO.STREAM] RETURNS [signal: Rope.ROPE] =
TRUSTED BEGIN
IF NOT IO.EndOf[fileHandle] THEN signal ← IO.GetRope[fileHandle, ColonBreak, NIL]
ELSE signal ← Rope.Concat[signal, "****"];
END; -- of NextSignal --


AtBreak: IO.BreakProc =
TRUSTED BEGIN
IF c = '@ THEN RETURN[KeepGoing]
ELSE RETURN[StopAndPutBackChar];
END; -- of AtBreak --


ColonBreak: IO.BreakProc =
TRUSTED BEGIN
IF c = ': THEN RETURN[StopAndTossChar]
ELSE RETURN[KeepGoing];
END; -- of ColonBreak --


CommaBreak: IO.BreakProc =
TRUSTED BEGIN
IF c = ', THEN RETURN[StopAndTossChar]
ELSE RETURN[KeepGoing];
END; -- of CommaBreak --


CrBreak: IO.BreakProc =
TRUSTED BEGIN
IF c = CR THEN RETURN[KeepGoing]
ELSE RETURN[StopAndTossChar];
END; -- of CrBreak --


EatDoubleCR: IO.BreakProc =
TRUSTED BEGIN
IF c = CR THEN
  BEGIN
  crCount ← crCount + 1;
  IF crCount = 2 THEN BEGIN
   crCount ← 0;
   RETURN[KeepGoing];
   END
  ELSE RETURN[StopAndTossChar];
  END
ELSE {crCount ← 0; RETURN[StopAndTossChar]};
END; -- of EatDoubleCR --


END. -- of Wiring --


CHANGE LOG

Created by L. Hilton, September 9, 1982 7:05 pm