-- Subroutine to generate CIF from Chipmonk

-- last modified by Dillon, March 12, 1984  9:23 PM
  -- to implement weak depletion thresholds
-- last modified by McCreight, December 21, 1983  2:40 PM
  -- to handle zero-threshold NMOS transistors
-- adapted from ppio.mesa by McCreight, November 9, 1982  5:09 PM

DIRECTORY
  ChipOrient,
  ChipUserInt,
  InlineDefs,
  StreamDefs,
  ppdddefs,
  ppddefs,
  ppdefs,
  ppMainDefs,
  pppdefs,
  ppoutdefs,
  TimeDefs,
  ZoneAllocDefs;

CIFGen: PROGRAM
  IMPORTS
    ChipOrient, ChipUserInt, InlineDefs,
    ppdefs, ppddefs, ppdddefs, ppMainDefs, pppdefs,
    StreamDefs, TimeDefs, ZoneAllocDefs
  EXPORTS ppdefs =
  BEGIN
  OPEN InlineDefs, StreamDefs, ppdefs, ppddefs, ppdddefs,
    ChipOrient, ChipUserInt;

  aux: PUBLIC TYPE = CifCell;

  CifCellPtr: TYPE = LONG POINTER TO CifCell;
  CifCell: TYPE = RECORD[id: CellId];
  CellId: TYPE = CARDINAL;


  stillInterestedInOffGrid, stillInterestedInShortingContacts: BOOLEAN ← TRUE;

  cifLevelName: ARRAY level OF Atom;

  chipmonkLayName: ARRAY level OF STRING ←
    [cut: "cut",
    dif: "dif",
    pol: "pol",
    met: "met",
    imp: "imp",
    ovg: "ovg",
    bur: "bur",
    snerd: "snerd",
    cut2: "cut2",
    pdif: "pdif",
    pwelCont: "pwelCont",
    met2: "met2",
    pwel: "pwel",
    nwel: "nwel",
    nwelCont: "nwelCont",
    NOcOL: "NOcOL"];

  usedLevel: ARRAY level OF BOOLEAN ← ALL[FALSE];
  resolution: LONG INTEGER;
  isCMOS: BOOLEAN;

  infinity: locNum = LAST[locNum];

  cellCnt: CellId ← 0;
  cifFile: StreamDefs.DiskHandle ← NIL;

  levelAnnounced: BOOLEAN ← FALSE;
  curLevel: level;
  cifScale: LONG INTEGER ← 200; -- CIF units per Lambda

  cifDrR: drRecord ← [
    [x1: -infinity, y1: -infinity, x2: infinity, y2: infinity],
    [x1: -infinity, y1: -infinity, x2: infinity, y2: infinity],
    cifOrArea, cifOrArea,
    nullOutl, nullCifDrawText, 0];

  cifDrContR: drRecord ← [
    [x1: -infinity, y1: -infinity, x2: infinity, y2: infinity],
    [x1: -infinity, y1: -infinity, x2: infinity, y2: infinity],
    cifOrContact, cifOrContact,
    nullOutl, nullCifDrawText, 0];

  cifDrXstrR: drRecord ← [
    [x1: -infinity, y1: -infinity, x2: infinity, y2: infinity],
    [x1: -infinity, y1: -infinity, x2: infinity, y2: infinity],
    cifOrXstr, cifOrXstr,
    nullOutl, nullCifDrawText, 0];

  nullOutl: PROCEDURE[a, b, c, d: INTEGER, q: color,
    p: POINTER TO Rect] = {NULL};

  nullCifDrawText: PROCEDURE[x, y, sx, sy: INTEGER,
    s: STRING, pz: POINTER TO Rect] = {NULL};


  lastCellName: LONG STRING ← "";
  cellBeingDefined: cellPtr ← NIL;

  cifDefineObject: PROC [ob: obPtr] =
    BEGIN

    SymHeader: PROC =
      BEGIN
      cifOutStr["DS "];
      cellCnt ← cellCnt+1;
      cifOutNum[cellCnt];
      ob.auxPnt ← uz.NEW[CifCell ← [id: cellCnt]];
      cifOutStr[" "];
      cifOutNum[cifScale];  -- CIF units per Lambda
      cifOutStr[" "];
      cifOutNum[resolution*Lambda];  -- output units per Lambda
      cifOutEndCom[];
      END;

    SymTrailer: PROC =
      BEGIN
      cifOutStr["DF"];
      cifOutEndCom[];
      END;

    GenerateGeometricOb: PROC [ob: obPtr, dr: POINTER TO drRecord] =
      BEGIN
      SymHeader[];
      FOR curLevel IN level DO
          BEGIN
          levelAnnounced ← FALSE;
          ob.p.drawme[0][ob, 0, 0, dr];
          END;
        ENDLOOP;
      SymTrailer[];
      END;

    IF ob.auxPnt#NIL THEN RETURN; -- already defined

    WITH dob: ob SELECT FROM
      wire, rect => NULL;

      cell =>
        BEGIN
        pp: listPtr;
        FOR pp ← dob.ptr, pp.nxt WHILE pp # NIL DO
          cifDefineObject[pp.ob];
          ENDLOOP;

        SymHeader[];
    
        cellBeingDefined ← @dob;
        IF dob.ptr=masterList THEN
          cifDrawCellName["TopLevelDesign"]
        ELSE
          FOR cl: LONG POINTER TO cList ← cellList, cl.nxt
            WHILE cl#NIL DO
            IF cl.ob = @dob THEN
              {cifDrawCellName[cl.name]; EXIT};
            REPEAT
              FINISHED => cifDrawCellName[("unnamed cell")];
            ENDLOOP;

        FOR pp ← dob.ptr, pp.nxt WHILE pp # NIL DO

          -- first call all interior cells
          WITH cob: pp.ob SELECT FROM
            rect, wire => NULL;
            ENDCASE =>
              BEGIN
              refCorner: Rect = ChipOrient.MapRect[
                itemInCell: [0, 0, 0, 0],
                cellSize: [x: cob.size[0], y: cob.size[1]],
                cellInstOrient: pp.idx,
                cellInstPos: [x: pp.lx, y: pp.ly]];
              cifSymbolCall[@cob];
              IF pp.idx # 0 THEN
                BEGIN
                jj: CARDINAL;
                IF (jj ← BITAND[pp.idx, 12]) # 0 THEN
                  BEGIN
                  cifOutStr[" R "];
                  cifOutStr[SELECT jj FROM
                    4 => "0,1",
                    8 => "-1,0",
                    12 => "0,-1",
                    ENDCASE => "1,0" -- we'll never use this one --];
                  END;
                IF BITAND[pp.idx, 1] # 0 THEN cifOutStr[" M X"];
                END;
              IF refCorner.x1#0 OR refCorner.y1#0 THEN
                BEGIN
                cifOutStr[" T "];
                cifOutPoint[refCorner.x1, refCorner.y1];
                END;
              cifOutEndCom[];
              END;
          ENDLOOP;

        -- next generate all rectangles, by layer
        FOR curLevel IN level DO
            BEGIN
            levelAnnounced ← FALSE;
            FOR pp ← dob.ptr, pp.nxt WHILE pp # NIL DO
              WITH cob: pp.ob SELECT FROM
                rect, wire => cob.p.drawme[pp.idx][@cob, pp.lx, pp.ly, @cifDrR];
                ENDCASE => NULL;
              ENDLOOP;
            END;
          ENDLOOP;

        -- generate all signal names
        FOR pp ← dob.ptr, pp.nxt WHILE pp # NIL DO
          FOR prop: propPtr ← pp.props, prop.next WHILE prop # NIL DO
            IF prop.attribute=signalName THEN WITH cob: pp.ob SELECT FROM
              wire =>
                cifLabelTerminal[pp, AtomToString[prop.value], pp.ob.l];
              cont =>
                BEGIN
                lev: level = (SELECT cob.typ FROM
                  burr => pol,
                  ENDCASE => met);
                cifLabelTerminal[pp, AtomToString[prop.value], lev];
                END;
              ENDCASE => NULL;
            ENDLOOP;
          ENDLOOP;

        -- generate all other properties as comments for now
        FOR pp ← dob.ptr, pp.nxt WHILE pp # NIL DO
          FOR prop: propPtr ← pp.props, prop.next WHILE prop # NIL DO
            IF prop.attribute#signalName THEN
              cifPutProperty[pp, AtomToString[prop.attribute], AtomToString[prop.value]];
            ENDLOOP;
          ENDLOOP;

        -- generate all other properties as comments for now
        FOR pp ← dob.ptr, pp.nxt WHILE pp # NIL DO
          WITH cob: pp.ob SELECT FROM
            cont =>
              IF cob.typ=difShort AND stillInterestedInShortingContacts THEN
                stillInterestedInShortingContacts ←
                  RemarkAboutCell[p: [pp.lx, pp.ly],
                    remark: "I'm not sure I will generate the right CIF for this shorting contact.."];
            ENDCASE => NULL;
          ENDLOOP;

        SymTrailer[];
        END; -- of cell

      cont => -- contact
        -- For ordinary CMOS geometries, where p-diffusion and
        -- n-diffusion are separated from
        -- one another by >= 3 lambda, a one-lambda enlarge (per side)
        -- of p is not a problem.  Things get
        -- more problematic in the combined source/substrate contact, where the best
        -- place to put the p/n interface is where it is drawn.  This is not
        -- a complete solution, but I think it will work in the interim.
        GenerateGeometricOb[ob: @dob,
          dr: IF dob.typ=difShort THEN @cifDrContR ELSE @cifDrR];

      xstr => -- transistor
        BEGIN
        depletionStrength ← dob.impl;
        GenerateGeometricOb[ob: @dob, dr: @cifDrXstrR];
        END;

      ENDCASE => -- geometry
        GenerateGeometricOb[ob: @dob, dr: @cifDrR];

    END; -- of cifDefineObject


  cifSymbolCall: PROCEDURE[ob: obPtr] =
    BEGIN
    cp: CifCellPtr = ob.auxPnt;
    IF cp=NIL THEN ERROR;
    cifOutStr["C "];
    cifOutNum[cp.id];
    END;

  cifOrArea: PROCEDURE [x1, y1, x2, y2: INTEGER, l: level,
    p: POINTER TO Rect] =
    {cifRectOut[x1: x1, y1: y1, x2: x2, y2: y2, l: l]};

  cifOrContact: PROCEDURE [x1, y1, x2, y2: INTEGER, l: level,
    p: POINTER TO Rect] =
    {cifRectOut[x1: x1, y1: y1, x2: x2, y2: y2, l: l, avoidEnlarge: TRUE]};

  depletionStrength: DepletionStrength; -- set by cifDefineObject
  pwelUsedByNMOS, nwelUsedByNMOS, fourNMOSThresholds: BOOLEAN ← FALSE;
  
  cifOrXstr: PROCEDURE [x1, y1, x2, y2: INTEGER, l: level,
    p: POINTER TO Rect] =
    BEGIN
    SELECT l FROM
      imp =>
        IF fourNMOSThresholds THEN
          SELECT depletionStrength FROM
            -- OLD Implant schedule for NSIL-III:
            -- enhancement: no mask
            -- zeroThresh: mask I2 (pwel layer)
            -- weakDepletion: mask I (imp layer)
            -- strongDepletion: masks I & I2
            -- NEW (4/10/84) Implant schedule for NSIL-III:
            -- enhancement: no mask
            -- zeroThresh: mask I0 (pwel layer)
            -- weakDepletion: mask I1 (nwel layer)
            -- strongDepletion: masks I (imp layer)
            strongDepletion =>
              BEGIN
              -- cifRectOut[x1: x1, y1: y1, x2: x2, y2: y2, l: l, avoidEnlarge: TRUE];
              -- levelAnnounced ← FALSE;
              -- l ← pwel;
                           -- strongDepletion gets implanted again
              END;
            zeroThresh =>
              l ← pwel;
            weakDepletion =>
              l ← nwel;
            ENDCASE -- other thresholds -- => NULL;
      ENDCASE -- other levels -- => NULL;
    cifRectOut[x1: x1, y1: y1, x2: x2, y2: y2, l: l, avoidEnlarge: TRUE];
    END;

  cifRectOut: PROCEDURE [x1, y1, x2, y2: LONG INTEGER, l: level,
    avoidEnlarge: BOOLEAN ← FALSE] =
    BEGIN

    OffGrid: PROC [coord: STRING] =
      BEGIN
      IF stillInterestedInOffGrid THEN
        BEGIN
        s: STRING ← [100];
        s.length ← 0;
        AppendString[to: s, from: chipmonkLayName[l]];
        AppendString[to: s, from: " is off-grid in "];
        AppendString[to: s, from: coord];
        stillInterestedInOffGrid ←
          RemarkAboutCell[p: [ToLocNum[(x1+x2)/2], ToLocNum[(y1+y2)/2]], remark: s];
        END;
      END;

    enlarge: LONG INTEGER;

    thisLevel: BOOLEAN = SELECT curLevel FROM
        dif => l=dif OR cifLevelName[l]=cifLevelName[dif]
          OR l=pdif OR cifLevelName[l]=cifLevelName[pdif],
        pdif => l=pdif OR cifLevelName[l]=cifLevelName[pdif],
        ENDCASE => l=curLevel AND NOT (cifLevelName[l]=cifLevelName[dif]
          OR cifLevelName[l]=cifLevelName[pdif]);

    IF NOT thisLevel OR cifLevelName[curLevel]=none
      OR x2=x1 OR y2=y1 THEN RETURN;

    IF x2<x1 THEN -- normalize the rectangle
      {t: LONG INTEGER ← x1; x1 ← x2; x2 ← t};
    IF y2<y1 THEN
      {t: LONG INTEGER ← y1; y1 ← y2; y2 ← t};

    IF NOT levelAnnounced THEN
      BEGIN
      cifOutStr["L "];
      cifOutStr[AtomToString[cifLevelName[curLevel]]];
      cifOutEndCom[];
      levelAnnounced ← TRUE;
      END;

    SELECT TRUE FROM
      curLevel=imp AND enlargeImplant AND NOT avoidEnlarge => enlarge ← Lambda;
      curLevel=pdif AND NOT avoidEnlarge => enlarge ← 3*Lambda;
      ENDCASE => enlarge ← 0;

    cifOutStr["B "];
    cifOutNum[resolution*(x2 - x1 + enlarge)]; -- width
    cifOutChr[' ];
    cifOutNum[resolution*(y2 - y1 + enlarge)];
    cifOutChr[' ];
    IF (resolution*(x1+x2)) MOD 2 # 0 THEN OffGrid["x"];
    cifOutNum[(resolution*(x1+x2))/2]; -- center
    cifOutChr[',];
    IF (resolution*(y1+y2)) MOD 2 # 0 THEN OffGrid["y"];
    cifOutNum[(resolution*(y1+y2))/2];
    cifOutEndCom[];
    END;

  cifLabelTerminal: PROCEDURE [lp: listPtr, s: LONG STRING,
    lev: level] =
    BEGIN
    size: Point =
      Size[size: [x: lp.ob.size[0], y: lp.ob.size[1]], orient: lp.idx];
    cifOutStr["94 "];
    cifOutStr[s];
    cifOutStr[" "];
    cifOutPoint[lp.lx+size.x/2, lp.ly+size.y/2]; -- in the center
    cifOutStr[" "];
    cifOutStr[AtomToString[cifLevelName[lev]]];
    cifOutEndCom[];
    END;

  cifPutProperty: PROCEDURE [lp: listPtr, attribute, value: LONG STRING] =
    BEGIN
    size: Point =
      Size[size: [x: lp.ob.size[0], y: lp.ob.size[1]], orient: lp.idx];
    cifOutStr["("];
    cifOutStr[attribute];
    cifOutStr[": "];
    cifOutStr[value];
    cifOutStr[" "];
    cifOutPoint[lp.lx+size.x/2, lp.ly+size.y/2]; -- in the center
    cifOutStr[")"];
    cifOutEndCom[];
    END;

  cifDrawCellName: PROCEDURE [s: LONG STRING] =
    BEGIN
    lastCellName ← s;
    cifOutStr["9 "];
    cifOutStr[s];
    cifOutEndCom[];
    END;

  cifOutStr: PUBLIC PROCEDURE [s: LONG STRING] =
    BEGIN
    FOR i: CARDINAL IN [0..s.length) DO
      cifFile.put[cifFile, s[i]];
      ENDLOOP;
    END;

  cifOutChr: PUBLIC PROCEDURE [c: CHARACTER] = INLINE
    {cifFile.put[cifFile, c]};

  cifOutEndCom: PROCEDURE =
    {cifOutChr[';]; cifOutChr[15C]};

  cifOutNum: PUBLIC PROCEDURE [num: LONG INTEGER, denom: LONG INTEGER ← 1] =
    BEGIN
    radix: INTEGER = 10;
    precision: INTEGER = 2;
    n: LONG INTEGER;
    IF num < 0 THEN {cifOutChr['-]; num ← -num};
    n ← num/denom;
    IF n>(radix-1) THEN cifOutNum[n/radix];
    cifOutChr['0 + LowHalf[n MOD radix]];
    IF num MOD denom # 0 THEN
      BEGIN
      frac: LONG INTEGER ← num MOD denom;
      cifOutChr['.];
      FOR digits: CARDINAL IN [0..precision) WHILE frac MOD denom # 0 DO
        cifOutChr['0 + LowHalf[(radix*frac)/denom]];
        frac ← (radix*frac) MOD denom;
        ENDLOOP;
      END;
    END;

  cifOutPoint: PROCEDURE [x, y: LONG INTEGER, denom: LONG INTEGER ← 1] =
    {cifOutPair[resolution*x, resolution*y, denom]}; 

  cifOutPair: PROCEDURE [x, y: LONG INTEGER, denom: LONG INTEGER ← 1] =
    {cifOutNum[x, denom]; cifOutChr[',]; cifOutNum[y, denom]}; 

  findname: PROCEDURE [p: LONG POINTER TO cell object]
    RETURNS[s: STRING] =
    BEGIN
    cp: LONG POINTER TO cList←cellList;
    s ← "";
    FOR cp: LONG POINTER TO cList←cellList, cp.nxt
      WHILE cp # NIL DO
      IF cp.ob = p THEN {s ← cp.name; RETURN};
      ENDLOOP;
    END;


  CoordRect: TYPE = RECORD[ x1, y1, x2, y2: INT];
  mainRect: CoordRect ← [x1: LAST[INT], y1: LAST[INT],
    x2: -LAST[INT], y2: -LAST[INT]];

  cifMeasureR: drRecord ← [
    [x1: -infinity, y1: -infinity, x2: infinity, y2: infinity],
    [x1: -infinity, y1: -infinity, x2: infinity, y2: infinity],
    cifMeasureArea, cifMeasureArea,
    nullOutl, nullCifDrawText, 0];

  cifMeasureArea: PROCEDURE [x1, y1, x2, y2: INTEGER, l: level,
    p: POINTER TO Rect] =
    BEGIN
    IF x2=x1 OR y2=y1 THEN RETURN;
    IF x2<x1 THEN
      {t: locNum ← x1; x1 ← x2; x2 ← t};
    IF y2<y1 THEN
      {t: locNum ← y1; y1 ← y2; y2 ← t};
    mainRect ←
      [x1: MIN[x1, mainRect.x1], y1: MIN[y1, mainRect.y1],
      x2: MAX[x2, mainRect.x2], y2: MAX[y2, mainRect.y2]];
    usedLevel[l] ← TRUE;
    IF ((x1+x2) MOD 2 # 0) OR ((y1+y2) MOD 2 # 0) THEN
      resolution ← 2; -- double resolution is needed to encode rectangle center
    END;

  NullLpAux: PROCEDURE[lp: listPtr] =
    BEGIN
    WHILE lp#NIL DO
      NullObAux[lp.ob];
      lp ← lp.nxt;
      ENDLOOP;
    END;

  NullObAux: PROCEDURE[ob: obPtr] =
    BEGIN
    ob.auxPnt ← NIL;
    WITH o: ob SELECT FROM
        cell => NullLpAux[o.ptr];
        ENDCASE => NULL;
    END;

  AppendString: PROC [to, from: LONG STRING] =
    BEGIN
    FOR i: CARDINAL IN [0..from.length) DO
      to[to.length] ← from[i];
      to.length ← to.length+1;
      ENDLOOP;
    END;

  ToLocNum: PROC [x: LONG INTEGER] RETURNS [locNum] =
    {IF x IN [FIRST[locNum]..LAST[locNum]] THEN
      RETURN[InlineDefs.LowHalf[x]] ELSE ERROR};

  RemarkAboutCell: PROC [p: Point, remark: STRING] RETURNS [stillInterested: BOOLEAN] =
    BEGIN
    savedMasterList: listPtr = masterList;
      BEGIN ENABLE UNWIND =>
        {flushDel[masterList]; masterList ← savedMasterList; dChange ← TRUE};
      s: STRING ← [100];
      masterList ← NIL;
      s.length ← 0;
      AppendString[to: s, from: "In cell "];
      AppendString[to: s, from: lastCellName];
      AppendString[to: s, from: ", "];
      AppendString[to: s, from: remark];
      AppendString[to: s, from: ". More?"];
      IF cellBeingDefined#NIL THEN
        FOR lp: listPtr ← cellBeingDefined.ptr, lp.nxt WHILE lp#NIL DO
          np: listPtr = makeList[lp.ob.p.anotherme[lp.ob], lp.lx, lp.ly, 0, 0];
          np.idx ← lp.idx;
          np.ridx ← lp.ridx;
          np.selected ← FALSE;
          copyProps[np, lp];
          masterList ← insertList[masterList, np];
          ENDLOOP;
      dChange ← TRUE;
      p ← GridPoint[p];
      setCoffset[p.x, p.y];
      putMark[p.x, p.y];

        BEGIN
        DEL: CHARACTER = 177C;
        ESC: CHARACTER = 033C;
        CR: CHARACTER = 015C;
        LF: CHARACTER = 012C;
        BS: CHARACTER = 010C;

        ans: STRING;
        breaks: STRING ← [20];
        breaks[0] ← CR;
        breaks[1] ← ESC;
        breaks[2] ← DEL;
        breaks[3] ← ' ;
        breaks[4] ← 'Y;
        breaks[5] ← 'y;
        breaks[6] ← 'N;
        breaks[7] ← 'n;
        breaks[8] ← 'T;
        breaks[9] ← 't;
        breaks[10] ← 'F;
        breaks[11] ← 'f;
        breaks[12] ← '1;
        breaks[13] ← '0;
        breaks.length ← 14;
        ans ← RequestString[s1: s, s2: "Still interested in this kind of observation?",
          breakChars: breaks, appendBreakChar: TRUE, flashColor: FALSE];
        IF ans.length > 0 THEN
          BEGIN
          c: CHARACTER ← ans[0];
          stillInterested ← SELECT c FROM
            'f, 'F, 'n, 'N, '0, DEL => FALSE,
            ENDCASE => TRUE;
          END
        ELSE stillInterested ← TRUE;
        FreeString[ans];
        END;
      flushDel[masterList];
      masterList ← savedMasterList;
      dChange ← TRUE;
      END;
    END;



  -- Module START code

  uz: UNCOUNTED ZONE ←
    ZoneAllocDefs.GetAnXMZone[checkSegments: TRUE];
  enlargeImplant: BOOLEAN ← FALSE;
  name, comment: STRING ← NIL;
  signalName: Atom = MakeAtom["Signal name"];
  none: Atom = MakeAtom["NONE"]; -- pseudo-layer name that is thrown on the floor

  NullLpAux[masterList];

    BEGIN OPEN TimeDefs;
    ENABLE Punt, UNWIND => GOTO Finished;
    time: STRING ← [100];
    mainOb: object ← [
      p: NIL,
      size: [infinity, infinity, infinity],
      refCnt: 0,
      auxPnt: NIL,
      l: NOcOL,
      returnable: FALSE,
      marked: FALSE,
      varpart: cell[cnt: 0, ptr: masterList, super: NIL]];
    resolution ← 1;
    name ← RequestString["Name of CIF file:"L,
      "... don't be alarmed if I contemplate for a minute or so ..."L];
    pppdefs.drCell0[ob: @mainOb, x: 0, y: 0, pr: @cifMeasureR];
    IF name=NIL OR name.length=0 THEN
      name ← newString[ppMainDefs.fileName];
    name ← FixExtension[name, ".cif"];
    cifFile ← NewByteStream[name, WriteAppend];
    cifScale ← RequestInteger["How many CIF units per lambda?",
      "(1 CIF unit = 0.01 micrometer)"];
    time.length ← 0;
    AppendDayTime[time, UnpackDT[CurrentDayTime[]]];
    cifOutStr["("];
    cifOutStr[name];
    cifOutStr[" - generated "];
    cifOutStr[time];
    cifOutStr[" by Xerox PARC Chipmonk with Lambda = "];
    cifOutNum[cifScale];
    cifOutStr[" CIF units)"];
    cifOutEndCom[];
    cifOutStr["(Origin = [x: 0, y: 0], Size = [x: "];
    cifOutNum[num: cifScale*(mainRect.x2-mainRect.x1), denom: Lambda];
    cifOutStr[", y: "];
    cifOutNum[num: cifScale*(mainRect.y2-mainRect.y1), denom: Lambda];
    cifOutStr["] CIF units)"];
    cifOutEndCom[];
    IF enlargeImplant THEN
      BEGIN
      cifOutStr["( Depletion implant rectangles enlarged by lambda/2 from Chipmonk design )"];
      cifOutEndCom[];
      END;
    comment ← RequestString[s1: "Comment line:",
      s2: "(any parentheses must be balanced)",
      s3: "(CR for no comment)",
      lowerCaseOK: TRUE];
    WHILE comment#NIL AND comment.length>0 DO
      cifOutStr["( "];
      cifOutStr[comment];
      cifOutStr[" )"];
      cifOutEndCom[];
      FreeString[comment];
      comment ← NIL;
      comment ← RequestString[s1: "Another comment line:",
        s2: "(any parentheses must be balanced)",
        s3: "(CR for no further comments)",
        lowerCaseOK: TRUE];
      ENDLOOP;
      isCMOS ← usedLevel[pdif] OR usedLevel[nwel];
      IF isCMOS THEN
        cifLevelName ← [
          cut: MakeAtom["CC"],
          dif: MakeAtom["CD"],
          pol: MakeAtom["CP"],
          met: MakeAtom["CM"],
          imp: MakeAtom["CI"],
          ovg: MakeAtom["CG"],
          bur: MakeAtom["CB"],
          snerd: MakeAtom["CX"],
          cut2: MakeAtom["CC2"],
          pdif: MakeAtom["CPI"],
          pwelCont: MakeAtom["CPI"],
          met2: MakeAtom["CM2"],
          pwel: MakeAtom["CPW"],
          nwel: MakeAtom["CNW"],
          nwelCont: MakeAtom["CD"],
          NOcOL: MakeAtom["CY"]]
      ELSE
        BEGIN
        cifLevelName ← [
          cut: MakeAtom["NC"],
          dif: MakeAtom["ND"],
          pol: MakeAtom["NP"],
          met: MakeAtom["NM"],
          imp: MakeAtom["NI"], -- used for vanilla implant
          ovg: MakeAtom["NG"],
          bur: MakeAtom["NB"],
          snerd: MakeAtom["U"],
          cut2: MakeAtom["NC2"],
          pdif: MakeAtom["Q"],
          pwelCont: MakeAtom["V"],
          met2: MakeAtom["NM2"],
          pwel: MakeAtom["NI0"], -- used for 0-threshold implant
          nwel: MakeAtom["NI1"], -- used for weak depletion implant
          nwelCont: MakeAtom["W"],
          NOcOL: MakeAtom["X"]];
          chipmonkLayName[pwel] ← "imp0"; -- feedback for the user
          chipmonkLayName[nwel] ← "imp1"; -- (NOT Chipmonk layer names)
        fourNMOSThresholds ←
          HeSaysYes["Do you want multiple depletion thresholds?"];
        pwelUsedByNMOS ← usedLevel[pwel]; -- so user may rename it
        usedLevel[pwel] ← fourNMOSThresholds;
        nwelUsedByNMOS ← usedLevel[nwel]; -- so user may rename it
        usedLevel[nwel] ← fourNMOSThresholds;
        END;
    IF HeSaysYes[(IF isCMOS THEN
      "Want to change standard CMOS layer names?"L
      ELSE "Want to change standard NMOS layer names?"L)] THEN
      FOR l:level IN level DO
        IF cifLevelName[l]#NIL AND
          AtomToString[cifLevelName[l]].length>0 AND usedLevel[l] THEN
          BEGIN
          cln: STRING ← NIL;
          s1: STRING ← [100];
          s2: STRING ← [100];
          s1.length ← s2.length ← 0;
          AppendString[to: s1, from: "CIF name for "];
          AppendString[to: s1, from: chipmonkLayName[l]];
          AppendString[to: s1, from: "?"];
          AppendString[to: s2, from: "(CR to keep standard name of "];
          AppendString[to: s2, from: AtomToString[cifLevelName[l]]];
          AppendString[to: s2, from: ", NONE to prevent its output)"];
          cln ← RequestString[s1, s2];
          IF cln # NIL AND cln.length > 0 THEN
            BEGIN
            cifLevelName[l] ← MakeAtom[cln];
            FreeString[cln];
            END;
          END;
        ENDLOOP;
    cifDefineObject[@mainOb];
    cifSymbolCall[@mainOb];
    cifOutStr[" M Y T "];
    cifOutPair[x: -cifScale*mainRect.x1/Lambda, y: cifScale*mainRect.y2/Lambda];
    cifOutStr[";"];
    cifOutChr[15C];
    cifOutStr["End ..."];
    cifOutChr[15C];
    EXITS Finished => NULL;
    END;

  IF NOT isCMOS THEN 
    BEGIN
    usedLevel[pwel] ← pwelUsedByNMOS;
    usedLevel[nwel] ← nwelUsedByNMOS;
    END;
  IF cifFile#NIL THEN
    BEGIN
    TruncateDiskStream[cifFile];
    cifFile ← NIL;
    END;
  IF name#NIL THEN {FreeString[name]; name ← NIL};
  IF comment#NIL THEN {FreeString[comment]; comment ← NIL};
  NullLpAux[masterList];
  uz ← ZoneAllocDefs.DestroyAnXMZone[uz];
  END. -- of CIFGen