Home » Archimedes archive » Archimedes World » AW-1993-09.adf » AWSept93 » !AWSept93/Goodies/Archive/!ArchivDem/!RunImage

!AWSept93/Goodies/Archive/!ArchivDem/!RunImage

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 » Archimedes World » AW-1993-09.adf » AWSept93
Filename: !AWSept93/Goodies/Archive/!ArchivDem/!RunImage
Read OK:
File size: 62FA bytes
Load address: 0000
Exec address: 0000
File contents
   10REM >!Archiver.!RunImage
   20REM Written by A. Rebmann, Version 2.02 LEN August 1992
   30REM Thanks to... (I Forgot!)   ...Oh, Simon Huntingdon for the brilliant         Interface module.
   40:
   50ON ERROR PROCer(REPORT$+" ( Internal code "+STR$ERL+"."+STR$ERR+" )."):GOTO 790
   60Task=&4B534154:Wimp_Version=2
   70SYS "Wimp_Initialise",Wimp_Version*100,Task,"Archiver" TO ,thand%
   80SYS "Wimp_ClaimInterface",,thand%
   90SYS "Hourglass_On"
  100DIM  q% 128,tq% 128,buffer% 1000
  110ts=&2000:DIM temp% ts:endtemp%=temp%+ts:current_menu%=0:topics%=0:catas%=0
  120DIM window% &3000,winpar% 512
  130DIM finds (640*4)
  140DIM t$(20),c$(20)
  150DIM table (130*640)+640
  160DIM topic_menu% 512,cata_menu% 512
  170data%=0:choices%=0:save%=0:backgnd%=FALSE:backsp$="":lastcard%=0:card%=0
  180adding%=TRUE:findtopic%=1:addtopic%=1:findcata%=1:addcata%=1:clear%=FALSE
  190PROCinitmenus
  200FOR clear=0 TO (130*640)+640 STEP 4
  210table!clear=0
  220NEXT clear
  230FOR clear=0 TO (640*4) STEP 4
  240finds!clear=0
  250NEXT clear
  260OSCLI("IconSprites <ArchiverDem$Dir>.Sprites")
  270SYS "Wimp_OpenTemplate",,"<ArchiverDem$Dir>.Templates"
  280SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"progInfo" TO ,,temp%
  290SYS "Wimp_CreateWindow",,window% TO info%
  300SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"addref2" TO ,,temp%
  310SYS "Wimp_CreateWindow",,window% TO find%
  320SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"options" TO ,,temp%
  330SYS "Wimp_CreateWindow",,window% TO options%
  340SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"addref" TO ,,temp%
  350SYS "Wimp_CreateWindow",,window% TO add%
  360SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"Browse" TO ,,temp%
  370SYS "Wimp_CreateWindow",,window% TO browse%
  380SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"save_temp" TO ,,temp%
  390SYS "Wimp_CreateWindow",,window% TO save%
  400SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"fileInfo" TO ,,temp%
  410SYS "Wimp_CreateWindow",,window% TO finfo%
  420SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"customize" TO ,,temp%
  430SYS "Wimp_CreateWindow",,window% TO config%
  440SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"matches" TO ,,temp%
  450SYS "Wimp_CreateWindow",,window% TO matches%
  460SYS "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"endofsearch" TO ,,temp%
  470SYS "Wimp_CreateWindow",,window% TO endsearch%
  480SYS "Wimp_CloseTemplate"
  550menu%=FNcreatemenu("Archiver,Info$,File,Show logs$,Browse$,Find item,Add item$,Options$,Quit")
  560browse_menu%=FNcreatemenu("Archiver,Goto$,Find item$,Add item,Edit item,Delete item")
  570goto_menu%=FNcreatemenu("Goto,Next,Previous$,First,Last")
  580file_menu%=FNcreatemenu("File,Info,Save,New file")
  590PROCwrite_mess(find%,3,t$(0))
  600PROCwrite_mess(add%,7,t$(0))
  610PROCwrite_mess(find%,6,c$(0))
  620PROCwrite_mess(add%,10,c$(0))
  622PROCtogglegrey(menu%,6)
  630PROCtogglegrey(menu%,5)
  640PROCtogglegrey(menu%,4)
  650PROCtogglegrey(file_menu%,1)
  660PROCtogglegrey(file_menu%,2)
  670PROCmenu_attach(menu%,1,info%)
  680PROCmenu_attach(menu%,2,file_menu%)
  690PROCmenu_attach(file_menu%,1,finfo%)
  700PROCmenu_attach(file_menu%,2,save%)
  710PROCmenu_attach(menu%,7,options%)
  720PROCmenu_attach(file_menu%,3,config%)
  730PROCmenu_attach(browse_menu%,1,goto_menu%)
  740icdata%=FNiconbar("<ArchiverDem$Dir>",-1,"!ArchivDem")
  750PROCwrite_mess(finfo%,2,"<Untitled>")
  760PROCupdatesize
  770PROCstartupanload
  780SYS "Hourglass_Off"
  790REPEAT
  800SYS "Wimp_Poll",0,buffer% TO poll%
  810SYS "Wimp_PollPointer",poll%,,thand%
  820CASE poll% OF
  830WHEN 0:
  840WHEN 1:IF matches%=!buffer% PROCredrawmatches ELSE PROCredrawwin(!buffer%)
  850WHEN 2:SYS "Wimp_OpenWindow",,buffer%
  860WHEN 3:SYS "Wimp_CloseWindow",,buffer%
  870WHEN 4:
  880WHEN 5:
  890WHEN 6:PROCmouseclick(buffer%!8,buffer%!12)
  910WHEN 8:
  920WHEN 9:PROCmenudone
  930WHEN 10:
  940WHEN 17,18:
  950CASE buffer%!16 OF
  960WHEN 0:PROCquit
  980WHEN 3,5:PROCloadsprites
  990WHEN &502:PROCsendhelp
 1000ENDCASE
 1010ENDCASE
 1020UNTIL 0
 1030END
 1040DEFPROCmouseclick(click%,click2%)
 1050SYS "Wimp_BorderIcon",,buffer%
 1060IF buffer%!16=icdata% AND click%=2 AND buffer%!12<0 THEN PROCshow_menu(menu%,!buffer%-64,FNmenu_height(menu%)+120):mx%=!buffer%:my%=buffer%!4
 1070IF buffer%!12=browse% AND click%=2 THEN PROCshow_menu(browse_menu%,!buffer%,buffer%!4)
 1080IF buffer%!16=icdata% AND click%=4 AND buffer%!12<0 AND clear% THEN PROCopenwindow(find%)
 1090IF buffer%!16=icdata% AND click%=1 AND buffer%!12<0 AND clear% THEN PROCalter_browse(card%):PROCopenwindow(browse%)
 1100IF FNclick(config%,64,5)  PROCshow_menu(-1,-1,-1)
 1110IF FNclick(config%,65,5)  PROCresetconfigurewin
 1120IF FNclick(config%,68,5) AND clear%=TRUE PROCcopyconfigure
 1130IF FNclick(config%,63,5)  PROCcreatenewfile:PROCshow_menu(-1,-1,-1)
 1140IF FNclick(find%,10,5)    PROCfind
 1150IF FNclick(finfo%,12,5)   PROCshow_menu(-1,-1,-1)
 1160IF FNclick(options%,13,5) PROCshow_menu(-1,-1,-1)
 1170IF FNclick(add%,13,5) AND adding%=TRUE     cardno%=lastcard%:PROCclosewindow(add%):PROCadd_card:PROCupdatesize:lastcard%+=1:IF lastcard%=1 THEN PROCchangegreys
 1180IF FNclick(add%,14,5)     cardno%=card%:PROCshiftcards(cardno%):PROCclosewindow(add%):PROCadd_card:PROCupdatesize
 1190IF FNclick(add%,13,5) AND adding%=FALSE THEN cardno%=card%:PROCclosewindow(add%):PROCadd_card
 1200IF FNclick(find%,4,5)    PROCshow_menu(topics%,!buffer%,buffer%!4):aw%=find%:ah%=3
 1210IF FNclick(add%,8,5)    PROCshow_menu(topics%,!buffer%,buffer%!4):aw%=add%:ah%=7
 1220IF FNclick(find%,7,5)    PROCshow_menu(catas%,!buffer%,buffer%!4):aw%=find%:ah%=6
 1230IF FNclick(add%,12,5)    PROCshow_menu(catas%,!buffer%,buffer%!4):aw%=add%:ah%=10
 1240IF FNclick(browse%,11,5) THEN card%-=1:PROCalter_browse(card%)
 1250IF FNclick(browse%,12,5) THEN card%+=1:PROCalter_browse(card%)
 1280IF FNclick(endsearch%,2,5) THEN PROCclosewindow(endsearch%)
 1290buffer%!8=0:SYS "Wimp_BorderIcon",,buffer%
 1300ENDPROC
 1310DEFFNclick(winder%,icern%,butterns%)
 1320IF buffer%!12=winder% AND buffer%!16=icern% AND (buffer%!8 OR butterns%)=butterns% =TRUE
 1330=FALSE
 1340DEFPROCmenudone
 1350LOCAL menutext$
 1360SYS "Wimp_DecodeMenu",,current_menu%,buffer%,STRING$(200," ") TO ,,,menutext$
 1370IF FNchoice("Quit") THEN PROCquit
 1380IF FNchoice("Find") THEN PROCopenwindow(find%)
 1390IF FNchoice("Browse") THEN PROCalter_browse(card%):PROCopenwindow(browse%)
 1400IF FNchoice("Add item") AND current_menu%=menu% THEN PROCDisableIcon(add%,14):adding%=TRUE:PROCdelete_fields:PROCopenwindow(add%)
 1410IF FNchoice("Add item") AND current_menu%=browse_menu% THEN PROCEnableIcon(add%,14):adding%=TRUE:PROCdelete_fields:PROCopenwindow(add%)
 1420IF FNchoice("Edit item") cardno%=card%:PROCFillInFields:adding%=FALSE:PROCDisableIcon(add%,14):PROCopenwindow(add%)
 1430IF FNchoice("Delete") THEN PROCdeletecard
 1440IF FNchoice("Next") THEN card%+=1:PROCalter_browse(card%)
 1450IF FNchoice("Previous") THEN card%-=1:PROCalter_browse(card%)
 1460IF FNchoice("First") THEN card%=0:PROCalter_browse(card%)
 1470IF FNchoice("Last") THEN card%=lastcard%-1:PROCalter_browse(card%)
 1480IF FNchoice("Show log") THEN
 1481$tq%="ArchiverDem$Dir"+CHR$(0)
 1482SYS "OS_ReadVarVal",tq%,q%,100,0,3 TO ,,l%
 1483f$=LEFT$($q%,l%)+".LogFiles":OSCLI("Filer_OpenDir "+f$)
 1485ENDIF
 1490IF current_menu%=topics% THEN PROCtopic(menutext$)
 1500IF current_menu%=catas% THEN PROCcatagory(menutext$)
 1510ENDPROC
 1520DEFFNchoice(choice$)
 1530IF INSTR(menutext$,choice$)>0 =TRUE ELSE =FALSE
 1540:
 1550DEFPROCquit
 1560SYS "Wimp_ReleaseInterface",,thand%
 1570SYS "Wimp_CloseDown",thand%,Task
 1580END
 1590:
 1600REM Menu facilities
 1610:
 1620DEFPROCinitmenus
 1630DIM menu_block% &2000:menu_free%=menu_block%
 1640ENDPROC
 1650:
 1660REM  menu%=FNcreatemenu("Title,Item1,Item2...")
 1670:
 1680DEFFNcreatemenu(menu$)
 1690menu_ptr%=menu_free%
 1700title$=FNfield(menu$,",")
 1710IF LEN(title$)>12 THEN
 1720$(menu_ptr%)=LEFT$(title$,12)
 1730width%=12
 1740ELSE
 1750$(menu_ptr%)=title$
 1760width%=LEN(title$)
 1770ENDIF
 1780menu_ptr%?12=7:menu_ptr%?13=2
 1790menu_ptr%?14=7:menu_ptr%?15=0
 1800menu_ptr%!20=44:menu_ptr%!24=0
 1810menu_item_ptr%=menu_ptr%+4
 1820WHILE menu$<>""
 1830menu_item_ptr%+=24
 1840menu_item$=FNfield(menu$,",")
 1850!menu_item_ptr%=0
 1860menu_item_ptr%!4=-1
 1870menu_item_ptr%!8=&7000021
 1880WHILE INSTR("#$%^",RIGHT$(menu_item$))>0
 1890CASE RIGHT$(menu_item$) OF
 1900WHEN "#":?menu_item_ptr%=?menu_item_ptr% OR %00000001
 1910WHEN "$":?menu_item_ptr%=?menu_item_ptr% OR %00000010
 1920WHEN "%":menu_item_ptr%?10=menu_item_ptr%?10 OR %01000000
 1930WHEN "^":?menu_item_ptr%=?menu_item_ptr% OR %00000100
 1940ENDCASE
 1950menu_item$=LEFT$(menu_item$)
 1960ENDWHILE
 1970IF LEN(menu_item$)>width% THEN width%=LEN(menu_item$)
 1980$(menu_item_ptr%+12)=menu_item$+CHR$(0)
 1990ENDWHILE
 2000?menu_item_ptr%=?menu_item_ptr% OR %10000000
 2010menu_ptr%!16=(width%*8+6)*2
 2020menu_free%=menu_item_ptr%+24
 2030=menu_ptr%
 2040DEFPROCshow_menu(menu%,x%,y%)
 2050current_menu%=menu%
 2060menu_x%=x%
 2070menu_y%=y%
 2080SYS "Wimp_CreateMenu",,menu%,x%,y%
 2090ENDPROC
 2100DEFFNfield(RETURN menu$,seperator$)
 2110result$=LEFT$(menu$,INSTR(menu$+seperator$,seperator$)-1)
 2120menu$=RIGHT$(menu$,LEN(menu$)-LEN(result$)-1)
 2130=result$
 2140DEFFNmenu_height(menu%)
 2150LOCAL height%,menu_item_ptr%
 2160menu_item_ptr%=menu%+28
 2170height%=0
 2180WHILE (?menu_item_ptr% AND %10000000)=0
 2190menu_item_ptr%+=24
 2200height%+=1
 2210ENDWHILE
 2220=96+(44*(height%+1))
 2230DEFPROCmenu_attach(menu%,position%,attachment%)
 2240menu%!(28+24*(position%-1)+4)=attachment%
 2250ENDPROC
 2260DEFFNiconbar(dir$,side,spname$)
 2270S%=OPENIN(dir$+".!Sprites"):T%=EXT#S%+16:CLOSE#S%
 2280DIM isprites% T%
 2290!isprites%=T%:isprites%!8=1
 2300SYS "OS_SpriteOp",&109,isprites%
 2310SYS "OS_SpriteOp",&10A,isprites%,dir$+".!Sprites"
 2320!q%=side:q%!4=0:q%!8=0:q%!12=68:q%!16=68:q%!20=&3102
 2330DIM q%!24 (LENspname$+1):$(q%!24)=spname$:q%!28=isprites%
 2340q%!32=LENspname$+1
 2350SYS "Wimp_CreateIcon",,q% TO ic%
 2360=ic%
 2370DEFPROCopenwindow(han%)
 2380!q%=han%
 2390SYS "Wimp_GetWindowState",,q%
 2400SYS "Wimp_OpenWindow",,q%
 2410ENDPROC
 2420DEFPROCclosewindow(han%)
 2430!q%=han%
 2440SYS "Wimp_CloseWindow",,q%
 2450ENDPROC
 2460DEFPROCer(error$)
 2470error$=error$+CHR$0
 2480!tq%=0:$(tq%+4)=error$
 2490SYS "Wimp_ReportError",tq%,1,"archiver"
 2500ENDPROC
 2510DEFPROCwrite_mess(win%,han%,mess$)
 2520!tq%=win%:tq%!4=han%:SYS "Wimp_GetIconState",,tq%
 2530$(tq%!28)=mess$+CHR$(0)
 2540SYS "Wimp_ForceRedraw",win%,tq%!8,tq%!12,tq%!16,tq%!20
 2550ENDPROC
 2560DEFFNgetbutton(window%,han%)
 2570!tq%=window%:tq%!4=han%:SYS "Wimp_GetIconState",,tq%
 2580=FNstring0(tq%!28)
 2590DEFPROCloadsprites
 2591ON ERROR LOCAL ENDPROC
 2600IF buffer%!40<>&194  AND buffer%!16=3 THEN ENDPROC
 2610IF buffer%!40<>&194 THEN ENDPROC
 2620file$=FNstring0(buffer%+44)
 2630buffer%!16=4:buffer%!12=buffer%!8
 2640SYS "Wimp_SendMessage",17,buffer%,0
 2641ON ERROR PROCer(REPORT$+" ( Internal code "+STR$ERL+"."+STR$ERR+" )."):GOTO 790
 2650PROCloadfile(file$)
 2660ENDPROC
 2670DEFFNoption(win%,han%)
 2680!tq%=win%:tq%!4=han%
 2690SYS "Wimp_GetIconState",,tq%
 2700=tq%!24 AND %1000000000000000000000
 2710DEFFNstring0(a%)LOCALa$:a$="":WHILE?a%>31:a$+=CHR$?a%:a%+=1:ENDWHILE:=a$
 2720DEFPROCforceredraw(han%)
 2730SYS "Wimp_ForceRedraw",han%,0,-8-(120*fcount),1280,0
 2740ENDPROC
 2750DEFPROCsetgrey(menu%,position%)
 2760menu%?(38+24*(position%-1))=menu%?(38+24*(position%-1)) OR  %1000000
 2770ENDPROC
 2780DEFPROCcleargrey(menu%,position%)
 2790menu%?(38+24*(position%-1))=menu%?(38+24*(position%-1)) AND %0111111
 2800ENDPROC
 2810DEFPROCtogglegrey(menu%,position%)
 2820menu%?(38+24*(position%-1))=menu%?(38+24*(position%-1)) EOR %1000000
 2830ENDPROC
 2840:
 2850DEFPROCDisableIcon(window%,icon%)
 2860tq%!0=window% : tq%!4=icon%
 2870tq%!8=1<<22   : tq%!12=1<<22
 2880SYS "Wimp_SetIconState",,tq%
 2890ENDPROC
 2900:
 2910DEFPROCEnableIcon(window%,icon%)
 2920tq%!0=window% : tq%!4=icon%
 2930tq%!8=0       : tq%!12=1<<22
 2940SYS "Wimp_SetIconState",,tq%
 2950ENDPROC
 2960:
 2970DEFPROCSetIcon(window%,icon%,state%)
 2980tq%!0=window% : tq%!4=icon%
 2990IF state%=TRUE THEN tq%!8=1<<21   : tq%!12=1<<21
 3000IF state%=FALSE THEN tq%!8=0      : tq%!12=1<<21
 3010SYS "Wimp_SetIconState",,tq%
 3020ENDPROC
 3030:
 3040DEFPROCdelete_fields
 3050IF clt%=TRUE THEN PROCwrite_mess(add%,2,"")
 3060IF cli%=TRUE THEN PROCwrite_mess(add%,17,"")
 3070IF cld%=TRUE THEN PROCwrite_mess(add%,9,"")
 3080IF clp%=TRUE THEN PROCwrite_mess(add%,5,"")
 3090ENDPROC
 3100:
 3110DEFPROCadd_card
 3120item$=FNgetbutton(add%,2)
 3130info$=FNgetbutton(add%,17)
 3140date$=FNgetbutton(add%,9)
 3150page$=FNgetbutton(add%,5)
 3160cata%=addcata%:topi%=addtopic%
 3170IF FNoption(add%,4)<>0  topi%+=100
 3180$(table+(cardno%*130)+640)=item$
 3190$(table+(cardno%*130)+640+32)=info$
 3200$(table+(cardno%*130)+640+64)=date$
 3210$(table+(cardno%*130)+640+96)=page$
 3220?(table+(cardno%*130)+640+128)=cata%
 3230?(table+(cardno%*130)+640+129)=topi%
 3240PROCalter_browse(card%)
 3250ENDPROC
 3260:
 3270DEFPROCFillInFields
 3280PROCwrite_mess(add%,2,$(table+(cardno%*130)+640))
 3290PROCwrite_mess(add%,17,$(table+(cardno%*130)+640+32))
 3300PROCwrite_mess(add%,9,$(table+(cardno%*130)+640+64))
 3310PROCwrite_mess(add%,5,$(table+(cardno%*130)+640+96))
 3320addcata%=?(table+(cardno%*130)+640+128):PROCwrite_mess(add%,10,c$(addcata%-1))
 3330addtopic%=?(table+(cardno%*130)+640+129):IF addtopic%>100 THEN addtopic%-=100:PROCSetIcon(add%,4,TRUE) ELSE PROCSetIcon(add%,4,FALSE)
 3332PROCwrite_mess(add%,7,t$(addtopic%-1))
 3340ENDPROC
 3350DEFPROCshiftcards(cardno%)
 3360LOCAL fcard%,lcard%,a,b
 3370FOR shiftloop=lastcard% TO cardno% STEP -1
 3380a=shiftloop:b=shiftloop+1
 3390$(table+(b*130)+640)=$(table+(a*130)+640)
 3400$(table+(b*130)+640+32)=$(table+(a*130)+640+32)
 3410$(table+(b*130)+640+64)=$(table+(a*130)+640+64)
 3420$(table+(b*130)+640+96)=$(table+(a*130)+640+96)
 3430?(table+(b*130)+640+128)=?(table+(a*130)+640+128)
 3440?(table+(b*130)+640+129)=?(table+(a*130)+640+129)
 3450NEXT shiftloop
 3460lastcard%+=1
 3470ENDPROC
 3480:
 3490DEFPROCdeletecard
 3500cardno%=card%
 3510m$="Delete item "+STR$(cardno%+1)+" ("+$(table+(cardno%*130)+640)+") ?"
 3520tq%!0=255:$(tq%+4)=m$+CHR$(0)
 3530SYS "Wimp_ReportError",tq%,%10011,"Delete item?" TO ,button%
 3540IF button%<>1 THEN ENDPROC
 3550FOR shiftloop=cardno% TO lastcard% STEP -1
 3560a=shiftloop+1:b=shiftloop
 3570$(table+(b*130)+640)=$(table+(a*130)+640)
 3580$(table+(b*130)+640+32)=$(table+(a*130)+640+32)
 3590$(table+(b*130)+640+64)=$(table+(a*130)+640+64)
 3600$(table+(b*130)+640+96)=$(table+(a*130)+640+96)
 3610?(table+(b*130)+640+128)=?(table+(a*130)+640+128)
 3620?(table+(b*130)+640+129)=?(table+(a*130)+640+129)
 3630NEXT shiftloop
 3640lastcard%-=1
 3650IF card%>lastcard% THEN card%=lastcard%
 3660PROCalter_browse(card%)
 3670ENDPROC
 3680:
 3690DEFPROCalter_browse(RETURN card%)
 3700IF card%=lastcard% card%=0
 3710IF card%<0 card%=lastcard%-1
 3720item$=$(table+(card%*130)+640)
 3730info$=$(table+(card%*130)+640+32)
 3740date$=$(table+(card%*130)+640+64)
 3750page$=$(table+(card%*130)+640+96)
 3760cata%=?(table+(card%*130)+640+128)
 3770topi%=?(table+(card%*130)+640+129)
 3772IF topi%>100 topi%-=100:opt$="("+optt$+")" ELSE opt$=""
 3780PROCwrite_mess(browse%,1,item$)
 3790PROCwrite_mess(browse%,2,info$)
 3800PROCwrite_mess(browse%,6,page$)
 3810PROCwrite_mess(browse%,4,date$)
 3812IF topi%=0 THEN topi%=1
 3814IF cata%=0 THEN cata%=1
 3820tops$=t$(topi%-1)+" "+c$(cata%-1)+" "+opt$
 3830PROCwrite_mess(browse%,8,tops$)
 3840PROCwrite_mess(browse%,13,STR$(card%+1)+" out of "+STR$(lastcard%))
 3850WAIT
 3860ENDPROC
 3870:
 4190DEFFNlastbit(s$)
 4200WHILE INSTR(s$,":")>0
 4210s$=MID$(s$,INSTR(s$,":")+1)
 4220ENDWHILE
 4230WHILE INSTR(s$,".")>0
 4240s$=MID$(s$,INSTR(s$,".")+1)
 4250ENDWHILE
 4260=s$
 4510DEFPROCloadfile(file$)
 4520SYS "Hourglass_On"
 4530FOR clear=0 TO (130*640)+640 STEP 4
 4540table!clear=0
 4550NEXT clear
 4560SYS "OS_File",12,file$,table,0
 4570card%=0
 4580lastcard%=table!636
 4590PROCalter_browse(card%)
 4600PROCwrite_mess(finfo%,4,FNstring0(table))
 4610PROCwrite_mess(finfo%,8,FNstring0(table+32))
 4620PROCupdatesize
 4630PROCwrite_mess(finfo%,2,RIGHT$(file$,27))
 4650te$=$(table+64):ce$=$(table+320)
 4660tst$=$(table+576):ist$=$(table+588)
 4670dst$=$(table+600):pst$=$(table+612)
 4680PROCwrite_mess(browse%,0,tst$+":")
 4690PROCwrite_mess(browse%,3,ist$+":")
 4700PROCwrite_mess(browse%,5,dst$+":")
 4710PROCwrite_mess(browse%,7,pst$+":")
 4720PROCwrite_mess(add%,23,tst$+":")
 4730PROCwrite_mess(add%,3,ist$+":")
 4740PROCwrite_mess(add%,11,dst$+":")
 4750PROCwrite_mess(add%,6,pst$+":")
 4752PROCwrite_mess(find%,13,tst$)
 4754PROCwrite_mess(find%,14,ist$)
 4756PROCwrite_mess(find%,15,dst$)
 4758PROCwrite_mess(find%,16,pst$)
 4760clt%=FALSE:cli%=FALSE:cld%=FALSE:clp%=FALSE
 4770IF (table?624 AND 8)>0 THEN clt%=TRUE
 4780IF (table?624 AND 4)>0 THEN cli%=TRUE
 4790IF (table?624 AND 2)>0 THEN cld%=TRUE
 4800IF (table?624 AND 1)>0 THEN clp%=TRUE
 4810optt$=LEFT$(FNstring0(table+627),7)
 4820topics%=FNcreatetopicmenu(te$)
 4830catas%=FNcreatecatagorymenu(ce$)
 4840PROCEnableIcon(find%,8)
 4850PROCEnableIcon(add%,4)
 4860PROCwrite_mess(find%,8,optt$)
 4870PROCwrite_mess(add%,4,optt$)
 4880IF optt$=" " OR optt$="" THEN
 4890PROCDisableIcon(find%,8)
 4900PROCDisableIcon(add%,4)
 4910ENDIF
 4920PROCwrite_mess(find%,3,t$(0))
 4930PROCwrite_mess(add%,7,t$(0))
 4940PROCwrite_mess(find%,6,c$(0))
 4950PROCwrite_mess(add%,10,c$(0))
 4960findtopic%=1:addtopic%=1
 4970findcata%=1:addcata%=1
 4980SYS "Hourglass_Smash"
 4990PROCchangegreys
 5000ENDPROC
 5060DEFPROCupdatesize
 5070IF lastcard%=0 THEN
 5080cards=0
 5090bytes=0
 5100ELSE
 5110cards=lastcard%
 5120bytes=(lastcard%*130)+640
 5130ENDIF
 5140IF cards=1 THEN phrase$="record" ELSE phrase$="records"
 5150sentence$=STR$cards+" "+phrase$+" ("+STR$bytes+" bytes)"+CHR$(0)
 5160PROCwrite_mess(finfo%,10,sentence$)
 5170ENDPROC
 5180DEFPROCtopic(topic$)
 5190PROCwrite_mess(aw%,ah%,topic$)
 5200IF aw%=find% findtopic%=!buffer%+1 ELSE addtopic%=!buffer%+1
 5210ENDPROC
 5220DEFPROCcatagory(catagory$)
 5230PROCwrite_mess(aw%,ah%,catagory$)
 5240IF aw%=find% findcata%=!buffer%+1 ELSE addcata%=!buffer%+1
 5250ENDPROC
 5260DEFPROCstartupanload
 5270LOCAL i,numspaces,command
 5280SYS "OS_GetEnv" TO command
 5290$q%=FNstring0(command)+CHR$(13)
 5300numspaces=0
 5310i=0
 5320WHILE numspaces<3
 5330IF q%?i=&20 numspaces+=1
 5340i+=1
 5350ENDWHILE
 5360file$=$(q%+i)
 5370IF INSTR(file$,"::")>0 PROCloadfile(file$)
 5380ENDPROC
 5390DEFPROCredrawwin(handle%)
 5400SYS "Wimp_RedrawWindow",0,buffer% TO more%
 5410WHILE more%
 5420SYS "Wimp_BorderWindow",,buffer%
 5430SYS "Wimp_GetRectangle",0,buffer% TO more%
 5440ENDWHILE
 5450ENDPROC
 5460DEFPROCredrawmatches
 5470LOCAL more%,x0%,y0%,i%
 5480SYS "Wimp_RedrawWindow",0,buffer% TO more%
 5490PROClwaorigin(buffer%+4,x0%,y0%)
 5500WHILE more%
 5510PROCwritetext(x0%,y0%,i%)
 5520GCOL RND(16)-1
 5530SYS "Wimp_GetRectangle",0,buffer% TO more%
 5540ENDWHILE
 5550ENDPROC
 5560DEFPROClwaorigin(b,RETURN x%,RETURN y%)
 5570x%=b!0-b!16
 5580y%=b!12-b!20
 5590ENDPROC
 5600:
 5610DEFPROCwritetext(x0%,y0%,index%)
 5620LOCAL i%,a%,b%,c%,d%,x1%,y1%,x2%,y2%
 5630PROClwacliprectangle(buffer%+4,x1%,y1%,x2%,y2%)
 5640a%=(1024-12-y2%) DIV 40+1
 5650b%=(1024-12-y1%) DIV 40+2
 5660c%=(x1%-4) DIV 16+1
 5670d%=(x2%-4) DIV 16+2
 5680d%=d%-c%
 5690GCOL 0,11
 5700FOR i%=a% TO b%
 5710text$=""
 5720IF (i%-28)>-1 THEN
 5730IF (i%-28) MOD 3=0 THEN
 5740GCOL 8
 5750RECTANGLE FILL x0%+16*(c%-1),y0%+1024-40*(i%-1)+4,d%*16,-36
 5760cata%=?(table+(FNcard((i%-28) DIV 3)*130)+640+128)
 5770topi%=?(table+(FNcard((i%-28) DIV 3)*130)+640+129)
 5780IF topi%>100 opt$="("+optt$+")":topi%-=100 ELSE opt$=""
 5790text$=t$(topi%-1)+" "+c$(cata%-1)+" : "+$(table+(FNcard((i%-28) DIV 3)*130)+640)+" "+opt$
 5800GCOL 1
 5810ELSE
 5820GCOL 7
 5830IF (i%-28) MOD 3=1 THEN text$=$(table+(FNcard((i%-28) DIV 3)*130)+640+32)+" "+$(table+(FNcard((i%-28) DIV 3)*130)+640+64)+", "
 5832IF (i%-28) MOD 3=1 AND pst$="Page" THEN text$+="Page "
 5834IF (i%-28) MOD 3=1 THEN text$+=$(table+(FNcard((i%-28) DIV 3)*130)+640+64+32) ELSE text$=""
 5840ENDIF
 5850ENDIF
 5860MOVE x0%+4+16*(c%-1),y0%+1024-40*(i%-1)
 5870PRINT MID$(text$,c%,d%);
 5880NEXT i%
 5890ENDPROC
 5900:
 5910DEFPROClwacliprectangle(b,RETURN x1%,RETURN y1%,RETURN x2%,RETURN y2%)
 5920LOCAL x0%,y0%
 5930PROClwaorigin(b,x0%,y0%)
 5940x1%=b!24-x0%:y1%=b!28-y0%
 5950x2%=b!32-x0%:y2%=b!36-y0%
 5960ENDPROC
 5970:
 5980DEFPROClimit(lower,RETURN value,upper)
 5990IF value<lower THEN value=lower
 6000IF value>upper THEN value=upper
 6010ENDPROC
 6020DEFFNcaps(a$)
 6030FOR loop=1 TO LENa$
 6040b$=MID$(a$,loop,1)
 6050IF b$>"`" AND b$<"{" THEN
 6060b$=CHR$(ASCb$-32)
 6070MID$(a$,loop,1)=b$
 6080ENDIF
 6090NEXT loop
 6100=a$
 6110DEFPROCfind
 6120SYS "Hourglass_On"
 6130find$=FNgetbutton(find%,9)
 6140find$=FNcaps(find$)
 6150topi%=findtopic%
 6160cata%=findcata%
 6162fno%=0:IF FNoption(find%,14)<>0 fno%=32
 6164IF FNoption(find%,15)<>0 fno%=64
 6166IF FNoption(find%,16)<>0 fno%=96
 6170IF FNoption(find%,8)<>0  opt%=TRUE ELSE opt%=FALSE
 6180usecata%=(FNoption(find%,5))
 6190usetopi%=(FNoption(find%,2))
 6200fcount=0:pc=0:pa=100/(lastcard%-1)
 6210IF FNoption(options%,12)>0 O=OPENOUT("<ArchiverDem$Dir>.Log�Files."+FNgetbutton(options%,4))
 6220FOR scard=0 TO lastcard%-1
 6230item$=FNcaps($(table+(scard*130)+640+fno%))
 6240chcata%=?(table+(scard*130)+640+128)
 6250chtopi%=?(table+(scard*130)+640+129)
 6260IF chtopi%>100 chtopi2%=chtopi%-100 ELSE chtopi2%=chtopi%
 6270IF usecata%=0 OR (usecata%>0 AND cata%=chcata%) THEN
 6280IF usetopi%=0 OR (usetopi%>0 AND topi%=chtopi2%) THEN
 6290IF opt%=FALSE OR (opt%=TRUE AND chtopi%>100) THEN
 6300IF INSTR(item$,find$)>0 THEN finds!(fcount*4)=scard:fcount+=1:IF FNoption(options%,12)>0 PROCaddtolog(scard)
 6310ENDIF
 6320ENDIF
 6330ENDIF
 6340pc+=pa
 6350SYS "Hourglass_Percentage",pc
 6360NEXT scard
 6370IF fcount>0 THEN
 6380 IF FNoption(options%,7)>0 THEN
 6390  !q%=0:q%!4=-8-(120*fcount)
 6400  q%!8=1280:q%!12=0
 6410  SYS "Wimp_SetExtent",matches%,q%
 6420  PROCwrite_mess(matches%,0,"Items found = "+STR$fcount)
 6430  PROCforceredraw(matches%)
 6440  PROCopenwindow(matches%)
 6450  PROCclosewindow(find%)
 6460 ELSE
 6470  IF fcount=1 s$="" ELSE s$="s"
 6480  PROCwrite_mess(endsearch%,1,STR$fcount+" item"+s$+" found")
 6490  PROCopenwindow(endsearch%)
 6500  PROCclosewindow(find%)
 6510 ENDIF
 6520ENDIF
 6530IF fcount=0 THEN
 6531PROCer("No matches found.")
 6532IF FNoption(options%,14)>0 THEN
 6533IF c$(findcata%)<>"" THEN
 6534ca$=c$(findcata%):findcata%+=1
 6535PROCwrite_mess(find%,6,ca$)
 6536ENDIF
 6537ENDIF
 6538ENDIF
 6540IF FNoption(options%,12)>0 CLOSE#O:OSCLI("SetType <ArchiverDem$Dir>.LogFiles."+FNgetbutton(options%,5)+" Text")
 6550SYS "Hourglass_Off"
 6560ENDPROC
 6570DEFFNcard(number)
 6580=finds!(number*4)
 6590DEFPROCchangegreys
 6600clear%=TRUE
 6602PROCcleargrey(menu%,6)
 6610PROCcleargrey(menu%,5)
 6620PROCcleargrey(menu%,4)
 6630PROCcleargrey(file_menu%,1)
 6640PROCcleargrey(file_menu%,2)
 6650ENDPROC
 6660DEFPROCwritetofile(a$)
 6670FOR b=1 TO LENa$
 6680BPUT#O,ASC(MID$(a$,b,1))
 6690NEXT b
 6700ENDPROC
 6710DEFPROCaddtolog(card)
 6720LOCAL cata%,topi%
 6730cata%=?(table+(card*130)+640+128)
 6740topi%=?(table+(card*130)+640+129)
 6750IF topi%>100 opt$="("+optt$+")":topi%-=100 ELSE opt$=""
 6760text$=t$(topi%-1)+" "+c$(cata%-1)+" : "+$(table+(card*130)+640)+" "+opt$
 6770mag$=$(table+(card*130)+640+32)
 6780date$=$(table+(card*130)+640+64)
 6790rest$=$(table+(card*130)+640+64+32)
 6792IF pst$="Page" THEN rest$="Page "+rest$
 6800IF FNoption(options%,10) THEN text$=text$+CHR$(10):text2$=mag$+" "+date$+", "+rest$+CHR$(10) ELSE text$=text$+" ("+date$+")"+CHR$(10):text2$=mag$+", "+rest$+CHR$(10)
 6810PROCwritetofile(text$)
 6820PROCwritetofile(text2$)
 6830PROCwritetofile(CHR$(10))
 6840ENDPROC
 6850:
 6860DEFPROCsendhelp
 6870IF buffer%!32=matches% THEN buffer%!36=0
 6880SYS "Wimp_SendInformation",,buffer%
 6890ENDPROC
 6900DEFFNcreatetopicmenu(menu$)
 6910tcnt%=0
 6920menu_ptr%=topic_menu%
 6930$(menu_ptr%)=" "
 6940width%=1
 6950ENDIF
 6960menu_ptr%?12=7:menu_ptr%?13=2
 6970menu_ptr%?14=7:menu_ptr%?15=0
 6980menu_ptr%!20=44:menu_ptr%!24=0
 6990menu_item_ptr%=menu_ptr%+4
 7000WHILE menu$<>""
 7010menu_item_ptr%+=24
 7020menu_item$=FNfield(menu$,",")
 7030!menu_item_ptr%=0
 7040menu_item_ptr%!4=-1
 7050menu_item_ptr%!8=&7000021
 7060IF LEN(menu_item$)>width% THEN width%=LEN(menu_item$)
 7070$(menu_item_ptr%+12)=menu_item$+CHR$(0)
 7080t$(tcnt%)=menu_item$:tcnt%+=1
 7090ENDWHILE
 7100?menu_item_ptr%=?menu_item_ptr% OR %10000000
 7110menu_ptr%!16=(width%*8+6)*2
 7120=menu_ptr%
 7130:
 7140DEFFNcreatecatagorymenu(menu$)
 7150ccnt%=0
 7160menu_ptr%=cata_menu%
 7170$(menu_ptr%)=" "
 7180width%=1
 7190ENDIF
 7200menu_ptr%?12=7:menu_ptr%?13=2
 7210menu_ptr%?14=7:menu_ptr%?15=0
 7220menu_ptr%!20=44:menu_ptr%!24=0
 7230menu_item_ptr%=menu_ptr%+4
 7240WHILE menu$<>""
 7250menu_item_ptr%+=24
 7260menu_item$=FNfield(menu$,",")
 7270!menu_item_ptr%=0
 7280menu_item_ptr%!4=-1
 7290menu_item_ptr%!8=&7000021
 7300IF LEN(menu_item$)>width% THEN width%=LEN(menu_item$)
 7310$(menu_item_ptr%+12)=menu_item$+CHR$(0)
 7320c$(ccnt%)=menu_item$:ccnt%+=1
 7330ENDWHILE
 7340?menu_item_ptr%=?menu_item_ptr% OR %10000000
 7350menu_ptr%!16=(width%*8+6)*2
 7360=menu_ptr%
 7370:
 7380DEFPROCresetconfigurewin
 7390PROCwrite_mess(config%,39,"")
 7400PROCwrite_mess(config%,19,"")
 7410PROCwrite_mess(config%,43,"")
 7420PROCwrite_mess(config%,40,"")
 7430FOR loop=1 TO 18
 7440PROCwrite_mess(config%,loop,"")
 7450PROCwrite_mess(config%,20+loop,"")
 7460NEXT loop
 7470PROCwrite_mess(config%,47,"")
 7480PROCwrite_mess(config%,50,"")
 7490PROCwrite_mess(config%,53,"")
 7500PROCwrite_mess(config%,56,"")
 7502PROCwrite_mess(config%,66,"")
 7510ENDPROC
 7520:
 7530DEFPROCcreatenewfile
 7540LOCAL handle%
 7550lastcard%=0:clear%=FALSE
 7552PROCcleargrey(menu%,6)
 7560PROCsetgrey(menu%,5)
 7570PROCsetgrey(menu%,4)
 7580PROCsetgrey(file_menu%,1)
 7590PROCsetgrey(file_menu%,2)
 7600$table=""+CHR$(0):$(table+32)=""+CHR$(0):table!636=0
 7610DATA 39,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,19,18
 7620DATA 21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,40,43
 7630RESTORE 7610
 7640te$="":ce$=""
 7650FOR loop=1 TO 20
 7660READ handle%
 7670text$=FNgetbutton(config%,handle%)
 7680IF text$<>"" AND text$<>" " THEN te$=te$+","+text$
 7690NEXT loop
 7700FOR loop=1 TO 20
 7710READ handle%
 7720text$=FNgetbutton(config%,handle%)
 7730IF text$<>"" AND text$<>" " THEN ce$=ce$+","+text$
 7740NEXT loop
 7750te$=RIGHT$(te$,LENte$-1)
 7760ce$=RIGHT$(ce$,LENce$-1)
 7770topics%=FNcreatetopicmenu(te$)
 7780catas%=FNcreatecatagorymenu(ce$)
 7790$(table+64)=te$:$(table+320)=ce$
 7800$(table+576)=FNgetbutton(config%,47)
 7810$(table+588)=FNgetbutton(config%,50)
 7820$(table+600)=FNgetbutton(config%,53)
 7830$(table+612)=FNgetbutton(config%,56)
 7840clearbits%=0
 7850IF FNoption(config%,59)>0 clearbits%+=8:clt%=TRUE ELSE clt%=FALSE
 7860IF FNoption(config%,60)>0 clearbits%+=4:cli%=TRUE ELSE cli%=FALSE
 7870IF FNoption(config%,61)>0 clearbits%+=2:cld%=TRUE ELSE cld%=FALSE
 7880IF FNoption(config%,62)>0 clearbits%+=1:clp%=TRUE ELSE clp%=FALSE
 7889table?624=clearbits%:$(table+627)=FNgetbutton(config%,66)
 7890optt$=LEFT$(FNstring0(table+627),8)
 7892PROCEnableIcon(find%,8)
 7893PROCEnableIcon(add%,4)
 7894PROCwrite_mess(find%,8,optt$)
 7895PROCwrite_mess(add%,4,optt$)
 7896IF optt$=" " OR optt$="" THEN
 7897PROCDisableIcon(find%,8)
 7899PROCDisableIcon(add%,4)
 7900ENDIF
 7904PROCalter_browse(card%)
 7905PROCwrite_mess(finfo%,4,"")
 7906PROCwrite_mess(finfo%,8,"")
 7907PROCupdatesize
 7908PROCwrite_mess(finfo%,2,"<Unitled>")
 7909IF tcnt%=0 THEN t$(0)=""
 7910IF ccnt%=0 THEN c$(0)=""
 7911PROCwrite_mess(find%,3,t$(0))
 7912PROCwrite_mess(add%,7,t$(0))
 7914PROCwrite_mess(find%,6,c$(0))
 7916PROCwrite_mess(add%,10,c$(0))
 7917findtopic%=1:addtopic%=1:IF tcnt%=0 THEN PROCDisableIcon(find%,4):PROCDisableIcon(add%,8) ELSE PROCEnableIcon(find%,4):PROCEnableIcon(add%,8)
 7918findcata%=1:addcata%=1:IF ccnt%=0 THEN PROCDisableIcon(find%,7):PROCDisableIcon(add%,12) ELSE PROCEnableIcon(find%,7):PROCEnableIcon(add%,12)
 7919tst$=$(table+576):ist$=$(table+588)
 7920dst$=$(table+600):pst$=$(table+612)
 7921PROCwrite_mess(browse%,0,tst$+":")
 7922PROCwrite_mess(browse%,3,ist$+":")
 7923PROCwrite_mess(browse%,5,dst$+":")
 7924PROCwrite_mess(browse%,7,pst$+":")
 7925PROCwrite_mess(add%,23,tst$+":")
 7926PROCwrite_mess(add%,3,ist$+":")
 7927PROCwrite_mess(add%,11,dst$+":")
 7928PROCwrite_mess(add%,6,pst$+":")
 7930PROCwrite_mess(find%,13,tst$)
 7940PROCwrite_mess(find%,14,ist$)
 7942PROCwrite_mess(find%,15,dst$)
 7943PROCwrite_mess(find%,16,pst$)
 7945ENDPROC
 7946DEFPROCcopyconfigure
 7947SYS "Hourglass_On"
 7948PROCresetconfigurewin
 7949PROCSetIcon(config%,59,clt%)
 7950PROCSetIcon(config%,60,cli%)
 7960PROCSetIcon(config%,61,cld%)
 7970PROCSetIcon(config%,62,clp%)
 7980PROCwrite_mess(config%,47,$(table+576))
 7990PROCwrite_mess(config%,50,$(table+588))
 8000PROCwrite_mess(config%,53,$(table+600))
 8010PROCwrite_mess(config%,56,$(table+612))
 8020te$=$(table+64)+","
 8080RESTORE 7610
 8090REPEAT
 8100READ handle%
 8110a=INSTR(te$,",")
 8120a$=LEFT$(te$,a-1)
 8130te$=MID$(te$,a+1,256)
 8140PROCwrite_mess(config%,handle%,a$)
 8150UNTIL a=0
 8160RESTORE 7620
 8170ce$=$(table+320)+","
 8180REPEAT
 8190READ handle%
 8200a=INSTR(ce$,",")
 8210a$=LEFT$(ce$,a-1)
 8220ce$=MID$(ce$,a+1,256)
 8230PROCwrite_mess(config%,handle%,a$)
 8240UNTIL a=0
 8250PROCwrite_mess(config%,66,optt$)
 8252PROCwritevalid
 8260SYS "Hourglass_Off"
 8270ENDPROC
 8280:
 8290DEFPROCwritevalid
 8300!tq%=config%:tq%!4=66:SYS "Wimp_GetIconState",,tq%
 8310$(tq%!32)="z3;iType in your optional topic here."
 8320ENDPROC

� >!Archiver.!RunImage
7� Written by A. Rebmann, Version 2.02 � August 1992
d� Thanks to... (I Forgot!)   ...Oh, Simon Huntingdon for the brilliant         Interface module.
(:
2:� � �er(�$+" ( Internal code "+Þ+"."+ß+" )."):� �TVC
<!Task=&4B534154:Wimp_Version=2
FCș "Wimp_Initialise",Wimp_Version*100,Task,"Archiver" � ,thand%
P$ș "Wimp_ClaimInterface",,thand%
Zș "Hourglass_On"
d"�  q% 128,tq% 128,buffer% 1000
nLts=&2000:� temp% ts:endtemp%=temp%+ts:current_menu%=0:topics%=0:catas%=0
x� window% &3000,winpar% 512
�� finds (640*4)
�� t$(20),c$(20)
�� table (130*640)+640
�$� topic_menu% 512,cata_menu% 512
�Hdata%=0:choices%=0:save%=0:backgnd%=�:backsp$="":lastcard%=0:card%=0
�Fadding%=�:findtopic%=1:addtopic%=1:findcata%=1:addcata%=1:clear%=�
��initmenus
�!� clear=0 � (130*640)+640 � 4
�table!clear=0
�� clear
�� clear=0 � (640*4) � 4
�finds!clear=0
�� clear
.�("IconSprites <ArchiverDem$Dir>.Sprites")
9ș "Wimp_OpenTemplate",,"<ArchiverDem$Dir>.Templates"
Jș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"progInfo" � ,,temp%
"+ș "Wimp_CreateWindow",,window% � info%
,Iș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"addref2" � ,,temp%
6+ș "Wimp_CreateWindow",,window% � find%
@Iș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"options" � ,,temp%
J.ș "Wimp_CreateWindow",,window% � options%
THș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"addref" � ,,temp%
^*ș "Wimp_CreateWindow",,window% � add%
hHș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"Browse" � ,,temp%
r-ș "Wimp_CreateWindow",,window% � browse%
|Kș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"save_temp" � ,,temp%
�+ș "Wimp_CreateWindow",,window% � save%
�Jș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"fileInfo" � ,,temp%
�,ș "Wimp_CreateWindow",,window% � finfo%
�Kș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"customize" � ,,temp%
�-ș "Wimp_CreateWindow",,window% � config%
�Iș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"matches" � ,,temp%
�.ș "Wimp_CreateWindow",,window% � matches%
�Mș "Wimp_LoadTemplate",,window%,temp%,endtemp%,-1,"endofsearch" � ,,temp%
�0ș "Wimp_CreateWindow",,window% � endsearch%
�ș "Wimp_CloseTemplate"
&amenu%=�createmenu("Archiver,Info$,File,Show logs$,Browse$,Find item,Add item$,Options$,Quit")
0Xbrowse_menu%=�createmenu("Archiver,Goto$,Find item$,Add item,Edit item,Delete item")
:<goto_menu%=�createmenu("Goto,Next,Previous$,First,Last")
D5file_menu%=�createmenu("File,Info,Save,New file")
N�write_mess(find%,3,t$(0))
X�write_mess(add%,7,t$(0))
b�write_mess(find%,6,c$(0))
l�write_mess(add%,10,c$(0))
n�togglegrey(menu%,6)
v�togglegrey(menu%,5)
��togglegrey(menu%,4)
��togglegrey(file_menu%,1)
��togglegrey(file_menu%,2)
��menu_attach(menu%,1,info%)
�$�menu_attach(menu%,2,file_menu%)
�%�menu_attach(file_menu%,1,finfo%)
�$�menu_attach(file_menu%,2,save%)
�"�menu_attach(menu%,7,options%)
�&�menu_attach(file_menu%,3,config%)
�+�menu_attach(browse_menu%,1,goto_menu%)
�9icdata%=�iconbar("<ArchiverDem$Dir>",-1,"!ArchivDem")
�&�write_mess(finfo%,2,"<Untitled>")
��updatesize
�startupanload
ș "Hourglass_Off"
�
 $ș "Wimp_Poll",0,buffer% � poll%
*'ș "Wimp_PollPointer",poll%,,thand%
4Ȏ poll% �
>� 0:
HA� 1:� matches%=!buffer% �redrawmatches � �redrawwin(!buffer%)
R%� 2:ș "Wimp_OpenWindow",,buffer%
\&� 3:ș "Wimp_CloseWindow",,buffer%
f� 4:
p� 5:
z)� 6:�mouseclick(buffer%!8,buffer%!12)
�� 8:
�� 9:�menudone
�	� 10:
�� 17,18:
�Ȏ buffer%!16 �
�
� 0:�quit
�� 3,5:�loadsprites
�� &502:�sendhelp
��
��
�� 0
�
 ��mouseclick(click%,click2%)
!ș "Wimp_BorderIcon",,buffer%
$�� buffer%!16=icdata% � click%=2 � buffer%!12<0 � �show_menu(menu%,!buffer%-64,�menu_height(menu%)+120):mx%=!buffer%:my%=buffer%!4
.Q� buffer%!12=browse% � click%=2 � �show_menu(browse_menu%,!buffer%,buffer%!4)
8P� buffer%!16=icdata% � click%=4 � buffer%!12<0 � clear% � �openwindow(find%)
Bg� buffer%!16=icdata% � click%=1 � buffer%!12<0 � clear% � �alter_browse(card%):�openwindow(browse%)
L0� �click(config%,64,5)  �show_menu(-1,-1,-1)
V.� �click(config%,65,5)  �resetconfigurewin
`4� �click(config%,68,5) � clear%=� �copyconfigure
j?� �click(config%,63,5)  �createnewfile:�show_menu(-1,-1,-1)
t!� �click(find%,10,5)    �find
~0� �click(finfo%,12,5)   �show_menu(-1,-1,-1)
�0� �click(options%,13,5) �show_menu(-1,-1,-1)
��� �click(add%,13,5) � adding%=�     cardno%=lastcard%:�closewindow(add%):�add_card:�updatesize:lastcard%+=1:� lastcard%=1 � �changegreys
�g� �click(add%,14,5)     cardno%=card%:�shiftcards(cardno%):�closewindow(add%):�add_card:�updatesize
�P� �click(add%,13,5) � adding%=� � cardno%=card%:�closewindow(add%):�add_card
�Q� �click(find%,4,5)    �show_menu(topics%,!buffer%,buffer%!4):aw%=find%:ah%=3
�O� �click(add%,8,5)    �show_menu(topics%,!buffer%,buffer%!4):aw%=add%:ah%=7
�P� �click(find%,7,5)    �show_menu(catas%,!buffer%,buffer%!4):aw%=find%:ah%=6
�P� �click(add%,12,5)    �show_menu(catas%,!buffer%,buffer%!4):aw%=add%:ah%=10
�:� �click(browse%,11,5) � card%-=1:�alter_browse(card%)
�:� �click(browse%,12,5) � card%+=1:�alter_browse(card%)
7� �click(endsearch%,2,5) � �closewindow(endsearch%)

-buffer%!8=0:ș "Wimp_BorderIcon",,buffer%
�
%ݤclick(winder%,icern%,butterns%)
(S� buffer%!12=winder% � buffer%!16=icern% � (buffer%!8 � butterns%)=butterns% =�
2=�
<��menudone
F� menutext$
PHș "Wimp_DecodeMenu",,current_menu%,buffer%,�200," ") � ,,,menutext$
Z� �choice("Quit") � �quit
d*� �choice("Find") � �openwindow(find%)
nC� �choice("Browse") � �alter_browse(card%):�openwindow(browse%)
xr� �choice("Add item") � current_menu%=menu% � �DisableIcon(add%,14):adding%=�:�delete_fields:�openwindow(add%)
�x� �choice("Add item") � current_menu%=browse_menu% � �EnableIcon(add%,14):adding%=�:�delete_fields:�openwindow(add%)
�h� �choice("Edit item") cardno%=card%:�FillInFields:adding%=�:�DisableIcon(add%,14):�openwindow(add%)
�%� �choice("Delete") � �deletecard
�5� �choice("Next") � card%+=1:�alter_browse(card%)
�9� �choice("Previous") � card%-=1:�alter_browse(card%)
�5� �choice("First") � card%=0:�alter_browse(card%)
�>� �choice("Last") � card%=lastcard%-1:�alter_browse(card%)
�� �choice("Show log") �
�$tq%="ArchiverDem$Dir"+�(0)
�,ș "OS_ReadVarVal",tq%,q%,100,0,3 � ,,l%
�2f$=�$q%,l%)+".LogFiles":�("Filer_OpenDir "+f$)
��
�/� current_menu%=topics% � �topic(menutext$)
�1� current_menu%=catas% � �catagory(menutext$)
��
�ݤchoice(choice$)
�#� �menutext$,choice$)>0 =� � =�
:

��quit
&ș "Wimp_ReleaseInterface",,thand%
"#ș "Wimp_CloseDown",thand%,Task
,�
6:
@� Menu facilities
J:
T��initmenus
^.� menu_block% &2000:menu_free%=menu_block%
h�
r:
|1�  menu%=FNcreatemenu("Title,Item1,Item2...")
�:
�ݤcreatemenu(menu$)
�menu_ptr%=menu_free%
�title$=�field(menu$,",")
�� �(title$)>12 �
�$(menu_ptr%)=�title$,12)
�
width%=12
��
�$(menu_ptr%)=title$
�width%=�(title$)
��
�!menu_ptr%?12=7:menu_ptr%?13=2
�!menu_ptr%?14=7:menu_ptr%?15=0
"menu_ptr%!20=44:menu_ptr%!24=0
menu_item_ptr%=menu_ptr%+4
ȕ menu$<>""
&menu_item_ptr%+=24
0 menu_item$=�field(menu$,",")
:!menu_item_ptr%=0
Dmenu_item_ptr%!4=-1
Nmenu_item_ptr%!8=&7000021
Xȕ �"#$%^",�menu_item$))>0
bȎ �menu_item$) �
l5� "#":?menu_item_ptr%=?menu_item_ptr% � %00000001
v5� "$":?menu_item_ptr%=?menu_item_ptr% � %00000010
�9� "%":menu_item_ptr%?10=menu_item_ptr%?10 � %01000000
�5� "^":?menu_item_ptr%=?menu_item_ptr% � %00000100
��
�menu_item$=�menu_item$)
��
�1� �(menu_item$)>width% � width%=�(menu_item$)
�($(menu_item_ptr%+12)=menu_item$+�(0)
��
�/?menu_item_ptr%=?menu_item_ptr% � %10000000
�menu_ptr%!16=(width%*8+6)*2
� menu_free%=menu_item_ptr%+24
�=menu_ptr%
���show_menu(menu%,x%,y%)
current_menu%=menu%
menu_x%=x%
menu_y%=y%
 %ș "Wimp_CreateMenu",,menu%,x%,y%
*�
4ݤfield(� menu$,seperator$)
>3result$=�menu$,�menu$+seperator$,seperator$)-1)
H'menu$=�menu$,�(menu$)-�(result$)-1)
R=result$
\ݤmenu_height(menu%)
f� height%,menu_item_ptr%
pmenu_item_ptr%=menu%+28
z
height%=0
�&ȕ (?menu_item_ptr% � %10000000)=0
�menu_item_ptr%+=24
�height%+=1
��
�=96+(44*(height%+1))
�.��menu_attach(menu%,position%,attachment%)
�-menu%!(28+24*(position%-1)+4)=attachment%
��
� ݤiconbar(dir$,side,spname$)
�*S%=�(dir$+".!Sprites"):T%=�#S%+16:�#S%
�� isprites% T%
�!isprites%=T%:isprites%!8=1
�#ș "OS_SpriteOp",&109,isprites%
	4ș "OS_SpriteOp",&10A,isprites%,dir$+".!Sprites"
	8!q%=side:q%!4=0:q%!8=0:q%!12=68:q%!16=68:q%!20=&3102
	9� q%!24 (�spname$+1):$(q%!24)=spname$:q%!28=isprites%
	$q%!32=�spname$+1
	."ș "Wimp_CreateIcon",,q% � ic%
	8=ic%
	B��openwindow(han%)
	L!q%=han%
	V ș "Wimp_GetWindowState",,q%
	`ș "Wimp_OpenWindow",,q%
	j�
	t��closewindow(han%)
	~!q%=han%
	�ș "Wimp_CloseWindow",,q%
	��
	���er(error$)
	�error$=error$+�0
	�!tq%=0:$(tq%+4)=error$
	�*ș "Wimp_ReportError",tq%,1,"archiver"
	��
	�!��write_mess(win%,han%,mess$)
	�4!tq%=win%:tq%!4=han%:ș "Wimp_GetIconState",,tq%
	�$(tq%!28)=mess$+�(0)
	�9ș "Wimp_ForceRedraw",win%,tq%!8,tq%!12,tq%!16,tq%!20
	��
ݤgetbutton(window%,han%)

7!tq%=window%:tq%!4=han%:ș "Wimp_GetIconState",,tq%
=�string0(tq%!28)
��loadsprites
� � � �
(*� buffer%!40<>&194  � buffer%!16=3 � �
2� buffer%!40<>&194 � �
<file$=�string0(buffer%+44)
F%buffer%!16=4:buffer%!12=buffer%!8
P&ș "Wimp_SendMessage",17,buffer%,0
Q:� � �er(�$+" ( Internal code "+Þ+"."+ß+" )."):� �TVC
Z�loadfile(file$)
d�
nݤoption(win%,han%)
x!tq%=win%:tq%!4=han%
�ș "Wimp_GetIconState",,tq%
�%=tq%!24 � %1000000000000000000000
�8ݤstring0(a%)�a$:a$="":ȕ?a%>31:a$+=�?a%:a%+=1:�:=a$
���forceredraw(han%)
�7ș "Wimp_ForceRedraw",han%,0,-8-(120*fcount),1280,0
��
���setgrey(menu%,position%)
�Gmenu%?(38+24*(position%-1))=menu%?(38+24*(position%-1)) �  %1000000
��
� ��cleargrey(menu%,position%)
�Fmenu%?(38+24*(position%-1))=menu%?(38+24*(position%-1)) � %0111111
��
�!��togglegrey(menu%,position%)
Fmenu%?(38+24*(position%-1))=menu%?(38+24*(position%-1)) � %1000000
�
:
" ��DisableIcon(window%,icon%)
,tq%!0=window% : tq%!4=icon%
6 tq%!8=1<<22   : tq%!12=1<<22
@ș "Wimp_SetIconState",,tq%
J�
T:
^��EnableIcon(window%,icon%)
htq%!0=window% : tq%!4=icon%
r tq%!8=0       : tq%!12=1<<22
|ș "Wimp_SetIconState",,tq%
��
�:
�#��SetIcon(window%,icon%,state%)
�tq%!0=window% : tq%!4=icon%
�-� state%=� � tq%!8=1<<21   : tq%!12=1<<21
�,� state%=� � tq%!8=0      : tq%!12=1<<21
�ș "Wimp_SetIconState",,tq%
��
�:
���delete_fields
�%� clt%=� � �write_mess(add%,2,"")
�&� cli%=� � �write_mess(add%,17,"")
�%� cld%=� � �write_mess(add%,9,"")
%� clp%=� � �write_mess(add%,5,"")
�
:
&��add_card
0item$=�getbutton(add%,2)
:info$=�getbutton(add%,17)
Ddate$=�getbutton(add%,9)
Npage$=�getbutton(add%,5)
X"cata%=addcata%:topi%=addtopic%
b$� �option(add%,4)<>0  topi%+=100
l$$(table+(cardno%*130)+640)=item$
v'$(table+(cardno%*130)+640+32)=info$
�'$(table+(cardno%*130)+640+64)=date$
�'$(table+(cardno%*130)+640+96)=page$
�(?(table+(cardno%*130)+640+128)=cata%
�(?(table+(cardno%*130)+640+129)=topi%
��alter_browse(card%)
��
�:
���FillInFields
�2�write_mess(add%,2,$(table+(cardno%*130)+640))
�6�write_mess(add%,17,$(table+(cardno%*130)+640+32))
�5�write_mess(add%,9,$(table+(cardno%*130)+640+64))
�5�write_mess(add%,5,$(table+(cardno%*130)+640+96))
�Oaddcata%=?(table+(cardno%*130)+640+128):�write_mess(add%,10,c$(addcata%-1))

uaddtopic%=?(table+(cardno%*130)+640+129):� addtopic%>100 � addtopic%-=100:�SetIcon(add%,4,�) � �SetIcon(add%,4,�)

'�write_mess(add%,7,t$(addtopic%-1))

�

��shiftcards(cardno%)

 � fcard%,lcard%,a,b

*(� shiftloop=lastcard% � cardno% � -1

4a=shiftloop:b=shiftloop+1

>-$(table+(b*130)+640)=$(table+(a*130)+640)

H3$(table+(b*130)+640+32)=$(table+(a*130)+640+32)

R3$(table+(b*130)+640+64)=$(table+(a*130)+640+64)

\3$(table+(b*130)+640+96)=$(table+(a*130)+640+96)

f5?(table+(b*130)+640+128)=?(table+(a*130)+640+128)

p5?(table+(b*130)+640+129)=?(table+(a*130)+640+129)

z� shiftloop

�lastcard%+=1

��

�:

���deletecard

�cardno%=card%

�Hm$="Delete item "+�(cardno%+1)+" ("+$(table+(cardno%*130)+640)+") ?"

�tq%!0=255:$(tq%+4)=m$+�(0)

�>ș "Wimp_ReportError",tq%,%10011,"Delete item?" � ,button%

�� button%<>1 � �

�(� shiftloop=cardno% � lastcard% � -1

�a=shiftloop+1:b=shiftloop

�-$(table+(b*130)+640)=$(table+(a*130)+640)

�3$(table+(b*130)+640+32)=$(table+(a*130)+640+32)
3$(table+(b*130)+640+64)=$(table+(a*130)+640+64)
3$(table+(b*130)+640+96)=$(table+(a*130)+640+96)
5?(table+(b*130)+640+128)=?(table+(a*130)+640+128)
$5?(table+(b*130)+640+129)=?(table+(a*130)+640+129)
.� shiftloop
8lastcard%-=1
B'� card%>lastcard% � card%=lastcard%
L�alter_browse(card%)
V�
`:
j��alter_browse(� card%)
t� card%=lastcard% card%=0
~� card%<0 card%=lastcard%-1
�"item$=$(table+(card%*130)+640)
�%info$=$(table+(card%*130)+640+32)
�%date$=$(table+(card%*130)+640+64)
�%page$=$(table+(card%*130)+640+96)
�&cata%=?(table+(card%*130)+640+128)
�&topi%=?(table+(card%*130)+640+129)
�7� topi%>100 topi%-=100:opt$="("+optt$+")" � opt$=""
� �write_mess(browse%,1,item$)
� �write_mess(browse%,2,info$)
� �write_mess(browse%,6,page$)
� �write_mess(browse%,4,date$)
�� topi%=0 � topi%=1
�� cata%=0 � cata%=1
�.tops$=t$(topi%-1)+" "+c$(cata%-1)+" "+opt$
� �write_mess(browse%,8,tops$)
>�write_mess(browse%,13,�(card%+1)+" out of "+�(lastcard%))

Ȗ
�
:
^ݤlastbit(s$)
hȕ �s$,":")>0
rs$=�s$,�s$,":")+1)
|�
�ȕ �s$,".")>0
�s$=�s$,�s$,".")+1)
��
�=s$
���loadfile(file$)
�ș "Hourglass_On"
�!� clear=0 � (130*640)+640 � 4
�table!clear=0
�� clear
�!ș "OS_File",12,file$,table,0
�card%=0
�lastcard%=table!636
��alter_browse(card%)
�)�write_mess(finfo%,4,�string0(table))
,�write_mess(finfo%,8,�string0(table+32))
�updatesize
$�write_mess(finfo%,2,�file$,27))
*$te$=$(table+64):ce$=$(table+320)
4'tst$=$(table+576):ist$=$(table+588)
>'dst$=$(table+600):pst$=$(table+612)
H#�write_mess(browse%,0,tst$+":")
R#�write_mess(browse%,3,ist$+":")
\#�write_mess(browse%,5,dst$+":")
f#�write_mess(browse%,7,pst$+":")
p!�write_mess(add%,23,tst$+":")
z �write_mess(add%,3,ist$+":")
�!�write_mess(add%,11,dst$+":")
� �write_mess(add%,6,pst$+":")
��write_mess(find%,13,tst$)
��write_mess(find%,14,ist$)
��write_mess(find%,15,dst$)
��write_mess(find%,16,pst$)
�clt%=�:cli%=�:cld%=�:clp%=�
� � (table?624 � 8)>0 � clt%=�
� � (table?624 � 4)>0 � cli%=�
� � (table?624 � 2)>0 � cld%=�
� � (table?624 � 1)>0 � clp%=�
�!optt$=��string0(table+627),7)
�!topics%=�createtopicmenu(te$)
�#catas%=�createcatagorymenu(ce$)
��EnableIcon(find%,8)
��EnableIcon(add%,4)
��write_mess(find%,8,optt$)
�write_mess(add%,4,optt$)
� optt$=" " � optt$="" �
�DisableIcon(find%,8)
$�DisableIcon(add%,4)
.�
8�write_mess(find%,3,t$(0))
B�write_mess(add%,7,t$(0))
L�write_mess(find%,6,c$(0))
V�write_mess(add%,10,c$(0))
`findtopic%=1:addtopic%=1
jfindcata%=1:addcata%=1
tș "Hourglass_Smash"
~�changegreys
��
���updatesize
�� lastcard%=0 �
�cards=0
�bytes=0
��
�cards=lastcard%
bytes=(lastcard%*130)+640

�
4� cards=1 � phrase$="record" � phrase$="records"
;sentence$=�cards+" "+phrase$+" ("+�bytes+" bytes)"+�(0)
($�write_mess(finfo%,10,sentence$)
2�
<��topic(topic$)
F�write_mess(aw%,ah%,topic$)
P<� aw%=find% findtopic%=!buffer%+1 � addtopic%=!buffer%+1
Z�
d��catagory(catagory$)
n"�write_mess(aw%,ah%,catagory$)
x:� aw%=find% findcata%=!buffer%+1 � addcata%=!buffer%+1
��
���startupanload
�� i,numspaces,command
�ș "OS_GetEnv" � command
�$q%=�string0(command)+�(13)
�numspaces=0
�i=0
�ȕ numspaces<3
�� q%?i=&20 numspaces+=1
�i+=1
��
�file$=$(q%+i)
�%� �file$,"::")>0 �loadfile(file$)
�
��redrawwin(handle%)
,ș "Wimp_RedrawWindow",0,buffer% � more%
"ȕ more%
,#ș "Wimp_BorderWindow",,buffer%
6,ș "Wimp_GetRectangle",0,buffer% � more%
@�
J�
T��redrawmatches
^� more%,x0%,y0%,i%
h,ș "Wimp_RedrawWindow",0,buffer% � more%
r!�lwaorigin(buffer%+4,x0%,y0%)
|ȕ more%
��writetext(x0%,y0%,i%)
�
� �(16)-1
�,ș "Wimp_GetRectangle",0,buffer% � more%
��
��
���lwaorigin(b,� x%,� y%)
�x%=b!0-b!16
�y%=b!12-b!20
��
�:
���writetext(x0%,y0%,index%)
�$� i%,a%,b%,c%,d%,x1%,y1%,x2%,y2%
�0�lwacliprectangle(buffer%+4,x1%,y1%,x2%,y2%)
a%=(1024-12-y2%) � 40+1
b%=(1024-12-y1%) � 40+2
c%=(x1%-4) � 16+1
&d%=(x2%-4) � 16+2
0d%=d%-c%
:
� 0,11
D� i%=a% � b%
Ntext$=""
X� (i%-28)>-1 �
b� (i%-28) � 3=0 �
l� 8
v6ȓ Ȑ x0%+16*(c%-1),y0%+1024-40*(i%-1)+4,d%*16,-36
�3cata%=?(table+(�card((i%-28) � 3)*130)+640+128)
�3topi%=?(table+(�card((i%-28) � 3)*130)+640+129)
�7� topi%>100 opt$="("+optt$+")":topi%-=100 � opt$=""
�Ztext$=t$(topi%-1)+" "+c$(cata%-1)+" : "+$(table+(�card((i%-28) � 3)*130)+640)+" "+opt$
�� 1
��
�� 7
�v� (i%-28) � 3=1 � text$=$(table+(�card((i%-28) � 3)*130)+640+32)+" "+$(table+(�card((i%-28) � 3)*130)+640+64)+", "
�2� (i%-28) � 3=1 � pst$="Page" � text$+="Page "
�S� (i%-28) � 3=1 � text$+=$(table+(�card((i%-28) � 3)*130)+640+64+32) � text$=""
��
��
�(� x0%+4+16*(c%-1),y0%+1024-40*(i%-1)
�� �text$,c%,d%);
�� i%
�
:
1��lwacliprectangle(b,� x1%,� y1%,� x2%,� y2%)
 
� x0%,y0%
*�lwaorigin(b,x0%,y0%)
4x1%=b!24-x0%:y1%=b!28-y0%
>x2%=b!32-x0%:y2%=b!36-y0%
H�
R:
\ ��limit(lower,� value,upper)
f� value<lower � value=lower
p� value>upper � value=upper
z�
�ݤcaps(a$)
�� loop=1 � �a$
�b$=�a$,loop,1)
�� b$>"`" � b$<"{" �
�b$=�(�b$-32)
��a$,loop,1)=b$
��
�
� loop
�=a$
�
��find
�ș "Hourglass_On"
�find$=�getbutton(find%,9)
�find$=�caps(find$)
topi%=findtopic%
cata%=findcata%
)fno%=0:� �option(find%,14)<>0 fno%=32
"� �option(find%,15)<>0 fno%=64
"� �option(find%,16)<>0 fno%=96
*� �option(find%,8)<>0  opt%=� � opt%=�
$usecata%=(�option(find%,5))
.usetopi%=(�option(find%,2))
8&fcount=0:pc=0:pa=100/(lastcard%-1)
BW� �option(options%,12)>0 O=�("<ArchiverDem$Dir>.Log�Files."+�getbutton(options%,4))
L� scard=0 � lastcard%-1
V.item$=�caps($(table+(scard*130)+640+fno%))
`(chcata%=?(table+(scard*130)+640+128)
j(chtopi%=?(table+(scard*130)+640+129)
t9� chtopi%>100 chtopi2%=chtopi%-100 � chtopi2%=chtopi%
~1� usecata%=0 � (usecata%>0 � cata%=chcata%) �
�2� usetopi%=0 � (usetopi%>0 � topi%=chtopi2%) �
�'� opt%=� � (opt%=� � chtopi%>100) �
�b� �item$,find$)>0 � finds!(fcount*4)=scard:fcount+=1:� �option(options%,12)>0 �addtolog(scard)
��
��
��
�
pc+=pa
� ș "Hourglass_Percentage",pc
�� scard
�� fcount>0 �
� � �option(options%,7)>0 �
�   !q%=0:q%!4=-8-(120*fcount)
  q%!8=1280:q%!12=0

%  ș "Wimp_SetExtent",matches%,q%
6  �write_mess(matches%,0,"Items found = "+�fcount)
  �forceredraw(matches%)
(  �openwindow(matches%)
2  �closewindow(find%)
< �
F  � fcount=1 s$="" � s$="s"
P;  �write_mess(endsearch%,1,�fcount+" item"+s$+" found")
Z  �openwindow(endsearch%)
d  �closewindow(find%)
n �
x�
�� fcount=0 �
��er("No matches found.")
�� �option(options%,14)>0 �
�� c$(findcata%)<>"" �
�"ca$=c$(findcata%):findcata%+=1
��write_mess(find%,6,ca$)
��
��
��
�h� �option(options%,12)>0 �#O:�("SetType <ArchiverDem$Dir>.LogFiles."+�getbutton(options%,5)+" Text")
�ș "Hourglass_Off"
��
�ݤcard(number)
�=finds!(number*4)
���changegreys
�clear%=�
��cleargrey(menu%,6)
��cleargrey(menu%,5)
��cleargrey(menu%,4)
��cleargrey(file_menu%,1)
��cleargrey(file_menu%,2)
��
��writetofile(a$)
� b=1 � �a$
�#O,�(�a$,b,1))
"� b
,�
6��addtolog(card)
@� cata%,topi%
J%cata%=?(table+(card*130)+640+128)
T%topi%=?(table+(card*130)+640+129)
^7� topi%>100 opt$="("+optt$+")":topi%-=100 � opt$=""
hLtext$=t$(topi%-1)+" "+c$(cata%-1)+" : "+$(table+(card*130)+640)+" "+opt$
r#mag$=$(table+(card*130)+640+32)
|$date$=$(table+(card*130)+640+64)
�'rest$=$(table+(card*130)+640+64+32)
�'� pst$="Page" � rest$="Page "+rest$
��� �option(options%,10) � text$=text$+�(10):text2$=mag$+" "+date$+", "+rest$+�(10) � text$=text$+" ("+date$+")"+�(10):text2$=mag$+", "+rest$+�(10)
��writetofile(text$)
��writetofile(text2$)
��writetofile(�(10))
��
�:
���sendhelp
�(� buffer%!32=matches% � buffer%!36=0
�&ș "Wimp_SendInformation",,buffer%
��
�ݤcreatetopicmenu(menu$)
�tcnt%=0
menu_ptr%=topic_menu%
$(menu_ptr%)=" "
width%=1
&�
0!menu_ptr%?12=7:menu_ptr%?13=2
:!menu_ptr%?14=7:menu_ptr%?15=0
D"menu_ptr%!20=44:menu_ptr%!24=0
Nmenu_item_ptr%=menu_ptr%+4
Xȕ menu$<>""
bmenu_item_ptr%+=24
l menu_item$=�field(menu$,",")
v!menu_item_ptr%=0
�menu_item_ptr%!4=-1
�menu_item_ptr%!8=&7000021
�1� �(menu_item$)>width% � width%=�(menu_item$)
�($(menu_item_ptr%+12)=menu_item$+�(0)
�!t$(tcnt%)=menu_item$:tcnt%+=1
��
�/?menu_item_ptr%=?menu_item_ptr% � %10000000
�menu_ptr%!16=(width%*8+6)*2
�=menu_ptr%
�:
�ݤcreatecatagorymenu(menu$)
�ccnt%=0
�menu_ptr%=cata_menu%
$(menu_ptr%)=" "
width%=1
�
 !menu_ptr%?12=7:menu_ptr%?13=2
*!menu_ptr%?14=7:menu_ptr%?15=0
4"menu_ptr%!20=44:menu_ptr%!24=0
>menu_item_ptr%=menu_ptr%+4
Hȕ menu$<>""
Rmenu_item_ptr%+=24
\ menu_item$=�field(menu$,",")
f!menu_item_ptr%=0
pmenu_item_ptr%!4=-1
zmenu_item_ptr%!8=&7000021
�1� �(menu_item$)>width% � width%=�(menu_item$)
�($(menu_item_ptr%+12)=menu_item$+�(0)
�!c$(ccnt%)=menu_item$:ccnt%+=1
��
�/?menu_item_ptr%=?menu_item_ptr% � %10000000
�menu_ptr%!16=(width%*8+6)*2
�=menu_ptr%
�:
���resetconfigurewin
��write_mess(config%,39,"")
��write_mess(config%,19,"")
��write_mess(config%,43,"")
��write_mess(config%,40,"")
� loop=1 � 18
 �write_mess(config%,loop,"")
#�write_mess(config%,20+loop,"")
$
� loop
.�write_mess(config%,47,"")
8�write_mess(config%,50,"")
B�write_mess(config%,53,"")
L�write_mess(config%,56,"")
N�write_mess(config%,66,"")
V�
`:
j��createnewfile
t
� handle%
~lastcard%=0:clear%=�
��cleargrey(menu%,6)
��setgrey(menu%,5)
��setgrey(menu%,4)
��setgrey(file_menu%,1)
��setgrey(file_menu%,2)
�2$table=""+�(0):$(table+32)=""+�(0):table!636=0
�8� 39,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,19,18
�A� 21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,40,43
�
� �tz]
�te$="":ce$=""
�� loop=1 � 20
�
� handle%
�%text$=�getbutton(config%,handle%)
0� text$<>"" � text$<>" " � te$=te$+","+text$


� loop
� loop=1 � 20

� handle%
(%text$=�getbutton(config%,handle%)
20� text$<>"" � text$<>" " � ce$=ce$+","+text$
<
� loop
Fte$=�te$,�te$-1)
Pce$=�ce$,�ce$-1)
Z!topics%=�createtopicmenu(te$)
d#catas%=�createcatagorymenu(ce$)
n$$(table+64)=te$:$(table+320)=ce$
x'$(table+576)=�getbutton(config%,47)
�'$(table+588)=�getbutton(config%,50)
�'$(table+600)=�getbutton(config%,53)
�'$(table+612)=�getbutton(config%,56)
�clearbits%=0
�9� �option(config%,59)>0 clearbits%+=8:clt%=� � clt%=�
�9� �option(config%,60)>0 clearbits%+=4:cli%=� � cli%=�
�9� �option(config%,61)>0 clearbits%+=2:cld%=� � cld%=�
�9� �option(config%,62)>0 clearbits%+=1:clp%=� � clp%=�
�<table?624=clearbits%:$(table+627)=�getbutton(config%,66)
�!optt$=��string0(table+627),8)
��EnableIcon(find%,8)
��EnableIcon(add%,4)
��write_mess(find%,8,optt$)
��write_mess(add%,4,optt$)
�� optt$=" " � optt$="" �
��DisableIcon(find%,8)
��DisableIcon(add%,4)
��
��alter_browse(card%)
��write_mess(finfo%,4,"")
��write_mess(finfo%,8,"")
��updatesize
�%�write_mess(finfo%,2,"<Unitled>")
�� tcnt%=0 � t$(0)=""
�� ccnt%=0 � c$(0)=""
��write_mess(find%,3,t$(0))
��write_mess(add%,7,t$(0))
��write_mess(find%,6,c$(0))
��write_mess(add%,10,c$(0))
�~findtopic%=1:addtopic%=1:� tcnt%=0 � �DisableIcon(find%,4):�DisableIcon(add%,8) � �EnableIcon(find%,4):�EnableIcon(add%,8)
�~findcata%=1:addcata%=1:� ccnt%=0 � �DisableIcon(find%,7):�DisableIcon(add%,12) � �EnableIcon(find%,7):�EnableIcon(add%,12)
�'tst$=$(table+576):ist$=$(table+588)
�'dst$=$(table+600):pst$=$(table+612)
�#�write_mess(browse%,0,tst$+":")
�#�write_mess(browse%,3,ist$+":")
�#�write_mess(browse%,5,dst$+":")
�#�write_mess(browse%,7,pst$+":")
�!�write_mess(add%,23,tst$+":")
� �write_mess(add%,3,ist$+":")
�!�write_mess(add%,11,dst$+":")
� �write_mess(add%,6,pst$+":")
��write_mess(find%,13,tst$)
�write_mess(find%,14,ist$)
�write_mess(find%,15,dst$)
�write_mess(find%,16,pst$)
	�

��copyconfigure
ș "Hourglass_On"
�resetconfigurewin

�SetIcon(config%,59,clt%)
�SetIcon(config%,60,cli%)
�SetIcon(config%,61,cld%)
"�SetIcon(config%,62,clp%)
,(�write_mess(config%,47,$(table+576))
6(�write_mess(config%,50,$(table+588))
@(�write_mess(config%,53,$(table+600))
J(�write_mess(config%,56,$(table+612))
Tte$=$(table+64)+","
�
� �tz]
��
�
� handle%
�a=�te$,",")
�a$=�te$,a-1)
�te$=�te$,a+1,256)
�#�write_mess(config%,handle%,a$)
�	� a=0
�
� �dD]
�ce$=$(table+320)+","
��
�
� handle%
 a=�ce$,",")
 a$=�ce$,a-1)
 ce$=�ce$,a+1,256)
 &#�write_mess(config%,handle%,a$)
 0	� a=0
 :!�write_mess(config%,66,optt$)
 <�writevalid
 Dș "Hourglass_Off"
 N�
 X:
 b��writevalid
 l5!tq%=config%:tq%!4=66:ș "Wimp_GetIconState",,tq%
 v5$(tq%!32)="z3;iType in your optional topic here."
 ��
�
00000000  0d 00 0a 1a f4 20 3e 21  41 72 63 68 69 76 65 72  |..... >!Archiver|
00000010  2e 21 52 75 6e 49 6d 61  67 65 0d 00 14 37 f4 20  |.!RunImage...7. |
00000020  57 72 69 74 74 65 6e 20  62 79 20 41 2e 20 52 65  |Written by A. Re|
00000030  62 6d 61 6e 6e 2c 20 56  65 72 73 69 6f 6e 20 32  |bmann, Version 2|
00000040  2e 30 32 20 a9 20 41 75  67 75 73 74 20 31 39 39  |.02 . August 199|
00000050  32 0d 00 1e 64 f4 20 54  68 61 6e 6b 73 20 74 6f  |2...d. Thanks to|
00000060  2e 2e 2e 20 28 49 20 46  6f 72 67 6f 74 21 29 20  |... (I Forgot!) |
00000070  20 20 2e 2e 2e 4f 68 2c  20 53 69 6d 6f 6e 20 48  |  ...Oh, Simon H|
00000080  75 6e 74 69 6e 67 64 6f  6e 20 66 6f 72 20 74 68  |untingdon for th|
00000090  65 20 62 72 69 6c 6c 69  61 6e 74 20 20 20 20 20  |e brilliant     |
000000a0  20 20 20 20 49 6e 74 65  72 66 61 63 65 20 6d 6f  |    Interface mo|
000000b0  64 75 6c 65 2e 0d 00 28  05 3a 0d 00 32 3a ee 20  |dule...(.:..2:. |
000000c0  85 20 f2 65 72 28 f6 24  2b 22 20 28 20 49 6e 74  |. .er(.$+" ( Int|
000000d0  65 72 6e 61 6c 20 63 6f  64 65 20 22 2b c3 9e 2b  |ernal code "+..+|
000000e0  22 2e 22 2b c3 9f 2b 22  20 29 2e 22 29 3a e5 20  |"."+..+" )."):. |
000000f0  8d 54 56 43 0d 00 3c 21  54 61 73 6b 3d 26 34 42  |.TVC..<!Task=&4B|
00000100  35 33 34 31 35 34 3a 57  69 6d 70 5f 56 65 72 73  |534154:Wimp_Vers|
00000110  69 6f 6e 3d 32 0d 00 46  43 c8 99 20 22 57 69 6d  |ion=2..FC.. "Wim|
00000120  70 5f 49 6e 69 74 69 61  6c 69 73 65 22 2c 57 69  |p_Initialise",Wi|
00000130  6d 70 5f 56 65 72 73 69  6f 6e 2a 31 30 30 2c 54  |mp_Version*100,T|
00000140  61 73 6b 2c 22 41 72 63  68 69 76 65 72 22 20 b8  |ask,"Archiver" .|
00000150  20 2c 74 68 61 6e 64 25  0d 00 50 24 c8 99 20 22  | ,thand%..P$.. "|
00000160  57 69 6d 70 5f 43 6c 61  69 6d 49 6e 74 65 72 66  |Wimp_ClaimInterf|
00000170  61 63 65 22 2c 2c 74 68  61 6e 64 25 0d 00 5a 15  |ace",,thand%..Z.|
00000180  c8 99 20 22 48 6f 75 72  67 6c 61 73 73 5f 4f 6e  |.. "Hourglass_On|
00000190  22 0d 00 64 22 de 20 20  71 25 20 31 32 38 2c 74  |"..d".  q% 128,t|
000001a0  71 25 20 31 32 38 2c 62  75 66 66 65 72 25 20 31  |q% 128,buffer% 1|
000001b0  30 30 30 0d 00 6e 4c 74  73 3d 26 32 30 30 30 3a  |000..nLts=&2000:|
000001c0  de 20 74 65 6d 70 25 20  74 73 3a 65 6e 64 74 65  |. temp% ts:endte|
000001d0  6d 70 25 3d 74 65 6d 70  25 2b 74 73 3a 63 75 72  |mp%=temp%+ts:cur|
000001e0  72 65 6e 74 5f 6d 65 6e  75 25 3d 30 3a 74 6f 70  |rent_menu%=0:top|
000001f0  69 63 73 25 3d 30 3a 63  61 74 61 73 25 3d 30 0d  |ics%=0:catas%=0.|
00000200  00 78 1f de 20 77 69 6e  64 6f 77 25 20 26 33 30  |.x.. window% &30|
00000210  30 30 2c 77 69 6e 70 61  72 25 20 35 31 32 0d 00  |00,winpar% 512..|
00000220  82 13 de 20 66 69 6e 64  73 20 28 36 34 30 2a 34  |... finds (640*4|
00000230  29 0d 00 8c 13 de 20 74  24 28 32 30 29 2c 63 24  |)..... t$(20),c$|
00000240  28 32 30 29 0d 00 96 19  de 20 74 61 62 6c 65 20  |(20)..... table |
00000250  28 31 33 30 2a 36 34 30  29 2b 36 34 30 0d 00 a0  |(130*640)+640...|
00000260  24 de 20 74 6f 70 69 63  5f 6d 65 6e 75 25 20 35  |$. topic_menu% 5|
00000270  31 32 2c 63 61 74 61 5f  6d 65 6e 75 25 20 35 31  |12,cata_menu% 51|
00000280  32 0d 00 aa 48 64 61 74  61 25 3d 30 3a 63 68 6f  |2...Hdata%=0:cho|
00000290  69 63 65 73 25 3d 30 3a  73 61 76 65 25 3d 30 3a  |ices%=0:save%=0:|
000002a0  62 61 63 6b 67 6e 64 25  3d a3 3a 62 61 63 6b 73  |backgnd%=.:backs|
000002b0  70 24 3d 22 22 3a 6c 61  73 74 63 61 72 64 25 3d  |p$="":lastcard%=|
000002c0  30 3a 63 61 72 64 25 3d  30 0d 00 b4 46 61 64 64  |0:card%=0...Fadd|
000002d0  69 6e 67 25 3d b9 3a 66  69 6e 64 74 6f 70 69 63  |ing%=.:findtopic|
000002e0  25 3d 31 3a 61 64 64 74  6f 70 69 63 25 3d 31 3a  |%=1:addtopic%=1:|
000002f0  66 69 6e 64 63 61 74 61  25 3d 31 3a 61 64 64 63  |findcata%=1:addc|
00000300  61 74 61 25 3d 31 3a 63  6c 65 61 72 25 3d a3 0d  |ata%=1:clear%=..|
00000310  00 be 0e f2 69 6e 69 74  6d 65 6e 75 73 0d 00 c8  |....initmenus...|
00000320  21 e3 20 63 6c 65 61 72  3d 30 20 b8 20 28 31 33  |!. clear=0 . (13|
00000330  30 2a 36 34 30 29 2b 36  34 30 20 88 20 34 0d 00  |0*640)+640 . 4..|
00000340  d2 11 74 61 62 6c 65 21  63 6c 65 61 72 3d 30 0d  |..table!clear=0.|
00000350  00 dc 0b ed 20 63 6c 65  61 72 0d 00 e6 1b e3 20  |.... clear..... |
00000360  63 6c 65 61 72 3d 30 20  b8 20 28 36 34 30 2a 34  |clear=0 . (640*4|
00000370  29 20 88 20 34 0d 00 f0  11 66 69 6e 64 73 21 63  |) . 4....finds!c|
00000380  6c 65 61 72 3d 30 0d 00  fa 0b ed 20 63 6c 65 61  |lear=0..... clea|
00000390  72 0d 01 04 2e ff 28 22  49 63 6f 6e 53 70 72 69  |r.....("IconSpri|
000003a0  74 65 73 20 3c 41 72 63  68 69 76 65 72 44 65 6d  |tes <ArchiverDem|
000003b0  24 44 69 72 3e 2e 53 70  72 69 74 65 73 22 29 0d  |$Dir>.Sprites").|
000003c0  01 0e 39 c8 99 20 22 57  69 6d 70 5f 4f 70 65 6e  |..9.. "Wimp_Open|
000003d0  54 65 6d 70 6c 61 74 65  22 2c 2c 22 3c 41 72 63  |Template",,"<Arc|
000003e0  68 69 76 65 72 44 65 6d  24 44 69 72 3e 2e 54 65  |hiverDem$Dir>.Te|
000003f0  6d 70 6c 61 74 65 73 22  0d 01 18 4a c8 99 20 22  |mplates"...J.. "|
00000400  57 69 6d 70 5f 4c 6f 61  64 54 65 6d 70 6c 61 74  |Wimp_LoadTemplat|
00000410  65 22 2c 2c 77 69 6e 64  6f 77 25 2c 74 65 6d 70  |e",,window%,temp|
00000420  25 2c 65 6e 64 74 65 6d  70 25 2c 2d 31 2c 22 70  |%,endtemp%,-1,"p|
00000430  72 6f 67 49 6e 66 6f 22  20 b8 20 2c 2c 74 65 6d  |rogInfo" . ,,tem|
00000440  70 25 0d 01 22 2b c8 99  20 22 57 69 6d 70 5f 43  |p%.."+.. "Wimp_C|
00000450  72 65 61 74 65 57 69 6e  64 6f 77 22 2c 2c 77 69  |reateWindow",,wi|
00000460  6e 64 6f 77 25 20 b8 20  69 6e 66 6f 25 0d 01 2c  |ndow% . info%..,|
00000470  49 c8 99 20 22 57 69 6d  70 5f 4c 6f 61 64 54 65  |I.. "Wimp_LoadTe|
00000480  6d 70 6c 61 74 65 22 2c  2c 77 69 6e 64 6f 77 25  |mplate",,window%|
00000490  2c 74 65 6d 70 25 2c 65  6e 64 74 65 6d 70 25 2c  |,temp%,endtemp%,|
000004a0  2d 31 2c 22 61 64 64 72  65 66 32 22 20 b8 20 2c  |-1,"addref2" . ,|
000004b0  2c 74 65 6d 70 25 0d 01  36 2b c8 99 20 22 57 69  |,temp%..6+.. "Wi|
000004c0  6d 70 5f 43 72 65 61 74  65 57 69 6e 64 6f 77 22  |mp_CreateWindow"|
000004d0  2c 2c 77 69 6e 64 6f 77  25 20 b8 20 66 69 6e 64  |,,window% . find|
000004e0  25 0d 01 40 49 c8 99 20  22 57 69 6d 70 5f 4c 6f  |%..@I.. "Wimp_Lo|
000004f0  61 64 54 65 6d 70 6c 61  74 65 22 2c 2c 77 69 6e  |adTemplate",,win|
00000500  64 6f 77 25 2c 74 65 6d  70 25 2c 65 6e 64 74 65  |dow%,temp%,endte|
00000510  6d 70 25 2c 2d 31 2c 22  6f 70 74 69 6f 6e 73 22  |mp%,-1,"options"|
00000520  20 b8 20 2c 2c 74 65 6d  70 25 0d 01 4a 2e c8 99  | . ,,temp%..J...|
00000530  20 22 57 69 6d 70 5f 43  72 65 61 74 65 57 69 6e  | "Wimp_CreateWin|
00000540  64 6f 77 22 2c 2c 77 69  6e 64 6f 77 25 20 b8 20  |dow",,window% . |
00000550  6f 70 74 69 6f 6e 73 25  0d 01 54 48 c8 99 20 22  |options%..TH.. "|
00000560  57 69 6d 70 5f 4c 6f 61  64 54 65 6d 70 6c 61 74  |Wimp_LoadTemplat|
00000570  65 22 2c 2c 77 69 6e 64  6f 77 25 2c 74 65 6d 70  |e",,window%,temp|
00000580  25 2c 65 6e 64 74 65 6d  70 25 2c 2d 31 2c 22 61  |%,endtemp%,-1,"a|
00000590  64 64 72 65 66 22 20 b8  20 2c 2c 74 65 6d 70 25  |ddref" . ,,temp%|
000005a0  0d 01 5e 2a c8 99 20 22  57 69 6d 70 5f 43 72 65  |..^*.. "Wimp_Cre|
000005b0  61 74 65 57 69 6e 64 6f  77 22 2c 2c 77 69 6e 64  |ateWindow",,wind|
000005c0  6f 77 25 20 b8 20 61 64  64 25 0d 01 68 48 c8 99  |ow% . add%..hH..|
000005d0  20 22 57 69 6d 70 5f 4c  6f 61 64 54 65 6d 70 6c  | "Wimp_LoadTempl|
000005e0  61 74 65 22 2c 2c 77 69  6e 64 6f 77 25 2c 74 65  |ate",,window%,te|
000005f0  6d 70 25 2c 65 6e 64 74  65 6d 70 25 2c 2d 31 2c  |mp%,endtemp%,-1,|
00000600  22 42 72 6f 77 73 65 22  20 b8 20 2c 2c 74 65 6d  |"Browse" . ,,tem|
00000610  70 25 0d 01 72 2d c8 99  20 22 57 69 6d 70 5f 43  |p%..r-.. "Wimp_C|
00000620  72 65 61 74 65 57 69 6e  64 6f 77 22 2c 2c 77 69  |reateWindow",,wi|
00000630  6e 64 6f 77 25 20 b8 20  62 72 6f 77 73 65 25 0d  |ndow% . browse%.|
00000640  01 7c 4b c8 99 20 22 57  69 6d 70 5f 4c 6f 61 64  |.|K.. "Wimp_Load|
00000650  54 65 6d 70 6c 61 74 65  22 2c 2c 77 69 6e 64 6f  |Template",,windo|
00000660  77 25 2c 74 65 6d 70 25  2c 65 6e 64 74 65 6d 70  |w%,temp%,endtemp|
00000670  25 2c 2d 31 2c 22 73 61  76 65 5f 74 65 6d 70 22  |%,-1,"save_temp"|
00000680  20 b8 20 2c 2c 74 65 6d  70 25 0d 01 86 2b c8 99  | . ,,temp%...+..|
00000690  20 22 57 69 6d 70 5f 43  72 65 61 74 65 57 69 6e  | "Wimp_CreateWin|
000006a0  64 6f 77 22 2c 2c 77 69  6e 64 6f 77 25 20 b8 20  |dow",,window% . |
000006b0  73 61 76 65 25 0d 01 90  4a c8 99 20 22 57 69 6d  |save%...J.. "Wim|
000006c0  70 5f 4c 6f 61 64 54 65  6d 70 6c 61 74 65 22 2c  |p_LoadTemplate",|
000006d0  2c 77 69 6e 64 6f 77 25  2c 74 65 6d 70 25 2c 65  |,window%,temp%,e|
000006e0  6e 64 74 65 6d 70 25 2c  2d 31 2c 22 66 69 6c 65  |ndtemp%,-1,"file|
000006f0  49 6e 66 6f 22 20 b8 20  2c 2c 74 65 6d 70 25 0d  |Info" . ,,temp%.|
00000700  01 9a 2c c8 99 20 22 57  69 6d 70 5f 43 72 65 61  |..,.. "Wimp_Crea|
00000710  74 65 57 69 6e 64 6f 77  22 2c 2c 77 69 6e 64 6f  |teWindow",,windo|
00000720  77 25 20 b8 20 66 69 6e  66 6f 25 0d 01 a4 4b c8  |w% . finfo%...K.|
00000730  99 20 22 57 69 6d 70 5f  4c 6f 61 64 54 65 6d 70  |. "Wimp_LoadTemp|
00000740  6c 61 74 65 22 2c 2c 77  69 6e 64 6f 77 25 2c 74  |late",,window%,t|
00000750  65 6d 70 25 2c 65 6e 64  74 65 6d 70 25 2c 2d 31  |emp%,endtemp%,-1|
00000760  2c 22 63 75 73 74 6f 6d  69 7a 65 22 20 b8 20 2c  |,"customize" . ,|
00000770  2c 74 65 6d 70 25 0d 01  ae 2d c8 99 20 22 57 69  |,temp%...-.. "Wi|
00000780  6d 70 5f 43 72 65 61 74  65 57 69 6e 64 6f 77 22  |mp_CreateWindow"|
00000790  2c 2c 77 69 6e 64 6f 77  25 20 b8 20 63 6f 6e 66  |,,window% . conf|
000007a0  69 67 25 0d 01 b8 49 c8  99 20 22 57 69 6d 70 5f  |ig%...I.. "Wimp_|
000007b0  4c 6f 61 64 54 65 6d 70  6c 61 74 65 22 2c 2c 77  |LoadTemplate",,w|
000007c0  69 6e 64 6f 77 25 2c 74  65 6d 70 25 2c 65 6e 64  |indow%,temp%,end|
000007d0  74 65 6d 70 25 2c 2d 31  2c 22 6d 61 74 63 68 65  |temp%,-1,"matche|
000007e0  73 22 20 b8 20 2c 2c 74  65 6d 70 25 0d 01 c2 2e  |s" . ,,temp%....|
000007f0  c8 99 20 22 57 69 6d 70  5f 43 72 65 61 74 65 57  |.. "Wimp_CreateW|
00000800  69 6e 64 6f 77 22 2c 2c  77 69 6e 64 6f 77 25 20  |indow",,window% |
00000810  b8 20 6d 61 74 63 68 65  73 25 0d 01 cc 4d c8 99  |. matches%...M..|
00000820  20 22 57 69 6d 70 5f 4c  6f 61 64 54 65 6d 70 6c  | "Wimp_LoadTempl|
00000830  61 74 65 22 2c 2c 77 69  6e 64 6f 77 25 2c 74 65  |ate",,window%,te|
00000840  6d 70 25 2c 65 6e 64 74  65 6d 70 25 2c 2d 31 2c  |mp%,endtemp%,-1,|
00000850  22 65 6e 64 6f 66 73 65  61 72 63 68 22 20 b8 20  |"endofsearch" . |
00000860  2c 2c 74 65 6d 70 25 0d  01 d6 30 c8 99 20 22 57  |,,temp%...0.. "W|
00000870  69 6d 70 5f 43 72 65 61  74 65 57 69 6e 64 6f 77  |imp_CreateWindow|
00000880  22 2c 2c 77 69 6e 64 6f  77 25 20 b8 20 65 6e 64  |",,window% . end|
00000890  73 65 61 72 63 68 25 0d  01 e0 1b c8 99 20 22 57  |search%...... "W|
000008a0  69 6d 70 5f 43 6c 6f 73  65 54 65 6d 70 6c 61 74  |imp_CloseTemplat|
000008b0  65 22 0d 02 26 61 6d 65  6e 75 25 3d a4 63 72 65  |e"..&amenu%=.cre|
000008c0  61 74 65 6d 65 6e 75 28  22 41 72 63 68 69 76 65  |atemenu("Archive|
000008d0  72 2c 49 6e 66 6f 24 2c  46 69 6c 65 2c 53 68 6f  |r,Info$,File,Sho|
000008e0  77 20 6c 6f 67 73 24 2c  42 72 6f 77 73 65 24 2c  |w logs$,Browse$,|
000008f0  46 69 6e 64 20 69 74 65  6d 2c 41 64 64 20 69 74  |Find item,Add it|
00000900  65 6d 24 2c 4f 70 74 69  6f 6e 73 24 2c 51 75 69  |em$,Options$,Qui|
00000910  74 22 29 0d 02 30 58 62  72 6f 77 73 65 5f 6d 65  |t")..0Xbrowse_me|
00000920  6e 75 25 3d a4 63 72 65  61 74 65 6d 65 6e 75 28  |nu%=.createmenu(|
00000930  22 41 72 63 68 69 76 65  72 2c 47 6f 74 6f 24 2c  |"Archiver,Goto$,|
00000940  46 69 6e 64 20 69 74 65  6d 24 2c 41 64 64 20 69  |Find item$,Add i|
00000950  74 65 6d 2c 45 64 69 74  20 69 74 65 6d 2c 44 65  |tem,Edit item,De|
00000960  6c 65 74 65 20 69 74 65  6d 22 29 0d 02 3a 3c 67  |lete item")..:<g|
00000970  6f 74 6f 5f 6d 65 6e 75  25 3d a4 63 72 65 61 74  |oto_menu%=.creat|
00000980  65 6d 65 6e 75 28 22 47  6f 74 6f 2c 4e 65 78 74  |emenu("Goto,Next|
00000990  2c 50 72 65 76 69 6f 75  73 24 2c 46 69 72 73 74  |,Previous$,First|
000009a0  2c 4c 61 73 74 22 29 0d  02 44 35 66 69 6c 65 5f  |,Last")..D5file_|
000009b0  6d 65 6e 75 25 3d a4 63  72 65 61 74 65 6d 65 6e  |menu%=.createmen|
000009c0  75 28 22 46 69 6c 65 2c  49 6e 66 6f 2c 53 61 76  |u("File,Info,Sav|
000009d0  65 2c 4e 65 77 20 66 69  6c 65 22 29 0d 02 4e 1e  |e,New file")..N.|
000009e0  f2 77 72 69 74 65 5f 6d  65 73 73 28 66 69 6e 64  |.write_mess(find|
000009f0  25 2c 33 2c 74 24 28 30  29 29 0d 02 58 1d f2 77  |%,3,t$(0))..X..w|
00000a00  72 69 74 65 5f 6d 65 73  73 28 61 64 64 25 2c 37  |rite_mess(add%,7|
00000a10  2c 74 24 28 30 29 29 0d  02 62 1e f2 77 72 69 74  |,t$(0))..b..writ|
00000a20  65 5f 6d 65 73 73 28 66  69 6e 64 25 2c 36 2c 63  |e_mess(find%,6,c|
00000a30  24 28 30 29 29 0d 02 6c  1e f2 77 72 69 74 65 5f  |$(0))..l..write_|
00000a40  6d 65 73 73 28 61 64 64  25 2c 31 30 2c 63 24 28  |mess(add%,10,c$(|
00000a50  30 29 29 0d 02 6e 18 f2  74 6f 67 67 6c 65 67 72  |0))..n..togglegr|
00000a60  65 79 28 6d 65 6e 75 25  2c 36 29 0d 02 76 18 f2  |ey(menu%,6)..v..|
00000a70  74 6f 67 67 6c 65 67 72  65 79 28 6d 65 6e 75 25  |togglegrey(menu%|
00000a80  2c 35 29 0d 02 80 18 f2  74 6f 67 67 6c 65 67 72  |,5).....togglegr|
00000a90  65 79 28 6d 65 6e 75 25  2c 34 29 0d 02 8a 1d f2  |ey(menu%,4).....|
00000aa0  74 6f 67 67 6c 65 67 72  65 79 28 66 69 6c 65 5f  |togglegrey(file_|
00000ab0  6d 65 6e 75 25 2c 31 29  0d 02 94 1d f2 74 6f 67  |menu%,1).....tog|
00000ac0  67 6c 65 67 72 65 79 28  66 69 6c 65 5f 6d 65 6e  |glegrey(file_men|
00000ad0  75 25 2c 32 29 0d 02 9e  1f f2 6d 65 6e 75 5f 61  |u%,2).....menu_a|
00000ae0  74 74 61 63 68 28 6d 65  6e 75 25 2c 31 2c 69 6e  |ttach(menu%,1,in|
00000af0  66 6f 25 29 0d 02 a8 24  f2 6d 65 6e 75 5f 61 74  |fo%)...$.menu_at|
00000b00  74 61 63 68 28 6d 65 6e  75 25 2c 32 2c 66 69 6c  |tach(menu%,2,fil|
00000b10  65 5f 6d 65 6e 75 25 29  0d 02 b2 25 f2 6d 65 6e  |e_menu%)...%.men|
00000b20  75 5f 61 74 74 61 63 68  28 66 69 6c 65 5f 6d 65  |u_attach(file_me|
00000b30  6e 75 25 2c 31 2c 66 69  6e 66 6f 25 29 0d 02 bc  |nu%,1,finfo%)...|
00000b40  24 f2 6d 65 6e 75 5f 61  74 74 61 63 68 28 66 69  |$.menu_attach(fi|
00000b50  6c 65 5f 6d 65 6e 75 25  2c 32 2c 73 61 76 65 25  |le_menu%,2,save%|
00000b60  29 0d 02 c6 22 f2 6d 65  6e 75 5f 61 74 74 61 63  |)...".menu_attac|
00000b70  68 28 6d 65 6e 75 25 2c  37 2c 6f 70 74 69 6f 6e  |h(menu%,7,option|
00000b80  73 25 29 0d 02 d0 26 f2  6d 65 6e 75 5f 61 74 74  |s%)...&.menu_att|
00000b90  61 63 68 28 66 69 6c 65  5f 6d 65 6e 75 25 2c 33  |ach(file_menu%,3|
00000ba0  2c 63 6f 6e 66 69 67 25  29 0d 02 da 2b f2 6d 65  |,config%)...+.me|
00000bb0  6e 75 5f 61 74 74 61 63  68 28 62 72 6f 77 73 65  |nu_attach(browse|
00000bc0  5f 6d 65 6e 75 25 2c 31  2c 67 6f 74 6f 5f 6d 65  |_menu%,1,goto_me|
00000bd0  6e 75 25 29 0d 02 e4 39  69 63 64 61 74 61 25 3d  |nu%)...9icdata%=|
00000be0  a4 69 63 6f 6e 62 61 72  28 22 3c 41 72 63 68 69  |.iconbar("<Archi|
00000bf0  76 65 72 44 65 6d 24 44  69 72 3e 22 2c 2d 31 2c  |verDem$Dir>",-1,|
00000c00  22 21 41 72 63 68 69 76  44 65 6d 22 29 0d 02 ee  |"!ArchivDem")...|
00000c10  26 f2 77 72 69 74 65 5f  6d 65 73 73 28 66 69 6e  |&.write_mess(fin|
00000c20  66 6f 25 2c 32 2c 22 3c  55 6e 74 69 74 6c 65 64  |fo%,2,"<Untitled|
00000c30  3e 22 29 0d 02 f8 0f f2  75 70 64 61 74 65 73 69  |>").....updatesi|
00000c40  7a 65 0d 03 02 12 f2 73  74 61 72 74 75 70 61 6e  |ze.....startupan|
00000c50  6c 6f 61 64 0d 03 0c 16  c8 99 20 22 48 6f 75 72  |load...... "Hour|
00000c60  67 6c 61 73 73 5f 4f 66  66 22 0d 03 16 05 f5 0d  |glass_Off"......|
00000c70  03 20 24 c8 99 20 22 57  69 6d 70 5f 50 6f 6c 6c  |. $.. "Wimp_Poll|
00000c80  22 2c 30 2c 62 75 66 66  65 72 25 20 b8 20 70 6f  |",0,buffer% . po|
00000c90  6c 6c 25 0d 03 2a 27 c8  99 20 22 57 69 6d 70 5f  |ll%..*'.. "Wimp_|
00000ca0  50 6f 6c 6c 50 6f 69 6e  74 65 72 22 2c 70 6f 6c  |PollPointer",pol|
00000cb0  6c 25 2c 2c 74 68 61 6e  64 25 0d 03 34 0e c8 8e  |l%,,thand%..4...|
00000cc0  20 70 6f 6c 6c 25 20 ca  0d 03 3e 08 c9 20 30 3a  | poll% ...>.. 0:|
00000cd0  0d 03 48 41 c9 20 31 3a  e7 20 6d 61 74 63 68 65  |..HA. 1:. matche|
00000ce0  73 25 3d 21 62 75 66 66  65 72 25 20 f2 72 65 64  |s%=!buffer% .red|
00000cf0  72 61 77 6d 61 74 63 68  65 73 20 8b 20 f2 72 65  |rawmatches . .re|
00000d00  64 72 61 77 77 69 6e 28  21 62 75 66 66 65 72 25  |drawwin(!buffer%|
00000d10  29 0d 03 52 25 c9 20 32  3a c8 99 20 22 57 69 6d  |)..R%. 2:.. "Wim|
00000d20  70 5f 4f 70 65 6e 57 69  6e 64 6f 77 22 2c 2c 62  |p_OpenWindow",,b|
00000d30  75 66 66 65 72 25 0d 03  5c 26 c9 20 33 3a c8 99  |uffer%..\&. 3:..|
00000d40  20 22 57 69 6d 70 5f 43  6c 6f 73 65 57 69 6e 64  | "Wimp_CloseWind|
00000d50  6f 77 22 2c 2c 62 75 66  66 65 72 25 0d 03 66 08  |ow",,buffer%..f.|
00000d60  c9 20 34 3a 0d 03 70 08  c9 20 35 3a 0d 03 7a 29  |. 4:..p.. 5:..z)|
00000d70  c9 20 36 3a f2 6d 6f 75  73 65 63 6c 69 63 6b 28  |. 6:.mouseclick(|
00000d80  62 75 66 66 65 72 25 21  38 2c 62 75 66 66 65 72  |buffer%!8,buffer|
00000d90  25 21 31 32 29 0d 03 8e  08 c9 20 38 3a 0d 03 98  |%!12)..... 8:...|
00000da0  11 c9 20 39 3a f2 6d 65  6e 75 64 6f 6e 65 0d 03  |.. 9:.menudone..|
00000db0  a2 09 c9 20 31 30 3a 0d  03 ac 0c c9 20 31 37 2c  |... 10:..... 17,|
00000dc0  31 38 3a 0d 03 b6 13 c8  8e 20 62 75 66 66 65 72  |18:...... buffer|
00000dd0  25 21 31 36 20 ca 0d 03  c0 0d c9 20 30 3a f2 71  |%!16 ...... 0:.q|
00000de0  75 69 74 0d 03 d4 16 c9  20 33 2c 35 3a f2 6c 6f  |uit..... 3,5:.lo|
00000df0  61 64 73 70 72 69 74 65  73 0d 03 de 14 c9 20 26  |adsprites..... &|
00000e00  35 30 32 3a f2 73 65 6e  64 68 65 6c 70 0d 03 e8  |502:.sendhelp...|
00000e10  05 cb 0d 03 f2 05 cb 0d  03 fc 07 fd 20 30 0d 04  |............ 0..|
00000e20  06 05 e0 0d 04 10 20 dd  f2 6d 6f 75 73 65 63 6c  |...... ..mousecl|
00000e30  69 63 6b 28 63 6c 69 63  6b 25 2c 63 6c 69 63 6b  |ick(click%,click|
00000e40  32 25 29 0d 04 1a 21 c8  99 20 22 57 69 6d 70 5f  |2%)...!.. "Wimp_|
00000e50  42 6f 72 64 65 72 49 63  6f 6e 22 2c 2c 62 75 66  |BorderIcon",,buf|
00000e60  66 65 72 25 0d 04 24 85  e7 20 62 75 66 66 65 72  |fer%..$.. buffer|
00000e70  25 21 31 36 3d 69 63 64  61 74 61 25 20 80 20 63  |%!16=icdata% . c|
00000e80  6c 69 63 6b 25 3d 32 20  80 20 62 75 66 66 65 72  |lick%=2 . buffer|
00000e90  25 21 31 32 3c 30 20 8c  20 f2 73 68 6f 77 5f 6d  |%!12<0 . .show_m|
00000ea0  65 6e 75 28 6d 65 6e 75  25 2c 21 62 75 66 66 65  |enu(menu%,!buffe|
00000eb0  72 25 2d 36 34 2c a4 6d  65 6e 75 5f 68 65 69 67  |r%-64,.menu_heig|
00000ec0  68 74 28 6d 65 6e 75 25  29 2b 31 32 30 29 3a 6d  |ht(menu%)+120):m|
00000ed0  78 25 3d 21 62 75 66 66  65 72 25 3a 6d 79 25 3d  |x%=!buffer%:my%=|
00000ee0  62 75 66 66 65 72 25 21  34 0d 04 2e 51 e7 20 62  |buffer%!4...Q. b|
00000ef0  75 66 66 65 72 25 21 31  32 3d 62 72 6f 77 73 65  |uffer%!12=browse|
00000f00  25 20 80 20 63 6c 69 63  6b 25 3d 32 20 8c 20 f2  |% . click%=2 . .|
00000f10  73 68 6f 77 5f 6d 65 6e  75 28 62 72 6f 77 73 65  |show_menu(browse|
00000f20  5f 6d 65 6e 75 25 2c 21  62 75 66 66 65 72 25 2c  |_menu%,!buffer%,|
00000f30  62 75 66 66 65 72 25 21  34 29 0d 04 38 50 e7 20  |buffer%!4)..8P. |
00000f40  62 75 66 66 65 72 25 21  31 36 3d 69 63 64 61 74  |buffer%!16=icdat|
00000f50  61 25 20 80 20 63 6c 69  63 6b 25 3d 34 20 80 20  |a% . click%=4 . |
00000f60  62 75 66 66 65 72 25 21  31 32 3c 30 20 80 20 63  |buffer%!12<0 . c|
00000f70  6c 65 61 72 25 20 8c 20  f2 6f 70 65 6e 77 69 6e  |lear% . .openwin|
00000f80  64 6f 77 28 66 69 6e 64  25 29 0d 04 42 67 e7 20  |dow(find%)..Bg. |
00000f90  62 75 66 66 65 72 25 21  31 36 3d 69 63 64 61 74  |buffer%!16=icdat|
00000fa0  61 25 20 80 20 63 6c 69  63 6b 25 3d 31 20 80 20  |a% . click%=1 . |
00000fb0  62 75 66 66 65 72 25 21  31 32 3c 30 20 80 20 63  |buffer%!12<0 . c|
00000fc0  6c 65 61 72 25 20 8c 20  f2 61 6c 74 65 72 5f 62  |lear% . .alter_b|
00000fd0  72 6f 77 73 65 28 63 61  72 64 25 29 3a f2 6f 70  |rowse(card%):.op|
00000fe0  65 6e 77 69 6e 64 6f 77  28 62 72 6f 77 73 65 25  |enwindow(browse%|
00000ff0  29 0d 04 4c 30 e7 20 a4  63 6c 69 63 6b 28 63 6f  |)..L0. .click(co|
00001000  6e 66 69 67 25 2c 36 34  2c 35 29 20 20 f2 73 68  |nfig%,64,5)  .sh|
00001010  6f 77 5f 6d 65 6e 75 28  2d 31 2c 2d 31 2c 2d 31  |ow_menu(-1,-1,-1|
00001020  29 0d 04 56 2e e7 20 a4  63 6c 69 63 6b 28 63 6f  |)..V.. .click(co|
00001030  6e 66 69 67 25 2c 36 35  2c 35 29 20 20 f2 72 65  |nfig%,65,5)  .re|
00001040  73 65 74 63 6f 6e 66 69  67 75 72 65 77 69 6e 0d  |setconfigurewin.|
00001050  04 60 34 e7 20 a4 63 6c  69 63 6b 28 63 6f 6e 66  |.`4. .click(conf|
00001060  69 67 25 2c 36 38 2c 35  29 20 80 20 63 6c 65 61  |ig%,68,5) . clea|
00001070  72 25 3d b9 20 f2 63 6f  70 79 63 6f 6e 66 69 67  |r%=. .copyconfig|
00001080  75 72 65 0d 04 6a 3f e7  20 a4 63 6c 69 63 6b 28  |ure..j?. .click(|
00001090  63 6f 6e 66 69 67 25 2c  36 33 2c 35 29 20 20 f2  |config%,63,5)  .|
000010a0  63 72 65 61 74 65 6e 65  77 66 69 6c 65 3a f2 73  |createnewfile:.s|
000010b0  68 6f 77 5f 6d 65 6e 75  28 2d 31 2c 2d 31 2c 2d  |how_menu(-1,-1,-|
000010c0  31 29 0d 04 74 21 e7 20  a4 63 6c 69 63 6b 28 66  |1)..t!. .click(f|
000010d0  69 6e 64 25 2c 31 30 2c  35 29 20 20 20 20 f2 66  |ind%,10,5)    .f|
000010e0  69 6e 64 0d 04 7e 30 e7  20 a4 63 6c 69 63 6b 28  |ind..~0. .click(|
000010f0  66 69 6e 66 6f 25 2c 31  32 2c 35 29 20 20 20 f2  |finfo%,12,5)   .|
00001100  73 68 6f 77 5f 6d 65 6e  75 28 2d 31 2c 2d 31 2c  |show_menu(-1,-1,|
00001110  2d 31 29 0d 04 88 30 e7  20 a4 63 6c 69 63 6b 28  |-1)...0. .click(|
00001120  6f 70 74 69 6f 6e 73 25  2c 31 33 2c 35 29 20 f2  |options%,13,5) .|
00001130  73 68 6f 77 5f 6d 65 6e  75 28 2d 31 2c 2d 31 2c  |show_menu(-1,-1,|
00001140  2d 31 29 0d 04 92 8c e7  20 a4 63 6c 69 63 6b 28  |-1)..... .click(|
00001150  61 64 64 25 2c 31 33 2c  35 29 20 80 20 61 64 64  |add%,13,5) . add|
00001160  69 6e 67 25 3d b9 20 20  20 20 20 63 61 72 64 6e  |ing%=.     cardn|
00001170  6f 25 3d 6c 61 73 74 63  61 72 64 25 3a f2 63 6c  |o%=lastcard%:.cl|
00001180  6f 73 65 77 69 6e 64 6f  77 28 61 64 64 25 29 3a  |osewindow(add%):|
00001190  f2 61 64 64 5f 63 61 72  64 3a f2 75 70 64 61 74  |.add_card:.updat|
000011a0  65 73 69 7a 65 3a 6c 61  73 74 63 61 72 64 25 2b  |esize:lastcard%+|
000011b0  3d 31 3a e7 20 6c 61 73  74 63 61 72 64 25 3d 31  |=1:. lastcard%=1|
000011c0  20 8c 20 f2 63 68 61 6e  67 65 67 72 65 79 73 0d  | . .changegreys.|
000011d0  04 9c 67 e7 20 a4 63 6c  69 63 6b 28 61 64 64 25  |..g. .click(add%|
000011e0  2c 31 34 2c 35 29 20 20  20 20 20 63 61 72 64 6e  |,14,5)     cardn|
000011f0  6f 25 3d 63 61 72 64 25  3a f2 73 68 69 66 74 63  |o%=card%:.shiftc|
00001200  61 72 64 73 28 63 61 72  64 6e 6f 25 29 3a f2 63  |ards(cardno%):.c|
00001210  6c 6f 73 65 77 69 6e 64  6f 77 28 61 64 64 25 29  |losewindow(add%)|
00001220  3a f2 61 64 64 5f 63 61  72 64 3a f2 75 70 64 61  |:.add_card:.upda|
00001230  74 65 73 69 7a 65 0d 04  a6 50 e7 20 a4 63 6c 69  |tesize...P. .cli|
00001240  63 6b 28 61 64 64 25 2c  31 33 2c 35 29 20 80 20  |ck(add%,13,5) . |
00001250  61 64 64 69 6e 67 25 3d  a3 20 8c 20 63 61 72 64  |adding%=. . card|
00001260  6e 6f 25 3d 63 61 72 64  25 3a f2 63 6c 6f 73 65  |no%=card%:.close|
00001270  77 69 6e 64 6f 77 28 61  64 64 25 29 3a f2 61 64  |window(add%):.ad|
00001280  64 5f 63 61 72 64 0d 04  b0 51 e7 20 a4 63 6c 69  |d_card...Q. .cli|
00001290  63 6b 28 66 69 6e 64 25  2c 34 2c 35 29 20 20 20  |ck(find%,4,5)   |
000012a0  20 f2 73 68 6f 77 5f 6d  65 6e 75 28 74 6f 70 69  | .show_menu(topi|
000012b0  63 73 25 2c 21 62 75 66  66 65 72 25 2c 62 75 66  |cs%,!buffer%,buf|
000012c0  66 65 72 25 21 34 29 3a  61 77 25 3d 66 69 6e 64  |fer%!4):aw%=find|
000012d0  25 3a 61 68 25 3d 33 0d  04 ba 4f e7 20 a4 63 6c  |%:ah%=3...O. .cl|
000012e0  69 63 6b 28 61 64 64 25  2c 38 2c 35 29 20 20 20  |ick(add%,8,5)   |
000012f0  20 f2 73 68 6f 77 5f 6d  65 6e 75 28 74 6f 70 69  | .show_menu(topi|
00001300  63 73 25 2c 21 62 75 66  66 65 72 25 2c 62 75 66  |cs%,!buffer%,buf|
00001310  66 65 72 25 21 34 29 3a  61 77 25 3d 61 64 64 25  |fer%!4):aw%=add%|
00001320  3a 61 68 25 3d 37 0d 04  c4 50 e7 20 a4 63 6c 69  |:ah%=7...P. .cli|
00001330  63 6b 28 66 69 6e 64 25  2c 37 2c 35 29 20 20 20  |ck(find%,7,5)   |
00001340  20 f2 73 68 6f 77 5f 6d  65 6e 75 28 63 61 74 61  | .show_menu(cata|
00001350  73 25 2c 21 62 75 66 66  65 72 25 2c 62 75 66 66  |s%,!buffer%,buff|
00001360  65 72 25 21 34 29 3a 61  77 25 3d 66 69 6e 64 25  |er%!4):aw%=find%|
00001370  3a 61 68 25 3d 36 0d 04  ce 50 e7 20 a4 63 6c 69  |:ah%=6...P. .cli|
00001380  63 6b 28 61 64 64 25 2c  31 32 2c 35 29 20 20 20  |ck(add%,12,5)   |
00001390  20 f2 73 68 6f 77 5f 6d  65 6e 75 28 63 61 74 61  | .show_menu(cata|
000013a0  73 25 2c 21 62 75 66 66  65 72 25 2c 62 75 66 66  |s%,!buffer%,buff|
000013b0  65 72 25 21 34 29 3a 61  77 25 3d 61 64 64 25 3a  |er%!4):aw%=add%:|
000013c0  61 68 25 3d 31 30 0d 04  d8 3a e7 20 a4 63 6c 69  |ah%=10...:. .cli|
000013d0  63 6b 28 62 72 6f 77 73  65 25 2c 31 31 2c 35 29  |ck(browse%,11,5)|
000013e0  20 8c 20 63 61 72 64 25  2d 3d 31 3a f2 61 6c 74  | . card%-=1:.alt|
000013f0  65 72 5f 62 72 6f 77 73  65 28 63 61 72 64 25 29  |er_browse(card%)|
00001400  0d 04 e2 3a e7 20 a4 63  6c 69 63 6b 28 62 72 6f  |...:. .click(bro|
00001410  77 73 65 25 2c 31 32 2c  35 29 20 8c 20 63 61 72  |wse%,12,5) . car|
00001420  64 25 2b 3d 31 3a f2 61  6c 74 65 72 5f 62 72 6f  |d%+=1:.alter_bro|
00001430  77 73 65 28 63 61 72 64  25 29 0d 05 00 37 e7 20  |wse(card%)...7. |
00001440  a4 63 6c 69 63 6b 28 65  6e 64 73 65 61 72 63 68  |.click(endsearch|
00001450  25 2c 32 2c 35 29 20 8c  20 f2 63 6c 6f 73 65 77  |%,2,5) . .closew|
00001460  69 6e 64 6f 77 28 65 6e  64 73 65 61 72 63 68 25  |indow(endsearch%|
00001470  29 0d 05 0a 2d 62 75 66  66 65 72 25 21 38 3d 30  |)...-buffer%!8=0|
00001480  3a c8 99 20 22 57 69 6d  70 5f 42 6f 72 64 65 72  |:.. "Wimp_Border|
00001490  49 63 6f 6e 22 2c 2c 62  75 66 66 65 72 25 0d 05  |Icon",,buffer%..|
000014a0  14 05 e1 0d 05 1e 25 dd  a4 63 6c 69 63 6b 28 77  |......%..click(w|
000014b0  69 6e 64 65 72 25 2c 69  63 65 72 6e 25 2c 62 75  |inder%,icern%,bu|
000014c0  74 74 65 72 6e 73 25 29  0d 05 28 53 e7 20 62 75  |tterns%)..(S. bu|
000014d0  66 66 65 72 25 21 31 32  3d 77 69 6e 64 65 72 25  |ffer%!12=winder%|
000014e0  20 80 20 62 75 66 66 65  72 25 21 31 36 3d 69 63  | . buffer%!16=ic|
000014f0  65 72 6e 25 20 80 20 28  62 75 66 66 65 72 25 21  |ern% . (buffer%!|
00001500  38 20 84 20 62 75 74 74  65 72 6e 73 25 29 3d 62  |8 . butterns%)=b|
00001510  75 74 74 65 72 6e 73 25  20 3d b9 0d 05 32 06 3d  |utterns% =...2.=|
00001520  a3 0d 05 3c 0e dd f2 6d  65 6e 75 64 6f 6e 65 0d  |...<...menudone.|
00001530  05 46 0f ea 20 6d 65 6e  75 74 65 78 74 24 0d 05  |.F.. menutext$..|
00001540  50 48 c8 99 20 22 57 69  6d 70 5f 44 65 63 6f 64  |PH.. "Wimp_Decod|
00001550  65 4d 65 6e 75 22 2c 2c  63 75 72 72 65 6e 74 5f  |eMenu",,current_|
00001560  6d 65 6e 75 25 2c 62 75  66 66 65 72 25 2c c4 32  |menu%,buffer%,.2|
00001570  30 30 2c 22 20 22 29 20  b8 20 2c 2c 2c 6d 65 6e  |00," ") . ,,,men|
00001580  75 74 65 78 74 24 0d 05  5a 1d e7 20 a4 63 68 6f  |utext$..Z.. .cho|
00001590  69 63 65 28 22 51 75 69  74 22 29 20 8c 20 f2 71  |ice("Quit") . .q|
000015a0  75 69 74 0d 05 64 2a e7  20 a4 63 68 6f 69 63 65  |uit..d*. .choice|
000015b0  28 22 46 69 6e 64 22 29  20 8c 20 f2 6f 70 65 6e  |("Find") . .open|
000015c0  77 69 6e 64 6f 77 28 66  69 6e 64 25 29 0d 05 6e  |window(find%)..n|
000015d0  43 e7 20 a4 63 68 6f 69  63 65 28 22 42 72 6f 77  |C. .choice("Brow|
000015e0  73 65 22 29 20 8c 20 f2  61 6c 74 65 72 5f 62 72  |se") . .alter_br|
000015f0  6f 77 73 65 28 63 61 72  64 25 29 3a f2 6f 70 65  |owse(card%):.ope|
00001600  6e 77 69 6e 64 6f 77 28  62 72 6f 77 73 65 25 29  |nwindow(browse%)|
00001610  0d 05 78 72 e7 20 a4 63  68 6f 69 63 65 28 22 41  |..xr. .choice("A|
00001620  64 64 20 69 74 65 6d 22  29 20 80 20 63 75 72 72  |dd item") . curr|
00001630  65 6e 74 5f 6d 65 6e 75  25 3d 6d 65 6e 75 25 20  |ent_menu%=menu% |
00001640  8c 20 f2 44 69 73 61 62  6c 65 49 63 6f 6e 28 61  |. .DisableIcon(a|
00001650  64 64 25 2c 31 34 29 3a  61 64 64 69 6e 67 25 3d  |dd%,14):adding%=|
00001660  b9 3a f2 64 65 6c 65 74  65 5f 66 69 65 6c 64 73  |.:.delete_fields|
00001670  3a f2 6f 70 65 6e 77 69  6e 64 6f 77 28 61 64 64  |:.openwindow(add|
00001680  25 29 0d 05 82 78 e7 20  a4 63 68 6f 69 63 65 28  |%)...x. .choice(|
00001690  22 41 64 64 20 69 74 65  6d 22 29 20 80 20 63 75  |"Add item") . cu|
000016a0  72 72 65 6e 74 5f 6d 65  6e 75 25 3d 62 72 6f 77  |rrent_menu%=brow|
000016b0  73 65 5f 6d 65 6e 75 25  20 8c 20 f2 45 6e 61 62  |se_menu% . .Enab|
000016c0  6c 65 49 63 6f 6e 28 61  64 64 25 2c 31 34 29 3a  |leIcon(add%,14):|
000016d0  61 64 64 69 6e 67 25 3d  b9 3a f2 64 65 6c 65 74  |adding%=.:.delet|
000016e0  65 5f 66 69 65 6c 64 73  3a f2 6f 70 65 6e 77 69  |e_fields:.openwi|
000016f0  6e 64 6f 77 28 61 64 64  25 29 0d 05 8c 68 e7 20  |ndow(add%)...h. |
00001700  a4 63 68 6f 69 63 65 28  22 45 64 69 74 20 69 74  |.choice("Edit it|
00001710  65 6d 22 29 20 63 61 72  64 6e 6f 25 3d 63 61 72  |em") cardno%=car|
00001720  64 25 3a f2 46 69 6c 6c  49 6e 46 69 65 6c 64 73  |d%:.FillInFields|
00001730  3a 61 64 64 69 6e 67 25  3d a3 3a f2 44 69 73 61  |:adding%=.:.Disa|
00001740  62 6c 65 49 63 6f 6e 28  61 64 64 25 2c 31 34 29  |bleIcon(add%,14)|
00001750  3a f2 6f 70 65 6e 77 69  6e 64 6f 77 28 61 64 64  |:.openwindow(add|
00001760  25 29 0d 05 96 25 e7 20  a4 63 68 6f 69 63 65 28  |%)...%. .choice(|
00001770  22 44 65 6c 65 74 65 22  29 20 8c 20 f2 64 65 6c  |"Delete") . .del|
00001780  65 74 65 63 61 72 64 0d  05 a0 35 e7 20 a4 63 68  |etecard...5. .ch|
00001790  6f 69 63 65 28 22 4e 65  78 74 22 29 20 8c 20 63  |oice("Next") . c|
000017a0  61 72 64 25 2b 3d 31 3a  f2 61 6c 74 65 72 5f 62  |ard%+=1:.alter_b|
000017b0  72 6f 77 73 65 28 63 61  72 64 25 29 0d 05 aa 39  |rowse(card%)...9|
000017c0  e7 20 a4 63 68 6f 69 63  65 28 22 50 72 65 76 69  |. .choice("Previ|
000017d0  6f 75 73 22 29 20 8c 20  63 61 72 64 25 2d 3d 31  |ous") . card%-=1|
000017e0  3a f2 61 6c 74 65 72 5f  62 72 6f 77 73 65 28 63  |:.alter_browse(c|
000017f0  61 72 64 25 29 0d 05 b4  35 e7 20 a4 63 68 6f 69  |ard%)...5. .choi|
00001800  63 65 28 22 46 69 72 73  74 22 29 20 8c 20 63 61  |ce("First") . ca|
00001810  72 64 25 3d 30 3a f2 61  6c 74 65 72 5f 62 72 6f  |rd%=0:.alter_bro|
00001820  77 73 65 28 63 61 72 64  25 29 0d 05 be 3e e7 20  |wse(card%)...>. |
00001830  a4 63 68 6f 69 63 65 28  22 4c 61 73 74 22 29 20  |.choice("Last") |
00001840  8c 20 63 61 72 64 25 3d  6c 61 73 74 63 61 72 64  |. card%=lastcard|
00001850  25 2d 31 3a f2 61 6c 74  65 72 5f 62 72 6f 77 73  |%-1:.alter_brows|
00001860  65 28 63 61 72 64 25 29  0d 05 c8 1b e7 20 a4 63  |e(card%)..... .c|
00001870  68 6f 69 63 65 28 22 53  68 6f 77 20 6c 6f 67 22  |hoice("Show log"|
00001880  29 20 8c 0d 05 c9 1f 24  74 71 25 3d 22 41 72 63  |) .....$tq%="Arc|
00001890  68 69 76 65 72 44 65 6d  24 44 69 72 22 2b bd 28  |hiverDem$Dir"+.(|
000018a0  30 29 0d 05 ca 2c c8 99  20 22 4f 53 5f 52 65 61  |0)...,.. "OS_Rea|
000018b0  64 56 61 72 56 61 6c 22  2c 74 71 25 2c 71 25 2c  |dVarVal",tq%,q%,|
000018c0  31 30 30 2c 30 2c 33 20  b8 20 2c 2c 6c 25 0d 05  |100,0,3 . ,,l%..|
000018d0  cb 32 66 24 3d c0 24 71  25 2c 6c 25 29 2b 22 2e  |.2f$=.$q%,l%)+".|
000018e0  4c 6f 67 46 69 6c 65 73  22 3a ff 28 22 46 69 6c  |LogFiles":.("Fil|
000018f0  65 72 5f 4f 70 65 6e 44  69 72 20 22 2b 66 24 29  |er_OpenDir "+f$)|
00001900  0d 05 cd 05 cd 0d 05 d2  2f e7 20 63 75 72 72 65  |......../. curre|
00001910  6e 74 5f 6d 65 6e 75 25  3d 74 6f 70 69 63 73 25  |nt_menu%=topics%|
00001920  20 8c 20 f2 74 6f 70 69  63 28 6d 65 6e 75 74 65  | . .topic(menute|
00001930  78 74 24 29 0d 05 dc 31  e7 20 63 75 72 72 65 6e  |xt$)...1. curren|
00001940  74 5f 6d 65 6e 75 25 3d  63 61 74 61 73 25 20 8c  |t_menu%=catas% .|
00001950  20 f2 63 61 74 61 67 6f  72 79 28 6d 65 6e 75 74  | .catagory(menut|
00001960  65 78 74 24 29 0d 05 e6  05 e1 0d 05 f0 15 dd a4  |ext$)...........|
00001970  63 68 6f 69 63 65 28 63  68 6f 69 63 65 24 29 0d  |choice(choice$).|
00001980  05 fa 23 e7 20 a7 6d 65  6e 75 74 65 78 74 24 2c  |..#. .menutext$,|
00001990  63 68 6f 69 63 65 24 29  3e 30 20 3d b9 20 8b 20  |choice$)>0 =. . |
000019a0  3d a3 0d 06 04 05 3a 0d  06 0e 0a dd f2 71 75 69  |=.....:......qui|
000019b0  74 0d 06 18 26 c8 99 20  22 57 69 6d 70 5f 52 65  |t...&.. "Wimp_Re|
000019c0  6c 65 61 73 65 49 6e 74  65 72 66 61 63 65 22 2c  |leaseInterface",|
000019d0  2c 74 68 61 6e 64 25 0d  06 22 23 c8 99 20 22 57  |,thand%.."#.. "W|
000019e0  69 6d 70 5f 43 6c 6f 73  65 44 6f 77 6e 22 2c 74  |imp_CloseDown",t|
000019f0  68 61 6e 64 25 2c 54 61  73 6b 0d 06 2c 05 e0 0d  |hand%,Task..,...|
00001a00  06 36 05 3a 0d 06 40 15  f4 20 4d 65 6e 75 20 66  |.6.:..@.. Menu f|
00001a10  61 63 69 6c 69 74 69 65  73 0d 06 4a 05 3a 0d 06  |acilities..J.:..|
00001a20  54 0f dd f2 69 6e 69 74  6d 65 6e 75 73 0d 06 5e  |T...initmenus..^|
00001a30  2e de 20 6d 65 6e 75 5f  62 6c 6f 63 6b 25 20 26  |.. menu_block% &|
00001a40  32 30 30 30 3a 6d 65 6e  75 5f 66 72 65 65 25 3d  |2000:menu_free%=|
00001a50  6d 65 6e 75 5f 62 6c 6f  63 6b 25 0d 06 68 05 e1  |menu_block%..h..|
00001a60  0d 06 72 05 3a 0d 06 7c  31 f4 20 20 6d 65 6e 75  |..r.:..|1.  menu|
00001a70  25 3d 46 4e 63 72 65 61  74 65 6d 65 6e 75 28 22  |%=FNcreatemenu("|
00001a80  54 69 74 6c 65 2c 49 74  65 6d 31 2c 49 74 65 6d  |Title,Item1,Item|
00001a90  32 2e 2e 2e 22 29 0d 06  86 05 3a 0d 06 90 17 dd  |2...")....:.....|
00001aa0  a4 63 72 65 61 74 65 6d  65 6e 75 28 6d 65 6e 75  |.createmenu(menu|
00001ab0  24 29 0d 06 9a 18 6d 65  6e 75 5f 70 74 72 25 3d  |$)....menu_ptr%=|
00001ac0  6d 65 6e 75 5f 66 72 65  65 25 0d 06 a4 1c 74 69  |menu_free%....ti|
00001ad0  74 6c 65 24 3d a4 66 69  65 6c 64 28 6d 65 6e 75  |tle$=.field(menu|
00001ae0  24 2c 22 2c 22 29 0d 06  ae 14 e7 20 a9 28 74 69  |$,",")..... .(ti|
00001af0  74 6c 65 24 29 3e 31 32  20 8c 0d 06 b8 1c 24 28  |tle$)>12 .....$(|
00001b00  6d 65 6e 75 5f 70 74 72  25 29 3d c0 74 69 74 6c  |menu_ptr%)=.titl|
00001b10  65 24 2c 31 32 29 0d 06  c2 0d 77 69 64 74 68 25  |e$,12)....width%|
00001b20  3d 31 32 0d 06 cc 05 cc  0d 06 d6 17 24 28 6d 65  |=12.........$(me|
00001b30  6e 75 5f 70 74 72 25 29  3d 74 69 74 6c 65 24 0d  |nu_ptr%)=title$.|
00001b40  06 e0 14 77 69 64 74 68  25 3d a9 28 74 69 74 6c  |...width%=.(titl|
00001b50  65 24 29 0d 06 ea 05 cd  0d 06 f4 21 6d 65 6e 75  |e$)........!menu|
00001b60  5f 70 74 72 25 3f 31 32  3d 37 3a 6d 65 6e 75 5f  |_ptr%?12=7:menu_|
00001b70  70 74 72 25 3f 31 33 3d  32 0d 06 fe 21 6d 65 6e  |ptr%?13=2...!men|
00001b80  75 5f 70 74 72 25 3f 31  34 3d 37 3a 6d 65 6e 75  |u_ptr%?14=7:menu|
00001b90  5f 70 74 72 25 3f 31 35  3d 30 0d 07 08 22 6d 65  |_ptr%?15=0..."me|
00001ba0  6e 75 5f 70 74 72 25 21  32 30 3d 34 34 3a 6d 65  |nu_ptr%!20=44:me|
00001bb0  6e 75 5f 70 74 72 25 21  32 34 3d 30 0d 07 12 1e  |nu_ptr%!24=0....|
00001bc0  6d 65 6e 75 5f 69 74 65  6d 5f 70 74 72 25 3d 6d  |menu_item_ptr%=m|
00001bd0  65 6e 75 5f 70 74 72 25  2b 34 0d 07 1c 10 c8 95  |enu_ptr%+4......|
00001be0  20 6d 65 6e 75 24 3c 3e  22 22 0d 07 26 16 6d 65  | menu$<>""..&.me|
00001bf0  6e 75 5f 69 74 65 6d 5f  70 74 72 25 2b 3d 32 34  |nu_item_ptr%+=24|
00001c00  0d 07 30 20 6d 65 6e 75  5f 69 74 65 6d 24 3d a4  |..0 menu_item$=.|
00001c10  66 69 65 6c 64 28 6d 65  6e 75 24 2c 22 2c 22 29  |field(menu$,",")|
00001c20  0d 07 3a 15 21 6d 65 6e  75 5f 69 74 65 6d 5f 70  |..:.!menu_item_p|
00001c30  74 72 25 3d 30 0d 07 44  17 6d 65 6e 75 5f 69 74  |tr%=0..D.menu_it|
00001c40  65 6d 5f 70 74 72 25 21  34 3d 2d 31 0d 07 4e 1d  |em_ptr%!4=-1..N.|
00001c50  6d 65 6e 75 5f 69 74 65  6d 5f 70 74 72 25 21 38  |menu_item_ptr%!8|
00001c60  3d 26 37 30 30 30 30 32  31 0d 07 58 1e c8 95 20  |=&7000021..X... |
00001c70  a7 22 23 24 25 5e 22 2c  c2 6d 65 6e 75 5f 69 74  |."#$%^",.menu_it|
00001c80  65 6d 24 29 29 3e 30 0d  07 62 15 c8 8e 20 c2 6d  |em$))>0..b... .m|
00001c90  65 6e 75 5f 69 74 65 6d  24 29 20 ca 0d 07 6c 35  |enu_item$) ...l5|
00001ca0  c9 20 22 23 22 3a 3f 6d  65 6e 75 5f 69 74 65 6d  |. "#":?menu_item|
00001cb0  5f 70 74 72 25 3d 3f 6d  65 6e 75 5f 69 74 65 6d  |_ptr%=?menu_item|
00001cc0  5f 70 74 72 25 20 84 20  25 30 30 30 30 30 30 30  |_ptr% . %0000000|
00001cd0  31 0d 07 76 35 c9 20 22  24 22 3a 3f 6d 65 6e 75  |1..v5. "$":?menu|
00001ce0  5f 69 74 65 6d 5f 70 74  72 25 3d 3f 6d 65 6e 75  |_item_ptr%=?menu|
00001cf0  5f 69 74 65 6d 5f 70 74  72 25 20 84 20 25 30 30  |_item_ptr% . %00|
00001d00  30 30 30 30 31 30 0d 07  80 39 c9 20 22 25 22 3a  |000010...9. "%":|
00001d10  6d 65 6e 75 5f 69 74 65  6d 5f 70 74 72 25 3f 31  |menu_item_ptr%?1|
00001d20  30 3d 6d 65 6e 75 5f 69  74 65 6d 5f 70 74 72 25  |0=menu_item_ptr%|
00001d30  3f 31 30 20 84 20 25 30  31 30 30 30 30 30 30 0d  |?10 . %01000000.|
00001d40  07 8a 35 c9 20 22 5e 22  3a 3f 6d 65 6e 75 5f 69  |..5. "^":?menu_i|
00001d50  74 65 6d 5f 70 74 72 25  3d 3f 6d 65 6e 75 5f 69  |tem_ptr%=?menu_i|
00001d60  74 65 6d 5f 70 74 72 25  20 84 20 25 30 30 30 30  |tem_ptr% . %0000|
00001d70  30 31 30 30 0d 07 94 05  cb 0d 07 9e 1b 6d 65 6e  |0100.........men|
00001d80  75 5f 69 74 65 6d 24 3d  c0 6d 65 6e 75 5f 69 74  |u_item$=.menu_it|
00001d90  65 6d 24 29 0d 07 a8 05  ce 0d 07 b2 31 e7 20 a9  |em$)........1. .|
00001da0  28 6d 65 6e 75 5f 69 74  65 6d 24 29 3e 77 69 64  |(menu_item$)>wid|
00001db0  74 68 25 20 8c 20 77 69  64 74 68 25 3d a9 28 6d  |th% . width%=.(m|
00001dc0  65 6e 75 5f 69 74 65 6d  24 29 0d 07 bc 28 24 28  |enu_item$)...($(|
00001dd0  6d 65 6e 75 5f 69 74 65  6d 5f 70 74 72 25 2b 31  |menu_item_ptr%+1|
00001de0  32 29 3d 6d 65 6e 75 5f  69 74 65 6d 24 2b bd 28  |2)=menu_item$+.(|
00001df0  30 29 0d 07 c6 05 ce 0d  07 d0 2f 3f 6d 65 6e 75  |0)......../?menu|
00001e00  5f 69 74 65 6d 5f 70 74  72 25 3d 3f 6d 65 6e 75  |_item_ptr%=?menu|
00001e10  5f 69 74 65 6d 5f 70 74  72 25 20 84 20 25 31 30  |_item_ptr% . %10|
00001e20  30 30 30 30 30 30 0d 07  da 1f 6d 65 6e 75 5f 70  |000000....menu_p|
00001e30  74 72 25 21 31 36 3d 28  77 69 64 74 68 25 2a 38  |tr%!16=(width%*8|
00001e40  2b 36 29 2a 32 0d 07 e4  20 6d 65 6e 75 5f 66 72  |+6)*2... menu_fr|
00001e50  65 65 25 3d 6d 65 6e 75  5f 69 74 65 6d 5f 70 74  |ee%=menu_item_pt|
00001e60  72 25 2b 32 34 0d 07 ee  0e 3d 6d 65 6e 75 5f 70  |r%+24....=menu_p|
00001e70  74 72 25 0d 07 f8 1c dd  f2 73 68 6f 77 5f 6d 65  |tr%......show_me|
00001e80  6e 75 28 6d 65 6e 75 25  2c 78 25 2c 79 25 29 0d  |nu(menu%,x%,y%).|
00001e90  08 02 17 63 75 72 72 65  6e 74 5f 6d 65 6e 75 25  |...current_menu%|
00001ea0  3d 6d 65 6e 75 25 0d 08  0c 0e 6d 65 6e 75 5f 78  |=menu%....menu_x|
00001eb0  25 3d 78 25 0d 08 16 0e  6d 65 6e 75 5f 79 25 3d  |%=x%....menu_y%=|
00001ec0  79 25 0d 08 20 25 c8 99  20 22 57 69 6d 70 5f 43  |y%.. %.. "Wimp_C|
00001ed0  72 65 61 74 65 4d 65 6e  75 22 2c 2c 6d 65 6e 75  |reateMenu",,menu|
00001ee0  25 2c 78 25 2c 79 25 0d  08 2a 05 e1 0d 08 34 1f  |%,x%,y%..*....4.|
00001ef0  dd a4 66 69 65 6c 64 28  f8 20 6d 65 6e 75 24 2c  |..field(. menu$,|
00001f00  73 65 70 65 72 61 74 6f  72 24 29 0d 08 3e 33 72  |seperator$)..>3r|
00001f10  65 73 75 6c 74 24 3d c0  6d 65 6e 75 24 2c a7 6d  |esult$=.menu$,.m|
00001f20  65 6e 75 24 2b 73 65 70  65 72 61 74 6f 72 24 2c  |enu$+seperator$,|
00001f30  73 65 70 65 72 61 74 6f  72 24 29 2d 31 29 0d 08  |seperator$)-1)..|
00001f40  48 27 6d 65 6e 75 24 3d  c2 6d 65 6e 75 24 2c a9  |H'menu$=.menu$,.|
00001f50  28 6d 65 6e 75 24 29 2d  a9 28 72 65 73 75 6c 74  |(menu$)-.(result|
00001f60  24 29 2d 31 29 0d 08 52  0c 3d 72 65 73 75 6c 74  |$)-1)..R.=result|
00001f70  24 0d 08 5c 18 dd a4 6d  65 6e 75 5f 68 65 69 67  |$..\...menu_heig|
00001f80  68 74 28 6d 65 6e 75 25  29 0d 08 66 1c ea 20 68  |ht(menu%)..f.. h|
00001f90  65 69 67 68 74 25 2c 6d  65 6e 75 5f 69 74 65 6d  |eight%,menu_item|
00001fa0  5f 70 74 72 25 0d 08 70  1b 6d 65 6e 75 5f 69 74  |_ptr%..p.menu_it|
00001fb0  65 6d 5f 70 74 72 25 3d  6d 65 6e 75 25 2b 32 38  |em_ptr%=menu%+28|
00001fc0  0d 08 7a 0d 68 65 69 67  68 74 25 3d 30 0d 08 84  |..z.height%=0...|
00001fd0  26 c8 95 20 28 3f 6d 65  6e 75 5f 69 74 65 6d 5f  |&.. (?menu_item_|
00001fe0  70 74 72 25 20 80 20 25  31 30 30 30 30 30 30 30  |ptr% . %10000000|
00001ff0  29 3d 30 0d 08 8e 16 6d  65 6e 75 5f 69 74 65 6d  |)=0....menu_item|
00002000  5f 70 74 72 25 2b 3d 32  34 0d 08 98 0e 68 65 69  |_ptr%+=24....hei|
00002010  67 68 74 25 2b 3d 31 0d  08 a2 05 ce 0d 08 ac 18  |ght%+=1.........|
00002020  3d 39 36 2b 28 34 34 2a  28 68 65 69 67 68 74 25  |=96+(44*(height%|
00002030  2b 31 29 29 0d 08 b6 2e  dd f2 6d 65 6e 75 5f 61  |+1))......menu_a|
00002040  74 74 61 63 68 28 6d 65  6e 75 25 2c 70 6f 73 69  |ttach(menu%,posi|
00002050  74 69 6f 6e 25 2c 61 74  74 61 63 68 6d 65 6e 74  |tion%,attachment|
00002060  25 29 0d 08 c0 2d 6d 65  6e 75 25 21 28 32 38 2b  |%)...-menu%!(28+|
00002070  32 34 2a 28 70 6f 73 69  74 69 6f 6e 25 2d 31 29  |24*(position%-1)|
00002080  2b 34 29 3d 61 74 74 61  63 68 6d 65 6e 74 25 0d  |+4)=attachment%.|
00002090  08 ca 05 e1 0d 08 d4 20  dd a4 69 63 6f 6e 62 61  |....... ..iconba|
000020a0  72 28 64 69 72 24 2c 73  69 64 65 2c 73 70 6e 61  |r(dir$,side,spna|
000020b0  6d 65 24 29 0d 08 de 2a  53 25 3d 8e 28 64 69 72  |me$)...*S%=.(dir|
000020c0  24 2b 22 2e 21 53 70 72  69 74 65 73 22 29 3a 54  |$+".!Sprites"):T|
000020d0  25 3d a2 23 53 25 2b 31  36 3a d9 23 53 25 0d 08  |%=.#S%+16:.#S%..|
000020e0  e8 12 de 20 69 73 70 72  69 74 65 73 25 20 54 25  |... isprites% T%|
000020f0  0d 08 f2 1f 21 69 73 70  72 69 74 65 73 25 3d 54  |....!isprites%=T|
00002100  25 3a 69 73 70 72 69 74  65 73 25 21 38 3d 31 0d  |%:isprites%!8=1.|
00002110  08 fc 23 c8 99 20 22 4f  53 5f 53 70 72 69 74 65  |..#.. "OS_Sprite|
00002120  4f 70 22 2c 26 31 30 39  2c 69 73 70 72 69 74 65  |Op",&109,isprite|
00002130  73 25 0d 09 06 34 c8 99  20 22 4f 53 5f 53 70 72  |s%...4.. "OS_Spr|
00002140  69 74 65 4f 70 22 2c 26  31 30 41 2c 69 73 70 72  |iteOp",&10A,ispr|
00002150  69 74 65 73 25 2c 64 69  72 24 2b 22 2e 21 53 70  |ites%,dir$+".!Sp|
00002160  72 69 74 65 73 22 0d 09  10 38 21 71 25 3d 73 69  |rites"...8!q%=si|
00002170  64 65 3a 71 25 21 34 3d  30 3a 71 25 21 38 3d 30  |de:q%!4=0:q%!8=0|
00002180  3a 71 25 21 31 32 3d 36  38 3a 71 25 21 31 36 3d  |:q%!12=68:q%!16=|
00002190  36 38 3a 71 25 21 32 30  3d 26 33 31 30 32 0d 09  |68:q%!20=&3102..|
000021a0  1a 39 de 20 71 25 21 32  34 20 28 a9 73 70 6e 61  |.9. q%!24 (.spna|
000021b0  6d 65 24 2b 31 29 3a 24  28 71 25 21 32 34 29 3d  |me$+1):$(q%!24)=|
000021c0  73 70 6e 61 6d 65 24 3a  71 25 21 32 38 3d 69 73  |spname$:q%!28=is|
000021d0  70 72 69 74 65 73 25 0d  09 24 14 71 25 21 33 32  |prites%..$.q%!32|
000021e0  3d a9 73 70 6e 61 6d 65  24 2b 31 0d 09 2e 22 c8  |=.spname$+1...".|
000021f0  99 20 22 57 69 6d 70 5f  43 72 65 61 74 65 49 63  |. "Wimp_CreateIc|
00002200  6f 6e 22 2c 2c 71 25 20  b8 20 69 63 25 0d 09 38  |on",,q% . ic%..8|
00002210  08 3d 69 63 25 0d 09 42  16 dd f2 6f 70 65 6e 77  |.=ic%..B...openw|
00002220  69 6e 64 6f 77 28 68 61  6e 25 29 0d 09 4c 0c 21  |indow(han%)..L.!|
00002230  71 25 3d 68 61 6e 25 0d  09 56 20 c8 99 20 22 57  |q%=han%..V .. "W|
00002240  69 6d 70 5f 47 65 74 57  69 6e 64 6f 77 53 74 61  |imp_GetWindowSta|
00002250  74 65 22 2c 2c 71 25 0d  09 60 1c c8 99 20 22 57  |te",,q%..`... "W|
00002260  69 6d 70 5f 4f 70 65 6e  57 69 6e 64 6f 77 22 2c  |imp_OpenWindow",|
00002270  2c 71 25 0d 09 6a 05 e1  0d 09 74 17 dd f2 63 6c  |,q%..j....t...cl|
00002280  6f 73 65 77 69 6e 64 6f  77 28 68 61 6e 25 29 0d  |osewindow(han%).|
00002290  09 7e 0c 21 71 25 3d 68  61 6e 25 0d 09 88 1d c8  |.~.!q%=han%.....|
000022a0  99 20 22 57 69 6d 70 5f  43 6c 6f 73 65 57 69 6e  |. "Wimp_CloseWin|
000022b0  64 6f 77 22 2c 2c 71 25  0d 09 92 05 e1 0d 09 9c  |dow",,q%........|
000022c0  10 dd f2 65 72 28 65 72  72 6f 72 24 29 0d 09 a6  |...er(error$)...|
000022d0  14 65 72 72 6f 72 24 3d  65 72 72 6f 72 24 2b bd  |.error$=error$+.|
000022e0  30 0d 09 b0 1a 21 74 71  25 3d 30 3a 24 28 74 71  |0....!tq%=0:$(tq|
000022f0  25 2b 34 29 3d 65 72 72  6f 72 24 0d 09 ba 2a c8  |%+4)=error$...*.|
00002300  99 20 22 57 69 6d 70 5f  52 65 70 6f 72 74 45 72  |. "Wimp_ReportEr|
00002310  72 6f 72 22 2c 74 71 25  2c 31 2c 22 61 72 63 68  |ror",tq%,1,"arch|
00002320  69 76 65 72 22 0d 09 c4  05 e1 0d 09 ce 21 dd f2  |iver"........!..|
00002330  77 72 69 74 65 5f 6d 65  73 73 28 77 69 6e 25 2c  |write_mess(win%,|
00002340  68 61 6e 25 2c 6d 65 73  73 24 29 0d 09 d8 34 21  |han%,mess$)...4!|
00002350  74 71 25 3d 77 69 6e 25  3a 74 71 25 21 34 3d 68  |tq%=win%:tq%!4=h|
00002360  61 6e 25 3a c8 99 20 22  57 69 6d 70 5f 47 65 74  |an%:.. "Wimp_Get|
00002370  49 63 6f 6e 53 74 61 74  65 22 2c 2c 74 71 25 0d  |IconState",,tq%.|
00002380  09 e2 18 24 28 74 71 25  21 32 38 29 3d 6d 65 73  |...$(tq%!28)=mes|
00002390  73 24 2b bd 28 30 29 0d  09 ec 39 c8 99 20 22 57  |s$+.(0)...9.. "W|
000023a0  69 6d 70 5f 46 6f 72 63  65 52 65 64 72 61 77 22  |imp_ForceRedraw"|
000023b0  2c 77 69 6e 25 2c 74 71  25 21 38 2c 74 71 25 21  |,win%,tq%!8,tq%!|
000023c0  31 32 2c 74 71 25 21 31  36 2c 74 71 25 21 32 30  |12,tq%!16,tq%!20|
000023d0  0d 09 f6 05 e1 0d 0a 00  1d dd a4 67 65 74 62 75  |...........getbu|
000023e0  74 74 6f 6e 28 77 69 6e  64 6f 77 25 2c 68 61 6e  |tton(window%,han|
000023f0  25 29 0d 0a 0a 37 21 74  71 25 3d 77 69 6e 64 6f  |%)...7!tq%=windo|
00002400  77 25 3a 74 71 25 21 34  3d 68 61 6e 25 3a c8 99  |w%:tq%!4=han%:..|
00002410  20 22 57 69 6d 70 5f 47  65 74 49 63 6f 6e 53 74  | "Wimp_GetIconSt|
00002420  61 74 65 22 2c 2c 74 71  25 0d 0a 14 15 3d a4 73  |ate",,tq%....=.s|
00002430  74 72 69 6e 67 30 28 74  71 25 21 32 38 29 0d 0a  |tring0(tq%!28)..|
00002440  1e 11 dd f2 6c 6f 61 64  73 70 72 69 74 65 73 0d  |....loadsprites.|
00002450  0a 1f 0b ee 20 85 20 ea  20 e1 0d 0a 28 2a e7 20  |.... . . ...(*. |
00002460  62 75 66 66 65 72 25 21  34 30 3c 3e 26 31 39 34  |buffer%!40<>&194|
00002470  20 20 80 20 62 75 66 66  65 72 25 21 31 36 3d 33  |  . buffer%!16=3|
00002480  20 8c 20 e1 0d 0a 32 1a  e7 20 62 75 66 66 65 72  | . ...2.. buffer|
00002490  25 21 34 30 3c 3e 26 31  39 34 20 8c 20 e1 0d 0a  |%!40<>&194 . ...|
000024a0  3c 1e 66 69 6c 65 24 3d  a4 73 74 72 69 6e 67 30  |<.file$=.string0|
000024b0  28 62 75 66 66 65 72 25  2b 34 34 29 0d 0a 46 25  |(buffer%+44)..F%|
000024c0  62 75 66 66 65 72 25 21  31 36 3d 34 3a 62 75 66  |buffer%!16=4:buf|
000024d0  66 65 72 25 21 31 32 3d  62 75 66 66 65 72 25 21  |fer%!12=buffer%!|
000024e0  38 0d 0a 50 26 c8 99 20  22 57 69 6d 70 5f 53 65  |8..P&.. "Wimp_Se|
000024f0  6e 64 4d 65 73 73 61 67  65 22 2c 31 37 2c 62 75  |ndMessage",17,bu|
00002500  66 66 65 72 25 2c 30 0d  0a 51 3a ee 20 85 20 f2  |ffer%,0..Q:. . .|
00002510  65 72 28 f6 24 2b 22 20  28 20 49 6e 74 65 72 6e  |er(.$+" ( Intern|
00002520  61 6c 20 63 6f 64 65 20  22 2b c3 9e 2b 22 2e 22  |al code "+..+"."|
00002530  2b c3 9f 2b 22 20 29 2e  22 29 3a e5 20 8d 54 56  |+..+" )."):. .TV|
00002540  43 0d 0a 5a 14 f2 6c 6f  61 64 66 69 6c 65 28 66  |C..Z..loadfile(f|
00002550  69 6c 65 24 29 0d 0a 64  05 e1 0d 0a 6e 17 dd a4  |ile$)..d....n...|
00002560  6f 70 74 69 6f 6e 28 77  69 6e 25 2c 68 61 6e 25  |option(win%,han%|
00002570  29 0d 0a 78 18 21 74 71  25 3d 77 69 6e 25 3a 74  |)..x.!tq%=win%:t|
00002580  71 25 21 34 3d 68 61 6e  25 0d 0a 82 1f c8 99 20  |q%!4=han%...... |
00002590  22 57 69 6d 70 5f 47 65  74 49 63 6f 6e 53 74 61  |"Wimp_GetIconSta|
000025a0  74 65 22 2c 2c 74 71 25  0d 0a 8c 25 3d 74 71 25  |te",,tq%...%=tq%|
000025b0  21 32 34 20 80 20 25 31  30 30 30 30 30 30 30 30  |!24 . %100000000|
000025c0  30 30 30 30 30 30 30 30  30 30 30 30 30 0d 0a 96  |0000000000000...|
000025d0  38 dd a4 73 74 72 69 6e  67 30 28 61 25 29 ea 61  |8..string0(a%).a|
000025e0  24 3a 61 24 3d 22 22 3a  c8 95 3f 61 25 3e 33 31  |$:a$="":..?a%>31|
000025f0  3a 61 24 2b 3d bd 3f 61  25 3a 61 25 2b 3d 31 3a  |:a$+=.?a%:a%+=1:|
00002600  ce 3a 3d 61 24 0d 0a a0  17 dd f2 66 6f 72 63 65  |.:=a$......force|
00002610  72 65 64 72 61 77 28 68  61 6e 25 29 0d 0a aa 37  |redraw(han%)...7|
00002620  c8 99 20 22 57 69 6d 70  5f 46 6f 72 63 65 52 65  |.. "Wimp_ForceRe|
00002630  64 72 61 77 22 2c 68 61  6e 25 2c 30 2c 2d 38 2d  |draw",han%,0,-8-|
00002640  28 31 32 30 2a 66 63 6f  75 6e 74 29 2c 31 32 38  |(120*fcount),128|
00002650  30 2c 30 0d 0a b4 05 e1  0d 0a be 1e dd f2 73 65  |0,0...........se|
00002660  74 67 72 65 79 28 6d 65  6e 75 25 2c 70 6f 73 69  |tgrey(menu%,posi|
00002670  74 69 6f 6e 25 29 0d 0a  c8 47 6d 65 6e 75 25 3f  |tion%)...Gmenu%?|
00002680  28 33 38 2b 32 34 2a 28  70 6f 73 69 74 69 6f 6e  |(38+24*(position|
00002690  25 2d 31 29 29 3d 6d 65  6e 75 25 3f 28 33 38 2b  |%-1))=menu%?(38+|
000026a0  32 34 2a 28 70 6f 73 69  74 69 6f 6e 25 2d 31 29  |24*(position%-1)|
000026b0  29 20 84 20 20 25 31 30  30 30 30 30 30 0d 0a d2  |) .  %1000000...|
000026c0  05 e1 0d 0a dc 20 dd f2  63 6c 65 61 72 67 72 65  |..... ..cleargre|
000026d0  79 28 6d 65 6e 75 25 2c  70 6f 73 69 74 69 6f 6e  |y(menu%,position|
000026e0  25 29 0d 0a e6 46 6d 65  6e 75 25 3f 28 33 38 2b  |%)...Fmenu%?(38+|
000026f0  32 34 2a 28 70 6f 73 69  74 69 6f 6e 25 2d 31 29  |24*(position%-1)|
00002700  29 3d 6d 65 6e 75 25 3f  28 33 38 2b 32 34 2a 28  |)=menu%?(38+24*(|
00002710  70 6f 73 69 74 69 6f 6e  25 2d 31 29 29 20 80 20  |position%-1)) . |
00002720  25 30 31 31 31 31 31 31  0d 0a f0 05 e1 0d 0a fa  |%0111111........|
00002730  21 dd f2 74 6f 67 67 6c  65 67 72 65 79 28 6d 65  |!..togglegrey(me|
00002740  6e 75 25 2c 70 6f 73 69  74 69 6f 6e 25 29 0d 0b  |nu%,position%)..|
00002750  04 46 6d 65 6e 75 25 3f  28 33 38 2b 32 34 2a 28  |.Fmenu%?(38+24*(|
00002760  70 6f 73 69 74 69 6f 6e  25 2d 31 29 29 3d 6d 65  |position%-1))=me|
00002770  6e 75 25 3f 28 33 38 2b  32 34 2a 28 70 6f 73 69  |nu%?(38+24*(posi|
00002780  74 69 6f 6e 25 2d 31 29  29 20 82 20 25 31 30 30  |tion%-1)) . %100|
00002790  30 30 30 30 0d 0b 0e 05  e1 0d 0b 18 05 3a 0d 0b  |0000.........:..|
000027a0  22 20 dd f2 44 69 73 61  62 6c 65 49 63 6f 6e 28  |" ..DisableIcon(|
000027b0  77 69 6e 64 6f 77 25 2c  69 63 6f 6e 25 29 0d 0b  |window%,icon%)..|
000027c0  2c 1f 74 71 25 21 30 3d  77 69 6e 64 6f 77 25 20  |,.tq%!0=window% |
000027d0  3a 20 74 71 25 21 34 3d  69 63 6f 6e 25 0d 0b 36  |: tq%!4=icon%..6|
000027e0  20 74 71 25 21 38 3d 31  3c 3c 32 32 20 20 20 3a  | tq%!8=1<<22   :|
000027f0  20 74 71 25 21 31 32 3d  31 3c 3c 32 32 0d 0b 40  | tq%!12=1<<22..@|
00002800  1f c8 99 20 22 57 69 6d  70 5f 53 65 74 49 63 6f  |... "Wimp_SetIco|
00002810  6e 53 74 61 74 65 22 2c  2c 74 71 25 0d 0b 4a 05  |nState",,tq%..J.|
00002820  e1 0d 0b 54 05 3a 0d 0b  5e 1f dd f2 45 6e 61 62  |...T.:..^...Enab|
00002830  6c 65 49 63 6f 6e 28 77  69 6e 64 6f 77 25 2c 69  |leIcon(window%,i|
00002840  63 6f 6e 25 29 0d 0b 68  1f 74 71 25 21 30 3d 77  |con%)..h.tq%!0=w|
00002850  69 6e 64 6f 77 25 20 3a  20 74 71 25 21 34 3d 69  |indow% : tq%!4=i|
00002860  63 6f 6e 25 0d 0b 72 20  74 71 25 21 38 3d 30 20  |con%..r tq%!8=0 |
00002870  20 20 20 20 20 20 3a 20  74 71 25 21 31 32 3d 31  |      : tq%!12=1|
00002880  3c 3c 32 32 0d 0b 7c 1f  c8 99 20 22 57 69 6d 70  |<<22..|... "Wimp|
00002890  5f 53 65 74 49 63 6f 6e  53 74 61 74 65 22 2c 2c  |_SetIconState",,|
000028a0  74 71 25 0d 0b 86 05 e1  0d 0b 90 05 3a 0d 0b 9a  |tq%.........:...|
000028b0  23 dd f2 53 65 74 49 63  6f 6e 28 77 69 6e 64 6f  |#..SetIcon(windo|
000028c0  77 25 2c 69 63 6f 6e 25  2c 73 74 61 74 65 25 29  |w%,icon%,state%)|
000028d0  0d 0b a4 1f 74 71 25 21  30 3d 77 69 6e 64 6f 77  |....tq%!0=window|
000028e0  25 20 3a 20 74 71 25 21  34 3d 69 63 6f 6e 25 0d  |% : tq%!4=icon%.|
000028f0  0b ae 2d e7 20 73 74 61  74 65 25 3d b9 20 8c 20  |..-. state%=. . |
00002900  74 71 25 21 38 3d 31 3c  3c 32 31 20 20 20 3a 20  |tq%!8=1<<21   : |
00002910  74 71 25 21 31 32 3d 31  3c 3c 32 31 0d 0b b8 2c  |tq%!12=1<<21...,|
00002920  e7 20 73 74 61 74 65 25  3d a3 20 8c 20 74 71 25  |. state%=. . tq%|
00002930  21 38 3d 30 20 20 20 20  20 20 3a 20 74 71 25 21  |!8=0      : tq%!|
00002940  31 32 3d 31 3c 3c 32 31  0d 0b c2 1f c8 99 20 22  |12=1<<21...... "|
00002950  57 69 6d 70 5f 53 65 74  49 63 6f 6e 53 74 61 74  |Wimp_SetIconStat|
00002960  65 22 2c 2c 74 71 25 0d  0b cc 05 e1 0d 0b d6 05  |e",,tq%.........|
00002970  3a 0d 0b e0 13 dd f2 64  65 6c 65 74 65 5f 66 69  |:......delete_fi|
00002980  65 6c 64 73 0d 0b ea 25  e7 20 63 6c 74 25 3d b9  |elds...%. clt%=.|
00002990  20 8c 20 f2 77 72 69 74  65 5f 6d 65 73 73 28 61  | . .write_mess(a|
000029a0  64 64 25 2c 32 2c 22 22  29 0d 0b f4 26 e7 20 63  |dd%,2,"")...&. c|
000029b0  6c 69 25 3d b9 20 8c 20  f2 77 72 69 74 65 5f 6d  |li%=. . .write_m|
000029c0  65 73 73 28 61 64 64 25  2c 31 37 2c 22 22 29 0d  |ess(add%,17,"").|
000029d0  0b fe 25 e7 20 63 6c 64  25 3d b9 20 8c 20 f2 77  |..%. cld%=. . .w|
000029e0  72 69 74 65 5f 6d 65 73  73 28 61 64 64 25 2c 39  |rite_mess(add%,9|
000029f0  2c 22 22 29 0d 0c 08 25  e7 20 63 6c 70 25 3d b9  |,"")...%. clp%=.|
00002a00  20 8c 20 f2 77 72 69 74  65 5f 6d 65 73 73 28 61  | . .write_mess(a|
00002a10  64 64 25 2c 35 2c 22 22  29 0d 0c 12 05 e1 0d 0c  |dd%,5,"").......|
00002a20  1c 05 3a 0d 0c 26 0e dd  f2 61 64 64 5f 63 61 72  |..:..&...add_car|
00002a30  64 0d 0c 30 1c 69 74 65  6d 24 3d a4 67 65 74 62  |d..0.item$=.getb|
00002a40  75 74 74 6f 6e 28 61 64  64 25 2c 32 29 0d 0c 3a  |utton(add%,2)..:|
00002a50  1d 69 6e 66 6f 24 3d a4  67 65 74 62 75 74 74 6f  |.info$=.getbutto|
00002a60  6e 28 61 64 64 25 2c 31  37 29 0d 0c 44 1c 64 61  |n(add%,17)..D.da|
00002a70  74 65 24 3d a4 67 65 74  62 75 74 74 6f 6e 28 61  |te$=.getbutton(a|
00002a80  64 64 25 2c 39 29 0d 0c  4e 1c 70 61 67 65 24 3d  |dd%,9)..N.page$=|
00002a90  a4 67 65 74 62 75 74 74  6f 6e 28 61 64 64 25 2c  |.getbutton(add%,|
00002aa0  35 29 0d 0c 58 22 63 61  74 61 25 3d 61 64 64 63  |5)..X"cata%=addc|
00002ab0  61 74 61 25 3a 74 6f 70  69 25 3d 61 64 64 74 6f  |ata%:topi%=addto|
00002ac0  70 69 63 25 0d 0c 62 24  e7 20 a4 6f 70 74 69 6f  |pic%..b$. .optio|
00002ad0  6e 28 61 64 64 25 2c 34  29 3c 3e 30 20 20 74 6f  |n(add%,4)<>0  to|
00002ae0  70 69 25 2b 3d 31 30 30  0d 0c 6c 24 24 28 74 61  |pi%+=100..l$$(ta|
00002af0  62 6c 65 2b 28 63 61 72  64 6e 6f 25 2a 31 33 30  |ble+(cardno%*130|
00002b00  29 2b 36 34 30 29 3d 69  74 65 6d 24 0d 0c 76 27  |)+640)=item$..v'|
00002b10  24 28 74 61 62 6c 65 2b  28 63 61 72 64 6e 6f 25  |$(table+(cardno%|
00002b20  2a 31 33 30 29 2b 36 34  30 2b 33 32 29 3d 69 6e  |*130)+640+32)=in|
00002b30  66 6f 24 0d 0c 80 27 24  28 74 61 62 6c 65 2b 28  |fo$...'$(table+(|
00002b40  63 61 72 64 6e 6f 25 2a  31 33 30 29 2b 36 34 30  |cardno%*130)+640|
00002b50  2b 36 34 29 3d 64 61 74  65 24 0d 0c 8a 27 24 28  |+64)=date$...'$(|
00002b60  74 61 62 6c 65 2b 28 63  61 72 64 6e 6f 25 2a 31  |table+(cardno%*1|
00002b70  33 30 29 2b 36 34 30 2b  39 36 29 3d 70 61 67 65  |30)+640+96)=page|
00002b80  24 0d 0c 94 28 3f 28 74  61 62 6c 65 2b 28 63 61  |$...(?(table+(ca|
00002b90  72 64 6e 6f 25 2a 31 33  30 29 2b 36 34 30 2b 31  |rdno%*130)+640+1|
00002ba0  32 38 29 3d 63 61 74 61  25 0d 0c 9e 28 3f 28 74  |28)=cata%...(?(t|
00002bb0  61 62 6c 65 2b 28 63 61  72 64 6e 6f 25 2a 31 33  |able+(cardno%*13|
00002bc0  30 29 2b 36 34 30 2b 31  32 39 29 3d 74 6f 70 69  |0)+640+129)=topi|
00002bd0  25 0d 0c a8 18 f2 61 6c  74 65 72 5f 62 72 6f 77  |%.....alter_brow|
00002be0  73 65 28 63 61 72 64 25  29 0d 0c b2 05 e1 0d 0c  |se(card%).......|
00002bf0  bc 05 3a 0d 0c c6 12 dd  f2 46 69 6c 6c 49 6e 46  |..:......FillInF|
00002c00  69 65 6c 64 73 0d 0c d0  32 f2 77 72 69 74 65 5f  |ields...2.write_|
00002c10  6d 65 73 73 28 61 64 64  25 2c 32 2c 24 28 74 61  |mess(add%,2,$(ta|
00002c20  62 6c 65 2b 28 63 61 72  64 6e 6f 25 2a 31 33 30  |ble+(cardno%*130|
00002c30  29 2b 36 34 30 29 29 0d  0c da 36 f2 77 72 69 74  |)+640))...6.writ|
00002c40  65 5f 6d 65 73 73 28 61  64 64 25 2c 31 37 2c 24  |e_mess(add%,17,$|
00002c50  28 74 61 62 6c 65 2b 28  63 61 72 64 6e 6f 25 2a  |(table+(cardno%*|
00002c60  31 33 30 29 2b 36 34 30  2b 33 32 29 29 0d 0c e4  |130)+640+32))...|
00002c70  35 f2 77 72 69 74 65 5f  6d 65 73 73 28 61 64 64  |5.write_mess(add|
00002c80  25 2c 39 2c 24 28 74 61  62 6c 65 2b 28 63 61 72  |%,9,$(table+(car|
00002c90  64 6e 6f 25 2a 31 33 30  29 2b 36 34 30 2b 36 34  |dno%*130)+640+64|
00002ca0  29 29 0d 0c ee 35 f2 77  72 69 74 65 5f 6d 65 73  |))...5.write_mes|
00002cb0  73 28 61 64 64 25 2c 35  2c 24 28 74 61 62 6c 65  |s(add%,5,$(table|
00002cc0  2b 28 63 61 72 64 6e 6f  25 2a 31 33 30 29 2b 36  |+(cardno%*130)+6|
00002cd0  34 30 2b 39 36 29 29 0d  0c f8 4f 61 64 64 63 61  |40+96))...Oaddca|
00002ce0  74 61 25 3d 3f 28 74 61  62 6c 65 2b 28 63 61 72  |ta%=?(table+(car|
00002cf0  64 6e 6f 25 2a 31 33 30  29 2b 36 34 30 2b 31 32  |dno%*130)+640+12|
00002d00  38 29 3a f2 77 72 69 74  65 5f 6d 65 73 73 28 61  |8):.write_mess(a|
00002d10  64 64 25 2c 31 30 2c 63  24 28 61 64 64 63 61 74  |dd%,10,c$(addcat|
00002d20  61 25 2d 31 29 29 0d 0d  02 75 61 64 64 74 6f 70  |a%-1))...uaddtop|
00002d30  69 63 25 3d 3f 28 74 61  62 6c 65 2b 28 63 61 72  |ic%=?(table+(car|
00002d40  64 6e 6f 25 2a 31 33 30  29 2b 36 34 30 2b 31 32  |dno%*130)+640+12|
00002d50  39 29 3a e7 20 61 64 64  74 6f 70 69 63 25 3e 31  |9):. addtopic%>1|
00002d60  30 30 20 8c 20 61 64 64  74 6f 70 69 63 25 2d 3d  |00 . addtopic%-=|
00002d70  31 30 30 3a f2 53 65 74  49 63 6f 6e 28 61 64 64  |100:.SetIcon(add|
00002d80  25 2c 34 2c b9 29 20 8b  20 f2 53 65 74 49 63 6f  |%,4,.) . .SetIco|
00002d90  6e 28 61 64 64 25 2c 34  2c a3 29 0d 0d 04 27 f2  |n(add%,4,.)...'.|
00002da0  77 72 69 74 65 5f 6d 65  73 73 28 61 64 64 25 2c  |write_mess(add%,|
00002db0  37 2c 74 24 28 61 64 64  74 6f 70 69 63 25 2d 31  |7,t$(addtopic%-1|
00002dc0  29 29 0d 0d 0c 05 e1 0d  0d 16 19 dd f2 73 68 69  |))...........shi|
00002dd0  66 74 63 61 72 64 73 28  63 61 72 64 6e 6f 25 29  |ftcards(cardno%)|
00002de0  0d 0d 20 17 ea 20 66 63  61 72 64 25 2c 6c 63 61  |.. .. fcard%,lca|
00002df0  72 64 25 2c 61 2c 62 0d  0d 2a 28 e3 20 73 68 69  |rd%,a,b..*(. shi|
00002e00  66 74 6c 6f 6f 70 3d 6c  61 73 74 63 61 72 64 25  |ftloop=lastcard%|
00002e10  20 b8 20 63 61 72 64 6e  6f 25 20 88 20 2d 31 0d  | . cardno% . -1.|
00002e20  0d 34 1d 61 3d 73 68 69  66 74 6c 6f 6f 70 3a 62  |.4.a=shiftloop:b|
00002e30  3d 73 68 69 66 74 6c 6f  6f 70 2b 31 0d 0d 3e 2d  |=shiftloop+1..>-|
00002e40  24 28 74 61 62 6c 65 2b  28 62 2a 31 33 30 29 2b  |$(table+(b*130)+|
00002e50  36 34 30 29 3d 24 28 74  61 62 6c 65 2b 28 61 2a  |640)=$(table+(a*|
00002e60  31 33 30 29 2b 36 34 30  29 0d 0d 48 33 24 28 74  |130)+640)..H3$(t|
00002e70  61 62 6c 65 2b 28 62 2a  31 33 30 29 2b 36 34 30  |able+(b*130)+640|
00002e80  2b 33 32 29 3d 24 28 74  61 62 6c 65 2b 28 61 2a  |+32)=$(table+(a*|
00002e90  31 33 30 29 2b 36 34 30  2b 33 32 29 0d 0d 52 33  |130)+640+32)..R3|
00002ea0  24 28 74 61 62 6c 65 2b  28 62 2a 31 33 30 29 2b  |$(table+(b*130)+|
00002eb0  36 34 30 2b 36 34 29 3d  24 28 74 61 62 6c 65 2b  |640+64)=$(table+|
00002ec0  28 61 2a 31 33 30 29 2b  36 34 30 2b 36 34 29 0d  |(a*130)+640+64).|
00002ed0  0d 5c 33 24 28 74 61 62  6c 65 2b 28 62 2a 31 33  |.\3$(table+(b*13|
00002ee0  30 29 2b 36 34 30 2b 39  36 29 3d 24 28 74 61 62  |0)+640+96)=$(tab|
00002ef0  6c 65 2b 28 61 2a 31 33  30 29 2b 36 34 30 2b 39  |le+(a*130)+640+9|
00002f00  36 29 0d 0d 66 35 3f 28  74 61 62 6c 65 2b 28 62  |6)..f5?(table+(b|
00002f10  2a 31 33 30 29 2b 36 34  30 2b 31 32 38 29 3d 3f  |*130)+640+128)=?|
00002f20  28 74 61 62 6c 65 2b 28  61 2a 31 33 30 29 2b 36  |(table+(a*130)+6|
00002f30  34 30 2b 31 32 38 29 0d  0d 70 35 3f 28 74 61 62  |40+128)..p5?(tab|
00002f40  6c 65 2b 28 62 2a 31 33  30 29 2b 36 34 30 2b 31  |le+(b*130)+640+1|
00002f50  32 39 29 3d 3f 28 74 61  62 6c 65 2b 28 61 2a 31  |29)=?(table+(a*1|
00002f60  33 30 29 2b 36 34 30 2b  31 32 39 29 0d 0d 7a 0f  |30)+640+129)..z.|
00002f70  ed 20 73 68 69 66 74 6c  6f 6f 70 0d 0d 84 10 6c  |. shiftloop....l|
00002f80  61 73 74 63 61 72 64 25  2b 3d 31 0d 0d 8e 05 e1  |astcard%+=1.....|
00002f90  0d 0d 98 05 3a 0d 0d a2  10 dd f2 64 65 6c 65 74  |....:......delet|
00002fa0  65 63 61 72 64 0d 0d ac  11 63 61 72 64 6e 6f 25  |ecard....cardno%|
00002fb0  3d 63 61 72 64 25 0d 0d  b6 48 6d 24 3d 22 44 65  |=card%...Hm$="De|
00002fc0  6c 65 74 65 20 69 74 65  6d 20 22 2b c3 28 63 61  |lete item "+.(ca|
00002fd0  72 64 6e 6f 25 2b 31 29  2b 22 20 28 22 2b 24 28  |rdno%+1)+" ("+$(|
00002fe0  74 61 62 6c 65 2b 28 63  61 72 64 6e 6f 25 2a 31  |table+(cardno%*1|
00002ff0  33 30 29 2b 36 34 30 29  2b 22 29 20 3f 22 0d 0d  |30)+640)+") ?"..|
00003000  c0 1e 74 71 25 21 30 3d  32 35 35 3a 24 28 74 71  |..tq%!0=255:$(tq|
00003010  25 2b 34 29 3d 6d 24 2b  bd 28 30 29 0d 0d ca 3e  |%+4)=m$+.(0)...>|
00003020  c8 99 20 22 57 69 6d 70  5f 52 65 70 6f 72 74 45  |.. "Wimp_ReportE|
00003030  72 72 6f 72 22 2c 74 71  25 2c 25 31 30 30 31 31  |rror",tq%,%10011|
00003040  2c 22 44 65 6c 65 74 65  20 69 74 65 6d 3f 22 20  |,"Delete item?" |
00003050  b8 20 2c 62 75 74 74 6f  6e 25 0d 0d d4 14 e7 20  |. ,button%..... |
00003060  62 75 74 74 6f 6e 25 3c  3e 31 20 8c 20 e1 0d 0d  |button%<>1 . ...|
00003070  de 28 e3 20 73 68 69 66  74 6c 6f 6f 70 3d 63 61  |.(. shiftloop=ca|
00003080  72 64 6e 6f 25 20 b8 20  6c 61 73 74 63 61 72 64  |rdno% . lastcard|
00003090  25 20 88 20 2d 31 0d 0d  e8 1d 61 3d 73 68 69 66  |% . -1....a=shif|
000030a0  74 6c 6f 6f 70 2b 31 3a  62 3d 73 68 69 66 74 6c  |tloop+1:b=shiftl|
000030b0  6f 6f 70 0d 0d f2 2d 24  28 74 61 62 6c 65 2b 28  |oop...-$(table+(|
000030c0  62 2a 31 33 30 29 2b 36  34 30 29 3d 24 28 74 61  |b*130)+640)=$(ta|
000030d0  62 6c 65 2b 28 61 2a 31  33 30 29 2b 36 34 30 29  |ble+(a*130)+640)|
000030e0  0d 0d fc 33 24 28 74 61  62 6c 65 2b 28 62 2a 31  |...3$(table+(b*1|
000030f0  33 30 29 2b 36 34 30 2b  33 32 29 3d 24 28 74 61  |30)+640+32)=$(ta|
00003100  62 6c 65 2b 28 61 2a 31  33 30 29 2b 36 34 30 2b  |ble+(a*130)+640+|
00003110  33 32 29 0d 0e 06 33 24  28 74 61 62 6c 65 2b 28  |32)...3$(table+(|
00003120  62 2a 31 33 30 29 2b 36  34 30 2b 36 34 29 3d 24  |b*130)+640+64)=$|
00003130  28 74 61 62 6c 65 2b 28  61 2a 31 33 30 29 2b 36  |(table+(a*130)+6|
00003140  34 30 2b 36 34 29 0d 0e  10 33 24 28 74 61 62 6c  |40+64)...3$(tabl|
00003150  65 2b 28 62 2a 31 33 30  29 2b 36 34 30 2b 39 36  |e+(b*130)+640+96|
00003160  29 3d 24 28 74 61 62 6c  65 2b 28 61 2a 31 33 30  |)=$(table+(a*130|
00003170  29 2b 36 34 30 2b 39 36  29 0d 0e 1a 35 3f 28 74  |)+640+96)...5?(t|
00003180  61 62 6c 65 2b 28 62 2a  31 33 30 29 2b 36 34 30  |able+(b*130)+640|
00003190  2b 31 32 38 29 3d 3f 28  74 61 62 6c 65 2b 28 61  |+128)=?(table+(a|
000031a0  2a 31 33 30 29 2b 36 34  30 2b 31 32 38 29 0d 0e  |*130)+640+128)..|
000031b0  24 35 3f 28 74 61 62 6c  65 2b 28 62 2a 31 33 30  |$5?(table+(b*130|
000031c0  29 2b 36 34 30 2b 31 32  39 29 3d 3f 28 74 61 62  |)+640+129)=?(tab|
000031d0  6c 65 2b 28 61 2a 31 33  30 29 2b 36 34 30 2b 31  |le+(a*130)+640+1|
000031e0  32 39 29 0d 0e 2e 0f ed  20 73 68 69 66 74 6c 6f  |29)..... shiftlo|
000031f0  6f 70 0d 0e 38 10 6c 61  73 74 63 61 72 64 25 2d  |op..8.lastcard%-|
00003200  3d 31 0d 0e 42 27 e7 20  63 61 72 64 25 3e 6c 61  |=1..B'. card%>la|
00003210  73 74 63 61 72 64 25 20  8c 20 63 61 72 64 25 3d  |stcard% . card%=|
00003220  6c 61 73 74 63 61 72 64  25 0d 0e 4c 18 f2 61 6c  |lastcard%..L..al|
00003230  74 65 72 5f 62 72 6f 77  73 65 28 63 61 72 64 25  |ter_browse(card%|
00003240  29 0d 0e 56 05 e1 0d 0e  60 05 3a 0d 0e 6a 1b dd  |)..V....`.:..j..|
00003250  f2 61 6c 74 65 72 5f 62  72 6f 77 73 65 28 f8 20  |.alter_browse(. |
00003260  63 61 72 64 25 29 0d 0e  74 1d e7 20 63 61 72 64  |card%)..t.. card|
00003270  25 3d 6c 61 73 74 63 61  72 64 25 20 63 61 72 64  |%=lastcard% card|
00003280  25 3d 30 0d 0e 7e 1f e7  20 63 61 72 64 25 3c 30  |%=0..~.. card%<0|
00003290  20 63 61 72 64 25 3d 6c  61 73 74 63 61 72 64 25  | card%=lastcard%|
000032a0  2d 31 0d 0e 88 22 69 74  65 6d 24 3d 24 28 74 61  |-1..."item$=$(ta|
000032b0  62 6c 65 2b 28 63 61 72  64 25 2a 31 33 30 29 2b  |ble+(card%*130)+|
000032c0  36 34 30 29 0d 0e 92 25  69 6e 66 6f 24 3d 24 28  |640)...%info$=$(|
000032d0  74 61 62 6c 65 2b 28 63  61 72 64 25 2a 31 33 30  |table+(card%*130|
000032e0  29 2b 36 34 30 2b 33 32  29 0d 0e 9c 25 64 61 74  |)+640+32)...%dat|
000032f0  65 24 3d 24 28 74 61 62  6c 65 2b 28 63 61 72 64  |e$=$(table+(card|
00003300  25 2a 31 33 30 29 2b 36  34 30 2b 36 34 29 0d 0e  |%*130)+640+64)..|
00003310  a6 25 70 61 67 65 24 3d  24 28 74 61 62 6c 65 2b  |.%page$=$(table+|
00003320  28 63 61 72 64 25 2a 31  33 30 29 2b 36 34 30 2b  |(card%*130)+640+|
00003330  39 36 29 0d 0e b0 26 63  61 74 61 25 3d 3f 28 74  |96)...&cata%=?(t|
00003340  61 62 6c 65 2b 28 63 61  72 64 25 2a 31 33 30 29  |able+(card%*130)|
00003350  2b 36 34 30 2b 31 32 38  29 0d 0e ba 26 74 6f 70  |+640+128)...&top|
00003360  69 25 3d 3f 28 74 61 62  6c 65 2b 28 63 61 72 64  |i%=?(table+(card|
00003370  25 2a 31 33 30 29 2b 36  34 30 2b 31 32 39 29 0d  |%*130)+640+129).|
00003380  0e bc 37 e7 20 74 6f 70  69 25 3e 31 30 30 20 74  |..7. topi%>100 t|
00003390  6f 70 69 25 2d 3d 31 30  30 3a 6f 70 74 24 3d 22  |opi%-=100:opt$="|
000033a0  28 22 2b 6f 70 74 74 24  2b 22 29 22 20 8b 20 6f  |("+optt$+")" . o|
000033b0  70 74 24 3d 22 22 0d 0e  c4 20 f2 77 72 69 74 65  |pt$=""... .write|
000033c0  5f 6d 65 73 73 28 62 72  6f 77 73 65 25 2c 31 2c  |_mess(browse%,1,|
000033d0  69 74 65 6d 24 29 0d 0e  ce 20 f2 77 72 69 74 65  |item$)... .write|
000033e0  5f 6d 65 73 73 28 62 72  6f 77 73 65 25 2c 32 2c  |_mess(browse%,2,|
000033f0  69 6e 66 6f 24 29 0d 0e  d8 20 f2 77 72 69 74 65  |info$)... .write|
00003400  5f 6d 65 73 73 28 62 72  6f 77 73 65 25 2c 36 2c  |_mess(browse%,6,|
00003410  70 61 67 65 24 29 0d 0e  e2 20 f2 77 72 69 74 65  |page$)... .write|
00003420  5f 6d 65 73 73 28 62 72  6f 77 73 65 25 2c 34 2c  |_mess(browse%,4,|
00003430  64 61 74 65 24 29 0d 0e  e4 17 e7 20 74 6f 70 69  |date$)..... topi|
00003440  25 3d 30 20 8c 20 74 6f  70 69 25 3d 31 0d 0e e6  |%=0 . topi%=1...|
00003450  17 e7 20 63 61 74 61 25  3d 30 20 8c 20 63 61 74  |.. cata%=0 . cat|
00003460  61 25 3d 31 0d 0e ec 2e  74 6f 70 73 24 3d 74 24  |a%=1....tops$=t$|
00003470  28 74 6f 70 69 25 2d 31  29 2b 22 20 22 2b 63 24  |(topi%-1)+" "+c$|
00003480  28 63 61 74 61 25 2d 31  29 2b 22 20 22 2b 6f 70  |(cata%-1)+" "+op|
00003490  74 24 0d 0e f6 20 f2 77  72 69 74 65 5f 6d 65 73  |t$... .write_mes|
000034a0  73 28 62 72 6f 77 73 65  25 2c 38 2c 74 6f 70 73  |s(browse%,8,tops|
000034b0  24 29 0d 0f 00 3e f2 77  72 69 74 65 5f 6d 65 73  |$)...>.write_mes|
000034c0  73 28 62 72 6f 77 73 65  25 2c 31 33 2c c3 28 63  |s(browse%,13,.(c|
000034d0  61 72 64 25 2b 31 29 2b  22 20 6f 75 74 20 6f 66  |ard%+1)+" out of|
000034e0  20 22 2b c3 28 6c 61 73  74 63 61 72 64 25 29 29  | "+.(lastcard%))|
000034f0  0d 0f 0a 06 c8 96 0d 0f  14 05 e1 0d 0f 1e 05 3a  |...............:|
00003500  0d 10 5e 11 dd a4 6c 61  73 74 62 69 74 28 73 24  |..^...lastbit(s$|
00003510  29 0d 10 68 11 c8 95 20  a7 73 24 2c 22 3a 22 29  |)..h... .s$,":")|
00003520  3e 30 0d 10 72 16 73 24  3d c1 73 24 2c a7 73 24  |>0..r.s$=.s$,.s$|
00003530  2c 22 3a 22 29 2b 31 29  0d 10 7c 05 ce 0d 10 86  |,":")+1)..|.....|
00003540  11 c8 95 20 a7 73 24 2c  22 2e 22 29 3e 30 0d 10  |... .s$,".")>0..|
00003550  90 16 73 24 3d c1 73 24  2c a7 73 24 2c 22 2e 22  |..s$=.s$,.s$,"."|
00003560  29 2b 31 29 0d 10 9a 05  ce 0d 10 a4 07 3d 73 24  |)+1).........=s$|
00003570  0d 11 9e 15 dd f2 6c 6f  61 64 66 69 6c 65 28 66  |......loadfile(f|
00003580  69 6c 65 24 29 0d 11 a8  15 c8 99 20 22 48 6f 75  |ile$)...... "Hou|
00003590  72 67 6c 61 73 73 5f 4f  6e 22 0d 11 b2 21 e3 20  |rglass_On"...!. |
000035a0  63 6c 65 61 72 3d 30 20  b8 20 28 31 33 30 2a 36  |clear=0 . (130*6|
000035b0  34 30 29 2b 36 34 30 20  88 20 34 0d 11 bc 11 74  |40)+640 . 4....t|
000035c0  61 62 6c 65 21 63 6c 65  61 72 3d 30 0d 11 c6 0b  |able!clear=0....|
000035d0  ed 20 63 6c 65 61 72 0d  11 d0 21 c8 99 20 22 4f  |. clear...!.. "O|
000035e0  53 5f 46 69 6c 65 22 2c  31 32 2c 66 69 6c 65 24  |S_File",12,file$|
000035f0  2c 74 61 62 6c 65 2c 30  0d 11 da 0b 63 61 72 64  |,table,0....card|
00003600  25 3d 30 0d 11 e4 17 6c  61 73 74 63 61 72 64 25  |%=0....lastcard%|
00003610  3d 74 61 62 6c 65 21 36  33 36 0d 11 ee 18 f2 61  |=table!636.....a|
00003620  6c 74 65 72 5f 62 72 6f  77 73 65 28 63 61 72 64  |lter_browse(card|
00003630  25 29 0d 11 f8 29 f2 77  72 69 74 65 5f 6d 65 73  |%)...).write_mes|
00003640  73 28 66 69 6e 66 6f 25  2c 34 2c a4 73 74 72 69  |s(finfo%,4,.stri|
00003650  6e 67 30 28 74 61 62 6c  65 29 29 0d 12 02 2c f2  |ng0(table))...,.|
00003660  77 72 69 74 65 5f 6d 65  73 73 28 66 69 6e 66 6f  |write_mess(finfo|
00003670  25 2c 38 2c a4 73 74 72  69 6e 67 30 28 74 61 62  |%,8,.string0(tab|
00003680  6c 65 2b 33 32 29 29 0d  12 0c 0f f2 75 70 64 61  |le+32)).....upda|
00003690  74 65 73 69 7a 65 0d 12  16 24 f2 77 72 69 74 65  |tesize...$.write|
000036a0  5f 6d 65 73 73 28 66 69  6e 66 6f 25 2c 32 2c c2  |_mess(finfo%,2,.|
000036b0  66 69 6c 65 24 2c 32 37  29 29 0d 12 2a 24 74 65  |file$,27))..*$te|
000036c0  24 3d 24 28 74 61 62 6c  65 2b 36 34 29 3a 63 65  |$=$(table+64):ce|
000036d0  24 3d 24 28 74 61 62 6c  65 2b 33 32 30 29 0d 12  |$=$(table+320)..|
000036e0  34 27 74 73 74 24 3d 24  28 74 61 62 6c 65 2b 35  |4'tst$=$(table+5|
000036f0  37 36 29 3a 69 73 74 24  3d 24 28 74 61 62 6c 65  |76):ist$=$(table|
00003700  2b 35 38 38 29 0d 12 3e  27 64 73 74 24 3d 24 28  |+588)..>'dst$=$(|
00003710  74 61 62 6c 65 2b 36 30  30 29 3a 70 73 74 24 3d  |table+600):pst$=|
00003720  24 28 74 61 62 6c 65 2b  36 31 32 29 0d 12 48 23  |$(table+612)..H#|
00003730  f2 77 72 69 74 65 5f 6d  65 73 73 28 62 72 6f 77  |.write_mess(brow|
00003740  73 65 25 2c 30 2c 74 73  74 24 2b 22 3a 22 29 0d  |se%,0,tst$+":").|
00003750  12 52 23 f2 77 72 69 74  65 5f 6d 65 73 73 28 62  |.R#.write_mess(b|
00003760  72 6f 77 73 65 25 2c 33  2c 69 73 74 24 2b 22 3a  |rowse%,3,ist$+":|
00003770  22 29 0d 12 5c 23 f2 77  72 69 74 65 5f 6d 65 73  |")..\#.write_mes|
00003780  73 28 62 72 6f 77 73 65  25 2c 35 2c 64 73 74 24  |s(browse%,5,dst$|
00003790  2b 22 3a 22 29 0d 12 66  23 f2 77 72 69 74 65 5f  |+":")..f#.write_|
000037a0  6d 65 73 73 28 62 72 6f  77 73 65 25 2c 37 2c 70  |mess(browse%,7,p|
000037b0  73 74 24 2b 22 3a 22 29  0d 12 70 21 f2 77 72 69  |st$+":")..p!.wri|
000037c0  74 65 5f 6d 65 73 73 28  61 64 64 25 2c 32 33 2c  |te_mess(add%,23,|
000037d0  74 73 74 24 2b 22 3a 22  29 0d 12 7a 20 f2 77 72  |tst$+":")..z .wr|
000037e0  69 74 65 5f 6d 65 73 73  28 61 64 64 25 2c 33 2c  |ite_mess(add%,3,|
000037f0  69 73 74 24 2b 22 3a 22  29 0d 12 84 21 f2 77 72  |ist$+":")...!.wr|
00003800  69 74 65 5f 6d 65 73 73  28 61 64 64 25 2c 31 31  |ite_mess(add%,11|
00003810  2c 64 73 74 24 2b 22 3a  22 29 0d 12 8e 20 f2 77  |,dst$+":")... .w|
00003820  72 69 74 65 5f 6d 65 73  73 28 61 64 64 25 2c 36  |rite_mess(add%,6|
00003830  2c 70 73 74 24 2b 22 3a  22 29 0d 12 90 1e f2 77  |,pst$+":").....w|
00003840  72 69 74 65 5f 6d 65 73  73 28 66 69 6e 64 25 2c  |rite_mess(find%,|
00003850  31 33 2c 74 73 74 24 29  0d 12 92 1e f2 77 72 69  |13,tst$).....wri|
00003860  74 65 5f 6d 65 73 73 28  66 69 6e 64 25 2c 31 34  |te_mess(find%,14|
00003870  2c 69 73 74 24 29 0d 12  94 1e f2 77 72 69 74 65  |,ist$).....write|
00003880  5f 6d 65 73 73 28 66 69  6e 64 25 2c 31 35 2c 64  |_mess(find%,15,d|
00003890  73 74 24 29 0d 12 96 1e  f2 77 72 69 74 65 5f 6d  |st$).....write_m|
000038a0  65 73 73 28 66 69 6e 64  25 2c 31 36 2c 70 73 74  |ess(find%,16,pst|
000038b0  24 29 0d 12 98 1f 63 6c  74 25 3d a3 3a 63 6c 69  |$)....clt%=.:cli|
000038c0  25 3d a3 3a 63 6c 64 25  3d a3 3a 63 6c 70 25 3d  |%=.:cld%=.:clp%=|
000038d0  a3 0d 12 a2 20 e7 20 28  74 61 62 6c 65 3f 36 32  |.... . (table?62|
000038e0  34 20 80 20 38 29 3e 30  20 8c 20 63 6c 74 25 3d  |4 . 8)>0 . clt%=|
000038f0  b9 0d 12 ac 20 e7 20 28  74 61 62 6c 65 3f 36 32  |.... . (table?62|
00003900  34 20 80 20 34 29 3e 30  20 8c 20 63 6c 69 25 3d  |4 . 4)>0 . cli%=|
00003910  b9 0d 12 b6 20 e7 20 28  74 61 62 6c 65 3f 36 32  |.... . (table?62|
00003920  34 20 80 20 32 29 3e 30  20 8c 20 63 6c 64 25 3d  |4 . 2)>0 . cld%=|
00003930  b9 0d 12 c0 20 e7 20 28  74 61 62 6c 65 3f 36 32  |.... . (table?62|
00003940  34 20 80 20 31 29 3e 30  20 8c 20 63 6c 70 25 3d  |4 . 1)>0 . clp%=|
00003950  b9 0d 12 ca 21 6f 70 74  74 24 3d c0 a4 73 74 72  |....!optt$=..str|
00003960  69 6e 67 30 28 74 61 62  6c 65 2b 36 32 37 29 2c  |ing0(table+627),|
00003970  37 29 0d 12 d4 21 74 6f  70 69 63 73 25 3d a4 63  |7)...!topics%=.c|
00003980  72 65 61 74 65 74 6f 70  69 63 6d 65 6e 75 28 74  |reatetopicmenu(t|
00003990  65 24 29 0d 12 de 23 63  61 74 61 73 25 3d a4 63  |e$)...#catas%=.c|
000039a0  72 65 61 74 65 63 61 74  61 67 6f 72 79 6d 65 6e  |reatecatagorymen|
000039b0  75 28 63 65 24 29 0d 12  e8 18 f2 45 6e 61 62 6c  |u(ce$).....Enabl|
000039c0  65 49 63 6f 6e 28 66 69  6e 64 25 2c 38 29 0d 12  |eIcon(find%,8)..|
000039d0  f2 17 f2 45 6e 61 62 6c  65 49 63 6f 6e 28 61 64  |...EnableIcon(ad|
000039e0  64 25 2c 34 29 0d 12 fc  1e f2 77 72 69 74 65 5f  |d%,4).....write_|
000039f0  6d 65 73 73 28 66 69 6e  64 25 2c 38 2c 6f 70 74  |mess(find%,8,opt|
00003a00  74 24 29 0d 13 06 1d f2  77 72 69 74 65 5f 6d 65  |t$).....write_me|
00003a10  73 73 28 61 64 64 25 2c  34 2c 6f 70 74 74 24 29  |ss(add%,4,optt$)|
00003a20  0d 13 10 1c e7 20 6f 70  74 74 24 3d 22 20 22 20  |..... optt$=" " |
00003a30  84 20 6f 70 74 74 24 3d  22 22 20 8c 0d 13 1a 19  |. optt$="" .....|
00003a40  f2 44 69 73 61 62 6c 65  49 63 6f 6e 28 66 69 6e  |.DisableIcon(fin|
00003a50  64 25 2c 38 29 0d 13 24  18 f2 44 69 73 61 62 6c  |d%,8)..$..Disabl|
00003a60  65 49 63 6f 6e 28 61 64  64 25 2c 34 29 0d 13 2e  |eIcon(add%,4)...|
00003a70  05 cd 0d 13 38 1e f2 77  72 69 74 65 5f 6d 65 73  |....8..write_mes|
00003a80  73 28 66 69 6e 64 25 2c  33 2c 74 24 28 30 29 29  |s(find%,3,t$(0))|
00003a90  0d 13 42 1d f2 77 72 69  74 65 5f 6d 65 73 73 28  |..B..write_mess(|
00003aa0  61 64 64 25 2c 37 2c 74  24 28 30 29 29 0d 13 4c  |add%,7,t$(0))..L|
00003ab0  1e f2 77 72 69 74 65 5f  6d 65 73 73 28 66 69 6e  |..write_mess(fin|
00003ac0  64 25 2c 36 2c 63 24 28  30 29 29 0d 13 56 1e f2  |d%,6,c$(0))..V..|
00003ad0  77 72 69 74 65 5f 6d 65  73 73 28 61 64 64 25 2c  |write_mess(add%,|
00003ae0  31 30 2c 63 24 28 30 29  29 0d 13 60 1c 66 69 6e  |10,c$(0))..`.fin|
00003af0  64 74 6f 70 69 63 25 3d  31 3a 61 64 64 74 6f 70  |dtopic%=1:addtop|
00003b00  69 63 25 3d 31 0d 13 6a  1a 66 69 6e 64 63 61 74  |ic%=1..j.findcat|
00003b10  61 25 3d 31 3a 61 64 64  63 61 74 61 25 3d 31 0d  |a%=1:addcata%=1.|
00003b20  13 74 18 c8 99 20 22 48  6f 75 72 67 6c 61 73 73  |.t... "Hourglass|
00003b30  5f 53 6d 61 73 68 22 0d  13 7e 10 f2 63 68 61 6e  |_Smash"..~..chan|
00003b40  67 65 67 72 65 79 73 0d  13 88 05 e1 0d 13 c4 10  |gegreys.........|
00003b50  dd f2 75 70 64 61 74 65  73 69 7a 65 0d 13 ce 13  |..updatesize....|
00003b60  e7 20 6c 61 73 74 63 61  72 64 25 3d 30 20 8c 0d  |. lastcard%=0 ..|
00003b70  13 d8 0b 63 61 72 64 73  3d 30 0d 13 e2 0b 62 79  |...cards=0....by|
00003b80  74 65 73 3d 30 0d 13 ec  05 cc 0d 13 f6 13 63 61  |tes=0.........ca|
00003b90  72 64 73 3d 6c 61 73 74  63 61 72 64 25 0d 14 00  |rds=lastcard%...|
00003ba0  1d 62 79 74 65 73 3d 28  6c 61 73 74 63 61 72 64  |.bytes=(lastcard|
00003bb0  25 2a 31 33 30 29 2b 36  34 30 0d 14 0a 05 cd 0d  |%*130)+640......|
00003bc0  14 14 34 e7 20 63 61 72  64 73 3d 31 20 8c 20 70  |..4. cards=1 . p|
00003bd0  68 72 61 73 65 24 3d 22  72 65 63 6f 72 64 22 20  |hrase$="record" |
00003be0  8b 20 70 68 72 61 73 65  24 3d 22 72 65 63 6f 72  |. phrase$="recor|
00003bf0  64 73 22 0d 14 1e 3b 73  65 6e 74 65 6e 63 65 24  |ds"...;sentence$|
00003c00  3d c3 63 61 72 64 73 2b  22 20 22 2b 70 68 72 61  |=.cards+" "+phra|
00003c10  73 65 24 2b 22 20 28 22  2b c3 62 79 74 65 73 2b  |se$+" ("+.bytes+|
00003c20  22 20 62 79 74 65 73 29  22 2b bd 28 30 29 0d 14  |" bytes)"+.(0)..|
00003c30  28 24 f2 77 72 69 74 65  5f 6d 65 73 73 28 66 69  |($.write_mess(fi|
00003c40  6e 66 6f 25 2c 31 30 2c  73 65 6e 74 65 6e 63 65  |nfo%,10,sentence|
00003c50  24 29 0d 14 32 05 e1 0d  14 3c 13 dd f2 74 6f 70  |$)..2....<...top|
00003c60  69 63 28 74 6f 70 69 63  24 29 0d 14 46 1f f2 77  |ic(topic$)..F..w|
00003c70  72 69 74 65 5f 6d 65 73  73 28 61 77 25 2c 61 68  |rite_mess(aw%,ah|
00003c80  25 2c 74 6f 70 69 63 24  29 0d 14 50 3c e7 20 61  |%,topic$)..P<. a|
00003c90  77 25 3d 66 69 6e 64 25  20 66 69 6e 64 74 6f 70  |w%=find% findtop|
00003ca0  69 63 25 3d 21 62 75 66  66 65 72 25 2b 31 20 8b  |ic%=!buffer%+1 .|
00003cb0  20 61 64 64 74 6f 70 69  63 25 3d 21 62 75 66 66  | addtopic%=!buff|
00003cc0  65 72 25 2b 31 0d 14 5a  05 e1 0d 14 64 19 dd f2  |er%+1..Z....d...|
00003cd0  63 61 74 61 67 6f 72 79  28 63 61 74 61 67 6f 72  |catagory(catagor|
00003ce0  79 24 29 0d 14 6e 22 f2  77 72 69 74 65 5f 6d 65  |y$)..n".write_me|
00003cf0  73 73 28 61 77 25 2c 61  68 25 2c 63 61 74 61 67  |ss(aw%,ah%,catag|
00003d00  6f 72 79 24 29 0d 14 78  3a e7 20 61 77 25 3d 66  |ory$)..x:. aw%=f|
00003d10  69 6e 64 25 20 66 69 6e  64 63 61 74 61 25 3d 21  |ind% findcata%=!|
00003d20  62 75 66 66 65 72 25 2b  31 20 8b 20 61 64 64 63  |buffer%+1 . addc|
00003d30  61 74 61 25 3d 21 62 75  66 66 65 72 25 2b 31 0d  |ata%=!buffer%+1.|
00003d40  14 82 05 e1 0d 14 8c 13  dd f2 73 74 61 72 74 75  |..........startu|
00003d50  70 61 6e 6c 6f 61 64 0d  14 96 19 ea 20 69 2c 6e  |panload..... i,n|
00003d60  75 6d 73 70 61 63 65 73  2c 63 6f 6d 6d 61 6e 64  |umspaces,command|
00003d70  0d 14 a0 1c c8 99 20 22  4f 53 5f 47 65 74 45 6e  |...... "OS_GetEn|
00003d80  76 22 20 b8 20 63 6f 6d  6d 61 6e 64 0d 14 aa 1f  |v" . command....|
00003d90  24 71 25 3d a4 73 74 72  69 6e 67 30 28 63 6f 6d  |$q%=.string0(com|
00003da0  6d 61 6e 64 29 2b bd 28  31 33 29 0d 14 b4 0f 6e  |mand)+.(13)....n|
00003db0  75 6d 73 70 61 63 65 73  3d 30 0d 14 be 07 69 3d  |umspaces=0....i=|
00003dc0  30 0d 14 c8 12 c8 95 20  6e 75 6d 73 70 61 63 65  |0...... numspace|
00003dd0  73 3c 33 0d 14 d2 1b e7  20 71 25 3f 69 3d 26 32  |s<3..... q%?i=&2|
00003de0  30 20 6e 75 6d 73 70 61  63 65 73 2b 3d 31 0d 14  |0 numspaces+=1..|
00003df0  dc 08 69 2b 3d 31 0d 14  e6 05 ce 0d 14 f0 11 66  |..i+=1.........f|
00003e00  69 6c 65 24 3d 24 28 71  25 2b 69 29 0d 14 fa 25  |ile$=$(q%+i)...%|
00003e10  e7 20 a7 66 69 6c 65 24  2c 22 3a 3a 22 29 3e 30  |. .file$,"::")>0|
00003e20  20 f2 6c 6f 61 64 66 69  6c 65 28 66 69 6c 65 24  | .loadfile(file$|
00003e30  29 0d 15 04 05 e1 0d 15  0e 18 dd f2 72 65 64 72  |)...........redr|
00003e40  61 77 77 69 6e 28 68 61  6e 64 6c 65 25 29 0d 15  |awwin(handle%)..|
00003e50  18 2c c8 99 20 22 57 69  6d 70 5f 52 65 64 72 61  |.,.. "Wimp_Redra|
00003e60  77 57 69 6e 64 6f 77 22  2c 30 2c 62 75 66 66 65  |wWindow",0,buffe|
00003e70  72 25 20 b8 20 6d 6f 72  65 25 0d 15 22 0c c8 95  |r% . more%.."...|
00003e80  20 6d 6f 72 65 25 0d 15  2c 23 c8 99 20 22 57 69  | more%..,#.. "Wi|
00003e90  6d 70 5f 42 6f 72 64 65  72 57 69 6e 64 6f 77 22  |mp_BorderWindow"|
00003ea0  2c 2c 62 75 66 66 65 72  25 0d 15 36 2c c8 99 20  |,,buffer%..6,.. |
00003eb0  22 57 69 6d 70 5f 47 65  74 52 65 63 74 61 6e 67  |"Wimp_GetRectang|
00003ec0  6c 65 22 2c 30 2c 62 75  66 66 65 72 25 20 b8 20  |le",0,buffer% . |
00003ed0  6d 6f 72 65 25 0d 15 40  05 ce 0d 15 4a 05 e1 0d  |more%..@....J...|
00003ee0  15 54 13 dd f2 72 65 64  72 61 77 6d 61 74 63 68  |.T...redrawmatch|
00003ef0  65 73 0d 15 5e 16 ea 20  6d 6f 72 65 25 2c 78 30  |es..^.. more%,x0|
00003f00  25 2c 79 30 25 2c 69 25  0d 15 68 2c c8 99 20 22  |%,y0%,i%..h,.. "|
00003f10  57 69 6d 70 5f 52 65 64  72 61 77 57 69 6e 64 6f  |Wimp_RedrawWindo|
00003f20  77 22 2c 30 2c 62 75 66  66 65 72 25 20 b8 20 6d  |w",0,buffer% . m|
00003f30  6f 72 65 25 0d 15 72 21  f2 6c 77 61 6f 72 69 67  |ore%..r!.lwaorig|
00003f40  69 6e 28 62 75 66 66 65  72 25 2b 34 2c 78 30 25  |in(buffer%+4,x0%|
00003f50  2c 79 30 25 29 0d 15 7c  0c c8 95 20 6d 6f 72 65  |,y0%)..|... more|
00003f60  25 0d 15 86 1a f2 77 72  69 74 65 74 65 78 74 28  |%.....writetext(|
00003f70  78 30 25 2c 79 30 25 2c  69 25 29 0d 15 90 0d e6  |x0%,y0%,i%).....|
00003f80  20 b3 28 31 36 29 2d 31  0d 15 9a 2c c8 99 20 22  | .(16)-1...,.. "|
00003f90  57 69 6d 70 5f 47 65 74  52 65 63 74 61 6e 67 6c  |Wimp_GetRectangl|
00003fa0  65 22 2c 30 2c 62 75 66  66 65 72 25 20 b8 20 6d  |e",0,buffer% . m|
00003fb0  6f 72 65 25 0d 15 a4 05  ce 0d 15 ae 05 e1 0d 15  |ore%............|
00003fc0  b8 1c dd f2 6c 77 61 6f  72 69 67 69 6e 28 62 2c  |....lwaorigin(b,|
00003fd0  f8 20 78 25 2c f8 20 79  25 29 0d 15 c2 0f 78 25  |. x%,. y%)....x%|
00003fe0  3d 62 21 30 2d 62 21 31  36 0d 15 cc 10 79 25 3d  |=b!0-b!16....y%=|
00003ff0  62 21 31 32 2d 62 21 32  30 0d 15 d6 05 e1 0d 15  |b!12-b!20.......|
00004000  e0 05 3a 0d 15 ea 1f dd  f2 77 72 69 74 65 74 65  |..:......writete|
00004010  78 74 28 78 30 25 2c 79  30 25 2c 69 6e 64 65 78  |xt(x0%,y0%,index|
00004020  25 29 0d 15 f4 24 ea 20  69 25 2c 61 25 2c 62 25  |%)...$. i%,a%,b%|
00004030  2c 63 25 2c 64 25 2c 78  31 25 2c 79 31 25 2c 78  |,c%,d%,x1%,y1%,x|
00004040  32 25 2c 79 32 25 0d 15  fe 30 f2 6c 77 61 63 6c  |2%,y2%...0.lwacl|
00004050  69 70 72 65 63 74 61 6e  67 6c 65 28 62 75 66 66  |iprectangle(buff|
00004060  65 72 25 2b 34 2c 78 31  25 2c 79 31 25 2c 78 32  |er%+4,x1%,y1%,x2|
00004070  25 2c 79 32 25 29 0d 16  08 1b 61 25 3d 28 31 30  |%,y2%)....a%=(10|
00004080  32 34 2d 31 32 2d 79 32  25 29 20 81 20 34 30 2b  |24-12-y2%) . 40+|
00004090  31 0d 16 12 1b 62 25 3d  28 31 30 32 34 2d 31 32  |1....b%=(1024-12|
000040a0  2d 79 31 25 29 20 81 20  34 30 2b 32 0d 16 1c 15  |-y1%) . 40+2....|
000040b0  63 25 3d 28 78 31 25 2d  34 29 20 81 20 31 36 2b  |c%=(x1%-4) . 16+|
000040c0  31 0d 16 26 15 64 25 3d  28 78 32 25 2d 34 29 20  |1..&.d%=(x2%-4) |
000040d0  81 20 31 36 2b 32 0d 16  30 0c 64 25 3d 64 25 2d  |. 16+2..0.d%=d%-|
000040e0  63 25 0d 16 3a 0a e6 20  30 2c 31 31 0d 16 44 10  |c%..:.. 0,11..D.|
000040f0  e3 20 69 25 3d 61 25 20  b8 20 62 25 0d 16 4e 0c  |. i%=a% . b%..N.|
00004100  74 65 78 74 24 3d 22 22  0d 16 58 12 e7 20 28 69  |text$=""..X.. (i|
00004110  25 2d 32 38 29 3e 2d 31  20 8c 0d 16 62 15 e7 20  |%-28)>-1 ...b.. |
00004120  28 69 25 2d 32 38 29 20  83 20 33 3d 30 20 8c 0d  |(i%-28) . 3=0 ..|
00004130  16 6c 07 e6 20 38 0d 16  76 36 c8 93 20 c8 90 20  |.l.. 8..v6.. .. |
00004140  78 30 25 2b 31 36 2a 28  63 25 2d 31 29 2c 79 30  |x0%+16*(c%-1),y0|
00004150  25 2b 31 30 32 34 2d 34  30 2a 28 69 25 2d 31 29  |%+1024-40*(i%-1)|
00004160  2b 34 2c 64 25 2a 31 36  2c 2d 33 36 0d 16 80 33  |+4,d%*16,-36...3|
00004170  63 61 74 61 25 3d 3f 28  74 61 62 6c 65 2b 28 a4  |cata%=?(table+(.|
00004180  63 61 72 64 28 28 69 25  2d 32 38 29 20 81 20 33  |card((i%-28) . 3|
00004190  29 2a 31 33 30 29 2b 36  34 30 2b 31 32 38 29 0d  |)*130)+640+128).|
000041a0  16 8a 33 74 6f 70 69 25  3d 3f 28 74 61 62 6c 65  |..3topi%=?(table|
000041b0  2b 28 a4 63 61 72 64 28  28 69 25 2d 32 38 29 20  |+(.card((i%-28) |
000041c0  81 20 33 29 2a 31 33 30  29 2b 36 34 30 2b 31 32  |. 3)*130)+640+12|
000041d0  39 29 0d 16 94 37 e7 20  74 6f 70 69 25 3e 31 30  |9)...7. topi%>10|
000041e0  30 20 6f 70 74 24 3d 22  28 22 2b 6f 70 74 74 24  |0 opt$="("+optt$|
000041f0  2b 22 29 22 3a 74 6f 70  69 25 2d 3d 31 30 30 20  |+")":topi%-=100 |
00004200  8b 20 6f 70 74 24 3d 22  22 0d 16 9e 5a 74 65 78  |. opt$=""...Ztex|
00004210  74 24 3d 74 24 28 74 6f  70 69 25 2d 31 29 2b 22  |t$=t$(topi%-1)+"|
00004220  20 22 2b 63 24 28 63 61  74 61 25 2d 31 29 2b 22  | "+c$(cata%-1)+"|
00004230  20 3a 20 22 2b 24 28 74  61 62 6c 65 2b 28 a4 63  | : "+$(table+(.c|
00004240  61 72 64 28 28 69 25 2d  32 38 29 20 81 20 33 29  |ard((i%-28) . 3)|
00004250  2a 31 33 30 29 2b 36 34  30 29 2b 22 20 22 2b 6f  |*130)+640)+" "+o|
00004260  70 74 24 0d 16 a8 07 e6  20 31 0d 16 b2 05 cc 0d  |pt$..... 1......|
00004270  16 bc 07 e6 20 37 0d 16  c6 76 e7 20 28 69 25 2d  |.... 7...v. (i%-|
00004280  32 38 29 20 83 20 33 3d  31 20 8c 20 74 65 78 74  |28) . 3=1 . text|
00004290  24 3d 24 28 74 61 62 6c  65 2b 28 a4 63 61 72 64  |$=$(table+(.card|
000042a0  28 28 69 25 2d 32 38 29  20 81 20 33 29 2a 31 33  |((i%-28) . 3)*13|
000042b0  30 29 2b 36 34 30 2b 33  32 29 2b 22 20 22 2b 24  |0)+640+32)+" "+$|
000042c0  28 74 61 62 6c 65 2b 28  a4 63 61 72 64 28 28 69  |(table+(.card((i|
000042d0  25 2d 32 38 29 20 81 20  33 29 2a 31 33 30 29 2b  |%-28) . 3)*130)+|
000042e0  36 34 30 2b 36 34 29 2b  22 2c 20 22 0d 16 c8 32  |640+64)+", "...2|
000042f0  e7 20 28 69 25 2d 32 38  29 20 83 20 33 3d 31 20  |. (i%-28) . 3=1 |
00004300  80 20 70 73 74 24 3d 22  50 61 67 65 22 20 8c 20  |. pst$="Page" . |
00004310  74 65 78 74 24 2b 3d 22  50 61 67 65 20 22 0d 16  |text$+="Page "..|
00004320  ca 53 e7 20 28 69 25 2d  32 38 29 20 83 20 33 3d  |.S. (i%-28) . 3=|
00004330  31 20 8c 20 74 65 78 74  24 2b 3d 24 28 74 61 62  |1 . text$+=$(tab|
00004340  6c 65 2b 28 a4 63 61 72  64 28 28 69 25 2d 32 38  |le+(.card((i%-28|
00004350  29 20 81 20 33 29 2a 31  33 30 29 2b 36 34 30 2b  |) . 3)*130)+640+|
00004360  36 34 2b 33 32 29 20 8b  20 74 65 78 74 24 3d 22  |64+32) . text$="|
00004370  22 0d 16 d0 05 cd 0d 16  da 05 cd 0d 16 e4 28 ec  |".............(.|
00004380  20 78 30 25 2b 34 2b 31  36 2a 28 63 25 2d 31 29  | x0%+4+16*(c%-1)|
00004390  2c 79 30 25 2b 31 30 32  34 2d 34 30 2a 28 69 25  |,y0%+1024-40*(i%|
000043a0  2d 31 29 0d 16 ee 14 f1  20 c1 74 65 78 74 24 2c  |-1)..... .text$,|
000043b0  63 25 2c 64 25 29 3b 0d  16 f8 08 ed 20 69 25 0d  |c%,d%);..... i%.|
000043c0  17 02 05 e1 0d 17 0c 05  3a 0d 17 16 31 dd f2 6c  |........:...1..l|
000043d0  77 61 63 6c 69 70 72 65  63 74 61 6e 67 6c 65 28  |wacliprectangle(|
000043e0  62 2c f8 20 78 31 25 2c  f8 20 79 31 25 2c f8 20  |b,. x1%,. y1%,. |
000043f0  78 32 25 2c f8 20 79 32  25 29 0d 17 20 0d ea 20  |x2%,. y2%).. .. |
00004400  78 30 25 2c 79 30 25 0d  17 2a 19 f2 6c 77 61 6f  |x0%,y0%..*..lwao|
00004410  72 69 67 69 6e 28 62 2c  78 30 25 2c 79 30 25 29  |rigin(b,x0%,y0%)|
00004420  0d 17 34 1d 78 31 25 3d  62 21 32 34 2d 78 30 25  |..4.x1%=b!24-x0%|
00004430  3a 79 31 25 3d 62 21 32  38 2d 79 30 25 0d 17 3e  |:y1%=b!28-y0%..>|
00004440  1d 78 32 25 3d 62 21 33  32 2d 78 30 25 3a 79 32  |.x2%=b!32-x0%:y2|
00004450  25 3d 62 21 33 36 2d 79  30 25 0d 17 48 05 e1 0d  |%=b!36-y0%..H...|
00004460  17 52 05 3a 0d 17 5c 20  dd f2 6c 69 6d 69 74 28  |.R.:..\ ..limit(|
00004470  6c 6f 77 65 72 2c f8 20  76 61 6c 75 65 2c 75 70  |lower,. value,up|
00004480  70 65 72 29 0d 17 66 1f  e7 20 76 61 6c 75 65 3c  |per)..f.. value<|
00004490  6c 6f 77 65 72 20 8c 20  76 61 6c 75 65 3d 6c 6f  |lower . value=lo|
000044a0  77 65 72 0d 17 70 1f e7  20 76 61 6c 75 65 3e 75  |wer..p.. value>u|
000044b0  70 70 65 72 20 8c 20 76  61 6c 75 65 3d 75 70 70  |pper . value=upp|
000044c0  65 72 0d 17 7a 05 e1 0d  17 84 0e dd a4 63 61 70  |er..z........cap|
000044d0  73 28 61 24 29 0d 17 8e  12 e3 20 6c 6f 6f 70 3d  |s(a$)..... loop=|
000044e0  31 20 b8 20 a9 61 24 0d  17 98 12 62 24 3d c1 61  |1 . .a$....b$=.a|
000044f0  24 2c 6c 6f 6f 70 2c 31  29 0d 17 a2 17 e7 20 62  |$,loop,1)..... b|
00004500  24 3e 22 60 22 20 80 20  62 24 3c 22 7b 22 20 8c  |$>"`" . b$<"{" .|
00004510  0d 17 ac 10 62 24 3d bd  28 97 62 24 2d 33 32 29  |....b$=.(.b$-32)|
00004520  0d 17 b6 12 c1 61 24 2c  6c 6f 6f 70 2c 31 29 3d  |.....a$,loop,1)=|
00004530  62 24 0d 17 c0 05 cd 0d  17 ca 0a ed 20 6c 6f 6f  |b$.......... loo|
00004540  70 0d 17 d4 07 3d 61 24  0d 17 de 0a dd f2 66 69  |p....=a$......fi|
00004550  6e 64 0d 17 e8 15 c8 99  20 22 48 6f 75 72 67 6c  |nd...... "Hourgl|
00004560  61 73 73 5f 4f 6e 22 0d  17 f2 1d 66 69 6e 64 24  |ass_On"....find$|
00004570  3d a4 67 65 74 62 75 74  74 6f 6e 28 66 69 6e 64  |=.getbutton(find|
00004580  25 2c 39 29 0d 17 fc 16  66 69 6e 64 24 3d a4 63  |%,9)....find$=.c|
00004590  61 70 73 28 66 69 6e 64  24 29 0d 18 06 14 74 6f  |aps(find$)....to|
000045a0  70 69 25 3d 66 69 6e 64  74 6f 70 69 63 25 0d 18  |pi%=findtopic%..|
000045b0  10 13 63 61 74 61 25 3d  66 69 6e 64 63 61 74 61  |..cata%=findcata|
000045c0  25 0d 18 12 29 66 6e 6f  25 3d 30 3a e7 20 a4 6f  |%...)fno%=0:. .o|
000045d0  70 74 69 6f 6e 28 66 69  6e 64 25 2c 31 34 29 3c  |ption(find%,14)<|
000045e0  3e 30 20 66 6e 6f 25 3d  33 32 0d 18 14 22 e7 20  |>0 fno%=32...". |
000045f0  a4 6f 70 74 69 6f 6e 28  66 69 6e 64 25 2c 31 35  |.option(find%,15|
00004600  29 3c 3e 30 20 66 6e 6f  25 3d 36 34 0d 18 16 22  |)<>0 fno%=64..."|
00004610  e7 20 a4 6f 70 74 69 6f  6e 28 66 69 6e 64 25 2c  |. .option(find%,|
00004620  31 36 29 3c 3e 30 20 66  6e 6f 25 3d 39 36 0d 18  |16)<>0 fno%=96..|
00004630  1a 2a e7 20 a4 6f 70 74  69 6f 6e 28 66 69 6e 64  |.*. .option(find|
00004640  25 2c 38 29 3c 3e 30 20  20 6f 70 74 25 3d b9 20  |%,8)<>0  opt%=. |
00004650  8b 20 6f 70 74 25 3d a3  0d 18 24 1f 75 73 65 63  |. opt%=...$.usec|
00004660  61 74 61 25 3d 28 a4 6f  70 74 69 6f 6e 28 66 69  |ata%=(.option(fi|
00004670  6e 64 25 2c 35 29 29 0d  18 2e 1f 75 73 65 74 6f  |nd%,5))....useto|
00004680  70 69 25 3d 28 a4 6f 70  74 69 6f 6e 28 66 69 6e  |pi%=(.option(fin|
00004690  64 25 2c 32 29 29 0d 18  38 26 66 63 6f 75 6e 74  |d%,2))..8&fcount|
000046a0  3d 30 3a 70 63 3d 30 3a  70 61 3d 31 30 30 2f 28  |=0:pc=0:pa=100/(|
000046b0  6c 61 73 74 63 61 72 64  25 2d 31 29 0d 18 42 57  |lastcard%-1)..BW|
000046c0  e7 20 a4 6f 70 74 69 6f  6e 28 6f 70 74 69 6f 6e  |. .option(option|
000046d0  73 25 2c 31 32 29 3e 30  20 4f 3d ae 28 22 3c 41  |s%,12)>0 O=.("<A|
000046e0  72 63 68 69 76 65 72 44  65 6d 24 44 69 72 3e 2e  |rchiverDem$Dir>.|
000046f0  4c 6f 67 a0 46 69 6c 65  73 2e 22 2b a4 67 65 74  |Log.Files."+.get|
00004700  62 75 74 74 6f 6e 28 6f  70 74 69 6f 6e 73 25 2c  |button(options%,|
00004710  34 29 29 0d 18 4c 1b e3  20 73 63 61 72 64 3d 30  |4))..L.. scard=0|
00004720  20 b8 20 6c 61 73 74 63  61 72 64 25 2d 31 0d 18  | . lastcard%-1..|
00004730  56 2e 69 74 65 6d 24 3d  a4 63 61 70 73 28 24 28  |V.item$=.caps($(|
00004740  74 61 62 6c 65 2b 28 73  63 61 72 64 2a 31 33 30  |table+(scard*130|
00004750  29 2b 36 34 30 2b 66 6e  6f 25 29 29 0d 18 60 28  |)+640+fno%))..`(|
00004760  63 68 63 61 74 61 25 3d  3f 28 74 61 62 6c 65 2b  |chcata%=?(table+|
00004770  28 73 63 61 72 64 2a 31  33 30 29 2b 36 34 30 2b  |(scard*130)+640+|
00004780  31 32 38 29 0d 18 6a 28  63 68 74 6f 70 69 25 3d  |128)..j(chtopi%=|
00004790  3f 28 74 61 62 6c 65 2b  28 73 63 61 72 64 2a 31  |?(table+(scard*1|
000047a0  33 30 29 2b 36 34 30 2b  31 32 39 29 0d 18 74 39  |30)+640+129)..t9|
000047b0  e7 20 63 68 74 6f 70 69  25 3e 31 30 30 20 63 68  |. chtopi%>100 ch|
000047c0  74 6f 70 69 32 25 3d 63  68 74 6f 70 69 25 2d 31  |topi2%=chtopi%-1|
000047d0  30 30 20 8b 20 63 68 74  6f 70 69 32 25 3d 63 68  |00 . chtopi2%=ch|
000047e0  74 6f 70 69 25 0d 18 7e  31 e7 20 75 73 65 63 61  |topi%..~1. useca|
000047f0  74 61 25 3d 30 20 84 20  28 75 73 65 63 61 74 61  |ta%=0 . (usecata|
00004800  25 3e 30 20 80 20 63 61  74 61 25 3d 63 68 63 61  |%>0 . cata%=chca|
00004810  74 61 25 29 20 8c 0d 18  88 32 e7 20 75 73 65 74  |ta%) ....2. uset|
00004820  6f 70 69 25 3d 30 20 84  20 28 75 73 65 74 6f 70  |opi%=0 . (usetop|
00004830  69 25 3e 30 20 80 20 74  6f 70 69 25 3d 63 68 74  |i%>0 . topi%=cht|
00004840  6f 70 69 32 25 29 20 8c  0d 18 92 27 e7 20 6f 70  |opi2%) ....'. op|
00004850  74 25 3d a3 20 84 20 28  6f 70 74 25 3d b9 20 80  |t%=. . (opt%=. .|
00004860  20 63 68 74 6f 70 69 25  3e 31 30 30 29 20 8c 0d  | chtopi%>100) ..|
00004870  18 9c 62 e7 20 a7 69 74  65 6d 24 2c 66 69 6e 64  |..b. .item$,find|
00004880  24 29 3e 30 20 8c 20 66  69 6e 64 73 21 28 66 63  |$)>0 . finds!(fc|
00004890  6f 75 6e 74 2a 34 29 3d  73 63 61 72 64 3a 66 63  |ount*4)=scard:fc|
000048a0  6f 75 6e 74 2b 3d 31 3a  e7 20 a4 6f 70 74 69 6f  |ount+=1:. .optio|
000048b0  6e 28 6f 70 74 69 6f 6e  73 25 2c 31 32 29 3e 30  |n(options%,12)>0|
000048c0  20 f2 61 64 64 74 6f 6c  6f 67 28 73 63 61 72 64  | .addtolog(scard|
000048d0  29 0d 18 a6 05 cd 0d 18  b0 05 cd 0d 18 ba 05 cd  |)...............|
000048e0  0d 18 c4 0a 70 63 2b 3d  70 61 0d 18 ce 20 c8 99  |....pc+=pa... ..|
000048f0  20 22 48 6f 75 72 67 6c  61 73 73 5f 50 65 72 63  | "Hourglass_Perc|
00004900  65 6e 74 61 67 65 22 2c  70 63 0d 18 d8 0b ed 20  |entage",pc..... |
00004910  73 63 61 72 64 0d 18 e2  10 e7 20 66 63 6f 75 6e  |scard..... fcoun|
00004920  74 3e 30 20 8c 0d 18 ec  1e 20 e7 20 a4 6f 70 74  |t>0 ..... . .opt|
00004930  69 6f 6e 28 6f 70 74 69  6f 6e 73 25 2c 37 29 3e  |ion(options%,7)>|
00004940  30 20 8c 0d 18 f6 20 20  20 21 71 25 3d 30 3a 71  |0 ....   !q%=0:q|
00004950  25 21 34 3d 2d 38 2d 28  31 32 30 2a 66 63 6f 75  |%!4=-8-(120*fcou|
00004960  6e 74 29 0d 19 00 17 20  20 71 25 21 38 3d 31 32  |nt)....  q%!8=12|
00004970  38 30 3a 71 25 21 31 32  3d 30 0d 19 0a 25 20 20  |80:q%!12=0...%  |
00004980  c8 99 20 22 57 69 6d 70  5f 53 65 74 45 78 74 65  |.. "Wimp_SetExte|
00004990  6e 74 22 2c 6d 61 74 63  68 65 73 25 2c 71 25 0d  |nt",matches%,q%.|
000049a0  19 14 36 20 20 f2 77 72  69 74 65 5f 6d 65 73 73  |..6  .write_mess|
000049b0  28 6d 61 74 63 68 65 73  25 2c 30 2c 22 49 74 65  |(matches%,0,"Ite|
000049c0  6d 73 20 66 6f 75 6e 64  20 3d 20 22 2b c3 66 63  |ms found = "+.fc|
000049d0  6f 75 6e 74 29 0d 19 1e  1c 20 20 f2 66 6f 72 63  |ount)....  .forc|
000049e0  65 72 65 64 72 61 77 28  6d 61 74 63 68 65 73 25  |eredraw(matches%|
000049f0  29 0d 19 28 1b 20 20 f2  6f 70 65 6e 77 69 6e 64  |)..(.  .openwind|
00004a00  6f 77 28 6d 61 74 63 68  65 73 25 29 0d 19 32 19  |ow(matches%)..2.|
00004a10  20 20 f2 63 6c 6f 73 65  77 69 6e 64 6f 77 28 66  |  .closewindow(f|
00004a20  69 6e 64 25 29 0d 19 3c  06 20 cc 0d 19 46 1f 20  |ind%)..<. ...F. |
00004a30  20 e7 20 66 63 6f 75 6e  74 3d 31 20 73 24 3d 22  | . fcount=1 s$="|
00004a40  22 20 8b 20 73 24 3d 22  73 22 0d 19 50 3b 20 20  |" . s$="s"..P;  |
00004a50  f2 77 72 69 74 65 5f 6d  65 73 73 28 65 6e 64 73  |.write_mess(ends|
00004a60  65 61 72 63 68 25 2c 31  2c c3 66 63 6f 75 6e 74  |earch%,1,.fcount|
00004a70  2b 22 20 69 74 65 6d 22  2b 73 24 2b 22 20 66 6f  |+" item"+s$+" fo|
00004a80  75 6e 64 22 29 0d 19 5a  1d 20 20 f2 6f 70 65 6e  |und")..Z.  .open|
00004a90  77 69 6e 64 6f 77 28 65  6e 64 73 65 61 72 63 68  |window(endsearch|
00004aa0  25 29 0d 19 64 19 20 20  f2 63 6c 6f 73 65 77 69  |%)..d.  .closewi|
00004ab0  6e 64 6f 77 28 66 69 6e  64 25 29 0d 19 6e 06 20  |ndow(find%)..n. |
00004ac0  cd 0d 19 78 05 cd 0d 19  82 10 e7 20 66 63 6f 75  |...x....... fcou|
00004ad0  6e 74 3d 30 20 8c 0d 19  83 1c f2 65 72 28 22 4e  |nt=0 ......er("N|
00004ae0  6f 20 6d 61 74 63 68 65  73 20 66 6f 75 6e 64 2e  |o matches found.|
00004af0  22 29 0d 19 84 1e e7 20  a4 6f 70 74 69 6f 6e 28  |")..... .option(|
00004b00  6f 70 74 69 6f 6e 73 25  2c 31 34 29 3e 30 20 8c  |options%,14)>0 .|
00004b10  0d 19 85 19 e7 20 63 24  28 66 69 6e 64 63 61 74  |..... c$(findcat|
00004b20  61 25 29 3c 3e 22 22 20  8c 0d 19 86 22 63 61 24  |a%)<>"" ...."ca$|
00004b30  3d 63 24 28 66 69 6e 64  63 61 74 61 25 29 3a 66  |=c$(findcata%):f|
00004b40  69 6e 64 63 61 74 61 25  2b 3d 31 0d 19 87 1c f2  |indcata%+=1.....|
00004b50  77 72 69 74 65 5f 6d 65  73 73 28 66 69 6e 64 25  |write_mess(find%|
00004b60  2c 36 2c 63 61 24 29 0d  19 88 05 cd 0d 19 89 05  |,6,ca$).........|
00004b70  cd 0d 19 8a 05 cd 0d 19  8c 68 e7 20 a4 6f 70 74  |.........h. .opt|
00004b80  69 6f 6e 28 6f 70 74 69  6f 6e 73 25 2c 31 32 29  |ion(options%,12)|
00004b90  3e 30 20 d9 23 4f 3a ff  28 22 53 65 74 54 79 70  |>0 .#O:.("SetTyp|
00004ba0  65 20 3c 41 72 63 68 69  76 65 72 44 65 6d 24 44  |e <ArchiverDem$D|
00004bb0  69 72 3e 2e 4c 6f 67 46  69 6c 65 73 2e 22 2b a4  |ir>.LogFiles."+.|
00004bc0  67 65 74 62 75 74 74 6f  6e 28 6f 70 74 69 6f 6e  |getbutton(option|
00004bd0  73 25 2c 35 29 2b 22 20  54 65 78 74 22 29 0d 19  |s%,5)+" Text")..|
00004be0  96 16 c8 99 20 22 48 6f  75 72 67 6c 61 73 73 5f  |.... "Hourglass_|
00004bf0  4f 66 66 22 0d 19 a0 05  e1 0d 19 aa 12 dd a4 63  |Off"...........c|
00004c00  61 72 64 28 6e 75 6d 62  65 72 29 0d 19 b4 15 3d  |ard(number)....=|
00004c10  66 69 6e 64 73 21 28 6e  75 6d 62 65 72 2a 34 29  |finds!(number*4)|
00004c20  0d 19 be 11 dd f2 63 68  61 6e 67 65 67 72 65 79  |......changegrey|
00004c30  73 0d 19 c8 0c 63 6c 65  61 72 25 3d b9 0d 19 ca  |s....clear%=....|
00004c40  17 f2 63 6c 65 61 72 67  72 65 79 28 6d 65 6e 75  |..cleargrey(menu|
00004c50  25 2c 36 29 0d 19 d2 17  f2 63 6c 65 61 72 67 72  |%,6).....cleargr|
00004c60  65 79 28 6d 65 6e 75 25  2c 35 29 0d 19 dc 17 f2  |ey(menu%,5).....|
00004c70  63 6c 65 61 72 67 72 65  79 28 6d 65 6e 75 25 2c  |cleargrey(menu%,|
00004c80  34 29 0d 19 e6 1c f2 63  6c 65 61 72 67 72 65 79  |4).....cleargrey|
00004c90  28 66 69 6c 65 5f 6d 65  6e 75 25 2c 31 29 0d 19  |(file_menu%,1)..|
00004ca0  f0 1c f2 63 6c 65 61 72  67 72 65 79 28 66 69 6c  |...cleargrey(fil|
00004cb0  65 5f 6d 65 6e 75 25 2c  32 29 0d 19 fa 05 e1 0d  |e_menu%,2)......|
00004cc0  1a 04 15 dd f2 77 72 69  74 65 74 6f 66 69 6c 65  |.....writetofile|
00004cd0  28 61 24 29 0d 1a 0e 0f  e3 20 62 3d 31 20 b8 20  |(a$)..... b=1 . |
00004ce0  a9 61 24 0d 1a 18 13 d5  23 4f 2c 97 28 c1 61 24  |.a$.....#O,.(.a$|
00004cf0  2c 62 2c 31 29 29 0d 1a  22 07 ed 20 62 0d 1a 2c  |,b,1))..".. b..,|
00004d00  05 e1 0d 1a 36 14 dd f2  61 64 64 74 6f 6c 6f 67  |....6...addtolog|
00004d10  28 63 61 72 64 29 0d 1a  40 11 ea 20 63 61 74 61  |(card)..@.. cata|
00004d20  25 2c 74 6f 70 69 25 0d  1a 4a 25 63 61 74 61 25  |%,topi%..J%cata%|
00004d30  3d 3f 28 74 61 62 6c 65  2b 28 63 61 72 64 2a 31  |=?(table+(card*1|
00004d40  33 30 29 2b 36 34 30 2b  31 32 38 29 0d 1a 54 25  |30)+640+128)..T%|
00004d50  74 6f 70 69 25 3d 3f 28  74 61 62 6c 65 2b 28 63  |topi%=?(table+(c|
00004d60  61 72 64 2a 31 33 30 29  2b 36 34 30 2b 31 32 39  |ard*130)+640+129|
00004d70  29 0d 1a 5e 37 e7 20 74  6f 70 69 25 3e 31 30 30  |)..^7. topi%>100|
00004d80  20 6f 70 74 24 3d 22 28  22 2b 6f 70 74 74 24 2b  | opt$="("+optt$+|
00004d90  22 29 22 3a 74 6f 70 69  25 2d 3d 31 30 30 20 8b  |")":topi%-=100 .|
00004da0  20 6f 70 74 24 3d 22 22  0d 1a 68 4c 74 65 78 74  | opt$=""..hLtext|
00004db0  24 3d 74 24 28 74 6f 70  69 25 2d 31 29 2b 22 20  |$=t$(topi%-1)+" |
00004dc0  22 2b 63 24 28 63 61 74  61 25 2d 31 29 2b 22 20  |"+c$(cata%-1)+" |
00004dd0  3a 20 22 2b 24 28 74 61  62 6c 65 2b 28 63 61 72  |: "+$(table+(car|
00004de0  64 2a 31 33 30 29 2b 36  34 30 29 2b 22 20 22 2b  |d*130)+640)+" "+|
00004df0  6f 70 74 24 0d 1a 72 23  6d 61 67 24 3d 24 28 74  |opt$..r#mag$=$(t|
00004e00  61 62 6c 65 2b 28 63 61  72 64 2a 31 33 30 29 2b  |able+(card*130)+|
00004e10  36 34 30 2b 33 32 29 0d  1a 7c 24 64 61 74 65 24  |640+32)..|$date$|
00004e20  3d 24 28 74 61 62 6c 65  2b 28 63 61 72 64 2a 31  |=$(table+(card*1|
00004e30  33 30 29 2b 36 34 30 2b  36 34 29 0d 1a 86 27 72  |30)+640+64)...'r|
00004e40  65 73 74 24 3d 24 28 74  61 62 6c 65 2b 28 63 61  |est$=$(table+(ca|
00004e50  72 64 2a 31 33 30 29 2b  36 34 30 2b 36 34 2b 33  |rd*130)+640+64+3|
00004e60  32 29 0d 1a 88 27 e7 20  70 73 74 24 3d 22 50 61  |2)...'. pst$="Pa|
00004e70  67 65 22 20 8c 20 72 65  73 74 24 3d 22 50 61 67  |ge" . rest$="Pag|
00004e80  65 20 22 2b 72 65 73 74  24 0d 1a 90 95 e7 20 a4  |e "+rest$..... .|
00004e90  6f 70 74 69 6f 6e 28 6f  70 74 69 6f 6e 73 25 2c  |option(options%,|
00004ea0  31 30 29 20 8c 20 74 65  78 74 24 3d 74 65 78 74  |10) . text$=text|
00004eb0  24 2b bd 28 31 30 29 3a  74 65 78 74 32 24 3d 6d  |$+.(10):text2$=m|
00004ec0  61 67 24 2b 22 20 22 2b  64 61 74 65 24 2b 22 2c  |ag$+" "+date$+",|
00004ed0  20 22 2b 72 65 73 74 24  2b bd 28 31 30 29 20 8b  | "+rest$+.(10) .|
00004ee0  20 74 65 78 74 24 3d 74  65 78 74 24 2b 22 20 28  | text$=text$+" (|
00004ef0  22 2b 64 61 74 65 24 2b  22 29 22 2b bd 28 31 30  |"+date$+")"+.(10|
00004f00  29 3a 74 65 78 74 32 24  3d 6d 61 67 24 2b 22 2c  |):text2$=mag$+",|
00004f10  20 22 2b 72 65 73 74 24  2b bd 28 31 30 29 0d 1a  | "+rest$+.(10)..|
00004f20  9a 17 f2 77 72 69 74 65  74 6f 66 69 6c 65 28 74  |...writetofile(t|
00004f30  65 78 74 24 29 0d 1a a4  18 f2 77 72 69 74 65 74  |ext$).....writet|
00004f40  6f 66 69 6c 65 28 74 65  78 74 32 24 29 0d 1a ae  |ofile(text2$)...|
00004f50  17 f2 77 72 69 74 65 74  6f 66 69 6c 65 28 bd 28  |..writetofile(.(|
00004f60  31 30 29 29 0d 1a b8 05  e1 0d 1a c2 05 3a 0d 1a  |10)).........:..|
00004f70  cc 0e dd f2 73 65 6e 64  68 65 6c 70 0d 1a d6 28  |....sendhelp...(|
00004f80  e7 20 62 75 66 66 65 72  25 21 33 32 3d 6d 61 74  |. buffer%!32=mat|
00004f90  63 68 65 73 25 20 8c 20  62 75 66 66 65 72 25 21  |ches% . buffer%!|
00004fa0  33 36 3d 30 0d 1a e0 26  c8 99 20 22 57 69 6d 70  |36=0...&.. "Wimp|
00004fb0  5f 53 65 6e 64 49 6e 66  6f 72 6d 61 74 69 6f 6e  |_SendInformation|
00004fc0  22 2c 2c 62 75 66 66 65  72 25 0d 1a ea 05 e1 0d  |",,buffer%......|
00004fd0  1a f4 1c dd a4 63 72 65  61 74 65 74 6f 70 69 63  |.....createtopic|
00004fe0  6d 65 6e 75 28 6d 65 6e  75 24 29 0d 1a fe 0b 74  |menu(menu$)....t|
00004ff0  63 6e 74 25 3d 30 0d 1b  08 19 6d 65 6e 75 5f 70  |cnt%=0....menu_p|
00005000  74 72 25 3d 74 6f 70 69  63 5f 6d 65 6e 75 25 0d  |tr%=topic_menu%.|
00005010  1b 12 14 24 28 6d 65 6e  75 5f 70 74 72 25 29 3d  |...$(menu_ptr%)=|
00005020  22 20 22 0d 1b 1c 0c 77  69 64 74 68 25 3d 31 0d  |" "....width%=1.|
00005030  1b 26 05 cd 0d 1b 30 21  6d 65 6e 75 5f 70 74 72  |.&....0!menu_ptr|
00005040  25 3f 31 32 3d 37 3a 6d  65 6e 75 5f 70 74 72 25  |%?12=7:menu_ptr%|
00005050  3f 31 33 3d 32 0d 1b 3a  21 6d 65 6e 75 5f 70 74  |?13=2..:!menu_pt|
00005060  72 25 3f 31 34 3d 37 3a  6d 65 6e 75 5f 70 74 72  |r%?14=7:menu_ptr|
00005070  25 3f 31 35 3d 30 0d 1b  44 22 6d 65 6e 75 5f 70  |%?15=0..D"menu_p|
00005080  74 72 25 21 32 30 3d 34  34 3a 6d 65 6e 75 5f 70  |tr%!20=44:menu_p|
00005090  74 72 25 21 32 34 3d 30  0d 1b 4e 1e 6d 65 6e 75  |tr%!24=0..N.menu|
000050a0  5f 69 74 65 6d 5f 70 74  72 25 3d 6d 65 6e 75 5f  |_item_ptr%=menu_|
000050b0  70 74 72 25 2b 34 0d 1b  58 10 c8 95 20 6d 65 6e  |ptr%+4..X... men|
000050c0  75 24 3c 3e 22 22 0d 1b  62 16 6d 65 6e 75 5f 69  |u$<>""..b.menu_i|
000050d0  74 65 6d 5f 70 74 72 25  2b 3d 32 34 0d 1b 6c 20  |tem_ptr%+=24..l |
000050e0  6d 65 6e 75 5f 69 74 65  6d 24 3d a4 66 69 65 6c  |menu_item$=.fiel|
000050f0  64 28 6d 65 6e 75 24 2c  22 2c 22 29 0d 1b 76 15  |d(menu$,",")..v.|
00005100  21 6d 65 6e 75 5f 69 74  65 6d 5f 70 74 72 25 3d  |!menu_item_ptr%=|
00005110  30 0d 1b 80 17 6d 65 6e  75 5f 69 74 65 6d 5f 70  |0....menu_item_p|
00005120  74 72 25 21 34 3d 2d 31  0d 1b 8a 1d 6d 65 6e 75  |tr%!4=-1....menu|
00005130  5f 69 74 65 6d 5f 70 74  72 25 21 38 3d 26 37 30  |_item_ptr%!8=&70|
00005140  30 30 30 32 31 0d 1b 94  31 e7 20 a9 28 6d 65 6e  |00021...1. .(men|
00005150  75 5f 69 74 65 6d 24 29  3e 77 69 64 74 68 25 20  |u_item$)>width% |
00005160  8c 20 77 69 64 74 68 25  3d a9 28 6d 65 6e 75 5f  |. width%=.(menu_|
00005170  69 74 65 6d 24 29 0d 1b  9e 28 24 28 6d 65 6e 75  |item$)...($(menu|
00005180  5f 69 74 65 6d 5f 70 74  72 25 2b 31 32 29 3d 6d  |_item_ptr%+12)=m|
00005190  65 6e 75 5f 69 74 65 6d  24 2b bd 28 30 29 0d 1b  |enu_item$+.(0)..|
000051a0  a8 21 74 24 28 74 63 6e  74 25 29 3d 6d 65 6e 75  |.!t$(tcnt%)=menu|
000051b0  5f 69 74 65 6d 24 3a 74  63 6e 74 25 2b 3d 31 0d  |_item$:tcnt%+=1.|
000051c0  1b b2 05 ce 0d 1b bc 2f  3f 6d 65 6e 75 5f 69 74  |......./?menu_it|
000051d0  65 6d 5f 70 74 72 25 3d  3f 6d 65 6e 75 5f 69 74  |em_ptr%=?menu_it|
000051e0  65 6d 5f 70 74 72 25 20  84 20 25 31 30 30 30 30  |em_ptr% . %10000|
000051f0  30 30 30 0d 1b c6 1f 6d  65 6e 75 5f 70 74 72 25  |000....menu_ptr%|
00005200  21 31 36 3d 28 77 69 64  74 68 25 2a 38 2b 36 29  |!16=(width%*8+6)|
00005210  2a 32 0d 1b d0 0e 3d 6d  65 6e 75 5f 70 74 72 25  |*2....=menu_ptr%|
00005220  0d 1b da 05 3a 0d 1b e4  1f dd a4 63 72 65 61 74  |....:......creat|
00005230  65 63 61 74 61 67 6f 72  79 6d 65 6e 75 28 6d 65  |ecatagorymenu(me|
00005240  6e 75 24 29 0d 1b ee 0b  63 63 6e 74 25 3d 30 0d  |nu$)....ccnt%=0.|
00005250  1b f8 18 6d 65 6e 75 5f  70 74 72 25 3d 63 61 74  |...menu_ptr%=cat|
00005260  61 5f 6d 65 6e 75 25 0d  1c 02 14 24 28 6d 65 6e  |a_menu%....$(men|
00005270  75 5f 70 74 72 25 29 3d  22 20 22 0d 1c 0c 0c 77  |u_ptr%)=" "....w|
00005280  69 64 74 68 25 3d 31 0d  1c 16 05 cd 0d 1c 20 21  |idth%=1....... !|
00005290  6d 65 6e 75 5f 70 74 72  25 3f 31 32 3d 37 3a 6d  |menu_ptr%?12=7:m|
000052a0  65 6e 75 5f 70 74 72 25  3f 31 33 3d 32 0d 1c 2a  |enu_ptr%?13=2..*|
000052b0  21 6d 65 6e 75 5f 70 74  72 25 3f 31 34 3d 37 3a  |!menu_ptr%?14=7:|
000052c0  6d 65 6e 75 5f 70 74 72  25 3f 31 35 3d 30 0d 1c  |menu_ptr%?15=0..|
000052d0  34 22 6d 65 6e 75 5f 70  74 72 25 21 32 30 3d 34  |4"menu_ptr%!20=4|
000052e0  34 3a 6d 65 6e 75 5f 70  74 72 25 21 32 34 3d 30  |4:menu_ptr%!24=0|
000052f0  0d 1c 3e 1e 6d 65 6e 75  5f 69 74 65 6d 5f 70 74  |..>.menu_item_pt|
00005300  72 25 3d 6d 65 6e 75 5f  70 74 72 25 2b 34 0d 1c  |r%=menu_ptr%+4..|
00005310  48 10 c8 95 20 6d 65 6e  75 24 3c 3e 22 22 0d 1c  |H... menu$<>""..|
00005320  52 16 6d 65 6e 75 5f 69  74 65 6d 5f 70 74 72 25  |R.menu_item_ptr%|
00005330  2b 3d 32 34 0d 1c 5c 20  6d 65 6e 75 5f 69 74 65  |+=24..\ menu_ite|
00005340  6d 24 3d a4 66 69 65 6c  64 28 6d 65 6e 75 24 2c  |m$=.field(menu$,|
00005350  22 2c 22 29 0d 1c 66 15  21 6d 65 6e 75 5f 69 74  |",")..f.!menu_it|
00005360  65 6d 5f 70 74 72 25 3d  30 0d 1c 70 17 6d 65 6e  |em_ptr%=0..p.men|
00005370  75 5f 69 74 65 6d 5f 70  74 72 25 21 34 3d 2d 31  |u_item_ptr%!4=-1|
00005380  0d 1c 7a 1d 6d 65 6e 75  5f 69 74 65 6d 5f 70 74  |..z.menu_item_pt|
00005390  72 25 21 38 3d 26 37 30  30 30 30 32 31 0d 1c 84  |r%!8=&7000021...|
000053a0  31 e7 20 a9 28 6d 65 6e  75 5f 69 74 65 6d 24 29  |1. .(menu_item$)|
000053b0  3e 77 69 64 74 68 25 20  8c 20 77 69 64 74 68 25  |>width% . width%|
000053c0  3d a9 28 6d 65 6e 75 5f  69 74 65 6d 24 29 0d 1c  |=.(menu_item$)..|
000053d0  8e 28 24 28 6d 65 6e 75  5f 69 74 65 6d 5f 70 74  |.($(menu_item_pt|
000053e0  72 25 2b 31 32 29 3d 6d  65 6e 75 5f 69 74 65 6d  |r%+12)=menu_item|
000053f0  24 2b bd 28 30 29 0d 1c  98 21 63 24 28 63 63 6e  |$+.(0)...!c$(ccn|
00005400  74 25 29 3d 6d 65 6e 75  5f 69 74 65 6d 24 3a 63  |t%)=menu_item$:c|
00005410  63 6e 74 25 2b 3d 31 0d  1c a2 05 ce 0d 1c ac 2f  |cnt%+=1......../|
00005420  3f 6d 65 6e 75 5f 69 74  65 6d 5f 70 74 72 25 3d  |?menu_item_ptr%=|
00005430  3f 6d 65 6e 75 5f 69 74  65 6d 5f 70 74 72 25 20  |?menu_item_ptr% |
00005440  84 20 25 31 30 30 30 30  30 30 30 0d 1c b6 1f 6d  |. %10000000....m|
00005450  65 6e 75 5f 70 74 72 25  21 31 36 3d 28 77 69 64  |enu_ptr%!16=(wid|
00005460  74 68 25 2a 38 2b 36 29  2a 32 0d 1c c0 0e 3d 6d  |th%*8+6)*2....=m|
00005470  65 6e 75 5f 70 74 72 25  0d 1c ca 05 3a 0d 1c d4  |enu_ptr%....:...|
00005480  17 dd f2 72 65 73 65 74  63 6f 6e 66 69 67 75 72  |...resetconfigur|
00005490  65 77 69 6e 0d 1c de 1e  f2 77 72 69 74 65 5f 6d  |ewin.....write_m|
000054a0  65 73 73 28 63 6f 6e 66  69 67 25 2c 33 39 2c 22  |ess(config%,39,"|
000054b0  22 29 0d 1c e8 1e f2 77  72 69 74 65 5f 6d 65 73  |").....write_mes|
000054c0  73 28 63 6f 6e 66 69 67  25 2c 31 39 2c 22 22 29  |s(config%,19,"")|
000054d0  0d 1c f2 1e f2 77 72 69  74 65 5f 6d 65 73 73 28  |.....write_mess(|
000054e0  63 6f 6e 66 69 67 25 2c  34 33 2c 22 22 29 0d 1c  |config%,43,"")..|
000054f0  fc 1e f2 77 72 69 74 65  5f 6d 65 73 73 28 63 6f  |...write_mess(co|
00005500  6e 66 69 67 25 2c 34 30  2c 22 22 29 0d 1d 06 11  |nfig%,40,"")....|
00005510  e3 20 6c 6f 6f 70 3d 31  20 b8 20 31 38 0d 1d 10  |. loop=1 . 18...|
00005520  20 f2 77 72 69 74 65 5f  6d 65 73 73 28 63 6f 6e  | .write_mess(con|
00005530  66 69 67 25 2c 6c 6f 6f  70 2c 22 22 29 0d 1d 1a  |fig%,loop,"")...|
00005540  23 f2 77 72 69 74 65 5f  6d 65 73 73 28 63 6f 6e  |#.write_mess(con|
00005550  66 69 67 25 2c 32 30 2b  6c 6f 6f 70 2c 22 22 29  |fig%,20+loop,"")|
00005560  0d 1d 24 0a ed 20 6c 6f  6f 70 0d 1d 2e 1e f2 77  |..$.. loop.....w|
00005570  72 69 74 65 5f 6d 65 73  73 28 63 6f 6e 66 69 67  |rite_mess(config|
00005580  25 2c 34 37 2c 22 22 29  0d 1d 38 1e f2 77 72 69  |%,47,"")..8..wri|
00005590  74 65 5f 6d 65 73 73 28  63 6f 6e 66 69 67 25 2c  |te_mess(config%,|
000055a0  35 30 2c 22 22 29 0d 1d  42 1e f2 77 72 69 74 65  |50,"")..B..write|
000055b0  5f 6d 65 73 73 28 63 6f  6e 66 69 67 25 2c 35 33  |_mess(config%,53|
000055c0  2c 22 22 29 0d 1d 4c 1e  f2 77 72 69 74 65 5f 6d  |,"")..L..write_m|
000055d0  65 73 73 28 63 6f 6e 66  69 67 25 2c 35 36 2c 22  |ess(config%,56,"|
000055e0  22 29 0d 1d 4e 1e f2 77  72 69 74 65 5f 6d 65 73  |")..N..write_mes|
000055f0  73 28 63 6f 6e 66 69 67  25 2c 36 36 2c 22 22 29  |s(config%,66,"")|
00005600  0d 1d 56 05 e1 0d 1d 60  05 3a 0d 1d 6a 13 dd f2  |..V....`.:..j...|
00005610  63 72 65 61 74 65 6e 65  77 66 69 6c 65 0d 1d 74  |createnewfile..t|
00005620  0d ea 20 68 61 6e 64 6c  65 25 0d 1d 7e 18 6c 61  |.. handle%..~.la|
00005630  73 74 63 61 72 64 25 3d  30 3a 63 6c 65 61 72 25  |stcard%=0:clear%|
00005640  3d a3 0d 1d 80 17 f2 63  6c 65 61 72 67 72 65 79  |=......cleargrey|
00005650  28 6d 65 6e 75 25 2c 36  29 0d 1d 88 15 f2 73 65  |(menu%,6).....se|
00005660  74 67 72 65 79 28 6d 65  6e 75 25 2c 35 29 0d 1d  |tgrey(menu%,5)..|
00005670  92 15 f2 73 65 74 67 72  65 79 28 6d 65 6e 75 25  |...setgrey(menu%|
00005680  2c 34 29 0d 1d 9c 1a f2  73 65 74 67 72 65 79 28  |,4).....setgrey(|
00005690  66 69 6c 65 5f 6d 65 6e  75 25 2c 31 29 0d 1d a6  |file_menu%,1)...|
000056a0  1a f2 73 65 74 67 72 65  79 28 66 69 6c 65 5f 6d  |..setgrey(file_m|
000056b0  65 6e 75 25 2c 32 29 0d  1d b0 32 24 74 61 62 6c  |enu%,2)...2$tabl|
000056c0  65 3d 22 22 2b bd 28 30  29 3a 24 28 74 61 62 6c  |e=""+.(0):$(tabl|
000056d0  65 2b 33 32 29 3d 22 22  2b bd 28 30 29 3a 74 61  |e+32)=""+.(0):ta|
000056e0  62 6c 65 21 36 33 36 3d  30 0d 1d ba 38 dc 20 33  |ble!636=0...8. 3|
000056f0  39 2c 31 2c 32 2c 33 2c  34 2c 35 2c 36 2c 37 2c  |9,1,2,3,4,5,6,7,|
00005700  38 2c 39 2c 31 30 2c 31  31 2c 31 32 2c 31 33 2c  |8,9,10,11,12,13,|
00005710  31 34 2c 31 35 2c 31 36  2c 31 37 2c 31 39 2c 31  |14,15,16,17,19,1|
00005720  38 0d 1d c4 41 dc 20 32  31 2c 32 32 2c 32 33 2c  |8...A. 21,22,23,|
00005730  32 34 2c 32 35 2c 32 36  2c 32 37 2c 32 38 2c 32  |24,25,26,27,28,2|
00005740  39 2c 33 30 2c 33 31 2c  33 32 2c 33 33 2c 33 34  |9,30,31,32,33,34|
00005750  2c 33 35 2c 33 36 2c 33  37 2c 33 38 2c 34 30 2c  |,35,36,37,38,40,|
00005760  34 33 0d 1d ce 0a f7 20  8d 74 7a 5d 0d 1d d8 11  |43..... .tz]....|
00005770  74 65 24 3d 22 22 3a 63  65 24 3d 22 22 0d 1d e2  |te$="":ce$=""...|
00005780  11 e3 20 6c 6f 6f 70 3d  31 20 b8 20 32 30 0d 1d  |.. loop=1 . 20..|
00005790  ec 0d f3 20 68 61 6e 64  6c 65 25 0d 1d f6 25 74  |... handle%...%t|
000057a0  65 78 74 24 3d a4 67 65  74 62 75 74 74 6f 6e 28  |ext$=.getbutton(|
000057b0  63 6f 6e 66 69 67 25 2c  68 61 6e 64 6c 65 25 29  |config%,handle%)|
000057c0  0d 1e 00 30 e7 20 74 65  78 74 24 3c 3e 22 22 20  |...0. text$<>"" |
000057d0  80 20 74 65 78 74 24 3c  3e 22 20 22 20 8c 20 74  |. text$<>" " . t|
000057e0  65 24 3d 74 65 24 2b 22  2c 22 2b 74 65 78 74 24  |e$=te$+","+text$|
000057f0  0d 1e 0a 0a ed 20 6c 6f  6f 70 0d 1e 14 11 e3 20  |..... loop..... |
00005800  6c 6f 6f 70 3d 31 20 b8  20 32 30 0d 1e 1e 0d f3  |loop=1 . 20.....|
00005810  20 68 61 6e 64 6c 65 25  0d 1e 28 25 74 65 78 74  | handle%..(%text|
00005820  24 3d a4 67 65 74 62 75  74 74 6f 6e 28 63 6f 6e  |$=.getbutton(con|
00005830  66 69 67 25 2c 68 61 6e  64 6c 65 25 29 0d 1e 32  |fig%,handle%)..2|
00005840  30 e7 20 74 65 78 74 24  3c 3e 22 22 20 80 20 74  |0. text$<>"" . t|
00005850  65 78 74 24 3c 3e 22 20  22 20 8c 20 63 65 24 3d  |ext$<>" " . ce$=|
00005860  63 65 24 2b 22 2c 22 2b  74 65 78 74 24 0d 1e 3c  |ce$+","+text$..<|
00005870  0a ed 20 6c 6f 6f 70 0d  1e 46 14 74 65 24 3d c2  |.. loop..F.te$=.|
00005880  74 65 24 2c a9 74 65 24  2d 31 29 0d 1e 50 14 63  |te$,.te$-1)..P.c|
00005890  65 24 3d c2 63 65 24 2c  a9 63 65 24 2d 31 29 0d  |e$=.ce$,.ce$-1).|
000058a0  1e 5a 21 74 6f 70 69 63  73 25 3d a4 63 72 65 61  |.Z!topics%=.crea|
000058b0  74 65 74 6f 70 69 63 6d  65 6e 75 28 74 65 24 29  |tetopicmenu(te$)|
000058c0  0d 1e 64 23 63 61 74 61  73 25 3d a4 63 72 65 61  |..d#catas%=.crea|
000058d0  74 65 63 61 74 61 67 6f  72 79 6d 65 6e 75 28 63  |tecatagorymenu(c|
000058e0  65 24 29 0d 1e 6e 24 24  28 74 61 62 6c 65 2b 36  |e$)..n$$(table+6|
000058f0  34 29 3d 74 65 24 3a 24  28 74 61 62 6c 65 2b 33  |4)=te$:$(table+3|
00005900  32 30 29 3d 63 65 24 0d  1e 78 27 24 28 74 61 62  |20)=ce$..x'$(tab|
00005910  6c 65 2b 35 37 36 29 3d  a4 67 65 74 62 75 74 74  |le+576)=.getbutt|
00005920  6f 6e 28 63 6f 6e 66 69  67 25 2c 34 37 29 0d 1e  |on(config%,47)..|
00005930  82 27 24 28 74 61 62 6c  65 2b 35 38 38 29 3d a4  |.'$(table+588)=.|
00005940  67 65 74 62 75 74 74 6f  6e 28 63 6f 6e 66 69 67  |getbutton(config|
00005950  25 2c 35 30 29 0d 1e 8c  27 24 28 74 61 62 6c 65  |%,50)...'$(table|
00005960  2b 36 30 30 29 3d a4 67  65 74 62 75 74 74 6f 6e  |+600)=.getbutton|
00005970  28 63 6f 6e 66 69 67 25  2c 35 33 29 0d 1e 96 27  |(config%,53)...'|
00005980  24 28 74 61 62 6c 65 2b  36 31 32 29 3d a4 67 65  |$(table+612)=.ge|
00005990  74 62 75 74 74 6f 6e 28  63 6f 6e 66 69 67 25 2c  |tbutton(config%,|
000059a0  35 36 29 0d 1e a0 10 63  6c 65 61 72 62 69 74 73  |56)....clearbits|
000059b0  25 3d 30 0d 1e aa 39 e7  20 a4 6f 70 74 69 6f 6e  |%=0...9. .option|
000059c0  28 63 6f 6e 66 69 67 25  2c 35 39 29 3e 30 20 63  |(config%,59)>0 c|
000059d0  6c 65 61 72 62 69 74 73  25 2b 3d 38 3a 63 6c 74  |learbits%+=8:clt|
000059e0  25 3d b9 20 8b 20 63 6c  74 25 3d a3 0d 1e b4 39  |%=. . clt%=....9|
000059f0  e7 20 a4 6f 70 74 69 6f  6e 28 63 6f 6e 66 69 67  |. .option(config|
00005a00  25 2c 36 30 29 3e 30 20  63 6c 65 61 72 62 69 74  |%,60)>0 clearbit|
00005a10  73 25 2b 3d 34 3a 63 6c  69 25 3d b9 20 8b 20 63  |s%+=4:cli%=. . c|
00005a20  6c 69 25 3d a3 0d 1e be  39 e7 20 a4 6f 70 74 69  |li%=....9. .opti|
00005a30  6f 6e 28 63 6f 6e 66 69  67 25 2c 36 31 29 3e 30  |on(config%,61)>0|
00005a40  20 63 6c 65 61 72 62 69  74 73 25 2b 3d 32 3a 63  | clearbits%+=2:c|
00005a50  6c 64 25 3d b9 20 8b 20  63 6c 64 25 3d a3 0d 1e  |ld%=. . cld%=...|
00005a60  c8 39 e7 20 a4 6f 70 74  69 6f 6e 28 63 6f 6e 66  |.9. .option(conf|
00005a70  69 67 25 2c 36 32 29 3e  30 20 63 6c 65 61 72 62  |ig%,62)>0 clearb|
00005a80  69 74 73 25 2b 3d 31 3a  63 6c 70 25 3d b9 20 8b  |its%+=1:clp%=. .|
00005a90  20 63 6c 70 25 3d a3 0d  1e d1 3c 74 61 62 6c 65  | clp%=....<table|
00005aa0  3f 36 32 34 3d 63 6c 65  61 72 62 69 74 73 25 3a  |?624=clearbits%:|
00005ab0  24 28 74 61 62 6c 65 2b  36 32 37 29 3d a4 67 65  |$(table+627)=.ge|
00005ac0  74 62 75 74 74 6f 6e 28  63 6f 6e 66 69 67 25 2c  |tbutton(config%,|
00005ad0  36 36 29 0d 1e d2 21 6f  70 74 74 24 3d c0 a4 73  |66)...!optt$=..s|
00005ae0  74 72 69 6e 67 30 28 74  61 62 6c 65 2b 36 32 37  |tring0(table+627|
00005af0  29 2c 38 29 0d 1e d4 18  f2 45 6e 61 62 6c 65 49  |),8).....EnableI|
00005b00  63 6f 6e 28 66 69 6e 64  25 2c 38 29 0d 1e d5 17  |con(find%,8)....|
00005b10  f2 45 6e 61 62 6c 65 49  63 6f 6e 28 61 64 64 25  |.EnableIcon(add%|
00005b20  2c 34 29 0d 1e d6 1e f2  77 72 69 74 65 5f 6d 65  |,4).....write_me|
00005b30  73 73 28 66 69 6e 64 25  2c 38 2c 6f 70 74 74 24  |ss(find%,8,optt$|
00005b40  29 0d 1e d7 1d f2 77 72  69 74 65 5f 6d 65 73 73  |).....write_mess|
00005b50  28 61 64 64 25 2c 34 2c  6f 70 74 74 24 29 0d 1e  |(add%,4,optt$)..|
00005b60  d8 1c e7 20 6f 70 74 74  24 3d 22 20 22 20 84 20  |... optt$=" " . |
00005b70  6f 70 74 74 24 3d 22 22  20 8c 0d 1e d9 19 f2 44  |optt$="" ......D|
00005b80  69 73 61 62 6c 65 49 63  6f 6e 28 66 69 6e 64 25  |isableIcon(find%|
00005b90  2c 38 29 0d 1e db 18 f2  44 69 73 61 62 6c 65 49  |,8).....DisableI|
00005ba0  63 6f 6e 28 61 64 64 25  2c 34 29 0d 1e dc 05 cd  |con(add%,4).....|
00005bb0  0d 1e e0 18 f2 61 6c 74  65 72 5f 62 72 6f 77 73  |.....alter_brows|
00005bc0  65 28 63 61 72 64 25 29  0d 1e e1 1c f2 77 72 69  |e(card%).....wri|
00005bd0  74 65 5f 6d 65 73 73 28  66 69 6e 66 6f 25 2c 34  |te_mess(finfo%,4|
00005be0  2c 22 22 29 0d 1e e2 1c  f2 77 72 69 74 65 5f 6d  |,"").....write_m|
00005bf0  65 73 73 28 66 69 6e 66  6f 25 2c 38 2c 22 22 29  |ess(finfo%,8,"")|
00005c00  0d 1e e3 0f f2 75 70 64  61 74 65 73 69 7a 65 0d  |.....updatesize.|
00005c10  1e e4 25 f2 77 72 69 74  65 5f 6d 65 73 73 28 66  |..%.write_mess(f|
00005c20  69 6e 66 6f 25 2c 32 2c  22 3c 55 6e 69 74 6c 65  |info%,2,"<Unitle|
00005c30  64 3e 22 29 0d 1e e5 18  e7 20 74 63 6e 74 25 3d  |d>")..... tcnt%=|
00005c40  30 20 8c 20 74 24 28 30  29 3d 22 22 0d 1e e6 18  |0 . t$(0)=""....|
00005c50  e7 20 63 63 6e 74 25 3d  30 20 8c 20 63 24 28 30  |. ccnt%=0 . c$(0|
00005c60  29 3d 22 22 0d 1e e7 1e  f2 77 72 69 74 65 5f 6d  |)="".....write_m|
00005c70  65 73 73 28 66 69 6e 64  25 2c 33 2c 74 24 28 30  |ess(find%,3,t$(0|
00005c80  29 29 0d 1e e8 1d f2 77  72 69 74 65 5f 6d 65 73  |)).....write_mes|
00005c90  73 28 61 64 64 25 2c 37  2c 74 24 28 30 29 29 0d  |s(add%,7,t$(0)).|
00005ca0  1e ea 1e f2 77 72 69 74  65 5f 6d 65 73 73 28 66  |....write_mess(f|
00005cb0  69 6e 64 25 2c 36 2c 63  24 28 30 29 29 0d 1e ec  |ind%,6,c$(0))...|
00005cc0  1e f2 77 72 69 74 65 5f  6d 65 73 73 28 61 64 64  |..write_mess(add|
00005cd0  25 2c 31 30 2c 63 24 28  30 29 29 0d 1e ed 7e 66  |%,10,c$(0))...~f|
00005ce0  69 6e 64 74 6f 70 69 63  25 3d 31 3a 61 64 64 74  |indtopic%=1:addt|
00005cf0  6f 70 69 63 25 3d 31 3a  e7 20 74 63 6e 74 25 3d  |opic%=1:. tcnt%=|
00005d00  30 20 8c 20 f2 44 69 73  61 62 6c 65 49 63 6f 6e  |0 . .DisableIcon|
00005d10  28 66 69 6e 64 25 2c 34  29 3a f2 44 69 73 61 62  |(find%,4):.Disab|
00005d20  6c 65 49 63 6f 6e 28 61  64 64 25 2c 38 29 20 8b  |leIcon(add%,8) .|
00005d30  20 f2 45 6e 61 62 6c 65  49 63 6f 6e 28 66 69 6e  | .EnableIcon(fin|
00005d40  64 25 2c 34 29 3a f2 45  6e 61 62 6c 65 49 63 6f  |d%,4):.EnableIco|
00005d50  6e 28 61 64 64 25 2c 38  29 0d 1e ee 7e 66 69 6e  |n(add%,8)...~fin|
00005d60  64 63 61 74 61 25 3d 31  3a 61 64 64 63 61 74 61  |dcata%=1:addcata|
00005d70  25 3d 31 3a e7 20 63 63  6e 74 25 3d 30 20 8c 20  |%=1:. ccnt%=0 . |
00005d80  f2 44 69 73 61 62 6c 65  49 63 6f 6e 28 66 69 6e  |.DisableIcon(fin|
00005d90  64 25 2c 37 29 3a f2 44  69 73 61 62 6c 65 49 63  |d%,7):.DisableIc|
00005da0  6f 6e 28 61 64 64 25 2c  31 32 29 20 8b 20 f2 45  |on(add%,12) . .E|
00005db0  6e 61 62 6c 65 49 63 6f  6e 28 66 69 6e 64 25 2c  |nableIcon(find%,|
00005dc0  37 29 3a f2 45 6e 61 62  6c 65 49 63 6f 6e 28 61  |7):.EnableIcon(a|
00005dd0  64 64 25 2c 31 32 29 0d  1e ef 27 74 73 74 24 3d  |dd%,12)...'tst$=|
00005de0  24 28 74 61 62 6c 65 2b  35 37 36 29 3a 69 73 74  |$(table+576):ist|
00005df0  24 3d 24 28 74 61 62 6c  65 2b 35 38 38 29 0d 1e  |$=$(table+588)..|
00005e00  f0 27 64 73 74 24 3d 24  28 74 61 62 6c 65 2b 36  |.'dst$=$(table+6|
00005e10  30 30 29 3a 70 73 74 24  3d 24 28 74 61 62 6c 65  |00):pst$=$(table|
00005e20  2b 36 31 32 29 0d 1e f1  23 f2 77 72 69 74 65 5f  |+612)...#.write_|
00005e30  6d 65 73 73 28 62 72 6f  77 73 65 25 2c 30 2c 74  |mess(browse%,0,t|
00005e40  73 74 24 2b 22 3a 22 29  0d 1e f2 23 f2 77 72 69  |st$+":")...#.wri|
00005e50  74 65 5f 6d 65 73 73 28  62 72 6f 77 73 65 25 2c  |te_mess(browse%,|
00005e60  33 2c 69 73 74 24 2b 22  3a 22 29 0d 1e f3 23 f2  |3,ist$+":")...#.|
00005e70  77 72 69 74 65 5f 6d 65  73 73 28 62 72 6f 77 73  |write_mess(brows|
00005e80  65 25 2c 35 2c 64 73 74  24 2b 22 3a 22 29 0d 1e  |e%,5,dst$+":")..|
00005e90  f4 23 f2 77 72 69 74 65  5f 6d 65 73 73 28 62 72  |.#.write_mess(br|
00005ea0  6f 77 73 65 25 2c 37 2c  70 73 74 24 2b 22 3a 22  |owse%,7,pst$+":"|
00005eb0  29 0d 1e f5 21 f2 77 72  69 74 65 5f 6d 65 73 73  |)...!.write_mess|
00005ec0  28 61 64 64 25 2c 32 33  2c 74 73 74 24 2b 22 3a  |(add%,23,tst$+":|
00005ed0  22 29 0d 1e f6 20 f2 77  72 69 74 65 5f 6d 65 73  |")... .write_mes|
00005ee0  73 28 61 64 64 25 2c 33  2c 69 73 74 24 2b 22 3a  |s(add%,3,ist$+":|
00005ef0  22 29 0d 1e f7 21 f2 77  72 69 74 65 5f 6d 65 73  |")...!.write_mes|
00005f00  73 28 61 64 64 25 2c 31  31 2c 64 73 74 24 2b 22  |s(add%,11,dst$+"|
00005f10  3a 22 29 0d 1e f8 20 f2  77 72 69 74 65 5f 6d 65  |:")... .write_me|
00005f20  73 73 28 61 64 64 25 2c  36 2c 70 73 74 24 2b 22  |ss(add%,6,pst$+"|
00005f30  3a 22 29 0d 1e fa 1e f2  77 72 69 74 65 5f 6d 65  |:").....write_me|
00005f40  73 73 28 66 69 6e 64 25  2c 31 33 2c 74 73 74 24  |ss(find%,13,tst$|
00005f50  29 0d 1f 04 1e f2 77 72  69 74 65 5f 6d 65 73 73  |).....write_mess|
00005f60  28 66 69 6e 64 25 2c 31  34 2c 69 73 74 24 29 0d  |(find%,14,ist$).|
00005f70  1f 06 1e f2 77 72 69 74  65 5f 6d 65 73 73 28 66  |....write_mess(f|
00005f80  69 6e 64 25 2c 31 35 2c  64 73 74 24 29 0d 1f 07  |ind%,15,dst$)...|
00005f90  1e f2 77 72 69 74 65 5f  6d 65 73 73 28 66 69 6e  |..write_mess(fin|
00005fa0  64 25 2c 31 36 2c 70 73  74 24 29 0d 1f 09 05 e1  |d%,16,pst$).....|
00005fb0  0d 1f 0a 13 dd f2 63 6f  70 79 63 6f 6e 66 69 67  |......copyconfig|
00005fc0  75 72 65 0d 1f 0b 15 c8  99 20 22 48 6f 75 72 67  |ure...... "Hourg|
00005fd0  6c 61 73 73 5f 4f 6e 22  0d 1f 0c 16 f2 72 65 73  |lass_On".....res|
00005fe0  65 74 63 6f 6e 66 69 67  75 72 65 77 69 6e 0d 1f  |etconfigurewin..|
00005ff0  0d 1d f2 53 65 74 49 63  6f 6e 28 63 6f 6e 66 69  |...SetIcon(confi|
00006000  67 25 2c 35 39 2c 63 6c  74 25 29 0d 1f 0e 1d f2  |g%,59,clt%).....|
00006010  53 65 74 49 63 6f 6e 28  63 6f 6e 66 69 67 25 2c  |SetIcon(config%,|
00006020  36 30 2c 63 6c 69 25 29  0d 1f 18 1d f2 53 65 74  |60,cli%).....Set|
00006030  49 63 6f 6e 28 63 6f 6e  66 69 67 25 2c 36 31 2c  |Icon(config%,61,|
00006040  63 6c 64 25 29 0d 1f 22  1d f2 53 65 74 49 63 6f  |cld%).."..SetIco|
00006050  6e 28 63 6f 6e 66 69 67  25 2c 36 32 2c 63 6c 70  |n(config%,62,clp|
00006060  25 29 0d 1f 2c 28 f2 77  72 69 74 65 5f 6d 65 73  |%)..,(.write_mes|
00006070  73 28 63 6f 6e 66 69 67  25 2c 34 37 2c 24 28 74  |s(config%,47,$(t|
00006080  61 62 6c 65 2b 35 37 36  29 29 0d 1f 36 28 f2 77  |able+576))..6(.w|
00006090  72 69 74 65 5f 6d 65 73  73 28 63 6f 6e 66 69 67  |rite_mess(config|
000060a0  25 2c 35 30 2c 24 28 74  61 62 6c 65 2b 35 38 38  |%,50,$(table+588|
000060b0  29 29 0d 1f 40 28 f2 77  72 69 74 65 5f 6d 65 73  |))..@(.write_mes|
000060c0  73 28 63 6f 6e 66 69 67  25 2c 35 33 2c 24 28 74  |s(config%,53,$(t|
000060d0  61 62 6c 65 2b 36 30 30  29 29 0d 1f 4a 28 f2 77  |able+600))..J(.w|
000060e0  72 69 74 65 5f 6d 65 73  73 28 63 6f 6e 66 69 67  |rite_mess(config|
000060f0  25 2c 35 36 2c 24 28 74  61 62 6c 65 2b 36 31 32  |%,56,$(table+612|
00006100  29 29 0d 1f 54 17 74 65  24 3d 24 28 74 61 62 6c  |))..T.te$=$(tabl|
00006110  65 2b 36 34 29 2b 22 2c  22 0d 1f 90 0a f7 20 8d  |e+64)+","..... .|
00006120  74 7a 5d 0d 1f 9a 05 f5  0d 1f a4 0d f3 20 68 61  |tz].......... ha|
00006130  6e 64 6c 65 25 0d 1f ae  0f 61 3d a7 74 65 24 2c  |ndle%....a=.te$,|
00006140  22 2c 22 29 0d 1f b8 10  61 24 3d c0 74 65 24 2c  |",")....a$=.te$,|
00006150  61 2d 31 29 0d 1f c2 15  74 65 24 3d c1 74 65 24  |a-1)....te$=.te$|
00006160  2c 61 2b 31 2c 32 35 36  29 0d 1f cc 23 f2 77 72  |,a+1,256)...#.wr|
00006170  69 74 65 5f 6d 65 73 73  28 63 6f 6e 66 69 67 25  |ite_mess(config%|
00006180  2c 68 61 6e 64 6c 65 25  2c 61 24 29 0d 1f d6 09  |,handle%,a$)....|
00006190  fd 20 61 3d 30 0d 1f e0  0a f7 20 8d 64 44 5d 0d  |. a=0..... .dD].|
000061a0  1f ea 18 63 65 24 3d 24  28 74 61 62 6c 65 2b 33  |...ce$=$(table+3|
000061b0  32 30 29 2b 22 2c 22 0d  1f f4 05 f5 0d 1f fe 0d  |20)+",".........|
000061c0  f3 20 68 61 6e 64 6c 65  25 0d 20 08 0f 61 3d a7  |. handle%. ..a=.|
000061d0  63 65 24 2c 22 2c 22 29  0d 20 12 10 61 24 3d c0  |ce$,","). ..a$=.|
000061e0  63 65 24 2c 61 2d 31 29  0d 20 1c 15 63 65 24 3d  |ce$,a-1). ..ce$=|
000061f0  c1 63 65 24 2c 61 2b 31  2c 32 35 36 29 0d 20 26  |.ce$,a+1,256). &|
00006200  23 f2 77 72 69 74 65 5f  6d 65 73 73 28 63 6f 6e  |#.write_mess(con|
00006210  66 69 67 25 2c 68 61 6e  64 6c 65 25 2c 61 24 29  |fig%,handle%,a$)|
00006220  0d 20 30 09 fd 20 61 3d  30 0d 20 3a 21 f2 77 72  |. 0.. a=0. :!.wr|
00006230  69 74 65 5f 6d 65 73 73  28 63 6f 6e 66 69 67 25  |ite_mess(config%|
00006240  2c 36 36 2c 6f 70 74 74  24 29 0d 20 3c 0f f2 77  |,66,optt$). <..w|
00006250  72 69 74 65 76 61 6c 69  64 0d 20 44 16 c8 99 20  |ritevalid. D... |
00006260  22 48 6f 75 72 67 6c 61  73 73 5f 4f 66 66 22 0d  |"Hourglass_Off".|
00006270  20 4e 05 e1 0d 20 58 05  3a 0d 20 62 10 dd f2 77  | N... X.:. b...w|
00006280  72 69 74 65 76 61 6c 69  64 0d 20 6c 35 21 74 71  |ritevalid. l5!tq|
00006290  25 3d 63 6f 6e 66 69 67  25 3a 74 71 25 21 34 3d  |%=config%:tq%!4=|
000062a0  36 36 3a c8 99 20 22 57  69 6d 70 5f 47 65 74 49  |66:.. "Wimp_GetI|
000062b0  63 6f 6e 53 74 61 74 65  22 2c 2c 74 71 25 0d 20  |conState",,tq%. |
000062c0  76 35 24 28 74 71 25 21  33 32 29 3d 22 7a 33 3b  |v5$(tq%!32)="z3;|
000062d0  69 54 79 70 65 20 69 6e  20 79 6f 75 72 20 6f 70  |iType in your op|
000062e0  74 69 6f 6e 61 6c 20 74  6f 70 69 63 20 68 65 72  |tional topic her|
000062f0  65 2e 22 0d 20 80 05 e1  0d ff                    |e.". .....|
000062fa