;======================================================================= ; ; ; R E M I N D ; ; A ZCPR3/ZSDOS Appointment Reminder Utility ; ; by ; Terry Hazen ; 21460 Bear Creek Road ; Los Gatos CA 95030 ; ; Voice.......... (408) 354-7188 ; Zee-Machine.... (408) 245-1420 ; Ladera Znode... (213) 670-9465 ; ;======================================================================= ; ; Revision History ; ---------------- ; ; 07/19/91 Added calendar display at startup. Use of '/' option ; v1.4 flag is now mandatory. Defaults to datafile filetype of ; 'REM' if the specified datafile is not found and the ; datafile filetype is blank, allowing the user to enter ; just the datafile filename for datafiles. Added screen ; paging option to allow turning off paging when sending ; reminders to the printer. Now does another printer ; check at the '[More]' message so the system won't hang ; if the printer is turned off at that point. Added the ; option (/1-12) to display a calendar and the upcoming ; reminders for a specified month only. ; - Terry Hazen ; ; 05/25/91 Added rudimentary maxdrv/maxusr test, found about a ; v1.3 dozen bytes of code to save to help "pay" for it. ; The new test prevents users with file patcher access ; from reaching files beyond these environment limits. ; Also modified "prsopt" and its calling code to allow ; specification of short datafile names as long as they ; don't include any option letters, the "prsopt" ; algorithm is now a tad more rigorous with regard to ; leading slashes as well, at the cost of a few bytes. ; Put the slash in help message. Changed message at ; "noclk" since the DSLIB calls aren't ZSDOS-specific ; -- they work with DateStamper and CP/M+ too. Got rid ; of the single use of the alternate HL register since ; it seemed unnecessary and had only a miniscule speed ; advantage over a conventional push/pop sequence. ; REMIND will no longer waste paper if options S and P ; are selected together, or if there are no reminders. ; Still (barely) 32 records -- and a great little tool! ; - Bruce Morgen ; ; 05/19/91 Fixed some remaining display bugs and a branching error ; v1.2 in the code causing lack of command-line 'U' option ; control of the upcoming reminder display if there were ; no reminders for the current day. Added a TPA check to ; avoid hanging the system if a file larger than the ; available TPA were accidentally read in. The TPA is ; also checked during index building and when building a ; new sorted file. Thanks to Howard Goldstein for the ; TPA check suggestion and bug reports. ; - Terry Hazen ; ; 05/11/91 Fixed bug involving proper display of 2-digit user ; v1.1 numbers in ZPRDFN. Now allows any number of spaces ; between date and time entries. Added CFG flag for ; automatic display of upcoming reminders if there are non ; for today. Changed printer initialization to length- ; prefixed string to allow hex 0 bytes in string. ; Increased length for default filename fields from 12 to ; 16 bytes. ; - Terry Hazen ; ; 05/01/91 Initial release ; v1.0 - Terry Hazen ; ;======================================================================= ; ; System equates ; off equ 0 on equ 0ffh no equ 0 yes equ not no ; ; Version ; vers equ 14 ; Version number vmonth equ 07 ; Revision month vday equ 19 ; ...day vyear equ 91 ; ...year ; ; System addresses ; bdos equ 0005h ; BDOS entry fcb1 equ 005Ch ; CP/M default fcb1 fcb2 equ 006Ch ; CP/M default fcb2 cmdbuf equ 0080h ; Command line buffer ; ; ASCII values ; bell equ 07 ; Ring console bell bs equ 08 ; Back space tab equ 09 ; Tab over lf equ 10 ; Line feed ff equ 12 ; Form feed cr equ 13 ; Carriage return esc equ 27 ; Escape ;======================================================================= ; public $memry,envptr ; ; Request library routines ; .request nztim ext date,mont,year,bc2bi,bi2bc .request jthlib ; Custom routines ext fnamz,zprdfn,dispfn,srdat1 ; .request dslib ext timini,rclock ; .request vlib ext z3vinit,stndout,stndend,tinit,dinit ; .request z3lib ext z3log ; .request syslib ext setdma,bios,hfilb ext f$open,f$close,f$read,f$rename ext f$make,f$write,f$delete ext compb,comphd,eval10,isdigit ext cin,cout,lout,sout,spstr,sprint,sctlfl ext ssbini,sort ;======================================================================= jp start db 'Z3ENV' ; ZCPR3 indentifier db 1 ; Type 1 utility envptr: dw 0 ; Z3ENV address ;======================================================================= ; ; Configuration area ; ; Display upcoming reminders as default. ; drflag: db 0 ; ON to display upcoming reminders as default ; lmarg: db 8 ; Number of spaces in left printer margin ; ; Default CFG filename ; db 'REMIND' ; Default CFG filename db vers/10+'0',vers mod 10+'0'; 8 characters db 0 ; Termination ; ; Default datafil filename in the form 'du:fname.typ '. The du: is ; optional, and there must be 17 characters total, including a mandatory ; terminating space. Fill unused trailing positions with spaces: ; defdf: db 'REMIND.REM '; Datafile name (16 chars max) db ' ' ; Termination ; ; Backup file filename in the form 'fname.typ '. There must be 13 ; characters total, including a mandatory terminating space. This file ; will be written to the datafile directory. ; backup: db 'BACKUP.REM '; Backup datafile filename (12 chars) db ' ' ; Termination ; ; Printer configuration area: ; ptrchk: db on ; ON to use BIOS listst printer check ; ; Length-prefixed printer initialization string ; pinit: db 0 ; Length of init string ds 6 ; Printer init string (6 bytes max) ; ; ON to send printer a form feed... ; useff: db off ; After printing current day's reminders endff: db off ; At exit ; ; Page display default ; dpage: db on ; ON to page display ;======================================================================= ; ; Command line help screen ; banner: call margin call sprint defnam: db 'REMIND Appointment Reminder Utility vers ' db vers/10+'0','.',vers mod 10+'0' db cr,lf,0 ret ; help: call banner call sprint db 'Syntax:',cr,lf,' ',0 ld hl,(dfname) ; Get name pointer ld b,8 call dispfn ; Display it call sprint db ' [[dir:]datafile] [/options]',cr,lf db ' (Default text datafile is ',0 ld b,16 ld hl,defdf ; Display default datafile name call dispfn call sprint db ')',cr,lf db 'Options:',cr,lf db ' U - ',0 ld a,(drflag) ; Check default flag or a ld hl,incmsg ; Point to include message jr z,help0 ; Off ; ld hl,nomsg ; help0: call spstr call sprint db 'upcoming reminders',cr,lf, db ' 1-12 Upcoming reminders for specified month only',cr,lf db ' P - Print reminders',cr,lf db ' D - ',0 ld hl,dtmsg ; Point to default message ld a,(dpage) ; Check default flag or a jr nz,help1 ld hl,pmsg ; help1: call spstr call sprint db 'age screen display',cr,lf db ' S - Sort datafile',cr,lf,0 ret ; ; Help messages ; dtmsg: db 'Don''t p',0 pmsg: db 'P',0 incmsg: db 'Include all ',0 ; ; Program start ; start: call cononly ; Initialize output flag ld (stack),sp ld sp,stack ; Set up internal stack ld hl,exit ; Put exit address on stack push hl ; xor a ld hl,data ; Initialize data area ld b,datalen call hfilb ; ld hl,(envptr) ; Do Z-system check call z3vinit ; Initialize for vlib push hl pop ix ld a,(ix+3) cp 'Z' ; Quick Z-system check jr z,start0 ; Ok ; call sprint db 'Not Z',0 ret ; Quit if not Z ; start0: ld a,(ix+3ah) ; Make sure Z3 allows formfeed ld (isffok),a ; Establish a local flag ld a,(ix+33h) ; Get number of lines for CRT dec a ; Overlap ld (slines),a ; Save text lines ld l,(ix+24h) ; Get efcb address low byte & ld h,(ix+25h) ; high byte ld a,l ; Need to know if there is one or h jr z,noefcb ; No EFCB, use default name ; inc hl ; Point to filename ld (dfname),hl ; Save filename pointer ; ; Check for extended environment ; noefcb: bit 7,(ix+8) ; By testing high bit of ENV+8 jr z,getccp ; No, infer CCP address ; ld l,(ix+3fh) ; Get CCP from environment ld h,(ix+40h) jr gettop ; getccp: ld hl,(1) ; HL=warmboot address ld de,-1603h ; Offset to CCP entry point add hl,de ; HL=CCPaddr ; gettop: ld de,(6) ; Get BDOS or protected RSX address call comphd jr c,savmem ; If no carry, HL (CCPSaddr) is smaller ; ex de,hl ; Else, use DE (BDOSaddr), which is less ; savmem: dec h ; Round down ld l,0 ld (mem),hl ; Save top of available memory ; ld a,(dpage) ; Set screen paging default ld (pflag),a ld a,(drflag) ; Set upcoming reminder default ld (rflag),a ; ld de,fcb1 ; Point to fcb1 ld a,(fcb1+2) ; Check for help request cp '/' jp z,help ; Display help screen ; ld hl,fcb2+1 ; Point to fcb2 filename cp (hl) ; Option request? call nz,prsopt ; Yes, parse options ; ld hl,fcb1+1 ; Point to fcb1 filename cp (hl) ; Empty? jr z,getdef ; Yes, get default filename ld a,'/' cp (hl) ; Option request? jr nz,chkfil ; No, assume filename spec. ; call prsopt ; Parse options ; getdef: ld hl,defdf ; Point to default datafile call fnamz ; Expand default datafile name to fcb ; chkfil: ld a,(de) ; Get fcb drive byte or a ; Current drive? jr z,chkusr ; Yes, test user ; dec a ; Otherwise make rel 0 cp (ix+2ch) ; Compare to ENV max drive jr nc,nodfil ; Must be smaller ; chkusr: ld a,(fcb1+13) ; Get parsed user code cp (ix+2dh) ; Compare to ENV max user jr z,openf ; Equal is OK jr nc,nodfil ; But not larger... ; openf: call z3log ; Log into specified dir: call f$open ; Check for filename jr z,chkclk ; Good open, check for clock ; chktyp: ld a,(fcb1+9) ; Check file type cp ' ' jr nz,nodfil ; Filetype already specified, so quit ; push de ; Save fcb pointer ld hl,deftyp ; Move default filetype ld de,fcb1+9 ; To fcb ld bc,3 ldir pop de ; Restore fcb pointer jr openf ; Try again ; nodfil: call commsg ; Display common prefix and msg db 'datafile ',0 call zprdfn ; Display du:filename.typ ; newline:call sprint ; Common routine to display new line nline: db cr,lf,0 ; And fall thru ; ; Increment line count, check for max, pause if so ; incline:ld a,(pflag) ; Check if we want paging or a ret z ; No, we're done ; ld hl,lines ; Bump counter inc (hl) ld a,(slines) ; Test for max cp (hl) ret nz ; Less than max ; ld a,(sctlfl) ; Get output control flag push af ; Save it xor a ; Reset line counter ld (lines),a call cononly ; Turn printer off call sprint db '[more] ',0 pop af ; Restore output control flag ld (sctlfl),a ; call cin ; Get user input push af ; Save character ld a,cr ; Erase message call cout ; ld b,6 call chkptr ; Check if printer is on line call z,cononly ; Off line call spaces ld a,cr ; Restart the line call sout pop af ; Restore character cp 3 jp z,exit ; Quit if ^C ret ; Else continue ; ; Check for clock, read it ; chkclk: call timini ; Check for clock jr z,noclk ; ld hl,yr ; Read clock into bcd buffer call rclock jr z,clkok ; Store date if good read ; noclk: call commsg ; Display common prefix and msg db 'clock',cr,lf,lf,0 ret ; clkok: ld hl,yr ; Point to bcd buffer ld de,byr ; Point to binary buffer ld b,3 ; Convert bcd date to binary ; binloop:ld a,(hl) ; Get bcd byte call bc2bi ; Make binary ld (de),a ; Save in binary buffer inc hl inc de djnz binloop ; ld hl,($memry) ; Get start of datafile buffer ld (buffer),hl ; Save it ld de,fcb1 ; Point to fcb ; rdfil: call setdma ; Set DMA call f$read ; Read record jr nz,rddun ; Eof ; ld bc,128 add hl,bc ; Bump DMA by one record call memchk ; Check for sufficient memory jr rdfil ; Continue till eof ; rddun: ld (first),hl ; Save start of index ld (order),hl ; And start of order table call index ; Create and sort index call pcheck ; Inititialize printer call chktr ; Check if reminders for today jr nz,tellm ; Yes, continue ; ld a,(rflag) ; Upcoming reminders requested? or a call z,cononly ; Neither, turn off printer & save paper ; tellm: call banner ; Tell'em who we are ld a,(sflag) ; Write sorted file? or a jr z,ddat ; No ; call cononly ; Turn off printer call sprint db 'Writing sorted file ',0 ld b,16 ld hl,defdf ; Display default datafile name call dispfn call newline jp writef ; Go write file ; ; Display calendar and current date ; ddat: call newdisps ; New line, margin call cal ; Display calendar call newline ; New line only ; ld a,(upmo) ; Upcoming month? or a jp nz,upcom0 ; Yes ; call newdisps ; New line, margin call chktr ; Check for today's reminders jr z,norem ; call stndout call sprint db 'R',0 ld a,bell ; Ring console bell call cout jr remmsg ; norem: call sprint ; Tell user there's nothing here db 'No r',0 ; remmsg: call sprint db 'eminders for ',0 ; ld hl,yr ; Point to date call srdat1 ; Display it call stndend ; End standout call newline ; call chktr ; Check for today's reminders jr z,dispw ; If none, check upcoming ; ld hl,(first) ; Point to first index record ; dispt: call tdisp ; Display today's reminders ld a,(useff) ; Check form feed flag or a call nz,sendff ; Send form feed to printer if requested ; dispw: ld a,(rflag) ; Display upcoming reminders? or a ret z ; No, we're done ; dispmo: ld hl,(order) ld de,(end) sbc hl,de ret z ; upcom: call newline ; Make new line and increment line count call newdisps ; Start display call stndout ; Set standout call sprint db '- Upcoming Reminders -',0 call stndend ; upcom0: call newline ; Make new line and increment line count call wdisp ; Display upcoming reminders ; ; Program exit ; exit: ld a,(endff) ; Send printer a form feed on exit? or a call nz,sendff ; Yes, send printer a form feed if on call dinit ; Deinit terminal ld sp,(stack) ; Restore system stack ret ; Back to Z3 ;----------------------------------------------------------------------- ; ; Subroutines ; ; Get contents of hl in hl ; lhlhl: ld a,(hl) ; Get record number inc hl ld h,(hl) ld l,a ret ; ; Create and sort index ; index: ld hl,0 ld (n),hl ; Zero the counter ld hl,(buffer) ; Start at the beginning... ; inxlp: ld a,(hl) ; Get next character cp 1ah ; EOF? jr z,inxsrt ; We're done, so sort index ; ld de,(first) ; Start of index call comphd ; nc if hl(bufptr)=>de(eob) jr nc,inxsrt ; We're done, so sort index ; ; Add new record to index table ; updinx: call movkey ; Add key ; inccnt: push hl ld hl,(n) ; Bump counter inc hl ld (n),hl pop hl jr inxlp ; Repeat until done ; ; Sort index ; inxsrt: ld hl,(order) ; Pointer to end of index table call memchk ld de,ssb ; Pointer to ssb call ssbini ; Create order table jp sort ; Sort index and return ; ; Add new key to index table. ; Entry: HL points to start of buffer line ; movkey: ex de,hl ; DE=buffer pointer ld hl,(order) ; Point to end of index table ld (hl),e ; Save line start address in index table inc hl ld (hl),d inc hl ; Point to date entry push hl ; Save index pointer push de ; Save month pointer ; ld hl,6 ; Offset to year add hl,de ; Year call eval10 ; Convert to binary ld (inxyr),a ; Save year in index buffer ; pop hl ; Restore month pointer call eval10 ; Convert to binary ld (inxmo),a ; Save month in index buffer ; inc hl ; Point to day call eval10 ; Convert to binary ld (inxda),a ; Save day in index buffer ; inc hl ; Point to hour inc hl inc hl call skipsp ; Skip spaces between date and time ; dohr: ld a,(hl) ; Get character call isdigit ; Check for digit jr z,savhr ; Yes ; xor a ; Else zero out rest of temp buffer ld (inxhr),a jr savh ; savhr: call eval10 ; Convert to binary ld (inxhr),a ; Save hour in index buffer ; inc hl ; Point to minute call eval10 ; Convert to binary ; savh: ld (inxmi),a ; Save minute in index buffer ; ; Compare date with today's date, skip this reminder if earlier ; push hl ; Save current buffer pointer ld hl,inxyr ; Get current index pointer ld de,byr ; Point to today's date ld b,3 ; Check date call compb pop hl ; Restore buffer pointer pop de ; Restore index pointer jr c,nosav ; Old, discard it ; ld a,(upmo) ; Check month flag or a jr z,savndx ; Save entry in index ; ld b,a ld a,(inxmo) ; Get entry month cp b ; Specified month? jr z,savndx ; Yes, save it in index ; nosav: pop de ; Discard return address call nxtline ; Get start of next line jp inxlp ; And loop to parse it ; savndx: push hl ; Save buffer pointer ld hl,inxyr ; Start of temp buffer ld bc,6 ; Move date to index ldir ld (order),de ; Save start of next index entry pop hl ; Restore buffer pointer ; ; Scan buffer for start of next text line ; nxtline:ld de,(first) ; End of buffer call comphd ; End? ret nc ; Yes, past end of buffer ; call linend ; Check for end of line inc hl ; Point to next jr nz,nxtline ; Not yet ret ; We're done ; ; Check for end of line. Return Z if so, else return NZ ; linend: ld a,(hl) ; Get character cp lf ; LF? ret z ; Yes, we're done with this line cp 1ah ; EOF? ret nz ; Set flags and return scf ; Set CARRY if no linefeed ret ; ; Check for today's reminders ; chktr: call dcheck ; Locate end of today's reminders ld de,(first) jp comphd ; ; Check for end of today's reminders, save n in (end) ; dcheck: ld hl,(first) ; Start with first index record ld de,byr-2 ld bc,(n) ; dcklp: ld (end),hl ; Save index pointer push bc ; Save pointers push de push hl ld b,3 ; Check for today's date call compd pop hl ; Restore pointers pop de pop bc ret nz ; Not today's date, so quit ; push de ; Save pointer ld de,(size) ; Step to next index record add hl,de pop de ; Restore pointer ld a,b or c jr nz,dcklp ; Loop ret ; ; Check for printer ready, initialize it if so and if requested ; pcheck: ld a,(sctlfl) ; Get output flag and 80h ; Printer output wanted? ret z ; No, quit now ; call chkptr ; Get printer status jr nz,pout1 ; Ok ; call commsg ; Display common prefix and msg db 'printer!',cr,lf,lf,0 ret ; chkptr: ld a,(ptrchk) ; Check bios printer test flag or a jr nz,pout0 ; or 0ffh ; Skip bios test and set good return ret ; pout0: ld a,15 ; Bios list status call bios ; Check for printer ready or a ; Set flag and return ret ; ; Send length-prefixed init string to printer ; pout1: ld hl,pinit ; Point to printer init string ld a,(hl) ; Get length of string or a ret z ; Quit if no string ; ld b,a ; B=length inc hl ; Point to first string byte ; pout2: ld a,(hl) ; Get character inc hl ; Point to next call lout ; Send character to printer djnz pout2 ret ; ; Display upcoming reminders ; wdisp: call updmo ; Update current month ld a,on ; Set upcoming flag ld (today),a ld de,(end) ; Get starting point ld hl,(order) ; Make new ending point ld (end),hl ex de,hl jr dispb ; Do display ; ; Display reminders in sorted order, ending with hl=(end) ; Send to printer if printer option ; Skip date display if today=0 ; Skip a line on change of month ; tdisp: ld hl,(first) ; Point to start of index table ; dispb: ld bc,(n) ; Number of lines ; dloop: ld de,(end) ; Check for end call comphd ret z ; Done ; dloop1: push bc ; Save count push hl ; Save index pointer push hl ; Two copies ; ld a,(oldmo) ; Get previous month ld b,a ; Save it call updmo ; Update current month cp b ; Same? jr z,dloop0 ; Month is unchanged ; call newline ; Make a new line when month changes ; dloop0: pop hl ; Restore index pointer call lhlhl ; Get reminder pointer call rprint ; Display line call incline ; Increment line count pop hl ; Restore index pointer ld de,(size) ; Size of index entry add hl,de ; Point to next index entry pop bc ; Restore count dec bc ; Decrement it ld a,b or c jr nz,dloop ret ; ; Get month from current index entry and save it ; updmo: inc hl ; Point to current month inc hl inc hl ld a,(hl) ; Get current month ld (oldmo),a ; Save as previous month ret ; ; Display reminder line pointed to by HL ; rprint: call margin ; linest: call threesp ; Start each line with 3 spaces ld a,(today) or a call z,skipdt ; rploop: ld a,(hl) ; Get character and 7fh ; Filter hi bit inc hl ; Point to next cp 1 ; Stndout? jr nz,rpt1 call stndout ; Yes jr rploop ; And do next ; rpt1: cp 2 ; Stndend? jr nz,rpt2 call stndend ; Yes jr rploop ; And do next ; rpt2: cp 1ah ; EOF? jr nz,rpt3 ; No ; ld a,cr ; User forgot eof crlf call sout ld a,lf ; rpt3: call sout ; Send character cp lf ; End of line? jr nz,rploop ; No, do next character ret ; Yes, we're done ; ; Display new line, margin, three spaces ; newdisps: call newdisp ; And fall thru ; ; Display 3 spaces ; threesp:ld b,3 ; ; Display B number of spaces ; spaces: ld a,' ' ; splp: call sout djnz splp ret ; ; Display space, saving AF ; space: push af ld a,' ' call sout pop af ret ; ; Display trailing message on console only ; cprint: call cononly jr sprjmp ; ; Display 'No' prefix and trailing message ; commsg: call cprint db bell nomsg: db 'No ',0 sprjmp: jp sprint ; ; Set output to console only ; cononly:ld a,1 ld (sctlfl),a ret ; ; Start new display ; newdisp:call newline ; And fall thru to add printer margin ; ; If printer output, send spaces to printer for left margin ; margin: ld a,(sctlfl) ; Check for printer output and 80h ret z ; No margin requirements ; ld a,(lmarg) ; Get count ld b,a ; In b or a ret z ; Quit if none ; ld a,' ' ; margl: call lout djnz margl ret ; ; Send form feed to printer ; sendff: ld a,(sctlfl) ; Get output flag and 80h ; Printer? ret z ; No, quit now ; ld a,(isffok) ; Make sure Z3 approves or a ret z ; No ; ld a,ff ; Yes, send form feed jp lout ; ; Skip date entry in reminder line, start with time ; skipdt: inc hl ld a,(hl) cp ' ' jr nz,skipdt ; ; Skip spaces starting with current HL pointer ; skipsp: inc hl ; At least one space ld a,(hl) cp ' ' ret nz ; HL points to next non-space character jr skipsp ; ; Create and write new sorted file ; writef: ld hl,(first) ; Point to start of index ld de,(order) ; Point to order table inc d ld e,0 ; Start of file buffer ld (wbuff),de ; Save it ld bc,(n) ; Number of entries ; buflp: push bc ; Save counter push hl ; Save index pointer call lhlhl ; HL=buffer pointer ; linlp: call linend ; Check for end of line ldi ; Move character to new buffer jr nz,linlp ; Not end of line, so loop jr nc,lindun ; addnl: ld hl,nline ; Add missing CR,LF to buffer ldi ldi ; lindun: ex de,hl call memchk ex de,hl pop hl ; Restore index pointer ld bc,8 add hl,bc ; Point to next index entry pop bc ; Restore counter dec bc ; One more line done ld a,b ; End? or c jr nz,buflp ; No, do next entry ; push de ; Save end of buffer ld hl,(wbuff) ; Get start of buffer ex de,hl ; HL=end, DE=start sbc hl,de ; HL=buffer length xor a ld de,80h ; Record size in DE ld b,a ; Init counter to 0 ld c,a ; divide: sbc hl,de inc bc jr nc,divide ; wrbuf: add hl,de ld a,l ; Even number of records? or h jr nz,wrb0 ; No, pad ; pop de ; Discard buffer end dec bc ; Yes, adjust number of records jr wrb1 ; And skip pad ; wrb0: ex de,hl sbc hl,de ; Length to pad ld b,l ; Fill remainder of record pop hl ; Buffer end ld a,01ah ; EOF ; ; Pad remainder of record with EOF characters ; call hfilb ; ; Write buffer to temporary sort file ; wrb1: ld hl,sortfn ; Point to sort filename ld de,sortfcb ; Point to fcb call fnamz ; Parse filename to fcb call f$make ; Make new one, deleting any previous file inc a ; Check for error jr z,dirful ; Directory full ; ld hl,(wbuff) ; Buffer start ld b,c ; Record count in B ; wrfil: push bc ; Save counter call setdma ; Set DMA call f$write ; Write record jr nz,wrterr ; Error ; ld bc,128 add hl,bc ; Bump DMA by one record pop bc ; Restore counter djnz wrfil ; Loop till all records written ; call f$close ; Close file ; ; Delete old backup file ; ld hl,backup ; Point to backup filename ld de,bakfcb ; Point to fcb call fnamz ; Parse filename to fcb call f$delete ; Delete it ; ; Rename current file to backup ; ld hl,bakfcb ld de,fcb1 call f$rename ; ; Rename temporary file to current ; ex de,hl ; hl = fcb1 ld de,sortfcb jp f$rename ; dirful: call cprint db 'Directory full',bell,0 ret ; wrterr: call cprint db 'Write error',bell,0 ret ; ; Compare DE.vector to HL.vector for B bytes ; Return C if DE.vector < HL.vector ; compv: ld b,5 ; compd: ex de,hl inc de ; Skip record address inc de inc hl ; Skip record address inc hl call compb ex de,hl ret ; ; Check if HL is less than top of memory address, return ; memchk: push de ex de,hl ld hl,(mem) call comphd ex de,hl pop de ret nc ; call cprint db 'TPA too small!',bell,cr,lf,lf,0 jp exit ; ; Parse option characters ; prsopt: inc hl ; Point to next option character ld a,(hl) ; Get option character and parse it cp ' ' ; End? ret z ; No more options ; prsop1: cp 'D' ; Page screen jr z,pdflag cp 'S' ; Write sorted file? jr z,ssflag cp 'P' ; Print reminders? jr z,spflag cp 'U' ; Reminder display toggle? jr z,srflag call isdigit ; Check for specified month jr nz,prsopt ; Bad options, skip it ; getmo: push de call eval10 ; Convert to binary pop de dec hl or a jr z,prsopt ; Too small cp 13 jr nc,prsopt ; Too large ld (upmo),a ; Month, save it jr srf0 ; And set upcoming ; srflag: ld a,(rflag) ; Toggle upcoming reminder flag cpl ; srf0: ld (rflag),a jr prsopt ; ssflag: ld (sflag),a ; Set sorted file flag jr prsopt ; spflag: ld a,81h ; Console+printer ld (sctlfl),a ; Set printer flag jr prsopt ; pdflag: ld a,(pflag) ; Toggle screen paging flag cpl ld (pflag),a jr prsopt ; ; Display calendar with current day highlighted ; cal: ld hl,yr ; Point to clock buffer ld de,inxyr ; Point to temporary buffer push de ld bc,6 ldir pop de ; Point to temp clock buffer ; ld a,(upmo) ; Check for specific upcoming month or a jr z,cal0 ; No, use current month ; inc de ; Point to month call bi2bc ; Convert month to bcd ld (de),a ; Save it dec de ; Point to year ld hl,mo ; Point to current month cp (hl) ; Compare to current month jr nc,curyr ; Upcoming month, use current year ; ld a,(de) ; Get current year inc a ; Increment it daa ld (de),a ; Save it ; curyr: ld a,1 ld (inxda),a ; Set the first of the month ; cal0: push de ; Save pointer call mont ; Get pointer to month string call disphdr ; Display month, year and header call newdisps ; New line, margin call sprint db 'Sun Mon Tue Wed Thu Fri Sat',0 call newdisps ; New line, margin call space ; One more space for calendar lines ; pop de ; Restore clock buffer pointer ld a,(inxda) ; Get day push af ; Save it ld a,1 ; First of the month ld (inxda),a call mont ld c,b ; Number of days in month call date ; Day of week for first day in B pop af ; Restore day ld (inxda),a ; ; Determine where to start calendar ; ld a,b ; Day of week (0-6) or a ; Sunday? jr nz,notsun ; ld b,7 ; It's sunday, so we'll have seven days jr dspcal ; In the first week of the month ; notsun: ld b,a ; Pad with blank spaces before day 1 push bc ; Save day of week for day 1 ; spdlp: push bc ld b,4 call spaces ; Spaces per date pop bc djnz spdlp ; pop bc ; Restore day of week ld a,7 ; Get number of days in first week sub b ld b,a ; B = number of days in first week ; ; Display calendar ; dspcal: xor a ; Initialize day push af ; Put it on stack ld d,a ; Set standout off ; wklp: pop af inc a ; Display a week ld hl,bda ; Point to binary current cp (hl) ; Check for today jr nz,cday ; No ; ; Set standout for current day if not specific upcoming month ; push af ; Save day ld a,(upmo) ; Check for specific upcoming month or a jr nz,sox ; Upcoming, don't highlight current day ; inc d ; Turn on standout for current day ; sox: pop af ; Restore day ; cday: call xadc ; Display day, turn off standout push af ; Save day push bc ld b,2 call spaces ; Space to next day pop bc dec c ; Decrement number of remaining days xor a ; Quit at end of month cp c jr z,cdun ; djnz wklp ; Loop until whole week is displayed ; call newdisps ; Advance to the next week call space ; One more space for calendar lines ld b,7 ; Initialize days in week jr wklp ; ; Display A as 2 decimal characters, with leading space if req'd ; D=0 for no standout, D=NZ for standout ; xadc: push af ; Save A push bc ; Save registers ; xadc1: ld b,10 ; Print tens ; ; Display result of A divided (Integer) by B with leading space ; xac: ld c,0 ; Set count ; xacl: sub b ; Compute count jr c,xacd ; inc c ; Bump count jr xacl ; xacd: add a,b ; Add B back in ld e,a ; Save A ld a,c ; Get count or a ; Zero? jr nz,xacd1 ; call space jr xacdun ; xacd1: xor a cp d call nz,stndout ; Set standout if D is NZ ; ld a,c ; Get count add '0' ; Convert to decimal call sout ; Print it ; xacdun: xor a cp d call nz,stndout ; Set standout ld a,e ; Restore a add '0' ; Convert to ascii call sout ; Print call stndend ld d,0 ; Reset standout flag pop bc ; Restore registers ; cdun: pop af ret ; ; Display month and year ; disphdr:call stndout push bc ld b,23 ; hdrlp: ld a,(hl) ; Get month character inc hl or a jr z,padsp ; Done here ld c,a ; Save character sub 'a' ; If character is lower case cp 'z'-'a'+1 ; set C, else NC sbc a,a ; Carry into A and 'a'-'A' ; Difference between upper and lower case xor c ; Convert to upper case call sout ; Display it djnz hdrlp ; Do next ; padsp: call spaces ; Pad to position of year display ld de,inxyr call year ; Get year and display it ld a,h call xadc ld a,l ld d,a ; Set standout call xadc pop bc ret ; ; Initialized data area ; dfname: dw defnam ; Default filename deftyp: db 'REM' ; Default filetype $memry: ds 2 ; Filled by linker ; ; Sort Specification Block for use with SORT ; ssb: first: dw 0 ; Address of the first record n: dw 0 ; Number of records size: dw 8 ; Length of each record comp: dw compv ; Address of our compare routine order: dw 0 ; Address of the order table point: db on ; ON to use pointers norec: db 0 ; ON to only sort pointers ; sortfn: db 'SORT.$$$ ' ; Temporary sort file filename ; ; Uninitialized data area ; dseg data: pflag: ds 1 ; NZ to page screen display sflag: ds 1 ; NZ to write new sorted file rflag: ds 1 ; NZ to display upcoming reminders end: ds 2 ; Index quitting point for display today: ds 1 ; OFF if displaying today's reminders oldmo: ds 1 ; Last month displayed upmo: ds 1 ; Display upcoming for this month lines: ds 1 ; Display line count slines: ds 1 ; Max number of text lines isffok: ds 1 ; buffer: ds 2 ; Start of datafile buffer bufend: ds 2 ; End of datafile buffer wbuff: ds 2 ; Start of new sorted file buffer mem: ds 2 ; Top of available memory ; ; Current system date in BCD ; yr: ds 1 ; BCD year mo: ds 1 ; BCD month da: ds 4 ; BCD day, etc ; ; Current system date in binary ; byr: ds 1 ; Binary year bmo: ds 1 ; Binary month bda: ds 4 ; Binary day, etc ; inxyr: ds 1 ; Temporary index date/time buffer inxmo: ds 1 inxda: ds 1 inxhr: ds 1 inxmi: ds 2 ; sortfcb:ds 36 ; Sorted file FCB bakfcb: ds 36 ; Backup file FCB ; datalen equ $-data ds 48 ; Local stack stack: ds 2 ; System stack pointer end