<> <> <> <> <<>> DIRECTORY Basics, CD, CDCells, CDOrient, CDRects, CDSymbolicObjects, CMosB, Core, CoreBlock, CoreCreate, CoreFrame, CoreGeometry, CoreLibrary, CoreName, CoreOps, IFUCoreCells, IFUCoreCtl, IFUCoreDrive, IO, Lists, PLAOps, PLASim, Ports, PW, PWC, PWCTilingClass, PWPins, REFBit, Rope; IFUCoreCtlPreCharge: CEDAR PROGRAM IMPORTS Basics, CD, CDCells, CDRects, CDSymbolicObjects, CoreBlock, CoreCreate, CoreFrame, CoreGeometry, CoreLibrary, CoreName, CoreOps, IFUCoreCells, IFUCoreDrive, IO, Lists, PLAOps, PLASim, Ports, PW, PWC, PWCTilingClass, PWPins, REFBit, Rope EXPORTS IFUCoreCtl = BEGIN ROPE: TYPE = Core.ROPE; CellType: TYPE = Core.CellType; Wire: TYPE = Core.Wire; Wires: TYPE = Core.Wires; Frame: TYPE = CoreFrame.Frame; Side: TYPE = CoreFrame.Side; PLADescription: TYPE = IFUCoreCtl.PLADescription; Connection: TYPE = IFUCoreCtl.Connection; PLAType: TYPE = IFUCoreDrive.PLAType; Drive: TYPE = IFUCoreDrive.Drive; Drives: TYPE = IFUCoreDrive.Drives; DriveRec: TYPE = IFUCoreDrive.DriveRec; RowType: TYPE = IFUCoreDrive.RowType; Dir: TYPE = IFUCoreDrive.Dir; DrGate: TYPE = IFUCoreDrive.DrGate; Ph: TYPE = IFUCoreDrive.Ph; Polarity: TYPE = IFUCoreDrive.Polarity; Signal: SIGNAL = CODE; in: ROPE _ CoreName.RopeNm["in"]; nin: ROPE _ CoreName.RopeNm["nin"]; in0: ROPE _ CoreName.RopeNm["in0"]; in1: ROPE _ CoreName.RopeNm["in1"]; out: ROPE _ CoreName.RopeNm["out"]; GND: ROPE _ CoreName.RopeNm["GND"]; VDD: ROPE _ CoreName.RopeNm["VDD"]; fire: ROPE _ CoreName.RopeNm["Fire"]; fireV: ROPE _ CoreName.RopeNm["FireControlV"]; nPreChg: ROPE _ CoreName.RopeNm["NotPreChg"]; dChrg: ROPE _ CoreName.RopeNm["DisChg"]; <<>> MakeHotPLA, MakePreChargedPLA: PUBLIC PROC[desc: PLADescription] = { log.PutF["\n Make PreCharged/Hot PLA %g", IO.rope[desc.name]]; ZeroUnusedTTTOutputs [desc]; DefinePLARows [desc]; DressInDrs [desc]; MakeOutDrs [desc]; NewMakePla [desc]}; <> DressInDrs: PROC [desc: PLADescription] = { desc.inDrs _ CONS[ NEW[DriveRec _ [drRowType: xfooter, fire: desc.fire, fireV: desc.fireV, nPreChg: desc.nPreChg] ], desc.inDrs]; FOR list: Drives _ desc.inDrs, list.rest WHILE list.rest#NIL DO REPEAT FINISHED => list.rest _ CONS [NEW[DriveRec _ [drRowType: xheader, fire: desc.fire, fireV: desc.fireV, nPreChg: desc.nPreChg]], NIL] ENDLOOP}; ZeroUnusedTTTOutputs: PROC [desc: PLADescription ] = { maskTerm: PLAOps.Term _ PLAOps.CopyTerm[desc.ttt.termList.begin]; log.PutRope["\n Zero unused TTT outputs"]; FOR i: CARDINAL IN [0..maskTerm.out.wdSize) DO maskTerm.out[i] _ PLAOps.initOutQrtWz ENDLOOP; FOR index: INT IN [0..desc.smlToBigOut.size) DO pos: INT _ desc.smlToBigOut[index]; PLAOps.SetOutQrt[one, maskTerm, REFBit.Desc[desc.ttt.out].bitForm[pos].firstBit] ENDLOOP; FOR term: PLAOps.Term _ desc.ttt.termList.begin, term.next WHILE term#NIL DO FOR i: CARDINAL IN [0..maskTerm.out.wdSize) DO term.out[i].d _ Basics.BITAND[term.out[i].d, maskTerm.out[i].d] ENDLOOP ENDLOOP }; PreChargedParams: TYPE = RECORD[ minConnSpace: INT _ 2, -- SPACING rows between driver rows; insPerExtra: INT _ 10, -- SPACING cols between extra columns; outsPerExtra: INT _ 10, nextTerm: PLAOps.Term _ NIL, -- specific parameter nextConn: INT _ 0, -- specific parameter rows: REF RowsRec _ NIL ]; -- specific parameter RowsRec: TYPE = RECORD[SEQUENCE size: CARDINAL OF REF RowRec]; RowRec: TYPE = RECORD[ dr: REF DriveRec, type: RowType, and: ColSeqRef, or: ColSeqRef ]; ColSeqRef: TYPE = REF ColSeqRec; ColSeqRec: TYPE = RECORD[SEQUENCE size: CARDINAL OF NormalCellType]; DefinePLARows: PROC [desc: PLADescription] = { pp: REF PreChargedParams _ NEW[PreChargedParams _ [ nextTerm: desc.ttt.termList.begin, nextConn: desc.connSeq.size-1, insPerExtra: IF desc.plaType = hot THEN 10000 ELSE 10]]; --extra AND column undefined firstRow: BOOL _ TRUE; index: INT _ 0; termUp: BOOL _ TRUE; nofOuts: INT _ MAX[Lists.ListLength[desc.plaOutNames], desc.nofOrCols]; nofIns: INT _ Lists.ListLength[desc.plaInNames]; cRowsLeft: INT _ Lists.ListLength[desc.plaOutNames]; dRowsLeft: INT _ desc.ttt.termList.length; hRowsLeft: INT; dRowsLeft _ MAX[dRowsLeft, cRowsLeft*(pp.minConnSpace)]; hRowsLeft _ MAX[1, (dRowsLeft+ desc.termsPerHeader/2)/desc.termsPerHeader]; log.PutRope["\n Assign precharged/hot pla row types"]; desc.data _ pp; desc.nofAndCols _ nofIns/2 + (nofIns/2 -1) / pp.insPerExtra; desc.nofOrCols _ nofOuts + (nofOuts -1) / pp.outsPerExtra; pp.rows _ NEW[RowsRec[cRowsLeft+dRowsLeft+2*hRowsLeft]]; index _ pp.rows.size-1; -- start at the top WHILE hRowsLeft#0 DO -- actually one more header is appended afterwards RperH: INT _ (cRowsLeft+dRowsLeft+hRowsLeft + hRowsLeft/2)/hRowsLeft; IF firstRow THEN firstRow_FALSE ELSE {pp.rows[index] _ NextRow[desc, xfooter]; index_index-1}; pp.rows[index] _ NextRow[desc, header]; index_index-1; RperH_RperH-1; hRowsLeft_hRowsLeft-1; WHILE RperH > 0 DO CperD, DperC: INT; CperD _ MAX[1, (cRowsLeft + dRowsLeft/2)/dRowsLeft]; DperC _ MAX[1, (dRowsLeft + cRowsLeft/2)/cRowsLeft]; IF DperC < pp.minConnSpace OR (CperD>1) AND (pp.minConnSpace>0) THEN ERROR; RperH _ RperH - CperD - DperC; WHILE CperD > 0 DO pp.rows[index] _ NextRow[desc, conn]; index_index-1; cRowsLeft_cRowsLeft-1; CperD_CperD-1; ENDLOOP; termUp _ TRUE; WHILE DperC > 0 DO pp.rows[index] _ NextRow[desc, IF termUp THEN dataUp ELSE dataDn]; index_index-1; dRowsLeft_dRowsLeft-1; DperC_DperC-1; termUp _ NOT termUp; ENDLOOP; ENDLOOP; ENDLOOP; IF index#0 THEN ERROR; pp.rows[index] _ NextRow[desc, footer]}; NextRow: PROC [desc: PLADescription, type: RowType] RETURNS[row: REF RowRec] = { pp: REF PreChargedParams _ NARROW[desc.data]; andIndex, orIndex, index: INT _ 0; data: PLAOps.Term; conn: Connection; row _ NEW[RowRec _ [type: type]]; row.and _ NEW[ColSeqRec[desc.nofAndCols]]; IF desc.nofOrCols#0 THEN row.or _ NEW[ColSeqRec[desc.nofOrCols]]; SELECT type FROM header => { }; conn => {conn _ NextConnection[desc]; row.dr _ conn.dr}; dataUp, dataDn => { data _ NextDataTerm[desc]; row.dr _ NIL; IF data=NIL THEN type _ row.type _ blank}; ENDCASE; FOR index IN[0..desc.nofAndCols) DO IF (index+1) MOD (pp.insPerExtra+1) = 0 THEN row.and[index] _ extra ELSE { SELECT type FROM dataUp, dataDn => SELECT PLAOps.GetInQrt [data, REFBit.Desc[desc.ttt.data].bitForm[andIndex].firstBit] FROM zero => row.and[index] _ left; one => row.and[index] _ right; ENDCASE => row.and[index] _ nc; conn => IF conn.isOutput OR conn.index#andIndex THEN row.and[index] _ nc ELSE IF conn.isLeftSide THEN row.and[index] _ left ELSE row.and[index] _ right; ENDCASE => row.and[index] _ nc; andIndex_andIndex+1 } ENDLOOP; IF desc.nofOrCols#0 THEN FOR index IN[0..desc.nofOrCols) DO IF (index+1) MOD (pp.outsPerExtra+1) = 0 THEN row.or[index] _ extra ELSE { row.or[index] _ nc; IF orIndex < desc.smlToBigOut.size THEN { IF (type=dataUp OR type=dataDn) AND PLAOps.GetOutQrt [data, REFBit.Desc[desc.ttt.out].bitForm[desc.smlToBigOut[orIndex]].firstBit]=one THEN row.or[index] _ left; IF type=conn AND conn.isOutput AND conn.index=desc.smlToBigOut[orIndex] THEN row.or[index] _ left }; orIndex_orIndex+1 } ENDLOOP}; NextDataTerm: PROC [desc: PLADescription] RETURNS[term: PLAOps.Term] = { pp: REF PreChargedParams _ NARROW[desc.data]; term _ pp.nextTerm; IF term#NIL THEN pp.nextTerm _ pp.nextTerm.next}; NextConnection: PROC [desc: PLADescription] RETURNS[conn: Connection] = { pp: REF PreChargedParams _ NARROW[desc.data]; conn _ desc.connSeq[pp.nextConn]; pp.nextConn _ pp.nextConn-1}; MakeOutDrs: PROC[desc: PLADescription] = { pp: REF PreChargedParams _ NARROW[desc.data]; last: INT _ pp.rows.size+pp.minConnSpace; FOR driverIndex: INT DECREASING IN [0..pp.rows.size) DO type: RowType _ pp.rows[driverIndex].type; template: DriveRec _ [plaType: desc.plaType, drRowType: type, fire: desc.fire, fireV: desc.fireV, nPreChg: desc.nPreChg]; SELECT type FROM header, xfooter, footer => { IF (last-driverIndex) <= pp.minConnSpace THEN ERROR; last _ driverIndex+pp.minConnSpace; desc.outDrs _ CONS[NEW[DriveRec _ template], desc.outDrs]}; blank, dataUp, dataDn => { IF (last-driverIndex) <= pp.minConnSpace THEN LOOP; desc.outDrs _ CONS[NEW[DriveRec _ template], desc.outDrs]}; conn => { IF (last-driverIndex) <= pp.minConnSpace THEN ERROR; last _ driverIndex; desc.outDrs _ CONS[pp.rows[driverIndex].dr, desc.outDrs]} ENDCASE => ERROR; ENDLOOP}; NewMakePla: PROC[desc: PLADescription] = { name: ROPE _ CoreName.RopeNm[desc.name.Cat["Body"]]; tiles: REF TileVarieties _ GetPLATiles[desc.plaType]; pp: REF PreChargedParams _ NARROW[desc.data]; obj: CD.Object; cellType: CellType; input: INT _ 0; output: INT _ 0; tileArray: PWCTilingClass.TileArray _ NIL; fireWire: Wire _ CoreCreate.Seq[desc.fire, 0]; fireVWire: Wire _ CoreCreate.Seq[desc.fireV, 0]; nPreChgWire: Wire _ CoreCreate.Seq[desc.nPreChg, 0]; extras: Wires _ IF desc.plaType#precharged THEN NIL ELSE LIST [fireWire, fireVWire, nPreChgWire ]; public: Wire _ PLASim.CreateSimplePLAPublic[desc.name, extras ]; vddWire: Wire _ CoreOps.FindWire[public, VDD]; gndWire: Wire _ CoreOps.FindWire[public, GND]; log.PutRope["\n Assemble precharged/hot pla row tiles"]; tileArray _ NEW[PWCTilingClass.TileArrayRec[pp.rows.size]]; FOR rr: INT IN [0..pp.rows.size) DO TileIt: PROC [cell: CellType, type: {in, out, none} _ none, index: INT _ 0, header: BOOL_FALSE] = { pas: LIST OF CoreCreate.PA _ NIL; SELECT type FROM in => pas _ LIST[ [in0, CoreOps.FindWire[public, in][index]], [in1, CoreOps.FindWire[public, nin][index]] ]; out => pas _ LIST[[out, CoreOps.FindWire[public, out][index]]]; ENDCASE; IF header THEN{ pas _ CONS[[VDD, vddWire], CONS[[GND, gndWire], pas]]; IF extras#NIL THEN pas _ CONS[[fire, fireWire], CONS[[fireV, fireVWire], CONS[[nPreChg, nPreChgWire], pas ] ] ]}; tileArray[rr][col] _ NEW[PWCTilingClass.TileRec _ [cell, pas]]; col _ col+1}; row: REF RowRec _ pp.rows[rr]; col: INT _ 1 + row.and.size + 1 + row.or.size + 1; header: BOOL _ row.type=header OR row.type=footer; tileArray[rr] _ NEW[PWCTilingClass.TileRowRec[col]]; col _ 0; TileIt[ tiles.glue[row.type][leftSide], none, 0]; FOR i: INT IN [0..row.and.size) DO IF rr=0 AND row.and[i]#extra THEN {TileIt[tiles.and[row.type][row.and[i]], in, input]; input _ input+1} ELSE {TileIt[tiles.and[row.type][row.and[i]]]}; ENDLOOP; TileIt[ tiles.glue[row.type][between]]; FOR i: INT IN [0..row.or.size) DO TileIt[ tiles.or[row.type][row.or[i]]] ENDLOOP; IF row.type#conn THEN {TileIt[tiles.glue[row.type][rightSide], none, 0, header]} ELSE {TileIt[tiles.glue[row.type][rightSide], out, output ]; output _ output+1}; ENDLOOP; AssignPublicNames[desc, public]; cellType _ PWCTilingClass.CreateTiling[ public: public, tileArray: tileArray, neighborX: PWCTilingClass.LayoutNeighborX, neighborY: PWCTilingClass.LayoutNeighborY, name: name, props: NIL, cacheNeighbor: TRUE ]; obj _ PWC.Layout[cellType]; -- cause recast cellType _ PWC.Extract[obj]; -- get record CT []_CoreName.CellNm[cellType, name]; PLASim.SetUpRose[cellType]; CoreBlock.MarkSides[cellType, desc.capSides]; desc.outBodyCT _ CoreFrame.NewFrameCell[0, name, [first: left, cell: cellType] ]}; MakePla: PROC[desc: PLADescription] = { name: ROPE _ CoreName.RopeNm[desc.name.Cat["Body"]]; <> { body: CD.Object; cellType: CellType; tiles: REF TileVarieties _ GetPLATiles[desc.plaType]; pp: REF PreChargedParams _ NARROW[desc.data]; refPhase: Ph _ unk; rowList: PW.ListOb _ NIL; log.PutRope["\n Assemble precharged/hot pla row cells"]; FOR rowIndex: INT IN [0..pp.rows.size) DO objects: PW.ListOb _ NIL; row: REF RowRec _ pp.rows[rowIndex]; IF pp.rows[rowIndex].dr#NIL THEN refPhase _ pp.rows[rowIndex].dr.ref.ph; objects _ CONS[PWC.Layout[tiles.glue[row.type][leftSide]], objects]; FOR index: INT IN [0..row.and.size) DO objects _ CONS[PWC.Layout[tiles.and[row.type][row.and[index]]], objects] ENDLOOP; IF desc.nofOrCols#0 THEN { objects _ CONS[PWC.Layout[tiles.glue[row.type][between]], objects]; FOR index: INT IN [0..row.or.size) DO objects _ CONS[PWC.Layout[tiles.or[row.type][row.or[index]]], objects] ENDLOOP; objects _ CONS[PWC.Layout[tiles.glue[row.type][rightSide]], objects] }; <> rowList _ CONS[PW.AbutListX[PW.Reverse[objects]], rowList] ENDLOOP; body _ PW.AbutListY[PW.Reverse[rowList]]; cellType _ MakeSimplePLACell[body, desc]; <> <> CoreBlock.MarkSides[cellType, desc.capSides]; desc.outBodyCT _ CoreFrame.NewFrameCell[0, name, [first: left, cell: cellType] ]; } }; <> MakeSimplePLACell: PROC[obj: CD.Object, desc: PLADescription] RETURNS[cellType: CellType] = { iSize: CD.Position _ CD.InterestSize[obj]; shell: CD.Object _ CDCells.CreateEmptyCell[]; minW: INT = CMosB.lambda; sides: CoreBlock.Sides; loc, size: INT; loc2, size2: CD.Position; wire: Wire; extras: Wires _ IF desc.plaType#precharged THEN NIL ELSE LIST [ CoreCreate.Seq[fire, 0], CoreCreate.Seq[fireV, 0], CoreCreate.Seq[nPreChg, 0], CoreCreate.Seq[dChrg, 0] ]; renameProc: PWPins.ChangePinProc ~ { -- oldPin: CD.Instance => newPin: CD.Instance newPin2: CD.Instance; -- additional copy for decorating cellType layer: CD.Layer _ CDSymbolicObjects.GetLayer[oldPin]; oldNm: ROPE _ CoreName.RopeNm[CDSymbolicObjects.GetName[oldPin]]; [sides, loc, size] _ CoreBlock.GetInstSideLocSize[obj, oldPin]; loc2 _ SELECT sides FROM left => [0, loc], right => [iSize.x-minW, loc], top => [loc, iSize.y-minW], bottom => [loc, 0], ENDCASE => ERROR; size2 _ SELECT sides FROM top, bottom => [size, minW] ENDCASE => [minW, size]; newPin _ PW.IncludeInCell[shell, CDRects.CreateRect[size2, layer], loc2]; newPin2 _ NEW[CD.InstanceRep _ newPin^]; wire _ FindPublicWire[desc, cellType.public, oldNm, loc]; CDSymbolicObjects.SetName[newPin, CoreName.WireNm[wire].n]; CoreGeometry.PutPins[ decoration: PWC.extractMode.decoration, public: wire, pins: CONS[ newPin2, CoreGeometry.GetPins[PWC.extractMode.decoration, wire] ] ]}; cellType _ PLASim.CreateSimplePLA [desc.name, PLASim.CreateSimplePLAPublic[desc.name, extras] ]; IF desc.plaType=precharged THEN { []_Ports.InitPort[wire: CoreOps.FindWire[cellType.public, fire], levelType:b, initDrive: none]; []_Ports.InitPort[wire: CoreOps.FindWire[cellType.public, fireV], levelType:b, initDrive: none]; []_Ports.InitPort[wire: CoreOps.FindWire[cellType.public, nPreChg], levelType:b, initDrive: none]; []_Ports.InitPort[wire: CoreOps.FindWire[cellType.public, dChrg], -- present by accident levelType:l, initDrive: none] }; AssignPublicNames[desc, cellType.public]; <> obj _ PWPins.ChangePins[obj, renameProc]; PWC.SetExtractCell[obj, cellType]; PWC.SetLayoutObj[cellType, obj]; CoreGeometry.PutIR[PWC.extractMode.decoration, cellType, CD.InterestRect[obj]]; PW.SetInterestRect[shell, iSize]; PW.RepositionCell[shell]}; -- note: this shell is not currently used AssignPublicNames: PROC[desc: PLADescription, public: Wire] = { pp: REF PreChargedParams _ NARROW[desc.data]; name: ROPE; oIndex: INT _ 0; iIndex: INT _ 0; IF desc.plaType=precharged AND desc.fire#NIL THEN [ ] _ CoreName.WireNm[CoreOps.FindWire[public, fire], desc.fire]; IF desc.plaType=precharged AND desc.fireV#NIL THEN [ ] _ CoreName.WireNm[CoreOps.FindWire[public, fireV], desc.fireV]; IF desc.plaType=precharged AND desc.nPreChg#NIL THEN [ ] _ CoreName.WireNm[CoreOps.FindWire[public, nPreChg], desc.nPreChg]; FOR rIndex: INT IN [0..pp.rows.size) DO IF pp.rows[rIndex].type # conn THEN LOOP; IF pp.rows[rIndex].dr = NIL THEN LOOP; name _ IFUCoreDrive.DriveName[pp.rows[rIndex].dr, nin]; [ ] _ CoreName.WireNm[CoreOps.FindWire[public, out][oIndex], name]; oIndex _ oIndex + 1 ENDLOOP; FOR list: LIST OF ROPE _ desc.plaInNames, list.rest.rest WHILE list#NIL DO [ ] _ CoreName.WireNm[CoreOps.FindWire[public, in ][iIndex], list.first]; [ ] _ CoreName.WireNm[CoreOps.FindWire[public, nin ][iIndex], list.rest.first]; iIndex _ iIndex + 1 ENDLOOP}; FindPublicWire: PROC[desc: PLADescription, public: Wire, oldNm: ROPE, loc: INT] RETURNS[wire: Wire] = { TileSize: PROC[cell: CellType] RETURNS[size: CD.Position] = {IF cell=NIL THEN RETURN[[0, 0]]; RETURN[PWC.InterestSize[cell]]}; pp: REF PreChargedParams _ NARROW[desc.data]; tiles: REF TileVarieties _ GetPLATiles[desc.plaType]; leftSize: INT _ TileSize[tiles.glue [blank] [leftSide]].x; andWidth: INT _ TileSize[tiles.and [blank] [nc]].x; extraWidth: INT _ TileSize[tiles.and [blank] [extra]].x; headHt: INT _ TileSize[tiles.glue [header] [rightSide]].y; xfootHt: INT _ TileSize[tiles.glue [xfooter] [rightSide]].y; rowHt: INT _ TileSize[tiles.glue [blank] [rightSide]].y; SELECT oldNm FROM out => { oIndex: INT _ 0; yPos: INT _ 0; FOR rIndex: INT IN [0..pp.rows.size) DO SELECT pp.rows[rIndex].type FROM header, footer => {yPos _ yPos + headHt; LOOP}; xfooter => {yPos _ yPos + xfootHt; LOOP}; dataUp, dataDn => {yPos _ yPos + rowHt; LOOP}; blank => {yPos _ yPos + rowHt; LOOP}; #conn => Signal[]; ENDCASE; SELECT loc FROM < yPos => Signal[]; < yPos + rowHt => RETURN[CoreOps.FindWire[public, out][oIndex]] ENDCASE; yPos _ yPos + rowHt; oIndex _ oIndex + 1; ENDLOOP; Signal[]}; in0, in1 => { xpos: INT _ (loc - leftSize)/(pp.insPerExtra*andWidth+extraWidth); xpos _ (loc - leftSize - extraWidth*xpos)/(andWidth/2); IF ((xpos MOD 2)=0) # (oldNm=in0) THEN Signal[]; IF ((xpos MOD 2)=0) THEN RETURN[CoreOps.FindWire[public, in ][xpos/2]] ELSE RETURN[CoreOps.FindWire[public, nin ][xpos/2]] }; ENDCASE => RETURN[CoreOps.FindWire[public, oldNm]]}; <> <> <<{IF obj=NIL THEN RETURN[[0, 0]]; RETURN[CD.InterestSize[obj]]};>> <> <> <> <> <> <> <> <> <> <> <> <> <> <<[side, loc] _ CoreBlock.GetInstSideLoc[oldObj, newPin];>> <> < {yPos _ yPos + headHt; LOOP};>> < {yPos _ yPos + xfootHt; LOOP};>> < {yPos _ yPos + rowHt; LOOP};>> < {yPos _ yPos + rowHt; LOOP};>> < {IF loc < yPos THEN Signal[]};>> < Signal[];>> <> < yPos THEN LOOP;>> <> <> <> <> < {>> <> <> <> <> <> <1 DO>> <> <> <> <> <> <> < CDSymbolicObjects.SetName[newPin, "PhB"];>> < CDSymbolicObjects.SetName[newPin, "FireControlV"]; -- to conn pad>> < CDSymbolicObjects.SetName[newPin, "NotPreChg"]; -- to conn pad>> < RETURN};>> <> <<>> tileBuffer: REF TileVarieties; hotTileBuffer: REF TileVarieties; TileVarieties: TYPE = RECORD[glue: REF GlueTiles, and, or: REF NormalTiles]; GlueTiles: TYPE = ARRAY RowType OF ARRAY GlueCellType OF CellType; GlueCellType: TYPE = {leftSide, between, rightSide}; NormalTiles: TYPE = ARRAY RowType OF ARRAY NormalCellType OF CellType; NormalCellType: TYPE = {left, right, nc, extra}; GetPLATiles: PROC[type: PLAType] RETURNS[tiles: REF TileVarieties] = { tiles _ SELECT type FROM hot => GetHotPLATiles[], ENDCASE => GetPreChargedPLATiles[]}; FlipY: PROC[orig: CellType] RETURNS[flipped: CellType] = { name: ROPE _ CoreName.CellNm[orig].n; IF name.Length[]=0 THEN Signal[]; flipped _ CoreFrame.RotateCellType[orig, CDOrient.mirrorY]; [] _ CoreName.CellNm[flipped, name.Cat["-FlipY"]]}; <> <> <> <> <> GetPreChargedPLATiles: PROC RETURNS[tiles: REF TileVarieties] = { Get: PROC[name: ROPE] RETURNS[CellType] = {RETURN[CoreLibrary.Get[library, name ]]}; library: CoreLibrary.Library _ IFUCoreCells.library; IF tileBuffer # NIL THEN RETURN[tileBuffer]; log.PutRope["\n Initialize precharged PLA tiles"]; tiles _ tileBuffer _ NEW[TileVarieties]; tiles.glue _ NEW[GlueTiles]; tiles.and _ NEW[NormalTiles]; tiles.or _ NEW[NormalTiles]; tiles.glue [xfooter][leftSide] _ Get[ "XLeftSide" ]; tiles.glue [xfooter][between] _ Get[ "XBetween" ]; tiles.glue [xfooter][rightSide] _ Get[ "XOrEx" ]; tiles.and [xfooter][nc] _ Get[ "XAnd" ]; tiles.and [xfooter][extra] _ Get[ "XAndEx" ]; tiles.or [xfooter][nc] _ Get[ "XOr" ]; tiles.or [xfooter][extra] _ Get[ "XOrEx" ]; tiles.glue [header][leftSide] _ Get[ "HLeftSide" ]; tiles.glue [header][between] _ Get[ "HBetween" ]; tiles.glue [header][rightSide] _ Get[ "HRightSide" ]; tiles.and [header][nc] _ Get[ "HAnd" ]; tiles.and [header][extra] _ Get[ "HAndEx" ]; tiles.or [header][nc] _ Get[ "HOr" ]; tiles.or [header][extra] _ Get[ "HOrEx" ]; tiles.glue [footer][leftSide] _ FlipY[ tiles.glue [header][leftSide] ]; tiles.glue [footer][between] _ FlipY[ tiles.glue [header][between] ]; tiles.glue [footer][rightSide] _ FlipY[ tiles.glue [header][rightSide] ]; tiles.and [footer][nc] _ FlipY[ tiles.and [header][nc] ]; tiles.and [footer][extra] _ FlipY[ tiles.and [header][extra] ]; tiles.or [footer][nc] _ Get[ "HOrFooter" ]; -- isolate outs from next stage tiles.or [footer][extra] _ FlipY[ tiles.or [header][extra] ]; tiles.glue [blank][leftSide] _ Get[ "BLeftSide" ]; tiles.glue [blank][between] _ Get[ "BBetween" ]; tiles.glue [blank][rightSide] _ Get[ "BOrEx" ]; tiles.and [blank][nc] _ Get[ "BAnd" ]; tiles.and [blank][extra] _ Get[ "BAndEx" ]; tiles.or [blank][nc] _ Get[ "BOr" ]; tiles.or [blank][extra] _ Get[ "BOrEx" ]; tiles.glue [conn][leftSide] _ Get[ "BLeftSide" ]; tiles.glue [conn][between] _ Get[ "BBetween" ]; tiles.glue [conn][rightSide] _ Get[ "CRightSide" ]; tiles.and [conn][left] _ Get[ "CAndLt" ]; tiles.and [conn][right] _ Get[ "CAndRt" ]; tiles.and [conn][nc] _ Get[ "BAnd" ]; tiles.and [conn][extra] _ Get[ "BAndEx" ]; tiles.or [conn][left] _ Get[ "COr" ]; tiles.or [conn][nc] _ Get[ "COrNC" ]; tiles.or [conn][extra] _ Get[ "COrEx" ]; tiles.glue [dataUp][leftSide] _ Get[ "DLeftSide" ]; tiles.glue [dataUp][between] _ Get[ "DBetween" ]; tiles.glue [dataUp][rightSide] _ Get[ "DRightSide" ]; tiles.and [dataUp][left] _ Get[ "DAndLt" ]; tiles.and [dataUp][right] _ Get[ "DAndRt" ]; tiles.and [dataUp][nc] _ Get[ "DAnd" ]; tiles.and [dataUp][extra] _ Get[ "DAndEx" ]; tiles.or [dataUp][left] _ Get[ "DOr" ]; tiles.or [dataUp][nc] _ Get[ "DOrNC" ]; tiles.or [dataUp][extra] _ Get[ "DOrEx" ]; tiles.glue [dataDn][leftSide] _ tiles.glue [dataUp][leftSide]; tiles.glue [dataDn][between] _ FlipY[ tiles.glue [dataUp][between] ]; tiles.glue [dataDn][rightSide] _ FlipY[ tiles.glue [dataUp][rightSide] ]; tiles.and [dataDn][left] _ tiles.and [dataUp][left]; tiles.and [dataDn][right] _ tiles.and [dataUp][right]; tiles.and [dataDn][nc] _ tiles.and [dataUp][nc]; tiles.and [dataDn][extra] _ tiles.and [dataUp][extra]; tiles.or [dataDn][left] _ FlipY[ tiles.or [dataUp][left] ]; tiles.or [dataDn][nc] _ FlipY[ tiles.or [dataUp][nc] ]; tiles.or [dataDn][extra] _ FlipY[ tiles.or [dataUp][extra] ]; RETURN[tiles]}; GetHotPLATiles: PROC RETURNS[tiles: REF TileVarieties] = { Get: PROC[name: ROPE] RETURNS[CellType] = {RETURN[CoreLibrary.Get[library, name ]]}; library: CoreLibrary.Library _ IFUCoreCells.library; IF hotTileBuffer # NIL THEN RETURN[hotTileBuffer]; log.PutRope["\n Initialize hot PLA tiles"]; tiles _ hotTileBuffer _ NEW[TileVarieties]; tiles.glue _ NEW[GlueTiles]; tiles.and _ NEW[NormalTiles]; tiles.or _ NEW[NormalTiles]; tiles.glue [header][leftSide] _ Get[ "HPlaHLeftSide" ]; tiles.glue [header][between] _ Get[ "HPlaHBetween" ]; tiles.glue [header][rightSide] _ Get[ "HPlaHRightSide" ]; tiles.and [header][nc] _ Get[ "HPlaHAnd" ]; tiles.or [header][nc] _ Get[ "HPlaHOr" ]; tiles.or [header][extra] _ Get[ "HPlaHOrEx" ]; tiles.glue [footer][leftSide] _ FlipY[ tiles.glue [header][leftSide] ]; tiles.glue [footer][between] _ FlipY[ tiles.glue [header][between] ]; tiles.glue [footer][rightSide] _ FlipY[ tiles.glue [header][rightSide] ]; tiles.and [footer][nc] _ FlipY[ tiles.and [header][nc] ]; tiles.or [footer][nc] _ FlipY[ tiles.or [header][nc] ]; tiles.or [footer][extra] _ FlipY[ tiles.or [header][extra] ]; tiles.glue [blank][leftSide] _ Get[ "HPlaBLeftSide" ]; tiles.glue [blank][between] _ Get[ "HPlaBBetween" ]; tiles.glue [blank][rightSide] _ Get[ "HPlaBRightSide" ]; tiles.and [blank][nc] _ Get[ "HPlaBAnd" ]; tiles.or [blank][nc] _ Get[ "BOr" ]; tiles.or [blank][extra] _ Get[ "HPlaBOrEx" ]; tiles.glue [conn][leftSide] _ Get[ "HPlaBLeftSide" ]; tiles.glue [conn][between] _ Get[ "HPlaBBetween" ]; tiles.glue [conn][rightSide] _ Get[ "HPlaCRightSide" ]; <> <> tiles.and [conn][nc] _ Get[ "HPlaBAnd" ]; -- input connections not used tiles.or [conn][left] _ Get[ "COr" ]; tiles.or [conn][nc] _ Get[ "COrNC" ]; tiles.or [conn][extra] _ Get[ "HPlaCOrEx" ]; tiles.glue [dataUp][leftSide] _ Get[ "HPlaDLeftSide" ]; tiles.glue [dataUp][between] _ Get[ "HPlaDBetween" ]; tiles.glue [dataUp][rightSide] _ Get[ "HPlaDRightSide" ]; tiles.and [dataUp][left] _ Get[ "DAndLt" ]; tiles.and [dataUp][right] _ Get[ "DAndRt" ]; tiles.and [dataUp][nc] _ Get[ "DAnd" ]; tiles.or [dataUp][left] _ Get[ "DOr" ]; tiles.or [dataUp][nc] _ Get[ "DOrNC" ]; tiles.or [dataUp][extra] _ Get[ "HPlaDOrEx" ]; tiles.glue [dataDn][leftSide] _ tiles.glue [dataUp][leftSide]; tiles.glue [dataDn][between] _ FlipY[ tiles.glue [dataUp][between] ]; tiles.glue [dataDn][rightSide] _ FlipY[ tiles.glue [dataUp][rightSide] ]; tiles.and [dataDn][left] _ tiles.and [dataUp][left]; tiles.and [dataDn][right] _ tiles.and [dataUp][right]; tiles.and [dataDn][nc] _ tiles.and [dataUp][nc]; tiles.and [dataDn][extra] _ tiles.and [dataUp][extra]; tiles.or [dataDn][left] _ FlipY[ tiles.or [dataUp][left] ]; tiles.or [dataDn][nc] _ FlipY[ tiles.or [dataUp][nc] ]; tiles.or [dataDn][extra] _ FlipY[ tiles.or [dataUp][extra] ]; RETURN[tiles]}; <<>> log: IO.STREAM _ CoreFrame.GetLog[]; <<>> END. <<>>