%include "inc:util.imp" !! *** SKETCH *** 14/07/81 ! updated dec1st (pmm) ! annotation sensible for tall thin chips ! nets drawn in tartan and not reordered ! updated (pmm) for hp plotter ! nets drawn in green ! a4 or a3 paper ! question about edge connections removed ! option to draw edge connections merely as dots added ! bug associated with workspace overflow corrected ! frame now drawn last of all ! annotation done by variable size ! updated (rwt 4/82) for pjl ! -option added for short fat chips to have ! (slotname:slottype/chipname:chiptype) ! contracted to just (slotname/chiptype) because ! if the compound names become too long it would ! at times truncate them beyond recognition. In any ! event slottype and chipname are usually irrelevant. ! -identify corners of chips nearest pin 1. ! updated (jgh 5/82) to allow users to say A1 for the big HP plotter. ! [01/03/83]: mods for IMP8 ! updated (jgh 3/83) to allow smaller character on the plotters. %include "EDWIN:SPECS.INC" %const %integer DEV UPDATE = 2, MOVE = 4 ! The above allows the moving to screen coordinates for keeping ! Tektronix terminals happy about where the prompts are appearing. %BEGIN !! routines from the IMP library %EXTERNALINTEGERFNSPEC DEF STREAMS(%STRING(127) PARM, DEFAULTS) %OWNSTRING(12) DEFAULTS=".BIC/:n.PDF" !! recordformats for data structures %RECORDFORMAT COORDF(%INTEGER X,Y) %CONSTINTEGER COORDLEN=2 %RECORDFORMAT EDGEF(%INTEGER NT, %STRING(255)%NAME NAME, %RECORD(COORDF)%ARRAY PIN(1:1000)) %CONSTINTEGER EDGELEN=2 %RECORDFORMAT EDGELIST(%RECORD(EDGEF)%NAME %ARRAY EDGE(1:1000)) %RECORD(EDGELIST)%NAME EDGES %RECORDFORMAT CHIPF(%INTEGER NT, %RECORD(COORDF)%ARRAY PIN(1:1000)) %CONSTINTEGER CHIPLEN=1 %RECORDFORMAT CHIPLIST(%RECORD(CHIPF)%NAME %ARRAY CHIP(1:1000)) %RECORD(CHIPLIST)%NAME CHIPS %RECORDFORMAT NETF(%INTEGER NT, %RECORD(COORDF) %ARRAY C(1:1000)) %CONSTINTEGER NETLEN=1 !! I/O streams %CONSTINTEGER ICODE=1, REPORT=0 %own %integer PDF = 1; ! PDF is set negitive if no PDF is to be produced. !! machine dependent constants %CONSTINTEGER LAUPW=2; !! log addressing units per word %CONSTINTEGER CPW=4; !! characters per word %CONSTINTEGER LCPW=2; !! log characters per word %CONSTINTEGER MAXINTEGER=2000000000 !! character interface %CONSTINTEGER CNTRL=128, CNTRLCHAR='^', END OF FILE=-1 %CONSTINTEGER ENDFILE=9, END OF STRING=-1 %INTEGER CH !! picture constants %CONSTINTEGER XO=5, YO=25; !! picture origin %OWNINTEGER XL=XO, YL=YO, YU=YO, XR=XO %CONSTINTEGER TITLEH=20, TITLEX=20, TITLEY=-16; !! title info !! I-code constants %CONSTINTEGER AT=1, ON=2, SIZE=7, PLACE=8 !! work stack %CONSTINTEGER STACKLEN=30000 %INTEGERARRAY STACK(0:STACKLEN) %INTEGER TOS, BOS %STRING(31) NAME %CONSTINTEGER YES=0, NO=-1 %STRING(15)%ARRAY IGNORE(1:10) !! I-code interface routines %OWNINTEGER STRINGLEN=-1 ! STATISTIC VARIABLES %integer total=0,wires=0,mean=0,variance=0 %routine statistics %return %if wires=0 selectoutput(report) printstring("total wire length = "); write(total,1) newline printstring("number of wires ="); write(wires,1) newline mean=total//wires printstring("mean wire length = "); write(mean,1) newline %end %ROUTINE RCH %INTEGER I, LEN %ON %EVENT 3,ENDFILE %START CH=END OF FILE %RETURN %FINISH START: READSYMBOL(CH) %UNTIL CH#NL %IF CH=CNTRLCHAR %START READSYMBOL(CH); CH=CH+CNTRL %IF CH=CNTRL+'K' %START READ(LEN); RCH RCH %FOR I=1,1,LEN ->START %FINISH %FINISH %END %ROUTINE GETCH READ(STRINGLEN) %AND RCH %IF STRINGLEN<0 CH=END OF STRING %AND %RETURN %IF STRINGLEN=0 RCH STRINGLEN=STRINGLEN-1 %END %ROUTINE FLUSH GETCH %WHILE STRINGLEN>0 STRINGLEN=-1 %END %ROUTINE RNUM(%INTEGERNAME RESULT) %INTEGER SIGN, N !! read a number from the I-code (from within a string) GETCH %IF CH='-' %THEN SIGN=-1 %AND GETCH %ELSE SIGN=1 N=0 %WHILE '0'<=CH<='9' %CYCLE N=N*10+CH-'0' GETCH %REPEAT N=-N %IF SIGN<0 RESULT=N %END %STRING(255)%MAP READ STRING %STRING(255)%NAME S %INTEGER I READ(STRINGLEN) %AND RCH %IF STRINGLEN<0 BOS=BOS-(STRINGLEN+CPW)>>LCPW S==STRING(BOS<>5 R=-R %IF SIGN<0 %RESULT=R %END %ROUTINE TRANSLATE(%RECORD(COORDF)%NAME C) C_X=XL+SCALE(C_X) C_Y=YL+SCALE(C_Y) %END %ROUTINE BOX REL(%INTEGER XS, YS) !! draw a box with opposite corner at relative !! coordinates XS,YS. XS and YS are unscaled XS=SCALE(XS); YS=SCALE(YS) LINEREL(XS,0); LINEREL(0,YS) LINEREL(-XS,0);LINEREL(0,-YS) %END %routine mark pin 1(%integer xs,ys) %integerfn sign(%integer x) %result=scale(-8) %if x<0; %result=scale(8) %end moverel(sign(xs),0) linerel(-sign(xs),sign(ys)) moverel(0,-sign(ys)) %end %STRING(31)%FN RSTRING %STRING(31) S %INTEGER CH S="" %CYCLE READSYMBOL(CH) %EXIT %UNLESS CH=' ' %OR CH=NL %REPEAT %WHILE CH#' ' %AND CH#NL %CYCLE CH=CH-'a'+'A' %IF 'a'<=CH<='z' s = s.tostring(ch) READSYMBOL(CH) %REPEAT %RESULT=S %END %ROUTINE CLAIM(%INTEGER NWORDS) TOS=TOS>>LAUPW+NWORDS %IF TOS>=BOS %START SELECTOUTPUT(REPORT) PRINTSTRING("Workspace full."); NEWLINE %STOP %FINISH TOS=TOS<A %RESULT=A %END %ROUTINE DRAW NET(%integer edges, %string(127) name,%RECORD(NETF)%NAME NET) %RECORD(COORDF)%NAME C1, C2 %INTEGER NT, f, distance %record(coordf)%name at,next %INTEGERFN D(%RECORD(COORDF)%NAME P1,P2) %RESULT=|P1_X-P2_X|+|P1_Y-P2_Y| %END %ROUTINE MOVE TO(%RECORD(COORDF)%NAME P) MOVE ABS(P_X,P_Y) %END %ROUTINE DRAW TO(%RECORD(COORDF)%NAME P) %onevent 1 %start selectoutput(0); printstring("Overflow:") phex(p_x); space; phex(p_y); %stop %finish %if p_x=16_aaaaaaaa %or p_y=16_aaaaaaaa %start selectoutput(0); printstring("*Crashing*") %finish LINE ABS(P_X,P_Y) %END distance = 0 NT=NET_NT %RETURN %IF NT<2 wires = wires+1 %if charno(name,1)='.' %then setColour(4) %c %else %if edges#0 %then setColour(3) %c %else setColour(2) at == net_c(1) moveTo(at) %for f = 2,1,nt %cycle next == net_c(f) drawTo(next) distance = distance+d(at,next) at == next %repeat total = total+distance %END %ROUTINE MARK(%INTEGER SIZE) !! draw a '+' centred at the current posn SIZE=SCALE(SIZE) MOVE REL(0,-SIZE) LINE REL(0,SIZE+SIZE) MOVE REL(-SIZE,-SIZE) LINE REL(SIZE+SIZE,0) MOVE REL(-SIZE,-size) %END !!******************************************* !! mainline code for SKETCH * !!******************************************* %INTEGER TERMINAL TYPE, PNO, NT, BOARDNSUBS, OLDBOS %INTEGER BOARDNT, I, SUBNO, TNO, BOARDXDIM, BOARDYDIM %INTEGER OLDTOS, X, Y, XS, YS, NPTS, NIG, USE, nedges %INTEGER LEN, CXS, CYS, XPROMPT, NXPROMPT, YPROMPT, ALL NETS %INTEGER REPLY, MAX XPROMPT, SIDE, SIDES, REPLY LEN %INTEGER EORIENT, temp1, temp2, plotter, edgeConnections %integer suppress, pinno, x1, y1 %STRING(255)%NAME SLOTNAME, SLOTTYPE, NETNAME, NULL STRING %STRING(255)%NAME CIRCUITNAME, BOARDNAME, CHIPNAME, CHIPTYPE %STRING(63) S %RECORD(EDGEF)%NAME EDGE %RECORD(COORDF)%NAME COORD %RECORD(CHIPF)%NAME CHIP %RECORD(NETF)%NAME NET %record(coordf)%name notch %record(coordf)no notch %STRING(63)%FN TRUNCATE(%STRING(63) S, %INTEGER LEN) %STRING(63) TS %INTEGER LLEN, RLEN %IF LEN>1 RLEN=LEN-LLEN TS=SUBSTRING(S,1,LLEN) TS=TS.SUBSTRING(S,LENGTH(S)-RLEN+1,LENGTH(S)) %IF RLEN > 0 %FINISH %ELSE TS=S %RESULT=TS %END %ROUTINE ANNOTATE(%INTEGER XS, YS, %STRING(63) S) %INTEGER CSIZE !! fit the annotation string into a box of size XS,YS !! with bottom LH corner at the current position %if plotter#0 %start CSIZE=MIN((YS*8)//20,XS//(LENGTH(S)+1)) MOVE REL((XS-(LENGTH(S)*CSIZE))//2,((YS-(20*CSIZE)//12)+1)//2) %return %if csize<1 SET CHAR SIZE(CSIZE) text(S) %finish %else %if ys>=cys %start text(truncate(s,xs//cxs+1)) %finish %END %ROUTINE GET REPLY(%INTEGERNAME R) %INTEGER CH REPLY LEN=0 READSYMBOL(CH) %AND REPLY LEN=REPLY LEN+1 %UNTIL CH#' ' %IF 'a'<=CH<='z' %THEN CH=CH-'a'+'A' R=CH READSYMBOL(CH) %AND REPLYLEN=REPLYLEN+1 %WHILE CH#NL %END %INTEGERFN REPLY TO(%STRING(63) S) %INTEGER LEN, REPLY S=TRUNCATE(S,15) LEN=LENGTH(S)*CXS+CXS %IF NXPROMPT+LEN>MAX XPROMPT %START YPROMPT=YPROMPT-CYS NXPROMPT=XPROMPT %FINISH DRIVE DEVICE (MOVE, NXPROMPT, YPROMPT) %if plotter=0; !move into position DRIVE DEVICE (DEV UPDATE, 0, 0); ! Get into character mode SELECTINPUT(0) PROMPT(S) GET REPLY(REPLY) SELECTINPUT(ICODE) NXPROMPT=NXPROMPT+LEN+REPLYLEN*CXS %RESULT=REPLY %END %stop %if def streams(cliparam,defaults) # 1 SELECTINPUT(REPORT) SELECTOUTPUT(REPORT) terminal type = default device initialise for (terminal type) print string ("Terminal set to "); print string (device data_name); newline plotter = 0 plotter = 1 %if terminalType=7221 %or terminalType=963 %or terminalType=0 %c %or terminalType=7220 %or terminalType=7580 %or terminalType=7585 CXS=12; CYS=20; ! To keep Tektronices happy, ie. prompts in right place CXS=8 %and CYS=13 %if TERMINAL TYPE = 4014 YPROMPT=760; MAX XPROMPT=1020 SET CHAR SIZE (1); ! Choose the smallest hardware character size %if plotter#0 %start %cycle printstring("A4 or A3 or A1 paper?"); newline prompt("Use A") get reply(side) %repeat %until '1'<=side<='4' %if plotter=963 %then plotter = 30 %else plotter=40 %if side='4' %then viewPort(0,275*plotter,0,190*plotter) %if side='3' %then viewPort(0,400*plotter,0,290*plotter) %if side='2' %or side='1' %start viewport (0, 900*plotter, 0, 600*plotter) %finish %finish !!******************************************* !! decide which side of board to draw first * !!******************************************* PRINTSTRING("Draw chip-side or wire-side of board?") %CYCLE NEWLINE PROMPT("Side= ") GET REPLY(SIDE) %EXIT %IF SIDE='C' %OR SIDE='W' PRINTSTRING("Options are 'chip' or 'wire'") %REPEAT printstring("Draw annotated edge connections?") %cycle newline prompt("Y or N?") getReply(edgeConnections) %repeat %until edgeConnections='Y' %or edgeConnections='N' %if edgeConnections='Y' %then edgeConnections=yes %else edgeConnections=no printstring("Suppress slot types and chip names?"); newline get reply(Suppress) %if Suppress='Y' %then Suppress=yes %else Suppress=no ! question removed since the answer is never used !NEWLINE !PRINTSTRING("On which edge are the edge connectors?") !%CYCLE ! NEWLINE ! PROMPT("Edge= ") ! GET REPLY(EORIENT) ! %EXIT %IF EORIENT='L' %OR EORIENT='R' %OR %C ! EORIENT='T' %OR EORIENT='B' ! PRINTSTRING("Options are 'top', 'bottom', 'left' or 'right'") !%REPEAT !%IF EORIENT='L' %OR EORIENT='R' %THEN EORIENT=0 %ELSE EORIENT=1 eorient = 0 SIDES=0 %CYCLE TOS=ADDR(STACK(0)); BOS=ADDR(STACK(STACKLEN))>>LAUPW NULL STRING==STRING(BOS<xr window(temp1,temp2,yo-titleh,yu) NEWFRAME STORE ON(PDF) %if PDF>=0 !! put out the terminals %FOR TNO=1,1,BOARDNT %CYCLE EDGE==EDGES_EDGE(TNO) %FOR I=1,1,EDGE_NT %CYCLE COORD==EDGE_PIN(I) TRANSLATE(COORD) %if edgeConnections=yes %start move abs(coord_x,coord_y) mark(3) ! always put out exactly four characters of terminal name s = edge_name s = s." " %while length(s)<4 s = substring(s,1,4) ANNOTATE(SCALE(24),SCALE(12),s) %finish %else markerAbs(0,coord_x,coord_y) %REPEAT %REPEAT !!********************************************** !! draw the chips in their correct positions * !!********************************************** RCH; !! ^J READ(BOARDNSUBS) CHIPS==RECORD(TOS); CLAIM(BOARDNSUBS) %FOR SUBNO=1,1,BOARDNSUBS %CYCLE CHIP==RECORD(TOS) CHIPS_CHIP(SUBNO)==CHIP RCH; !!^H READ(NT) %FOR I=1,1,5 OLDBOS=BOS CHIPNAME==READSTRING; CHIPTYPE==READSTRING CHIP_NT=NT; notch==no notch %FOR TNO=1,1,NT %CYCLE RCH; SKIP NUM COORD==CHIP_PIN(TNO) RNUM(COORD_X); RNUM(COORD_Y) rnum(pinno); notch==coord %if pinno=1 COORD_X=-COORD_X %IF SIDE='C' TRANSLATE(COORD) FLUSH SKIP STRING %REPEAT CLAIM(CHIPLEN+NT*COORDLEN) SLOTNAME==NULL STRING; SLOTTYPE==NULL STRING %CYCLE RCH %EXIT %UNLESS CH=CNTRL+'P' READ(PNO) %IF PNO=SIZE %START RNUM(XS); RNUM(YS) XS=-XS %IF SIDE='C' FLUSH %ELSE %IF PNO=PLACE RNUM(X); RNUM(Y) X=-X %IF SIDE='C' FLUSH %ELSE %IF PNO=AT SLOTNAME==READ STRING %ELSE %IF PNO=ON SLOTTYPE==READ STRING %ELSE SKIP STRING %FINISH %REPEAT X=XL+SCALE(X); Y=YL+SCALE(Y) MOVEABS(X,Y) BOX REL(XS,YS) XS=SCALE(XS); YS=SCALE(YS) %IF XS<0 %THEN X=X+XS %AND XS=-XS %IF YS<0 %THEN Y=Y+YS %AND YS=-YS %unless notch==no notch %start x1=x; y1=y x1=x+xs %if |x+xs-notch_x|<|x-notch_x| y1=y+ys %if |y+ys-notch_y|<|y-notch_y| moveabs(x1,y1) %if x1=x %then x1=xs %else x1=-xs %if y1=y %then y1=ys %else y1=-ys mark pin 1(x1,y1) %finish MOVE ABS(X,Y) LEN=(XS//CXS)+1 %if xs>=ys %start ys = ys//2 %if suppress=yes %then s=chiptype %else S=CHIPNAME.":".CHIPTYPE annotate(xs,ys,s) MOVE ABS(X,Y+YS) %if suppress=yes %then s=slotname %else S=SLOTNAME.":".SLOTTYPE annotate(xs,ys,s) %finishelseif suppress=yes %start ys=ys//2 annotate(xs,ys,chiptype) moveabs(x,y+ys) annotate(xs,ys,slotname) %else ys = ys//4 annotate(xs,ys,chipname) moveAbs(x,y+ys) annotate(xs,ys,chipType) moveAbs(x,y+ys+ys) annotate(xs,ys,slotName) moveAbs(x,y+ys+ys+ys) annotate(xs,ys,slotType) %finish BOS=OLDBOS %REPEAT update -> NEXT SIDE %IF SIDE='C' REPLY=REPLY TO("Draw all nets? ") %IF REPLY='N' %THEN ALL NETS=NO %ELSE ALL NETS=YES YPROMPT=YPROMPT-CYS NXPROMPT=XPROMPT NET==RECORD(TOS) set colour(4) OLDTOS=TOS; OLDBOS=BOS RCH %WHILE CH=CNTRL+'N' %CYCLE USE=YES; NPTS=0; nedges = 0 RCH %WHILE CH=CNTRL+'A' %CYCLE NETNAME==READSTRING %FOR I=1,1,NIG %CYCLE %IF NETNAME=IGNORE(I) %THEN USE=NO %AND %EXIT %REPEAT READ(NT) %FOR I=1,1,NT %CYCLE NPTS=NPTS+1 READ(SUBNO); READ(TNO) %IF SUBNO=0 %START nedges = nedges+1 COORD==EDGES_EDGE(TNO)_PIN(1) %ELSE COORD==CHIPS_CHIP(SUBNO)_PIN(TNO) %FINISH NET_C(NPTS)=COORD %REPEAT RCH %REPEAT NET_NT=NPTS CLAIM(NETLEN+NPTS*COORDLEN) %IF USE=YES %AND NPTS>1 %START %IF ALL NETS=YES %START DRAW NET(nedges,netname,NET) %ELSE REPLY=REPLY TO(NETNAME) %EXIT %IF REPLY='*' DRAW NET(nedges,netname,NET) %IF REPLY=',' %FINISH %FINISH TOS=OLDTOS; BOS=OLDBOS %REPEAT set colour(1) NEXT SIDE: !! draw board surroundings SET CHAR SIZE (10) MOVE ABS(XL,YL) BOX REL(BOARDXDIM,BOARDYDIM) MOVE ABS(XL,YO) LINEREL(0,-TITLEH); X=SCALE(BOARDXDIM) LINEREL(X,0); LINEREL(0,TITLEH) MOVEABS(TITLEX+XO,TITLEY+YO) TEXT("Circuit "); TEXT(CIRCUITNAME) TEXT(" on board "); TEXT(BOARDNAME) %IF SIDE='W' %THEN S="(wire" %ELSE S="(chip" S=S." side)" I=(18+LENGTH(CIRCUITNAME)+LENGTH(BOARDNAME))*12+TITLEX+TITLEX YS=TITLEX*3+LENGTH(S)*12 X=|X|; I=SCALE(I); YS=SCALE(YS) XS=X-YS; Y=TITLEY+YO %IF I< X %START !! got some room for the annotation %IF XS>I %START MOVE ABS(XO+XS,Y) text(S) %ELSE MOVE ABS(XO+I,Y) ANNOTATE(X-I,SCALE(20),S) %FINISH %FINISH update %EXIT %IF SIDES>=2 setcharsize(1) SIDE='W'+'C'-SIDE S="Draw " %IF SIDE='C' %THEN S=S."chip" %ELSE S=S."wire" %EXIT %UNLESS REPLY TO(S." side?")='Y' RESET INPUT %REPEAT terminate edwin {discontinued statistics %ENDOFPROGRAM