DPMux:
CEDAR
PROGRAM
IMPORTS CDBasics, CDRects, CDSatellites, CDSimpleRules, CDTexts, CMosB, CMosBObjects, CoreGeometry, CoreOps, CoreProperties, DP, IO, Lists, PW, RefTab, Rope, RopeList, Sisyph, SourceFromLayout, SymTab, TerminalIO
EXPORTS DP =
BEGIN
Signal: SIGNAL = CODE;
textScale: INT ← 2;
font: CDTexts.CDFont ← CDTexts.MakeFont["Xerox/TiogaFonts/Helvetica7", textScale];
dwText: CD.Object ← CDTexts.Create["driveWeak", font];
Vdd: DP.ROPE ← "Vdd";
Gnd: DP.ROPE ← "Gnd";
plus: DP.ROPE ← "+";
minus: DP.ROPE ← "-";
log: IO.STREAM ← TerminalIO.TOS[];
lambda: INT ← DP.lambda;
pwrW: INT ← DP.pwrW;
metW: INT ← DP.metW;
met2W: INT ← DP.met2W;
polW: INT ← DP.polW;
difW: INT ← DP.difW;
topTail: INT ← DP.topTail;
leftTail: INT ← DP.leftTail; -- to center of 0th channel
rightTail: INT ← DP.rightTail; -- metPitch-leftTail
botTail: INT ← DP.botTail;
cnctSize: INT ← DP.cnctSize;
metPitch: INT ← DP.metPitch;
met2Pitch: INT ← DP.met2Pitch;
layRules: ATOM ← $cmosB;
nullCC: DP.ROPE ← "=";
dpCharCodeProp: ATOM ← CoreProperties.RegisterProperty[$DPCharCode];
GetCharCode:
PUBLIC
PROC[wire:
DP.Wire]
RETURNS[charCode:
DP.
ROPE] = {
IF wire=NIL THEN RETURN[nullCC];
charCode ← NARROW [CoreProperties.GetWireProp[wire, dpCharCodeProp]];
IF charCode=NIL THEN RETURN[nullCC]};
SetCharCode:
PUBLIC
PROC[wire:
DP.Wire, charCode:
DP.
ROPE] =
{CoreProperties.PutWireProp[wire, dpCharCodeProp, charCode]};
GetMuxCellTypes:
PUBLIC
PROC[dp:
DP.DataPath, inst:
DP.CellInstance]
RETURNS[muxes: DP.CellTypeSeq] = {
OPEN CG: CoreGeometry;
data: CoreClasses.RecordCellType ← NARROW[inst.type.data];
top, bot, ctl, in, out: DP.Wire;
wires: DP.Wires;
gnd: DP.Wire ← FindCCWire[data.internal, minus];
vdd: DP.Wire ← FindCCWire[data.internal, plus];
schDeco: CG.Decoration ← Sisyph.mode.decoration;
name: DP.ROPE ← "Mux|";
char: CHAR ← 'a;
FindCCWire:
PROC[wire:
DP.Wire, cc:
DP.ROPE]
RETURNS[subWire:
DP.Wire] = {
FOR i:
NAT
IN [0..wire.size)
DO
IF Rope.Equal[GetCharCode[wire[i]], cc] THEN RETURN[wire[i]];
REPEAT FINISHED => ERROR ENDLOOP};
SetCC:
PROC[wire:
DP.Wire] = {
cc: DP.ROPE ← GetCharCode[wire];
IF wire#
NIL
AND Rope.Equal[cc, nullCC]
THEN
{cc ← IO.PutFR["%g", IO.char[char]]; char𡤌har+1; SetCharCode[wire, cc]};
name ← name.Cat[cc]};
EachSideWire: CG.EachSortedPinProc = {wires ← CONS[wire, wires]};
EachChanWire:
CG.EachSortedPinProc = {
-- wire min max layer
count: INT ← 0;
chan: INT ← (DP.SchHalfChan[(min+max)/2]-1)/2;
FOR ws: DP.Wires ← wires, ws.rest WHILE ws#NIL DO count ← count+1 ENDLOOP;
IF dp.spec.chans
IN [count..chan)
THEN {
THROUGH [count..dp.spec.chans) DO wires ← CONS[NIL, wires] ENDLOOP;
wires ← CONS[gnd, wires];
wires ← CONS[vdd, wires];
count ← dp.spec.chans+2};
IF chan < count THEN Signal[];
THROUGH [count..chan) DO wires ← CONS[NIL, wires] ENDLOOP;
wires ← CONS[wire, wires]};
SetCharCode[gnd, minus];
SetCharCode[vdd, plus];
wires ← NIL; []←CG.EnumerateSortedSides[schDeco, inst.type, top, EachChanWire];
top ← CoreOps.CreateWire[CoreOps.Reverse[wires]];
wires ← NIL; []←CG.EnumerateSortedSides[schDeco, inst.type, bottom, EachChanWire];
bot ← CoreOps.CreateWire[CoreOps.Reverse[wires]];
wires ← NIL; []←CG.EnumerateSortedSides[schDeco, inst.type, left, EachSideWire];
ctl ← CoreOps.CreateWire[CoreOps.Reverse[wires]];
in ← CoreOps.CreateWires[ctl.size];
FOR child:
NAT
IN [0..data.size)
DO
gate: DP.Wire ← data[child].actual[CoreOps.GetWireIndex[data[child].type.public, "gate"]];
ch1: DP.Wire ← data[child].actual[CoreOps.GetWireIndex[data[child].type.public, "ch1"]];
ch2: DP.Wire ← data[child].actual[CoreOps.GetWireIndex[data[child].type.public, "ch2"]];
FOR index:
INT
IN [0..ctl.size)
DO
IF ctl[index]#gate THEN LOOP;
IF in[index]#NIL THEN Signal[]; in[index] ← ch1;
IF out#NIL AND out#ch2 THEN Signal[]; out ← ch2;
EXIT REPEAT FINISHED=> Signal[] ENDLOOP;
ENDLOOP;
FOR index: INT IN [0..top.size) DO SetCC[top[index]] ENDLOOP; name ← name.Cat["|"];
FOR index: INT IN [0..bot.size) DO SetCC[bot[index]] ENDLOOP; name ← name.Cat["|"];
FOR index: INT IN [0..ctl.size) DO SetCC[ctl[index]] ENDLOOP; name ← name.Cat["|"];
FOR index: INT IN [0..in.size) DO SetCC[in[index]] ENDLOOP; name ← name.Cat["|"];
SetCC[out];
muxes ← NEW[DP.CellTypeSeqRec[dp.spec.n]];
FOR bit:
INT
IN [0..dp.spec.n)
DO muxes[bit] ← GetMux[dp.spec.chans, dp.spec.dChans, name] ENDLOOP};
objCache: SymTab.Ref ← SymTab.Create[];
cellCache: RefTab.Ref ← RefTab.Create[];
GetMux:
PROC[rChans, dChans:
INT, refName:
DP.
ROPE]
RETURNS[mux: DP.CellType] = {
Valid:
PROC
RETURNS[
BOOL] = {
IF name.Length=0 THEN RETURN[FALSE];
char ← name.Fetch[]; name ← name.Substr[1];
RETURN[char#'|]};
char: CHAR;
name: DP.ROPE;
object: CD.Object ← NARROW[SymTab.Fetch[objCache, refName].val];
IF object=
NIL
THEN {
RP:
PROC[ch:
CHAR]
RETURNS[rope:
DP.
ROPE] =
{IF ch = '= THEN RETURN[NIL]; rope←IO.PutFR["%g", IO.char[ch]]};
Rev:
PROC [ls:
LIST
OF
DP.
ROPE]
RETURNS[
LIST
OF
DP.
ROPE] =
{RETURN[RopeList.Reverse[ls]]};
top, bot, ctl, in, out: LIST OF DP.ROPE ← NIL;
name ← refName.Substr[4];
WHILE Valid[] DO top ← CONS[RP[char], top] ENDLOOP; top ← Rev[top];
WHILE Valid[] DO bot ← CONS[RP[char], bot] ENDLOOP; bot ← Rev[bot];
WHILE Valid[] DO ctl ← CONS[RP[char], ctl] ENDLOOP; ctl ← Rev[ctl];
WHILE Valid[] DO in ← CONS[RP[char], in] ENDLOOP; in ← Rev[in];
WHILE Valid[] DO out ← CONS[RP[char], out] ENDLOOP; out ← Rev[out];
object ← Mux[refName, rChans, dChans, top, ctl, in, out, bot];
[]←SymTab.Store[objCache, refName, object]};
IF (mux ←
NARROW[RefTab.Fetch[cellCache, object].val])=
NIL
THEN {
mux ← SourceFromLayout.LayoutSource[object, refName];
[]←RefTab.Store[cellCache, object, mux]}};
Mux:
PROC [
name: Rope.ROPE,
rChans: INT,
dChans: INT,
top: LIST OF DP.ROPE,
ctl: LIST OF DP.ROPE,
in: LIST OF DP.ROPE,
out: LIST OF DP.ROPE,
bot:
LIST
OF
DP.
ROPE]
RETURNS [cell: CD.Object] = {
cellWidth: INT ← (rChans + dChans)*DP.layChanW;
xstrLgth: INT ← 8*lambda;
xstrWth: INT ← (4+4)*lambda;
xstrWthBig: INT ← (4+8)*lambda;
tranBiasx: INT ← (xstrWth-metW)/2;
tranBiasLtx: INT ← tranBiasx + 4*lambda;
xstrHt: INT ← xstrLgth + 2*difW;
pFrng: INT ← (pwrW-metW)/2;
topExtra: INT ← cnctSize/2 + topTail;
botExtra: INT ← cnctSize/2 + botTail;
pitch: CD.Position = [metPitch, met2Pitch];
usingMinTransistor: BOOL ← FALSE;
muxEvenDn: BOOL = TRUE;
range: CD.Position;
outN: DP.ROPE ← IF out=NIL THEN NIL ELSE out.first;
iRect: CD.Rect;
gnd: INT ← rChans;
vdd: INT ← rChans+1;
cnctBiasx: INT ← (cnctSize-metW)/2;
outIndex, outIndexBot: INT;
insts: CD.InstanceList ← NIL;
top ← FixGVCharInList[rChans, top];
bot ← FixGVCharInList[rChans, bot];
range ← [MAX[Lists.ListLength[top],Lists.ListLength[bot]], Lists.ListLength[ctl]];
outIndex ← Lists.ListItemIndexMin[top, outN];
outIndexBot ← Lists.ListItemIndexMin[bot, outN];
IF outIndex # Lists.ListItemIndexMax[top, outN]
OR
outIndexBot # Lists.ListItemIndexMax[bot, outN] OR
(outIndex#-1
AND outIndexBot#-1
AND outIndex#outIndexBot)
THEN {
log.PutF["Multiple column output %g- ABORT", IO.rope[outN]];
Signal[]};
IF outIndex = -1 THEN outIndex ← outIndexBot;
Metal wires and their pins
IF outN#
NIL
AND Lists.ListItemIndexMax[top, outN]=-1
AND Lists.ListItemIndexMax[bot, outN]=-1
THEN {
log.PutF["\n Output signal (%g) is not in either top or bot lists - ABORT",
IO.rope[outN]];
Signal[]};
IF outN#
NIL
AND Lists.ListItemIndexMax[in, outN]#-1
THEN{
log.PutF["\n Output signal (%g) is also used as input - ABORT", IO.rope[outN]];
Signal[]};
FOR i:
INT
IN [0..range.x)
DO
loc: CD.Position ← [i*pitch.x, 0];
tIO: DP.ROPE ← Lists.ListIndexItem[top, i];
bIO: DP.ROPE ← Lists.ListIndexItem[bot, i];
topOut: BOOL ← Rope.Equal[tIO,outN];
botOut: BOOL ← Rope.Equal[bIO,outN];
tY: INT ← IF topOut THEN Lists.ListNonNILIndexMin[in] ELSE Lists.ListItemIndexMin[in,tIO];
bY: INT ← IF botOut THEN Lists.ListNonNILIndexMax[in] ELSE Lists.ListItemIndexMax[in,bIO];
tY ← tY + ((tY + (IF topOut=muxEvenDn THEN 1 ELSE 2)) MOD 2);
bY ← bY + ((bY + (IF botOut=muxEvenDn THEN 1 ELSE 2)) MOD 2);
IF tY=-1 AND bY=-1 THEN tY𡤋Y𡤀
IF ~Rope.Equal[tIO, bIO]
AND tY<=bY
AND tIO#
NIL
AND bIO#
NIL
THEN {
log.PutF["\n 2 signals (%g, %g) in same channel - ABORT",
IO.rope[tIO], IO.rope[bIO]];
Signal[]};
IF tIO#
NIL
THEN insts ← AddRetInst[insts: insts, name: tIO, level: CMosB.met,
size: [metW, (range.y-tY) * pitch.y + topExtra ],
loc: [i*pitch.x, tY * pitch.y ]];
IF bIO#
NIL
THEN insts ← AddRetInst[insts: insts, name: bIO, level: CMosB.met,
size: [metW, bY * pitch.y + botExtra ],
loc: [i*pitch.x, 0 * pitch.y - botExtra ]];
ENDLOOP;
FOR vgIndex:
INT
IN [gnd..vdd]
DO insts ← AddRetInst[
insts: insts, name: (IF vgIndex=gnd THEN minus ELSE plus), level: CMosB.met,
size: [pwrW, range.y * pitch.y + topExtra + botExtra ],
loc: [vgIndex*pitch.x-pFrng, - botExtra ]] ENDLOOP;
AddMetalPins
[cell, top, bot, 0, range.y*pitch.y+ topExtra, - botExtra, TRUE];
BEGIN
xstr:
CD.Object ← CMosBObjects.CreateTransistor
[size: [xstrWth, xstrLgth], difLayer: CMosB.ndif];
xstrBig:
CD.Object ← CMosBObjects.CreateTransistor
[size: [xstrWthBig, xstrLgth], difLayer: CMosB.ndif];
dcon: CD.Object ← CDSimpleRules.Contact[layRules, CMosB.met, CMosB.ndif];
pcon: CD.Object ← CDSimpleRules.Contact[layRules, CMosB.met, CMosB.pol];
vcon: CD.Object ← CDSimpleRules.Contact[layRules, CMosB.met, CMosB.met2];
scon: CD.Object ← CMosBObjects.CreateDifCon[CMosB.pwellCont];
pvconn: CD.Object ← CDRects.CreateRect[[2*cnctSize, cnctSize], CMosB.met];
lstIONotGnd: BOOL ← TRUE;
lstGndClear: BOOL ← TRUE;
thsIONotGnd: BOOL ← TRUE;
thsGndClear: BOOL ← TRUE;
FOR ctlIndex:
INT
IN [0..range.y)
DO
Include:
PROC[object:
CD.Object, location:
CD.Position] =
{insts ← CONS[ NEW[CD.InstanceRep ← [object, [location]]], insts]};
AddGndContact:
PROC[updn: {up, dn}] = {
IF updn=up
THEN Include[scon, [gnd*pitch.x-cnctBiasx, (ctlIndex+1)*pitch.y -cnctSize/2 ]]
ELSE Include[scon, [gnd*pitch.x-cnctBiasx, (ctlIndex+0)*pitch.y -cnctSize/2 ]]};
AddMux:
PROC [index:
CD.Position, lt, rt:
BOOL] = {
ptchOset: INT ← (xstrLgth+difW)/2; -- for gap between transistor and diff wire
dWL: INT ← (ABS[outIndex-index.x])*pitch.x+cnctSize;
pWL: INT ← (range.x-index.x)*pitch.x;
minX: INT ← MIN[outIndex, index.x];
polX: INT ← MIN[outIndex, index.x];
pol: CD.Object ← CDRects.CreateRect[[pWL, polW], CMosB.pol];
dif: CD.Object ← CDRects.CreateRect[[dWL, difW], CMosB.ndif];
dPtch: CD.Object ← CDRects.CreateRect[[xstrWth, difW], CMosB.ndif];
dir: INT ← IF ((index.y MOD 2)=0)=muxEvenDn THEN 1 ELSE -1;
yloc: INT ← index.y*pitch.y + pitch.y/2;
Include[pcon, [range.x *pitch.x -cnctBiasx, yloc -cnctSize/2 ]];
Include[pvconn, [range.x *pitch.x -cnctBiasx, yloc -cnctSize/2 ]];
Include[vcon, [range.x *pitch.x -cnctBiasx+cnctSize+lambda, yloc -cnctSize/2 ]];
Include[pol, [index.x *pitch.x -cnctBiasx, yloc -polW/2 ]];
Include[dif, [minX *pitch.x -cnctBiasx, yloc +dir*pitch.y/2 -difW/2 ]];
Include[dPtch, [index.x *pitch.x -cnctBiasx, yloc +dir*ptchOset -difW/2 ]];
Include[dcon, [outIndex *pitch.x -cnctBiasx, yloc +dir*pitch.y/2 -cnctSize/2 ]];
Include[dcon, [index.x *pitch.x -cnctBiasx, yloc -dir*pitch.y/2 -cnctSize/2 ]];
Include[dwText, [index.x *pitch.x -tranBiasx, yloc -lambda*textScale/2 ]];
SELECT
TRUE
FROM
lt => Include[xstrBig, [index.x *pitch.x -tranBiasLtx, yloc -xstrLgth/2 ]];
rt => Include[xstrBig, [index.x *pitch.x -tranBiasx, yloc -xstrLgth/2 ]];
ENDCASE => Include[xstr, [index.x *pitch.x -tranBiasx, yloc -xstrLgth/2 ]];
CDSatellites.Associate[master: insts.first, text: insts.rest.first]};
cName: DP.ROPE ← Lists.ListIndexItem[ctl, ctlIndex];
size: CD.Position ← [cellWidth, met2W];
loc: CD.Position ← [metW/2-leftTail, ctlIndex*pitch.y+pitch.y/2-met2W/2];
insts ← AddRetInst[insts: insts, name: cName, size:size, loc:loc, level: CMosB.met2];
PutPin [cell, [met2W, met2W], loc,
CMosB.met2, cName];
PutPin [cell, [met2W, met2W], [metW/2-leftTail+cellWidth-met2W, loc.y],
CMosB.met2, cName];
IF outN#
NIL
THEN {
ioIndex: INT ← IOIndex[ctlIndex, in, top, bot];
ioItem: DP.ROPE ← Lists.ListIndexItem[in, ctlIndex];
IF ioIndex >=0
THEN {
First try to make the transistor larger
inDn: BOOL ← ((ctlIndex MOD 2)=0)=muxEvenDn;
If inDn then there can be no clash above to making the transistor larger since that is the side of the output connection. In this case, ioIndexUp will get -1 even if the correcsponding control really does gate some input.
ioIndexUp: INT ← IF inDn THEN -1 ELSE IOIndex[ctlIndex+1, in, top, bot];
ioIndexDn: INT ← IF ~inDn THEN -1 ELSE IOIndex[ctlIndex-1, in, top, bot];
extLt:
BOOL ← ioIndex # (gnd+1)
AND ioIndex # 0
AND
(ioIndexUp=-1 OR ioIndexUp#(ioIndex-1)) AND
(ioIndexDn=-1 OR ioIndexDn#(ioIndex-1));
extRt:
BOOL ← ioIndex # (gnd-1)
AND ioIndex < (range.x-1) AND
(ioIndexUp=-1 OR ioIndexUp#(ioIndex+1)) AND
(ioIndexDn=-1 OR ioIndexDn#(ioIndex+1));
IF NOT(extLt OR extRt) THEN usingMinTransistor ← TRUE;
AddMux[[ioIndex, ctlIndex], extLt, extRt]};
thsIONotGnd ← ioIndex # gnd;
thsGndClear ← thsIONotGnd AND ((ioIndex<gnd)=(outIndex<gnd));
IF ((ctlIndex
MOD 2)=0)=muxEvenDn
THEN {IF thsIONotGnd AND lstIONotGnd THEN AddGndContact[dn]}
ELSE {IF thsGndClear AND lstGndClear THEN AddGndContact[dn]};
IF (ctlIndex+1) = range.y
THEN
IF ((ctlIndex
MOD 2)=0)=muxEvenDn
THEN {IF thsGndClear THEN AddGndContact[up]}
ELSE {IF thsIONotGnd THEN AddGndContact[up]};
lstIONotGnd ← thsIONotGnd;
lstGndClear ← thsGndClear}
ELSE AddGndContact[dn];
ENDLOOP;
END;
iRect ← [
x1: metW/2-leftTail, y1: -botExtra,
x2: metW/2-leftTail+cellWidth, y2: range.y*pitch.y + topExtra];
cell ← PW.CreateCell[instances: insts, name: name, ir: iRect];
IF usingMinTransistor
THEN
TerminalIO.PutF["Using minimum transistor in mux: %g\n", IO.rope[name]];
RETURN[cell]};
IOIndex:
PROC[ctl:
INT, in, top, bot:
LIST
OF
DP.ROPE]
RETURNS[ioIndex:
INT] = {
ioItem: DP.ROPE;
IF ctl<0 THEN RETURN[-1];
ioItem ← Lists.ListIndexItem[in, ctl];
IF ioItem = NIL THEN RETURN[-1];
ioIndex ← Lists.ListItemIndexMax[top, ioItem];
IF ioIndex>-1 THEN RETURN[ioIndex];
ioIndex ← Lists.ListItemIndexMax[bot, ioItem]};
AddMetalPins: PROC
[cell: CD.Object, top, bot: LIST OF DP.ROPE, refX, topY, botY: INT, realNames: BOOL] = {
length: INT ← MAX[Lists.ListLength[top], Lists.ListLength[bot]];
FOR i: INT IN [0..length) DO
tName: DP.ROPE ← Lists.ListIndexItem[top, i];
bName: DP.ROPE ← Lists.ListIndexItem[bot, i];
size: CD.Position ← [metW, metW];
loc: CD.Position ← [refX+i*metPitch, topY-size.y];
IF tName #NIL THEN PutPin [cell, size, loc, CMosB.met,
(IF realNames THEN tName ELSE NIL)];
IF bName #NIL THEN PutPin [cell, size, [loc.x, botY], CMosB.met,
(IF realNames THEN bName ELSE NIL)];
ENDLOOP};
AddRetInst:
PROC
[insts:
CD.InstanceList, name:
DP.
ROPE, size:
CD.Position, loc:
CD.Position, level:
CD.Layer]
RETURNS[CD.InstanceList] = {
text: CD.Object ← CDTexts.Create[name, font];
textSize: CD.Position ← CDBasics.SizeOfRect[text.bbox];
textLoc:
CD.Position ←
IF size.x>size.y
THEN [loc.x, loc.y + size.y/2 - lambda*textScale/2]
ELSE
IF loc.y < 0
THEN [loc.x + size.x/2 - textSize.x/2, loc.y]
ELSE [loc.x + size.x/2 - textSize.x/2, loc.y + size.y - textSize.y];
IF size.x<0
OR size.y<0
THEN
{log.PutF["Strange rectangle size [%g, %g]\n", IO.int[size.x], IO.int[size.y] ]; Signal[]};
IF size.x=0 OR size.y=0 THEN RETURN[insts];
insts ← CONS[ NEW[CD.InstanceRep ← [text, [textLoc ]]], insts];
insts ← CONS[ NEW[CD.InstanceRep ← [CDRects.CreateRect[size, level], [loc ]]], insts];
CDSatellites.Associate[master: insts.first, text: insts.rest.first];
RETURN[insts]};
FixGVCharInList:
PROC [chans:
INT, list:
LIST
OF
DP.
ROPE]
RETURNS[new: LIST OF DP.ROPE] =
{RETURN[AddGVCharToList[chans, DelGVFromList[list]]]};
DelGVFromList:
PROC [list:
LIST
OF
DP.
ROPE]
RETURNS[new:
LIST
OF
DP.
ROPE] = {
nonNilItemAdded: BOOL ← FALSE;
IF list=NIL THEN RETURN[NIL];
FOR ii:
INT
DECREASING
IN [0..Lists.ListLength[list])
DO
item: DP.ROPE ← Lists.ListIndexItem[list, ii];
IF
Rope.Equal[item, Gnd] OR
Rope.Equal[item, Vdd] OR
Rope.Equal[item, plus] OR
Rope.Equal[item, minus] THEN item ← NIL;
IF item=NIL AND NOT nonNilItemAdded THEN LOOP;
nonNilItemAdded ← TRUE;
new ← CONS[item, new] ENDLOOP};
AddGVCharToList:
PROC [chans:
INT, list:
LIST
OF
DP.
ROPE]
RETURNS[new: LIST OF DP.ROPE] = {
FOR ii:
INT
DECREASING
IN [0..
MAX[chans+2, Lists.ListLength[list]])
DO
item: DP.ROPE ← Lists.ListIndexItem[list, ii];
IF ii=chans+1 THEN item ← plus;
IF ii=chans THEN item ← minus;
new ← CONS[item, new] ENDLOOP};
END.