Home » Archimedes archive » Acorn User » AU 1993-09.adf » !Bio_Bio » !Bio/Library/TtoD

!Bio/Library/TtoD

This website contains an archive of files for the Acorn Electron, BBC Micro, Acorn Archimedes, Commodore 16 and Commodore 64 computers, which Dominic Ford has rescued from his private collection of floppy disks and cassettes.

Some of these files were originally commercial releases in the 1980s and 1990s, but they are now widely available online. I assume that copyright over them is no longer being asserted. If you own the copyright and would like files to be removed, please contact me.

Tape/disk: Home » Archimedes archive » Acorn User » AU 1993-09.adf » !Bio_Bio
Filename: !Bio/Library/TtoD
Read OK:
File size: 5286 bytes
Load address: 0000
Exec address: 0000
File contents
   10REM     >TtoD (BIO3)
   20REM By  Gary Palmer
   30REM For use with Bio
   40REM (c) BAU September 1993
   50END
   60:
   70DEF FNttod_name="Text to DrawFile"
   80:
   90DEF FNttod_args="-in Text -out drawfile -send"
  100:
  110DEF FNttod_init
  120SYS "Hourglass_On"
  130LOCAL font_no%, status%
  140ttod_inch_scale=180*256:ttod_mm_scale=ttod_inch_scale/25.4
  150ttod_mp_per_inch=72000:ttod_mp_per_mm=ttod_mp_per_inch/25.4
  160ttod_scale=ttod_mm_scale:ttod_millipoints=ttod_mp_per_mm
  170DIM ttod_font_name$(64), ttod_font_size(64), ttod_work% 8192, ttod_error_q% 256
  180ttod_font_no%=0
  190ttod_rect_args$="first/k,second/k,width=w/k,fill=f/k,line=l/k"
  200ttod_line_args$="start/k,end/k,width=w/k,line=l/k"
  210ttod_ltext_args$="x/k,y/k,text=t/k,path=p/s"
  220ttod_ctext_args$="first/k,second/k,text=t/k,path=p/s"
  230ttod_font_args$="number=no/k,name=na/k,size=sz/k"
  240ttod_sprite_args$="file=f/k,sprite=name/k,first/k,second/k"
  250ttod_path_args$="width=w/k,fill=f/k,line=l/k"
  260ttod_one_args$="to/k"
  270ttod_three_args$="to/k,first/k,second/k"
  280ttod_ellipse_args$="centre=c/k,horz=h/k,vert=v/k,width=w/k,line=l/k,fill=f/k"
  290ttod_used_handles$=""
  300SYS "Wimp_ReadSysInfo",7 TO ttod_version% ; status%
  310IF (status% AND 1)=1 THEN ttod_version%=200
  320SYS "Hourglass_Smash"
  330=0
  340:
  350DEF FNttod(in$, out$)
  360ttod_error%=FALSE
  370LOCAL in_file%, out_file%
  380SYS "Hourglass_On"
  390in_file%=OPENIN(in$)
  400IF in_file%=0 THEN PROCttod_error("Cannot open input file", 0):=1
  410out_file%=OPENOUT(out$)
  420IF out_file%=0 THEN PROCttod_error("Cannot open output file", 0):CLOSE #in_file%:=1
  430PROCttod_scan_fonts_needed(in_file%)
  440IF NOT ttod_error% PROCttod_start_file(out_file%)
  450IF NOT ttod_error% PROCttod_create_font_table(out_file%)
  460IF NOT ttod_error% PROCttod_generate_file(in_file%, out_file%)
  470CLOSE#in_file%
  480CLOSE#out_file%
  490SYS "Hourglass_Smash"
  500IF ttod_error% THEN =1 ELSE =0
  510:
  520DEF PROCttod_scan_fonts_needed(file%)
  530LOCAL in$, line_no%, com$, param$, name$, size$, no%, status%, handle%
  540PTR#file%=0
  550line_no%=0:ttod_used_handles$=""
  560WHILE (NOT EOF#in_file%) AND (NOT ttod_error%)
  570 in$=FNstrip_spaces(GET$#file%)
  580 line_no%+=1
  590 IF FNttod_parse(in$, com$, param$)  AND (LEFT$(in$, 1)<>"#") THEN
  600  CASE com$ OF
  610   WHEN "font":
  620    SYS &20049, ttod_font_args$, param$, ttod_work%, 1024 TO ;status%
  630    IF (status% AND 1)=1 THEN PROCttod_error("Syntax error", line_no%):ENDPROC
  640    IF ttod_work%!0<>0 THEN no%=VAL(FNget_str(ttod_work%!0)) ELSE PROCttod_error("Font number needed",line_no%):ENDPROC
  650    IF FNttod_check_font_handle(ttod_used_handles$, no%) THEN
  660     IF ttod_work%!4=0 THEN PROCttod_error("Font name needed",line_no%):ENDPROC
  670     IF ttod_work%!8=0 THEN PROCttod_error("Font size needed",line_no%):ENDPROC
  680     name$=FNget_str(ttod_work%!4)
  690     SYS &60081,,name$, 16, 16, 0, 0 TO handle%;status%
  700     IF (status% AND 1)=1 THEN PROCttod_error("Incorrect font name",line_no%):ENDPROC
  710     SYS &40082, handle%
  720     ttod_font_name$(no%)=name$
  730     ttod_font_size(no%)=VAL(FNget_str(ttod_work%!8))
  740     IF ttod_used_handles$<>"" THEN ttod_used_handles$+=" "+STR$(no%) ELSE ttod_used_handles$=STR$(no%)
  750    ENDIF
  760  ENDCASE
  770 ENDIF
  780ENDWHILE
  790PTR#file%=0
  800ENDPROC
  810:
  820DEF PROCttod_start_file(file%)
  830BPUT#file%,"Draw";
  840PROCwput(file%, 201)
  850PROCwput(file%, 0)
  860BPUT#file%,"TextToDraw  ";
  870PROCwput(file%, 0)
  880PROCwput(file%, 0)
  890PROCwput(file%, ttod_scale*210)
  900PROCwput(file%, ttod_scale*297)
  910ENDPROC
  920:
  930DEF PROCttod_create_font_table(file%)
  940LOCAL used$, len%, tmp$, no%, pad%, tmp%
  950used$=ttod_used_handles$:len%=0
  960PROCwput(file%, 0)
  970tmp%=PTR#file%
  980PROCwput(file%, 0)
  990REPEAT
 1000 IF FNttod_parse(used$, tmp$, used$)<>0 THEN
 1010  no%=VAL(tmp$)
 1020 ELSE
 1030  no%=VAL(tmp$):used$=""
 1040 ENDIF
 1050 len%+=LEN(ttod_font_name$(no%))+2
 1060 BPUT#file%, no%
 1070 BPUT#file%, ttod_font_name$(no%)+CHR$(0);
 1080UNTIL used$=""
 1090PTR#file%=tmp%
 1100tmp%=len%:len%=(len%+3) AND NOT 3:pad%=len%-tmp%
 1110PROCwput(file%, len%+8)
 1120PTR#file%=EXT#file%
 1130IF pad%<>0 THEN FOR no%=1 TO pad%:BPUT#file%, 0:NEXT no%
 1140ENDPROC
 1150:
 1160DEF PROCttod_generate_file(in_file%, out_file%)
 1170LOCAL in$, com$, param$, line_no%, no%, font_handle%, real_handle%, first%, status%
 1180line_no%=0:first%=TRUE
 1190WHILE (NOT EOF#in_file%) AND (NOT ttod_error%)
 1200 in$=FNstrip_spaces(GET$#in_file%)
 1210 line_no%+=1
 1220 IF FNttod_parse(in$, com$, param$) THEN
 1230  CASE com$ OF
 1240   WHEN "ltext" :
 1250    PROCttod_generate_ltext(out_file%, font_handle%, param$, line_no%)
 1260   WHEN "ctext" :
 1270    PROCttod_generate_ctext(out_file%, font_handle%, param$, line_no%)
 1280   WHEN "font" :
 1290    SYS &20049, ttod_font_args$, param$, ttod_work%, 1024 TO ;status%
 1300    IF (status% AND 1)=1 THEN PROCttod_error("Syntax error", line_no%):ENDPROC
 1310    no%=VAL(FNget_str(ttod_work%!0))
 1320    IF no%<1 OR no%>64 THEN PROCttod_error("Incorrect font number",line_no%):ENDPROC
 1330    IF (NOT FNttod_check_font_handle(ttod_used_handles$,no%)) THEN
 1340     font_handle%=no%
 1350    ELSE
 1360     PROCttod_error("SERIOUS INTERNL ERROR : I've lost track of a font handle ("+no$+")!!", line_no%):ENDPROC
 1370    ENDIF
 1380    IF first% THEN first%=FALSE ELSE SYS &40082, real_handle%
 1390    SYS &40081,,ttod_font_name$(font_handle%), ttod_font_size(no%)*16, ttod_font_size(no%)*16, 0, 0 TO real_handle%
 1400   WHEN "line" :
 1410    PROCttod_generate_line(out_file%, param$, line_no%)
 1420   WHEN "units" :
 1430    CASE FNlc(param$) OF
 1440     WHEN "inch" : ttod_scale=ttod_inch_scale:ttod_millipoints=ttod_mp_per_inch
 1450     WHEN "mm" : ttod_scale=ttod_mm_scale:ttod_millipoints=ttod_mp_per_mm
 1460     OTHERWISE : PROCttod_error("Illegal measurement scale in 'units' command",line_no%):ENDPROC
 1470    ENDCASE
 1480   WHEN "rectangle" :
 1490    PROCttod_generate_box(out_file%, param$, line_no%)
 1500   WHEN "sprite" :
 1510    PROCttod_include_sprite(out_file%, param$, line_no%)
 1520   WHEN "path" :
 1530    PROCttod_generate_path(in_file%, out_file%, param$, line_no%)
 1540   WHEN "ellipse" :
 1550    PROCttod_generate_oval(out_file%, param$, line_no%)
 1560  OTHERWISE: IF (LEFT$(com$, 1)<>"#") THEN PROCttod_error("Unknown command",line_no%)
 1570  ENDCASE
 1580 ENDIF
 1590ENDWHILE
 1600IF NOT first% THEN SYS &40082, real_handle%
 1610ENDPROC
 1620:
 1630DEF PROCttod_generate_ltext(file%, handle%, param$, line%)
 1640LOCAL x, y, text$, bound_x, bound_y, len%, status%, path%, need%
 1650SYS &20049, ttod_ltext_args$, param$, ttod_work%, 1024 TO ;status%
 1660IF (status% AND 1)=1 THEN PROCttod_error("Syntax error",line%):ENDPROC
 1670IF ttod_work%!0=0 THEN PROCttod_error("Missing x position definition from 'ltext' command",line%):ENDPROC
 1680IF ttod_work%!4=0 THEN PROCttod_error("Missing y position definition from 'ltext' command",line%):ENDPROC
 1690IF ttod_work%!8=0 THEN PROCttod_error("Missing text information from 'ltext' command",line%):ENDPROC
 1700x=VAL(FNget_str(ttod_work%!0)):y=VAL(FNget_str(ttod_work%!4)):path%=((ttod_work%!12)<>0)
 1710text$=FNget_str(ttod_work%!8)
 1720IF path% THEN
 1730 x=x*ttod_millipoints:y=y*ttod_millipoints
 1740 SYS &4009E,%1,8
 1750 SYS &40086,0,text$,%01100000000,x,y
 1760 SYS &4009E,0,0 TO ,need%
 1770 IF need%>=8184 THEN PROCttod_error("Text path too big for buffer!!", line%):ENDPROC
 1780 !ttod_work%=0:!ttod_work%=8184
 1790 SYS &4009E,%10010,ttod_work%
 1800 SYS &40086,0,text$,%01100000000,x,y
 1810 SYS &4009E,0,0 TO ,need%
 1820 SYS "OS_GBPB",2,file%,ttod_work%,need%-ttod_work%
 1830ELSE
 1840 SYS &40097,,text$ TO ,,, bound_x, bound_y
 1850 bound_x=bound_x/ttod_millipoints*ttod_scale
 1860 bound_y=bound_y/ttod_millipoints*ttod_scale
 1870 x=x*ttod_scale:y=y*ttod_scale
 1880 len%=(LEN(text$)+1+3) AND NOT 3
 1890 PROCttod_put_head(file%, 1, 52+len%, x, y, bound_x+1+x, bound_y+1+y)
 1900 PROCwput(file%, 0)
 1910 PROCwput(file%, &FFFFFF00)
 1920 PROCwput(file%, handle%)
 1930 PROCwput(file%, ttod_font_size(handle%)*640)
 1940 PROCwput(file%, ttod_font_size(handle%)*640)
 1950 PROCwput(file%, x)
 1960 PROCwput(file%, y)
 1970 PROCttod_put_padded(file%, len%, text$+CHR$(0), CHR$(0))
 1980ENDIF
 1990ENDPROC
 2000:
 2010DEF PROCttod_generate_ctext(file%, handle%, param$, line%)
 2020LOCAL x1, y1, x2, y2, x_low, y_low, x_high, y_high, text$, bound_x, bound_y, len%, status%, path%
 2030SYS &20049, ttod_ctext_args$, param$, ttod_work%, 1024 TO ;status%
 2040IF (status% AND 1)=1 THEN PROCttod_error("Syntax error",line%):ENDPROC
 2050IF ttod_work%!0=0 THEN PROCttod_error("Missing first position definition from 'ctext' command",line%):ENDPROC
 2060IF ttod_work%!4=0 THEN PROCttod_error("Missing second position definition from 'ctext' command",line%):ENDPROC
 2070IF ttod_work%!8=0 THEN PROCttod_error("Missing text information from 'ctext' command",line%):ENDPROC
 2080PROCttod_get_xy(FNget_str(ttod_work%!0), x1, y1)
 2090PROCttod_get_xy(FNget_str(ttod_work%!4), x2, y2)
 2100text$=FNget_str(ttod_work%!8):path%=((ttod_work%!12)<>0)
 2110x1=x1*ttod_scale:x2=x2*ttod_scale
 2120y1=y1*ttod_scale:y2=y2*ttod_scale
 2130IF x1<x2 THEN x_low=x1:x_high=x2 ELSE x_low=x2:x_high=x1
 2140IF y1<y2 THEN y_low=y1:y_high=y2 ELSE y_low=y2:y_high=y1
 2150SYS &40097,,text$ TO ,,, bound_x, bound_y
 2160bound_x=bound_x/ttod_millipoints*ttod_scale
 2170bound_y=bound_y/ttod_millipoints*ttod_scale
 2180IF (x_high-x_low)<bound_x THEN PROCttod_error("Bounding box too small (in x) in ctext command",line%):ENDPROC
 2190IF (y_high-y_low)<bound_y THEN PROCttod_error("Bounding box too small (in y) in ctext command",line%):ENDPROC
 2200x_low+=(x_high-x_low-bound_x)/2
 2210y_low+=(y_high-y_low-bound_y)/2
 2220len%=(LEN(text$)+1) AND NOT 3:IF ((LEN(text$)+1) MOD 4)<>0 THEN len%+=4
 2230IF path% THEN
 2240 x_low=x_low*ttod_millipoints/ttod_scale:y_low=y_low*ttod_millipoints/ttod_scale
 2250 SYS &4009E,%1,8
 2260 SYS &40086,0,text$,%01100000000,x_low,y_low
 2270 SYS &4009E,0,0 TO ,need%
 2280 IF need%>=8184 THEN PROCttod_error("Text path too big for buffer!!", line%):ENDPROC
 2290 !ttod_work%=0:!ttod_work%=8184
 2300 SYS &4009E,%10010,ttod_work%
 2310 SYS &40086,0,text$,%01100000000,x_low,y_low
 2320 SYS &4009E,0,0 TO ,need%
 2330 SYS "OS_GBPB",2,file%,ttod_work%,need%-ttod_work%
 2340ELSE
 2350 PROCttod_put_head(file%, 1, 52+len%, x_low, y_low, x_low+bound_x, y_low+bound_y)
 2360 PROCwput(file%, 0)
 2370 PROCwput(file%, &FFFFFF00)
 2380 PROCwput(file%, handle%)
 2390 PROCwput(file%, ttod_font_size(handle%)*640)
 2400 PROCwput(file%, ttod_font_size(handle%)*640)
 2410 PROCwput(file%, x_low)
 2420 PROCwput(file%, y_low)
 2430 PROCttod_put_padded(file%, len%, text$+CHR$(0), CHR$(0))
 2440ENDIF
 2450ENDPROC
 2460:
 2470DEF PROCttod_generate_line(file%, param$, line_no%)
 2480LOCAL start_x, start_y, finish_x, finish_y, x_low, y_low, x_high, y_high, width, status%, colour%
 2490width=0:start%=FALSE:finish%=FALSE:colour%=&00000000
 2500SYS &20049, ttod_line_args$, param$, ttod_work%, 1024 TO ;status%
 2510IF (status% AND 1)=1 THEN PROCttod_error("Syntax error",line_no%):ENDPROC
 2520IF ttod_work%!0=0 THEN PROCttod_error("Missing start position definition from 'line' command",line_no%):ENDPROC
 2530IF ttod_work%!4=0 THEN PROCttod_error("Missing end position definition from 'line' command",line_no%):ENDPROC
 2540PROCttod_get_xy(FNget_str(ttod_work%!0), start_x, start_y)
 2550PROCttod_get_xy(FNget_str(ttod_work%!4), finish_x, finish_y)
 2560IF ttod_work%!8<>0 THEN width=VAL(FNget_str(ttod_work%!8))*640
 2570IF ttod_work%!12<>0 THEN colour%=EVAL(FNget_str(ttod_work%!12))
 2580start_x=start_x*ttod_scale:start_y=start_y*ttod_scale
 2590finish_x=finish_x*ttod_scale:finish_y=finish_y*ttod_scale
 2600IF start_x<finish_x THEN x_low=start_x:x_high=finish_x ELSE x_low=finish_x:x_high=start_x
 2610IF start_y<finish_y THEN y_low=start_y:y_high=finish_y ELSE y_low=finish_y:y_high=start_y
 2620PROCttod_put_head(file%, 2, 68, x_low, y_low, x_high, y_high)
 2630PROCwput(file%, &FFFFFFFF)
 2640PROCwput(file%, colour%)
 2650PROCwput(file%, width)
 2660PROCwput(file%, %00000000)
 2670PROCttod_put_path(file%, 2, start_x, start_y)
 2680PROCttod_put_path(file%, 8, finish_x, finish_y)
 2690PROCwput(file%, 0)
 2700ENDPROC
 2710:
 2720DEF PROCttod_generate_box(file%, param$, line_no%)
 2730LOCAL x1, y1, x2, y2, x_low, y_low, x_high, y_high, width, status%, line_col%, fille_col%
 2740width=0:line_col%=&00000000:fill_col%=&FFFFFFFF
 2750SYS &20049, ttod_rect_args$, param$, ttod_work%, 1024 TO ;status%
 2760IF (status% AND 1)=1 THEN PROCttod_error("Syntax error",line_no%):ENDPROC
 2770IF ttod_work%!0=0 THEN PROCttod_error("Missing first position definition from 'box' command",line_no%):ENDPROC
 2780IF ttod_work%!4=0 THEN PROCttod_error("Missing second position definition from 'box' command",line_no%):ENDPROC
 2790PROCttod_get_xy(FNget_str(ttod_work%!0), x1, y1)
 2800PROCttod_get_xy(FNget_str(ttod_work%!4), x2, y2)
 2810IF ttod_work%!8<>0 THEN width=VAL(FNget_str(ttod_work%!8))*640
 2820IF ttod_work%!12<>0 THEN fill_col%=EVAL(FNget_str(ttod_work%!12))
 2830IF ttod_work%!16<>0 THEN line_col%=EVAL(FNget_str(ttod_work%!16))
 2840x1=x1*ttod_scale:x2=x2*ttod_scale
 2850y1=y1*ttod_scale:y2=y2*ttod_scale
 2860IF x1<x2 THEN x_low=x1:x_high=x2 ELSE x_low=x2:x_high=x1
 2870IF y1<y2 THEN y_low=y1:y_high=y2 ELSE y_low=y2:y_high=y1
 2880PROCttod_put_head(file%, 2, 108, x_low, y_low, x_high, y_high)
 2890PROCwput(file%, fill_col%)
 2900PROCwput(file%, line_col%)
 2910PROCwput(file%, width)
 2920PROCwput(file%, %00000000)
 2930PROCttod_put_path(file%, 2, x1, y1)
 2940PROCttod_put_path(file%, 8, x2, y1)
 2950PROCttod_put_path(file%, 8, x2, y2)
 2960PROCttod_put_path(file%, 8, x1, y2)
 2970PROCttod_put_path(file%, 8, x1, y1)
 2980PROCwput(file%, 5)
 2990PROCwput(file%, 0)
 3000ENDPROC
 3010:
 3020DEF PROCttod_include_sprite(out_file%, param$, line_no%)
 3030LOCAL x1, y1, x2, y2, x_low, y_low, x_high, y_high, file$, in_file%, sprite$, status%, number%, len%, tmp$, tmp%
 3040SYS &20049, ttod_sprite_args$, param$, ttod_work%, 1024 TO ;status%
 3050IF (status% AND 1)=1 THEN PROCttod_error("Syntax error",line_no%):ENDPROC
 3060IF ttod_work%!0=0 THEN PROCttod_error("Missing file name from 'sprite' command",line_no%):ENDPROC
 3070IF ttod_work%!4=0 THEN PROCttod_error("Missing sprite name from 'sprite' command", line_no%):ENDPROC
 3080IF ttod_work%!8=0 THEN PROCttod_error("Missing first position definition from 'sprite' command",line_no%):ENDPROC
 3090IF ttod_work%!12=0 THEN PROCttod_error("Missing second position definition from 'sprite' command",line_no%):ENDPROC
 3100sprite$=FNget_str(ttod_work%!4)
 3110IF LEN(sprite$)>12 THEN PROCttod_error("Illegal sprite name in 'sprite' command", line_no%):ENDPROC
 3120file$=FNget_str(ttod_work%!0)
 3130in_file%=OPENIN(file$)
 3140IF in_file%=0 THEN PROCttod_error("File '"+file$+"' not found in 'sprite' command",line_no%):ENDPROC
 3150number%=FNwget(in_file%)
 3160IF number%=0 THEN PROCttod_error("File '"+file$+"' contains no sprites"):ENDPROC
 3170PTR#in_file%=FNwget(in_file%)-4
 3180tmp%=PTR#in_file%
 3190REPEAT
 3200 len%=FNwget(in_file%)
 3210 tmp$=GET$#in_file%
 3220 IF tmp$<>sprite$ THEN number%=-1 ELSE number%-=1
 3230 IF number%>0 THEN PTR#in_file%=PTR#in_file%+len%-16:tmp%=PTR#in_file%
 3240UNTIL number%<1
 3250IF number%<>-1 THEN PROCttod_error("Sprite '"+sprite$+" not found in file '"+file$+"'"):ENDPROC
 3260PROCttod_get_xy(FNget_str(ttod_work%!8), x1, y1)
 3270PROCttod_get_xy(FNget_str(ttod_work%!12), x2, y2)
 3280x1=x1*ttod_scale:x2=x2*ttod_scale
 3290y1=y1*ttod_scale:y2=y2*ttod_scale
 3300IF x1<x2 THEN x_low=x1:x_high=x2 ELSE x_low=x2:x_high=x1
 3310IF y1<y2 THEN y_low=y1:y_high=y2 ELSE y_low=y2:y_high=y1
 3320PROCttod_put_head(out_file%, 5, 24+((len%+3) AND NOT 3), x_low, y_low, x_high, y_high)
 3330PTR#in_file%=tmp%
 3340IF len%<=1024 THEN
 3350 SYS &c, 4, in_file%, ttod_work%, len%
 3360 SYS &c, 2, out_file%, ttod_work%, len%
 3370ELSE
 3380 tmp%=0
 3390 WHILE tmp%=0
 3400  SYS &c, 4, in_file%, ttod_work%, 1024 TO ,,,tmp%
 3410  SYS &c, 2, out_file%, ttod_work%, 1024-tmp%
 3420 ENDWHILE
 3430ENDIF
 3440CLOSE#in_file%
 3450ENDPROC
 3460:
 3470DEF PROCttod_generate_oval(file%, param$, line_no%)
 3480LOCAL x, y, horz, vert, width, line_col%, fill_col%, const
 3490width=0:colour%=&000000:const=0.552256944
 3500SYS &20049, ttod_ellipse_args$, param$, ttod_work%, 1024 TO ;status%
 3510IF (status% AND 1)=1 THEN PROCttod_error("Syntax error",line_no%):ENDPROC
 3520IF ttod_work%!0=0 THEN PROCttod_error("Missing centre position definition from 'ellipse' command",line_no%):ENDPROC
 3530IF ttod_work%!4=0 THEN PROCttod_error("Missing horizontal size definition from 'ellipse' command",line_no%):ENDPROC
 3540IF ttod_work%!8=0 THEN PROCttod_error("Missing vertical size definition from 'ellipse' command",line_no%):ENDPROC
 3550PROCttod_get_xy(FNget_str(ttod_work%!0), x,y)
 3560horz=VAL(FNget_str(ttod_work%!4)):vert=VAL(FNget_str(ttod_work%!8))
 3570IF ttod_work%!12<>0 THEN width=VAL(FNget_str(ttod_work%!12))*640
 3580IF ttod_work%!16<>0 THEN line_col%=EVAL(FNget_str(ttod_work%!16))
 3590IF ttod_work%!20<>0 THEN fill_col%=EVAL(FNget_str(ttod_work%!20))
 3600x=x*ttod_scale:y=y*ttod_scale:horz=horz*ttod_scale:vert=vert*ttod_scale
 3610PROCttod_put_head(file%, 2, 172, x-horz,y-vert,x+horz,y+vert)
 3620PROCwput(file%, fill_col%)
 3630PROCwput(file%, line_col%)
 3640PROCwput(file%, width)
 3650PROCwput(file%, %00000000)
 3660PROCttod_put_path(file%, 2, x, y-vert)
 3670PROCttod_put_bezier(file%, x+horz, y, x+horz*const, y-vert, x+horz, y-vert*const)
 3680PROCttod_put_bezier(file%, x, y+vert, x+horz, y+vert*const, x+horz*const, y+vert)
 3690PROCttod_put_bezier(file%, x-horz, y, x-horz*const, y+vert, x-horz, y+vert*const)
 3700PROCttod_put_bezier(file%, x, y-vert, x-horz, y-vert*const, x-horz*const, y-vert)
 3710PROCwput(file%, 5)
 3720PROCwput(file%, 0)
 3730ENDPROC
 3740:
 3750DEF PROCttod_generate_path(in_file%, out_file%, param$, RETURN line_no%)
 3760LOCAL in$, com$, par$, status%, head_pos%, x_low, x_high, y_low, y_high, sub%, x1, x2, y1, y2, finish%
 3770finish%=FALSE:sub%=FALSE:x_low=&7FFFFFFF:x_high=0:y_low=&7FFFFFFF:y_high=0
 3780head_pos%=PTR#out_file%
 3790PROCttod_put_head(out_file%, 2, 0, 0, 0, 0, 0)
 3800SYS &20049, ttod_path_args$, param$, ttod_work%, 1024 TO ;status%
 3810IF (status% AND 1)=1 THEN PROCttod_error("Syntax error in command 'path'",line_no%):ENDPROC
 3820IF ttod_work%!8=0 THEN PROCwput(out_file%, &FFFFFF00) ELSE PROCwput(out_file%, VAL(FNget_str(ttod_work%!0)))
 3830IF ttod_work%!4=0 THEN PROCwput(out_file%, 0) ELSE PROCwput(out_file%, VAL(FNget_str(ttod_work%!0)))
 3840IF ttod_work%!0=0 THEN PROCwput(out_file%, 0) ELSE PROCwput(out_file%, VAL(FNget_str(ttod_work%!0))*640)
 3850PROCwput(out_file%, 0)
 3860WHILE (finish%=FALSE) AND (NOT ttod_error%)
 3870 in$=FNstrip_spaces(GET$#in_file%)
 3880 line_no%+=1
 3890 status%=FNttod_parse(in$, com$, par$)
 3900 CASE com$ OF
 3910  WHEN "draw" :
 3920   IF NOT sub% THEN
 3930    PROCttod_error("Not in a sub-path for 'draw' command", line_no%):ENDPROC
 3940   ELSE
 3950    PROCttod_path_draw(out_file%, par$, line_no%, x1, y1)
 3960    IF x1>x_high THEN x_high=x1
 3970    IF x1<x_low  THEN x_low=x1
 3980    IF y1>y_high THEN y_high=y1
 3990    IF y1<y_low  THEN y_low=y1
 4000   ENDIF
 4010  WHEN "move" :
 4020   sub%=TRUE
 4030   PROCttod_path_move(out_file%, par$, line_no%, x1, y1)
 4040   IF x1>x_high THEN x_high=x1
 4050   IF x1<x_low  THEN x_low=x1
 4060   IF y1>y_high THEN y_high=y1
 4070   IF y1<y_low  THEN y_low=y1
 4080  WHEN "curve" :
 4090   PROCttod_path_curve(out_file%, par$, line_no%, x1, y1, x2, y2)
 4100   IF x1>x_high THEN x_high=x1
 4110   IF x1<x_low  THEN x_low=x1
 4120   IF y1>y_high THEN y_high=y1
 4130   IF y1<y_low  THEN y_low=y1
 4140   IF x2>x_high THEN x_high=x2
 4150   IF x2<x_low  THEN x_low=x2
 4160   IF y2>y_high THEN y_high=y2
 4170   IF y2<y_low  THEN y_low=y2
 4180  WHEN "close" :
 4190   IF sub%=FALSE THEN
 4200    PROCttod_error("Not in a sub-path for 'close' command", line_no%):ENDPROC
 4210   ELSE
 4220    sub%=FALSE
 4230    PROCwput(out_file%, 5)
 4240   ENDIF
 4250  WHEN "end" :
 4260   PROCwput(out_file%, 0)
 4270   finish%=TRUE
 4280 OTHERWISE :
 4290  IF LEFT$(com$, 1)<>"#" THEN PROCttod_error("Illegal command in path segment", line_no%):ENDPROC
 4300 ENDCASE
 4310ENDWHILE
 4320len%=PTR#out_file% - head_pos%
 4330PTR#out_file%=head_pos%
 4340PROCttod_put_head(out_file%, 2, len%, x_low, y_low, x_high, y_high)
 4350PTR#out_file%=EXT#out_file%
 4360ENDPROC
 4370:
 4380DEF PROCttod_path_move(file%, param$, line%, RETURN x, RETURN y)
 4390SYS &20049, ttod_one_args$, param$, ttod_work%, 1024 TO ;status%
 4400IF (status% AND 1)=1 THEN PROCttod_error("Syntax error in 'move' command",line_no%):ENDPROC
 4410IF ttod_work%!0=0 THEN PROCttod_error("Missing co-ordinates from 'move' command",line_no%):ENDPROC
 4420PROCttod_get_xy(FNget_str(ttod_work%!0), x, y)
 4430x=x*ttod_scale:y=y*ttod_scale
 4440PROCttod_put_path(file%, 2, x, y)
 4450ENDPROC
 4460:
 4470DEF PROCttod_path_draw(file%, param$, line%, RETURN x, RETURN y)
 4480SYS &20049, ttod_one_args$, param$, ttod_work%, 1024 TO ;status%
 4490IF (status% AND 1)=1 THEN PROCttod_error("Syntax error in 'draw' command",line_no%):ENDPROC
 4500IF ttod_work%!0=0 THEN PROCttod_error("Missing co-ordinates from 'draw' command",line_no%):ENDPROC
 4510PROCttod_get_xy(FNget_str(ttod_work%!0), x, y)
 4520x=x*ttod_scale:y=y*ttod_scale
 4530PROCttod_put_path(file%, 8, x, y)
 4540ENDPROC
 4550:
 4560DEF PROCttod_path_curve(file%, param$, line%, RETURN x1, RETURN y1, RETURN x2, RETURN y2)
 4570LOCAL x, y
 4580SYS &20049, ttod_three_args$, param$, ttod_work%, 1024 TO ;status%
 4590IF (status% AND 1)=1 THEN PROCttod_error("Syntax error in 'curve' command",line_no%):ENDPROC
 4600IF ttod_work%!0=0 THEN PROCttod_error("Missing co-ordinates from 'curve' command",line_no%):ENDPROC
 4610IF ttod_work%!4=0 THEN PROCttod_error("Missing co-ordinates from 'curve' command",line_no%):ENDPROC
 4620IF ttod_work%!8=0 THEN PROCttod_error("Missing co-ordinates from 'curve' command",line_no%):ENDPROC
 4630PROCttod_get_xy(FNget_str(ttod_work%!0), x, y)
 4640PROCttod_get_xy(FNget_str(ttod_work%!4), x1, y1)
 4650PROCttod_get_xy(FNget_str(ttod_work%!8), x2, y2)
 4660x=x*ttod_scale:y=y*ttod_scale
 4670x1=x1*ttod_scale:y1=y1*ttod_scale
 4680x2=x2*ttod_scale:y2=y2*ttod_scale
 4690PROCttod_put_path(file%, 6, x1, y1)
 4700PROCwput(file%,x2)
 4710PROCwput(file%,y2)
 4720PROCwput(file%,x)
 4730PROCwput(file%,y)
 4740ENDPROC
 4750:
 4760DEF PROCttod_get_xy(par$, RETURN x, RETURN y)
 4770LOCAL pos%
 4780pos%=INSTR(par$, ",")
 4790x=VAL(FNstrip_spaces(LEFT$(par$,pos%-1)))
 4800y=VAL(FNstrip_spaces(RIGHT$(par$,LEN(par$)-pos%)))
 4810ENDPROC
 4820:
 4830DEF PROCttod_put_path(file%, id%, x, y)
 4840PROCwput(file%, id%):PROCwput(file%, x):PROCwput(file%, y)
 4850ENDPROC
 4860:
 4870DEF PROCttod_put_bezier(file%, x, y, x1, y1, x2, y2)
 4880PROCwput(file%, 6):PROCwput(file%, x1):PROCwput(file%, y1)
 4890PROCwput(file%, x2):PROCwput(file%, y2)
 4900PROCwput(file%, x):PROCwput(file%, y)
 4910ENDPROC
 4920:
 4930DEF PROCttod_put_head(file%, id%, size%, x1, y1, x2, y2)
 4940PROCwput(file%, id%):PROCwput(file%, size%)
 4950PROCwput(file%, x1):PROCwput(file%, y1)
 4960PROCwput(file%, x2):PROCwput(file%, y2)
 4970ENDPROC
 4980:
 4990DEF PROCttod_put_padded(file%, len%, str$, pad$)
 5000LOCAL strlen%
 5010strlen%=LEN(str$)
 5020IF strlen% < len% THEN
 5030 BPUT#file%, str$;
 5040 BPUT#file%, STRING$(len%-strlen%, pad$);
 5050ELSE
 5060 BPUT#file%, str$;
 5070ENDIF
 5080ENDPROC
 5090:
 5100DEF FNttod_check_font_handle(handles$, no%)
 5110=(INSTR(handles$, STR$(no%)) = 0)
 5120:
 5130DEF PROCttod_error(error$, no%)
 5140IF no%=0 THEN
 5150 $(ttod_error_q%+4)=error$
 5160 SYS &400DF,ttod_error_q%, %1, "Text-2-Draw"
 5170 ttod_error%=TRUE
 5180ELSE
 5190 $(ttod_error_q%+4)=error$+" at line "+STR$(no%)
 5200 SYS &400DF,ttod_error_q%, %1, "Text-2-Draw"
 5210 ttod_error%=TRUE
 5220ENDIF
 5230ENDPROC
 5240:
 5250DEF FNttod_parse(in$, RETURN com$, RETURN par$)
 5260LOCAL pos%
 5270pos%=INSTR(in$, " ")
 5280com$=FNlc(FNstrip_spaces(LEFT$(in$, pos%)))
 5290par$=FNstrip_spaces(RIGHT$(in$, LEN(in$) - pos%))
 5300IF pos%=0 THEN com$=in$:par$=""
 5310=pos%
 5320:
 5330DEF FNttod_help(window%,icon%)
 5340IF window%=-1 THEN ="Drag a draw description file here to generate a draw file." ELSE =""

�     >TtoD (BIO3)
� By  Gary Palmer
� For use with Bio
(� (c) BAU September 1993
2�
<:
F#� �ttod_name="Text to DrawFile"
P:
Z/� �ttod_args="-in Text -out drawfile -send"
d:
n� �ttod_init
xș "Hourglass_On"
�� font_no%, status%
�>ttod_inch_scale=180*256:ttod_mm_scale=ttod_inch_scale/25.4
�?ttod_mp_per_inch=72000:ttod_mp_per_mm=ttod_mp_per_inch/25.4
�<ttod_scale=ttod_mm_scale:ttod_millipoints=ttod_mp_per_mm
�Q� ttod_font_name$(64), ttod_font_size(64), ttod_work% 8192, ttod_error_q% 256
�ttod_font_no%=0
�Bttod_rect_args$="first/k,second/k,width=w/k,fill=f/k,line=l/k"
�6ttod_line_args$="start/k,end/k,width=w/k,line=l/k"
�0ttod_ltext_args$="x/k,y/k,text=t/k,path=p/s"
�9ttod_ctext_args$="first/k,second/k,text=t/k,path=p/s"
�5ttod_font_args$="number=no/k,name=na/k,size=sz/k"
�?ttod_sprite_args$="file=f/k,sprite=name/k,first/k,second/k"
�1ttod_path_args$="width=w/k,fill=f/k,line=l/k"
ttod_one_args$="to/k"
,ttod_three_args$="to/k,first/k,second/k"
Qttod_ellipse_args$="centre=c/k,horz=h/k,vert=v/k,width=w/k,line=l/k,fill=f/k"
"ttod_used_handles$=""
,5ș "Wimp_ReadSysInfo",7 � ttod_version% ; status%
6)� (status% � 1)=1 � ttod_version%=200
@ș "Hourglass_Smash"
J=0
T:
^� �ttod(in$, out$)
httod_error%=�
r� in_file%, out_file%
|ș "Hourglass_On"
�in_file%=�(in$)
�>� in_file%=0 � �ttod_error("Cannot open input file", 0):=1
�out_file%=�(out$)
�L� out_file%=0 � �ttod_error("Cannot open output file", 0):� #in_file%:=1
�%�ttod_scan_fonts_needed(in_file%)
�/� � ttod_error% �ttod_start_file(out_file%)
�6� � ttod_error% �ttod_create_font_table(out_file%)
�<� � ttod_error% �ttod_generate_file(in_file%, out_file%)
��#in_file%
��#out_file%
�ș "Hourglass_Smash"
�� ttod_error% � =1 � =0
�:
$� �ttod_scan_fonts_needed(file%)
F� in$, line_no%, com$, param$, name$, size$, no%, status%, handle%

�#file%=0
&$line_no%=0:ttod_used_handles$=""
0'ȕ (� �#in_file%) � (� ttod_error%)
: in$=�strip_spaces(�#file%)
D line_no%+=1
N: � �ttod_parse(in$, com$, param$)  � (�in$, 1)<>"#") �
X  Ȏ com$ �
b   � "font":
lG    ș &20049, ttod_font_args$, param$, ttod_work%, 1024 � ;status%
vC    � (status% � 1)=1 � �ttod_error("Syntax error", line_no%):�
�h    � ttod_work%!0<>0 � no%=�(�get_str(ttod_work%!0)) � �ttod_error("Font number needed",line_no%):�
�<    � �ttod_check_font_handle(ttod_used_handles$, no%) �
�F     � ttod_work%!4=0 � �ttod_error("Font name needed",line_no%):�
�F     � ttod_work%!8=0 � �ttod_error("Font size needed",line_no%):�
�%     name$=�get_str(ttod_work%!4)
�9     ș &60081,,name$, 16, 16, 0, 0 � handle%;status%
�J     � (status% � 1)=1 � �ttod_error("Incorrect font name",line_no%):�
�     ș &40082, handle%
�#     ttod_font_name$(no%)=name$
�6     ttod_font_size(no%)=�(�get_str(ttod_work%!8))
�^     � ttod_used_handles$<>"" � ttod_used_handles$+=" "+�(no%) � ttod_used_handles$=�(no%)
�	    �
�  �
 �
�

�#file%=0
 �
*:
4� �ttod_start_file(file%)
>�#file%,"Draw";
H�wput(file%, 201)
R�wput(file%, 0)
\�#file%,"TextToDraw  ";
f�wput(file%, 0)
p�wput(file%, 0)
z �wput(file%, ttod_scale*210)
� �wput(file%, ttod_scale*297)
��
�:
�$� �ttod_create_font_table(file%)
�(� used$, len%, tmp$, no%, pad%, tmp%
�#used$=ttod_used_handles$:len%=0
��wput(file%, 0)
�tmp%=�#file%
��wput(file%, 0)
��
�+ � �ttod_parse(used$, tmp$, used$)<>0 �
�  no%=�(tmp$)
� �
  no%=�(tmp$):used$=""
 �
$ len%+=�(ttod_font_name$(no%))+2
$ �#file%, no%
.( �#file%, ttod_font_name$(no%)+�(0);
8� used$=""
B�#file%=tmp%
L0tmp%=len%:len%=(len%+3) � � 3:pad%=len%-tmp%
V�wput(file%, len%+8)
`�#file%=�#file%
j/� pad%<>0 � � no%=1 � pad%:�#file%, 0:� no%
t�
~:
�.� �ttod_generate_file(in_file%, out_file%)
�S� in$, com$, param$, line_no%, no%, font_handle%, real_handle%, first%, status%
�line_no%=0:first%=�
�'ȕ (� �#in_file%) � (� ttod_error%)
�" in$=�strip_spaces(�#in_file%)
� line_no%+=1
�' � �ttod_parse(in$, com$, param$) �
�  Ȏ com$ �
�   � "ltext" :
�G    �ttod_generate_ltext(out_file%, font_handle%, param$, line_no%)
�   � "ctext" :
�G    �ttod_generate_ctext(out_file%, font_handle%, param$, line_no%)
   � "font" :

G    ș &20049, ttod_font_args$, param$, ttod_work%, 1024 � ;status%
C    � (status% � 1)=1 � �ttod_error("Syntax error", line_no%):�
%    no%=�(�get_str(ttod_work%!0))
(J    � no%<1 � no%>64 � �ttod_error("Incorrect font number",line_no%):�
2?    � (� �ttod_check_font_handle(ttod_used_handles$,no%)) �
<     font_handle%=no%
F	    �
Ph     �ttod_error("SERIOUS INTERNL ERROR : I've lost track of a font handle ("+no$+")!!", line_no%):�
Z	    �
d5    � first% � first%=� � ș &40082, real_handle%
nu    ș &40081,,ttod_font_name$(font_handle%), ttod_font_size(no%)*16, ttod_font_size(no%)*16, 0, 0 � real_handle%
x   � "line" :
�8    �ttod_generate_line(out_file%, param$, line_no%)
�   � "units" :
�    Ȏ �lc(param$) �
�P     � "inch" : ttod_scale=ttod_inch_scale:ttod_millipoints=ttod_mp_per_inch
�J     � "mm" : ttod_scale=ttod_mm_scale:ttod_millipoints=ttod_mp_per_mm
�S      : �ttod_error("Illegal measurement scale in 'units' command",line_no%):�
�	    �
�   � "rectangle" :
�7    �ttod_generate_box(out_file%, param$, line_no%)
�   � "sprite" :
�9    �ttod_include_sprite(out_file%, param$, line_no%)
�   � "path" :
�B    �ttod_generate_path(in_file%, out_file%, param$, line_no%)
   � "ellipse" :
8    �ttod_generate_oval(out_file%, param$, line_no%)
E  : � (�com$, 1)<>"#") � �ttod_error("Unknown command",line_no%)
"  �
, �
6�
@(� � first% � ș &40082, real_handle%
J�
T:
^9� �ttod_generate_ltext(file%, handle%, param$, line%)
h@� x, y, text$, bound_x, bound_y, len%, status%, path%, need%
rDș &20049, ttod_ltext_args$, param$, ttod_work%, 1024 � ;status%
|;� (status% � 1)=1 � �ttod_error("Syntax error",line%):�
�`� ttod_work%!0=0 � �ttod_error("Missing x position definition from 'ltext' command",line%):�
�`� ttod_work%!4=0 � �ttod_error("Missing y position definition from 'ltext' command",line%):�
�[� ttod_work%!8=0 � �ttod_error("Missing text information from 'ltext' command",line%):�
�Vx=�(�get_str(ttod_work%!0)):y=�(�get_str(ttod_work%!4)):path%=((ttod_work%!12)<>0)
� text$=�get_str(ttod_work%!8)
�
� path% �
�. x=x*ttod_millipoints:y=y*ttod_millipoints
� ș &4009E,%1,8
�' ș &40086,0,text$,%01100000000,x,y
� ș &4009E,0,0 � ,need%
�K � need%>=8184 � �ttod_error("Text path too big for buffer!!", line%):�
�# !ttod_work%=0:!ttod_work%=8184
�  ș &4009E,%10010,ttod_work%
' ș &40086,0,text$,%01100000000,x,y
 ș &4009E,0,0 � ,need%
5 ș "OS_GBPB",2,file%,ttod_work%,need%-ttod_work%
&�
0, ș &40097,,text$ � ,,, bound_x, bound_y
:0 bound_x=bound_x/ttod_millipoints*ttod_scale
D0 bound_y=bound_y/ttod_millipoints*ttod_scale
N" x=x*ttod_scale:y=y*ttod_scale
X len%=(�(text$)+1+3) � � 3
bF �ttod_put_head(file%, 1, 52+len%, x, y, bound_x+1+x, bound_y+1+y)
l �wput(file%, 0)
v �wput(file%, &FFFFFF00)
� �wput(file%, handle%)
�. �wput(file%, ttod_font_size(handle%)*640)
�. �wput(file%, ttod_font_size(handle%)*640)
� �wput(file%, x)
� �wput(file%, y)
�4 �ttod_put_padded(file%, len%, text$+�(0), �(0))
��
��
�:
�9� �ttod_generate_ctext(file%, handle%, param$, line%)
�a� x1, y1, x2, y2, x_low, y_low, x_high, y_high, text$, bound_x, bound_y, len%, status%, path%
�Dș &20049, ttod_ctext_args$, param$, ttod_work%, 1024 � ;status%
�;� (status% � 1)=1 � �ttod_error("Syntax error",line%):�
d� ttod_work%!0=0 � �ttod_error("Missing first position definition from 'ctext' command",line%):�
e� ttod_work%!4=0 � �ttod_error("Missing second position definition from 'ctext' command",line%):�
[� ttod_work%!8=0 � �ttod_error("Missing text information from 'ctext' command",line%):�
 0�ttod_get_xy(�get_str(ttod_work%!0), x1, y1)
*0�ttod_get_xy(�get_str(ttod_work%!4), x2, y2)
4;text$=�get_str(ttod_work%!8):path%=((ttod_work%!12)<>0)
>%x1=x1*ttod_scale:x2=x2*ttod_scale
H%y1=y1*ttod_scale:y2=y2*ttod_scale
R5� x1<x2 � x_low=x1:x_high=x2 � x_low=x2:x_high=x1
\5� y1<y2 � y_low=y1:y_high=y2 � y_low=y2:y_high=y1
f+ș &40097,,text$ � ,,, bound_x, bound_y
p/bound_x=bound_x/ttod_millipoints*ttod_scale
z/bound_y=bound_y/ttod_millipoints*ttod_scale
�d� (x_high-x_low)<bound_x � �ttod_error("Bounding box too small (in x) in ctext command",line%):�
�d� (y_high-y_low)<bound_y � �ttod_error("Bounding box too small (in y) in ctext command",line%):�
�#x_low+=(x_high-x_low-bound_x)/2
�#y_low+=(y_high-y_low-bound_y)/2
�=len%=(�(text$)+1) � � 3:� ((�(text$)+1) � 4)<>0 � len%+=4
�
� path% �
�T x_low=x_low*ttod_millipoints/ttod_scale:y_low=y_low*ttod_millipoints/ttod_scale
� ș &4009E,%1,8
�/ ș &40086,0,text$,%01100000000,x_low,y_low
� ș &4009E,0,0 � ,need%
�K � need%>=8184 � �ttod_error("Text path too big for buffer!!", line%):�
�# !ttod_work%=0:!ttod_work%=8184
�  ș &4009E,%10010,ttod_work%
	/ ș &40086,0,text$,%01100000000,x_low,y_low
	 ș &4009E,0,0 � ,need%
	5 ș "OS_GBPB",2,file%,ttod_work%,need%-ttod_work%
	$�
	.R �ttod_put_head(file%, 1, 52+len%, x_low, y_low, x_low+bound_x, y_low+bound_y)
	8 �wput(file%, 0)
	B �wput(file%, &FFFFFF00)
	L �wput(file%, handle%)
	V. �wput(file%, ttod_font_size(handle%)*640)
	`. �wput(file%, ttod_font_size(handle%)*640)
	j �wput(file%, x_low)
	t �wput(file%, y_low)
	~4 �ttod_put_padded(file%, len%, text$+�(0), �(0))
	��
	��
	�:
	�2� �ttod_generate_line(file%, param$, line_no%)
	�a� start_x, start_y, finish_x, finish_y, x_low, y_low, x_high, y_high, width, status%, colour%
	�0width=0:start%=�:finish%=�:colour%=&00000000
	�Cș &20049, ttod_line_args$, param$, ttod_work%, 1024 � ;status%
	�>� (status% � 1)=1 � �ttod_error("Syntax error",line_no%):�
	�f� ttod_work%!0=0 � �ttod_error("Missing start position definition from 'line' command",line_no%):�
	�d� ttod_work%!4=0 � �ttod_error("Missing end position definition from 'line' command",line_no%):�
	�:�ttod_get_xy(�get_str(ttod_work%!0), start_x, start_y)
	�<�ttod_get_xy(�get_str(ttod_work%!4), finish_x, finish_y)
;� ttod_work%!8<>0 � width=�(�get_str(ttod_work%!8))*640

;� ttod_work%!12<>0 � colour%=�(�get_str(ttod_work%!12))
9start_x=start_x*ttod_scale:start_y=start_y*ttod_scale
=finish_x=finish_x*ttod_scale:finish_y=finish_y*ttod_scale
(V� start_x<finish_x � x_low=start_x:x_high=finish_x � x_low=finish_x:x_high=start_x
2V� start_y<finish_y � y_low=start_y:y_high=finish_y � y_low=finish_y:y_high=start_y
<>�ttod_put_head(file%, 2, 68, x_low, y_low, x_high, y_high)
F�wput(file%, &FFFFFFFF)
P�wput(file%, colour%)
Z�wput(file%, width)
d�wput(file%, %00000000)
n.�ttod_put_path(file%, 2, start_x, start_y)
x0�ttod_put_path(file%, 8, finish_x, finish_y)
��wput(file%, 0)
��
�:
�1� �ttod_generate_box(file%, param$, line_no%)
�Y� x1, y1, x2, y2, x_low, y_low, x_high, y_high, width, status%, line_col%, fille_col%
�3width=0:line_col%=&00000000:fill_col%=&FFFFFFFF
�Cș &20049, ttod_rect_args$, param$, ttod_work%, 1024 � ;status%
�>� (status% � 1)=1 � �ttod_error("Syntax error",line_no%):�
�e� ttod_work%!0=0 � �ttod_error("Missing first position definition from 'box' command",line_no%):�
�f� ttod_work%!4=0 � �ttod_error("Missing second position definition from 'box' command",line_no%):�
�0�ttod_get_xy(�get_str(ttod_work%!0), x1, y1)
�0�ttod_get_xy(�get_str(ttod_work%!4), x2, y2)
�;� ttod_work%!8<>0 � width=�(�get_str(ttod_work%!8))*640
=� ttod_work%!12<>0 � fill_col%=�(�get_str(ttod_work%!12))
=� ttod_work%!16<>0 � line_col%=�(�get_str(ttod_work%!16))
%x1=x1*ttod_scale:x2=x2*ttod_scale
"%y1=y1*ttod_scale:y2=y2*ttod_scale
,5� x1<x2 � x_low=x1:x_high=x2 � x_low=x2:x_high=x1
65� y1<y2 � y_low=y1:y_high=y2 � y_low=y2:y_high=y1
@?�ttod_put_head(file%, 2, 108, x_low, y_low, x_high, y_high)
J�wput(file%, fill_col%)
T�wput(file%, line_col%)
^�wput(file%, width)
h�wput(file%, %00000000)
r$�ttod_put_path(file%, 2, x1, y1)
|$�ttod_put_path(file%, 8, x2, y1)
�$�ttod_put_path(file%, 8, x2, y2)
�$�ttod_put_path(file%, 8, x1, y2)
�$�ttod_put_path(file%, 8, x1, y1)
��wput(file%, 5)
��wput(file%, 0)
��
�:
�7� �ttod_include_sprite(out_file%, param$, line_no%)
�p� x1, y1, x2, y2, x_low, y_low, x_high, y_high, file$, in_file%, sprite$, status%, number%, len%, tmp$, tmp%
�Eș &20049, ttod_sprite_args$, param$, ttod_work%, 1024 � ;status%
�>� (status% � 1)=1 � �ttod_error("Syntax error",line_no%):�
�X� ttod_work%!0=0 � �ttod_error("Missing file name from 'sprite' command",line_no%):�
�[� ttod_work%!4=0 � �ttod_error("Missing sprite name from 'sprite' command", line_no%):�
h� ttod_work%!8=0 � �ttod_error("Missing first position definition from 'sprite' command",line_no%):�
j� ttod_work%!12=0 � �ttod_error("Missing second position definition from 'sprite' command",line_no%):�
"sprite$=�get_str(ttod_work%!4)
&X� �(sprite$)>12 � �ttod_error("Illegal sprite name in 'sprite' command", line_no%):�
0 file$=�get_str(ttod_work%!0)
:in_file%=�(file$)
D[� in_file%=0 � �ttod_error("File '"+file$+"' not found in 'sprite' command",line_no%):�
Nnumber%=�wget(in_file%)
XG� number%=0 � �ttod_error("File '"+file$+"' contains no sprites"):�
b �#in_file%=�wget(in_file%)-4
ltmp%=�#in_file%
v�
� len%=�wget(in_file%)
� tmp$=�#in_file%
�. � tmp$<>sprite$ � number%=-1 � number%-=1
�@ � number%>0 � �#in_file%=�#in_file%+len%-16:tmp%=�#in_file%
�� number%<1
�V� number%<>-1 � �ttod_error("Sprite '"+sprite$+" not found in file '"+file$+"'"):�
�0�ttod_get_xy(�get_str(ttod_work%!8), x1, y1)
�1�ttod_get_xy(�get_str(ttod_work%!12), x2, y2)
�%x1=x1*ttod_scale:x2=x2*ttod_scale
�%y1=y1*ttod_scale:y2=y2*ttod_scale
�5� x1<x2 � x_low=x1:x_high=x2 � x_low=x2:x_high=x1
�5� y1<y2 � y_low=y1:y_high=y2 � y_low=y2:y_high=y1
�S�ttod_put_head(out_file%, 5, 24+((len%+3) � � 3), x_low, y_low, x_high, y_high)

�#in_file%=tmp%

� len%<=1024 �

) ș &c, 4, in_file%, ttod_work%, len%

 * ș &c, 2, out_file%, ttod_work%, len%

*�

4 tmp%=0

> ȕ tmp%=0

H4  ș &c, 4, in_file%, ttod_work%, 1024 � ,,,tmp%

R0  ș &c, 2, out_file%, ttod_work%, 1024-tmp%

\ �

f�

p�#in_file%

z�

�:

�2� �ttod_generate_oval(file%, param$, line_no%)

�:� x, y, horz, vert, width, line_col%, fill_col%, const

�-width=0:colour%=&000000:const=0.552256944

�Fș &20049, ttod_ellipse_args$, param$, ttod_work%, 1024 � ;status%

�>� (status% � 1)=1 � �ttod_error("Syntax error",line_no%):�

�j� ttod_work%!0=0 � �ttod_error("Missing centre position definition from 'ellipse' command",line_no%):�

�j� ttod_work%!4=0 � �ttod_error("Missing horizontal size definition from 'ellipse' command",line_no%):�

�h� ttod_work%!8=0 � �ttod_error("Missing vertical size definition from 'ellipse' command",line_no%):�

�-�ttod_get_xy(�get_str(ttod_work%!0), x,y)

�Ahorz=�(�get_str(ttod_work%!4)):vert=�(�get_str(ttod_work%!8))

�=� ttod_work%!12<>0 � width=�(�get_str(ttod_work%!12))*640

�=� ttod_work%!16<>0 � line_col%=�(�get_str(ttod_work%!16))
=� ttod_work%!20<>0 � fill_col%=�(�get_str(ttod_work%!20))
Kx=x*ttod_scale:y=y*ttod_scale:horz=horz*ttod_scale:vert=vert*ttod_scale
>�ttod_put_head(file%, 2, 172, x-horz,y-vert,x+horz,y+vert)
$�wput(file%, fill_col%)
.�wput(file%, line_col%)
8�wput(file%, width)
B�wput(file%, %00000000)
L'�ttod_put_path(file%, 2, x, y-vert)
VR�ttod_put_bezier(file%, x+horz, y, x+horz*const, y-vert, x+horz, y-vert*const)
`R�ttod_put_bezier(file%, x, y+vert, x+horz, y+vert*const, x+horz*const, y+vert)
jR�ttod_put_bezier(file%, x-horz, y, x-horz*const, y+vert, x-horz, y+vert*const)
tR�ttod_put_bezier(file%, x, y-vert, x-horz, y-vert*const, x-horz*const, y-vert)
~�wput(file%, 5)
��wput(file%, 0)
��
�:
�B� �ttod_generate_path(in_file%, out_file%, param$, � line_no%)
�f� in$, com$, par$, status%, head_pos%, x_low, x_high, y_low, y_high, sub%, x1, x2, y1, y2, finish%
�Ffinish%=�:sub%=�:x_low=&7FFFFFFF:x_high=0:y_low=&7FFFFFFF:y_high=0
�head_pos%=�#out_file%
�/�ttod_put_head(out_file%, 2, 0, 0, 0, 0, 0)
�Cș &20049, ttod_path_args$, param$, ttod_work%, 1024 � ;status%
�P� (status% � 1)=1 � �ttod_error("Syntax error in command 'path'",line_no%):�
�`� ttod_work%!8=0 � �wput(out_file%, &FFFFFF00) � �wput(out_file%, �(�get_str(ttod_work%!0)))
�X� ttod_work%!4=0 � �wput(out_file%, 0) � �wput(out_file%, �(�get_str(ttod_work%!0)))
\� ttod_work%!0=0 � �wput(out_file%, 0) � �wput(out_file%, �(�get_str(ttod_work%!0))*640)

�wput(out_file%, 0)
$ȕ (finish%=�) � (� ttod_error%)
" in$=�strip_spaces(�#in_file%)
( line_no%+=1
2) status%=�ttod_parse(in$, com$, par$)
< Ȏ com$ �
F  � "draw" :
P   � � sub% �
ZG    �ttod_error("Not in a sub-path for 'draw' command", line_no%):�
d   �
n:    �ttod_path_draw(out_file%, par$, line_no%, x1, y1)
x    � x1>x_high � x_high=x1
�    � x1<x_low  � x_low=x1
�    � y1>y_high � y_high=y1
�    � y1<y_low  � y_low=y1
�   �
�  � "move" :
�
   sub%=�
�9   �ttod_path_move(out_file%, par$, line_no%, x1, y1)
�   � x1>x_high � x_high=x1
�   � x1<x_low  � x_low=x1
�   � y1>y_high � y_high=y1
�   � y1<y_low  � y_low=y1
�  � "curve" :
�B   �ttod_path_curve(out_file%, par$, line_no%, x1, y1, x2, y2)
   � x1>x_high � x_high=x1
   � x1<x_low  � x_low=x1
   � y1>y_high � y_high=y1
"   � y1<y_low  � y_low=y1
,   � x2>x_high � x_high=x2
6   � x2<x_low  � x_low=x2
@   � y2>y_high � y_high=y2
J   � y2<y_low  � y_low=y2
T  � "close" :
^   � sub%=� �
hH    �ttod_error("Not in a sub-path for 'close' command", line_no%):�
r   �
|    sub%=�
�    �wput(out_file%, 5)
�   �
�  � "end" :
�   �wput(out_file%, 0)
�   finish%=�
�  :
�S  � �com$, 1)<>"#" � �ttod_error("Illegal command in path segment", line_no%):�
� �
��
� len%=�#out_file% - head_pos%
��#out_file%=head_pos%
�D�ttod_put_head(out_file%, 2, len%, x_low, y_low, x_high, y_high)
��#out_file%=�#out_file%
�
:
5� �ttod_path_move(file%, param$, line%, � x, � y)
&Bș &20049, ttod_one_args$, param$, ttod_work%, 1024 � ;status%
0P� (status% � 1)=1 � �ttod_error("Syntax error in 'move' command",line_no%):�
:Y� ttod_work%!0=0 � �ttod_error("Missing co-ordinates from 'move' command",line_no%):�
D.�ttod_get_xy(�get_str(ttod_work%!0), x, y)
N!x=x*ttod_scale:y=y*ttod_scale
X"�ttod_put_path(file%, 2, x, y)
b�
l:
v5� �ttod_path_draw(file%, param$, line%, � x, � y)
�Bș &20049, ttod_one_args$, param$, ttod_work%, 1024 � ;status%
�P� (status% � 1)=1 � �ttod_error("Syntax error in 'draw' command",line_no%):�
�Y� ttod_work%!0=0 � �ttod_error("Missing co-ordinates from 'draw' command",line_no%):�
�.�ttod_get_xy(�get_str(ttod_work%!0), x, y)
�!x=x*ttod_scale:y=y*ttod_scale
�"�ttod_put_path(file%, 8, x, y)
��
�:
�D� �ttod_path_curve(file%, param$, line%, � x1, � y1, � x2, � y2)
�
� x, y
�Dș &20049, ttod_three_args$, param$, ttod_work%, 1024 � ;status%
�Q� (status% � 1)=1 � �ttod_error("Syntax error in 'curve' command",line_no%):�
�Z� ttod_work%!0=0 � �ttod_error("Missing co-ordinates from 'curve' command",line_no%):�
Z� ttod_work%!4=0 � �ttod_error("Missing co-ordinates from 'curve' command",line_no%):�
Z� ttod_work%!8=0 � �ttod_error("Missing co-ordinates from 'curve' command",line_no%):�
.�ttod_get_xy(�get_str(ttod_work%!0), x, y)
 0�ttod_get_xy(�get_str(ttod_work%!4), x1, y1)
*0�ttod_get_xy(�get_str(ttod_work%!8), x2, y2)
4!x=x*ttod_scale:y=y*ttod_scale
>%x1=x1*ttod_scale:y1=y1*ttod_scale
H%x2=x2*ttod_scale:y2=y2*ttod_scale
R$�ttod_put_path(file%, 6, x1, y1)
\�wput(file%,x2)
f�wput(file%,y2)
p�wput(file%,x)
z�wput(file%,y)
��
�:
�"� �ttod_get_xy(par$, � x, � y)
�
� pos%
�pos%=�par$, ",")
�%x=�(�strip_spaces(�par$,pos%-1)))
�+y=�(�strip_spaces(�par$,�(par$)-pos%)))
��
�:
�&� �ttod_put_path(file%, id%, x, y)
�5�wput(file%, id%):�wput(file%, x):�wput(file%, y)
��
�:
3� �ttod_put_bezier(file%, x, y, x1, y1, x2, y2)
5�wput(file%, 6):�wput(file%, x1):�wput(file%, y1)
%�wput(file%, x2):�wput(file%, y2)
$#�wput(file%, x):�wput(file%, y)
.�
8:
B7� �ttod_put_head(file%, id%, size%, x1, y1, x2, y2)
L)�wput(file%, id%):�wput(file%, size%)
V%�wput(file%, x1):�wput(file%, y1)
`%�wput(file%, x2):�wput(file%, y2)
j�
t:
~/� �ttod_put_padded(file%, len%, str$, pad$)
�
� strlen%
�strlen%=�(str$)
�� strlen% < len% �
� �#file%, str$;
�# �#file%, �len%-strlen%, pad$);
��
� �#file%, str$;
��
��
�:
�,� �ttod_check_font_handle(handles$, no%)
�=(�handles$, �(no%)) = 0)
:

� �ttod_error(error$, no%)

� no%=0 �
 $(ttod_error_q%+4)=error$
(/ ș &400DF,ttod_error_q%, %1, "Text-2-Draw"
2 ttod_error%=�
<�
F1 $(ttod_error_q%+4)=error$+" at line "+�(no%)
P/ ș &400DF,ttod_error_q%, %1, "Text-2-Draw"
Z ttod_error%=�
d�
n�
x:
�&� �ttod_parse(in$, � com$, � par$)
�
� pos%
�pos%=�in$, " ")
�(com$=�lc(�strip_spaces(�in$, pos%)))
�,par$=�strip_spaces(�in$, �(in$) - pos%))
�� pos%=0 � com$=in$:par$=""
�	=pos%
�:
�� �ttod_help(window%,icon%)
�V� window%=-1 � ="Drag a draw description file here to generate a draw file." � =""
�
00000000  0d 00 0a 16 f4 20 20 20  20 20 3e 54 74 6f 44 20  |.....     >TtoD |
00000010  28 42 49 4f 33 29 0d 00  14 15 f4 20 42 79 20 20  |(BIO3)..... By  |
00000020  47 61 72 79 20 50 61 6c  6d 65 72 0d 00 1e 16 f4  |Gary Palmer.....|
00000030  20 46 6f 72 20 75 73 65  20 77 69 74 68 20 42 69  | For use with Bi|
00000040  6f 0d 00 28 1c f4 20 28  63 29 20 42 41 55 20 53  |o..(.. (c) BAU S|
00000050  65 70 74 65 6d 62 65 72  20 31 39 39 33 0d 00 32  |eptember 1993..2|
00000060  05 e0 0d 00 3c 05 3a 0d  00 46 23 dd 20 a4 74 74  |....<.:..F#. .tt|
00000070  6f 64 5f 6e 61 6d 65 3d  22 54 65 78 74 20 74 6f  |od_name="Text to|
00000080  20 44 72 61 77 46 69 6c  65 22 0d 00 50 05 3a 0d  | DrawFile"..P.:.|
00000090  00 5a 2f dd 20 a4 74 74  6f 64 5f 61 72 67 73 3d  |.Z/. .ttod_args=|
000000a0  22 2d 69 6e 20 54 65 78  74 20 2d 6f 75 74 20 64  |"-in Text -out d|
000000b0  72 61 77 66 69 6c 65 20  2d 73 65 6e 64 22 0d 00  |rawfile -send"..|
000000c0  64 05 3a 0d 00 6e 10 dd  20 a4 74 74 6f 64 5f 69  |d.:..n.. .ttod_i|
000000d0  6e 69 74 0d 00 78 15 c8  99 20 22 48 6f 75 72 67  |nit..x... "Hourg|
000000e0  6c 61 73 73 5f 4f 6e 22  0d 00 82 17 ea 20 66 6f  |lass_On"..... fo|
000000f0  6e 74 5f 6e 6f 25 2c 20  73 74 61 74 75 73 25 0d  |nt_no%, status%.|
00000100  00 8c 3e 74 74 6f 64 5f  69 6e 63 68 5f 73 63 61  |..>ttod_inch_sca|
00000110  6c 65 3d 31 38 30 2a 32  35 36 3a 74 74 6f 64 5f  |le=180*256:ttod_|
00000120  6d 6d 5f 73 63 61 6c 65  3d 74 74 6f 64 5f 69 6e  |mm_scale=ttod_in|
00000130  63 68 5f 73 63 61 6c 65  2f 32 35 2e 34 0d 00 96  |ch_scale/25.4...|
00000140  3f 74 74 6f 64 5f 6d 70  5f 70 65 72 5f 69 6e 63  |?ttod_mp_per_inc|
00000150  68 3d 37 32 30 30 30 3a  74 74 6f 64 5f 6d 70 5f  |h=72000:ttod_mp_|
00000160  70 65 72 5f 6d 6d 3d 74  74 6f 64 5f 6d 70 5f 70  |per_mm=ttod_mp_p|
00000170  65 72 5f 69 6e 63 68 2f  32 35 2e 34 0d 00 a0 3c  |er_inch/25.4...<|
00000180  74 74 6f 64 5f 73 63 61  6c 65 3d 74 74 6f 64 5f  |ttod_scale=ttod_|
00000190  6d 6d 5f 73 63 61 6c 65  3a 74 74 6f 64 5f 6d 69  |mm_scale:ttod_mi|
000001a0  6c 6c 69 70 6f 69 6e 74  73 3d 74 74 6f 64 5f 6d  |llipoints=ttod_m|
000001b0  70 5f 70 65 72 5f 6d 6d  0d 00 aa 51 de 20 74 74  |p_per_mm...Q. tt|
000001c0  6f 64 5f 66 6f 6e 74 5f  6e 61 6d 65 24 28 36 34  |od_font_name$(64|
000001d0  29 2c 20 74 74 6f 64 5f  66 6f 6e 74 5f 73 69 7a  |), ttod_font_siz|
000001e0  65 28 36 34 29 2c 20 74  74 6f 64 5f 77 6f 72 6b  |e(64), ttod_work|
000001f0  25 20 38 31 39 32 2c 20  74 74 6f 64 5f 65 72 72  |% 8192, ttod_err|
00000200  6f 72 5f 71 25 20 32 35  36 0d 00 b4 13 74 74 6f  |or_q% 256....tto|
00000210  64 5f 66 6f 6e 74 5f 6e  6f 25 3d 30 0d 00 be 42  |d_font_no%=0...B|
00000220  74 74 6f 64 5f 72 65 63  74 5f 61 72 67 73 24 3d  |ttod_rect_args$=|
00000230  22 66 69 72 73 74 2f 6b  2c 73 65 63 6f 6e 64 2f  |"first/k,second/|
00000240  6b 2c 77 69 64 74 68 3d  77 2f 6b 2c 66 69 6c 6c  |k,width=w/k,fill|
00000250  3d 66 2f 6b 2c 6c 69 6e  65 3d 6c 2f 6b 22 0d 00  |=f/k,line=l/k"..|
00000260  c8 36 74 74 6f 64 5f 6c  69 6e 65 5f 61 72 67 73  |.6ttod_line_args|
00000270  24 3d 22 73 74 61 72 74  2f 6b 2c 65 6e 64 2f 6b  |$="start/k,end/k|
00000280  2c 77 69 64 74 68 3d 77  2f 6b 2c 6c 69 6e 65 3d  |,width=w/k,line=|
00000290  6c 2f 6b 22 0d 00 d2 30  74 74 6f 64 5f 6c 74 65  |l/k"...0ttod_lte|
000002a0  78 74 5f 61 72 67 73 24  3d 22 78 2f 6b 2c 79 2f  |xt_args$="x/k,y/|
000002b0  6b 2c 74 65 78 74 3d 74  2f 6b 2c 70 61 74 68 3d  |k,text=t/k,path=|
000002c0  70 2f 73 22 0d 00 dc 39  74 74 6f 64 5f 63 74 65  |p/s"...9ttod_cte|
000002d0  78 74 5f 61 72 67 73 24  3d 22 66 69 72 73 74 2f  |xt_args$="first/|
000002e0  6b 2c 73 65 63 6f 6e 64  2f 6b 2c 74 65 78 74 3d  |k,second/k,text=|
000002f0  74 2f 6b 2c 70 61 74 68  3d 70 2f 73 22 0d 00 e6  |t/k,path=p/s"...|
00000300  35 74 74 6f 64 5f 66 6f  6e 74 5f 61 72 67 73 24  |5ttod_font_args$|
00000310  3d 22 6e 75 6d 62 65 72  3d 6e 6f 2f 6b 2c 6e 61  |="number=no/k,na|
00000320  6d 65 3d 6e 61 2f 6b 2c  73 69 7a 65 3d 73 7a 2f  |me=na/k,size=sz/|
00000330  6b 22 0d 00 f0 3f 74 74  6f 64 5f 73 70 72 69 74  |k"...?ttod_sprit|
00000340  65 5f 61 72 67 73 24 3d  22 66 69 6c 65 3d 66 2f  |e_args$="file=f/|
00000350  6b 2c 73 70 72 69 74 65  3d 6e 61 6d 65 2f 6b 2c  |k,sprite=name/k,|
00000360  66 69 72 73 74 2f 6b 2c  73 65 63 6f 6e 64 2f 6b  |first/k,second/k|
00000370  22 0d 00 fa 31 74 74 6f  64 5f 70 61 74 68 5f 61  |"...1ttod_path_a|
00000380  72 67 73 24 3d 22 77 69  64 74 68 3d 77 2f 6b 2c  |rgs$="width=w/k,|
00000390  66 69 6c 6c 3d 66 2f 6b  2c 6c 69 6e 65 3d 6c 2f  |fill=f/k,line=l/|
000003a0  6b 22 0d 01 04 19 74 74  6f 64 5f 6f 6e 65 5f 61  |k"....ttod_one_a|
000003b0  72 67 73 24 3d 22 74 6f  2f 6b 22 0d 01 0e 2c 74  |rgs$="to/k"...,t|
000003c0  74 6f 64 5f 74 68 72 65  65 5f 61 72 67 73 24 3d  |tod_three_args$=|
000003d0  22 74 6f 2f 6b 2c 66 69  72 73 74 2f 6b 2c 73 65  |"to/k,first/k,se|
000003e0  63 6f 6e 64 2f 6b 22 0d  01 18 51 74 74 6f 64 5f  |cond/k"...Qttod_|
000003f0  65 6c 6c 69 70 73 65 5f  61 72 67 73 24 3d 22 63  |ellipse_args$="c|
00000400  65 6e 74 72 65 3d 63 2f  6b 2c 68 6f 72 7a 3d 68  |entre=c/k,horz=h|
00000410  2f 6b 2c 76 65 72 74 3d  76 2f 6b 2c 77 69 64 74  |/k,vert=v/k,widt|
00000420  68 3d 77 2f 6b 2c 6c 69  6e 65 3d 6c 2f 6b 2c 66  |h=w/k,line=l/k,f|
00000430  69 6c 6c 3d 66 2f 6b 22  0d 01 22 19 74 74 6f 64  |ill=f/k"..".ttod|
00000440  5f 75 73 65 64 5f 68 61  6e 64 6c 65 73 24 3d 22  |_used_handles$="|
00000450  22 0d 01 2c 35 c8 99 20  22 57 69 6d 70 5f 52 65  |"..,5.. "Wimp_Re|
00000460  61 64 53 79 73 49 6e 66  6f 22 2c 37 20 b8 20 74  |adSysInfo",7 . t|
00000470  74 6f 64 5f 76 65 72 73  69 6f 6e 25 20 3b 20 73  |tod_version% ; s|
00000480  74 61 74 75 73 25 0d 01  36 29 e7 20 28 73 74 61  |tatus%..6). (sta|
00000490  74 75 73 25 20 80 20 31  29 3d 31 20 8c 20 74 74  |tus% . 1)=1 . tt|
000004a0  6f 64 5f 76 65 72 73 69  6f 6e 25 3d 32 30 30 0d  |od_version%=200.|
000004b0  01 40 18 c8 99 20 22 48  6f 75 72 67 6c 61 73 73  |.@... "Hourglass|
000004c0  5f 53 6d 61 73 68 22 0d  01 4a 06 3d 30 0d 01 54  |_Smash"..J.=0..T|
000004d0  05 3a 0d 01 5e 16 dd 20  a4 74 74 6f 64 28 69 6e  |.:..^.. .ttod(in|
000004e0  24 2c 20 6f 75 74 24 29  0d 01 68 11 74 74 6f 64  |$, out$)..h.ttod|
000004f0  5f 65 72 72 6f 72 25 3d  a3 0d 01 72 19 ea 20 69  |_error%=...r.. i|
00000500  6e 5f 66 69 6c 65 25 2c  20 6f 75 74 5f 66 69 6c  |n_file%, out_fil|
00000510  65 25 0d 01 7c 15 c8 99  20 22 48 6f 75 72 67 6c  |e%..|... "Hourgl|
00000520  61 73 73 5f 4f 6e 22 0d  01 86 13 69 6e 5f 66 69  |ass_On"....in_fi|
00000530  6c 65 25 3d 8e 28 69 6e  24 29 0d 01 90 3e e7 20  |le%=.(in$)...>. |
00000540  69 6e 5f 66 69 6c 65 25  3d 30 20 8c 20 f2 74 74  |in_file%=0 . .tt|
00000550  6f 64 5f 65 72 72 6f 72  28 22 43 61 6e 6e 6f 74  |od_error("Cannot|
00000560  20 6f 70 65 6e 20 69 6e  70 75 74 20 66 69 6c 65  | open input file|
00000570  22 2c 20 30 29 3a 3d 31  0d 01 9a 15 6f 75 74 5f  |", 0):=1....out_|
00000580  66 69 6c 65 25 3d ae 28  6f 75 74 24 29 0d 01 a4  |file%=.(out$)...|
00000590  4c e7 20 6f 75 74 5f 66  69 6c 65 25 3d 30 20 8c  |L. out_file%=0 .|
000005a0  20 f2 74 74 6f 64 5f 65  72 72 6f 72 28 22 43 61  | .ttod_error("Ca|
000005b0  6e 6e 6f 74 20 6f 70 65  6e 20 6f 75 74 70 75 74  |nnot open output|
000005c0  20 66 69 6c 65 22 2c 20  30 29 3a d9 20 23 69 6e  | file", 0):. #in|
000005d0  5f 66 69 6c 65 25 3a 3d  31 0d 01 ae 25 f2 74 74  |_file%:=1...%.tt|
000005e0  6f 64 5f 73 63 61 6e 5f  66 6f 6e 74 73 5f 6e 65  |od_scan_fonts_ne|
000005f0  65 64 65 64 28 69 6e 5f  66 69 6c 65 25 29 0d 01  |eded(in_file%)..|
00000600  b8 2f e7 20 ac 20 74 74  6f 64 5f 65 72 72 6f 72  |./. . ttod_error|
00000610  25 20 f2 74 74 6f 64 5f  73 74 61 72 74 5f 66 69  |% .ttod_start_fi|
00000620  6c 65 28 6f 75 74 5f 66  69 6c 65 25 29 0d 01 c2  |le(out_file%)...|
00000630  36 e7 20 ac 20 74 74 6f  64 5f 65 72 72 6f 72 25  |6. . ttod_error%|
00000640  20 f2 74 74 6f 64 5f 63  72 65 61 74 65 5f 66 6f  | .ttod_create_fo|
00000650  6e 74 5f 74 61 62 6c 65  28 6f 75 74 5f 66 69 6c  |nt_table(out_fil|
00000660  65 25 29 0d 01 cc 3c e7  20 ac 20 74 74 6f 64 5f  |e%)...<. . ttod_|
00000670  65 72 72 6f 72 25 20 f2  74 74 6f 64 5f 67 65 6e  |error% .ttod_gen|
00000680  65 72 61 74 65 5f 66 69  6c 65 28 69 6e 5f 66 69  |erate_file(in_fi|
00000690  6c 65 25 2c 20 6f 75 74  5f 66 69 6c 65 25 29 0d  |le%, out_file%).|
000006a0  01 d6 0e d9 23 69 6e 5f  66 69 6c 65 25 0d 01 e0  |....#in_file%...|
000006b0  0f d9 23 6f 75 74 5f 66  69 6c 65 25 0d 01 ea 18  |..#out_file%....|
000006c0  c8 99 20 22 48 6f 75 72  67 6c 61 73 73 5f 53 6d  |.. "Hourglass_Sm|
000006d0  61 73 68 22 0d 01 f4 1b  e7 20 74 74 6f 64 5f 65  |ash"..... ttod_e|
000006e0  72 72 6f 72 25 20 8c 20  3d 31 20 8b 20 3d 30 0d  |rror% . =1 . =0.|
000006f0  01 fe 05 3a 0d 02 08 24  dd 20 f2 74 74 6f 64 5f  |...:...$. .ttod_|
00000700  73 63 61 6e 5f 66 6f 6e  74 73 5f 6e 65 65 64 65  |scan_fonts_neede|
00000710  64 28 66 69 6c 65 25 29  0d 02 12 46 ea 20 69 6e  |d(file%)...F. in|
00000720  24 2c 20 6c 69 6e 65 5f  6e 6f 25 2c 20 63 6f 6d  |$, line_no%, com|
00000730  24 2c 20 70 61 72 61 6d  24 2c 20 6e 61 6d 65 24  |$, param$, name$|
00000740  2c 20 73 69 7a 65 24 2c  20 6e 6f 25 2c 20 73 74  |, size$, no%, st|
00000750  61 74 75 73 25 2c 20 68  61 6e 64 6c 65 25 0d 02  |atus%, handle%..|
00000760  1c 0d cf 23 66 69 6c 65  25 3d 30 0d 02 26 24 6c  |...#file%=0..&$l|
00000770  69 6e 65 5f 6e 6f 25 3d  30 3a 74 74 6f 64 5f 75  |ine_no%=0:ttod_u|
00000780  73 65 64 5f 68 61 6e 64  6c 65 73 24 3d 22 22 0d  |sed_handles$="".|
00000790  02 30 27 c8 95 20 28 ac  20 c5 23 69 6e 5f 66 69  |.0'.. (. .#in_fi|
000007a0  6c 65 25 29 20 80 20 28  ac 20 74 74 6f 64 5f 65  |le%) . (. ttod_e|
000007b0  72 72 6f 72 25 29 0d 02  3a 1f 20 69 6e 24 3d a4  |rror%)..:. in$=.|
000007c0  73 74 72 69 70 5f 73 70  61 63 65 73 28 be 23 66  |strip_spaces(.#f|
000007d0  69 6c 65 25 29 0d 02 44  10 20 6c 69 6e 65 5f 6e  |ile%)..D. line_n|
000007e0  6f 25 2b 3d 31 0d 02 4e  3a 20 e7 20 a4 74 74 6f  |o%+=1..N: . .tto|
000007f0  64 5f 70 61 72 73 65 28  69 6e 24 2c 20 63 6f 6d  |d_parse(in$, com|
00000800  24 2c 20 70 61 72 61 6d  24 29 20 20 80 20 28 c0  |$, param$)  . (.|
00000810  69 6e 24 2c 20 31 29 3c  3e 22 23 22 29 20 8c 0d  |in$, 1)<>"#") ..|
00000820  02 58 0f 20 20 c8 8e 20  63 6f 6d 24 20 ca 0d 02  |.X.  .. com$ ...|
00000830  62 10 20 20 20 c9 20 22  66 6f 6e 74 22 3a 0d 02  |b.   . "font":..|
00000840  6c 47 20 20 20 20 c8 99  20 26 32 30 30 34 39 2c  |lG    .. &20049,|
00000850  20 74 74 6f 64 5f 66 6f  6e 74 5f 61 72 67 73 24  | ttod_font_args$|
00000860  2c 20 70 61 72 61 6d 24  2c 20 74 74 6f 64 5f 77  |, param$, ttod_w|
00000870  6f 72 6b 25 2c 20 31 30  32 34 20 b8 20 3b 73 74  |ork%, 1024 . ;st|
00000880  61 74 75 73 25 0d 02 76  43 20 20 20 20 e7 20 28  |atus%..vC    . (|
00000890  73 74 61 74 75 73 25 20  80 20 31 29 3d 31 20 8c  |status% . 1)=1 .|
000008a0  20 f2 74 74 6f 64 5f 65  72 72 6f 72 28 22 53 79  | .ttod_error("Sy|
000008b0  6e 74 61 78 20 65 72 72  6f 72 22 2c 20 6c 69 6e  |ntax error", lin|
000008c0  65 5f 6e 6f 25 29 3a e1  0d 02 80 68 20 20 20 20  |e_no%):....h    |
000008d0  e7 20 74 74 6f 64 5f 77  6f 72 6b 25 21 30 3c 3e  |. ttod_work%!0<>|
000008e0  30 20 8c 20 6e 6f 25 3d  bb 28 a4 67 65 74 5f 73  |0 . no%=.(.get_s|
000008f0  74 72 28 74 74 6f 64 5f  77 6f 72 6b 25 21 30 29  |tr(ttod_work%!0)|
00000900  29 20 8b 20 f2 74 74 6f  64 5f 65 72 72 6f 72 28  |) . .ttod_error(|
00000910  22 46 6f 6e 74 20 6e 75  6d 62 65 72 20 6e 65 65  |"Font number nee|
00000920  64 65 64 22 2c 6c 69 6e  65 5f 6e 6f 25 29 3a e1  |ded",line_no%):.|
00000930  0d 02 8a 3c 20 20 20 20  e7 20 a4 74 74 6f 64 5f  |...<    . .ttod_|
00000940  63 68 65 63 6b 5f 66 6f  6e 74 5f 68 61 6e 64 6c  |check_font_handl|
00000950  65 28 74 74 6f 64 5f 75  73 65 64 5f 68 61 6e 64  |e(ttod_used_hand|
00000960  6c 65 73 24 2c 20 6e 6f  25 29 20 8c 0d 02 94 46  |les$, no%) ....F|
00000970  20 20 20 20 20 e7 20 74  74 6f 64 5f 77 6f 72 6b  |     . ttod_work|
00000980  25 21 34 3d 30 20 8c 20  f2 74 74 6f 64 5f 65 72  |%!4=0 . .ttod_er|
00000990  72 6f 72 28 22 46 6f 6e  74 20 6e 61 6d 65 20 6e  |ror("Font name n|
000009a0  65 65 64 65 64 22 2c 6c  69 6e 65 5f 6e 6f 25 29  |eeded",line_no%)|
000009b0  3a e1 0d 02 9e 46 20 20  20 20 20 e7 20 74 74 6f  |:....F     . tto|
000009c0  64 5f 77 6f 72 6b 25 21  38 3d 30 20 8c 20 f2 74  |d_work%!8=0 . .t|
000009d0  74 6f 64 5f 65 72 72 6f  72 28 22 46 6f 6e 74 20  |tod_error("Font |
000009e0  73 69 7a 65 20 6e 65 65  64 65 64 22 2c 6c 69 6e  |size needed",lin|
000009f0  65 5f 6e 6f 25 29 3a e1  0d 02 a8 25 20 20 20 20  |e_no%):....%    |
00000a00  20 6e 61 6d 65 24 3d a4  67 65 74 5f 73 74 72 28  | name$=.get_str(|
00000a10  74 74 6f 64 5f 77 6f 72  6b 25 21 34 29 0d 02 b2  |ttod_work%!4)...|
00000a20  39 20 20 20 20 20 c8 99  20 26 36 30 30 38 31 2c  |9     .. &60081,|
00000a30  2c 6e 61 6d 65 24 2c 20  31 36 2c 20 31 36 2c 20  |,name$, 16, 16, |
00000a40  30 2c 20 30 20 b8 20 68  61 6e 64 6c 65 25 3b 73  |0, 0 . handle%;s|
00000a50  74 61 74 75 73 25 0d 02  bc 4a 20 20 20 20 20 e7  |tatus%...J     .|
00000a60  20 28 73 74 61 74 75 73  25 20 80 20 31 29 3d 31  | (status% . 1)=1|
00000a70  20 8c 20 f2 74 74 6f 64  5f 65 72 72 6f 72 28 22  | . .ttod_error("|
00000a80  49 6e 63 6f 72 72 65 63  74 20 66 6f 6e 74 20 6e  |Incorrect font n|
00000a90  61 6d 65 22 2c 6c 69 6e  65 5f 6e 6f 25 29 3a e1  |ame",line_no%):.|
00000aa0  0d 02 c6 1b 20 20 20 20  20 c8 99 20 26 34 30 30  |....     .. &400|
00000ab0  38 32 2c 20 68 61 6e 64  6c 65 25 0d 02 d0 23 20  |82, handle%...# |
00000ac0  20 20 20 20 74 74 6f 64  5f 66 6f 6e 74 5f 6e 61  |    ttod_font_na|
00000ad0  6d 65 24 28 6e 6f 25 29  3d 6e 61 6d 65 24 0d 02  |me$(no%)=name$..|
00000ae0  da 36 20 20 20 20 20 74  74 6f 64 5f 66 6f 6e 74  |.6     ttod_font|
00000af0  5f 73 69 7a 65 28 6e 6f  25 29 3d bb 28 a4 67 65  |_size(no%)=.(.ge|
00000b00  74 5f 73 74 72 28 74 74  6f 64 5f 77 6f 72 6b 25  |t_str(ttod_work%|
00000b10  21 38 29 29 0d 02 e4 5e  20 20 20 20 20 e7 20 74  |!8))...^     . t|
00000b20  74 6f 64 5f 75 73 65 64  5f 68 61 6e 64 6c 65 73  |tod_used_handles|
00000b30  24 3c 3e 22 22 20 8c 20  74 74 6f 64 5f 75 73 65  |$<>"" . ttod_use|
00000b40  64 5f 68 61 6e 64 6c 65  73 24 2b 3d 22 20 22 2b  |d_handles$+=" "+|
00000b50  c3 28 6e 6f 25 29 20 8b  20 74 74 6f 64 5f 75 73  |.(no%) . ttod_us|
00000b60  65 64 5f 68 61 6e 64 6c  65 73 24 3d c3 28 6e 6f  |ed_handles$=.(no|
00000b70  25 29 0d 02 ee 09 20 20  20 20 cd 0d 02 f8 07 20  |%)....    ..... |
00000b80  20 cb 0d 03 02 06 20 cd  0d 03 0c 05 ce 0d 03 16  | ..... .........|
00000b90  0d cf 23 66 69 6c 65 25  3d 30 0d 03 20 05 e1 0d  |..#file%=0.. ...|
00000ba0  03 2a 05 3a 0d 03 34 1d  dd 20 f2 74 74 6f 64 5f  |.*.:..4.. .ttod_|
00000bb0  73 74 61 72 74 5f 66 69  6c 65 28 66 69 6c 65 25  |start_file(file%|
00000bc0  29 0d 03 3e 13 d5 23 66  69 6c 65 25 2c 22 44 72  |)..>..#file%,"Dr|
00000bd0  61 77 22 3b 0d 03 48 15  f2 77 70 75 74 28 66 69  |aw";..H..wput(fi|
00000be0  6c 65 25 2c 20 32 30 31  29 0d 03 52 13 f2 77 70  |le%, 201)..R..wp|
00000bf0  75 74 28 66 69 6c 65 25  2c 20 30 29 0d 03 5c 1b  |ut(file%, 0)..\.|
00000c00  d5 23 66 69 6c 65 25 2c  22 54 65 78 74 54 6f 44  |.#file%,"TextToD|
00000c10  72 61 77 20 20 22 3b 0d  03 66 13 f2 77 70 75 74  |raw  ";..f..wput|
00000c20  28 66 69 6c 65 25 2c 20  30 29 0d 03 70 13 f2 77  |(file%, 0)..p..w|
00000c30  70 75 74 28 66 69 6c 65  25 2c 20 30 29 0d 03 7a  |put(file%, 0)..z|
00000c40  20 f2 77 70 75 74 28 66  69 6c 65 25 2c 20 74 74  | .wput(file%, tt|
00000c50  6f 64 5f 73 63 61 6c 65  2a 32 31 30 29 0d 03 84  |od_scale*210)...|
00000c60  20 f2 77 70 75 74 28 66  69 6c 65 25 2c 20 74 74  | .wput(file%, tt|
00000c70  6f 64 5f 73 63 61 6c 65  2a 32 39 37 29 0d 03 8e  |od_scale*297)...|
00000c80  05 e1 0d 03 98 05 3a 0d  03 a2 24 dd 20 f2 74 74  |......:...$. .tt|
00000c90  6f 64 5f 63 72 65 61 74  65 5f 66 6f 6e 74 5f 74  |od_create_font_t|
00000ca0  61 62 6c 65 28 66 69 6c  65 25 29 0d 03 ac 28 ea  |able(file%)...(.|
00000cb0  20 75 73 65 64 24 2c 20  6c 65 6e 25 2c 20 74 6d  | used$, len%, tm|
00000cc0  70 24 2c 20 6e 6f 25 2c  20 70 61 64 25 2c 20 74  |p$, no%, pad%, t|
00000cd0  6d 70 25 0d 03 b6 23 75  73 65 64 24 3d 74 74 6f  |mp%...#used$=tto|
00000ce0  64 5f 75 73 65 64 5f 68  61 6e 64 6c 65 73 24 3a  |d_used_handles$:|
00000cf0  6c 65 6e 25 3d 30 0d 03  c0 13 f2 77 70 75 74 28  |len%=0.....wput(|
00000d00  66 69 6c 65 25 2c 20 30  29 0d 03 ca 10 74 6d 70  |file%, 0)....tmp|
00000d10  25 3d 8f 23 66 69 6c 65  25 0d 03 d4 13 f2 77 70  |%=.#file%.....wp|
00000d20  75 74 28 66 69 6c 65 25  2c 20 30 29 0d 03 de 05  |ut(file%, 0)....|
00000d30  f5 0d 03 e8 2b 20 e7 20  a4 74 74 6f 64 5f 70 61  |....+ . .ttod_pa|
00000d40  72 73 65 28 75 73 65 64  24 2c 20 74 6d 70 24 2c  |rse(used$, tmp$,|
00000d50  20 75 73 65 64 24 29 3c  3e 30 20 8c 0d 03 f2 11  | used$)<>0 .....|
00000d60  20 20 6e 6f 25 3d bb 28  74 6d 70 24 29 0d 03 fc  |  no%=.(tmp$)...|
00000d70  06 20 cc 0d 04 06 1a 20  20 6e 6f 25 3d bb 28 74  |. .....  no%=.(t|
00000d80  6d 70 24 29 3a 75 73 65  64 24 3d 22 22 0d 04 10  |mp$):used$=""...|
00000d90  06 20 cd 0d 04 1a 24 20  6c 65 6e 25 2b 3d a9 28  |. ....$ len%+=.(|
00000da0  74 74 6f 64 5f 66 6f 6e  74 5f 6e 61 6d 65 24 28  |ttod_font_name$(|
00000db0  6e 6f 25 29 29 2b 32 0d  04 24 11 20 d5 23 66 69  |no%))+2..$. .#fi|
00000dc0  6c 65 25 2c 20 6e 6f 25  0d 04 2e 28 20 d5 23 66  |le%, no%...( .#f|
00000dd0  69 6c 65 25 2c 20 74 74  6f 64 5f 66 6f 6e 74 5f  |ile%, ttod_font_|
00000de0  6e 61 6d 65 24 28 6e 6f  25 29 2b bd 28 30 29 3b  |name$(no%)+.(0);|
00000df0  0d 04 38 0e fd 20 75 73  65 64 24 3d 22 22 0d 04  |..8.. used$=""..|
00000e00  42 10 cf 23 66 69 6c 65  25 3d 74 6d 70 25 0d 04  |B..#file%=tmp%..|
00000e10  4c 30 74 6d 70 25 3d 6c  65 6e 25 3a 6c 65 6e 25  |L0tmp%=len%:len%|
00000e20  3d 28 6c 65 6e 25 2b 33  29 20 80 20 ac 20 33 3a  |=(len%+3) . . 3:|
00000e30  70 61 64 25 3d 6c 65 6e  25 2d 74 6d 70 25 0d 04  |pad%=len%-tmp%..|
00000e40  56 18 f2 77 70 75 74 28  66 69 6c 65 25 2c 20 6c  |V..wput(file%, l|
00000e50  65 6e 25 2b 38 29 0d 04  60 13 cf 23 66 69 6c 65  |en%+8)..`..#file|
00000e60  25 3d a2 23 66 69 6c 65  25 0d 04 6a 2f e7 20 70  |%=.#file%..j/. p|
00000e70  61 64 25 3c 3e 30 20 8c  20 e3 20 6e 6f 25 3d 31  |ad%<>0 . . no%=1|
00000e80  20 b8 20 70 61 64 25 3a  d5 23 66 69 6c 65 25 2c  | . pad%:.#file%,|
00000e90  20 30 3a ed 20 6e 6f 25  0d 04 74 05 e1 0d 04 7e  | 0:. no%..t....~|
00000ea0  05 3a 0d 04 88 2e dd 20  f2 74 74 6f 64 5f 67 65  |.:..... .ttod_ge|
00000eb0  6e 65 72 61 74 65 5f 66  69 6c 65 28 69 6e 5f 66  |nerate_file(in_f|
00000ec0  69 6c 65 25 2c 20 6f 75  74 5f 66 69 6c 65 25 29  |ile%, out_file%)|
00000ed0  0d 04 92 53 ea 20 69 6e  24 2c 20 63 6f 6d 24 2c  |...S. in$, com$,|
00000ee0  20 70 61 72 61 6d 24 2c  20 6c 69 6e 65 5f 6e 6f  | param$, line_no|
00000ef0  25 2c 20 6e 6f 25 2c 20  66 6f 6e 74 5f 68 61 6e  |%, no%, font_han|
00000f00  64 6c 65 25 2c 20 72 65  61 6c 5f 68 61 6e 64 6c  |dle%, real_handl|
00000f10  65 25 2c 20 66 69 72 73  74 25 2c 20 73 74 61 74  |e%, first%, stat|
00000f20  75 73 25 0d 04 9c 17 6c  69 6e 65 5f 6e 6f 25 3d  |us%....line_no%=|
00000f30  30 3a 66 69 72 73 74 25  3d b9 0d 04 a6 27 c8 95  |0:first%=....'..|
00000f40  20 28 ac 20 c5 23 69 6e  5f 66 69 6c 65 25 29 20  | (. .#in_file%) |
00000f50  80 20 28 ac 20 74 74 6f  64 5f 65 72 72 6f 72 25  |. (. ttod_error%|
00000f60  29 0d 04 b0 22 20 69 6e  24 3d a4 73 74 72 69 70  |)..." in$=.strip|
00000f70  5f 73 70 61 63 65 73 28  be 23 69 6e 5f 66 69 6c  |_spaces(.#in_fil|
00000f80  65 25 29 0d 04 ba 10 20  6c 69 6e 65 5f 6e 6f 25  |e%).... line_no%|
00000f90  2b 3d 31 0d 04 c4 27 20  e7 20 a4 74 74 6f 64 5f  |+=1...' . .ttod_|
00000fa0  70 61 72 73 65 28 69 6e  24 2c 20 63 6f 6d 24 2c  |parse(in$, com$,|
00000fb0  20 70 61 72 61 6d 24 29  20 8c 0d 04 ce 0f 20 20  | param$) .....  |
00000fc0  c8 8e 20 63 6f 6d 24 20  ca 0d 04 d8 12 20 20 20  |.. com$ .....   |
00000fd0  c9 20 22 6c 74 65 78 74  22 20 3a 0d 04 e2 47 20  |. "ltext" :...G |
00000fe0  20 20 20 f2 74 74 6f 64  5f 67 65 6e 65 72 61 74  |   .ttod_generat|
00000ff0  65 5f 6c 74 65 78 74 28  6f 75 74 5f 66 69 6c 65  |e_ltext(out_file|
00001000  25 2c 20 66 6f 6e 74 5f  68 61 6e 64 6c 65 25 2c  |%, font_handle%,|
00001010  20 70 61 72 61 6d 24 2c  20 6c 69 6e 65 5f 6e 6f  | param$, line_no|
00001020  25 29 0d 04 ec 12 20 20  20 c9 20 22 63 74 65 78  |%)....   . "ctex|
00001030  74 22 20 3a 0d 04 f6 47  20 20 20 20 f2 74 74 6f  |t" :...G    .tto|
00001040  64 5f 67 65 6e 65 72 61  74 65 5f 63 74 65 78 74  |d_generate_ctext|
00001050  28 6f 75 74 5f 66 69 6c  65 25 2c 20 66 6f 6e 74  |(out_file%, font|
00001060  5f 68 61 6e 64 6c 65 25  2c 20 70 61 72 61 6d 24  |_handle%, param$|
00001070  2c 20 6c 69 6e 65 5f 6e  6f 25 29 0d 05 00 11 20  |, line_no%).... |
00001080  20 20 c9 20 22 66 6f 6e  74 22 20 3a 0d 05 0a 47  |  . "font" :...G|
00001090  20 20 20 20 c8 99 20 26  32 30 30 34 39 2c 20 74  |    .. &20049, t|
000010a0  74 6f 64 5f 66 6f 6e 74  5f 61 72 67 73 24 2c 20  |tod_font_args$, |
000010b0  70 61 72 61 6d 24 2c 20  74 74 6f 64 5f 77 6f 72  |param$, ttod_wor|
000010c0  6b 25 2c 20 31 30 32 34  20 b8 20 3b 73 74 61 74  |k%, 1024 . ;stat|
000010d0  75 73 25 0d 05 14 43 20  20 20 20 e7 20 28 73 74  |us%...C    . (st|
000010e0  61 74 75 73 25 20 80 20  31 29 3d 31 20 8c 20 f2  |atus% . 1)=1 . .|
000010f0  74 74 6f 64 5f 65 72 72  6f 72 28 22 53 79 6e 74  |ttod_error("Synt|
00001100  61 78 20 65 72 72 6f 72  22 2c 20 6c 69 6e 65 5f  |ax error", line_|
00001110  6e 6f 25 29 3a e1 0d 05  1e 25 20 20 20 20 6e 6f  |no%):....%    no|
00001120  25 3d bb 28 a4 67 65 74  5f 73 74 72 28 74 74 6f  |%=.(.get_str(tto|
00001130  64 5f 77 6f 72 6b 25 21  30 29 29 0d 05 28 4a 20  |d_work%!0))..(J |
00001140  20 20 20 e7 20 6e 6f 25  3c 31 20 84 20 6e 6f 25  |   . no%<1 . no%|
00001150  3e 36 34 20 8c 20 f2 74  74 6f 64 5f 65 72 72 6f  |>64 . .ttod_erro|
00001160  72 28 22 49 6e 63 6f 72  72 65 63 74 20 66 6f 6e  |r("Incorrect fon|
00001170  74 20 6e 75 6d 62 65 72  22 2c 6c 69 6e 65 5f 6e  |t number",line_n|
00001180  6f 25 29 3a e1 0d 05 32  3f 20 20 20 20 e7 20 28  |o%):...2?    . (|
00001190  ac 20 a4 74 74 6f 64 5f  63 68 65 63 6b 5f 66 6f  |. .ttod_check_fo|
000011a0  6e 74 5f 68 61 6e 64 6c  65 28 74 74 6f 64 5f 75  |nt_handle(ttod_u|
000011b0  73 65 64 5f 68 61 6e 64  6c 65 73 24 2c 6e 6f 25  |sed_handles$,no%|
000011c0  29 29 20 8c 0d 05 3c 19  20 20 20 20 20 66 6f 6e  |)) ...<.     fon|
000011d0  74 5f 68 61 6e 64 6c 65  25 3d 6e 6f 25 0d 05 46  |t_handle%=no%..F|
000011e0  09 20 20 20 20 cc 0d 05  50 68 20 20 20 20 20 f2  |.    ...Ph     .|
000011f0  74 74 6f 64 5f 65 72 72  6f 72 28 22 53 45 52 49  |ttod_error("SERI|
00001200  4f 55 53 20 49 4e 54 45  52 4e 4c 20 45 52 52 4f  |OUS INTERNL ERRO|
00001210  52 20 3a 20 49 27 76 65  20 6c 6f 73 74 20 74 72  |R : I've lost tr|
00001220  61 63 6b 20 6f 66 20 61  20 66 6f 6e 74 20 68 61  |ack of a font ha|
00001230  6e 64 6c 65 20 28 22 2b  6e 6f 24 2b 22 29 21 21  |ndle ("+no$+")!!|
00001240  22 2c 20 6c 69 6e 65 5f  6e 6f 25 29 3a e1 0d 05  |", line_no%):...|
00001250  5a 09 20 20 20 20 cd 0d  05 64 35 20 20 20 20 e7  |Z.    ...d5    .|
00001260  20 66 69 72 73 74 25 20  8c 20 66 69 72 73 74 25  | first% . first%|
00001270  3d a3 20 8b 20 c8 99 20  26 34 30 30 38 32 2c 20  |=. . .. &40082, |
00001280  72 65 61 6c 5f 68 61 6e  64 6c 65 25 0d 05 6e 75  |real_handle%..nu|
00001290  20 20 20 20 c8 99 20 26  34 30 30 38 31 2c 2c 74  |    .. &40081,,t|
000012a0  74 6f 64 5f 66 6f 6e 74  5f 6e 61 6d 65 24 28 66  |tod_font_name$(f|
000012b0  6f 6e 74 5f 68 61 6e 64  6c 65 25 29 2c 20 74 74  |ont_handle%), tt|
000012c0  6f 64 5f 66 6f 6e 74 5f  73 69 7a 65 28 6e 6f 25  |od_font_size(no%|
000012d0  29 2a 31 36 2c 20 74 74  6f 64 5f 66 6f 6e 74 5f  |)*16, ttod_font_|
000012e0  73 69 7a 65 28 6e 6f 25  29 2a 31 36 2c 20 30 2c  |size(no%)*16, 0,|
000012f0  20 30 20 b8 20 72 65 61  6c 5f 68 61 6e 64 6c 65  | 0 . real_handle|
00001300  25 0d 05 78 11 20 20 20  c9 20 22 6c 69 6e 65 22  |%..x.   . "line"|
00001310  20 3a 0d 05 82 38 20 20  20 20 f2 74 74 6f 64 5f  | :...8    .ttod_|
00001320  67 65 6e 65 72 61 74 65  5f 6c 69 6e 65 28 6f 75  |generate_line(ou|
00001330  74 5f 66 69 6c 65 25 2c  20 70 61 72 61 6d 24 2c  |t_file%, param$,|
00001340  20 6c 69 6e 65 5f 6e 6f  25 29 0d 05 8c 12 20 20  | line_no%)....  |
00001350  20 c9 20 22 75 6e 69 74  73 22 20 3a 0d 05 96 18  | . "units" :....|
00001360  20 20 20 20 c8 8e 20 a4  6c 63 28 70 61 72 61 6d  |    .. .lc(param|
00001370  24 29 20 ca 0d 05 a0 50  20 20 20 20 20 c9 20 22  |$) ....P     . "|
00001380  69 6e 63 68 22 20 3a 20  74 74 6f 64 5f 73 63 61  |inch" : ttod_sca|
00001390  6c 65 3d 74 74 6f 64 5f  69 6e 63 68 5f 73 63 61  |le=ttod_inch_sca|
000013a0  6c 65 3a 74 74 6f 64 5f  6d 69 6c 6c 69 70 6f 69  |le:ttod_millipoi|
000013b0  6e 74 73 3d 74 74 6f 64  5f 6d 70 5f 70 65 72 5f  |nts=ttod_mp_per_|
000013c0  69 6e 63 68 0d 05 aa 4a  20 20 20 20 20 c9 20 22  |inch...J     . "|
000013d0  6d 6d 22 20 3a 20 74 74  6f 64 5f 73 63 61 6c 65  |mm" : ttod_scale|
000013e0  3d 74 74 6f 64 5f 6d 6d  5f 73 63 61 6c 65 3a 74  |=ttod_mm_scale:t|
000013f0  74 6f 64 5f 6d 69 6c 6c  69 70 6f 69 6e 74 73 3d  |tod_millipoints=|
00001400  74 74 6f 64 5f 6d 70 5f  70 65 72 5f 6d 6d 0d 05  |ttod_mp_per_mm..|
00001410  b4 53 20 20 20 20 20 7f  20 3a 20 f2 74 74 6f 64  |.S     . : .ttod|
00001420  5f 65 72 72 6f 72 28 22  49 6c 6c 65 67 61 6c 20  |_error("Illegal |
00001430  6d 65 61 73 75 72 65 6d  65 6e 74 20 73 63 61 6c  |measurement scal|
00001440  65 20 69 6e 20 27 75 6e  69 74 73 27 20 63 6f 6d  |e in 'units' com|
00001450  6d 61 6e 64 22 2c 6c 69  6e 65 5f 6e 6f 25 29 3a  |mand",line_no%):|
00001460  e1 0d 05 be 09 20 20 20  20 cb 0d 05 c8 16 20 20  |.....    .....  |
00001470  20 c9 20 22 72 65 63 74  61 6e 67 6c 65 22 20 3a  | . "rectangle" :|
00001480  0d 05 d2 37 20 20 20 20  f2 74 74 6f 64 5f 67 65  |...7    .ttod_ge|
00001490  6e 65 72 61 74 65 5f 62  6f 78 28 6f 75 74 5f 66  |nerate_box(out_f|
000014a0  69 6c 65 25 2c 20 70 61  72 61 6d 24 2c 20 6c 69  |ile%, param$, li|
000014b0  6e 65 5f 6e 6f 25 29 0d  05 dc 13 20 20 20 c9 20  |ne_no%)....   . |
000014c0  22 73 70 72 69 74 65 22  20 3a 0d 05 e6 39 20 20  |"sprite" :...9  |
000014d0  20 20 f2 74 74 6f 64 5f  69 6e 63 6c 75 64 65 5f  |  .ttod_include_|
000014e0  73 70 72 69 74 65 28 6f  75 74 5f 66 69 6c 65 25  |sprite(out_file%|
000014f0  2c 20 70 61 72 61 6d 24  2c 20 6c 69 6e 65 5f 6e  |, param$, line_n|
00001500  6f 25 29 0d 05 f0 11 20  20 20 c9 20 22 70 61 74  |o%)....   . "pat|
00001510  68 22 20 3a 0d 05 fa 42  20 20 20 20 f2 74 74 6f  |h" :...B    .tto|
00001520  64 5f 67 65 6e 65 72 61  74 65 5f 70 61 74 68 28  |d_generate_path(|
00001530  69 6e 5f 66 69 6c 65 25  2c 20 6f 75 74 5f 66 69  |in_file%, out_fi|
00001540  6c 65 25 2c 20 70 61 72  61 6d 24 2c 20 6c 69 6e  |le%, param$, lin|
00001550  65 5f 6e 6f 25 29 0d 06  04 14 20 20 20 c9 20 22  |e_no%)....   . "|
00001560  65 6c 6c 69 70 73 65 22  20 3a 0d 06 0e 38 20 20  |ellipse" :...8  |
00001570  20 20 f2 74 74 6f 64 5f  67 65 6e 65 72 61 74 65  |  .ttod_generate|
00001580  5f 6f 76 61 6c 28 6f 75  74 5f 66 69 6c 65 25 2c  |_oval(out_file%,|
00001590  20 70 61 72 61 6d 24 2c  20 6c 69 6e 65 5f 6e 6f  | param$, line_no|
000015a0  25 29 0d 06 18 45 20 20  7f 3a 20 e7 20 28 c0 63  |%)...E  .: . (.c|
000015b0  6f 6d 24 2c 20 31 29 3c  3e 22 23 22 29 20 8c 20  |om$, 1)<>"#") . |
000015c0  f2 74 74 6f 64 5f 65 72  72 6f 72 28 22 55 6e 6b  |.ttod_error("Unk|
000015d0  6e 6f 77 6e 20 63 6f 6d  6d 61 6e 64 22 2c 6c 69  |nown command",li|
000015e0  6e 65 5f 6e 6f 25 29 0d  06 22 07 20 20 cb 0d 06  |ne_no%)..".  ...|
000015f0  2c 06 20 cd 0d 06 36 05  ce 0d 06 40 28 e7 20 ac  |,. ...6....@(. .|
00001600  20 66 69 72 73 74 25 20  8c 20 c8 99 20 26 34 30  | first% . .. &40|
00001610  30 38 32 2c 20 72 65 61  6c 5f 68 61 6e 64 6c 65  |082, real_handle|
00001620  25 0d 06 4a 05 e1 0d 06  54 05 3a 0d 06 5e 39 dd  |%..J....T.:..^9.|
00001630  20 f2 74 74 6f 64 5f 67  65 6e 65 72 61 74 65 5f  | .ttod_generate_|
00001640  6c 74 65 78 74 28 66 69  6c 65 25 2c 20 68 61 6e  |ltext(file%, han|
00001650  64 6c 65 25 2c 20 70 61  72 61 6d 24 2c 20 6c 69  |dle%, param$, li|
00001660  6e 65 25 29 0d 06 68 40  ea 20 78 2c 20 79 2c 20  |ne%)..h@. x, y, |
00001670  74 65 78 74 24 2c 20 62  6f 75 6e 64 5f 78 2c 20  |text$, bound_x, |
00001680  62 6f 75 6e 64 5f 79 2c  20 6c 65 6e 25 2c 20 73  |bound_y, len%, s|
00001690  74 61 74 75 73 25 2c 20  70 61 74 68 25 2c 20 6e  |tatus%, path%, n|
000016a0  65 65 64 25 0d 06 72 44  c8 99 20 26 32 30 30 34  |eed%..rD.. &2004|
000016b0  39 2c 20 74 74 6f 64 5f  6c 74 65 78 74 5f 61 72  |9, ttod_ltext_ar|
000016c0  67 73 24 2c 20 70 61 72  61 6d 24 2c 20 74 74 6f  |gs$, param$, tto|
000016d0  64 5f 77 6f 72 6b 25 2c  20 31 30 32 34 20 b8 20  |d_work%, 1024 . |
000016e0  3b 73 74 61 74 75 73 25  0d 06 7c 3b e7 20 28 73  |;status%..|;. (s|
000016f0  74 61 74 75 73 25 20 80  20 31 29 3d 31 20 8c 20  |tatus% . 1)=1 . |
00001700  f2 74 74 6f 64 5f 65 72  72 6f 72 28 22 53 79 6e  |.ttod_error("Syn|
00001710  74 61 78 20 65 72 72 6f  72 22 2c 6c 69 6e 65 25  |tax error",line%|
00001720  29 3a e1 0d 06 86 60 e7  20 74 74 6f 64 5f 77 6f  |):....`. ttod_wo|
00001730  72 6b 25 21 30 3d 30 20  8c 20 f2 74 74 6f 64 5f  |rk%!0=0 . .ttod_|
00001740  65 72 72 6f 72 28 22 4d  69 73 73 69 6e 67 20 78  |error("Missing x|
00001750  20 70 6f 73 69 74 69 6f  6e 20 64 65 66 69 6e 69  | position defini|
00001760  74 69 6f 6e 20 66 72 6f  6d 20 27 6c 74 65 78 74  |tion from 'ltext|
00001770  27 20 63 6f 6d 6d 61 6e  64 22 2c 6c 69 6e 65 25  |' command",line%|
00001780  29 3a e1 0d 06 90 60 e7  20 74 74 6f 64 5f 77 6f  |):....`. ttod_wo|
00001790  72 6b 25 21 34 3d 30 20  8c 20 f2 74 74 6f 64 5f  |rk%!4=0 . .ttod_|
000017a0  65 72 72 6f 72 28 22 4d  69 73 73 69 6e 67 20 79  |error("Missing y|
000017b0  20 70 6f 73 69 74 69 6f  6e 20 64 65 66 69 6e 69  | position defini|
000017c0  74 69 6f 6e 20 66 72 6f  6d 20 27 6c 74 65 78 74  |tion from 'ltext|
000017d0  27 20 63 6f 6d 6d 61 6e  64 22 2c 6c 69 6e 65 25  |' command",line%|
000017e0  29 3a e1 0d 06 9a 5b e7  20 74 74 6f 64 5f 77 6f  |):....[. ttod_wo|
000017f0  72 6b 25 21 38 3d 30 20  8c 20 f2 74 74 6f 64 5f  |rk%!8=0 . .ttod_|
00001800  65 72 72 6f 72 28 22 4d  69 73 73 69 6e 67 20 74  |error("Missing t|
00001810  65 78 74 20 69 6e 66 6f  72 6d 61 74 69 6f 6e 20  |ext information |
00001820  66 72 6f 6d 20 27 6c 74  65 78 74 27 20 63 6f 6d  |from 'ltext' com|
00001830  6d 61 6e 64 22 2c 6c 69  6e 65 25 29 3a e1 0d 06  |mand",line%):...|
00001840  a4 56 78 3d bb 28 a4 67  65 74 5f 73 74 72 28 74  |.Vx=.(.get_str(t|
00001850  74 6f 64 5f 77 6f 72 6b  25 21 30 29 29 3a 79 3d  |tod_work%!0)):y=|
00001860  bb 28 a4 67 65 74 5f 73  74 72 28 74 74 6f 64 5f  |.(.get_str(ttod_|
00001870  77 6f 72 6b 25 21 34 29  29 3a 70 61 74 68 25 3d  |work%!4)):path%=|
00001880  28 28 74 74 6f 64 5f 77  6f 72 6b 25 21 31 32 29  |((ttod_work%!12)|
00001890  3c 3e 30 29 0d 06 ae 20  74 65 78 74 24 3d a4 67  |<>0)... text$=.g|
000018a0  65 74 5f 73 74 72 28 74  74 6f 64 5f 77 6f 72 6b  |et_str(ttod_work|
000018b0  25 21 38 29 0d 06 b8 0d  e7 20 70 61 74 68 25 20  |%!8)..... path% |
000018c0  8c 0d 06 c2 2e 20 78 3d  78 2a 74 74 6f 64 5f 6d  |..... x=x*ttod_m|
000018d0  69 6c 6c 69 70 6f 69 6e  74 73 3a 79 3d 79 2a 74  |illipoints:y=y*t|
000018e0  74 6f 64 5f 6d 69 6c 6c  69 70 6f 69 6e 74 73 0d  |tod_millipoints.|
000018f0  06 cc 13 20 c8 99 20 26  34 30 30 39 45 2c 25 31  |... .. &4009E,%1|
00001900  2c 38 0d 06 d6 27 20 c8  99 20 26 34 30 30 38 36  |,8...' .. &40086|
00001910  2c 30 2c 74 65 78 74 24  2c 25 30 31 31 30 30 30  |,0,text$,%011000|
00001920  30 30 30 30 30 2c 78 2c  79 0d 06 e0 1b 20 c8 99  |00000,x,y.... ..|
00001930  20 26 34 30 30 39 45 2c  30 2c 30 20 b8 20 2c 6e  | &4009E,0,0 . ,n|
00001940  65 65 64 25 0d 06 ea 4b  20 e7 20 6e 65 65 64 25  |eed%...K . need%|
00001950  3e 3d 38 31 38 34 20 8c  20 f2 74 74 6f 64 5f 65  |>=8184 . .ttod_e|
00001960  72 72 6f 72 28 22 54 65  78 74 20 70 61 74 68 20  |rror("Text path |
00001970  74 6f 6f 20 62 69 67 20  66 6f 72 20 62 75 66 66  |too big for buff|
00001980  65 72 21 21 22 2c 20 6c  69 6e 65 25 29 3a e1 0d  |er!!", line%):..|
00001990  06 f4 23 20 21 74 74 6f  64 5f 77 6f 72 6b 25 3d  |..# !ttod_work%=|
000019a0  30 3a 21 74 74 6f 64 5f  77 6f 72 6b 25 3d 38 31  |0:!ttod_work%=81|
000019b0  38 34 0d 06 fe 20 20 c8  99 20 26 34 30 30 39 45  |84...  .. &4009E|
000019c0  2c 25 31 30 30 31 30 2c  74 74 6f 64 5f 77 6f 72  |,%10010,ttod_wor|
000019d0  6b 25 0d 07 08 27 20 c8  99 20 26 34 30 30 38 36  |k%...' .. &40086|
000019e0  2c 30 2c 74 65 78 74 24  2c 25 30 31 31 30 30 30  |,0,text$,%011000|
000019f0  30 30 30 30 30 2c 78 2c  79 0d 07 12 1b 20 c8 99  |00000,x,y.... ..|
00001a00  20 26 34 30 30 39 45 2c  30 2c 30 20 b8 20 2c 6e  | &4009E,0,0 . ,n|
00001a10  65 65 64 25 0d 07 1c 35  20 c8 99 20 22 4f 53 5f  |eed%...5 .. "OS_|
00001a20  47 42 50 42 22 2c 32 2c  66 69 6c 65 25 2c 74 74  |GBPB",2,file%,tt|
00001a30  6f 64 5f 77 6f 72 6b 25  2c 6e 65 65 64 25 2d 74  |od_work%,need%-t|
00001a40  74 6f 64 5f 77 6f 72 6b  25 0d 07 26 05 cc 0d 07  |tod_work%..&....|
00001a50  30 2c 20 c8 99 20 26 34  30 30 39 37 2c 2c 74 65  |0, .. &40097,,te|
00001a60  78 74 24 20 b8 20 2c 2c  2c 20 62 6f 75 6e 64 5f  |xt$ . ,,, bound_|
00001a70  78 2c 20 62 6f 75 6e 64  5f 79 0d 07 3a 30 20 62  |x, bound_y..:0 b|
00001a80  6f 75 6e 64 5f 78 3d 62  6f 75 6e 64 5f 78 2f 74  |ound_x=bound_x/t|
00001a90  74 6f 64 5f 6d 69 6c 6c  69 70 6f 69 6e 74 73 2a  |tod_millipoints*|
00001aa0  74 74 6f 64 5f 73 63 61  6c 65 0d 07 44 30 20 62  |ttod_scale..D0 b|
00001ab0  6f 75 6e 64 5f 79 3d 62  6f 75 6e 64 5f 79 2f 74  |ound_y=bound_y/t|
00001ac0  74 6f 64 5f 6d 69 6c 6c  69 70 6f 69 6e 74 73 2a  |tod_millipoints*|
00001ad0  74 74 6f 64 5f 73 63 61  6c 65 0d 07 4e 22 20 78  |ttod_scale..N" x|
00001ae0  3d 78 2a 74 74 6f 64 5f  73 63 61 6c 65 3a 79 3d  |=x*ttod_scale:y=|
00001af0  79 2a 74 74 6f 64 5f 73  63 61 6c 65 0d 07 58 1e  |y*ttod_scale..X.|
00001b00  20 6c 65 6e 25 3d 28 a9  28 74 65 78 74 24 29 2b  | len%=(.(text$)+|
00001b10  31 2b 33 29 20 80 20 ac  20 33 0d 07 62 46 20 f2  |1+3) . . 3..bF .|
00001b20  74 74 6f 64 5f 70 75 74  5f 68 65 61 64 28 66 69  |ttod_put_head(fi|
00001b30  6c 65 25 2c 20 31 2c 20  35 32 2b 6c 65 6e 25 2c  |le%, 1, 52+len%,|
00001b40  20 78 2c 20 79 2c 20 62  6f 75 6e 64 5f 78 2b 31  | x, y, bound_x+1|
00001b50  2b 78 2c 20 62 6f 75 6e  64 5f 79 2b 31 2b 79 29  |+x, bound_y+1+y)|
00001b60  0d 07 6c 14 20 f2 77 70  75 74 28 66 69 6c 65 25  |..l. .wput(file%|
00001b70  2c 20 30 29 0d 07 76 1c  20 f2 77 70 75 74 28 66  |, 0)..v. .wput(f|
00001b80  69 6c 65 25 2c 20 26 46  46 46 46 46 46 30 30 29  |ile%, &FFFFFF00)|
00001b90  0d 07 80 1a 20 f2 77 70  75 74 28 66 69 6c 65 25  |.... .wput(file%|
00001ba0  2c 20 68 61 6e 64 6c 65  25 29 0d 07 8a 2e 20 f2  |, handle%).... .|
00001bb0  77 70 75 74 28 66 69 6c  65 25 2c 20 74 74 6f 64  |wput(file%, ttod|
00001bc0  5f 66 6f 6e 74 5f 73 69  7a 65 28 68 61 6e 64 6c  |_font_size(handl|
00001bd0  65 25 29 2a 36 34 30 29  0d 07 94 2e 20 f2 77 70  |e%)*640).... .wp|
00001be0  75 74 28 66 69 6c 65 25  2c 20 74 74 6f 64 5f 66  |ut(file%, ttod_f|
00001bf0  6f 6e 74 5f 73 69 7a 65  28 68 61 6e 64 6c 65 25  |ont_size(handle%|
00001c00  29 2a 36 34 30 29 0d 07  9e 14 20 f2 77 70 75 74  |)*640).... .wput|
00001c10  28 66 69 6c 65 25 2c 20  78 29 0d 07 a8 14 20 f2  |(file%, x).... .|
00001c20  77 70 75 74 28 66 69 6c  65 25 2c 20 79 29 0d 07  |wput(file%, y)..|
00001c30  b2 34 20 f2 74 74 6f 64  5f 70 75 74 5f 70 61 64  |.4 .ttod_put_pad|
00001c40  64 65 64 28 66 69 6c 65  25 2c 20 6c 65 6e 25 2c  |ded(file%, len%,|
00001c50  20 74 65 78 74 24 2b bd  28 30 29 2c 20 bd 28 30  | text$+.(0), .(0|
00001c60  29 29 0d 07 bc 05 cd 0d  07 c6 05 e1 0d 07 d0 05  |))..............|
00001c70  3a 0d 07 da 39 dd 20 f2  74 74 6f 64 5f 67 65 6e  |:...9. .ttod_gen|
00001c80  65 72 61 74 65 5f 63 74  65 78 74 28 66 69 6c 65  |erate_ctext(file|
00001c90  25 2c 20 68 61 6e 64 6c  65 25 2c 20 70 61 72 61  |%, handle%, para|
00001ca0  6d 24 2c 20 6c 69 6e 65  25 29 0d 07 e4 61 ea 20  |m$, line%)...a. |
00001cb0  78 31 2c 20 79 31 2c 20  78 32 2c 20 79 32 2c 20  |x1, y1, x2, y2, |
00001cc0  78 5f 6c 6f 77 2c 20 79  5f 6c 6f 77 2c 20 78 5f  |x_low, y_low, x_|
00001cd0  68 69 67 68 2c 20 79 5f  68 69 67 68 2c 20 74 65  |high, y_high, te|
00001ce0  78 74 24 2c 20 62 6f 75  6e 64 5f 78 2c 20 62 6f  |xt$, bound_x, bo|
00001cf0  75 6e 64 5f 79 2c 20 6c  65 6e 25 2c 20 73 74 61  |und_y, len%, sta|
00001d00  74 75 73 25 2c 20 70 61  74 68 25 0d 07 ee 44 c8  |tus%, path%...D.|
00001d10  99 20 26 32 30 30 34 39  2c 20 74 74 6f 64 5f 63  |. &20049, ttod_c|
00001d20  74 65 78 74 5f 61 72 67  73 24 2c 20 70 61 72 61  |text_args$, para|
00001d30  6d 24 2c 20 74 74 6f 64  5f 77 6f 72 6b 25 2c 20  |m$, ttod_work%, |
00001d40  31 30 32 34 20 b8 20 3b  73 74 61 74 75 73 25 0d  |1024 . ;status%.|
00001d50  07 f8 3b e7 20 28 73 74  61 74 75 73 25 20 80 20  |..;. (status% . |
00001d60  31 29 3d 31 20 8c 20 f2  74 74 6f 64 5f 65 72 72  |1)=1 . .ttod_err|
00001d70  6f 72 28 22 53 79 6e 74  61 78 20 65 72 72 6f 72  |or("Syntax error|
00001d80  22 2c 6c 69 6e 65 25 29  3a e1 0d 08 02 64 e7 20  |",line%):....d. |
00001d90  74 74 6f 64 5f 77 6f 72  6b 25 21 30 3d 30 20 8c  |ttod_work%!0=0 .|
00001da0  20 f2 74 74 6f 64 5f 65  72 72 6f 72 28 22 4d 69  | .ttod_error("Mi|
00001db0  73 73 69 6e 67 20 66 69  72 73 74 20 70 6f 73 69  |ssing first posi|
00001dc0  74 69 6f 6e 20 64 65 66  69 6e 69 74 69 6f 6e 20  |tion definition |
00001dd0  66 72 6f 6d 20 27 63 74  65 78 74 27 20 63 6f 6d  |from 'ctext' com|
00001de0  6d 61 6e 64 22 2c 6c 69  6e 65 25 29 3a e1 0d 08  |mand",line%):...|
00001df0  0c 65 e7 20 74 74 6f 64  5f 77 6f 72 6b 25 21 34  |.e. ttod_work%!4|
00001e00  3d 30 20 8c 20 f2 74 74  6f 64 5f 65 72 72 6f 72  |=0 . .ttod_error|
00001e10  28 22 4d 69 73 73 69 6e  67 20 73 65 63 6f 6e 64  |("Missing second|
00001e20  20 70 6f 73 69 74 69 6f  6e 20 64 65 66 69 6e 69  | position defini|
00001e30  74 69 6f 6e 20 66 72 6f  6d 20 27 63 74 65 78 74  |tion from 'ctext|
00001e40  27 20 63 6f 6d 6d 61 6e  64 22 2c 6c 69 6e 65 25  |' command",line%|
00001e50  29 3a e1 0d 08 16 5b e7  20 74 74 6f 64 5f 77 6f  |):....[. ttod_wo|
00001e60  72 6b 25 21 38 3d 30 20  8c 20 f2 74 74 6f 64 5f  |rk%!8=0 . .ttod_|
00001e70  65 72 72 6f 72 28 22 4d  69 73 73 69 6e 67 20 74  |error("Missing t|
00001e80  65 78 74 20 69 6e 66 6f  72 6d 61 74 69 6f 6e 20  |ext information |
00001e90  66 72 6f 6d 20 27 63 74  65 78 74 27 20 63 6f 6d  |from 'ctext' com|
00001ea0  6d 61 6e 64 22 2c 6c 69  6e 65 25 29 3a e1 0d 08  |mand",line%):...|
00001eb0  20 30 f2 74 74 6f 64 5f  67 65 74 5f 78 79 28 a4  | 0.ttod_get_xy(.|
00001ec0  67 65 74 5f 73 74 72 28  74 74 6f 64 5f 77 6f 72  |get_str(ttod_wor|
00001ed0  6b 25 21 30 29 2c 20 78  31 2c 20 79 31 29 0d 08  |k%!0), x1, y1)..|
00001ee0  2a 30 f2 74 74 6f 64 5f  67 65 74 5f 78 79 28 a4  |*0.ttod_get_xy(.|
00001ef0  67 65 74 5f 73 74 72 28  74 74 6f 64 5f 77 6f 72  |get_str(ttod_wor|
00001f00  6b 25 21 34 29 2c 20 78  32 2c 20 79 32 29 0d 08  |k%!4), x2, y2)..|
00001f10  34 3b 74 65 78 74 24 3d  a4 67 65 74 5f 73 74 72  |4;text$=.get_str|
00001f20  28 74 74 6f 64 5f 77 6f  72 6b 25 21 38 29 3a 70  |(ttod_work%!8):p|
00001f30  61 74 68 25 3d 28 28 74  74 6f 64 5f 77 6f 72 6b  |ath%=((ttod_work|
00001f40  25 21 31 32 29 3c 3e 30  29 0d 08 3e 25 78 31 3d  |%!12)<>0)..>%x1=|
00001f50  78 31 2a 74 74 6f 64 5f  73 63 61 6c 65 3a 78 32  |x1*ttod_scale:x2|
00001f60  3d 78 32 2a 74 74 6f 64  5f 73 63 61 6c 65 0d 08  |=x2*ttod_scale..|
00001f70  48 25 79 31 3d 79 31 2a  74 74 6f 64 5f 73 63 61  |H%y1=y1*ttod_sca|
00001f80  6c 65 3a 79 32 3d 79 32  2a 74 74 6f 64 5f 73 63  |le:y2=y2*ttod_sc|
00001f90  61 6c 65 0d 08 52 35 e7  20 78 31 3c 78 32 20 8c  |ale..R5. x1<x2 .|
00001fa0  20 78 5f 6c 6f 77 3d 78  31 3a 78 5f 68 69 67 68  | x_low=x1:x_high|
00001fb0  3d 78 32 20 8b 20 78 5f  6c 6f 77 3d 78 32 3a 78  |=x2 . x_low=x2:x|
00001fc0  5f 68 69 67 68 3d 78 31  0d 08 5c 35 e7 20 79 31  |_high=x1..\5. y1|
00001fd0  3c 79 32 20 8c 20 79 5f  6c 6f 77 3d 79 31 3a 79  |<y2 . y_low=y1:y|
00001fe0  5f 68 69 67 68 3d 79 32  20 8b 20 79 5f 6c 6f 77  |_high=y2 . y_low|
00001ff0  3d 79 32 3a 79 5f 68 69  67 68 3d 79 31 0d 08 66  |=y2:y_high=y1..f|
00002000  2b c8 99 20 26 34 30 30  39 37 2c 2c 74 65 78 74  |+.. &40097,,text|
00002010  24 20 b8 20 2c 2c 2c 20  62 6f 75 6e 64 5f 78 2c  |$ . ,,, bound_x,|
00002020  20 62 6f 75 6e 64 5f 79  0d 08 70 2f 62 6f 75 6e  | bound_y..p/boun|
00002030  64 5f 78 3d 62 6f 75 6e  64 5f 78 2f 74 74 6f 64  |d_x=bound_x/ttod|
00002040  5f 6d 69 6c 6c 69 70 6f  69 6e 74 73 2a 74 74 6f  |_millipoints*tto|
00002050  64 5f 73 63 61 6c 65 0d  08 7a 2f 62 6f 75 6e 64  |d_scale..z/bound|
00002060  5f 79 3d 62 6f 75 6e 64  5f 79 2f 74 74 6f 64 5f  |_y=bound_y/ttod_|
00002070  6d 69 6c 6c 69 70 6f 69  6e 74 73 2a 74 74 6f 64  |millipoints*ttod|
00002080  5f 73 63 61 6c 65 0d 08  84 64 e7 20 28 78 5f 68  |_scale...d. (x_h|
00002090  69 67 68 2d 78 5f 6c 6f  77 29 3c 62 6f 75 6e 64  |igh-x_low)<bound|
000020a0  5f 78 20 8c 20 f2 74 74  6f 64 5f 65 72 72 6f 72  |_x . .ttod_error|
000020b0  28 22 42 6f 75 6e 64 69  6e 67 20 62 6f 78 20 74  |("Bounding box t|
000020c0  6f 6f 20 73 6d 61 6c 6c  20 28 69 6e 20 78 29 20  |oo small (in x) |
000020d0  69 6e 20 63 74 65 78 74  20 63 6f 6d 6d 61 6e 64  |in ctext command|
000020e0  22 2c 6c 69 6e 65 25 29  3a e1 0d 08 8e 64 e7 20  |",line%):....d. |
000020f0  28 79 5f 68 69 67 68 2d  79 5f 6c 6f 77 29 3c 62  |(y_high-y_low)<b|
00002100  6f 75 6e 64 5f 79 20 8c  20 f2 74 74 6f 64 5f 65  |ound_y . .ttod_e|
00002110  72 72 6f 72 28 22 42 6f  75 6e 64 69 6e 67 20 62  |rror("Bounding b|
00002120  6f 78 20 74 6f 6f 20 73  6d 61 6c 6c 20 28 69 6e  |ox too small (in|
00002130  20 79 29 20 69 6e 20 63  74 65 78 74 20 63 6f 6d  | y) in ctext com|
00002140  6d 61 6e 64 22 2c 6c 69  6e 65 25 29 3a e1 0d 08  |mand",line%):...|
00002150  98 23 78 5f 6c 6f 77 2b  3d 28 78 5f 68 69 67 68  |.#x_low+=(x_high|
00002160  2d 78 5f 6c 6f 77 2d 62  6f 75 6e 64 5f 78 29 2f  |-x_low-bound_x)/|
00002170  32 0d 08 a2 23 79 5f 6c  6f 77 2b 3d 28 79 5f 68  |2...#y_low+=(y_h|
00002180  69 67 68 2d 79 5f 6c 6f  77 2d 62 6f 75 6e 64 5f  |igh-y_low-bound_|
00002190  79 29 2f 32 0d 08 ac 3d  6c 65 6e 25 3d 28 a9 28  |y)/2...=len%=(.(|
000021a0  74 65 78 74 24 29 2b 31  29 20 80 20 ac 20 33 3a  |text$)+1) . . 3:|
000021b0  e7 20 28 28 a9 28 74 65  78 74 24 29 2b 31 29 20  |. ((.(text$)+1) |
000021c0  83 20 34 29 3c 3e 30 20  8c 20 6c 65 6e 25 2b 3d  |. 4)<>0 . len%+=|
000021d0  34 0d 08 b6 0d e7 20 70  61 74 68 25 20 8c 0d 08  |4..... path% ...|
000021e0  c0 54 20 78 5f 6c 6f 77  3d 78 5f 6c 6f 77 2a 74  |.T x_low=x_low*t|
000021f0  74 6f 64 5f 6d 69 6c 6c  69 70 6f 69 6e 74 73 2f  |tod_millipoints/|
00002200  74 74 6f 64 5f 73 63 61  6c 65 3a 79 5f 6c 6f 77  |ttod_scale:y_low|
00002210  3d 79 5f 6c 6f 77 2a 74  74 6f 64 5f 6d 69 6c 6c  |=y_low*ttod_mill|
00002220  69 70 6f 69 6e 74 73 2f  74 74 6f 64 5f 73 63 61  |ipoints/ttod_sca|
00002230  6c 65 0d 08 ca 13 20 c8  99 20 26 34 30 30 39 45  |le.... .. &4009E|
00002240  2c 25 31 2c 38 0d 08 d4  2f 20 c8 99 20 26 34 30  |,%1,8.../ .. &40|
00002250  30 38 36 2c 30 2c 74 65  78 74 24 2c 25 30 31 31  |086,0,text$,%011|
00002260  30 30 30 30 30 30 30 30  2c 78 5f 6c 6f 77 2c 79  |00000000,x_low,y|
00002270  5f 6c 6f 77 0d 08 de 1b  20 c8 99 20 26 34 30 30  |_low.... .. &400|
00002280  39 45 2c 30 2c 30 20 b8  20 2c 6e 65 65 64 25 0d  |9E,0,0 . ,need%.|
00002290  08 e8 4b 20 e7 20 6e 65  65 64 25 3e 3d 38 31 38  |..K . need%>=818|
000022a0  34 20 8c 20 f2 74 74 6f  64 5f 65 72 72 6f 72 28  |4 . .ttod_error(|
000022b0  22 54 65 78 74 20 70 61  74 68 20 74 6f 6f 20 62  |"Text path too b|
000022c0  69 67 20 66 6f 72 20 62  75 66 66 65 72 21 21 22  |ig for buffer!!"|
000022d0  2c 20 6c 69 6e 65 25 29  3a e1 0d 08 f2 23 20 21  |, line%):....# !|
000022e0  74 74 6f 64 5f 77 6f 72  6b 25 3d 30 3a 21 74 74  |ttod_work%=0:!tt|
000022f0  6f 64 5f 77 6f 72 6b 25  3d 38 31 38 34 0d 08 fc  |od_work%=8184...|
00002300  20 20 c8 99 20 26 34 30  30 39 45 2c 25 31 30 30  |  .. &4009E,%100|
00002310  31 30 2c 74 74 6f 64 5f  77 6f 72 6b 25 0d 09 06  |10,ttod_work%...|
00002320  2f 20 c8 99 20 26 34 30  30 38 36 2c 30 2c 74 65  |/ .. &40086,0,te|
00002330  78 74 24 2c 25 30 31 31  30 30 30 30 30 30 30 30  |xt$,%01100000000|
00002340  2c 78 5f 6c 6f 77 2c 79  5f 6c 6f 77 0d 09 10 1b  |,x_low,y_low....|
00002350  20 c8 99 20 26 34 30 30  39 45 2c 30 2c 30 20 b8  | .. &4009E,0,0 .|
00002360  20 2c 6e 65 65 64 25 0d  09 1a 35 20 c8 99 20 22  | ,need%...5 .. "|
00002370  4f 53 5f 47 42 50 42 22  2c 32 2c 66 69 6c 65 25  |OS_GBPB",2,file%|
00002380  2c 74 74 6f 64 5f 77 6f  72 6b 25 2c 6e 65 65 64  |,ttod_work%,need|
00002390  25 2d 74 74 6f 64 5f 77  6f 72 6b 25 0d 09 24 05  |%-ttod_work%..$.|
000023a0  cc 0d 09 2e 52 20 f2 74  74 6f 64 5f 70 75 74 5f  |....R .ttod_put_|
000023b0  68 65 61 64 28 66 69 6c  65 25 2c 20 31 2c 20 35  |head(file%, 1, 5|
000023c0  32 2b 6c 65 6e 25 2c 20  78 5f 6c 6f 77 2c 20 79  |2+len%, x_low, y|
000023d0  5f 6c 6f 77 2c 20 78 5f  6c 6f 77 2b 62 6f 75 6e  |_low, x_low+boun|
000023e0  64 5f 78 2c 20 79 5f 6c  6f 77 2b 62 6f 75 6e 64  |d_x, y_low+bound|
000023f0  5f 79 29 0d 09 38 14 20  f2 77 70 75 74 28 66 69  |_y)..8. .wput(fi|
00002400  6c 65 25 2c 20 30 29 0d  09 42 1c 20 f2 77 70 75  |le%, 0)..B. .wpu|
00002410  74 28 66 69 6c 65 25 2c  20 26 46 46 46 46 46 46  |t(file%, &FFFFFF|
00002420  30 30 29 0d 09 4c 1a 20  f2 77 70 75 74 28 66 69  |00)..L. .wput(fi|
00002430  6c 65 25 2c 20 68 61 6e  64 6c 65 25 29 0d 09 56  |le%, handle%)..V|
00002440  2e 20 f2 77 70 75 74 28  66 69 6c 65 25 2c 20 74  |. .wput(file%, t|
00002450  74 6f 64 5f 66 6f 6e 74  5f 73 69 7a 65 28 68 61  |tod_font_size(ha|
00002460  6e 64 6c 65 25 29 2a 36  34 30 29 0d 09 60 2e 20  |ndle%)*640)..`. |
00002470  f2 77 70 75 74 28 66 69  6c 65 25 2c 20 74 74 6f  |.wput(file%, tto|
00002480  64 5f 66 6f 6e 74 5f 73  69 7a 65 28 68 61 6e 64  |d_font_size(hand|
00002490  6c 65 25 29 2a 36 34 30  29 0d 09 6a 18 20 f2 77  |le%)*640)..j. .w|
000024a0  70 75 74 28 66 69 6c 65  25 2c 20 78 5f 6c 6f 77  |put(file%, x_low|
000024b0  29 0d 09 74 18 20 f2 77  70 75 74 28 66 69 6c 65  |)..t. .wput(file|
000024c0  25 2c 20 79 5f 6c 6f 77  29 0d 09 7e 34 20 f2 74  |%, y_low)..~4 .t|
000024d0  74 6f 64 5f 70 75 74 5f  70 61 64 64 65 64 28 66  |tod_put_padded(f|
000024e0  69 6c 65 25 2c 20 6c 65  6e 25 2c 20 74 65 78 74  |ile%, len%, text|
000024f0  24 2b bd 28 30 29 2c 20  bd 28 30 29 29 0d 09 88  |$+.(0), .(0))...|
00002500  05 cd 0d 09 92 05 e1 0d  09 9c 05 3a 0d 09 a6 32  |...........:...2|
00002510  dd 20 f2 74 74 6f 64 5f  67 65 6e 65 72 61 74 65  |. .ttod_generate|
00002520  5f 6c 69 6e 65 28 66 69  6c 65 25 2c 20 70 61 72  |_line(file%, par|
00002530  61 6d 24 2c 20 6c 69 6e  65 5f 6e 6f 25 29 0d 09  |am$, line_no%)..|
00002540  b0 61 ea 20 73 74 61 72  74 5f 78 2c 20 73 74 61  |.a. start_x, sta|
00002550  72 74 5f 79 2c 20 66 69  6e 69 73 68 5f 78 2c 20  |rt_y, finish_x, |
00002560  66 69 6e 69 73 68 5f 79  2c 20 78 5f 6c 6f 77 2c  |finish_y, x_low,|
00002570  20 79 5f 6c 6f 77 2c 20  78 5f 68 69 67 68 2c 20  | y_low, x_high, |
00002580  79 5f 68 69 67 68 2c 20  77 69 64 74 68 2c 20 73  |y_high, width, s|
00002590  74 61 74 75 73 25 2c 20  63 6f 6c 6f 75 72 25 0d  |tatus%, colour%.|
000025a0  09 ba 30 77 69 64 74 68  3d 30 3a 73 74 61 72 74  |..0width=0:start|
000025b0  25 3d a3 3a 66 69 6e 69  73 68 25 3d a3 3a 63 6f  |%=.:finish%=.:co|
000025c0  6c 6f 75 72 25 3d 26 30  30 30 30 30 30 30 30 0d  |lour%=&00000000.|
000025d0  09 c4 43 c8 99 20 26 32  30 30 34 39 2c 20 74 74  |..C.. &20049, tt|
000025e0  6f 64 5f 6c 69 6e 65 5f  61 72 67 73 24 2c 20 70  |od_line_args$, p|
000025f0  61 72 61 6d 24 2c 20 74  74 6f 64 5f 77 6f 72 6b  |aram$, ttod_work|
00002600  25 2c 20 31 30 32 34 20  b8 20 3b 73 74 61 74 75  |%, 1024 . ;statu|
00002610  73 25 0d 09 ce 3e e7 20  28 73 74 61 74 75 73 25  |s%...>. (status%|
00002620  20 80 20 31 29 3d 31 20  8c 20 f2 74 74 6f 64 5f  | . 1)=1 . .ttod_|
00002630  65 72 72 6f 72 28 22 53  79 6e 74 61 78 20 65 72  |error("Syntax er|
00002640  72 6f 72 22 2c 6c 69 6e  65 5f 6e 6f 25 29 3a e1  |ror",line_no%):.|
00002650  0d 09 d8 66 e7 20 74 74  6f 64 5f 77 6f 72 6b 25  |...f. ttod_work%|
00002660  21 30 3d 30 20 8c 20 f2  74 74 6f 64 5f 65 72 72  |!0=0 . .ttod_err|
00002670  6f 72 28 22 4d 69 73 73  69 6e 67 20 73 74 61 72  |or("Missing star|
00002680  74 20 70 6f 73 69 74 69  6f 6e 20 64 65 66 69 6e  |t position defin|
00002690  69 74 69 6f 6e 20 66 72  6f 6d 20 27 6c 69 6e 65  |ition from 'line|
000026a0  27 20 63 6f 6d 6d 61 6e  64 22 2c 6c 69 6e 65 5f  |' command",line_|
000026b0  6e 6f 25 29 3a e1 0d 09  e2 64 e7 20 74 74 6f 64  |no%):....d. ttod|
000026c0  5f 77 6f 72 6b 25 21 34  3d 30 20 8c 20 f2 74 74  |_work%!4=0 . .tt|
000026d0  6f 64 5f 65 72 72 6f 72  28 22 4d 69 73 73 69 6e  |od_error("Missin|
000026e0  67 20 65 6e 64 20 70 6f  73 69 74 69 6f 6e 20 64  |g end position d|
000026f0  65 66 69 6e 69 74 69 6f  6e 20 66 72 6f 6d 20 27  |efinition from '|
00002700  6c 69 6e 65 27 20 63 6f  6d 6d 61 6e 64 22 2c 6c  |line' command",l|
00002710  69 6e 65 5f 6e 6f 25 29  3a e1 0d 09 ec 3a f2 74  |ine_no%):....:.t|
00002720  74 6f 64 5f 67 65 74 5f  78 79 28 a4 67 65 74 5f  |tod_get_xy(.get_|
00002730  73 74 72 28 74 74 6f 64  5f 77 6f 72 6b 25 21 30  |str(ttod_work%!0|
00002740  29 2c 20 73 74 61 72 74  5f 78 2c 20 73 74 61 72  |), start_x, star|
00002750  74 5f 79 29 0d 09 f6 3c  f2 74 74 6f 64 5f 67 65  |t_y)...<.ttod_ge|
00002760  74 5f 78 79 28 a4 67 65  74 5f 73 74 72 28 74 74  |t_xy(.get_str(tt|
00002770  6f 64 5f 77 6f 72 6b 25  21 34 29 2c 20 66 69 6e  |od_work%!4), fin|
00002780  69 73 68 5f 78 2c 20 66  69 6e 69 73 68 5f 79 29  |ish_x, finish_y)|
00002790  0d 0a 00 3b e7 20 74 74  6f 64 5f 77 6f 72 6b 25  |...;. ttod_work%|
000027a0  21 38 3c 3e 30 20 8c 20  77 69 64 74 68 3d bb 28  |!8<>0 . width=.(|
000027b0  a4 67 65 74 5f 73 74 72  28 74 74 6f 64 5f 77 6f  |.get_str(ttod_wo|
000027c0  72 6b 25 21 38 29 29 2a  36 34 30 0d 0a 0a 3b e7  |rk%!8))*640...;.|
000027d0  20 74 74 6f 64 5f 77 6f  72 6b 25 21 31 32 3c 3e  | ttod_work%!12<>|
000027e0  30 20 8c 20 63 6f 6c 6f  75 72 25 3d a0 28 a4 67  |0 . colour%=.(.g|
000027f0  65 74 5f 73 74 72 28 74  74 6f 64 5f 77 6f 72 6b  |et_str(ttod_work|
00002800  25 21 31 32 29 29 0d 0a  14 39 73 74 61 72 74 5f  |%!12))...9start_|
00002810  78 3d 73 74 61 72 74 5f  78 2a 74 74 6f 64 5f 73  |x=start_x*ttod_s|
00002820  63 61 6c 65 3a 73 74 61  72 74 5f 79 3d 73 74 61  |cale:start_y=sta|
00002830  72 74 5f 79 2a 74 74 6f  64 5f 73 63 61 6c 65 0d  |rt_y*ttod_scale.|
00002840  0a 1e 3d 66 69 6e 69 73  68 5f 78 3d 66 69 6e 69  |..=finish_x=fini|
00002850  73 68 5f 78 2a 74 74 6f  64 5f 73 63 61 6c 65 3a  |sh_x*ttod_scale:|
00002860  66 69 6e 69 73 68 5f 79  3d 66 69 6e 69 73 68 5f  |finish_y=finish_|
00002870  79 2a 74 74 6f 64 5f 73  63 61 6c 65 0d 0a 28 56  |y*ttod_scale..(V|
00002880  e7 20 73 74 61 72 74 5f  78 3c 66 69 6e 69 73 68  |. start_x<finish|
00002890  5f 78 20 8c 20 78 5f 6c  6f 77 3d 73 74 61 72 74  |_x . x_low=start|
000028a0  5f 78 3a 78 5f 68 69 67  68 3d 66 69 6e 69 73 68  |_x:x_high=finish|
000028b0  5f 78 20 8b 20 78 5f 6c  6f 77 3d 66 69 6e 69 73  |_x . x_low=finis|
000028c0  68 5f 78 3a 78 5f 68 69  67 68 3d 73 74 61 72 74  |h_x:x_high=start|
000028d0  5f 78 0d 0a 32 56 e7 20  73 74 61 72 74 5f 79 3c  |_x..2V. start_y<|
000028e0  66 69 6e 69 73 68 5f 79  20 8c 20 79 5f 6c 6f 77  |finish_y . y_low|
000028f0  3d 73 74 61 72 74 5f 79  3a 79 5f 68 69 67 68 3d  |=start_y:y_high=|
00002900  66 69 6e 69 73 68 5f 79  20 8b 20 79 5f 6c 6f 77  |finish_y . y_low|
00002910  3d 66 69 6e 69 73 68 5f  79 3a 79 5f 68 69 67 68  |=finish_y:y_high|
00002920  3d 73 74 61 72 74 5f 79  0d 0a 3c 3e f2 74 74 6f  |=start_y..<>.tto|
00002930  64 5f 70 75 74 5f 68 65  61 64 28 66 69 6c 65 25  |d_put_head(file%|
00002940  2c 20 32 2c 20 36 38 2c  20 78 5f 6c 6f 77 2c 20  |, 2, 68, x_low, |
00002950  79 5f 6c 6f 77 2c 20 78  5f 68 69 67 68 2c 20 79  |y_low, x_high, y|
00002960  5f 68 69 67 68 29 0d 0a  46 1b f2 77 70 75 74 28  |_high)..F..wput(|
00002970  66 69 6c 65 25 2c 20 26  46 46 46 46 46 46 46 46  |file%, &FFFFFFFF|
00002980  29 0d 0a 50 19 f2 77 70  75 74 28 66 69 6c 65 25  |)..P..wput(file%|
00002990  2c 20 63 6f 6c 6f 75 72  25 29 0d 0a 5a 17 f2 77  |, colour%)..Z..w|
000029a0  70 75 74 28 66 69 6c 65  25 2c 20 77 69 64 74 68  |put(file%, width|
000029b0  29 0d 0a 64 1b f2 77 70  75 74 28 66 69 6c 65 25  |)..d..wput(file%|
000029c0  2c 20 25 30 30 30 30 30  30 30 30 29 0d 0a 6e 2e  |, %00000000)..n.|
000029d0  f2 74 74 6f 64 5f 70 75  74 5f 70 61 74 68 28 66  |.ttod_put_path(f|
000029e0  69 6c 65 25 2c 20 32 2c  20 73 74 61 72 74 5f 78  |ile%, 2, start_x|
000029f0  2c 20 73 74 61 72 74 5f  79 29 0d 0a 78 30 f2 74  |, start_y)..x0.t|
00002a00  74 6f 64 5f 70 75 74 5f  70 61 74 68 28 66 69 6c  |tod_put_path(fil|
00002a10  65 25 2c 20 38 2c 20 66  69 6e 69 73 68 5f 78 2c  |e%, 8, finish_x,|
00002a20  20 66 69 6e 69 73 68 5f  79 29 0d 0a 82 13 f2 77  | finish_y).....w|
00002a30  70 75 74 28 66 69 6c 65  25 2c 20 30 29 0d 0a 8c  |put(file%, 0)...|
00002a40  05 e1 0d 0a 96 05 3a 0d  0a a0 31 dd 20 f2 74 74  |......:...1. .tt|
00002a50  6f 64 5f 67 65 6e 65 72  61 74 65 5f 62 6f 78 28  |od_generate_box(|
00002a60  66 69 6c 65 25 2c 20 70  61 72 61 6d 24 2c 20 6c  |file%, param$, l|
00002a70  69 6e 65 5f 6e 6f 25 29  0d 0a aa 59 ea 20 78 31  |ine_no%)...Y. x1|
00002a80  2c 20 79 31 2c 20 78 32  2c 20 79 32 2c 20 78 5f  |, y1, x2, y2, x_|
00002a90  6c 6f 77 2c 20 79 5f 6c  6f 77 2c 20 78 5f 68 69  |low, y_low, x_hi|
00002aa0  67 68 2c 20 79 5f 68 69  67 68 2c 20 77 69 64 74  |gh, y_high, widt|
00002ab0  68 2c 20 73 74 61 74 75  73 25 2c 20 6c 69 6e 65  |h, status%, line|
00002ac0  5f 63 6f 6c 25 2c 20 66  69 6c 6c 65 5f 63 6f 6c  |_col%, fille_col|
00002ad0  25 0d 0a b4 33 77 69 64  74 68 3d 30 3a 6c 69 6e  |%...3width=0:lin|
00002ae0  65 5f 63 6f 6c 25 3d 26  30 30 30 30 30 30 30 30  |e_col%=&00000000|
00002af0  3a 66 69 6c 6c 5f 63 6f  6c 25 3d 26 46 46 46 46  |:fill_col%=&FFFF|
00002b00  46 46 46 46 0d 0a be 43  c8 99 20 26 32 30 30 34  |FFFF...C.. &2004|
00002b10  39 2c 20 74 74 6f 64 5f  72 65 63 74 5f 61 72 67  |9, ttod_rect_arg|
00002b20  73 24 2c 20 70 61 72 61  6d 24 2c 20 74 74 6f 64  |s$, param$, ttod|
00002b30  5f 77 6f 72 6b 25 2c 20  31 30 32 34 20 b8 20 3b  |_work%, 1024 . ;|
00002b40  73 74 61 74 75 73 25 0d  0a c8 3e e7 20 28 73 74  |status%...>. (st|
00002b50  61 74 75 73 25 20 80 20  31 29 3d 31 20 8c 20 f2  |atus% . 1)=1 . .|
00002b60  74 74 6f 64 5f 65 72 72  6f 72 28 22 53 79 6e 74  |ttod_error("Synt|
00002b70  61 78 20 65 72 72 6f 72  22 2c 6c 69 6e 65 5f 6e  |ax error",line_n|
00002b80  6f 25 29 3a e1 0d 0a d2  65 e7 20 74 74 6f 64 5f  |o%):....e. ttod_|
00002b90  77 6f 72 6b 25 21 30 3d  30 20 8c 20 f2 74 74 6f  |work%!0=0 . .tto|
00002ba0  64 5f 65 72 72 6f 72 28  22 4d 69 73 73 69 6e 67  |d_error("Missing|
00002bb0  20 66 69 72 73 74 20 70  6f 73 69 74 69 6f 6e 20  | first position |
00002bc0  64 65 66 69 6e 69 74 69  6f 6e 20 66 72 6f 6d 20  |definition from |
00002bd0  27 62 6f 78 27 20 63 6f  6d 6d 61 6e 64 22 2c 6c  |'box' command",l|
00002be0  69 6e 65 5f 6e 6f 25 29  3a e1 0d 0a dc 66 e7 20  |ine_no%):....f. |
00002bf0  74 74 6f 64 5f 77 6f 72  6b 25 21 34 3d 30 20 8c  |ttod_work%!4=0 .|
00002c00  20 f2 74 74 6f 64 5f 65  72 72 6f 72 28 22 4d 69  | .ttod_error("Mi|
00002c10  73 73 69 6e 67 20 73 65  63 6f 6e 64 20 70 6f 73  |ssing second pos|
00002c20  69 74 69 6f 6e 20 64 65  66 69 6e 69 74 69 6f 6e  |ition definition|
00002c30  20 66 72 6f 6d 20 27 62  6f 78 27 20 63 6f 6d 6d  | from 'box' comm|
00002c40  61 6e 64 22 2c 6c 69 6e  65 5f 6e 6f 25 29 3a e1  |and",line_no%):.|
00002c50  0d 0a e6 30 f2 74 74 6f  64 5f 67 65 74 5f 78 79  |...0.ttod_get_xy|
00002c60  28 a4 67 65 74 5f 73 74  72 28 74 74 6f 64 5f 77  |(.get_str(ttod_w|
00002c70  6f 72 6b 25 21 30 29 2c  20 78 31 2c 20 79 31 29  |ork%!0), x1, y1)|
00002c80  0d 0a f0 30 f2 74 74 6f  64 5f 67 65 74 5f 78 79  |...0.ttod_get_xy|
00002c90  28 a4 67 65 74 5f 73 74  72 28 74 74 6f 64 5f 77  |(.get_str(ttod_w|
00002ca0  6f 72 6b 25 21 34 29 2c  20 78 32 2c 20 79 32 29  |ork%!4), x2, y2)|
00002cb0  0d 0a fa 3b e7 20 74 74  6f 64 5f 77 6f 72 6b 25  |...;. ttod_work%|
00002cc0  21 38 3c 3e 30 20 8c 20  77 69 64 74 68 3d bb 28  |!8<>0 . width=.(|
00002cd0  a4 67 65 74 5f 73 74 72  28 74 74 6f 64 5f 77 6f  |.get_str(ttod_wo|
00002ce0  72 6b 25 21 38 29 29 2a  36 34 30 0d 0b 04 3d e7  |rk%!8))*640...=.|
00002cf0  20 74 74 6f 64 5f 77 6f  72 6b 25 21 31 32 3c 3e  | ttod_work%!12<>|
00002d00  30 20 8c 20 66 69 6c 6c  5f 63 6f 6c 25 3d a0 28  |0 . fill_col%=.(|
00002d10  a4 67 65 74 5f 73 74 72  28 74 74 6f 64 5f 77 6f  |.get_str(ttod_wo|
00002d20  72 6b 25 21 31 32 29 29  0d 0b 0e 3d e7 20 74 74  |rk%!12))...=. tt|
00002d30  6f 64 5f 77 6f 72 6b 25  21 31 36 3c 3e 30 20 8c  |od_work%!16<>0 .|
00002d40  20 6c 69 6e 65 5f 63 6f  6c 25 3d a0 28 a4 67 65  | line_col%=.(.ge|
00002d50  74 5f 73 74 72 28 74 74  6f 64 5f 77 6f 72 6b 25  |t_str(ttod_work%|
00002d60  21 31 36 29 29 0d 0b 18  25 78 31 3d 78 31 2a 74  |!16))...%x1=x1*t|
00002d70  74 6f 64 5f 73 63 61 6c  65 3a 78 32 3d 78 32 2a  |tod_scale:x2=x2*|
00002d80  74 74 6f 64 5f 73 63 61  6c 65 0d 0b 22 25 79 31  |ttod_scale.."%y1|
00002d90  3d 79 31 2a 74 74 6f 64  5f 73 63 61 6c 65 3a 79  |=y1*ttod_scale:y|
00002da0  32 3d 79 32 2a 74 74 6f  64 5f 73 63 61 6c 65 0d  |2=y2*ttod_scale.|
00002db0  0b 2c 35 e7 20 78 31 3c  78 32 20 8c 20 78 5f 6c  |.,5. x1<x2 . x_l|
00002dc0  6f 77 3d 78 31 3a 78 5f  68 69 67 68 3d 78 32 20  |ow=x1:x_high=x2 |
00002dd0  8b 20 78 5f 6c 6f 77 3d  78 32 3a 78 5f 68 69 67  |. x_low=x2:x_hig|
00002de0  68 3d 78 31 0d 0b 36 35  e7 20 79 31 3c 79 32 20  |h=x1..65. y1<y2 |
00002df0  8c 20 79 5f 6c 6f 77 3d  79 31 3a 79 5f 68 69 67  |. y_low=y1:y_hig|
00002e00  68 3d 79 32 20 8b 20 79  5f 6c 6f 77 3d 79 32 3a  |h=y2 . y_low=y2:|
00002e10  79 5f 68 69 67 68 3d 79  31 0d 0b 40 3f f2 74 74  |y_high=y1..@?.tt|
00002e20  6f 64 5f 70 75 74 5f 68  65 61 64 28 66 69 6c 65  |od_put_head(file|
00002e30  25 2c 20 32 2c 20 31 30  38 2c 20 78 5f 6c 6f 77  |%, 2, 108, x_low|
00002e40  2c 20 79 5f 6c 6f 77 2c  20 78 5f 68 69 67 68 2c  |, y_low, x_high,|
00002e50  20 79 5f 68 69 67 68 29  0d 0b 4a 1b f2 77 70 75  | y_high)..J..wpu|
00002e60  74 28 66 69 6c 65 25 2c  20 66 69 6c 6c 5f 63 6f  |t(file%, fill_co|
00002e70  6c 25 29 0d 0b 54 1b f2  77 70 75 74 28 66 69 6c  |l%)..T..wput(fil|
00002e80  65 25 2c 20 6c 69 6e 65  5f 63 6f 6c 25 29 0d 0b  |e%, line_col%)..|
00002e90  5e 17 f2 77 70 75 74 28  66 69 6c 65 25 2c 20 77  |^..wput(file%, w|
00002ea0  69 64 74 68 29 0d 0b 68  1b f2 77 70 75 74 28 66  |idth)..h..wput(f|
00002eb0  69 6c 65 25 2c 20 25 30  30 30 30 30 30 30 30 29  |ile%, %00000000)|
00002ec0  0d 0b 72 24 f2 74 74 6f  64 5f 70 75 74 5f 70 61  |..r$.ttod_put_pa|
00002ed0  74 68 28 66 69 6c 65 25  2c 20 32 2c 20 78 31 2c  |th(file%, 2, x1,|
00002ee0  20 79 31 29 0d 0b 7c 24  f2 74 74 6f 64 5f 70 75  | y1)..|$.ttod_pu|
00002ef0  74 5f 70 61 74 68 28 66  69 6c 65 25 2c 20 38 2c  |t_path(file%, 8,|
00002f00  20 78 32 2c 20 79 31 29  0d 0b 86 24 f2 74 74 6f  | x2, y1)...$.tto|
00002f10  64 5f 70 75 74 5f 70 61  74 68 28 66 69 6c 65 25  |d_put_path(file%|
00002f20  2c 20 38 2c 20 78 32 2c  20 79 32 29 0d 0b 90 24  |, 8, x2, y2)...$|
00002f30  f2 74 74 6f 64 5f 70 75  74 5f 70 61 74 68 28 66  |.ttod_put_path(f|
00002f40  69 6c 65 25 2c 20 38 2c  20 78 31 2c 20 79 32 29  |ile%, 8, x1, y2)|
00002f50  0d 0b 9a 24 f2 74 74 6f  64 5f 70 75 74 5f 70 61  |...$.ttod_put_pa|
00002f60  74 68 28 66 69 6c 65 25  2c 20 38 2c 20 78 31 2c  |th(file%, 8, x1,|
00002f70  20 79 31 29 0d 0b a4 13  f2 77 70 75 74 28 66 69  | y1).....wput(fi|
00002f80  6c 65 25 2c 20 35 29 0d  0b ae 13 f2 77 70 75 74  |le%, 5).....wput|
00002f90  28 66 69 6c 65 25 2c 20  30 29 0d 0b b8 05 e1 0d  |(file%, 0)......|
00002fa0  0b c2 05 3a 0d 0b cc 37  dd 20 f2 74 74 6f 64 5f  |...:...7. .ttod_|
00002fb0  69 6e 63 6c 75 64 65 5f  73 70 72 69 74 65 28 6f  |include_sprite(o|
00002fc0  75 74 5f 66 69 6c 65 25  2c 20 70 61 72 61 6d 24  |ut_file%, param$|
00002fd0  2c 20 6c 69 6e 65 5f 6e  6f 25 29 0d 0b d6 70 ea  |, line_no%)...p.|
00002fe0  20 78 31 2c 20 79 31 2c  20 78 32 2c 20 79 32 2c  | x1, y1, x2, y2,|
00002ff0  20 78 5f 6c 6f 77 2c 20  79 5f 6c 6f 77 2c 20 78  | x_low, y_low, x|
00003000  5f 68 69 67 68 2c 20 79  5f 68 69 67 68 2c 20 66  |_high, y_high, f|
00003010  69 6c 65 24 2c 20 69 6e  5f 66 69 6c 65 25 2c 20  |ile$, in_file%, |
00003020  73 70 72 69 74 65 24 2c  20 73 74 61 74 75 73 25  |sprite$, status%|
00003030  2c 20 6e 75 6d 62 65 72  25 2c 20 6c 65 6e 25 2c  |, number%, len%,|
00003040  20 74 6d 70 24 2c 20 74  6d 70 25 0d 0b e0 45 c8  | tmp$, tmp%...E.|
00003050  99 20 26 32 30 30 34 39  2c 20 74 74 6f 64 5f 73  |. &20049, ttod_s|
00003060  70 72 69 74 65 5f 61 72  67 73 24 2c 20 70 61 72  |prite_args$, par|
00003070  61 6d 24 2c 20 74 74 6f  64 5f 77 6f 72 6b 25 2c  |am$, ttod_work%,|
00003080  20 31 30 32 34 20 b8 20  3b 73 74 61 74 75 73 25  | 1024 . ;status%|
00003090  0d 0b ea 3e e7 20 28 73  74 61 74 75 73 25 20 80  |...>. (status% .|
000030a0  20 31 29 3d 31 20 8c 20  f2 74 74 6f 64 5f 65 72  | 1)=1 . .ttod_er|
000030b0  72 6f 72 28 22 53 79 6e  74 61 78 20 65 72 72 6f  |ror("Syntax erro|
000030c0  72 22 2c 6c 69 6e 65 5f  6e 6f 25 29 3a e1 0d 0b  |r",line_no%):...|
000030d0  f4 58 e7 20 74 74 6f 64  5f 77 6f 72 6b 25 21 30  |.X. ttod_work%!0|
000030e0  3d 30 20 8c 20 f2 74 74  6f 64 5f 65 72 72 6f 72  |=0 . .ttod_error|
000030f0  28 22 4d 69 73 73 69 6e  67 20 66 69 6c 65 20 6e  |("Missing file n|
00003100  61 6d 65 20 66 72 6f 6d  20 27 73 70 72 69 74 65  |ame from 'sprite|
00003110  27 20 63 6f 6d 6d 61 6e  64 22 2c 6c 69 6e 65 5f  |' command",line_|
00003120  6e 6f 25 29 3a e1 0d 0b  fe 5b e7 20 74 74 6f 64  |no%):....[. ttod|
00003130  5f 77 6f 72 6b 25 21 34  3d 30 20 8c 20 f2 74 74  |_work%!4=0 . .tt|
00003140  6f 64 5f 65 72 72 6f 72  28 22 4d 69 73 73 69 6e  |od_error("Missin|
00003150  67 20 73 70 72 69 74 65  20 6e 61 6d 65 20 66 72  |g sprite name fr|
00003160  6f 6d 20 27 73 70 72 69  74 65 27 20 63 6f 6d 6d  |om 'sprite' comm|
00003170  61 6e 64 22 2c 20 6c 69  6e 65 5f 6e 6f 25 29 3a  |and", line_no%):|
00003180  e1 0d 0c 08 68 e7 20 74  74 6f 64 5f 77 6f 72 6b  |....h. ttod_work|
00003190  25 21 38 3d 30 20 8c 20  f2 74 74 6f 64 5f 65 72  |%!8=0 . .ttod_er|
000031a0  72 6f 72 28 22 4d 69 73  73 69 6e 67 20 66 69 72  |ror("Missing fir|
000031b0  73 74 20 70 6f 73 69 74  69 6f 6e 20 64 65 66 69  |st position defi|
000031c0  6e 69 74 69 6f 6e 20 66  72 6f 6d 20 27 73 70 72  |nition from 'spr|
000031d0  69 74 65 27 20 63 6f 6d  6d 61 6e 64 22 2c 6c 69  |ite' command",li|
000031e0  6e 65 5f 6e 6f 25 29 3a  e1 0d 0c 12 6a e7 20 74  |ne_no%):....j. t|
000031f0  74 6f 64 5f 77 6f 72 6b  25 21 31 32 3d 30 20 8c  |tod_work%!12=0 .|
00003200  20 f2 74 74 6f 64 5f 65  72 72 6f 72 28 22 4d 69  | .ttod_error("Mi|
00003210  73 73 69 6e 67 20 73 65  63 6f 6e 64 20 70 6f 73  |ssing second pos|
00003220  69 74 69 6f 6e 20 64 65  66 69 6e 69 74 69 6f 6e  |ition definition|
00003230  20 66 72 6f 6d 20 27 73  70 72 69 74 65 27 20 63  | from 'sprite' c|
00003240  6f 6d 6d 61 6e 64 22 2c  6c 69 6e 65 5f 6e 6f 25  |ommand",line_no%|
00003250  29 3a e1 0d 0c 1c 22 73  70 72 69 74 65 24 3d a4  |):...."sprite$=.|
00003260  67 65 74 5f 73 74 72 28  74 74 6f 64 5f 77 6f 72  |get_str(ttod_wor|
00003270  6b 25 21 34 29 0d 0c 26  58 e7 20 a9 28 73 70 72  |k%!4)..&X. .(spr|
00003280  69 74 65 24 29 3e 31 32  20 8c 20 f2 74 74 6f 64  |ite$)>12 . .ttod|
00003290  5f 65 72 72 6f 72 28 22  49 6c 6c 65 67 61 6c 20  |_error("Illegal |
000032a0  73 70 72 69 74 65 20 6e  61 6d 65 20 69 6e 20 27  |sprite name in '|
000032b0  73 70 72 69 74 65 27 20  63 6f 6d 6d 61 6e 64 22  |sprite' command"|
000032c0  2c 20 6c 69 6e 65 5f 6e  6f 25 29 3a e1 0d 0c 30  |, line_no%):...0|
000032d0  20 66 69 6c 65 24 3d a4  67 65 74 5f 73 74 72 28  | file$=.get_str(|
000032e0  74 74 6f 64 5f 77 6f 72  6b 25 21 30 29 0d 0c 3a  |ttod_work%!0)..:|
000032f0  15 69 6e 5f 66 69 6c 65  25 3d 8e 28 66 69 6c 65  |.in_file%=.(file|
00003300  24 29 0d 0c 44 5b e7 20  69 6e 5f 66 69 6c 65 25  |$)..D[. in_file%|
00003310  3d 30 20 8c 20 f2 74 74  6f 64 5f 65 72 72 6f 72  |=0 . .ttod_error|
00003320  28 22 46 69 6c 65 20 27  22 2b 66 69 6c 65 24 2b  |("File '"+file$+|
00003330  22 27 20 6e 6f 74 20 66  6f 75 6e 64 20 69 6e 20  |"' not found in |
00003340  27 73 70 72 69 74 65 27  20 63 6f 6d 6d 61 6e 64  |'sprite' command|
00003350  22 2c 6c 69 6e 65 5f 6e  6f 25 29 3a e1 0d 0c 4e  |",line_no%):...N|
00003360  1b 6e 75 6d 62 65 72 25  3d a4 77 67 65 74 28 69  |.number%=.wget(i|
00003370  6e 5f 66 69 6c 65 25 29  0d 0c 58 47 e7 20 6e 75  |n_file%)..XG. nu|
00003380  6d 62 65 72 25 3d 30 20  8c 20 f2 74 74 6f 64 5f  |mber%=0 . .ttod_|
00003390  65 72 72 6f 72 28 22 46  69 6c 65 20 27 22 2b 66  |error("File '"+f|
000033a0  69 6c 65 24 2b 22 27 20  63 6f 6e 74 61 69 6e 73  |ile$+"' contains|
000033b0  20 6e 6f 20 73 70 72 69  74 65 73 22 29 3a e1 0d  | no sprites"):..|
000033c0  0c 62 20 cf 23 69 6e 5f  66 69 6c 65 25 3d a4 77  |.b .#in_file%=.w|
000033d0  67 65 74 28 69 6e 5f 66  69 6c 65 25 29 2d 34 0d  |get(in_file%)-4.|
000033e0  0c 6c 13 74 6d 70 25 3d  8f 23 69 6e 5f 66 69 6c  |.l.tmp%=.#in_fil|
000033f0  65 25 0d 0c 76 05 f5 0d  0c 80 19 20 6c 65 6e 25  |e%..v...... len%|
00003400  3d a4 77 67 65 74 28 69  6e 5f 66 69 6c 65 25 29  |=.wget(in_file%)|
00003410  0d 0c 8a 14 20 74 6d 70  24 3d be 23 69 6e 5f 66  |.... tmp$=.#in_f|
00003420  69 6c 65 25 0d 0c 94 2e  20 e7 20 74 6d 70 24 3c  |ile%.... . tmp$<|
00003430  3e 73 70 72 69 74 65 24  20 8c 20 6e 75 6d 62 65  |>sprite$ . numbe|
00003440  72 25 3d 2d 31 20 8b 20  6e 75 6d 62 65 72 25 2d  |r%=-1 . number%-|
00003450  3d 31 0d 0c 9e 40 20 e7  20 6e 75 6d 62 65 72 25  |=1...@ . number%|
00003460  3e 30 20 8c 20 cf 23 69  6e 5f 66 69 6c 65 25 3d  |>0 . .#in_file%=|
00003470  8f 23 69 6e 5f 66 69 6c  65 25 2b 6c 65 6e 25 2d  |.#in_file%+len%-|
00003480  31 36 3a 74 6d 70 25 3d  8f 23 69 6e 5f 66 69 6c  |16:tmp%=.#in_fil|
00003490  65 25 0d 0c a8 0f fd 20  6e 75 6d 62 65 72 25 3c  |e%..... number%<|
000034a0  31 0d 0c b2 56 e7 20 6e  75 6d 62 65 72 25 3c 3e  |1...V. number%<>|
000034b0  2d 31 20 8c 20 f2 74 74  6f 64 5f 65 72 72 6f 72  |-1 . .ttod_error|
000034c0  28 22 53 70 72 69 74 65  20 27 22 2b 73 70 72 69  |("Sprite '"+spri|
000034d0  74 65 24 2b 22 20 6e 6f  74 20 66 6f 75 6e 64 20  |te$+" not found |
000034e0  69 6e 20 66 69 6c 65 20  27 22 2b 66 69 6c 65 24  |in file '"+file$|
000034f0  2b 22 27 22 29 3a e1 0d  0c bc 30 f2 74 74 6f 64  |+"'"):....0.ttod|
00003500  5f 67 65 74 5f 78 79 28  a4 67 65 74 5f 73 74 72  |_get_xy(.get_str|
00003510  28 74 74 6f 64 5f 77 6f  72 6b 25 21 38 29 2c 20  |(ttod_work%!8), |
00003520  78 31 2c 20 79 31 29 0d  0c c6 31 f2 74 74 6f 64  |x1, y1)...1.ttod|
00003530  5f 67 65 74 5f 78 79 28  a4 67 65 74 5f 73 74 72  |_get_xy(.get_str|
00003540  28 74 74 6f 64 5f 77 6f  72 6b 25 21 31 32 29 2c  |(ttod_work%!12),|
00003550  20 78 32 2c 20 79 32 29  0d 0c d0 25 78 31 3d 78  | x2, y2)...%x1=x|
00003560  31 2a 74 74 6f 64 5f 73  63 61 6c 65 3a 78 32 3d  |1*ttod_scale:x2=|
00003570  78 32 2a 74 74 6f 64 5f  73 63 61 6c 65 0d 0c da  |x2*ttod_scale...|
00003580  25 79 31 3d 79 31 2a 74  74 6f 64 5f 73 63 61 6c  |%y1=y1*ttod_scal|
00003590  65 3a 79 32 3d 79 32 2a  74 74 6f 64 5f 73 63 61  |e:y2=y2*ttod_sca|
000035a0  6c 65 0d 0c e4 35 e7 20  78 31 3c 78 32 20 8c 20  |le...5. x1<x2 . |
000035b0  78 5f 6c 6f 77 3d 78 31  3a 78 5f 68 69 67 68 3d  |x_low=x1:x_high=|
000035c0  78 32 20 8b 20 78 5f 6c  6f 77 3d 78 32 3a 78 5f  |x2 . x_low=x2:x_|
000035d0  68 69 67 68 3d 78 31 0d  0c ee 35 e7 20 79 31 3c  |high=x1...5. y1<|
000035e0  79 32 20 8c 20 79 5f 6c  6f 77 3d 79 31 3a 79 5f  |y2 . y_low=y1:y_|
000035f0  68 69 67 68 3d 79 32 20  8b 20 79 5f 6c 6f 77 3d  |high=y2 . y_low=|
00003600  79 32 3a 79 5f 68 69 67  68 3d 79 31 0d 0c f8 53  |y2:y_high=y1...S|
00003610  f2 74 74 6f 64 5f 70 75  74 5f 68 65 61 64 28 6f  |.ttod_put_head(o|
00003620  75 74 5f 66 69 6c 65 25  2c 20 35 2c 20 32 34 2b  |ut_file%, 5, 24+|
00003630  28 28 6c 65 6e 25 2b 33  29 20 80 20 ac 20 33 29  |((len%+3) . . 3)|
00003640  2c 20 78 5f 6c 6f 77 2c  20 79 5f 6c 6f 77 2c 20  |, x_low, y_low, |
00003650  78 5f 68 69 67 68 2c 20  79 5f 68 69 67 68 29 0d  |x_high, y_high).|
00003660  0d 02 13 cf 23 69 6e 5f  66 69 6c 65 25 3d 74 6d  |....#in_file%=tm|
00003670  70 25 0d 0d 0c 12 e7 20  6c 65 6e 25 3c 3d 31 30  |p%..... len%<=10|
00003680  32 34 20 8c 0d 0d 16 29  20 c8 99 20 26 63 2c 20  |24 ....) .. &c, |
00003690  34 2c 20 69 6e 5f 66 69  6c 65 25 2c 20 74 74 6f  |4, in_file%, tto|
000036a0  64 5f 77 6f 72 6b 25 2c  20 6c 65 6e 25 0d 0d 20  |d_work%, len%.. |
000036b0  2a 20 c8 99 20 26 63 2c  20 32 2c 20 6f 75 74 5f  |* .. &c, 2, out_|
000036c0  66 69 6c 65 25 2c 20 74  74 6f 64 5f 77 6f 72 6b  |file%, ttod_work|
000036d0  25 2c 20 6c 65 6e 25 0d  0d 2a 05 cc 0d 0d 34 0b  |%, len%..*....4.|
000036e0  20 74 6d 70 25 3d 30 0d  0d 3e 0e 20 c8 95 20 74  | tmp%=0..>. .. t|
000036f0  6d 70 25 3d 30 0d 0d 48  34 20 20 c8 99 20 26 63  |mp%=0..H4  .. &c|
00003700  2c 20 34 2c 20 69 6e 5f  66 69 6c 65 25 2c 20 74  |, 4, in_file%, t|
00003710  74 6f 64 5f 77 6f 72 6b  25 2c 20 31 30 32 34 20  |tod_work%, 1024 |
00003720  b8 20 2c 2c 2c 74 6d 70  25 0d 0d 52 30 20 20 c8  |. ,,,tmp%..R0  .|
00003730  99 20 26 63 2c 20 32 2c  20 6f 75 74 5f 66 69 6c  |. &c, 2, out_fil|
00003740  65 25 2c 20 74 74 6f 64  5f 77 6f 72 6b 25 2c 20  |e%, ttod_work%, |
00003750  31 30 32 34 2d 74 6d 70  25 0d 0d 5c 06 20 ce 0d  |1024-tmp%..\. ..|
00003760  0d 66 05 cd 0d 0d 70 0e  d9 23 69 6e 5f 66 69 6c  |.f....p..#in_fil|
00003770  65 25 0d 0d 7a 05 e1 0d  0d 84 05 3a 0d 0d 8e 32  |e%..z......:...2|
00003780  dd 20 f2 74 74 6f 64 5f  67 65 6e 65 72 61 74 65  |. .ttod_generate|
00003790  5f 6f 76 61 6c 28 66 69  6c 65 25 2c 20 70 61 72  |_oval(file%, par|
000037a0  61 6d 24 2c 20 6c 69 6e  65 5f 6e 6f 25 29 0d 0d  |am$, line_no%)..|
000037b0  98 3a ea 20 78 2c 20 79  2c 20 68 6f 72 7a 2c 20  |.:. x, y, horz, |
000037c0  76 65 72 74 2c 20 77 69  64 74 68 2c 20 6c 69 6e  |vert, width, lin|
000037d0  65 5f 63 6f 6c 25 2c 20  66 69 6c 6c 5f 63 6f 6c  |e_col%, fill_col|
000037e0  25 2c 20 63 6f 6e 73 74  0d 0d a2 2d 77 69 64 74  |%, const...-widt|
000037f0  68 3d 30 3a 63 6f 6c 6f  75 72 25 3d 26 30 30 30  |h=0:colour%=&000|
00003800  30 30 30 3a 63 6f 6e 73  74 3d 30 2e 35 35 32 32  |000:const=0.5522|
00003810  35 36 39 34 34 0d 0d ac  46 c8 99 20 26 32 30 30  |56944...F.. &200|
00003820  34 39 2c 20 74 74 6f 64  5f 65 6c 6c 69 70 73 65  |49, ttod_ellipse|
00003830  5f 61 72 67 73 24 2c 20  70 61 72 61 6d 24 2c 20  |_args$, param$, |
00003840  74 74 6f 64 5f 77 6f 72  6b 25 2c 20 31 30 32 34  |ttod_work%, 1024|
00003850  20 b8 20 3b 73 74 61 74  75 73 25 0d 0d b6 3e e7  | . ;status%...>.|
00003860  20 28 73 74 61 74 75 73  25 20 80 20 31 29 3d 31  | (status% . 1)=1|
00003870  20 8c 20 f2 74 74 6f 64  5f 65 72 72 6f 72 28 22  | . .ttod_error("|
00003880  53 79 6e 74 61 78 20 65  72 72 6f 72 22 2c 6c 69  |Syntax error",li|
00003890  6e 65 5f 6e 6f 25 29 3a  e1 0d 0d c0 6a e7 20 74  |ne_no%):....j. t|
000038a0  74 6f 64 5f 77 6f 72 6b  25 21 30 3d 30 20 8c 20  |tod_work%!0=0 . |
000038b0  f2 74 74 6f 64 5f 65 72  72 6f 72 28 22 4d 69 73  |.ttod_error("Mis|
000038c0  73 69 6e 67 20 63 65 6e  74 72 65 20 70 6f 73 69  |sing centre posi|
000038d0  74 69 6f 6e 20 64 65 66  69 6e 69 74 69 6f 6e 20  |tion definition |
000038e0  66 72 6f 6d 20 27 65 6c  6c 69 70 73 65 27 20 63  |from 'ellipse' c|
000038f0  6f 6d 6d 61 6e 64 22 2c  6c 69 6e 65 5f 6e 6f 25  |ommand",line_no%|
00003900  29 3a e1 0d 0d ca 6a e7  20 74 74 6f 64 5f 77 6f  |):....j. ttod_wo|
00003910  72 6b 25 21 34 3d 30 20  8c 20 f2 74 74 6f 64 5f  |rk%!4=0 . .ttod_|
00003920  65 72 72 6f 72 28 22 4d  69 73 73 69 6e 67 20 68  |error("Missing h|
00003930  6f 72 69 7a 6f 6e 74 61  6c 20 73 69 7a 65 20 64  |orizontal size d|
00003940  65 66 69 6e 69 74 69 6f  6e 20 66 72 6f 6d 20 27  |efinition from '|
00003950  65 6c 6c 69 70 73 65 27  20 63 6f 6d 6d 61 6e 64  |ellipse' command|
00003960  22 2c 6c 69 6e 65 5f 6e  6f 25 29 3a e1 0d 0d d4  |",line_no%):....|
00003970  68 e7 20 74 74 6f 64 5f  77 6f 72 6b 25 21 38 3d  |h. ttod_work%!8=|
00003980  30 20 8c 20 f2 74 74 6f  64 5f 65 72 72 6f 72 28  |0 . .ttod_error(|
00003990  22 4d 69 73 73 69 6e 67  20 76 65 72 74 69 63 61  |"Missing vertica|
000039a0  6c 20 73 69 7a 65 20 64  65 66 69 6e 69 74 69 6f  |l size definitio|
000039b0  6e 20 66 72 6f 6d 20 27  65 6c 6c 69 70 73 65 27  |n from 'ellipse'|
000039c0  20 63 6f 6d 6d 61 6e 64  22 2c 6c 69 6e 65 5f 6e  | command",line_n|
000039d0  6f 25 29 3a e1 0d 0d de  2d f2 74 74 6f 64 5f 67  |o%):....-.ttod_g|
000039e0  65 74 5f 78 79 28 a4 67  65 74 5f 73 74 72 28 74  |et_xy(.get_str(t|
000039f0  74 6f 64 5f 77 6f 72 6b  25 21 30 29 2c 20 78 2c  |tod_work%!0), x,|
00003a00  79 29 0d 0d e8 41 68 6f  72 7a 3d bb 28 a4 67 65  |y)...Ahorz=.(.ge|
00003a10  74 5f 73 74 72 28 74 74  6f 64 5f 77 6f 72 6b 25  |t_str(ttod_work%|
00003a20  21 34 29 29 3a 76 65 72  74 3d bb 28 a4 67 65 74  |!4)):vert=.(.get|
00003a30  5f 73 74 72 28 74 74 6f  64 5f 77 6f 72 6b 25 21  |_str(ttod_work%!|
00003a40  38 29 29 0d 0d f2 3d e7  20 74 74 6f 64 5f 77 6f  |8))...=. ttod_wo|
00003a50  72 6b 25 21 31 32 3c 3e  30 20 8c 20 77 69 64 74  |rk%!12<>0 . widt|
00003a60  68 3d bb 28 a4 67 65 74  5f 73 74 72 28 74 74 6f  |h=.(.get_str(tto|
00003a70  64 5f 77 6f 72 6b 25 21  31 32 29 29 2a 36 34 30  |d_work%!12))*640|
00003a80  0d 0d fc 3d e7 20 74 74  6f 64 5f 77 6f 72 6b 25  |...=. ttod_work%|
00003a90  21 31 36 3c 3e 30 20 8c  20 6c 69 6e 65 5f 63 6f  |!16<>0 . line_co|
00003aa0  6c 25 3d a0 28 a4 67 65  74 5f 73 74 72 28 74 74  |l%=.(.get_str(tt|
00003ab0  6f 64 5f 77 6f 72 6b 25  21 31 36 29 29 0d 0e 06  |od_work%!16))...|
00003ac0  3d e7 20 74 74 6f 64 5f  77 6f 72 6b 25 21 32 30  |=. ttod_work%!20|
00003ad0  3c 3e 30 20 8c 20 66 69  6c 6c 5f 63 6f 6c 25 3d  |<>0 . fill_col%=|
00003ae0  a0 28 a4 67 65 74 5f 73  74 72 28 74 74 6f 64 5f  |.(.get_str(ttod_|
00003af0  77 6f 72 6b 25 21 32 30  29 29 0d 0e 10 4b 78 3d  |work%!20))...Kx=|
00003b00  78 2a 74 74 6f 64 5f 73  63 61 6c 65 3a 79 3d 79  |x*ttod_scale:y=y|
00003b10  2a 74 74 6f 64 5f 73 63  61 6c 65 3a 68 6f 72 7a  |*ttod_scale:horz|
00003b20  3d 68 6f 72 7a 2a 74 74  6f 64 5f 73 63 61 6c 65  |=horz*ttod_scale|
00003b30  3a 76 65 72 74 3d 76 65  72 74 2a 74 74 6f 64 5f  |:vert=vert*ttod_|
00003b40  73 63 61 6c 65 0d 0e 1a  3e f2 74 74 6f 64 5f 70  |scale...>.ttod_p|
00003b50  75 74 5f 68 65 61 64 28  66 69 6c 65 25 2c 20 32  |ut_head(file%, 2|
00003b60  2c 20 31 37 32 2c 20 78  2d 68 6f 72 7a 2c 79 2d  |, 172, x-horz,y-|
00003b70  76 65 72 74 2c 78 2b 68  6f 72 7a 2c 79 2b 76 65  |vert,x+horz,y+ve|
00003b80  72 74 29 0d 0e 24 1b f2  77 70 75 74 28 66 69 6c  |rt)..$..wput(fil|
00003b90  65 25 2c 20 66 69 6c 6c  5f 63 6f 6c 25 29 0d 0e  |e%, fill_col%)..|
00003ba0  2e 1b f2 77 70 75 74 28  66 69 6c 65 25 2c 20 6c  |...wput(file%, l|
00003bb0  69 6e 65 5f 63 6f 6c 25  29 0d 0e 38 17 f2 77 70  |ine_col%)..8..wp|
00003bc0  75 74 28 66 69 6c 65 25  2c 20 77 69 64 74 68 29  |ut(file%, width)|
00003bd0  0d 0e 42 1b f2 77 70 75  74 28 66 69 6c 65 25 2c  |..B..wput(file%,|
00003be0  20 25 30 30 30 30 30 30  30 30 29 0d 0e 4c 27 f2  | %00000000)..L'.|
00003bf0  74 74 6f 64 5f 70 75 74  5f 70 61 74 68 28 66 69  |ttod_put_path(fi|
00003c00  6c 65 25 2c 20 32 2c 20  78 2c 20 79 2d 76 65 72  |le%, 2, x, y-ver|
00003c10  74 29 0d 0e 56 52 f2 74  74 6f 64 5f 70 75 74 5f  |t)..VR.ttod_put_|
00003c20  62 65 7a 69 65 72 28 66  69 6c 65 25 2c 20 78 2b  |bezier(file%, x+|
00003c30  68 6f 72 7a 2c 20 79 2c  20 78 2b 68 6f 72 7a 2a  |horz, y, x+horz*|
00003c40  63 6f 6e 73 74 2c 20 79  2d 76 65 72 74 2c 20 78  |const, y-vert, x|
00003c50  2b 68 6f 72 7a 2c 20 79  2d 76 65 72 74 2a 63 6f  |+horz, y-vert*co|
00003c60  6e 73 74 29 0d 0e 60 52  f2 74 74 6f 64 5f 70 75  |nst)..`R.ttod_pu|
00003c70  74 5f 62 65 7a 69 65 72  28 66 69 6c 65 25 2c 20  |t_bezier(file%, |
00003c80  78 2c 20 79 2b 76 65 72  74 2c 20 78 2b 68 6f 72  |x, y+vert, x+hor|
00003c90  7a 2c 20 79 2b 76 65 72  74 2a 63 6f 6e 73 74 2c  |z, y+vert*const,|
00003ca0  20 78 2b 68 6f 72 7a 2a  63 6f 6e 73 74 2c 20 79  | x+horz*const, y|
00003cb0  2b 76 65 72 74 29 0d 0e  6a 52 f2 74 74 6f 64 5f  |+vert)..jR.ttod_|
00003cc0  70 75 74 5f 62 65 7a 69  65 72 28 66 69 6c 65 25  |put_bezier(file%|
00003cd0  2c 20 78 2d 68 6f 72 7a  2c 20 79 2c 20 78 2d 68  |, x-horz, y, x-h|
00003ce0  6f 72 7a 2a 63 6f 6e 73  74 2c 20 79 2b 76 65 72  |orz*const, y+ver|
00003cf0  74 2c 20 78 2d 68 6f 72  7a 2c 20 79 2b 76 65 72  |t, x-horz, y+ver|
00003d00  74 2a 63 6f 6e 73 74 29  0d 0e 74 52 f2 74 74 6f  |t*const)..tR.tto|
00003d10  64 5f 70 75 74 5f 62 65  7a 69 65 72 28 66 69 6c  |d_put_bezier(fil|
00003d20  65 25 2c 20 78 2c 20 79  2d 76 65 72 74 2c 20 78  |e%, x, y-vert, x|
00003d30  2d 68 6f 72 7a 2c 20 79  2d 76 65 72 74 2a 63 6f  |-horz, y-vert*co|
00003d40  6e 73 74 2c 20 78 2d 68  6f 72 7a 2a 63 6f 6e 73  |nst, x-horz*cons|
00003d50  74 2c 20 79 2d 76 65 72  74 29 0d 0e 7e 13 f2 77  |t, y-vert)..~..w|
00003d60  70 75 74 28 66 69 6c 65  25 2c 20 35 29 0d 0e 88  |put(file%, 5)...|
00003d70  13 f2 77 70 75 74 28 66  69 6c 65 25 2c 20 30 29  |..wput(file%, 0)|
00003d80  0d 0e 92 05 e1 0d 0e 9c  05 3a 0d 0e a6 42 dd 20  |.........:...B. |
00003d90  f2 74 74 6f 64 5f 67 65  6e 65 72 61 74 65 5f 70  |.ttod_generate_p|
00003da0  61 74 68 28 69 6e 5f 66  69 6c 65 25 2c 20 6f 75  |ath(in_file%, ou|
00003db0  74 5f 66 69 6c 65 25 2c  20 70 61 72 61 6d 24 2c  |t_file%, param$,|
00003dc0  20 f8 20 6c 69 6e 65 5f  6e 6f 25 29 0d 0e b0 66  | . line_no%)...f|
00003dd0  ea 20 69 6e 24 2c 20 63  6f 6d 24 2c 20 70 61 72  |. in$, com$, par|
00003de0  24 2c 20 73 74 61 74 75  73 25 2c 20 68 65 61 64  |$, status%, head|
00003df0  5f 70 6f 73 25 2c 20 78  5f 6c 6f 77 2c 20 78 5f  |_pos%, x_low, x_|
00003e00  68 69 67 68 2c 20 79 5f  6c 6f 77 2c 20 79 5f 68  |high, y_low, y_h|
00003e10  69 67 68 2c 20 73 75 62  25 2c 20 78 31 2c 20 78  |igh, sub%, x1, x|
00003e20  32 2c 20 79 31 2c 20 79  32 2c 20 66 69 6e 69 73  |2, y1, y2, finis|
00003e30  68 25 0d 0e ba 46 66 69  6e 69 73 68 25 3d a3 3a  |h%...Ffinish%=.:|
00003e40  73 75 62 25 3d a3 3a 78  5f 6c 6f 77 3d 26 37 46  |sub%=.:x_low=&7F|
00003e50  46 46 46 46 46 46 3a 78  5f 68 69 67 68 3d 30 3a  |FFFFFF:x_high=0:|
00003e60  79 5f 6c 6f 77 3d 26 37  46 46 46 46 46 46 46 3a  |y_low=&7FFFFFFF:|
00003e70  79 5f 68 69 67 68 3d 30  0d 0e c4 19 68 65 61 64  |y_high=0....head|
00003e80  5f 70 6f 73 25 3d 8f 23  6f 75 74 5f 66 69 6c 65  |_pos%=.#out_file|
00003e90  25 0d 0e ce 2f f2 74 74  6f 64 5f 70 75 74 5f 68  |%.../.ttod_put_h|
00003ea0  65 61 64 28 6f 75 74 5f  66 69 6c 65 25 2c 20 32  |ead(out_file%, 2|
00003eb0  2c 20 30 2c 20 30 2c 20  30 2c 20 30 2c 20 30 29  |, 0, 0, 0, 0, 0)|
00003ec0  0d 0e d8 43 c8 99 20 26  32 30 30 34 39 2c 20 74  |...C.. &20049, t|
00003ed0  74 6f 64 5f 70 61 74 68  5f 61 72 67 73 24 2c 20  |tod_path_args$, |
00003ee0  70 61 72 61 6d 24 2c 20  74 74 6f 64 5f 77 6f 72  |param$, ttod_wor|
00003ef0  6b 25 2c 20 31 30 32 34  20 b8 20 3b 73 74 61 74  |k%, 1024 . ;stat|
00003f00  75 73 25 0d 0e e2 50 e7  20 28 73 74 61 74 75 73  |us%...P. (status|
00003f10  25 20 80 20 31 29 3d 31  20 8c 20 f2 74 74 6f 64  |% . 1)=1 . .ttod|
00003f20  5f 65 72 72 6f 72 28 22  53 79 6e 74 61 78 20 65  |_error("Syntax e|
00003f30  72 72 6f 72 20 69 6e 20  63 6f 6d 6d 61 6e 64 20  |rror in command |
00003f40  27 70 61 74 68 27 22 2c  6c 69 6e 65 5f 6e 6f 25  |'path'",line_no%|
00003f50  29 3a e1 0d 0e ec 60 e7  20 74 74 6f 64 5f 77 6f  |):....`. ttod_wo|
00003f60  72 6b 25 21 38 3d 30 20  8c 20 f2 77 70 75 74 28  |rk%!8=0 . .wput(|
00003f70  6f 75 74 5f 66 69 6c 65  25 2c 20 26 46 46 46 46  |out_file%, &FFFF|
00003f80  46 46 30 30 29 20 8b 20  f2 77 70 75 74 28 6f 75  |FF00) . .wput(ou|
00003f90  74 5f 66 69 6c 65 25 2c  20 bb 28 a4 67 65 74 5f  |t_file%, .(.get_|
00003fa0  73 74 72 28 74 74 6f 64  5f 77 6f 72 6b 25 21 30  |str(ttod_work%!0|
00003fb0  29 29 29 0d 0e f6 58 e7  20 74 74 6f 64 5f 77 6f  |)))...X. ttod_wo|
00003fc0  72 6b 25 21 34 3d 30 20  8c 20 f2 77 70 75 74 28  |rk%!4=0 . .wput(|
00003fd0  6f 75 74 5f 66 69 6c 65  25 2c 20 30 29 20 8b 20  |out_file%, 0) . |
00003fe0  f2 77 70 75 74 28 6f 75  74 5f 66 69 6c 65 25 2c  |.wput(out_file%,|
00003ff0  20 bb 28 a4 67 65 74 5f  73 74 72 28 74 74 6f 64  | .(.get_str(ttod|
00004000  5f 77 6f 72 6b 25 21 30  29 29 29 0d 0f 00 5c e7  |_work%!0)))...\.|
00004010  20 74 74 6f 64 5f 77 6f  72 6b 25 21 30 3d 30 20  | ttod_work%!0=0 |
00004020  8c 20 f2 77 70 75 74 28  6f 75 74 5f 66 69 6c 65  |. .wput(out_file|
00004030  25 2c 20 30 29 20 8b 20  f2 77 70 75 74 28 6f 75  |%, 0) . .wput(ou|
00004040  74 5f 66 69 6c 65 25 2c  20 bb 28 a4 67 65 74 5f  |t_file%, .(.get_|
00004050  73 74 72 28 74 74 6f 64  5f 77 6f 72 6b 25 21 30  |str(ttod_work%!0|
00004060  29 29 2a 36 34 30 29 0d  0f 0a 17 f2 77 70 75 74  |))*640).....wput|
00004070  28 6f 75 74 5f 66 69 6c  65 25 2c 20 30 29 0d 0f  |(out_file%, 0)..|
00004080  14 24 c8 95 20 28 66 69  6e 69 73 68 25 3d a3 29  |.$.. (finish%=.)|
00004090  20 80 20 28 ac 20 74 74  6f 64 5f 65 72 72 6f 72  | . (. ttod_error|
000040a0  25 29 0d 0f 1e 22 20 69  6e 24 3d a4 73 74 72 69  |%)..." in$=.stri|
000040b0  70 5f 73 70 61 63 65 73  28 be 23 69 6e 5f 66 69  |p_spaces(.#in_fi|
000040c0  6c 65 25 29 0d 0f 28 10  20 6c 69 6e 65 5f 6e 6f  |le%)..(. line_no|
000040d0  25 2b 3d 31 0d 0f 32 29  20 73 74 61 74 75 73 25  |%+=1..2) status%|
000040e0  3d a4 74 74 6f 64 5f 70  61 72 73 65 28 69 6e 24  |=.ttod_parse(in$|
000040f0  2c 20 63 6f 6d 24 2c 20  70 61 72 24 29 0d 0f 3c  |, com$, par$)..<|
00004100  0e 20 c8 8e 20 63 6f 6d  24 20 ca 0d 0f 46 10 20  |. .. com$ ...F. |
00004110  20 c9 20 22 64 72 61 77  22 20 3a 0d 0f 50 11 20  | . "draw" :..P. |
00004120  20 20 e7 20 ac 20 73 75  62 25 20 8c 0d 0f 5a 47  |  . . sub% ...ZG|
00004130  20 20 20 20 f2 74 74 6f  64 5f 65 72 72 6f 72 28  |    .ttod_error(|
00004140  22 4e 6f 74 20 69 6e 20  61 20 73 75 62 2d 70 61  |"Not in a sub-pa|
00004150  74 68 20 66 6f 72 20 27  64 72 61 77 27 20 63 6f  |th for 'draw' co|
00004160  6d 6d 61 6e 64 22 2c 20  6c 69 6e 65 5f 6e 6f 25  |mmand", line_no%|
00004170  29 3a e1 0d 0f 64 08 20  20 20 cc 0d 0f 6e 3a 20  |):...d.   ...n: |
00004180  20 20 20 f2 74 74 6f 64  5f 70 61 74 68 5f 64 72  |   .ttod_path_dr|
00004190  61 77 28 6f 75 74 5f 66  69 6c 65 25 2c 20 70 61  |aw(out_file%, pa|
000041a0  72 24 2c 20 6c 69 6e 65  5f 6e 6f 25 2c 20 78 31  |r$, line_no%, x1|
000041b0  2c 20 79 31 29 0d 0f 78  1f 20 20 20 20 e7 20 78  |, y1)..x.    . x|
000041c0  31 3e 78 5f 68 69 67 68  20 8c 20 78 5f 68 69 67  |1>x_high . x_hig|
000041d0  68 3d 78 31 0d 0f 82 1e  20 20 20 20 e7 20 78 31  |h=x1....    . x1|
000041e0  3c 78 5f 6c 6f 77 20 20  8c 20 78 5f 6c 6f 77 3d  |<x_low  . x_low=|
000041f0  78 31 0d 0f 8c 1f 20 20  20 20 e7 20 79 31 3e 79  |x1....    . y1>y|
00004200  5f 68 69 67 68 20 8c 20  79 5f 68 69 67 68 3d 79  |_high . y_high=y|
00004210  31 0d 0f 96 1e 20 20 20  20 e7 20 79 31 3c 79 5f  |1....    . y1<y_|
00004220  6c 6f 77 20 20 8c 20 79  5f 6c 6f 77 3d 79 31 0d  |low  . y_low=y1.|
00004230  0f a0 08 20 20 20 cd 0d  0f aa 10 20 20 c9 20 22  |...   .....  . "|
00004240  6d 6f 76 65 22 20 3a 0d  0f b4 0d 20 20 20 73 75  |move" :....   su|
00004250  62 25 3d b9 0d 0f be 39  20 20 20 f2 74 74 6f 64  |b%=....9   .ttod|
00004260  5f 70 61 74 68 5f 6d 6f  76 65 28 6f 75 74 5f 66  |_path_move(out_f|
00004270  69 6c 65 25 2c 20 70 61  72 24 2c 20 6c 69 6e 65  |ile%, par$, line|
00004280  5f 6e 6f 25 2c 20 78 31  2c 20 79 31 29 0d 0f c8  |_no%, x1, y1)...|
00004290  1e 20 20 20 e7 20 78 31  3e 78 5f 68 69 67 68 20  |.   . x1>x_high |
000042a0  8c 20 78 5f 68 69 67 68  3d 78 31 0d 0f d2 1d 20  |. x_high=x1.... |
000042b0  20 20 e7 20 78 31 3c 78  5f 6c 6f 77 20 20 8c 20  |  . x1<x_low  . |
000042c0  78 5f 6c 6f 77 3d 78 31  0d 0f dc 1e 20 20 20 e7  |x_low=x1....   .|
000042d0  20 79 31 3e 79 5f 68 69  67 68 20 8c 20 79 5f 68  | y1>y_high . y_h|
000042e0  69 67 68 3d 79 31 0d 0f  e6 1d 20 20 20 e7 20 79  |igh=y1....   . y|
000042f0  31 3c 79 5f 6c 6f 77 20  20 8c 20 79 5f 6c 6f 77  |1<y_low  . y_low|
00004300  3d 79 31 0d 0f f0 11 20  20 c9 20 22 63 75 72 76  |=y1....  . "curv|
00004310  65 22 20 3a 0d 0f fa 42  20 20 20 f2 74 74 6f 64  |e" :...B   .ttod|
00004320  5f 70 61 74 68 5f 63 75  72 76 65 28 6f 75 74 5f  |_path_curve(out_|
00004330  66 69 6c 65 25 2c 20 70  61 72 24 2c 20 6c 69 6e  |file%, par$, lin|
00004340  65 5f 6e 6f 25 2c 20 78  31 2c 20 79 31 2c 20 78  |e_no%, x1, y1, x|
00004350  32 2c 20 79 32 29 0d 10  04 1e 20 20 20 e7 20 78  |2, y2)....   . x|
00004360  31 3e 78 5f 68 69 67 68  20 8c 20 78 5f 68 69 67  |1>x_high . x_hig|
00004370  68 3d 78 31 0d 10 0e 1d  20 20 20 e7 20 78 31 3c  |h=x1....   . x1<|
00004380  78 5f 6c 6f 77 20 20 8c  20 78 5f 6c 6f 77 3d 78  |x_low  . x_low=x|
00004390  31 0d 10 18 1e 20 20 20  e7 20 79 31 3e 79 5f 68  |1....   . y1>y_h|
000043a0  69 67 68 20 8c 20 79 5f  68 69 67 68 3d 79 31 0d  |igh . y_high=y1.|
000043b0  10 22 1d 20 20 20 e7 20  79 31 3c 79 5f 6c 6f 77  |.".   . y1<y_low|
000043c0  20 20 8c 20 79 5f 6c 6f  77 3d 79 31 0d 10 2c 1e  |  . y_low=y1..,.|
000043d0  20 20 20 e7 20 78 32 3e  78 5f 68 69 67 68 20 8c  |   . x2>x_high .|
000043e0  20 78 5f 68 69 67 68 3d  78 32 0d 10 36 1d 20 20  | x_high=x2..6.  |
000043f0  20 e7 20 78 32 3c 78 5f  6c 6f 77 20 20 8c 20 78  | . x2<x_low  . x|
00004400  5f 6c 6f 77 3d 78 32 0d  10 40 1e 20 20 20 e7 20  |_low=x2..@.   . |
00004410  79 32 3e 79 5f 68 69 67  68 20 8c 20 79 5f 68 69  |y2>y_high . y_hi|
00004420  67 68 3d 79 32 0d 10 4a  1d 20 20 20 e7 20 79 32  |gh=y2..J.   . y2|
00004430  3c 79 5f 6c 6f 77 20 20  8c 20 79 5f 6c 6f 77 3d  |<y_low  . y_low=|
00004440  79 32 0d 10 54 11 20 20  c9 20 22 63 6c 6f 73 65  |y2..T.  . "close|
00004450  22 20 3a 0d 10 5e 11 20  20 20 e7 20 73 75 62 25  |" :..^.   . sub%|
00004460  3d a3 20 8c 0d 10 68 48  20 20 20 20 f2 74 74 6f  |=. ...hH    .tto|
00004470  64 5f 65 72 72 6f 72 28  22 4e 6f 74 20 69 6e 20  |d_error("Not in |
00004480  61 20 73 75 62 2d 70 61  74 68 20 66 6f 72 20 27  |a sub-path for '|
00004490  63 6c 6f 73 65 27 20 63  6f 6d 6d 61 6e 64 22 2c  |close' command",|
000044a0  20 6c 69 6e 65 5f 6e 6f  25 29 3a e1 0d 10 72 08  | line_no%):...r.|
000044b0  20 20 20 cc 0d 10 7c 0e  20 20 20 20 73 75 62 25  |   ...|.    sub%|
000044c0  3d a3 0d 10 86 1b 20 20  20 20 f2 77 70 75 74 28  |=.....    .wput(|
000044d0  6f 75 74 5f 66 69 6c 65  25 2c 20 35 29 0d 10 90  |out_file%, 5)...|
000044e0  08 20 20 20 cd 0d 10 9a  0f 20 20 c9 20 22 65 6e  |.   .....  . "en|
000044f0  64 22 20 3a 0d 10 a4 1a  20 20 20 f2 77 70 75 74  |d" :....   .wput|
00004500  28 6f 75 74 5f 66 69 6c  65 25 2c 20 30 29 0d 10  |(out_file%, 0)..|
00004510  ae 10 20 20 20 66 69 6e  69 73 68 25 3d b9 0d 10  |..   finish%=...|
00004520  b8 08 20 7f 20 3a 0d 10  c2 53 20 20 e7 20 c0 63  |.. . :...S  . .c|
00004530  6f 6d 24 2c 20 31 29 3c  3e 22 23 22 20 8c 20 f2  |om$, 1)<>"#" . .|
00004540  74 74 6f 64 5f 65 72 72  6f 72 28 22 49 6c 6c 65  |ttod_error("Ille|
00004550  67 61 6c 20 63 6f 6d 6d  61 6e 64 20 69 6e 20 70  |gal command in p|
00004560  61 74 68 20 73 65 67 6d  65 6e 74 22 2c 20 6c 69  |ath segment", li|
00004570  6e 65 5f 6e 6f 25 29 3a  e1 0d 10 cc 06 20 cb 0d  |ne_no%):..... ..|
00004580  10 d6 05 ce 0d 10 e0 20  6c 65 6e 25 3d 8f 23 6f  |....... len%=.#o|
00004590  75 74 5f 66 69 6c 65 25  20 2d 20 68 65 61 64 5f  |ut_file% - head_|
000045a0  70 6f 73 25 0d 10 ea 19  cf 23 6f 75 74 5f 66 69  |pos%.....#out_fi|
000045b0  6c 65 25 3d 68 65 61 64  5f 70 6f 73 25 0d 10 f4  |le%=head_pos%...|
000045c0  44 f2 74 74 6f 64 5f 70  75 74 5f 68 65 61 64 28  |D.ttod_put_head(|
000045d0  6f 75 74 5f 66 69 6c 65  25 2c 20 32 2c 20 6c 65  |out_file%, 2, le|
000045e0  6e 25 2c 20 78 5f 6c 6f  77 2c 20 79 5f 6c 6f 77  |n%, x_low, y_low|
000045f0  2c 20 78 5f 68 69 67 68  2c 20 79 5f 68 69 67 68  |, x_high, y_high|
00004600  29 0d 10 fe 1b cf 23 6f  75 74 5f 66 69 6c 65 25  |).....#out_file%|
00004610  3d a2 23 6f 75 74 5f 66  69 6c 65 25 0d 11 08 05  |=.#out_file%....|
00004620  e1 0d 11 12 05 3a 0d 11  1c 35 dd 20 f2 74 74 6f  |.....:...5. .tto|
00004630  64 5f 70 61 74 68 5f 6d  6f 76 65 28 66 69 6c 65  |d_path_move(file|
00004640  25 2c 20 70 61 72 61 6d  24 2c 20 6c 69 6e 65 25  |%, param$, line%|
00004650  2c 20 f8 20 78 2c 20 f8  20 79 29 0d 11 26 42 c8  |, . x, . y)..&B.|
00004660  99 20 26 32 30 30 34 39  2c 20 74 74 6f 64 5f 6f  |. &20049, ttod_o|
00004670  6e 65 5f 61 72 67 73 24  2c 20 70 61 72 61 6d 24  |ne_args$, param$|
00004680  2c 20 74 74 6f 64 5f 77  6f 72 6b 25 2c 20 31 30  |, ttod_work%, 10|
00004690  32 34 20 b8 20 3b 73 74  61 74 75 73 25 0d 11 30  |24 . ;status%..0|
000046a0  50 e7 20 28 73 74 61 74  75 73 25 20 80 20 31 29  |P. (status% . 1)|
000046b0  3d 31 20 8c 20 f2 74 74  6f 64 5f 65 72 72 6f 72  |=1 . .ttod_error|
000046c0  28 22 53 79 6e 74 61 78  20 65 72 72 6f 72 20 69  |("Syntax error i|
000046d0  6e 20 27 6d 6f 76 65 27  20 63 6f 6d 6d 61 6e 64  |n 'move' command|
000046e0  22 2c 6c 69 6e 65 5f 6e  6f 25 29 3a e1 0d 11 3a  |",line_no%):...:|
000046f0  59 e7 20 74 74 6f 64 5f  77 6f 72 6b 25 21 30 3d  |Y. ttod_work%!0=|
00004700  30 20 8c 20 f2 74 74 6f  64 5f 65 72 72 6f 72 28  |0 . .ttod_error(|
00004710  22 4d 69 73 73 69 6e 67  20 63 6f 2d 6f 72 64 69  |"Missing co-ordi|
00004720  6e 61 74 65 73 20 66 72  6f 6d 20 27 6d 6f 76 65  |nates from 'move|
00004730  27 20 63 6f 6d 6d 61 6e  64 22 2c 6c 69 6e 65 5f  |' command",line_|
00004740  6e 6f 25 29 3a e1 0d 11  44 2e f2 74 74 6f 64 5f  |no%):...D..ttod_|
00004750  67 65 74 5f 78 79 28 a4  67 65 74 5f 73 74 72 28  |get_xy(.get_str(|
00004760  74 74 6f 64 5f 77 6f 72  6b 25 21 30 29 2c 20 78  |ttod_work%!0), x|
00004770  2c 20 79 29 0d 11 4e 21  78 3d 78 2a 74 74 6f 64  |, y)..N!x=x*ttod|
00004780  5f 73 63 61 6c 65 3a 79  3d 79 2a 74 74 6f 64 5f  |_scale:y=y*ttod_|
00004790  73 63 61 6c 65 0d 11 58  22 f2 74 74 6f 64 5f 70  |scale..X".ttod_p|
000047a0  75 74 5f 70 61 74 68 28  66 69 6c 65 25 2c 20 32  |ut_path(file%, 2|
000047b0  2c 20 78 2c 20 79 29 0d  11 62 05 e1 0d 11 6c 05  |, x, y)..b....l.|
000047c0  3a 0d 11 76 35 dd 20 f2  74 74 6f 64 5f 70 61 74  |:..v5. .ttod_pat|
000047d0  68 5f 64 72 61 77 28 66  69 6c 65 25 2c 20 70 61  |h_draw(file%, pa|
000047e0  72 61 6d 24 2c 20 6c 69  6e 65 25 2c 20 f8 20 78  |ram$, line%, . x|
000047f0  2c 20 f8 20 79 29 0d 11  80 42 c8 99 20 26 32 30  |, . y)...B.. &20|
00004800  30 34 39 2c 20 74 74 6f  64 5f 6f 6e 65 5f 61 72  |049, ttod_one_ar|
00004810  67 73 24 2c 20 70 61 72  61 6d 24 2c 20 74 74 6f  |gs$, param$, tto|
00004820  64 5f 77 6f 72 6b 25 2c  20 31 30 32 34 20 b8 20  |d_work%, 1024 . |
00004830  3b 73 74 61 74 75 73 25  0d 11 8a 50 e7 20 28 73  |;status%...P. (s|
00004840  74 61 74 75 73 25 20 80  20 31 29 3d 31 20 8c 20  |tatus% . 1)=1 . |
00004850  f2 74 74 6f 64 5f 65 72  72 6f 72 28 22 53 79 6e  |.ttod_error("Syn|
00004860  74 61 78 20 65 72 72 6f  72 20 69 6e 20 27 64 72  |tax error in 'dr|
00004870  61 77 27 20 63 6f 6d 6d  61 6e 64 22 2c 6c 69 6e  |aw' command",lin|
00004880  65 5f 6e 6f 25 29 3a e1  0d 11 94 59 e7 20 74 74  |e_no%):....Y. tt|
00004890  6f 64 5f 77 6f 72 6b 25  21 30 3d 30 20 8c 20 f2  |od_work%!0=0 . .|
000048a0  74 74 6f 64 5f 65 72 72  6f 72 28 22 4d 69 73 73  |ttod_error("Miss|
000048b0  69 6e 67 20 63 6f 2d 6f  72 64 69 6e 61 74 65 73  |ing co-ordinates|
000048c0  20 66 72 6f 6d 20 27 64  72 61 77 27 20 63 6f 6d  | from 'draw' com|
000048d0  6d 61 6e 64 22 2c 6c 69  6e 65 5f 6e 6f 25 29 3a  |mand",line_no%):|
000048e0  e1 0d 11 9e 2e f2 74 74  6f 64 5f 67 65 74 5f 78  |......ttod_get_x|
000048f0  79 28 a4 67 65 74 5f 73  74 72 28 74 74 6f 64 5f  |y(.get_str(ttod_|
00004900  77 6f 72 6b 25 21 30 29  2c 20 78 2c 20 79 29 0d  |work%!0), x, y).|
00004910  11 a8 21 78 3d 78 2a 74  74 6f 64 5f 73 63 61 6c  |..!x=x*ttod_scal|
00004920  65 3a 79 3d 79 2a 74 74  6f 64 5f 73 63 61 6c 65  |e:y=y*ttod_scale|
00004930  0d 11 b2 22 f2 74 74 6f  64 5f 70 75 74 5f 70 61  |...".ttod_put_pa|
00004940  74 68 28 66 69 6c 65 25  2c 20 38 2c 20 78 2c 20  |th(file%, 8, x, |
00004950  79 29 0d 11 bc 05 e1 0d  11 c6 05 3a 0d 11 d0 44  |y).........:...D|
00004960  dd 20 f2 74 74 6f 64 5f  70 61 74 68 5f 63 75 72  |. .ttod_path_cur|
00004970  76 65 28 66 69 6c 65 25  2c 20 70 61 72 61 6d 24  |ve(file%, param$|
00004980  2c 20 6c 69 6e 65 25 2c  20 f8 20 78 31 2c 20 f8  |, line%, . x1, .|
00004990  20 79 31 2c 20 f8 20 78  32 2c 20 f8 20 79 32 29  | y1, . x2, . y2)|
000049a0  0d 11 da 0a ea 20 78 2c  20 79 0d 11 e4 44 c8 99  |..... x, y...D..|
000049b0  20 26 32 30 30 34 39 2c  20 74 74 6f 64 5f 74 68  | &20049, ttod_th|
000049c0  72 65 65 5f 61 72 67 73  24 2c 20 70 61 72 61 6d  |ree_args$, param|
000049d0  24 2c 20 74 74 6f 64 5f  77 6f 72 6b 25 2c 20 31  |$, ttod_work%, 1|
000049e0  30 32 34 20 b8 20 3b 73  74 61 74 75 73 25 0d 11  |024 . ;status%..|
000049f0  ee 51 e7 20 28 73 74 61  74 75 73 25 20 80 20 31  |.Q. (status% . 1|
00004a00  29 3d 31 20 8c 20 f2 74  74 6f 64 5f 65 72 72 6f  |)=1 . .ttod_erro|
00004a10  72 28 22 53 79 6e 74 61  78 20 65 72 72 6f 72 20  |r("Syntax error |
00004a20  69 6e 20 27 63 75 72 76  65 27 20 63 6f 6d 6d 61  |in 'curve' comma|
00004a30  6e 64 22 2c 6c 69 6e 65  5f 6e 6f 25 29 3a e1 0d  |nd",line_no%):..|
00004a40  11 f8 5a e7 20 74 74 6f  64 5f 77 6f 72 6b 25 21  |..Z. ttod_work%!|
00004a50  30 3d 30 20 8c 20 f2 74  74 6f 64 5f 65 72 72 6f  |0=0 . .ttod_erro|
00004a60  72 28 22 4d 69 73 73 69  6e 67 20 63 6f 2d 6f 72  |r("Missing co-or|
00004a70  64 69 6e 61 74 65 73 20  66 72 6f 6d 20 27 63 75  |dinates from 'cu|
00004a80  72 76 65 27 20 63 6f 6d  6d 61 6e 64 22 2c 6c 69  |rve' command",li|
00004a90  6e 65 5f 6e 6f 25 29 3a  e1 0d 12 02 5a e7 20 74  |ne_no%):....Z. t|
00004aa0  74 6f 64 5f 77 6f 72 6b  25 21 34 3d 30 20 8c 20  |tod_work%!4=0 . |
00004ab0  f2 74 74 6f 64 5f 65 72  72 6f 72 28 22 4d 69 73  |.ttod_error("Mis|
00004ac0  73 69 6e 67 20 63 6f 2d  6f 72 64 69 6e 61 74 65  |sing co-ordinate|
00004ad0  73 20 66 72 6f 6d 20 27  63 75 72 76 65 27 20 63  |s from 'curve' c|
00004ae0  6f 6d 6d 61 6e 64 22 2c  6c 69 6e 65 5f 6e 6f 25  |ommand",line_no%|
00004af0  29 3a e1 0d 12 0c 5a e7  20 74 74 6f 64 5f 77 6f  |):....Z. ttod_wo|
00004b00  72 6b 25 21 38 3d 30 20  8c 20 f2 74 74 6f 64 5f  |rk%!8=0 . .ttod_|
00004b10  65 72 72 6f 72 28 22 4d  69 73 73 69 6e 67 20 63  |error("Missing c|
00004b20  6f 2d 6f 72 64 69 6e 61  74 65 73 20 66 72 6f 6d  |o-ordinates from|
00004b30  20 27 63 75 72 76 65 27  20 63 6f 6d 6d 61 6e 64  | 'curve' command|
00004b40  22 2c 6c 69 6e 65 5f 6e  6f 25 29 3a e1 0d 12 16  |",line_no%):....|
00004b50  2e f2 74 74 6f 64 5f 67  65 74 5f 78 79 28 a4 67  |..ttod_get_xy(.g|
00004b60  65 74 5f 73 74 72 28 74  74 6f 64 5f 77 6f 72 6b  |et_str(ttod_work|
00004b70  25 21 30 29 2c 20 78 2c  20 79 29 0d 12 20 30 f2  |%!0), x, y).. 0.|
00004b80  74 74 6f 64 5f 67 65 74  5f 78 79 28 a4 67 65 74  |ttod_get_xy(.get|
00004b90  5f 73 74 72 28 74 74 6f  64 5f 77 6f 72 6b 25 21  |_str(ttod_work%!|
00004ba0  34 29 2c 20 78 31 2c 20  79 31 29 0d 12 2a 30 f2  |4), x1, y1)..*0.|
00004bb0  74 74 6f 64 5f 67 65 74  5f 78 79 28 a4 67 65 74  |ttod_get_xy(.get|
00004bc0  5f 73 74 72 28 74 74 6f  64 5f 77 6f 72 6b 25 21  |_str(ttod_work%!|
00004bd0  38 29 2c 20 78 32 2c 20  79 32 29 0d 12 34 21 78  |8), x2, y2)..4!x|
00004be0  3d 78 2a 74 74 6f 64 5f  73 63 61 6c 65 3a 79 3d  |=x*ttod_scale:y=|
00004bf0  79 2a 74 74 6f 64 5f 73  63 61 6c 65 0d 12 3e 25  |y*ttod_scale..>%|
00004c00  78 31 3d 78 31 2a 74 74  6f 64 5f 73 63 61 6c 65  |x1=x1*ttod_scale|
00004c10  3a 79 31 3d 79 31 2a 74  74 6f 64 5f 73 63 61 6c  |:y1=y1*ttod_scal|
00004c20  65 0d 12 48 25 78 32 3d  78 32 2a 74 74 6f 64 5f  |e..H%x2=x2*ttod_|
00004c30  73 63 61 6c 65 3a 79 32  3d 79 32 2a 74 74 6f 64  |scale:y2=y2*ttod|
00004c40  5f 73 63 61 6c 65 0d 12  52 24 f2 74 74 6f 64 5f  |_scale..R$.ttod_|
00004c50  70 75 74 5f 70 61 74 68  28 66 69 6c 65 25 2c 20  |put_path(file%, |
00004c60  36 2c 20 78 31 2c 20 79  31 29 0d 12 5c 13 f2 77  |6, x1, y1)..\..w|
00004c70  70 75 74 28 66 69 6c 65  25 2c 78 32 29 0d 12 66  |put(file%,x2)..f|
00004c80  13 f2 77 70 75 74 28 66  69 6c 65 25 2c 79 32 29  |..wput(file%,y2)|
00004c90  0d 12 70 12 f2 77 70 75  74 28 66 69 6c 65 25 2c  |..p..wput(file%,|
00004ca0  78 29 0d 12 7a 12 f2 77  70 75 74 28 66 69 6c 65  |x)..z..wput(file|
00004cb0  25 2c 79 29 0d 12 84 05  e1 0d 12 8e 05 3a 0d 12  |%,y).........:..|
00004cc0  98 22 dd 20 f2 74 74 6f  64 5f 67 65 74 5f 78 79  |.". .ttod_get_xy|
00004cd0  28 70 61 72 24 2c 20 f8  20 78 2c 20 f8 20 79 29  |(par$, . x, . y)|
00004ce0  0d 12 a2 0a ea 20 70 6f  73 25 0d 12 ac 14 70 6f  |..... pos%....po|
00004cf0  73 25 3d a7 70 61 72 24  2c 20 22 2c 22 29 0d 12  |s%=.par$, ",")..|
00004d00  b6 25 78 3d bb 28 a4 73  74 72 69 70 5f 73 70 61  |.%x=.(.strip_spa|
00004d10  63 65 73 28 c0 70 61 72  24 2c 70 6f 73 25 2d 31  |ces(.par$,pos%-1|
00004d20  29 29 29 0d 12 c0 2b 79  3d bb 28 a4 73 74 72 69  |)))...+y=.(.stri|
00004d30  70 5f 73 70 61 63 65 73  28 c2 70 61 72 24 2c a9  |p_spaces(.par$,.|
00004d40  28 70 61 72 24 29 2d 70  6f 73 25 29 29 29 0d 12  |(par$)-pos%)))..|
00004d50  ca 05 e1 0d 12 d4 05 3a  0d 12 de 26 dd 20 f2 74  |.......:...&. .t|
00004d60  74 6f 64 5f 70 75 74 5f  70 61 74 68 28 66 69 6c  |tod_put_path(fil|
00004d70  65 25 2c 20 69 64 25 2c  20 78 2c 20 79 29 0d 12  |e%, id%, x, y)..|
00004d80  e8 35 f2 77 70 75 74 28  66 69 6c 65 25 2c 20 69  |.5.wput(file%, i|
00004d90  64 25 29 3a f2 77 70 75  74 28 66 69 6c 65 25 2c  |d%):.wput(file%,|
00004da0  20 78 29 3a f2 77 70 75  74 28 66 69 6c 65 25 2c  | x):.wput(file%,|
00004db0  20 79 29 0d 12 f2 05 e1  0d 12 fc 05 3a 0d 13 06  | y).........:...|
00004dc0  33 dd 20 f2 74 74 6f 64  5f 70 75 74 5f 62 65 7a  |3. .ttod_put_bez|
00004dd0  69 65 72 28 66 69 6c 65  25 2c 20 78 2c 20 79 2c  |ier(file%, x, y,|
00004de0  20 78 31 2c 20 79 31 2c  20 78 32 2c 20 79 32 29  | x1, y1, x2, y2)|
00004df0  0d 13 10 35 f2 77 70 75  74 28 66 69 6c 65 25 2c  |...5.wput(file%,|
00004e00  20 36 29 3a f2 77 70 75  74 28 66 69 6c 65 25 2c  | 6):.wput(file%,|
00004e10  20 78 31 29 3a f2 77 70  75 74 28 66 69 6c 65 25  | x1):.wput(file%|
00004e20  2c 20 79 31 29 0d 13 1a  25 f2 77 70 75 74 28 66  |, y1)...%.wput(f|
00004e30  69 6c 65 25 2c 20 78 32  29 3a f2 77 70 75 74 28  |ile%, x2):.wput(|
00004e40  66 69 6c 65 25 2c 20 79  32 29 0d 13 24 23 f2 77  |file%, y2)..$#.w|
00004e50  70 75 74 28 66 69 6c 65  25 2c 20 78 29 3a f2 77  |put(file%, x):.w|
00004e60  70 75 74 28 66 69 6c 65  25 2c 20 79 29 0d 13 2e  |put(file%, y)...|
00004e70  05 e1 0d 13 38 05 3a 0d  13 42 37 dd 20 f2 74 74  |....8.:..B7. .tt|
00004e80  6f 64 5f 70 75 74 5f 68  65 61 64 28 66 69 6c 65  |od_put_head(file|
00004e90  25 2c 20 69 64 25 2c 20  73 69 7a 65 25 2c 20 78  |%, id%, size%, x|
00004ea0  31 2c 20 79 31 2c 20 78  32 2c 20 79 32 29 0d 13  |1, y1, x2, y2)..|
00004eb0  4c 29 f2 77 70 75 74 28  66 69 6c 65 25 2c 20 69  |L).wput(file%, i|
00004ec0  64 25 29 3a f2 77 70 75  74 28 66 69 6c 65 25 2c  |d%):.wput(file%,|
00004ed0  20 73 69 7a 65 25 29 0d  13 56 25 f2 77 70 75 74  | size%)..V%.wput|
00004ee0  28 66 69 6c 65 25 2c 20  78 31 29 3a f2 77 70 75  |(file%, x1):.wpu|
00004ef0  74 28 66 69 6c 65 25 2c  20 79 31 29 0d 13 60 25  |t(file%, y1)..`%|
00004f00  f2 77 70 75 74 28 66 69  6c 65 25 2c 20 78 32 29  |.wput(file%, x2)|
00004f10  3a f2 77 70 75 74 28 66  69 6c 65 25 2c 20 79 32  |:.wput(file%, y2|
00004f20  29 0d 13 6a 05 e1 0d 13  74 05 3a 0d 13 7e 2f dd  |)..j....t.:..~/.|
00004f30  20 f2 74 74 6f 64 5f 70  75 74 5f 70 61 64 64 65  | .ttod_put_padde|
00004f40  64 28 66 69 6c 65 25 2c  20 6c 65 6e 25 2c 20 73  |d(file%, len%, s|
00004f50  74 72 24 2c 20 70 61 64  24 29 0d 13 88 0d ea 20  |tr$, pad$)..... |
00004f60  73 74 72 6c 65 6e 25 0d  13 92 13 73 74 72 6c 65  |strlen%....strle|
00004f70  6e 25 3d a9 28 73 74 72  24 29 0d 13 9c 16 e7 20  |n%=.(str$)..... |
00004f80  73 74 72 6c 65 6e 25 20  3c 20 6c 65 6e 25 20 8c  |strlen% < len% .|
00004f90  0d 13 a6 13 20 d5 23 66  69 6c 65 25 2c 20 73 74  |.... .#file%, st|
00004fa0  72 24 3b 0d 13 b0 23 20  d5 23 66 69 6c 65 25 2c  |r$;...# .#file%,|
00004fb0  20 c4 6c 65 6e 25 2d 73  74 72 6c 65 6e 25 2c 20  | .len%-strlen%, |
00004fc0  70 61 64 24 29 3b 0d 13  ba 05 cc 0d 13 c4 13 20  |pad$);......... |
00004fd0  d5 23 66 69 6c 65 25 2c  20 73 74 72 24 3b 0d 13  |.#file%, str$;..|
00004fe0  ce 05 cd 0d 13 d8 05 e1  0d 13 e2 05 3a 0d 13 ec  |............:...|
00004ff0  2c dd 20 a4 74 74 6f 64  5f 63 68 65 63 6b 5f 66  |,. .ttod_check_f|
00005000  6f 6e 74 5f 68 61 6e 64  6c 65 28 68 61 6e 64 6c  |ont_handle(handl|
00005010  65 73 24 2c 20 6e 6f 25  29 0d 13 f6 1d 3d 28 a7  |es$, no%)....=(.|
00005020  68 61 6e 64 6c 65 73 24  2c 20 c3 28 6e 6f 25 29  |handles$, .(no%)|
00005030  29 20 3d 20 30 29 0d 14  00 05 3a 0d 14 0a 1e dd  |) = 0)....:.....|
00005040  20 f2 74 74 6f 64 5f 65  72 72 6f 72 28 65 72 72  | .ttod_error(err|
00005050  6f 72 24 2c 20 6e 6f 25  29 0d 14 14 0d e7 20 6e  |or$, no%)..... n|
00005060  6f 25 3d 30 20 8c 0d 14  1e 1e 20 24 28 74 74 6f  |o%=0 ..... $(tto|
00005070  64 5f 65 72 72 6f 72 5f  71 25 2b 34 29 3d 65 72  |d_error_q%+4)=er|
00005080  72 6f 72 24 0d 14 28 2f  20 c8 99 20 26 34 30 30  |ror$..(/ .. &400|
00005090  44 46 2c 74 74 6f 64 5f  65 72 72 6f 72 5f 71 25  |DF,ttod_error_q%|
000050a0  2c 20 25 31 2c 20 22 54  65 78 74 2d 32 2d 44 72  |, %1, "Text-2-Dr|
000050b0  61 77 22 0d 14 32 12 20  74 74 6f 64 5f 65 72 72  |aw"..2. ttod_err|
000050c0  6f 72 25 3d b9 0d 14 3c  05 cc 0d 14 46 31 20 24  |or%=...<....F1 $|
000050d0  28 74 74 6f 64 5f 65 72  72 6f 72 5f 71 25 2b 34  |(ttod_error_q%+4|
000050e0  29 3d 65 72 72 6f 72 24  2b 22 20 61 74 20 6c 69  |)=error$+" at li|
000050f0  6e 65 20 22 2b c3 28 6e  6f 25 29 0d 14 50 2f 20  |ne "+.(no%)..P/ |
00005100  c8 99 20 26 34 30 30 44  46 2c 74 74 6f 64 5f 65  |.. &400DF,ttod_e|
00005110  72 72 6f 72 5f 71 25 2c  20 25 31 2c 20 22 54 65  |rror_q%, %1, "Te|
00005120  78 74 2d 32 2d 44 72 61  77 22 0d 14 5a 12 20 74  |xt-2-Draw"..Z. t|
00005130  74 6f 64 5f 65 72 72 6f  72 25 3d b9 0d 14 64 05  |tod_error%=...d.|
00005140  cd 0d 14 6e 05 e1 0d 14  78 05 3a 0d 14 82 26 dd  |...n....x.:...&.|
00005150  20 a4 74 74 6f 64 5f 70  61 72 73 65 28 69 6e 24  | .ttod_parse(in$|
00005160  2c 20 f8 20 63 6f 6d 24  2c 20 f8 20 70 61 72 24  |, . com$, . par$|
00005170  29 0d 14 8c 0a ea 20 70  6f 73 25 0d 14 96 13 70  |)..... pos%....p|
00005180  6f 73 25 3d a7 69 6e 24  2c 20 22 20 22 29 0d 14  |os%=.in$, " ")..|
00005190  a0 28 63 6f 6d 24 3d a4  6c 63 28 a4 73 74 72 69  |.(com$=.lc(.stri|
000051a0  70 5f 73 70 61 63 65 73  28 c0 69 6e 24 2c 20 70  |p_spaces(.in$, p|
000051b0  6f 73 25 29 29 29 0d 14  aa 2c 70 61 72 24 3d a4  |os%)))...,par$=.|
000051c0  73 74 72 69 70 5f 73 70  61 63 65 73 28 c2 69 6e  |strip_spaces(.in|
000051d0  24 2c 20 a9 28 69 6e 24  29 20 2d 20 70 6f 73 25  |$, .(in$) - pos%|
000051e0  29 29 0d 14 b4 1f e7 20  70 6f 73 25 3d 30 20 8c  |))..... pos%=0 .|
000051f0  20 63 6f 6d 24 3d 69 6e  24 3a 70 61 72 24 3d 22  | com$=in$:par$="|
00005200  22 0d 14 be 09 3d 70 6f  73 25 0d 14 c8 05 3a 0d  |"....=pos%....:.|
00005210  14 d2 1f dd 20 a4 74 74  6f 64 5f 68 65 6c 70 28  |.... .ttod_help(|
00005220  77 69 6e 64 6f 77 25 2c  69 63 6f 6e 25 29 0d 14  |window%,icon%)..|
00005230  dc 56 e7 20 77 69 6e 64  6f 77 25 3d 2d 31 20 8c  |.V. window%=-1 .|
00005240  20 3d 22 44 72 61 67 20  61 20 64 72 61 77 20 64  | ="Drag a draw d|
00005250  65 73 63 72 69 70 74 69  6f 6e 20 66 69 6c 65 20  |escription file |
00005260  68 65 72 65 20 74 6f 20  67 65 6e 65 72 61 74 65  |here to generate|
00005270  20 61 20 64 72 61 77 20  66 69 6c 65 2e 22 20 8b  | a draw file." .|
00005280  20 3d 22 22 0d ff                                 | =""..|
00005286