DIRECTORY IO, Rope, FileNames, CD, CDOrient, CDSymbolicObjects, Misc, IP, IPBasicOps, IPToolBox; IPToolBoxImpl: CEDAR PROGRAM IMPORTS CD, CDSymbolicObjects, IO, Rope, FileNames, CDOrient, Misc, IPBasicOps EXPORTS IPToolBox = BEGIN OPEN BO: IPBasicOps, IPToolBox; IPPinsFromCDPins: PUBLIC PROC [cdObj: CD.Object] RETURNS [iPins: LIST OF REF IP.PinRep _ NIL] ={ EachPin: CDSymbolicObjects.InstEnumerator ~ { pLoc: CD.Position _ inst.location; pSize: CD.Position _ CD.InterestSize[inst.ob]; coord: IntVector _ [pLoc.x + pSize.x/2, pLoc.y + pSize.y/2]; --use the center phyPins: PhysicalPins _ LIST[NEW[IP.PhysicalPinRep _ [coord]]]; pin: REF IP.PinRep _ NEW[IP.PinRep _ [CDSymbolicObjects.GetName[inst], phyPins]]; iPins _ CONS[pin, iPins]; }; [] _ CDSymbolicObjects.EnumerateSymbolicObs[cdObj, EachPin]; }; --IPPinsFromCDPins -- IPPinFromCDPin: PROC [cdPin: CD.Instance] RETURNS [REF IP.PinRep] = { -- physicalPins: PROC RETURNS [phyPins: PhysicalPins _ NIL] = { -- FOR pPins: LIST OF REF CDPins.PhysicalPin _ cdPin.physicalPin, pPins.rest UNTIL pPins = NIL DO -- pRect: CD.Rect _ pPins.first.rect; -- coord: IntVector _ [(pRect.x1 + pRect.x2)/2, (pRect.y1 + pRect.y2)/2]; -- phyPins _ CONS[NEW[IP.PhysicalPinRep _ [coord]], phyPins]; -- ENDLOOP; -- }; --physicalPins -- RETURN [NEW[IP.PinRep _ [cdPin.pinName, physicalPins[]]]] -- }; --IPPinFromCDPin MakeIPPins: PUBLIC PROC[ipPins: LIST OF REF IP.PinRep, origin: IntVector _ [0, 0], coShape: REF IP.ShapeRep _ NIL, cutOff: NAT _ 0] RETURNS [newPins: LIST OF REF IP.PinRep _ NIL] ={ makePhyPin: PROC [phyPin: REF IP.PhysicalPinRep] RETURNS [REF IP.PhysicalPinRep] = { coord: IntVector _ [phyPin.coord.x - origin.x, phyPin.coord.y - origin.y]; side: IP.PinSideType _ NearestSide[coShape, coord, cutOff].side; RETURN [NEW[IP.PhysicalPinRep _ [coord, side, phyPin.active]]]; }; --makePhyPin makeIPPins: PROC[ipPin: REF IP.PinRep] RETURNS [REF IP.PinRep] ={ phyPins: PhysicalPins _ NIL; FOR l: PhysicalPins _ ipPin.physicalPins, l.rest UNTIL l = NIL DO phyPins _ CONS[makePhyPin[l.first], phyPins]; ENDLOOP; RETURN [NEW[IP.PinRep _ [ipPin.name, phyPins, ipPin.auxInfo]]] }; --makeIPPins WHILE ipPins # NIL DO newPins _ CONS[makeIPPins[ipPins.first], newPins]; ipPins _ ipPins.rest; ENDLOOP; }; --MakeIPPins NearestSide: PUBLIC PROC [shape: REF IP.ShapeRep, point: IntVector, cutOff: NAT _ 0] RETURNS [inShape: BOOL, side: IP.PinSideType] ={ minDist: INT _ LAST[INT]; inShape _ Misc.RectContainPt[GetBRect[shape], point.x, point.y]; FOR corner: IP.CornerTypes IN [sw..nw] DO IF Misc.RectContainPt[GetCornerRect[shape, corner], point.x, point.y] THEN inShape _ FALSE; ENDLOOP; FOR pSide: IP.PinSideType IN [south..nwVer] DO newDist: INT _ DistFromSide[shape, point, pSide]; IF newDist < minDist THEN {minDist _ newDist; side _ pSide}; ENDLOOP; IF minDist > cutOff THEN side _ interior; }; --NearestSide DistFromSide: PUBLIC PROC[shape: REF IP.ShapeRep, point: IntVector, side: IP.PinSideType] RETURNS [INT] ={ ptCoord, ptProj, sdCoord: INT; sdIntl: Misc.Interval; rect: Misc.Rect; IF shape = NIL THEN RETURN [LAST[INT]]; SELECT side FROM south, north, swHor, seHor, neHor, nwHor => {ptProj _ point.x; ptCoord _ point.y}; east, west, swVer, seVer, neVer, nwVer => {ptProj _ point.y; ptCoord _ point.x}; interior, unknown => RETURN [LAST [INT]]; -- no need to do anything ENDCASE => ERROR; IF side IN [south..west] THEN { rect _ GetBRect[shape]; SELECT side FROM south => {sdCoord _ Misc.yMin[rect]; sdIntl _ Misc.x[rect]; sdIntl _ Misc.IntlSubtract[sdIntl, Misc.x[GetCornerRect[shape, sw]]]; sdIntl _ Misc.IntlSubtract[sdIntl, Misc.x[GetCornerRect[shape, se]]];}; east => {sdCoord _ Misc.xMax[rect]; sdIntl _ Misc.y[rect]; sdIntl _ Misc.IntlSubtract[sdIntl, Misc.y[GetCornerRect[shape, se]]]; sdIntl _ Misc.IntlSubtract[sdIntl, Misc.y[GetCornerRect[shape, ne]]];}; north => {sdCoord _ Misc.yMax[rect]; sdIntl _ Misc.x[rect]; sdIntl _ Misc.IntlSubtract[sdIntl, Misc.x[GetCornerRect[shape, ne]]]; sdIntl _ Misc.IntlSubtract[sdIntl, Misc.x[GetCornerRect[shape, nw]]];}; west => {sdCoord _ Misc.xMin[rect]; sdIntl _ Misc.y[rect]; sdIntl _ Misc.IntlSubtract[sdIntl, Misc.y[GetCornerRect[shape, nw]]]; sdIntl _ Misc.IntlSubtract[sdIntl, Misc.y[GetCornerRect[shape, sw]]];}; ENDCASE => ERROR; } ELSE { SELECT side FROM swHor => {rect _ GetCornerRect[shape, sw, , 0]; IF rect = NIL THEN RETURN [LAST[INT]]; sdCoord _ Misc.yMax[rect]; sdIntl _ Misc.x[rect];}; seHor => {rect _ GetCornerRect[shape, se, , 0]; IF rect = NIL THEN RETURN [LAST[INT]]; sdCoord _ Misc.yMax[rect]; sdIntl _ Misc.x[rect];}; neHor => {rect _ GetCornerRect[shape, ne, , 0]; IF rect = NIL THEN RETURN [LAST[INT]]; sdCoord _ Misc.yMin[rect]; sdIntl _ Misc.x[rect];}; nwHor => {rect _ GetCornerRect[shape, nw, , 0]; IF rect = NIL THEN RETURN [LAST[INT]]; sdCoord _ Misc.yMin[rect]; sdIntl _ Misc.x[rect];}; swVer => {rect _ GetCornerRect[shape, sw, , 0]; IF rect = NIL THEN RETURN [LAST[INT]]; sdCoord _ Misc.xMax[rect]; sdIntl _ Misc.y[rect];}; seVer => {rect _ GetCornerRect[shape, se, , 0]; IF rect = NIL THEN RETURN [LAST[INT]]; sdCoord _ Misc.xMax[rect]; sdIntl _ Misc.y[rect];}; neVer => {rect _ GetCornerRect[shape, ne, , 0]; IF rect = NIL THEN RETURN [LAST[INT]]; sdCoord _ Misc.xMin[rect]; sdIntl _ Misc.y[rect];}; nwVer => {rect _ GetCornerRect[shape, nw, , 0]; IF rect = NIL THEN RETURN [LAST[INT]]; sdCoord _ Misc.xMin[rect]; sdIntl _ Misc.y[rect];}; ENDCASE => ERROR; }; IF Misc.IntlContainPt[sdIntl, ptProj] THEN RETURN [ABS[ptCoord - sdCoord]] ELSE RETURN [LAST[INT]]; }; --DistFromSide GetCorner: PUBLIC PROC [shape: IP.ShapeRep, corner: IP.CornerTypes] RETURNS [REF IP.NatVector] ={ SELECT corner FROM sw => RETURN [shape.cornerSpaces.sw]; se => RETURN [shape.cornerSpaces.se]; ne => RETURN [shape.cornerSpaces.ne]; nw => RETURN [shape.cornerSpaces.nw]; ENDCASE => ERROR; };--GetCorner GetBRect: PUBLIC PROC[shape: REF IP.ShapeRep, origin: IntVector _ [0, 0]] RETURNS [Misc.Rect] ={ IF shape = NIL THEN RETURN [NIL]; RETURN[Misc.RectCreate[origin.x, origin.y, origin.x + shape.dim.x, origin.y + shape.dim.y ]] }; --GetBRect GetCornerRect: PUBLIC PROC[shape: REF IP.ShapeRep, corner: IP.CornerTypes, origin: IntVector _ [0, 0], crop: INT _ 1] RETURNS [Misc.Rect] ={ cSpace: REF IP.NatVector _ GetCorner[shape^, corner]; IF cSpace = NIL THEN RETURN [NIL]; BEGIN OPEN s: shape.cornerSpaces; SELECT corner FROM sw => RETURN [Misc.RectCreate[origin.x, origin.y, origin.x + s.sw.x - crop, origin.y + s.sw.y - crop]]; se => RETURN [Misc.RectCreate[origin.x + shape.dim.x - s.se.x + crop, origin.y, origin.x + shape.dim.x, origin.y + s.se.y - crop]] ; ne => RETURN [Misc.RectCreate[origin.x+ shape.dim.x - s.ne.x + crop, origin.y+shape.dim.y - s.ne.y + crop, origin.x+ shape.dim.x, origin.y+shape.dim.y]]; nw => RETURN [Misc.RectCreate[origin.x, origin.y + shape.dim.y - s.nw.y + crop, origin.x + s.nw.x - crop, origin.y + shape.dim.y]]; ENDCASE => ERROR; END; };--GetCornerRect GetCornerRects: PUBLIC PROC[shape: REF IP.ShapeRep, origin: IntVector _ [0, 0], crop: INT _ 1] RETURNS [sw, se, ne, nw: Misc.Rect _ NIL] ={ IF shape = NIL THEN RETURN; BEGIN OPEN s: shape.cornerSpaces; IF s.sw # NIL THEN sw _ Misc.RectCreate[origin.x, origin.y, origin.x + s.sw.x - crop, origin.y + s.sw.y - crop]; IF s.se # NIL THEN se _ Misc.RectCreate[origin.x + shape.dim.x - s.se.x + crop, origin.y, origin.x + shape.dim.x, origin.y + s.se.y - crop]; IF s.ne # NIL THEN ne _ Misc.RectCreate[origin.x+ shape.dim.x - s.ne.x + crop, origin.y+shape.dim.y - s.ne.y + crop, origin.x+ shape.dim.x, origin.y+shape.dim.y]; IF s.nw # NIL THEN nw _ Misc.RectCreate[origin.x, origin.y + shape.dim.y - s.nw.y + crop, origin.x + s.nw.x - crop, origin.y + shape.dim.y]; END; };--GetCornerRects CopyShape: PUBLIC PROC[oShape: REF IP.ShapeRep, orient: CD.Orientation] RETURNS [nShape: REF IP.ShapeRep] ={ nShape _ BO.Copy1Shape[oShape]; OrientShape[nShape, orient]; }; --CopyShape OrientShape: PUBLIC PROC[shape: REF IP.ShapeRep, orient: IP.Orientation] ={ IF CDOrient.IncludesMirrorX[orient] THEN MirrorXShape[shape]; Rotate90Shape[shape, orient/2]; }; --OrientShape MirrorXShape: PUBLIC PROC[shape: REF IP.ShapeRep] ={ OPEN sC: shape.cornerSpaces; sw, se, ne, nw: REF IP.NatVector; [sw, se, ne, nw] _ shape.cornerSpaces; sC.sw _ se; sC.se _ sw; sC.nw _ ne; sC.ne _ nw; };--MirrorXShape Rotate90Shape: PUBLIC PROC [shape: REF IP.ShapeRep, numberOfRot: INT _ 1] ={ OPEN sC: shape.cornerSpaces; sw, se, ne, nw: REF IP.NatVector; [sw, se, ne, nw] _ shape.cornerSpaces; SELECT numberOfRot MOD 4 FROM 0 => NULL; 1, -3 => {sC.sw _ nw; sC.se _ sw; sC.ne _ se; sC.nw _ ne}; 2, -2 => {sC.sw _ ne; sC.se _ nw; sC.ne _ sw; sC.nw _ se}; 3, -1 => {sC.nw _ sw; sC.sw _ se; sC.se _ ne; sC.ne _ nw}; ENDCASE => ERROR; }; --Rotate90Shape ParseError: PUBLIC ERROR [reason: ATOM, at: REF] = CODE; GetIdRope: PUBLIC PROC[stream: IO.STREAM] RETURNS [Rope.ROPE]={ id: Rope.ROPE _ stream.GetID[]; char: CHAR; WHILE (char _ stream.GetChar) # ': DO id _ Rope.Cat[id, Rope.FromChar[char]] ENDLOOP; RETURN [id]; }; --GetIdRope-- GetIdAtom: PUBLIC PROC[stream: IO.STREAM] RETURNS [ATOM]={ id: ATOM _ stream.GetAtom[]; char: CHAR; IF (char _ stream.GetChar) = ': THEN RETURN [id] ELSE ERROR ParseError[$syntaxError, NEW[CHAR _ char]]; }; --GetIdRope-- EnterBlock: PUBLIC PROC [stream: IO.STREAM] = { char: CHAR; [] _ stream.SkipWhitespace[]; IF (char _ stream.GetChar) # '{ THEN ERROR ParseError[$noBegin, NEW[CHAR _ char]]; }; --EnterBlock ExitBlock: PUBLIC PROC [stream: IO.STREAM] RETURNS [BOOL _ TRUE]= { [] _ stream.SkipWhitespace[]; IF stream.PeekChar = '} THEN [] _ stream.GetChar ELSE RETURN [FALSE] }; --ExitBlock RemoveBlock: PUBLIC PROC [stream: IO.STREAM] = { EnterBlock[stream]; UNTIL ExitBlock[stream] DO IF stream.GetChar = '{ THEN RemoveBlock[stream]; ENDLOOP; }; --RemoveBlock GetNatVector: PUBLIC PROC[stream: IO.STREAM] RETURNS [REF IP.NatVector] = { refPair: LIST OF REF ANY _ NARROW[stream.GetRefAny]; x, y: NAT; IF refPair = NIL THEN RETURN [NIL]; x _ NARROW[refPair.first, REF INT]^; y _ NARROW[refPair.rest.first, REF INT]^; RETURN [BO.NuNatVector[x, y]] }; --GetNatVector-- GetIntVector: PUBLIC PROC[stream: IO.STREAM] RETURNS [REF IntVector] = { refPair: LIST OF REF ANY _ NARROW[stream.GetRefAny]; x, y: INT; IF refPair = NIL THEN RETURN [NIL]; x _ NARROW[refPair.first, REF INT]^; y _ NARROW[refPair.rest.first, REF INT]^; RETURN [BO.NuIntVector[x, y]] }; --GetIntVector-- GetShape: PUBLIC PROC [stream: IO.STREAM] RETURNS [shape: REF IP.ShapeRep] = { OPEN sC: shape.cornerSpaces; EnterBlock[stream]; shape _ NEW[IP.ShapeRep _ [dim: GetNatVector[stream]]]; UNTIL ExitBlock[stream] DO token: ATOM _ GetIdAtom[stream]; SELECT token FROM $sw => sC.sw _ GetNatVector[stream]; --$sw $se => sC.se _ GetNatVector[stream]; --$se $ne => sC.ne _ GetNatVector[stream]; --$ne $nw => sC.nw _ GetNatVector[stream]; --$nw ENDCASE => ERROR ParseError[$badToken, token]; ENDLOOP; }; --GetShape GetPhysicalPins: PUBLIC PROC[stream: IO.STREAM] RETURNS [phyPins: PhysicalPins _ NIL] ={ getPhyPin: PROC RETURNS [REF IP.PhysicalPinRep] ={ coord: IntVector _ GetIntVector[stream]^; side: IP.PinSideType _ GetPinSide[stream]; active: BOOL _ stream.GetBool; RETURN [NEW [IP.PhysicalPinRep _ [coord, side, active]]] }; --getPhyPin EnterBlock[stream]; UNTIL ExitBlock[stream] DO phyPins _ CONS [getPhyPin[], phyPins]; ENDLOOP; }; --GetPhysicalPins PutShape: PUBLIC PROC[stream: IO.STREAM, shape: REF IP.ShapeRep] ={ stream.PutF["{"]; IF shape # NIL THEN { OPEN sC: shape.cornerSpaces; stream.PutF["(%g %g) ", IO.int[shape.dim.x], IO.int[shape.dim.y]]; IF sC.sw # NIL THEN stream.PutF["sw: (%g %g) ", IO.int[sC.sw.x], IO.int[sC.sw.y]]; IF sC.se # NIL THEN stream.PutF["se: (%g %g) ", IO.int[sC.se.x], IO.int[sC.se.y]]; IF sC.ne # NIL THEN stream.PutF["ne: (%g %g) ", IO.int[sC.ne.x], IO.int[sC.ne.y]]; IF sC.nw # NIL THEN stream.PutF["nw: (%g %g) ", IO.int[sC.nw.x], IO.int[sC.nw.y]]; }; --endIF stream.PutF["}"]; };--PutShape PutPhysicalPins: PUBLIC PROC[stream: IO.STREAM, physicalPins: PhysicalPins] ={ stream.PutF["{"]; WHILE physicalPins # NIL DO phyPin: REF IP.PhysicalPinRep _ physicalPins.first; stream.PutF[" (%g %g) %g %g", IO.int[phyPin.coord.x], IO.int[phyPin.coord.y], IO.atom[IPPinSideToAtom[phyPin.side]], IO.bool[phyPin.active], ]; physicalPins _ physicalPins.rest; ENDLOOP; stream.PutF["}"]; }; --PutShape OrientPhysicalPins: PUBLIC PROC [phyPins: PhysicalPins, cellDim: IP.NatVector, cellOrient: IP.Orientation, cellOrigin: IntVector _ [0, 0]] ={ WHILE phyPins # NIL DO pPin: REF IP.PhysicalPinRep _ phyPins.first; pPin.coord _ CDOrient.MapPoint[pPin.coord, [cellDim.x, cellDim.y], cellOrient, cellOrigin]; pPin.side _ OrientPinSide[pPin.side, cellOrient]; phyPins _ phyPins.rest; ENDLOOP; }; --OrientPhysicalPins MirrorXPhysicalPins: PUBLIC PROC [phyPins: PhysicalPins, cellDim: IP.NatVector, cellOrigin: IntVector _ [0, 0]] ={ WHILE phyPins # NIL DO pPin: REF IP.PhysicalPinRep _ phyPins.first; pPin.coord _ CDOrient.MapPoint[pPin.coord, [cellDim.x, cellDim.y], CDOrient.mirrorX, cellOrigin]; pPin.side _ MirrorXPinSide[pPin.side]; phyPins _ phyPins.rest; ENDLOOP; };--MirrorXPhysicalPins Rotate90PhysicalPins: PUBLIC PROC [phyPins: PhysicalPins, cellDim: IP.NatVector, numberOfRot: INT _ 1, cellOrigin: IntVector _ [0, 0]] ={ CDRotn: CDOrient.Orientation; SELECT numberOfRot MOD 4 FROM 0 => CDRotn _ 0; 1, -3 => CDRotn _ 2; 2, -2 => CDRotn _ 4; 3, -1 => CDRotn _ 6; ENDCASE => ERROR; WHILE phyPins # NIL DO pPin: REF IP.PhysicalPinRep _ phyPins.first; pPin.coord _ CDOrient.MapPoint[pPin.coord, [cellDim.x, cellDim.y], CDRotn, cellOrigin]; pPin.side _ Rotate90PinSide[pPin.side, numberOfRot]; phyPins _ phyPins.rest; ENDLOOP; };--Rotate90PhysicalPins OrientPinSide: PUBLIC PROC[side: IP.PinSideType, orient: IP.Orientation] RETURNS [IP.PinSideType] ={ IF CDOrient.IncludesMirrorX[orient] THEN side _ MirrorXPinSide[side]; RETURN [Rotate90PinSide[side, orient/2]]; }; --OrientPinSide MirrorXPinSide: PUBLIC PROC[side: IP.PinSideType] RETURNS [IP.PinSideType] ={ RETURN [ SELECT side FROM south, north, interior, unknown => side, east => west, west => east, swHor => seHor, seHor => swHor, neHor => nwHor, nwHor => neHor, swVer => seVer, seVer => swVer, neVer => nwVer, nwVer => neVer, ENDCASE => ERROR ]; };--MirrorXPinSide Rotate90PinSide: PUBLIC PROC [side: IP.PinSideType, numberOfRot: INT _ 1] RETURNS [IP.PinSideType]={ rot1: PROC [s: IP.PinSideType] RETURNS [IP.PinSideType] = { RETURN [SELECT s FROM south => east, east => north, north => west, west => south, swHor => seVer, seVer => neHor, neHor => nwVer, nwVer => swHor, swVer => seHor, seHor => neVer, neVer => nwHor, nwHor => swVer, interior, unknown => side, ENDCASE => ERROR]; }; --rot1 rot2: PROC [s: IP.PinSideType] RETURNS [IP.PinSideType] = { RETURN [SELECT s FROM south => north, north => south, east => west, west => east, swHor => neHor, swVer => neVer, seHor => nwHor, seVer => nwVer, neHor => swHor, neVer => swVer, nwHor => seHor, nwVer => seVer, interior, unknown => side, ENDCASE => ERROR]; }; --rot2 rot3: PROC [s: IP.PinSideType] RETURNS [IP.PinSideType] = { RETURN [SELECT s FROM south => west, west => north, north => east, east => south, swHor => nwVer, nwVer => neHor, neHor => seVer, seVer => swHor, swVer => nwHor, nwHor => neVer, neVer => seHor, seHor => swVer, interior, unknown => side, ENDCASE => ERROR]; }; --rot3 RETURN [SELECT numberOfRot MOD 4 FROM 0 => side, 1, -3 => rot1[side], 2, -2 => rot2[side], 3, -1 => rot3[side], ENDCASE => ERROR]; }; --Rotate90PinSide CoChannels: PUBLIC PROC[co: REF IP.ComponentRep, action: PROC[REF IP.ChannelRep] RETURNS [quit: BOOL]] ={ OPEN coP: co.prinChannels, coC: co.cornerChannels; IF action[coP.south] THEN RETURN; IF action[coP.east] THEN RETURN; IF action[coP.north] THEN RETURN; IF action[coP.west] THEN RETURN; IF coC.sw # NIL THEN { IF action[coC.sw.hor] THEN RETURN; IF action[coC.sw.ver] THEN RETURN; }; IF coC.se # NIL THEN { IF action[coC.se.hor] THEN RETURN; IF action[coC.se.ver] THEN RETURN; }; IF coC.ne # NIL THEN { IF action[coC.ne.hor] THEN RETURN; IF action[coC.ne.ver] THEN RETURN; }; IF coC.nw # NIL THEN { IF action[coC.nw.hor] THEN RETURN; IF action[coC.nw.ver] THEN RETURN; }; }; --CoChannels IPPinSideToAtom: PROC[side: IP.PinSideType] RETURNS [ATOM] ={ RETURN[ SELECT side FROM south => $south, east => $east, north => $north, west => $west, swHor => $swHor, seHor => $seHor, neHor => $neHor, nwHor => $nwHor, swVer => $swVer, seVer => $seVer, neVer => $neVer, nwVer => $nwVer, interior => $interior, unknown => $unknown, ENDCASE => ERROR]; }; --IPPinSideToAtom GetPinSide: PROC[stream: IO.STREAM] RETURNS [IP.PinSideType] ={ token: ATOM _ stream.GetAtom; RETURN [SELECT token FROM $south => south, $east => east, $north => north, $west => west, $swHor => swHor, $seHor => seHor, $neHor => neHor, $nwHor => nwHor, $swVer => swVer, $seVer => seVer, $neVer => neVer, $nwVer => nwVer, $interior => interior, $unknown => unknown, ENDCASE => ERROR ParseError[$badToken, token]]; }; --GetPinSide ConstructFileName: PUBLIC PROC[defaultDir, inputFile, defaultExt: Rope.ROPE] RETURNS[fullName: Rope.ROPE] = { dirPart: Rope.ROPE _ FileNames.Directory[inputFile]; IF Rope.IsEmpty[inputFile] THEN RETURN[NIL]; IF Rope.IsEmpty[dirPart] THEN dirPart _ defaultDir; fullName _ Rope.Cat[dirPart, FileNames.GetShortName[inputFile]]; IF Rope.Find[inputFile, "."] < 0 AND Rope.Find[inputFile, "!"] < 0 THEN fullName _ Rope.Cat[fullName, ".", defaultExt]; }; -- ConstructFileName END. R--File: IPToolBoxImpl.mesa Last Edited by: Preas, August 2, 1986 10:09:59 am PDT --(1) Check if point is in shape --(2) Now find nearest side (this is not very efficient but is ok?) --Algorithm: IF ptProj IN sdIntl --THEN distance = ABS[ptCoord - sdCoord] --ELSE (also for any other patho cases) distance = LAST[INT] --(0) For patho cases simply return infinity --(1) Compute ptCoord, ptProj --(3) Compute sdCoord and sdIntl -- REMARK: Here is okay to use 'IP.ShapeRep' as argument instead of `REF IP.ShapeRep' -- because callers do not intend to modify shape. Remember that parameters are pass by -- value in Cedar --Decompose orient into its basis and calls MirrorXShape and Rotate90Shape --modifies shape: (shape.dim <=> shape.dim; shape.sw <=> shape.se; shape.ne <=> shape.nw) --(1) Swap bottom --(2) Swap top modifies shape: if numberOfRot = 1 then --(shape.dim <=> shape.dim; se _ sw, ne _ se, nw _ ne, sw_ nw) --numberOfRot can be any positive or negative --Simple parsing routines --Need to search further because "Input[0]" could be a valid name --###Low level Private routines###-- Κα˜J™J™5J™šΟk ˜ Jšœ˜J˜J˜ Jšœ˜J˜ J˜J˜Jšœ˜J˜ Jšœ ˜ —J˜šœœ˜Jšœœœ-˜NJšœ œœœ˜9J˜codešΟnœœœ œ˜0Kš œ œœœœ œ˜/K˜šžœ&˜-Kšœœ˜"Kšœœ œ˜.Kšœ=Οc˜MKšœœœœ˜?Kš œœœ œœ6˜QKšœœ ˜K˜—K˜Kšœ<˜KšœŸ ˜—K˜šœ œ˜Kšœ œ$˜2Kšœ˜Kšœ˜—JšœŸ ˜—J˜šž œœœ œœ œ œœ œœ˜…Jšœ œœœ˜J™ Jšœ@˜@šœ œ œ ˜)šœD˜FKšœ œ˜—Kšœ˜—J˜J™Cšœœ œ˜.Kšœ œ%˜1Kšœœ#˜™>KšŸ-™-J˜šœ˜Jšœœœ ˜!Jšœ&˜&šœ œ˜Kšœœ˜ Kšœ:˜:Kšœ:˜:Kšœ;˜;Kšœœ˜——J˜JšœŸ˜—J™J™J™J˜Jš œ œœ œœœ˜8K˜K˜šž œœœ œœœœ˜?Kšœ œ˜Kšœœ˜ K™Ašœ˜%Kšœ&˜&Kšœ˜—Kšœ˜ KšœŸ œ˜—K˜šž œœœ œœœœ˜:Kšœœ˜Kšœœ˜ šœ˜ Kšœœ˜Kšœœœœ ˜6—KšœŸ œ˜—J˜š ž œœœ œœ˜/Kšœœ˜ Kšœ˜šœ˜!Kšœœœœ ˜2—KšœŸ ˜—J˜šž œœœ œœœœœ˜CKšœ˜šœ˜Kšœ˜Kšœœœ˜—KšœŸ ˜—K˜š ž œœœ œœ˜0Kšœ˜šœ˜Kšœœ˜0Kšœ˜—KšœŸ ˜—K˜šž œœœ œœœœœ˜KKš œ œœœœœ˜4Kšœœ˜ Kš œ œœœœ˜#Kšœœœœ˜$Kšœœœœ˜)Kšœœ˜KšœŸœ˜—K˜šž œœœ œœœœ œ˜HKš œ œœœœœ˜4Kšœœ˜ Kš œ œœœœ˜#Kšœœœœ˜$Kšœœœœ˜)Kšœœ˜KšœŸ˜—K˜•StartOfExpansion[]šžœœœ œœœ œœ˜Nšœ˜Kšœ˜Kšœœœ)˜7šœ˜Kšœœ˜ šœ˜Kšœ%Ÿ˜*Kšœ%Ÿ˜*Kšœ%Ÿ˜*Kšœ&Ÿ˜+Kšœœ˜.—Kšœ˜——KšœŸ ˜ —J˜šžœœœ œœœœ˜X– "Cedar" styleš œ œœœœ˜2K– "Cedar" stylešœ œ˜)K– "Cedar" stylešœœ"˜*K– "Cedar" stylešœœ˜K– "Cedar" stylešœœœ)˜8K– "Cedar" stylešœŸ ˜—K– "Cedar" stylešœ˜– "Cedar" stylešœ˜Kšœ œ˜&Kšœ˜—JšœŸ˜—J˜J˜šžœœœ œœ œœ ˜CJ˜šœ œœœ˜2Kšœœœ˜BKš œ œœœœ˜RKš œ œœœœ˜RKš œ œœœœ˜RKš œ œœœœ˜RKšœŸ˜ —K˜JšœŸ ˜ —J˜J˜š žœœœ œœ ˜NK˜šœœ˜Kšœœ%˜3˜Kšœ˜Kšœ˜Kšœ$˜&Kšœ˜K˜—Kšœ!˜!Kš˜—K˜JšœŸ ˜ —J˜š žœœœ"œœ œ ˜šœ œ˜Kšœœœ ˜,Kšœ[˜[Kšœ1˜1Kšœ˜Kšœ˜—JšœŸ˜—J˜š žœœœ"œ œ ˜ršœ œ˜Kšœœœ ˜,Kšœa˜aKšœ&˜&Kšœ˜Kšœ˜—JšœŸ˜—J˜š žœœœ"œœ œ ˜‰Kšœ˜šœ œ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœœ˜—J˜šœ œ˜Kšœœœ ˜,KšœW˜WKšœ4˜4Kšœ˜Kšœ˜—JšœŸ˜—J˜šž œœœœœœœ˜dJšœ"œ˜EKšœ#˜)JšœŸ˜—J˜š žœœœœœœ˜Mšœ˜šœ˜Kšœ(˜(Kšœ ˜ K˜ Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜—K˜—J˜JšœŸ˜—J˜šžœœœœœœœ˜dš œœœœœ˜;šœœ˜K˜K˜K˜K˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœœ˜—KšœŸ˜ —š œœœœœ˜;šœœ˜K˜K˜K˜ K˜ Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœœ˜—KšœŸ˜ —š œœœœœ˜;šœœ˜K˜K˜K˜K˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœœ˜—KšœŸ˜ —J˜K˜šœœ œ˜%Kšœ ˜ Kšœ˜Kšœ˜Kšœ˜Kšœœ˜—J˜JšœŸ˜—J˜šž œœœœœœœœ œœ˜išœ.˜2Kšœœœ˜!Kšœœœ˜ Kšœœœ˜!Kšœœœ˜ šœ œœ˜Kšœœœ˜"Kšœœœ˜"Kšœ˜—šœ œœ˜Kšœœœ˜"Kšœœœ˜"Kšœ˜—šœ œœ˜Kšœœœ˜"Kšœœœ˜"Kšœ˜—šœ œœ˜Kšœœœ˜"Kšœœœ˜"Kšœ˜—K˜—JšœŸ ˜—J˜J™$š žœœœœœ˜=šœ˜šœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœœ˜——KšœŸ˜—J˜J˜š ž œœ œœœœ˜?Kšœœ˜šœœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœ˜Kšœœ˜/—JšœŸ ˜—J˜šžœœœ)œ˜LJšœœ˜ Jšœœ"˜4Jšœœœœ˜,Jšœœ˜3Jšœ@˜@šœœ˜GJšœ/˜/—JšœŸ˜—J˜Jšœ˜——…—DBbu