home *** CD-ROM | disk | FTP | other *** search
- ;
- ; DISC LABELING PROGRAM..............
- ;
- ;+======================================================================+
- ;| |
- ;|TITLE: LABLDISK.ASM - Print Sorted Disk Directory on Label |
- ;| |
- ;|DATE: 02/16/83 VERSION: 2.0 LANGUAGE: ASM-80 |
- ;|SQUEEZED NAME: LABLDISK.AQM LIBRARY NAME: none |
- ;|RELATED FILES: none |
- ;| |
- ;|SYSTEM: Standard CP/M-80, minimum 24k |
- ;| |
- ;|PURPOSE: To print an alphabetically sorted disk directory on a label |
- ;| using the condensed font of your printer for the main |
- ;| directory and an enlarged font to print the first entry |
- ;| in the directory as a title on the label. |
- ;| |
- ;|SUMMARIZE REVISION: Made printer and label characteristics modular |
- ;| at front of program. Deleted 'SETUP' function |
- ;| key printout. Added optional title capability. |
- ;| |
- ;|SUBMITTED BY: Melissa Gray [leave messages on RBBS (415)965-4097] |
- ;|ORIGINAL AUTHOR: unknown (derived from FMAP (Catalog) program) |
- ;|OTHER CONTRIBUTORS: Dennis McFerran (called it DSCLABEL.ASM) |
- ;| (There's also another new version of DSCLABEL |
- ;| with the 'SETUP' printout changed to an option) |
- ;| |
- ;|REFERENCE: FMAP program |
- ;| |
- ;|DOCUMENTATION: Fairly extensive setup documentation in front of the |
- ;| source, though not entirely clear. User documentation|
- ;| is limited and source documentation is fairly good. |
- ;| |
- ;|PROGRAM USAGE: Would be very useful to anyone needing this |
- ;| capability. Fairly easy to install, although it |
- ;| requires edits for printers other than the NEC-8023 |
- ;| and label sizes other than 5"x3" to be cut to 5"x2" |
- ;| |
- ;|RATING: *** (needs to be able to read label size parameters on-line) |
- ;| |
- ;+======================================================================+
- ;
- ;
- ; 6/29/82---THIS PROGRAM, WHICH WAS ADAPTED FROM
- ; THE FMAP(CATALOG) PROGRAM, WILL LIST
- ; YOUR FILE DIRECTORY ON A LABEL SIZED
- ; OUTPUT AND THEN LIST THE SPECIAL FUNCTION
- ; KEY INSTRUCTIONS THAT HAVE BEEN ADDED TO
- ; YOUR DISC VIA THE 'SETUP' PROGRAM. I AM
- ; USING AN EPSON MX-100. I THINK THAT THE
- ; COMMANDS, WILL WORK ON AN MX-80 BUT I'M NOT
- ; SURE. TRY IT AND LET ME KNOW. IT WOULD
- ; HAVE TO BE MODIFIED FOR OTHER PRINTERS.
- ;
- ;*******************************************************************
- ;
- ; THIS IS MY ABOUT MY FIRST USABLE(?) ASSEMBLY LANGUAGE EFFORT.
- ; I WOULD APPRECIATE ANY COMMENTS OR SUGGESTIONS:
- ; DENNIS MC FERRAN
- ; 1038 POLK LANE
- ; SAN JOSE, CA 95117
- ; (408-296-6021)
- ;********************************************************************
- ;
- ; TO USE--------
- ; 1) PLACE DISC WITH THIS PROGRAM ON IT IN ONE DRIVE
- ; 2) TURN ON YOUR PRINTER AND HAVE LABELS IN TO PRINT
- ; 3) PLACE DISC THAT YOU WOULD LIKE TO LABEL IN OTHER DRIVE
- ; (YOU MAY ALSO LABEL THE DISC CONTAINING THIS PROGRAM)
- ; 4) RESET THE DRIVE WITH THE DISC TO BE LABELLED (^C)
- ; 5) RUN LABLDISK (e.g,: B> A:LABLDISK) [Optionally you may
- ; specify a filename using conventional wildcards (e.g.:
- ; B> A:LABLDISK *.COM). For this option, the title in
- ; its current form is generally inappropriate.
- ; 6) REPEAT AS MANY TIMES AS YOU'D LIKE FROM STEP 3
- ;
- TRUE EQU 0FFH
- FALSE EQU 0
- ;
- ;
- ;*********EQUATES TO SET FOR YOUR SYSTEM********************************
- ;
- DOTITLE EQU TRUE ;Set TRUE if you supply TITLED parameters for
- ; your printer below
- NEC8023 EQU TRUE ;Set TRUE if your printer is the NEC PC-8023A-C
- EPMX100 EQU FALSE ;Set TRUE if your printer is the EPSON MX-100
- ;
- LBLLNG EQU 16 ;Set value to the number of lines your label can
- ; hold based on the line spacing you select below
- ; and the length of your label in inches
- LBLSPC EQU 10 ;Set value to the number of lines between labels
- ; on your sheet, based on your line spacing
- LENCOL EQU 82 ;Set value to # of usable columns across label,
- ; based on width (in inches) of label times
- ; characters per inch(CPI) of your condensed font.
- LBLWID SET (LENCOL+SPCSIZ)/(12+SPCSIZ)
- ; Sets value to the number of 12 character file
- ; names and SPACES (see below) that can be
- ; printed across the width of your label.
- MAXFIL EQU 255 ;Set value to the maximum number of disk files
- ; that may be encountered on one of the disks
- ; you will be labelling
- ;
- ;
- ;*********EQUATE TABLE - BDOS***********************
- ; *
- RDCHR EQU 1 ;READ CHAR FROM CONSOLE *
- WRCHR EQU 5 ;WRITE CHR TO PRINTER *
- PSTRING EQU 9 ;PRINT CONSOLE BUFF *
- CONST EQU 11 ;CHECK CONS STAT *
- FSRCHF EQU 17 ; " " *
- FSRCHN EQU 18 ; " " *
- FCB EQU 5CH ;FILE CONTROL BLOCK *
- BDOS EQU 5 ; *
- ; *
- ESC EQU 1BH ;<ESCAPE> CODE *
- CR EQU 0DH ;CARRIAGE RETURN *
- LF EQU 0AH ;LINE FEED *
- ;***************************************************
- ;
- ;
- ORG 100H
- JMP START ;Bypass User changeable data
- ;
- ;***********************************************************************
- ;
- ; BUILD THE FOLLOWING TABLES FOR YOUR PRINTER IF IT'S NOT HERE
- ;
- ; TITLED is the table used to set your line spacing (usually 6
- ; lines per inch) and your large print font (usually
- ; 10 CPI) and your enlarged print mode for printing the
- ; the first directory (in alphabetical order) as the
- ; title on your label. This parameter is not required
- ; if DOTITLE is set to FALSE above.
- ;
- ; SETPRT is the table used to set your line spacing (usually to 9
- ; lines per inch) and your small print font (usually
- ; Condensed). It may include any other printer characteristics
- ; you'd like. It must end with an '$'.
- ;
- ; RESET is the table used to return your printer to its normal
- ; line spacing (usually 6 lines per inch) and print font
- ; (usually 10 CPI). It may also include any other printer
- ; characteristics you'd like. It must also end with an "$".
- ;
- ;
- TITLED EQU $
- IF NEC8023
- DB ESC,'B' ;Set line spacing to 1/8"
- DB ESC,'N' ;Set font to Normal (10 CPI)
- DB 0EH ;Set Enlarged character command
- DB ESC,'!' ;Set Enhanced print mode on
- ENDIF
- ; Insert new printer definitions here (with IF/ENDIF)
- DB '$' ;End of TITLED table
- ;
- SETPRT EQU $
- IF NEC8023
- DB CR,ESC,'T',31H,37H ;Set line spacing to 17/144"
- DB ESC,'Q' ;Set font to Condensed (17 CPI)
- DB 0FH ;Clear Enlarged character command
- DB ESC,'!' ;Set Enhanced print mode on
- ENDIF
- IF EPMX100
- DB CR,ESC,'A',8 ;Set line spacing to 8/72"
- DB 0FH ;Set font to Condensed
- ENDIF
- ; Insert new definitions here (with IF/ENDIF)
- DB '$' ;End of SETPRT table
- ;
- RESET EQU $
- IF NEC8023
- DB ESC,'A' ;Set line spacing to 1/6"
- DB ESC,'N' ;Set font to Normal (10 CPI)
- DB ESC,'"' ;Set enhanced print mode off
- ENDIF
- ;
- IF EPMX100
- DB ESC,'A',12 ;Set line spacing to 12/72"
- DB 12H ;Set font to Normal
- ENDIF
- ; Insert new definitions here (with IF/ENDIF)
- DB '$' ;End of RESET table
- ;
- ;***THE FOLLOWING TABLE DEFINES THE DIVIDER PRINTED BETWEEN FILE NAMES
- ; ACROSS THE LABEL AND CAN BE ADJUSTED AS REQUIRED. Note: It is not
- ; printed after the last filename on the line.
- ;
- SPACES DB ' | ' ;This table must end in an '$'
- SPCSIZ EQU $-SPACES ;# of characters between fields
- ; (filenames) on label
- DB '$' ;End of SPACES table
- ;
- ;***********************************************************************
- ;
- ;
- START EQU $
- LXI H,0 ;SAVE THE OLD STACK
- DAD SP ;H=STACK
- SHLD STACK ;SAVE IT
- LXI SP,STACK ;GET NEW STACK
- ; FCB SPECIFIED ?
- LXI H,FCB+1
- MOV A,M
- CPI ' '
- JNZ GOTFCB ;YES - SEE IF IT IS IN DIRECTORY
- ;NO FCB - MAKE FCB = ALL = '?'
- MVI B,11 ;FN+FT COUNT
- QLOOP EQU $
- MVI M,'?' ;STORE '?' IN FCB
- INX H
- DCR B
- JNZ QLOOP
- ;LOOK UP THE FCB IN THE DIRECTORY
- GOTFCB EQU $
- MVI A,LBLLNG ;Initialize # of lines remaining on
- STA LCOUNT ; label to full count
- MVI C,FSRCHF ;GET 'SEARCH FIRST' FNC
- LXI D,FCB
- CALL BDOS ;READ FIRST
- INR A ;WERE THERE ANY ?
- STA TEMP ;SAVE
- JNZ PRTSET ;GOT SOME - SET UP PRINTER
- LXI D,NONMSG
- JMP ERRXIT
- NONMSG EQU $
- DB '++FILE NOT FOUND',CR,'$'
- ;SET UP PRINTER COMMANDS
- PRTSET EQU $
- IF DOTITLE
- LXI H,TITLED
- MVI A,TRUE
- ENDIF
- IF NOT DOTITLE
- LXI H,SETPRT
- MVI A,FALSE
- ENDIF
- STA TTLSWC
- CALL WRPRNT
- LDA TEMP ;RELOAD EXTENT
- ;POINT TO DIRECTORY ENTRY
- SOME EQU $
- DCR A ;UNDO PREV 'INR A'
- ANI 3 ;MAKE MODULUS 4
- ADD A ;MULTIPLY...
- ADD A ;..BY 32 BECAUSE
- ADD A ;..EACH DIRECTORY
- ADD A ;..ENTRY IS 32
- ADD A ;..BYTES LONG
- LXI H,81H ;POINT TO BUFFER (SKIP TO FN/FT)
- ADD L ;POINT TO ENTRY
- MOV L,A ;SAVE (CAN'T CARRY TO H)
- LDA COUNT ;Is there room in table for entry ?
- CPI MAXFIL
- JZ NOTALL ;No - cannot list all files - alarm
- ;MOVE ENTRY TO TABLE
- XCHG ;ENTRY TO DE
- LHLD NEXTT ;NEXT TABLE ENTRY TO HL
- MVI B,31 ;ENTRY LENGTH
- TMOVE EQU $
- LDAX D ;GET ENTRY CHAR
- MOV M,A ;STORE IN TABLE
- INX D
- INX H
- DCR B ;MORE?
- JNZ TMOVE
- SHLD NEXTT ;SAVE UPDATED TABLE ADDR
- LDA COUNT ;GET PREV COUNT
- INR A
- STA COUNT
- ;READ MORE DIRECTORY ENTRIES
- MVI C,FSRCHN ;SEARCH NEXT
- LXI D,FCB
- CALL BDOS ;READ DIR ENTRY
- INR A ;CHECK FOR END (0FFH)
- JNZ SOME ;MORE
- ;SORT AND PRINT
- LDA COUNT ;INIT THE ORDER TABLE
- STA SCOUNT ;SAVE AS # TO SORT
- LXI H,ORDER
- LXI D,TABLE
- LXI B,31 ;ENTRY LENGTH
- BLDORD EQU $
- MOV M,E ;SAVE LO ORD ADDR
- INX H
- MOV M,D ;SAVE HI ORD ADDR
- INX H
- XCHG ;TABLE ADDR TO HL
- DAD B ;POINT TO NEXT ENTRY
- XCHG
- DCR A ;MORE?
- JNZ BLDORD ;..YES
- SORT XRA A ;GET A ZERO
- STA SWITCH ;SHOW NONE SWITCHED
- LDA SCOUNT ;GET COUNT
- DCR A ;USE 1 LESS
- STA TEMP ;SAVE # TO COMPARE
- STA SCOUNT ;SAVE HIGHEST ENTRY
- JZ DONE ;EXIT IF NO MORE
- LXI H,ORDER ;POINT TO ORDER TABLE
- SORTLP CALL COMPR ;COMPARE 2 ENTRIES
- CM SWAP ;SWAP IF NOT IN ORDER
- INX H ;BUMP ORDER
- INX H ;..TABLE POINTER
- LDA TEMP ;GET COUNT
- DCR A
- STA TEMP
- JNZ SORTLP ;CONTINUE
- ;ONE PASS OF SORT DONE
- LDA SWITCH ;ANY SWAPS DONE?
- ORA A
- JNZ SORT
- ;
- ;SORT IS ALL DONE - PRINT ENTRIES
- DONE LXI D,ORDER ;D/E point to 1st entry in ORDER
- PUSH D ;Save DE
- MVI A,LBLWID ;Initialize count of file names per
- STA WCOUNT ; line
- ;PRINT AN ENTRY
- PRINT EQU $
- MVI C,CONST ;CK STATUS OF KB
- CALL BDOS ;ANY KEY PRESSED?
- DCR A
- JZ ABORT ;YES, ABORT
- POP D ;Restore DE
- LDAX D ;No - get memory byte addressed by DE
- MOV L,A ; and put in L
- INX D ;Move to next location in ORDER
- LDAX D ;Get memory byte addressed by DE
- MOV H,A ; and put in L
- INX D ;Move to next location in ORDER
- PUSH D ; and save DE
- MVI B,8 ;FILE NAME LENGTH
- CALL TYPEIT ;TYPE FILENAME
- MVI E,'.'
- CALL TYPE
- MVI B,3 ;GET THE FILETYPE
- CALL TYPEIT
- ;
- LDA COUNT ;Decrement count of file names to print
- DCR A
- STA COUNT
- JZ EXIT ;All done - Exit
- ;
- LDA TTLSWC ;Put only Title on its line in
- CPI FALSE
- JZ TTLDONE
- MVI A,FALSE
- STA TTLSWC
- LXI H,SETPRT ; enlarged font - then switch to
- CALL WRPRNT ; condensed font
- MVI B,1
- CALL CRLF ;Double-space between title & directory
- JMP NXTLIN ;Start rest of directory on next line
- ;
- TTLDONE LDA WCOUNT ;Decrement # of entries left on this
- DCR A ; line for filenames
- STA WCOUNT
- JZ NXTLIN ;No more room on line - go to next line
- ENDIF
- ;
- LXI H,SPACES ;Room for another filename
- CALL WRPRNT ; Put in divider between names
- JMP PRINT
- ;
- NXTLIN EQU $
- MVI B,1 ;Set request for one CR/LF
- CALL CRLF ;Output CR/LF and test for end of label
- JMP PRINT ;Go to print next file name
- ;
- ;
- ;TYPE CHAR IN E
- TYPE PUSH B
- PUSH D
- PUSH H
- MVI C,WRCHR
- CALL BDOS
- POP H
- POP D
- POP B
- RET
- ;
- ;
- ; PRINT STRING SPECIFIED BY HL
- WRPRNT MVI A,'$'
- CMP M
- RZ
- MOV E,M
- CALL TYPE
- INX H
- JMP WRPRNT
- ;
- ;
- ; TYPE STRING WHOSE LENGTH IS IN B AND ADDR IN HL
- TYPEIT EQU $
- MOV A,M ;Get rid of any tag bits in name
- ANI 07Fh ; for print out
- MOV E,A
- CALL TYPE
- INX H
- DCR B
- JNZ TYPEIT
- RET
- ;
- ;
- ; OUTPUT SPECIFIED # OF CR/LF's TO PRINTER AND CHECK FOR END OF LABEL.
- ; AT END OF LABEL, FEED TO NEXT LABEL.
- CRLF EQU $
- LDA LCOUNT ;Get count of lines remaining on label
- SUB B ; Less # of LF's requested
- STA LCOUNT ; and save as # of lines remaining
- MVI A,LBLWID ;Initialize # of file names across label
- STA WCOUNT
- MVI E,CR ;Get CR character in E
- CALL TYPE ; and output it
- MVI E,LF ;Get LF character in E
- MOV A,B ;Check # of requested LF's for zero
- CPI 0
- JZ NXTLBL ;If so, feed to next label
- LFLOOP EQU $
- CALL TYPE ;Output LF
- DCR B ;Decrement count of LF's to perform
- JNZ LFLOOP ;Loop till none left
- ;
- NXTLBL LDA LCOUNT ;Check for end of Label
- CPI 0
- RNZ ;More lines left - Return
- MVI A,LBLLNG ;Initialize # of lines per label
- STA LCOUNT
- MVI B,LBLSPC ;Set count to specified # of lines
- JMP LFLOOP ;between labels and do LF's to next labl
- ;
- ;
- ;ERROR EXIT
- ;
- OVRFLMS EQU $
- DB '++ TOO MANY FILES FOR PROGRAM TABLE',CR,LF,'$'
- NOTALL EQU $
- LXI D,OVRFLMS
- ERRXIT MVI C,PSTRING ;SET UP TO PRINT STRING TO CONSOLE
- JMP CALLB ;PRINT MSG, EXIT
- ;
- ;ABORT - READ CHAR ENTERED
- ABORT MVI C,RDCHR
- CALLB CALL BDOS ;DELETE THE CHAR
- ;
- ;EXIT - ALL DONE
- EXIT EQU $
- LDA LCOUNT
- CPI LBLLNG ;Are we at top of a label ?
- JZ FINAL ;Yes - no need to go to top of label
- MOV B,A ;No - Get remaining lines on label in B
- CALL CRLF ;Go to top of next label
- FINAL EQU $
- LXI H,RESET ;Reset printer to Normal mode
- CALL WRPRNT
- LHLD STACK ;GET OLD STACK
- SPHL ;MOVE TO STACK
- RET ;..AND RETURN
-
- ;COMPARE ROUTINE FOR SORT
-
- COMPR PUSH H ;SAVE TABLE ADDR
- MOV E,M ;LOAD LO
- INX H
- MOV D,M ;LOAD HI
- INX H
- MOV C,M
- INX H
- MOV B,M
- ;BC, DE NOW POINT TO ENTRIES TO BE COMPARED
- XCHG
- CMPLP EQU $
- MOV A,M ;Get rid of any tag bit in name
- ANI 07FH ; before comparing names for sort
- MOV M,A
- LDAX B
- ANI 07FH
- CMP M
- INX H
- INX B
- JZ CMPLP
- POP H
- RET ;COND CODE TELLS ALL
- ;SWAP ENTRIES IN THE ORDER TABLE
- SWAP MVI A,1
- STA SWITCH ;SHOW A SWAP WAS MADE
- MOV C,M
- INX H
- PUSH H ;SAVE TABLE ADDR+1
- MOV B,M
- INX H
- MOV E,M
- MOV M,C
- INX H
- MOV D,M
- MOV M,B
- POP H
- MOV M,D
- DCX H ;BACK POINTER TO CORRECT LOC'N
- MOV M,E
- RET
- ;
- ;
- ;
- DS 40 ;STACK AREA
- STACK DS 2 ;SAVE OLD STACK HERE
- NEXTT DW TABLE ;NEXT TABLE ENTRY
- COUNT DB 0 ;ENTRY COUNT
- SCOUNT DB 0 ;# TO SORT
- WCOUNT DB 0 ;# OF FILENAME SPACES LEFT ACROSS LINE
- LCOUNT DB 0 ;# of Lines remaining on this Label
- SWITCH DB 0 ;SWAP SWITCH FOR SORT
- TTLSWC DB 0 ;Switch for Title font
- TEMP DS 1
- ORDER DS 2*MAXFIL ;ORDER TABLE
- TABLE EQU $ ;READ ENTRIES IN HERE
- END 100H