; Program : VCOMP Z-TOOL - COMPARE TWO TEXT FILES ; Usage : VCOMP [DU:] FILE1 [DU:] FILE2 ; Date : 10/15/87 ; Author : Rob Friefeld ; Assembly: SLR assembler and linker ; Copyright 1987 by Rob Friefeld, 4607 Colorado St., Long Beach, CA 90814 ; Requires Z3TCAP, screen at least 80 x 24, cursor addressing. ; Version 1.3 ; - Fixed known bugs in READ and LIST commands. ; - When reading more of a file, keepthe last screen for overlap. ; - Reorganization of code gets program down to 4k ; - Option to use hard coded Wyse compatible CRT protocol instead of VLIB ; - Top of memory routine allows for RSX. ; Version 1.2: ; Bug: Could use column 80 causing a on some terminals. Now stops at 79. ; - permit syntax: "vcomp file1 du:" to compare same file in different du: ; If one file is in default du:, it must be named first. ; e.g. VCOMP TEST.FIL B1: ; Version 1.1 Revisions: ; - clear screen on exit ; - echo status doesn't get lost when going to full screen and back ; - if file2 not specified on command line, file1 is repeated ; - scrolling has one line of overlap (patchable option) ; - tab expansion is 8 vers equ 13 ; Version number true equ -1 false equ 0 hlpdoc equ true ; include help screen lstok equ true ; keep listing options hardvid equ false ; use Wyse compatible routines instead of VLIB initsz equ 16 ; Maximum length of printer init string ; ; LIBRARY ROUTINES ; .request vlib,z3lib,syslib ; VLIB ext z3vinit if [not hardvid] ext tinit,dinit,stndout,stndend,at,cls,ereol endif ; Z3LIB ext getvid,getcrt,wait1s ; SYSLIB ext $MEMRY ; ; PROGRAM EQUATES ; fstring equ 20 ; max length of FIND string bdos equ 5 fcb equ 5ch fcb2 equ 6ch ; BDOS FUNCTIONS rdconf equ 1 wrconf equ 2 ; Character from E to screen listf equ 5 ; Character from E to list dirconf equ 6 ; Direct console i/o readst equ 10 ; Read string breakf equ 11 ; Break function openf equ 15 ; Open file readf equ 20 ; Read file sequential setdmaf equ 26 ; Set DMA address ; ASCII bell equ 7 bs equ 8 tab equ 9 lf equ 0ah cr equ 0dh esc equ 1bh eof equ 1ah dim equ 1 bright equ 2 tabsize equ 8 ovrlap equ 1 ; Scroll overlap lines ; ; Flag testing macros ; echo? macro ld a,(eflag) or a endm file? macro ld a,(sflag) or a endm window? macro ld a,(wflag) or a endm ; ; START OF PROGRAM ; ; jp start ; Supplied by linker db 'Z3ENV' ; Z-tool header db 1 z3eadr: dw 0fe00h ; Installed by Z3INS if lstok lstini: db 1 ; Printer initialization : # of bytes db cr ; Bytes, 16 max ds [initsz+1] - [$-lstini] endif ; ; BEGINNING OF PROGRAM CODE ; start: ld (stksav),sp ; Set up local stack ld sp,stack ; ENV INITIALIZATION ld hl,(z3eadr) ; Initialize vlib routines call z3vinit call GETVID jp z,novid ; Exit with message if no TCAP support call GETCRT ld a,(hl) cp 80 jp c,novid dec a ld (width),a ; Save useable line length inc hl ld a,(hl) cp 24 jp c,novid call TINIT ; INIT POINTER TABLES ld b,stksav-ptrbuf ld hl,ptrbuf call zfill ; SET UP BUFFER SPACES call topram ; Get top page of free ram in A ld (top2),a ; Top of text2 ld hl,($MEMRY) ; Get end of code inc h ; Assure page boundary ld l,0 ld (txt1),hl ; First buffer at end of code inc h ; Round up top of code high byte sub h ; Buffer space srl a ; Halve it add h ; Start of text2 buffer ld (top1),a ld (txt2+1),a ; High byte, same as top1 xor a ; Low byte = 00 ld (txt2),a ; SET UP FCB's call filspecs ; Which files were specified ; Save FCB's ld hl,fcb ; File1 ld de,fcb1buf ld bc,10h ldir ld a,(fcb+13) ld (usr1),a ld hl,fcb2 ; File2 ld de,fcb2buf ld bc,10h ldir ld a,(fcb2+13) ld (usr2),a ; READ IN TEXTS ld hl,(txt1) ld (txtloc),hl ld a,(top1) ld (topmem),a ld a,(usr1) ld (usr),a call rfile ; Load text1 call sw0 ; Switch to file2 call rfile call sw0 ; Back to file1 ; ; DISPLAY INITIAL SCREEN ; scrn1: call CLS call prnscr ; Print the first screen of text1 window? jp nz,what call divide ; Print the divider ld a,(eflag) call echo1 ; Print echo status call sw0 call prnscr ; Screen of text2 call sw0 ; Back to text1 jp what ; Display file names ; SET CURSOR AT SELECTED FILE comcrs: file? push af call z,end1crs pop af call nz,retcrs ld a,(cmdflag) ; Is there a command pending? or a jr z,command ; There isn't. Go get one. xor a ; Reset flag ld (cmdflag),a ld a,(comchr) ; Recover command char jr clist ; And do it ; ; COMMAND INPUT ROUTINE ; command: ; Command input routine call getc ; Get command clist: call upcase call case ; Scan following command list db 'A' ; End of file dw last db 'D' ; Forward a line dw down db 'E' ; Echo command to both screens dw echo db 'F' ; Next screen dw next db 'G' ; Find dw dfind db 'H' ; Repeat find, same string dw dfind0 if lstok db 'I' ; Initialize printer dw linit endif db 'J' ; Previous screen dw prev db 'K' ; Back a line dw up db 'L' ; Back 5 lines dw dblup db 'O' ; Mark beginning of block dw mark if lstok db 'P' ; List from mark to cursor dw list endif db 'Q' ; Select character to find for re-sync dw setsync db 'R' ; Read more (if file was too big) dw read db 'S' ; Forward 5 lines dw dbldown if lstok db 'T' ; Type a line on printer dw type endif db 'U' ; Re-sync (sets both files to next line with dw sync ; selected character) db 'W' ; Toggle single/double file display dw window db 'X' ; Exit dw exit0 db 'Y' ; Auto compare, go to next differnce dw auto db ';' ; Top of file dw top db 20h ; switch files dw switch db cr ; Forward screen both files dw next2 db '0' ; Go to block marker dw gomark if hlpdoc db '/' dw help db '?' dw help endif db 0 ; Table delimiter jp comcrs ; Loop back on invalid input ; ; PRINT ONE SCREEN OF SELECTED TEXT ; prnscr: file? ; 0 - file1 / ff - file2 push af call z,homcrs pop af call nz,top2crs ld hl,(srtptr) push hl ; If near end then print entire last screen ld de,(eosptr) ; Compute position relative to last screen xor a ; Reset carry flag sbc hl,de pop hl jr z,prn1 ; We are at or before last screen so go ahead jp nc,last0 ; We are past last screen so back up prn1: ld a,(scrlns) ld b,a ; Line count in B prnlp1: call clreol call prnline djnz prnlp1 ; Print SCRLNS lines ret ; ; Print one line of text. Return HL -> next line of text. ; prnline: push bc ; Preserve whatever is here ld c,0 ; Char counter prnl1: ld a,(hl) cp eof jr z,prnl2 ; Can occur on text smaller than one screen call prnl3 cp lf ; Are we at end of line? inc hl jr nz,prnl1 ; No prnl2: pop bc ret prnl3: cp cr jp z,conout cp lf jp z,conout cp tab jr z,prnl5 prnl4: ld e,a inc c ld a,(width) cp c jr c,prnl6 ld a,e jp outchr prnl5: ld a,c sub tabsize jr nc,$-2 neg ld b,a ld a,' ' prnl51: call prnl4 ret c djnz prnl51 ret prnl6: push af call print db 1,'>',bs,2,0 pop af ret ; TOGGLE ECHO STATE echo: window? jr nz,echox ; Disable function ld a,(eflag) ; Toggle echo flag cpl ld (eflag),a call echo1 echox: jp comcrs echo1: or a ; Print reminder push af call AT db 12,72 pop af jr z,echoff call print db 1,' ECHO ',2,0 ret echoff: call print db '======',0 ret ; NEXT SCREEN next: call next0 ; Print next screen echo? ; In ECHO mode? jr z,nextx ; No, quit next1: call sw0 ; Switch and advance other screen call next0 call sw0 nextx: jp comcrs next0: call nxtscr ; Set start to top of next screen jp prnscr next2: ; Double next without echo flag check window? call z,next0 jr next1 nxtscr: ld b,ovrlap ; Lines to overlap ld a,(scrlns) ; Count scrlns lines ahead, set pointer sub b ; minus overlap ld b,a call dnline djnz $-3 ret ; PREVIOUS SCREEN prev: call prev1 echo? jr z,prevx call sw0 call prev1 call sw0 prevx: jp comcrs prev1: ld hl,(srtptr) ; Print previous screen ld b,ovrlap ; Lines to overlap ld a,(scrlns) sub b ld b,a prev0: call pvline ; Count back SCRLNS - Overlap lines djnz prev0 ld (srtptr),hl ; Set Start Pointer jp prnscr ; FIRST SCREEN top: call top0 echo? jr z,topx call sw0 call top0 call sw0 topx: jp comcrs top0: ld hl,(txtloc) ; Print first page ld (srtptr),hl jp prnscr ; LAST SCREEN last: call last0 echo? jr z,lastx call sw0 call last0 call sw0 lastx: jp comcrs last0: ld hl,(eosptr) ; Print last page ld (srtptr),hl ; Start at end of text jp prnscr ; DOWN A LINE down: ld b,1 down1: push bc call dnline djnz $-3 call prnscr pop bc echo? jr z,downx call sw0 call dnline ; Print next line djnz $-3 call prnscr call sw0 downx: jp comcrs dbldown: ld b,5 jr down1 dnline: ld hl,(srtptr) call nxline ld (srtptr),hl ret nxline: ld a,(hl) ; Search for next line of text cp eof ret z inc hl cp lf jr nz,nxline ; or 0ffh ; Return Z = EOF else NZ ret ; Returns HL at character after LF ; UP A LINE up: ld b,1 up1: push bc call upline djnz $-3 call prnscr pop bc echo? jr z,upx call sw0 call upline djnz $-3 call prnscr call sw0 upx: jp comcrs dblup: ld b,5 jr up1 upline: ld hl,(srtptr) ; Back up a line call pvline ld (srtptr),hl ; Set pointer ret pvline: push bc ; Search for previous line of text ld b,2 ; We need the LF BEFORE the last one ld a,(hl) ; These four instructions for case of LF,LF,LF cp lf jr nz,prvlp dec hl prvlp: xor a ; Reset carry flag ld de,(txtloc) ; Are we already at beginning of file? push hl sbc hl,de pop hl jr c,prv0 ; Yes, so we are done ld a,(hl) ; Look for last LF cp lf dec hl jr nz,prvlp djnz prvlp ; Do it once more inc hl ; Move HL pointer to character after LF prv0: inc hl pop bc ret ; FIND NEXT SYNC CHARACTER IN BOTH TEXTS sync: ; Auto find next label window? jr nz,syncx ; Disable function ld hl,finbuf+1 ; Save current find string ld de,syncbuf ld bc,fstring+1 ldir ld hl,finbuf+1 ; Load buffer char (':' default) ld (hl),1 inc hl ld a,(synchr) ld (hl),a call find0 ; Find it jr z,sync1 ; Didn't find it call sw0 ; Do it for other file call find0 call sw0 sync1: ld hl,syncbuf ; Restore find buffer ld de,finbuf+1 ld bc,fstring+1 ldir syncx: jp comcrs syncbuf: ds fstring+2 ; SET UP A SYNC CHARACTER setsync: call retcrs call print db 1,'Sync Char {follow with }-> ',2,0 call getc set1: ld (synchr),a ; Save it call pctl ; Display it call getc ; next? cp cr jr nz,set1 ; No, keep looking call clrln setx: jp comcrs synchr: db ':' ; Default will jump to next label ; SET THE TEXT MARKER mark: ; Set text marker call mark0 echo? jr z,markx call sw0 call mark0 call sw0 markx: jp comcrs mark0: call retcrs call print db 1,'Marker Set ',2,bell+80h call wait1s call clrln ld hl,(srtptr) ld (mrkptr),hl ret ; GO TO THE TEXT MARKER gomark: ; Go to text marker call gomark0 echo? jr z,gomarkx call sw0 call gomark0 call sw0 gomarkx: jp comcrs gomark0: ld hl,(mrkptr) ld (srtptr),hl jp prnscr ; AUTO COMPARE THE TEXTS, STOP AT FIRST DIFFERENCE auto: ; Find next difference between texts window? jp nz,compx ; Disable function call sw0 file? push af call nz,sw0 ld hl,(srt2) call nxline ex de,hl ; de -> start of file2 next line ld hl,(srt1) call nxline ; hl -> start of file1 next line compare: ld a,eof cp (hl) jr z,comp0 ex de,hl cp (hl) ex de,hl jr z,comp0 ld a,(de) cp (hl) jr nz,comp1 ; Found a difference inc de inc hl jr compare comp0: call retcrs call clrln call print db 1,'EOF ',2,bell+80h ; No difference call getc call clrln jr comp3 comp1: push de call pvline call nxline ld (srt1),hl pop hl call pvline call nxline ld (srt2),hl ld hl,(srt1) comp2: ld (srtptr),hl comp3: call prnscr call sw0 call prnscr pop af call nz,sw0 compx: jp comcrs ; FIND A STRING dfind: ; Double find call find df0: echo? jr z,dfx ; If no echo, then done df1: call sw0 call find0 ; Find same string call sw0 dfx: jp what dfind0: call find0 jr df0 find: call retcrs call cr$clr call print ; Find string in following pages db 1,'Find ->',' '+80h ld de,finbuf ; Read string to find ld c,readst call bdos call stndend call clrln ; Erase it from screen find0: ld ix,finbuf+1 ; IX points to string length ld a,(ix) or a jp z,finret ; 0 length string ... abort find1: ld b,a ; Upcase string ld hl,findat find11: ld a,(hl) call upcase ld (hl),a inc hl djnz find11 ld hl,(srtptr) ; Start search at next line call nxline finlp: ld iy,findat ; IY points to char string to match finlp1: ld a,(hl) call upcase cp eof jr z,finot ; Hit end of file before match cp (iy) inc hl jr nz,finlp1 ld b,(ix) ; At this point, first char is matched dec b jr z,findex ; Done if only 1 char to match finlp2: inc iy ; Compare the next chars ld a,(hl) call upcase cp (iy) jr nz,finlp ; No match ... start looking again inc hl ; So far, so good djnz finlp2 ; Match next chars findex: call pvline ; Find previous line call nxline ; Go to beginning of this line ld (srtptr),hl call prnscr jp finret ; Exit finot: call retcrs call clrln ; String not found - print message call stndout ld hl,finbuf+1 ld b,(hl) finot0: inc hl ld a,(hl) call pctl djnz finot0 call print db ' ??',' '+80h call stndend call getc call clrln xor a ; Return Z = NOT FOUND ret finret: or -1 ; Return NZ = OK ret finbuf: db fstring ; String to match, max = 20 characters ds 1 ; Returned char count findat: ds fstring ; Buffer ; ; SWITCH TO OTHER FILE ; switch: call sw0 call prnscr window? jp nz,what1 switx: jp comcrs ; Switch pointers without print affecting display sw0: push bc file? ; 0 = file1, ff = file2 jr nz,sw2 sw1: ld hl,srtptr ; Save current pointer table ld de,srt1 call movptr ld hl,srt2 ; Load other pointer table ld de,srtptr call movptr ld hl,fcb ; Save current FCB ld de,fcb1buf call movfcb1 ld hl,fcb2buf ; Load other FCB call movfcb or 0ffh ; Change flag jr swex sw2: ld hl,srtptr ld de,srt2 call movptr ld hl,srt1 ld de,srtptr call movptr ld hl,fcb ld de,fcb2buf call movfcb1 ld hl,fcb1buf call movfcb xor a swex: ld (sflag),a pop bc ret ; TOGGLE WINDOW STATE window: ld a,(sflag) ; Preserve file flag ld (wsave),a or a jr z,wind11 call sw0 ; Force file1 wind11: ld hl,(eosptr) ; Get eos pointer ld a,(wflag) ; Toggle window flag cpl ld (wflag),a or a jr z,windoff windon: ld a,23 ; Full screen ld (scrlns),a ld a,(eflag) ld (esave),a ; Save echo flag state xor a ld (eflag),a ; No echo call wind1 ; Reset last screen pointers ld (eosptr),hl call sw0 ; Force file2, save file1 pointers ld hl,(eosptr) call wind1 jr windex windoff: ld a,11 ; Half screen ld (scrlns),a ld a,(esave) ; Restore echo flag state ld (eflag),a call wind2 ld (eosptr),hl call sw0 ld hl,(eosptr) call wind2 windex: ld (eosptr),hl call sw0 ; Save changed file2 ptr ld a,(wsave) ; Where were we? ld b,a ld a,(sflag) ; Where are we now? cp b jr z,wind0 ; In same place call sw0 ; Back to original file wind0: jp scrn1 wind1: ld b,12 call pvline djnz $-3 ret wind2: ld b,12 call nxline djnz $-3 ret wsave: ds 1 esave: ds 1 ; ; LISTING FUNCTIONS ; if lstok ; LIST MARKED BLOCK list: call lst$on ; On first call, is printer on? call print db 1,'Printing ... ',2,0 ; Compute block size ld de,(mrkptr) ; Beginning of block ld hl,(srtptr) ; Find bottom of screen ; ld b,ovrlap ; Lines to overlap ld a,(scrlns) ; Count scrlns lines ahead, set pointer ; sub b ; minus overlap ld b,a call nxline djnz $-3 ; On exit, HL -> start of next screen list1: xor a sbc hl,de ; Block size now in HL jr c,listx ; If beginning at or after end then jr z,listx ; Abort ; Send text out ex de,hl ; Load block size into DE byte counter ld hl,(mrkptr) ; Beginning address in HL pointer call lst$out listx: ld a,bell call conout call clrln jp comcrs ; INIT PRINTER linit: call lst$on ; Warn user to turn on printer ld hl,lstini ; Send printer initialization string ld e,(hl) ; String begins with character count ld d,0 inc hl call lst$out linitx: jp comcrs ; The first time called, check printer on lst$on: call retcrs call clrln ld a,(lstflg) or a ret nz call print db 1,'Printer on? (N=ABORT) ',2,bell+80h call getc and 5fh cp 'N' jr z,lbrkx call clrln ld a,0ffh ld (lstflg),a ret lstflg: db 0 ; SEND BLOCK TO PRINTER ; HL -> start DE = char counter lst$out: push de push hl ld e,(hl) call lst$f call lbreak pop hl pop de inc hl dec de ld a,e or d jr nz,lst$out ret lst$f: ld c,listf jp bdos ; Permit aborting loop with ^C or ESC lbreak: ld c,breakf ; Check for key pressed call bdos or a ret z ; No key -> continue printing ld c,rdconf ; Fetch the char call bdos cp 3 jr z,lbrkx cp esc jr z,lbrkx ret lbrkx: ld sp,stack ; Reset stack (dispose of ret and pushes) call clrln jp comcrs ; GET A LINE AND PRINT IT type: call lst$on call cr$clr call print ; Type a line on printer db 1,'Type ->',' '+80h ld hl,tbuf ld (hl),80 ex de,hl ld c,readst call bdos ld hl,tbuf+1 ; Contains returned character count ld e,(hl) xor a ; Zero A ld d,a or e jr z,tex ; If there was no input, just send CRLF inc hl call lst$out ; Send the line out tex: ld e,cr ; Send a terminating CR,LF call lst$f ld e,lf call lst$f call stndend call cr$clr ; Clear the command line jp what tbuf: db 75 ; Buffer for returned line ds 76 endif ; lstok ; ; File Manipulation ; ; Check command line specs filspecs: ld a,(fcb+1) ; Reject blank file spec cp ' ' jp z,nope cp '/' jp z,nope ld hl,fcb+1 ; Reject ambiguous file spec call ambig ld hl,fcb2+1 call ambig ld a,(fcb2+1) ; Was second file name specified? cp ' ' ret nz ; Yes fils1: ld hl,fcb+1 ; Copy 1st file name ld de,fcb2+1 ld bc,11 ldir ld a,(fcb) ; If 1st d: default, leave 2nd d: alone or a ret z ld (fcb2),a ; If not, copy to 2nd du: ld a,(fcb+13) ld (fcb2+13),a ret ; Scan for ambig filspec ambig: ld bc,11 ld a,'?' cpir jp z,nope ret ; Set user from USR setusr: ld a,(usr) ld e,a ld c,32 ; Select the new user code jp bdos ; ; Read file in fcb ; getfil: ld de,fcb ; Open the file ld c,openf call bdos cp 0ffh ld hl,fcb jp z,nofile ; Open fails xor a ld (eoflag),a ; 0 = EOF not encountered. ld hl,(txtloc) ; Place to put text getlp1: ld (txtptr),hl ; Read text 128 byte record at a time ld a,(topmem) ; Have we reached top page of available memory? cp h jr z,toobig ; If yes, quit and mark end of text ex de,hl ld c,setdmaf ; File read into current position call bdos ld de,fcb ld c,readf call bdos or a ; Check for end of file encountered jr nz,geteof ; Yes ld hl,(txtptr) ; Move pointer along one record worth ld de,128 add hl,de jr getlp1 geteof: ld (eoflag),a ; Note EOF reached. ld hl,(txtptr) ; Eof not returned until read after eof! ld de,-128 add hl,de ; Back up a record ld a,eof ld bc,128 cpir ; Find the first eof dec hl getmrk: ld (hl),eof ld (eofptr),hl ; Store it for later call msbmask call seteos ret toobig: push hl ld hl,fcb call pfil call print db ' - Memory full ',bell+80h call WAIT1S call clrln pop hl dec hl ld a,(hl) ; Save last char ld (lastchr),a jr getmrk msbmask: ld hl,(txtloc) msb1: ld a,(hl) cp eof ret z and 7fh ld (hl),a inc hl jr msb1 ; ; Read more file ; read: ld a,(eoflag) ; Has all of file1 been read? or a jr nz,reread ; Yes read1: call rfile ; Read in some more call prnscr readx: jp comcrs reread: call retcrs call clrln call print db 1,'No more to read. Start over? (y/N) ',2,0 call getc and 5fh cp 'Y' push af call clrln pop af jr nz,readx ; Start over not wanted call zbuf xor a ld (rflag),a jr read1 rfile: call setusr ; Set user ld hl,(txtloc) ld (txtptr),hl ld (mrkptr),hl ld (srtptr),hl ld a,(rflag) ; Has file been opened? or a jp z,getfil ; No, start over ; Move last screen of text up to top of buffer movscr: ex de,hl ; Text pointer to DE ld hl,(eosptr) movscr1: ldi ld a,(hl) cp eof jr nz,movscr1 ld a,(lastchr) ld (de),a inc de ex de,hl jp getlp1 ; Read the file into memory ; ; Zero control bytes of fcb ; zbuf: ld hl,fcb+12 ld b,24 zfill: ld (hl),0 inc hl djnz $-3 ret ; ; Set final pointers after file read ; seteos: ; Set Start Pointer to beginning of file ld hl,(eofptr) ; Set End of Screen Pointer to beginning ld a,(scrlns) ; Of last screen ld b,a srt0: call pvline ; Back up one screen from end djnz srt0 ld (eosptr),hl ; Now set pointer or -1 ld (rflag),a ; Indicate file opened ret ; ; Display file names ; what: ; Print file names window? jr nz,what1 ld a,(usr) ; Save user # push af call AT ; Place cursor db 24,43 call stndout ld hl,fcb1buf ; Print file1 name ld a,(usr1) ld (usr),a call pfil call print ; Print file2 name db ' / ',0 ld hl,fcb2buf ld a,(usr2) ld (usr),a call pfil pop af ld (usr),a what0: call stndend whatx: jp comcrs what1: call AT db 24,43 call ereol call stndout file? jr nz,what2 ld hl,fcb1buf jr what3 what2: ld hl,fcb2buf what3: call pfil jr what0 ; ; Print file name pointed to by pfcb ; pfil: call pdsk ; Print du:file.typ call pusr ld a,':' call conout jr pfn pdsk: push hl ld a,(hl) cp 0 jr nz,pdsk0 ld c,25 call bdos inc a pdsk0: add a,'A'-1 call conout pop hl ret pusr: ld a,(usr) pusr02: cp 10 jr c,pusr0 ld b,0 pusr1: sub 10 inc b cp 10 jr nc,pusr1 push af ld a,'0' add b call conout pop af pusr0: add a,'0' jp conout pfn: ld b,8 ; Print file name inc hl call pfn0 push hl ld a,'.' call conout pop hl ld b,3 pfn0: ld a,(hl) cp ' ' jr z,pfn1 call conout pfn1: inc hl djnz pfn0 ret ; ; Utilities ; outchr: ; Displays control characters cp 20h jr nc,conout ; Not a control inc c ; Bump char counter in c for '^' display pctl: ; Print controls in stndout cp 20h jr nc,conout push af call stndout ld a,'^' call conout pctl1: pop af add 40h call conout jp stndend conout: push hl push de push bc push af ld e,a ld c,wrconf call bdos pop af pop bc pop de pop hl ret cr$clr: ld a,cr ; Print CR, CLREOL call conout clreol: jp EREOL homcrs: call AT db 1,1 ret retcrs: call AT ; Go to status line prrow: db 24 db 1 ret end1crs: ; End of text1 screen window? jr nz,retcrs call AT db 12,1 ret top2crs: ; Top of text2 screen window? jr nz,homcrs call AT db 13,1 ret clrln: ld a,cr ; Blank first part of status line call conout ld b,41 ld a,' ' call conout djnz $-3 ld a,cr jp conout divide: ; Print screen divider call end1crs ld a,' ' call conout ld a,(width) ld b,a dec b ld a,'=' call conout djnz $-3 ret vprint: print: ex (sp),hl ; get address call print1 ex (sp),hl ; put address ret ; ; Print String (terminated in 0) pted to by HL ; print1: ld a,(hl) ; done? inc hl ; pt to next or a ; 0 terminator ret z cp dim ; standout? jr z,print1d cp bright ; standend? jr z,print1b push af and 7fh call conout ; print char pop af ret m jr print1 print1d: call stndout ; dim jr print1 print1b: call stndend ; bright jr print1 getc: ld c,dirconf ; Get character without screen echo ld e,-1 call bdos or a jr z,getc ; Loop until input ret upcase: cp 'a' ret c cp 'z'+1 ret nc and 5fh ret abort: cp esc ; Check for escape or ^C ret z cp 3 ; ^C ret ; ; Case - jump table scanner ; Change only alternate registers ; Format: call case ;call with value to match in A ; db val1 ;first val to match ; dw addr1 ;jump address ; ... ; db 0 ;end table ; else next instuction executes if no match case: exx ;save HL,DE,BC ex (sp),hl ;hl -> next addr after call ex af,af' ;save char xor a case1: ex af,af' ;restore char cp (hl) ;match? inc hl ;set pointer to val's jump addr jr z,case0 ;if match, jump inc hl ;point to next val inc hl ex af,af' ;check for list terminator cp (hl) jr nz,case1 ;keep looking inc hl ;no match, execute next instruction ex af,af' ;restore A casex: ex (sp),hl exx ;restore regs ret case0: ld e,(hl) ;load address inc hl ld d,(hl) ex de,hl jr casex ;go topram: ld a,(7) ; Get BDOS page ld b,a ; Stash it in B ld a,(2) ; Get BIOS page sub b ; Get offset cp 0eh ; Test for standard offset ld a,b ret nz ; NZ means CCP protected sub 9 ; Leave room for CCP ret movptr: ld bc,stksav-srt2 ldir ret movfcb: ld de,fcb movfcb1: ld bc,36 ldir ret ; End Utilities help: call CLS call info call retcrs call cr$clr call print db 1,'Command?',2,' '+80h call getc ld (comchr),a ; Save it or -1 ; Set command pending flag ld (cmdflag),a ; Save and get on with things jp scrn1 info: if hlpdoc call print db cr,lf,tab,tab,tab,1,'<<<< VCOMP ' db vers/10+'0','.',vers mod 10 + '0' db ' COMMANDS >>>>',2 db cr,lf,lf db ' ---',tab,tab,tab,tab,tab,tab,tab,' ---',cr,lf db '|',1,'ESC',2,'| Halt Listing ' db tab,tab,tab,tab,' Go To Mark |',1,' 0 ',2,'|',cr,lf db ' ---',tab,tab,tab,tab,tab,tab,tab,' ---',cr,lf,lf db ' Set Echo Auto Re-' db cr,lf db ' Sync Window Mode Read Type ' db 'Compare Sync Init Mark Print' db cr,lf db ' --- --- --- --- --- ' db '--- --- --- --- ---' db cr,lf db ' |',1,' Q ',2,'| |',1,' W ',2,'| |',1,' E ',2 db '| |',1,' R ',2,'| ' db '|',1,' T ',2,'| |',1,' Y ',2,'| |',1,' U ',2 db '| |',1,' I ',2,'| ' db '|',1,' O ',2,'| |',1,' P ',2,'|' db cr,lf db ' --- --- --- --- --- ' db '--- --- --- --- ---' db cr,lf db ' --- --- --- --- --- --- ' db '--- --- --- ---' db cr,lf db ' |',1,' A ',2,'| |',1,' S ',2,'| |',1,' D ',2 db '| |',1,' F ',2,'| ' db '|',1,' G ',2,'| |',1,' H ',2,'| |',1,' J ',2 db '| |',1,' K ',2,'| ' db '|',1,' L ',2,'| |',1,' ; ',2,'|' db cr,lf db ' --- --- --- --- --- ' db '--- --- --- --- ---' db cr,lf db ' End Next Next Next Find ' db 'Rpt Up Up Up Top' db cr,lf db ' x 5 Line Screen ' db 'Find Screen Line x 5' db cr,lf,lf db ' ',1,'X',2,' - Exit <',1,'sp',2,'> - Switch ' db 'Files <',1,'cr',2,'> - Next Screens <',1,'?,/',2 db '> - Help' db cr,lf db 0 endif ; helpdoc ret nope: call print db 'VCOMP, Ver ',vers/10+'0','.',vers mod 10+'0',cr,lf db 'Syntax: VCOMP [du:|dir:]file1 [du:|dir:][file2]',0 call info jr exit nofile: call pfil call print db ' not found',lf+80h jr exit novid: call print db 'TCAP SUPPOR','T'+80h jr exit exit0: call CLS exit: call DINIT ld sp,(stksav) ; Restore stack pointer ret ; To CCP ; ; OPTION HARD CODED VIDEO ROUTINES, SAVE 500 BYTES ; if hardvid include hardvid.lib endif ; ; Storage ; width db 79 ; Useable screen width (dynamically loaded) scrlns db 11 ; Screen lines ptrbuf equ $ cmdflag db 0 ; Command pending flag comchr db 0 ; Pending command txtptr dw 0 ; Scratch pointer fcb1buf: ds 36 fcb2buf: ds 36 eflag ds 1 ; Echo flag 0 = ECHO FF = NO ECHO sflag ds 1 ; Switch flag 0 = FILE1 FF = FILE2 wflag ds 1 ; Window flag 0 = No FF = Yes srtptr dw 0 ; Start Pointer -> beginning of screen eosptr dw 0 ; End of Screen Pointer -> last screen mrkptr dw 0 ; Print marker eofptr dw 0 ; End of File Pointer txtloc dw 0 ; Start of text Pointer topmem ds 1 ; Top of mem high bytes lastchr ds 1 ; Save last chr eoflag ds 1 ; File completely read rflag ds 1 usr ds 1 srt1 dw 0 eos1 dw 0 mrk1 dw 0 eof1 dw 0 txt1 dw 0 top1 ds 1 lcr1 ds 1 efl1 ds 1 rfl1 ds 1 usr1 ds 1 srt2 dw 0 eos2 dw 0 mrk2 dw 0 eof2 dw 0 txt2 dw 0 top2 ds 1 lcr2 ds 1 efl2 ds 1 rfl2 ds 1 usr2 ds 1 stksav ds 60 ; Save incoming stack pointer stack equ $ ; Top of local stack end start