-- ChipReticleImpl2.mesa

-- Auxiliary functions to support reticle production.

-- last modified by E. McCreight, November 23, 1982  1:40 PM
-- written by E. McCreight, May 19, 1982  3:32 PM

DIRECTORY
  ChipFeature,
  ChipNetDefs,
  ChipReticle,
  ChipUserInt,
  CoordRectPQ,
  FeaturePST,
  InlineDefs,
  ppdddefs,
  ppddefs,
  ppdefs,
  ReticleBandFormat,
  SegmentDefs,
  StreamDefs,
  StringDefs;

ChipReticleImpl2: PROGRAM
  IMPORTS ChipFeature, ChipNetDefs,
    ChipReticle, ChipUserInt,
    CoordRectPQ, FeaturePST, InlineDefs,
    ppdddefs, ppddefs, ppdefs,
    StreamDefs, StringDefs
  EXPORTS ChipReticle SHARES ChipReticle =
  BEGIN OPEN StreamDefs, StringDefs, ppdddefs, ppddefs, ppdefs,
    ChipUserInt, ChipNetDefs,
    ChipReticle, FeaturePST, CoordRectPQ;

  InitMaskStates: PUBLIC PROCEDURE[] =
    BEGIN
    hasPad, hasNBuriedContact, hasMetal2, hasCMOS, hasNDepletion:
      BOOLEAN ← FALSE;

    UnmarkList: PROC[lp: listPtr] =
      BEGIN
      FOR p: listPtr ← lp, p.nxt WHILE p#NIL DO
        UnmarkObject[p.ob];
        ENDLOOP;
      END;

    UnmarkObject: PROC[ob: obPtr] =
      BEGIN
      ob.marked ← FALSE;
      WITH dob: ob SELECT FROM
        cell => UnmarkList[dob.ptr];
        ENDCASE => NULL;
      END;


    ScanListForLayers: PROC [lp: listPtr] =
      BEGIN
      FOR p: listPtr ← lp, p.nxt WHILE p#NIL DO
        ScanObjectForLayers[p.ob];
        ENDLOOP;
      END;

    ScanObjectForLayers: PROC [ob: obPtr] =
      BEGIN
      IF NOT ob.marked THEN
        BEGIN
        ob.marked ← TRUE;
        WITH dob: ob SELECT FROM
          rect, wire =>
            SELECT ob.l FROM
              imp => hasNDepletion ← TRUE;
              met2, cut2 => hasMetal2 ← TRUE;
              pdif, nwel => hasCMOS ← TRUE;
              bur => hasNBuriedContact ← TRUE;
              ovg => hasPad ← TRUE;
              ENDCASE => NULL;
          cont =>
            SELECT dob.typ FROM
              burr => hasNBuriedContact ← TRUE;
              nwell, mPDif => hasCMOS ← TRUE;
              mmPDif => hasMetal2 ← hasCMOS ← TRUE;
              mmDif, mmPol, mmButt => hasMetal2 ← TRUE;
              ENDCASE => NULL;
          xstr =>
            BEGIN
            IF dob.impl OR dob.pullup THEN hasNDepletion ← TRUE;
            IF dob.l = pdif THEN hasCMOS ← TRUE;
            END;
          cell => ScanListForLayers[dob.ptr];
          ENDCASE => NULL;
        END;
      END;


    UnmarkList[masterList];
    ScanListForLayers[masterList];

    FOR mask: Masks IN Masks DO
      state: ReticleStatePtr ← @maskStates[mask];
      state↑ ← [
        mask: mask,
        block: uz.NEW[CoordRectBlock],
        slice: NewFeaturePST[featureZ],
        cover: NewFeaturePST[featureZ],
        inReticleSet: (SELECT mask FROM
          pad => hasPad AND NOT HeSaysYes[IF hasMetal2
            THEN "Merge pad mask with via mask?"L
            ELSE "Merge pad mask with cut mask?"L],
          nBuriedContact => hasNBuriedContact,
          via, metal2 => hasMetal2,
          nWell, nImplant, pImplant => hasCMOS,
          nDepletion => hasNDepletion,
          thinOx, poly, cut, metal => TRUE,
          ENDCASE => FALSE),
        fieldPolarity: (SELECT mask FROM
          thinOx, poly, metal, metal2 => transparent,
          ENDCASE => opaque)
        ];
      ENDLOOP;
    SetStretches[];
    Explain["Set non-standard stretches now if you wish."];
    END; -- of InitMaskStates


  FinishMask: PUBLIC PROCEDURE[state: ReticleStatePtr,
    mask: Masks,
    showMasks: BOOLEAN, screenClip: CoordRect] =
    BEGIN OPEN ReticleBandFormat;

    deltaY: DeltaY = LAST[DeltaY];
    BandBlock: TYPE = CARDINAL[0..100];
    overflowRects: ARRAY BandBlock OF CARDINAL ← ALL[0];
    overflowBandsInDeltaY: BandBlock = 1+
      ((deltaY-2)/herald.bandHeight);

    ScaleToReticle: PROCEDURE[x: Coord] RETURNS[ReticleUnit] =
      INLINE
      {RETURN[InlineDefs.LowHalf[x/coordsPerReticle]]};

    NextYMin: PROCEDURE[y: ReticleUnit] =
      BEGIN
      WHILE thisBand+herald.bandHeight<=y DO
        IF overflowRects[0]>0 THEN
          FOR b: BandBlock IN (0..overflowBandsInDeltaY) DO
            overflowRects[b-1] ← overflowRects[b];
            ENDLOOP;
        overflowRects[overflowBandsInDeltaY-1] ← 0;
        thisBand ← thisBand+herald.bandHeight;
        [] ← WriteBlock[stream: reticleFile, address: @endObject,
          words: SIZE[EndObject]];
        ENDLOOP;
      END;

    ClaimBands: PROCEDURE[y1, y2: ReticleUnit]
      RETURNS[midY: ReticleUnit] =
      BEGIN
      -- We would like to have this rectangle cover the interval from
      -- [y1..y2). Unfortunately two conditions could prevent this.
      -- The first is that that interval could be larger than DeltaY.
      -- The second is that we are only allowed to carry 1000
      -- rectangles from one band to the next.
      b: BandBlock ← 0;
      NextYMin[y1];
      y2 ← MIN[y2, y1+deltaY];
      FOR midY ← thisBand+herald.bandHeight,
        midY+herald.bandHeight WHILE midY<y2 AND
        overflowRects[b]<1000 DO
        overflowRects[b] ← overflowRects[b]+1;
        b ← b+1;
        ENDLOOP;
      midY ← MIN[midY, y2];
      END; -- of ClaimBands

    WriteRect: PROCEDURE[r: CoordRect] =
      BEGIN
      retRect: ReticleRect ← [
        x1: ScaleToReticle[r.x1],
        x2: ScaleToReticle[r.x2],
        y1: ScaleToReticle[r.y1],
        y2: ScaleToReticle[r.y2]];

      midX: ReticleUnit ← maxReticle.y-
        ClaimBands[maxReticle.y-retRect.x2, maxReticle.y-retRect.x1];

      IF retRect.x1<midX THEN
        BEGIN -- save the remainder for later
        InsertCoordRectPQ[pending, [x1: r.x1,
          x2: r.x1+coordsPerReticle*(midX-retRect.x1),
          y1: r.y1, y2: r.y2]];
        retRect.x1 ← midX;
        END;

      -- Here, for the first time, we have to know exactly how the
      -- design will be fabricated.  The reticle generator insists that
      -- its rectangles be in increasing order by min y, while at this
      -- point our CoordRect's are in decreasing order of max x.
      -- This is handled by a 90-degree rotation.  The design suffers
      -- a further mirroring because the reticle is written
      -- emulsion-up but projected emulsion-down.  This is handled
      -- by mirroring the CoordRect's y axis.

      object ← [
        xmin: maxReticle.x-retRect.y2, -- mirror in y
        deltaX: retRect.y2-retRect.y1,
        ymin: (maxReticle.y-retRect.x2)-thisBand,
        deltaY: retRect.x2-retRect.x1];

      [] ← WriteBlock[stream: reticleFile, address: @object,
        words: SIZE[Object]];
      END; -- of WriteRect

    WriteRectOnScreen: PROCEDURE[r: CoordRect] =
      BEGIN
      p1: Point ← ScalePointToChipmonk[[
        x: MAX[r.x1, screenClip.x1],
        y: MAX[r.y1, screenClip.y1]]];
      p2: Point ← ScalePointToChipmonk[[
        x: MIN[r.x2, screenClip.x2],
        y: MIN[r.y2, screenClip.y2]]];
      IF p1.x<p2.x AND p1.y<p2.y THEN
        masterList ← insertList[mp: masterList,
          lp: makeList[
            p: makeRect[x: p2.x-p1.x, y: p2.y-p1.y, l: met],
            x: p1.x, y: p1.y, o: 0, refl: 0]];
      END; -- of WriteRectOnScreen

    RecoverOriginalMasterList: PROCEDURE[] =
      BEGIN
      IF showMasks THEN
        BEGIN
        flushDel[masterList];
        masterList ← originalMasterList;
        dChange ← TRUE
        END;
      END; -- of RecoverOriginalMasterList

    object: Object ← [];
    endObject: EndObject ← [];
    maxReticle: ReticlePoint ← [
      x: 16*herald.bandWidth-1,
      y: herald.bandCount*herald.bandHeight-1];
    reticleFile, reticleRectFile: DiskHandle ← NIL;
    pending: CoordRectPQHandle ← NewCoordRectPQ[uz];
    thisBand: ReticleUnit ← 0; -- increases by herald.bandHeight
    name: STRING ← [50];
    originalMasterList: listPtr ← masterList;


    IF state.fieldPolarity=transparent AND
      state.designAreaStarted AND
      NOT state.designAreaFinished THEN
      BEGIN -- finish complemented polarity region
      FinishTransparentFeature[state: state, x: state.fieldRect.x2,
        y: [state.fieldRect.y1, state.fieldRect.y2]];
      state.designAreaFinished ← TRUE;
      END;

    IF state.file#NIL THEN
      {TruncateDiskStream[state.file]; state.file ← NIL};
    name.length ← 0;
    AppendString[to: name, from: reticleName];
    AppendChar[name, '-];
    AppendString[to: name, from: levelNames[mask]];
    AppendString[to: name, from: ".reticle"];
    reticleFile ← NewWordStream[name, WriteAppend];
    [] ← WriteBlock[stream: reticleFile, address: @herald,
      words: SIZE[HeraldObject]];

      BEGIN ENABLE UNWIND => RecoverOriginalMasterList[];
      IF showMasks THEN
        BEGIN
        p1: Point ←
          ScalePointToChipmonk[[x: screenClip.x1, y: screenClip.y1]];
        p2: Point ←
          ScalePointToChipmonk[[x: screenClip.x2, y: screenClip.y2]];
        masterList ← makeList[
          p: makeCell[sx: p2.x-p1.x, sy: p2.y-p1.y, cnt: 0, ptr: NIL],
          x: p1.x, y: p1.y, o: 0, refl: 0];
        masterList.selected ← TRUE;
        END;
      FOR i: LONG INTEGER
        DECREASING IN [0..state.rectCount) DO
        r: CoordRect;
        IF ((i+1) MOD RectsPerBlock)=0 THEN
          BEGIN
          block: CoordRectBlock;
          IF reticleRectFile=NIL THEN
            reticleRectFile ← NewWordStream[
              TempFileName[name, mask], ReadWrite];
          SetPosition[stream: reticleRectFile,
            pos: (i/RectsPerBlock)*2*SIZE[CoordRectBlock]];
            -- pos is in bytes, first byte is 0
          [] ← ReadBlock[stream: reticleRectFile, address: @block,
            words: SIZE[CoordRectBlock]];
          state.block↑ ← block;
          END;
        r ← state.block[InlineDefs.LowHalf[i MOD RectsPerBlock]];
        WHILE CoordRectPQSize[pending]>0 AND
          r.x2<=CoordRectPQMin[pending].x2 DO
          WriteRect[ExtractCoordRectPQ[pending]];
          ENDLOOP;
        WriteRect[r];
        IF showMasks THEN WriteRectOnScreen[r];
        ENDLOOP;
      WHILE CoordRectPQSize[pending]>0 DO
        WriteRect[ExtractCoordRectPQ[pending]];
        ENDLOOP;
      IF showMasks THEN
        BEGIN
        dChange ← TRUE;
        Explain[levelNames[mask], "(clipped mask)"L];
        END;
      END;

    RecoverOriginalMasterList[];
    NextYMin[maxReticle.y];
    [] ← WriteBlock[stream: reticleFile, address: @endObject,
      words: SIZE[EndObject]];
    TruncateDiskStream[reticleFile];
    IF reticleRectFile#NIL THEN
      BEGIN
      reticleRectFile.reset[reticleRectFile]; -- free up its disk space
      TruncateDiskStream[reticleRectFile];
      reticleRectFile ← NIL;
      END;
    pending ← DestroyCoordRectPQ[pending];
    END; -- of FinishMask


  WriteCoordRect: PUBLIC PROCEDURE[mask: Masks, r: CoordRect] =
    BEGIN -- called in order of increasing r.x2
    state: ReticleStatePtr ← @maskStates[mask];
    IF state.inReticleSet AND r.x1<r.x2 AND r.y1<r.y2 THEN
      BEGIN OPEN InlineDefs;
      state.block[InlineDefs.LowHalf[
        state.rectCount MOD RectsPerBlock]] ← r;
      IF state.rectCount>0 AND r.x2<state.lastRect.x2 THEN
        BEGIN
        ChipUserInt.RemarkAtPoint[RefCoordPt[state.lastRect],
          "Either this rectangle..."L];
        ChipUserInt.DebugAtPoint[RefCoordPt[r],
          "... or this one is out of order in x2."L];
        END;
      state.lastRect ← r;
      state.rectCount ← state.rectCount+1;
      IF (state.rectCount MOD RectsPerBlock)=0 THEN
        BEGIN
        block: CoordRectBlock ← state.block↑;
        IF state.file=NIL THEN
          BEGIN
          name: STRING ← [50];
          state.file ← NewWordStream[TempFileName[name, mask],
            WriteAppend];
          END;
        [] ← WriteBlock[stream: state.file, address: @block,
          words: SIZE[CoordRectBlock]];
        END;
      END;
    END; -- of WriteCoordRect


  TempFileName: PROCEDURE[name: STRING, mask: Masks]
    RETURNS[STRING] =
    BEGIN
    name.length ← 0;
    AppendString[to: name, from: "temp-"];
    AppendString[to: name, from: levelNames[mask]];
    AppendString[to: name, from: ".rects"];
    RETURN[name];
    END; -- TempFileName

  NoteFeature: PUBLIC PROCEDURE[state: ReticleStatePtr,
    f: FeaturePtr] =
    BEGIN
    IF state.inReticleSet THEN

      -- There are two possibilities here. The first is that
      -- we are outside the "aligned design" or we are inside
      -- the aligned design but working on an opaque fieldPolarity
      -- mask.  In this case we output a cover on the features.
      -- Otherwise we output a cover on the complement of
      -- the features.

      BEGIN
      IF state.fieldPolarity=opaque THEN
        StartTransparentFeature[state: state, x: f.cover.x1,
            y: [f.cover.y1, f.cover.y2]]
      ELSE -- must complement polarity of design area
        BEGIN
        CheckDesignBoundary[state: state, x: f.cover.x1];
        SELECT TRUE FROM
          NOT state.designAreaStarted,
          state.designAreaFinished,
          f.cover.y2<=state.fieldRect.y1,
          state.fieldRect.y2<=f.cover.y1 =>
            StartTransparentFeature[state: state, x: f.cover.x1,
              y: [f.cover.y1, f.cover.y2]];

          ENDCASE => -- complemented polarity region
            StartOpaqueFeature[state: state, x: f.cover.x1,
              y: [f.cover.y1, f.cover.y2]];
        END;
      END;
    InsertFeaturePST[p: state.slice, item: f];
    END; -- of NoteFeature

  ForgetFeature: PUBLIC PROCEDURE[state: ReticleStatePtr,
    f: FeaturePtr] =
    BEGIN
    DeleteFeaturePST[p: state.slice, item: f];
    IF NOT state.inReticleSet THEN RETURN;

    -- There are the same two possibilities here.

    IF state.fieldPolarity=opaque THEN
      FinishTransparentFeature[state: state, x: f.cover.x2,
        y: [f.cover.y1, f.cover.y2]]
    ELSE
      BEGIN
      CheckDesignBoundary[state: state, x: f.cover.x2];
      SELECT TRUE FROM
        NOT state.designAreaStarted,
        state.designAreaFinished,
        f.cover.y2<=state.fieldRect.y1,
        state.fieldRect.y2<=f.cover.y1 =>
          FinishTransparentFeature[state: state, x: f.cover.x2,
            y: [f.cover.y1, f.cover.y2]];

        ENDCASE => -- complemented polarity region
          FinishOpaqueFeature[state: state, x: f.cover.x2,
            y: [f.cover.y1, f.cover.y2]];
      END;
    END; -- of ForgetFeature


  CheckDesignBoundary: PROCEDURE[state: ReticleStatePtr,
    x: Coord] =
    BEGIN -- only for fieldPolarity=transparent
    IF state.fieldRect.x1<=x AND
      NOT state.designAreaStarted THEN
      BEGIN -- start complemented polarity region
      StartTransparentFeature[state: state, x: state.fieldRect.x1,
        y: [state.fieldRect.y1, state.fieldRect.y2]];
      state.designAreaStarted ← TRUE;
      END;
    IF state.fieldRect.x2<x AND
      NOT state.designAreaFinished THEN
      BEGIN -- finish complemented polarity region
      FinishTransparentFeature[state: state, x: state.fieldRect.x2,
        y: [state.fieldRect.y1, state.fieldRect.y2]];
      state.designAreaFinished ← TRUE;
      END;
    END; -- of CheckDesignBoundary

  StartTransparentFeature: PROCEDURE[state: ReticleStatePtr, x: Coord,
    y: Interval] =
    BEGIN
      -- cover is transparent, slice is transparent,
      -- so cover is union of slice
    minField: Interval ← MinField[p: state.cover, y: y];
    IF minField.min<minField.max THEN
      BEGIN
      coverInt: Interval ← TerminateCover[p: state.cover, x: x,
        y: minField, mask: state.mask];
      InsertFeaturePST[p: state.cover,
        item: NewReticleFeature[
          cover: [x1: x, x2: 0 -- not used --,
            y1: coverInt.min, y2: coverInt.max], mask: state.mask]];
      END;
    END; -- of StartTransparentFeature


  StartOpaqueFeature: PROCEDURE[state: ReticleStatePtr, x: Coord,
    y: Interval] =
    BEGIN
      -- cover is transparent, slice is opaque,
      -- so cover is complement of union of slice
    coverInt: Interval ← TerminateCover[p: state.cover, x: x, y: y,
        mask: state.mask];
    IF coverInt.min<y.min THEN
      InsertFeaturePST[p: state.cover,
        item: NewReticleFeature[
          cover: [x1: x, x2: 0 -- not used --,
            y1: coverInt.min, y2: y.min], mask: state.mask]];
    IF y.max<coverInt.max THEN
      InsertFeaturePST[p: state.cover,
        item: NewReticleFeature[
          cover: [x1: x, x2: 0 -- not used --,
            y1: y.max, y2: coverInt.max], mask: state.mask]];
    END; -- of StartOpaqueFeature

  FinishTransparentFeature: PROCEDURE[state: ReticleStatePtr, x: Coord,
    y: Interval] =
    BEGIN
      -- cover is transparent, slice is transparent,
      -- so cover is union of slice
    minField: Interval ← MinField[p: state.slice, y: y];
    IF minField.min<minField.max THEN
      BEGIN

      RenewFeatureCover: PROCEDURE[int: Interval,
        repItem: FeaturePtr] =
        BEGIN
        InsertFeaturePST[p: state.cover,
          item: NewReticleFeature[
            cover: [x1: x, x2: 0 -- not used --,
              y1: int.min, y2: int.max], mask: state.mask]];
        END; -- of RenewFeatureCover

      coverInt: Interval ← TerminateCover[p: state.cover,
        x: x, y: minField, mask: state.mask];
      ClassifyFeaturePSTInterval[p: state.slice, int: coverInt,
        covered: RenewFeatureCover, gap: ReticleNullGap];
      END;
    END; -- of FinishTransparentFeature


  FinishOpaqueFeature: PROCEDURE[state: ReticleStatePtr, x: Coord,
    y: Interval] =
    BEGIN
      -- cover is transparent, slice is opaque,
      -- so cover is complement of union of slice

    RenewFieldCover: PROCEDURE[int: Interval] =
      BEGIN
      InsertFeaturePST[p: state.cover,
        item: NewReticleFeature[
          cover: [x1: x, x2: 0 -- not used --,
            y1: int.min, y2: int.max], mask: state.mask]];
      END; -- of RenewFieldCover

    coverInt: Interval ← TerminateCover[p: state.cover, x: x, y: y,
      mask: state.mask];
    ClassifyFeaturePSTInterval[p: state.slice, int: coverInt,
      covered: ReticleNullCover, gap: RenewFieldCover];
    END; -- of FinishOpaqueFeature

  MinField: PROCEDURE[p: FeaturePSTHandle, y: Interval]
    RETURNS[Interval] =
    BEGIN
    minField: Interval ← y;

    ReduceField: PROCEDURE[int: Interval, repItem: FeaturePtr] =
      BEGIN
      SELECT TRUE FROM
        int.min=y.min => minField.min ← int.max;
        int.max=y.max => minField.max ← int.min;
        ENDCASE => NULL;
      END; -- of ReduceField

    ClassifyFeaturePSTInterval[p: p, int: y,
      covered: ReduceField, gap: ReticleNullGap];
    RETURN[minField];
    END; -- of MinField


  TerminateCover: PROCEDURE[p: FeaturePSTHandle, x: Coord,
    y: Interval, mask: Masks] RETURNS[Interval] =
    BEGIN

    TouchedFeatureList: TYPE = LONG POINTER TO
      TouchedFeature ← NIL;
    TouchedFeature: TYPE = RECORD[
      next: TouchedFeatureList,
      f: FeaturePtr];

    list: TouchedFeatureList ← NIL;
    int: Interval ← y;

    TouchFeature: PROCEDURE[item: FeaturePtr] =
      BEGIN
      list  ← uz.NEW[TouchedFeature ← [next: list, f: item]];
      int ← [MIN[int.min, item.cover.y1],
        MAX[int.max, item.cover.y2]];
      END; -- of TouchFeature

    SearchFeaturePST[p: p, int: y, touch: TouchFeature];

    WHILE list#NIL DO
      t: TouchedFeatureList ← list.next;
      WriteCoordRect[mask: mask,
        r: [x1: list.f.cover.x1, x2: x,
          y1: list.f.cover.y1, y2: list.f.cover.y2]];
      DeleteFeaturePST[p: p, item: list.f];
      list.f ← ChipFeature.DestroyFeature[list.f];
      uz.FREE[@list];
      list ← t;
      ENDLOOP;

    RETURN[int];
    END; -- of TerminateCover


  ReticleNullCover: PROCEDURE[int: Interval, repItem: FeaturePtr] =
    {NULL};


  ReticleNullGap: PROCEDURE[int: Interval] = {NULL};


  END. -- of ChipReticleImpl2