; ; ZDB -- Z-Database ; ; Original Author: Joseph I. Mortensen ; 4214 Chelsea Ct. ; Midland, MI ; 517-835-6923 ; Compuserve 70037,3161 ; GEnie J.MORTENSEN3 ; ; Major customization and contributions by Terry Hazen. ; ; Assembler: ZMAC ; Linker: ZML ; ; Version 1.0 -- 11/23/90 -- incorporating revisions from 0.9 and ; Terry Hazen's 0.8z. ; ; For version history see ZDB.UPD. ; For documentation see ZDBDOC.WS ; ; ; vers equ 10 ; version suffix equ ' ' ; space if none or ascii chr ('x') day equ 11 ; revision day month equ 23 ; ... month year equ 90 ; ... year ; ; the usual equates ; ctrld equ 04h ctrle equ 05h bel equ 07h bs equ 08h tab equ 09h lf equ 0ah ff equ 0ch cr equ 0dh ctrls equ 13h ctrlx equ 18h ctrly equ 19h esc equ 1bh del equ 7fh fcb equ 5ch false equ 00h true equ 0ffh on equ true lstat equ 15 ; .request dslib ext timini,rclock,bin2bcd .request vlib ext stndout,stndend,gxymsg,vprint,vpstr ext at,cls,ereol,gotoxy,gz3init,drhorz ext drbox,erabox,grxon,grxoff,tinit,dinit ext @goxy .request z3lib ext zsyschk .request syslib ext f$make,f$open,f$close,f$write,f$append,getfs ext f$exist,r$write,r$read,setdma,mfn2,f$rename,f$delete ext codend,fname,condin,logud,bios ext isctrl,hmovb,moveb,compb,acase3 ext capin,cin,cout,pa2hc,phldc,phlfdc,mafdc ext lout,lcrlf,capstr,caps ext comphd,mulhd,eval10 ; jp start db 'Z3ENV' ; standard z3 header db 1 ; type 1 program z3addr: dw 0 ; ; configuration flags ; termf: db '<' ; char to terminate fields, 00h if none ; ; Default data file name ; 'filename.typ' deffn: db 'ZDB.DTA ' ; default data file name db 0 ; termination ; ; Printer string patches go here. Each string must be zero-terminated. ; Extra space is provided for longer printer codes. To eliminate any ; of these strings, make the first byte 0. The following are epson ; fx-85 compatible codes. ; ; Printer reset string, sent at start and end of each label/envelope ; printing session: ; db 'RST' reset: db esc,'@' ; printer reset string ds 2 ; extra space db 0 ; termination ; ; Set printer for printing return address: ; db 'RIN' rin: db esc,'x',1 ; printer nlq string db 0fh ; condensed print db esc,'p',1 ; proportional print ds 5 ; extra space db 0 ; termination ; ; Set printer for printing main address: ; db 'AIN' ain: db 12h ; cancel condensed print db esc,'E' ; set emphasized print db esc,'x',1 ; set nlq mode db esc,'p',1 ; set proportional print ds 3 ; extra space ds 0 ; termination ; ; Set left margin for envelope address: ; db 'ELM' lemarg: db esc,'l',40 ; may also use tabs ds 9 ; extra space db 0 ; termination ; ; Set left margin for label address. Set to 0 if no return address is ; desired. ; db 'LLM' llmarg: db 0 ; printer init string or tabs/spaces ds 11 ; extra space db 0 ; termination ; ; Use return address in label (only if labels are large enough): ; db 'LRA' lra: db 0 ; 0 if no return address is desired ; ; Set number of lines per label: ; db 'LPL' labln: db esc,'C',6 ; set lines per label ds 5 ; extra space db 0 ; termination ; ; Return address patch goes here. For normal business size ; envelopes, the number of line feeds must remain 14 and the string ; must be 0-terminated. To eliminate the return address change retadr ; to a terminating null (00h) and put 14 line feeds in addrsp. ; db 'RTA' retadr: line1: db 'Joseph I. Mortensen' db cr,lf line2: db '4214 Chelsea Ct.' db cr,lf line3: db 'Midland, MI 48640' db cr,lf,lf ; ; Pad the remainder of the address space with 0's ; rept 80-($-retadr)-3 db 0 endm ; ; ; Space from return address to address. For normal business envelopes, ; the total number of line feeds in the return address and addrsp should ; be 14. If the return address is the normal three lines, addrsp should ; contain 10 line feeds. ; db 'ASP' addrsp: db lf,lf,lf,lf,lf db lf,lf,lf,lf,lf ds 4 ; room for 14 line feeds db 0 ; termination ; ; command line help message ; hlpmsg: call vprint db 'ZDB vers ',vers/10+ '0','.',vers mod 10 + '0' if suffix db suffix endif db ' name and address database file manager' db cr,lf db ' Syntax: ZDB [[dir:]datafile.typ] ',cr,lf db ' Default datafile: ',0 ld hl,deffn ; display default filename call vpstr call vprint db cr,lf,0 jp exit2 ; ; program starts here ; start: ld (stack),sp ld sp,stack ; set up internal stack xor a ; ;initialize data area ld hl,data ld de,data+1 ld (hl),a ld bc,datalen ldir ld hl,(z3addr) ; check for z3 system call zsyschk jp nz,exit2 ; not present, exit call gz3init ; initialize vlib stuff call tinit ld a,(fcb+1) ; check command tail cp '/' ; asking for help? jp z,hlpmsg ; yes, print help message call timini ; check for clock jr z,nclk ; if no clock, jump ld hl,today call rclock ; store time if clock ok jr z,clkok nclk: call noclk ; otherwise get date from manual entry clkok: ld a,(fcb) ; get drive or a ; is it default? jr nz,gotdrv ; (no) ld c,25 ; get default call 5 inc a ; a=0 changed to a=1 gotdrv: add a,40h ; make it printable ld (fdrv),a ; store it ld (datafil),a ; and in header ld a,(fcb+13) ; get user for file ld (fusr),a ; store it ld hl,(z3addr) ; initialize terminal arrow keys ld de,146 ; add offset from env add hl,de ld bc,2 ; move two bytes ld de,rarrow ldir ; ; if no data file specified, use default datafile name ; ld a,(fcb+1) ; check first filename character cp ' ' jr nz,reopen ; filename specified ld de,fcb ; no filename, use default ld hl,deffn call fname ; parse filename to fcb ; ; after a sort, program loops to reopen ; reopen: ld a,(fusr) ; set user area for file ld e,a ld c,32 call 5 xor a ; set a to 0 ld (fcb+12),a ; set extent to 0 ld (fcb+32),a ; likewise w/ current record ld a,(fdrv) sub a,41h ld b,a ld a,(fusr) ld c,a call logud ld de,datafil+1 ; save user in header call mafdc ex de,hl ld a,':' ld (hl),a ; store colon inc hl push hl ; save header pointer ; ; open file ; ld de,fcb call f$exist ; check to see if it exists jr nz,open call f$make ; if not, create and open it cp 0ffh jp z,nogood open: call f$open jp nz,nogood ld de,fcb+1 ; save original name in buffer ld hl,nambuf call mfn2 pop hl ; restore header pointer call mfn2 ; save filename call frame ; file now open call scrn1 ; print frame and screen display ld de,fcb call getfs ; get file size in records ld (recs),hl ; store in recs ld a,h ; check for empty file or l jr z,menu ; if empty, go to menu xor a ld (srttyp),a ; reset sort type to default call index ; create index call first ; and display first record ; ; main program loop ; menu: call curtim ; display current time & date call menu1 ; display main menu call capin ; wait for command ld de,cmdtbl ; run command thro' command table call acase3 jr menu ; ; end of main loop ; ; command table ; cmdtbl: db 15 ; no. of entries in command table dw menu db 'Q' dw exit db 'A' dw new db 'E' dw edit db 'D' dw delete db 'F' dw find db ',' dw prev db '<' dw prev db '.' dw next db '>' dw next db 'P' dw output db 'R'-40h ; ^R to refresh screen if it gets out of whack dw refscr db 'S'-40h ; ^S for Sort dw asksrt db 'T' dw first db 'X' dw qfind db 'B' dw last ; ; exit routines ; exit: ld de,fcb call f$close call dinit exit2: ld sp,(stack) ret ; ; main subroutines ; ; screen display routines ; frame: call cls ; clear screen call at ; do standout header db 1,1 ld b,66 ; do standout bar call pad call drhorz ; puts frame at top and bottom db 2,1,79,0 ; of screen call drhorz ; uses graphics characters as db 23,1,79,0 ; found in in extended tcap ret refscr: call frame ; refreshes entire screen call scrn1 ; mostly used during debugging bldisp: call clrdis call displa currec: ld hl,(fptr) ; display of record count srl h ; divide by 2 rr l call gxymsg db 1,45,1,0 call phldc call vprint db ' of ',0 ld hl,(recs) ; divide by 2 srl h rr l call phlfdc call vprint ; terminate field and end standout db ' ',2,0 ret scrn1: ld hl,panel ld b,(hl) ; enter with hl=panel pointer inc hl ; scrnloop: call @goxy call vpstr djnz scrnloop ret ; menu1: call clrmnu ; main menu line call vprint db 1,'A=Add E=Edit D=Delete X=Xfind F=Find >=Next <=Prev ' db 'P=Print ^S=Sort Q=Quit ?',bs,2,0 ret curtim: ld hl,today ; displays current date and time call rclock call gxymsg db 1,66,1,0 ld a,(today+1) call pa2hc ld a,'/' call cout ld a,(today+2) call pa2hc ld a,'/' call cout ld a,(today) call pa2hc ld a,(clkflg) ; if no clock, don't go on jr nz,ctdun ld a,' ' call cout ld a,(today+3) call pa2hc ld a,':' call cout ld a,(today+4) call pa2hc ctdun: jp stndend ; ; fill record display fields with blanks ; clrdis: ld hl,pospanel ; point to cursor position panel ld b,(hl) inc hl clrloop: call @goxy ; position cursor to field start push bc ; save count ld b,(hl) ; get field length call pad ; pad field with blanks pop bc ; restore count inc hl ; point to next field djnz clrloop ret ; ; display current record ; displa: ld hl,pospanel ; point to cursor position panel ld de,fieldpanel ; point to field panel ld b,(hl) inc hl displaloop: call @goxy ; position cursor to field start inc hl ; point to next field call stndout ex de,hl ; hl=field address ld a,(hl) ; get field addr in hl inc hl push hl ld h,(hl) ld l,a call vpstr ; display field call stndend pop hl inc hl ; point to next field ex de,hl djnz displaloop newdat: call gxymsg db 3,66,1,0 ; date location ld a,(datmod+1) ; displays date call pa2hc ld a,'/' call cout ld a,(datmod+2) call pa2hc ld a,'/' call cout ld a,(datmod) call pa2hc jp stndend ; ; routines for adding, editing, and deleting records ; edit: xor a ; edit existing record ld (newflg),a ld hl,fptr dec (hl) dec (hl) call clrdis call displa call edita ld hl,edblk call rwrite ld hl,edblk ld de,128 add hl,de call rwrite jp bldisp new: ld de,fcb ; adding a new record call f$close ; close file call f$append ; open file to append mode ; new2: call clrdis call iniblk ; initialize edblk ld a,true ; set "new" flag ld (newflg),a ; edita: ld hl,today ; get date from "today" ld de,datmod ; and move to datmod ld bc,3 ldir call newdat ; get the date and display it call drbox db 20,1,3,79 call boxmsg call vprint db 1,'^X/TAB/RET=nxt fld ^E=prv fld ^S/^D=char l/r' db ' ^Y=era cursor rt ESC=exit',2,0 ; edfields: ld hl,pospanel ; point to cursor position panel ld de,fieldpanel ; point to field address panel ld b,(hl) ; number of fields inc hl ; efloop: ld a,(hl) ; save column position ld (cpos),a call @goxy ; position cursor push bc ; save count ld b,(hl) ; get field length dec hl ; save row position ld a,(hl) ld (lpos),a inc hl ; point to next field inc hl ex de,hl ; hl=field address push hl ld a,(hl) ; get field pointer in hl inc hl ld h,(hl) ld l,a call edloop ; edit field pop hl inc hl ; point to next field address inc hl ex de,hl ; hl=next field cursor position pop bc cp esc ; quit edloop? jp z,term ; yes, go to end cp ctrle ; if ^e, go to previous field jr z,prevf djnz efloop ; else do next field jr term ; done ; prevf: or a ; clear carry push bc ; save count ld bc,6 ; back up to previous field cursor pos sbc hl,bc ex de,hl ld bc,4 ; back up to previous field sbc hl,bc ex de,hl pop bc ; restore count inc b ; back up one field ld a,(pospanel) ; get number of fields cp b ; test for first field jr nc,efloop ; loop or fall thru if past first field ; term: call erabox db 20,1,3,79 call drbox35 call vprint db 1,'TAB starts over, RETURN saves.',2,0 call cin call erabox35 cp tab jp z,edita ld a,(newflg) ; if editing an existing record or a ; return to "edit" ret z ; call fwrite call drbox30 call vprint db 1,'Add another record? [Y]/n?',2,0 call capin call erabox30 cp 'Y' jp z,new2 cp cr jp z,new2 call asksrt call index ; update index jp last ; display most recent entry delete: ; delete routine call drbox25 call vprint db bel,1,'Are you sure? y/[N]',2,0 call capin call erabox25 cp 'Y' ret nz call iniblk ; fill current record w/ nulls ld hl,edblk ld (hl),0ffh ; make first byte 0ffh ld hl,fptr dec (hl) dec (hl) ld hl,edblk push hl call rwrite ; write to file pop hl ld de,128 add hl,de call rwrite ; write to file call index ; update index and fall thru ; ; file movement routines ; next: call ckemt ; find and display next record ret z ; check for empty file call ckeof ; check for end of file jr nz,oknxt call gotop ; set pointer to beginning of file oknxt: call rread ; read a record ld hl,edblk ; check first byte to see if it's a ld a,(hl) ; valid record. 0ffh = deleted record. cp 0ffh jr z,next ; if deleted, try the next one jp bldisp prev: call ckemt ; find previous record ret z ; check for empty file call backup ; move pointer back twice call backup call rread ; read a record ld hl,edblk ; check first byte to see if it's a ld a,(hl) ; valid record. 0ffh = deleted record. cp 0ffh jr z,prev ; if deleted, try the previous one jp bldisp last: ld hl,(recs) ; show last record in file dec hl dec hl ld (fptr),hl jp next first: ; show first record in file call gotop jp next ; ; search routines. uses a revised 'scanner' from syslib which eliminates ; case sensitivity. QFIND uses an index in RAM to find file pointers for ; last names. FIND runs through the file, top to bottom, to do its search. ; ; scanner: push bc ; save registers push de ; ; main loop ; scan: ld a,b ; done if b 1? jp p,oksort ; if so, go on with sort jp endsrt ; otherwise, end the sort oksort: srl h ; divide offset by 2 rr l ld (offset),hl ; save it ex de,hl ; store in DE ld hl,(total) sbc hl,de ; subtract offset from total ld (max),hl ; store in max as upper limit of loop loop2: ld de,0 ; set counter to 0 ld (count),de ld a,true ; set "in order" = true ld (ordflg),a loop3: ld hl,(max) ; compare counter to max to see if ld de,(count) ; loop is complete call comphd jr z,endlp3 ; if count = max, loop is done ld hl,(keylen) call mulhd ; multiply offset (count) * keylength ex de,hl ; store result in de ld hl,(inxbas) ; get index base address add hl,de ; add count * keylength to it ld (ptr1),hl ; store as ptr1 ld hl,(offset) ; get offset again ld de,(count) ; add count to it add hl,de ld de,(keylen) ; multiply * keylength call mulhd ld de,(inxbas) ; add to index base address add hl,de ld (ptr2),hl ; store result as ptr2 ld de,(ptr1) ld bc,(keyofs) ; number bytes to compare ld b,c call compb ; compare ptr1 and ptr2 call c,swap ; if hl (HL) ex af,af' ; original (HL) ld (de),a ; (HL) -> (DE) inc hl inc de ; bump the pointers dec bc ; decrement count ld a,b or c ; check for zero jr nz,swp ; again xor a ; set in order flag to false ld (ordflg),a ret ; ; output routines ; output: ; printed output options ; check to see if printer ready ld a,lstat ; bios list status call bios jr nz,prtrdy call drbox db 20,1,3,71 call boxmsg call vprint db bel db 1,'Printer Not Responding...Check It, Then Press Any Key',2 db ' (ESC to Quit)',0 call cin cp esc ; an escape route, if needed jr nz,output1 call erabox db 20,1,3,71 ret ; output1:call erabox db 20,1,3,71 jr output ; try again ; prtrdy: call clrmnu call vprint db 1,'Output Options: L=Labels E=Envelopes Q=Quit ?',2,bs,0 call capin cp 'L' call z,labels cp 'E' call z,envel cp 'Q' ret z jr prtrdy ret labels: ld a,1 ; initialize copies to 1 ld (copies),a call clrmnu call vprint db 1,'S=Single Label K=By Key M=Multiple Copies ' db 'C=Complete File Q=Quit ?',2,bs,0 call capin cp 'Q' ret z cp 'S' jr z,lblm cp 'K' jp z,lblkey cp 'M' jp z,multi cp 'C' jr nz,labels fulset: ; prints entire file call gotop fullp: call ckemt jr z,lblm call ckeof jr z,lblm call rread ld hl,edblk ; point to current record ld a,(hl) cp 0ffh ; skip if it's a deleted record jr z,fullp call prlbl jr fullp lblm: call fnpmen call capin cp 'Q' ret z cp 'F' call z,find cp 'X' call z,qfind cp 'N' call z,next cp 'P' call z,prlbl jr lblm ret ; ; input for search ; getkey: call drbox db 20,1,3,45 call boxmsg call vprint db 1,'Look for >',2,0 push bc ; b has number of characters call pad ld h,21 ; set screen location ld l,13 ld (lpos),hl ; save it call gotoxy pop bc ; get bc back ld hl,srch ; save search string call edloop ld hl,srch call capstr ; make search string all caps call erabox db 20,1,3,45 ret ; ; label output selection keys ; lblkey: call clrmnu call vprint db 1,'Select Key: C=City S=State Z=Zip X=Code ' db 'Q=Quit ?',2,bs,0 keylp: call capin ld de,keytbl call acase3 jr lblkey keytbl: db 5 dw keylp db 'Q' dw menu db 'C' dw keyc db 'S' dw keys db 'Z' dw keyz db 'X' dw keyx keyc: ld hl,city ld b,25 jr keyok keys: ld hl,state ld b,3 jr keyok keyz: ld hl,zip ld b,11 jr keyok keyx: ld hl,cmnts2 ld b,3 keyok: ld (prkey),hl call getkey ; get input for key call gotop ; search from beginning of file xor a ld (fndflg),a loopk: call ckemt ; quit if file empty ret z call ckeof ; quit at end of file jr z,notfnd call rread ; read file ld hl,srch ; search string ld de,(prkey) ; search target push bc ld b,c ; exact match call scanner ; do search jr nz,noluck ld a,true ld (fndflg),a call prlbl ; on a match, print label noluck: pop bc jr loopk ; repeat notfnd: ld a,(fndflg) ; check found flag or a ret nz nomat: call drbox30 call vprint db bel,'No Match, Press Any Key',0 call cin call erabox30 ret fnpmen: call clrmnu ; find, next, print menu call vprint db 1,'F=Find X=Xfind N=Next P=Print Q=Quit ?',2,bs,0 ret envel: call fnpmen ; envelope printing menu call capin cp 'F' call z,find cp 'X' call z,qfind cp 'N' call z,next cp 'Q' ret z cp 'P' call z,prenv jr envel ret prenv: ; print envelope ld a,true ld (envflg),a call prrta ; print return address ld hl,addrsp ; space down to address call elpstr jr pradr ; print the address prlbl: ; print labels xor a ld (envflg),a ld a,(copies) ; get number of copies or a ; if it's zero, quit ret z ; ldb: ld b,a ; number in b prlbl1: call condin ; a keypress will interrupt printing jr nz,quitpr ; of multiple copies push bc ; save number or pradr will lose it call prrtal call pradr pop bc ; get number back djnz prlbl1 ; loop until b=0 quitpr: ld a,1 ; reset counter to 1 ld (copies),a ld hl,reset ; reset printer on exit ; ; send 0-terminated string to printer ; elpstr: ld a,(hl) inc hl or a ret z call lout jr elpstr ; adrtab: ld hl,lemarg ; point to envelope left margin string ld a,(envflg) ; check if label, tho or a jr nz,elpstr ld hl,llmarg ; if label, use label left margin jr elpstr ; pradr: ld hl,ain ; initialize printer for address call elpstr call adrtab ; tab over if envelope ld hl,fieldpanel ld b,8 ; number of fields to print ; paloop: push bc ; save field count ld a,(hl) ; get field address in hl inc hl push hl ld h,(hl) ld l,a ld a,(hl) ; skip empty fields or a jr z,paldun call elpstr ; print field ; ld a,b ; put field count in a ld de,patbl ; run through the patbl call acase3 jr palnl ; palret: pop de ; pop acase3 return address palnl: call lcrlf ; do new line paltab: call adrtab ; tab over to start of new field paldun: pop hl ; restore field address pointer pop bc ; restore field count inc hl ; point to next field address djnz paloop ; formfd: ld a,ff ; sends final formfeed jp lout ; ; special case: ; sfirst: ld a,' ' ; add a space, skip new line and envtab call lout pop de ; clear return address from stack jr paldun ; ; special case table ; patbl: db 3 dw palret ; default on no match db 8 ; dw sfirst ; first name adds space, no new line db 4 dw sfirst ; city adds space, no new line db 3 dw sfirst ; state adds space, no new line ; multi: ; multiple copy option call drbox25 call vprint db 1,'How many copies? ',2,0 ld c,0 ld hl,xcopy getnum: call cin cp cr jr z,cpyfin call cout ld (hl),a inc hl inc c ld a,c cp 3 ; maximum 3 digits jr nz,getnum cpyfin: ld (hl),0 ld hl,xcopy call eval10 ; convert to binary ld (copies),a ; store it call erabox25 jp prlbl ; print labels ; ; print return address on label ; prrtal: ld a,(lra) ; check if return address is desired or a jr nz,prrta ; yes rsll: ld hl,reset ; reset printer call elpstr ld hl,labln ; set label form length jp elpstr ; ; print return address on envelope ; prrta: call rsll ; reset printer and set label form length prrt: ld hl,rin ; initialize printer for return address call elpstr ld hl,retadr ; point to return address jp elpstr ; and print it ; ; support routines ; ; edloop is a simple line editor. maximum number of characters ; is passed in b. esc will exit at any point and take you back ; to the calling routine. edloop: ld c,0 ; initialize character count xor a ld (capflag),a ; set cap flag to no ld a,b ; get count cp 3 ; state? jr nz,edlp1 ; no ld (capflag),a ; else set caps flag ; edlp1: ld a,(capflag) ; check caps flag or a jr z,edlp2 ; get exact input call capin ; get caps input jr edlp3 edlp2: call cin ; get character edlp3: call isctrl ; is it a control character? jr nz,alpha ; no, jump cp esc ; esc - finish add/edit ret z cp ctrle ; ^e - move to previous field ret z cp cr ; cr - next field ret z cp tab ; tab - next field ret z cp ctrlx ; ^x - next field ret z cp ctrly ; ^y -- erases from cursor to end of line call z,eralin jr z,edlp1 cp del ; delete backspaces and deletes jr nz,arokey ; check for right/left terminal arrow keys ; and ^s/^d and bs keys xor a cp c ; don't backspace if no characters in string jr z,edlp1 call lcurs ; move cursor left call eralin ; kill last part of line jr edlp1 ; alpha: ex af,af' ; save character in af' inc c ld a,c ; check to see if you've reached the maximum cp b ; number of characters jr z,noroom call stndout ex af,af' ; get character back call cout ; handle alphanumeric characters normally ld (hl),a ; add to string inc hl ; update string pointer call stndend call currt ; update cursor position jr edlp1 ; get next character noroom: ex af,af' call beep dec c jr edlp1 ; ; handler for cursor keys and terminal arrow keys ; arokey: cp ctrls ; ^s -- cursor left jr z,lcur bksp: cp bs ; ^h -- cursor left lcur: call z,lcurs jr z,edlp1 ctrd: cp ctrld ; ^d -- cursor right call z,rcurs jr z,edlp1 termky: push de ; check for terminal arrow keys ex af,af' ; save keyboard character ld a,(rarrow) ; get right arrow or a ; if null, quit jr z,akdun ld e,a ; store right arrow key in e ld a,(larrow) ; get left arrow or a ; if null, quit jr z,akdun ld d,a ; store left arrow in d ex af,af' ; get keyboard character back cp e ; compare it to e call z,rcurs ; if match, move cursor right cp d ; compare it to d call z,lcurs ; if match, move cursor left akdun: pop de jp edlp1 ; movcur: push hl ; move cursor to position stored ld hl,(lpos) ; in lpos call gotoxy pop hl ret currt: push hl ; increment cursor location in lpos ld hl,(lpos) inc l ld (lpos),hl pop hl ret curlf: push hl ; decrement cursor location in lpos ld hl,(lpos) dec l ld (lpos),hl pop hl ret lcurs: dec c ; decrement character count ld a,c cp -1 ; if character count <0, don't move jr nz,movel call beep inc c ret movel: dec hl ; move pointer call curlf ; decrement cursor position call movcur ; move cursor ret rcurs: dec b ld a,b cp c ; if maximum reached, don't move jr nz,mover call beep inc b ret mover: inc c inc b inc hl ; increment pointer call currt ; increment cursor position call movcur ; move cursor ret eralin: ; erase from cursor to end of line push bc ; save bc ld a,b sub a,c ; how many spaces to end of field? ld b,a ; number of spaces to underscore push bc ; save count call pad pop bc ; restore count push hl ; save field pointer call clean ; fill remainder of field with 0's pop hl ; restore field pointer call movcur ; restore cursor to original position pop bc ret iniblk: ld hl,edblk ; zeroes everything in the ld b,255 ; editing block clean: ld (hl),0 inc hl djnz clean ret gotop: ld hl,fptr ; set file pointer to beginning of file ld (hl),0 ret ckemt: ld hl,(recs) ; check for empty (0 record) file ld a,h or l ret ckeof: ld de,(fptr) ; check for end of file call comphd ret wrtinc: call setdma ; hl points to dma ld de,fcb call f$write ; writes one 128 byte record jp nz,wrterr ld a,(newflg) ; is it a new record? or a ; if not, don't increment pointer ret z ld hl,fptr ; increments file pointer inc (hl) ret fwrite: ld hl,edblk push hl call wrtinc pop hl ld de,128 add hl,de call wrtinc ld a,(newflg) ; if it's a new record, increment or a ; the record count. ret z ld hl,recs inc (hl) inc (hl) ret rrdinc: ; random read one record call setdma ld hl,(fptr) ld de,fcb call r$read jp nz,ermgr1 inc hl ld (fptr),hl ; increment file pointer ret rread: ; rec num to read in (fptr) ld hl,edblk push hl call rrdinc pop hl ld de,128 add hl,de jr rrdinc rwrite: call setdma ld hl,(fptr) ld de,fcb call r$write jp nz,ermgr1 ld hl,fptr ; increment file pointer inc (hl) ret backup: ld hl,(fptr) ; back up file pointer 256 bytes ld a,h or l ; if file pointer at zero, jr nz,ok ; point to end of file ld hl,(recs) ld (fptr),hl jr backup ok: dec hl dec hl ld (fptr),hl ret pad: call stndout ; set standout ld a,' ' ; character to pad padchr equ $-1 pad0: dec b ; b has byte count on entry ploop: call cout djnz ploop call stndend ld a,(termf) ; check for termination character or a ret z jp cout drbox25:call drbox db 20,1,3,25 jr boxmsg drbox30:call drbox db 20,1,3,30 jr boxmsg drbox35:call drbox db 20,1,3,35 ; fall through boxmsg: call at db 21,3 ret erabox25: call erabox db 20,1,3,25 ret erabox30: call erabox db 20,1,3,30 ret erabox35: call erabox db 20,1,3,35 ret clrmnu: call at ; clears menu line db 24,1 jp ereol beep: ld a,bel ; beeps jp cout ; ; error handlers and messages ; nogood: call vprint db 'Could not open file',0 jp exit noclk: xor a ; sets clock flag to false ld (clkflg),a call vprint db bel,'No clock/bad clock.',cr,lf,lf db 'Enter today''s date:',cr,lf db tab,'Month (MM): ',0 call getdat ld hl,today+1 ld (hl),a ; a has bcd from getdat call vprint db tab,'Day (DD): ',0 call getdat ld hl,today+2 ld (hl),a call vprint db tab,'Year (YY): ',0 call getdat ld hl,today ld (hl),a ret getdat: ld c,0 ; routine for manual date input ld hl,datbuf datlp: call cin cp 'C'-40h ; ^C to exit program jp z,exit2 call cout ld (hl),a inc hl inc c ld a,c cp 2 ; maximum 3 digits jr nz,datlp ld (hl),0 ; terminate with a null ld hl,datbuf call eval10 ; convert to binary jp bin2bcd ; binary to bcd, bcd in a reg wrterr: call vprint db 'Write Error',cr,lf,0 jp menu ermgr1: call at ; random read error handler db 22,1 ld hl,errmsg1 cp 1 jr z,disperr ld hl,errmsg3 cp 3 jr z,disperr ld hl,errmsg4 cp 4 jr z,disperr ld hl,errmsg6 cp 6 jr z,disperr ld hl,errmsgx ; unknown error disperr:call vpstr jp menu ; ; string and data storage ; errmsg1:db bel,'Reading unwritten record',0 errmsg3:db bel,'Can''t close current extent',0 errmsg4:db bel,'Reading unwritten extent',0 errmsg6:db bel,'Read beyond end of disk',0 errmsgx:db bel,'Unknown read error',0 srtfnm: db 'SORTED.$$$',0 ; temporary file name for sort file bakfil: db 'BACKUP.DTA',0 ; backup file name ; ; Field title panel ; panel: db 14 ; number of elements db 01,01,1,'ZDB vers ',vers/10+ '0','.',vers mod 10 +'0' if suffix ; if suffix, add revision date db suffix ; db ' ' ; db month/10 + '0',month mod 10 + '0','/' ; db day/10 + '0',day mod 10 + '0','/' ; db year/10 + '0',year mod 10 + '0' endif db 2,0 db 01,22,1 datafil:db ' ',2,0 db 03,51,'Last modified >',0 db 06,10,'First Name >',0 db 07,11,'Last Name >',0 db 08,11,'Address 1 >',0 db 09,11,'Address 2 >',0 db 10,16,'City >',0 db 11,15,'State >',0 db 12,17,'Zip >',0 db 13,13,'Country >',0 db 15,15,'Phone >',0 db 17,10,'Comments 1 >',0 db 18,10,'Comments 2 >',0 ; ; cursor positions for record display fields ; pospanel: db 11 ; number of fields db 06,22,fslen ; fstnm db 07,22,lnlen ; lname db 08,22,a1len ; addr1 db 09,22,a2len ; addr2 db 10,22,cilen ; city db 11,22,stlen ; state db 12,22,zilen ; zip db 13,22,ctlen ; ctry db 15,22,phlen ; phon db 17,22,c1len ; cmnts1 db 18,22,c2len ; cmnts2 ; ; addresses of record buffer fields ; fieldpanel: dw fstnm dw lname dw addr1 dw addr2 dw city dw state dw zip dw ctry dw phon dw cmnts1 dw cmnts2 ; ; uninitialized data area ; dseg ; ; initialize the following data area at startup ; data equ $ ; start of data area ; ; record fields and field lengths ; ; each of these fields must be null-terminated so actual actual ; field length is one less ; edblk: fstnm: ds 21 fslen equ $-fstnm lname: ds 21 lnlen equ $-lname addr1: ds 24 a1len equ $-addr1 addr2: ds 24 a2len equ $-addr2 city: ds 18 cilen equ $-city state: ds 3 ; only 2-letter codes allowed stlen equ $-state zip: ds 11 zilen equ $-zip ctry: ds 14 ctlen equ $-ctry phon: ds 39 phlen equ $-phon cmnts1: ds 39 c1len equ $-cmnts1 cmnts2: ds 39 c2len equ $-cmnts2 datmod: ds 3 ; no need for null-terminator here ; stored as bcd ; rarrow: ds 1 ; arrow keys from tcap larrow: ds 1 lpos: ds 1 ; cursor position (line and column) cpos: ds 1 ; xcopy: ds 4 ; input buffer for number of copies copies: ds 1 ; copies to print envflg: ds 1 ; envelope flag prkey: ds 2 ; address of key to search fndflg: ds 1 ; found flag for selection key ; clkflg: ds 1 ; clock flag - 0FFh = no clock capflag:ds 1 ; edloop flag for state caps input datbuf: ds 3 ; temporary date buffer today: ds 6 ; current date and time (bcd) ; recs: ds 2 ; number of records in file fptr: ds 2 ; pointer to current record xfptr: ds 2 ; last record read newflg: ds 1 ; new flag (used with add/edit) srttyp: ds 1 ; sort type flag keylen: ds 2 ; key length keyofs: ds 2 ; key offset inxptr: ds 2 ; pointer to sort index inxbas: ds 2 ; address of index base (1st record) ordflg: ds 1 ; "in order flag" total: ds 2 ; number of records to sort offset: ds 2 ; offset for sort count: ds 2 ; counter for sort loop xcount: ds 2 ; counter for express search max: ds 2 ; max reiterations for sort loop ptr1: ds 2 ; pointer to first record in sort ptr2: ds 2 ; pointer to second record in sort srtfcb: ds 36 ; sort file control block sfdrv: ds 1 ; sort file drive sfusr: ds 1 ; sort file user area bakfcb: ds 36 ; backup file control block fdrv: ds 1 ; file drive fusr: ds 1 ; file user area nambuf: ds 12 ; buffer for original file name srch: ds 11 ; search string datalen equ $-data ds 80 ; stack space stack: ds 2 ; old stack location end