home *** CD-ROM | disk | FTP | other *** search
Text File | 1993-06-07 | 46.9 KB | 1,799 lines |
- ;-----------------------------------------------------------------------
- ; Zplot
- ;-----------------------------------------------------------------------
- ;
- ;This program reads a sequential plot command file, makes a memory image
- ;of the plot, and prints the plot on the printer.
- ;
- ;Adapted and Z-ified by Greg Trice
- ; 476 Thorndale Drive
- ; Waterloo, Ontario N2T1W5
- ; Canada
- ; from the program Plot33 by Thomas E. Speer
- ;
- ; This program is released to the Public Domain
- ;
- ;Revision history
- ;
- ; Zplot version 1.0 December 1989 Greg Trice
- ; Rewritten in Z80 code, Z-system support added, allowing
- ; du: or dir: specs for files. Support for non-Epson
- ; printers removed (as just about every printer today supports
- ; Epson graphics)
- ;------------------------------------------------------------------------
- ;
- true equ 0ffffh
- false equ not true
- blank equ ' '
- CR equ 0dh
- LF equ 0ah
- bel equ 7
- ESC equ 1bh
- ;
- boot equ 0 ;warm boot entry point
- fcb equ 5ch ;file control block
- tbuff equ 80h ;buffer
- bdos equ 5 ;o/s entry point
- ;
- ;====================== Printer parameters ===============================
- ;this section sets the specific constants for your printer.
- ;
- ;***** NOTE ***** The maximum value for maxx that can be used is 1530.
- ;The maximum value for maxy that can be used is 1785. these limits
- ;are required to avoid arithmetic overflows.
- ;The size of the map ( (maxx+1)*(maxy+1)/7 ) must fit between the end of
- ;the program and the end of the tpa.
- ;To go into graphics mode, Epson printers use an <esc> sequence
- ;followed by a specified number of graphics bytes.
- ;
- maxx equ 479 ;set maximum width to epson low res mode
- maxy equ 573 ;set maximum height to make square plot
- mapsize equ 39360 ;total size of map
- cwidth equ 6 ;raster width of a printed character
-
- org 100h ;beginning of tpa
- jp entry
- db 'Z3ENV'
- db 0
- z3eadr:
- dw 0
- banner:
- db ' ZPLOT Version 1.0 Dec 12 1989',CR,LF,'$'
- ;
- ; set up graphic output buffer area
- esck:
- db ESC,'K' ;define esc "K" character sequence
- ngraph:
- dw 0 ;initialize graphic counter
- gbuff:
- ds maxx+1 ;set aside area for graphic o/p buffer
- ;
- ;========================= data storage section ============================
- ;
- color:
- db 0
- xpos:
- dw 0
- ypos:
- dw 0
- x:
- dw 0
- y:
- dw 0
- yfill:
- dw 0
- pointer:
- db 128 ;file buffer ptr
- pointr2:
- db 0 ;output file buffer ptr
- sysstk:
- dw 0
- oldstk:
- dw 0
- stack:
- ds 80h ;128 level stack
- olduser:
- db 0
- xdot:
- dw 0 ;dot x-coord
- ydot:
- dw 0 ;dot y-coord
- xyaddr:
- dw origin ;address of x,y location
- divdnd:
- dw 0 ;divide routine variables
- divsor:
- db 0 ; "
- qotent:
- db 0 ; "
- rmandr:
- db 0 ; "
- nomem:
- db 'Not Enough Memory',CR,LF,'$'
- nofile:
- db 'File Not Found',CR,LF,'$'
- eofmsg:
- db 'End of File',CR,LF,'$'
- nodir:
- db 'No Directory Space Available',CR,LF,'$'
- noroom:
- db 'Disk is Full',CR,LF,'$'
- unknch:
- db 'Undefined Command Character Encountered',CR,LF,'$'
- stat1:
- db ' Working ... ',CR,'$'
- stat2:
- db ' ... Working ',CR,'$'
- stat3:
- db ' Printing Picture ',bel,CR,'$'
- statno:
- db 0
- deltax:
- dw 0 ;local variables for incplt
- deltay:
- dw 0 ; "
- epslnx:
- dw 0 ; "
- epslny:
- dw 0 ; "
- sx:
- dw 0 ; "
- sy:
- dw 0 ; "
- delta3:
- dw 0 ; "
- ni:
- dw 0 ; "
- ;
- cmask:
- db 0ffh ;color mask
- patrn:
- ds 8 ;cell storage for clrmap (erase)
- plaids:
- db 00h,01h,71h,13h,05h,0fh,35h,11h ;cross hatched patterns
- ;
- cifpat:
- db 00h, 03h, 48h, 03h, 00h, 30h, 84h, 30h ;nd
- db 00h,0cch, 00h,0cch, 00h, 00h, 00h, 00h ;ni s
- db 08h, 04h, 02h, 01h, 80h, 40h, 20h, 10h ;nt p
- db 11h, 30h, 71h, 30h, 11h, 03h, 17h, 03h ;nc e
- db 22h, 00h, 88h, 00h, 22h, 00h, 88h, 00h ;nm c
- db 0c0h,81h, 03h, 06h, 03h, 81h,0c0h, 60h ;nb p i
- db 1ch, 3eh, 36h, 3eh, 1ch, 00h, 00h, 00h ;ng a a
- db 00h, 00h, 00h, 00h, 00h, 00h, 00h, 01h ;cw t l
- db 04h, 11h, 04h, 00h, 40h, 11h, 40h, 00h ;cd t
- db 02h, 04h, 08h, 10h, 20h, 40h, 80h, 01h ;cp e
- db 00h, 00h, 10h, 38h, 10h, 00h, 00h, 00h ;cs r
- db 66h, 99h, 99h, 66h, 66h, 99h, 99h, 66h ;cc n
- db 00h, 00h, 80h, 10h, 00h, 00h, 10h, 80h ;cm s
- db 81h,0c3h, 66h, 66h,0c3h, 81h, 00h, 00h ;cg
- db 0fh, 0eh, 0ch, 08h, 00h, 00h, 00h, 00h ;ce
- ;
- ditharr:
- db 63, 95, 71, 103, 65, 97, 73, 105 ;ordered
- db 111, 79, 119, 87, 113, 81, 121, 89 ;
- db 75, 107, 67, 99, 77, 109, 69, 101 ;dither
- db 123, 91, 115, 83, 125, 93, 117, 85 ;
- db 66, 98, 74, 106, 64, 96, 72, 104 ;matrix
- db 114, 82, 122, 90, 112, 80, 120, 88 ;
- db 78, 110, 70, 102, 76, 108, 68, 100 ;
- db 126, 94, 118, 86, 124, 92, 116, 84 ;
- fcb2:
- ds 33 ;output fcb
- obuff:
- ds 128 ;output file buffer
- opdisk:
- db 0 ;output to disk flag
- ;
- ;-----------------------------------------------------------------------
- ;
- helpmsg:
- db 'ZPLOT 1.0 ',CR,LF
- db 'Usage - ZPLOT infile[.VEC] [outfile[.PLT]]',CR,LF
- db 'If outfile is not supplied,'
- db ' output goes directly to printer.',CR,LF,'$'
- help:
- ld c,9
- ld de,helpmsg
- jp bdos
- ;
- ;----------------------------------------------------------------------
- ;
- entry:
- ld a,(tbuff)
- or a ;no command tail
- jr z,help
- ld a,(fcb+1)
- cp '/'
- jr z,help ;help requested
- ld c,9
- ld de,banner ;print banner message
- call bdos
- ld hl,(bdos+1) ;get end of tpa
- ld de,origin ;start of bitmap
- or a
- sbc hl,de ;total workspace available in HL
- ld de,mapsize ;workspace needed
- sbc hl,de ;must be >=0
- jr nc,wsok
- ld de,nomem ;error message
- ld c,9
- jp bdos ;display it and exit
-
- wsok:
- ld hl,0
- add hl,sp
- ld (sysstk),hl ;save system stack
- ld sp,stack+80h ;set new stack
- ld c,32
- ld e,0ffh ;get user
- call bdos
- ld (olduser),a ;save it
- ld iy,fcb ;pointer to fcb
- ld a,(iy+9) ;get first character of file type
- cp blank ;is type blank?
- jr nz,name ;no type has been specified
- ld a,'V' ;make default type "VEC"
- ld (iy+9),a
- ld a,'E'
- ld (iy+10),a
- ld a,'C'
- ld (iy+11),a
- name:
- ld a,(iy+17) ;get 1st char of o/p file
- cp blank ;is name blank?
- jr z,openfil ;blank= normal print output
- ld a,1 ;set o/p file flag=1 (disk o/p)
- ld (opdisk),a ;store flag
- ld bc,16
- ld hl,fcb+16 ;move o/p file name
- ld de,fcb2 ;to output fcb
- ldir
- xor a
- ld ix,fcb2 ;pointer to output fcb
- ld (ix+32),a ;zero cr field in o/p fcb
- ld a,(ix+9) ;get 1st char in o/p file type
- cp blank ;is file type blank?
- jr nz,delete ;not blank- go to delete old
- ld a,'P' ;make default 'plt'
- ld (ix+9),a
- ld a,'L'
- ld (ix+10),a
- ld a,'T'
- ld (ix+11),a
- delete:
- ld e,(iy+29)
- ld c,32
- call bdos ;set o/p user #
- ld de,fcb2 ;o/p fcb
- ld c,19 ;delete
- call bdos
- ld c,26 ;set dma
- ld de,obuff ;o/p file buffer
- call bdos
- ld c,22 ;make file
- ld de,fcb2 ;o/p fcb
- call bdos
- cp 0ffh ;is directory full?
- jr nz,openfil ;no- go on with program
- ld c,9
- ld de,nodir ;no directory space msg
- call bdos
- jp exit ;fatal error- quit
-
- ;
- ;open disk file of plot commands
- ;
- openfil:
- ld e,(iy+13)
- ld c,32
- call bdos ;set user #
- ld c,26 ;set dma
- ld de,tbuff ;i/p buffer
- call bdos
- ld c,15 ;open file
- xor a
- ld (iy+12),a ;clear extent counter
- ld (iy+14),a ;clear s2
- ld de,fcb
- call bdos
- cp 0ffh ;was file found?
- jr nz,rewind ;if file exits, rewind it
- ld c,9
- ld de,nofile ;error message
- call bdos
- jp exit ;done
- ;
- rewind:
- xor a
- ld (iy+32),a ;rewind by setting record#=0
- parse:
- call byte ;get command character
- cp 60h ;is it lower case?
- jr c,parse0 ;no
- xor 00100000b ;change to upper case
- parse0:
- ld bc,16 ;number of valid command bytes
- ld hl,commands ;list of command bytes
- cpir ;check against list
- jr z,parse1 ;a match is found
- ld c,9
- ld de,unknch ;unknown command
- call bdos
- jr parse ;get next byte
-
- parse1:
- ld ix,comtabl ;table of command routines
- add ix,bc
- add ix,bc ;point to selected routine
- ld de,parse ;return address
- push de
- ld l,(ix+0) ;get the address in HL
- ld h,(ix+1)
- jp (hl) ;dispatch to routine
-
- parse2:
- pop hl ;discard return address
- jr parse ;get next byte
-
- commands:
- db 'PCDEFIMNOQSTUX',CR,LF
- comtabl:
- dw parse2 ;ignore line feeds
- dw parse2 ;ignore carriage returns
- dw xtend ;provision for non-standard commands
- dw upload ;upload of color patterns
- dw text ;raw text output
- dw string ;character string plotting
- dw quit ;termination of program
- dw mapout ;printing of plot
- dw parse2 ;no operation loop
- dw move ;move to coord w/o plotting
- dw incplt ;plot incremental segment
- dw fill ;fill area to color
- dw clrmap ;clear memory map to color
- dw plotseg ;plot segment
- dw colour ;set color
- dw point ;plot point
- ;
- ;-----------------------------------------------------------------------
- ; Exit restoring original user
- exit:
- ld a,(olduser)
- ld e,a
- ld c,32 ;set user #
- call bdos
- ld hl,(sysstk) ;get system stack
- ld sp,hl ;reset stack
- jp boot ;back to system
- ;
- ;-----------------------------------------------------------------------
- ; Multiply A by HL, result in AHL
- bmult:
- ld hl,0 ;zero partial product
- ld de,7 ;d=0,e=bit counter
- add a,a ;get first multiplier bit
- loop1:
- jr nc,zero ;zero skip
- add hl,bc ;one-add multiplicand
- adc a,d ;add carry to third byte of product
- zero:
- add hl,hl ;shift product left
- adc a,a
- dec e ;decr bit counter
- jr nz,loop1 ;loop until done
- ret nc ;done if no carry
- add hl,bc ;otherwise do last add
- adc a,d
- ret
- ;-----------------------------------------------------------------------
- ; Gets next byte in buffer, next record is read if need be
- byte:
- push bc ;save registers
- push de
- push hl
- ld a,(pointer) ;get pointer value
- cp 128 ;is pointer=128?
- call z,read ;get record if last one was #128
- ld hl,pointer ;get new pointer
- inc (hl) ;incr pointer
- ld c,(hl) ;get pointer in BC
- ld b,0
- ld hl,tbuff-1 ;load hl with byte before tbuff
- add hl,bc ;calculate addr of desired byte
- ld a,(hl) ;get byte
- pop hl ;restore registers
- pop de
- pop bc
- ret ;done-- byte is in A
- ;-----------------------------------------------------------------------
- ; Print character in A
- ; outputs:
- ; graphic buffer is flushed
- ; character is put out to printer
- ; address in HL is incremented by (cwidth - 1)
- ; dot counter incremented by (cwidth - 1)
- ; the above are to account for the size of a character
- ; as opposed to a single dot
- charout:
- push af ;save registers
- push bc
- push de
- push hl
- xor 10000000b ;clear high bit of character
- call gbufout ;flush graphic buffer
- ld c,5 ;list output
- ld e,a ;character
- call pdos ;send character to printer
- pop hl ;recall registers
- pop de
- ld a,cwidth-1
- charo1:
- inc hl ;incr address
- dec de ;decr dot counter
- sub 1 ;decr loop counter
- jr nz,charo1
- pop bc
- pop af
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Clear memory
- ; inputs: bitmap of size mapsize located at origin
- ; map color stored in color
- ; (pos = patterned, 0 = white, - = complementary)
- ; Entire map area set to desired color or pattern
- clrmap:
- ld a,(color) ;get color
- or a ;check color
- jr nz,clrnz ;non-white?
- ld de,mapsize ;put mapsize in DE as counter
- ld hl,origin ;put start of map in HL
- ld c,0 ;c contains image of white byte
- clrlp1:
- ld (hl),c ;store byte
- inc hl ;incr address in map
- dec de ;decr loop counter
- ld a,d
- or e
- jr nz,clrlp1 ;loop until done
- ret
- ;
- clrnz:
- push af ;save flag values
- ld hl,patrn+7 ;point to last in pattern sequence
- ld c,7 ;initialize x counter
- clrlp2:
- ld d,80h ;set up y bit select
- ld e,7 ;initialize y counter
- ld b,0 ;initialize pattern
- clrlp3:
- call clrmsk ;form color mask based on x,y
- ld a,(cmask) ;get mask
- and d ;one bit
- or b ;add bit to pattern
- ld b,a ;save new pattern
- rrc d ;move select bit down one notch
- dec e ;decr y counter
- jp p,clrlp3 ;jump back if not negative (need 0 pass)
- pop af ;retrieve color code flag settings
- push af ;re-save flags settings
- jp p,clrl31 ;positive flag means pattern is ok
- ld a,b ;get pattern
- cpl ;complement pattern for negative colors
- ld b,a ;store pattern byte
- clrl31:
- ld (hl),b ;save pattern for this x location
- dec hl ;move memory pointer over
- dec c ;decr x coordinate/counter
- jp p,clrlp2 ;only done when negative (need 0 pass)
- ld c,[maxy+1] mod 8+1 ;counter for rotations due to mismatch
- clrlp4:
- call rotpat ;rotate pattern array 1 position
- dec c ;decr counter
- jr nz,clrlp4 ;loop back if not done
- ld hl,origin ;set map pointer to start of map
- ld bc,[maxy+1]/7 ;initialize line counter
- clrlp5:
- ld de,[maxx+1]/8 ;initalize dot counter
- clrl51:
- ld ix,patrn ;pointer to pattern
- exx
- ld b,8 ;loop counter
- clrl52:
- exx
- ld a,(ix+0) ;get byte
- and 7fh ;clear hi bit
- ld (hl),a ;store pattern in memory map
- inc hl ;move memory pointer
- inc ix ;move pattern pointer
- exx
- djnz clrl52 ;repeat for entire pattern
- exx
- dec de ;decr x counter
- ld a,e
- or d ;is counter zero?
- jr nz,clrl51 ;loop back until done
- ld e,[maxx+1]mod 8 ;set counter for rest of line
- ld d,7 ;pattern loop counter
- ld ix,patrn ;pointer to pattern
- inc e
- clrl53:
- dec e
- jr z,clrlp6 ;jump out of loop if done
- ld a,(ix+0) ;apply pattern to remaining bytes
- and 7fh ;clear hi bit
- ld (hl),a ;store pattern in memory map
- inc hl ;move memory pointer
- inc ix
- dec d
- jr nz,clrl53 ;repeat for entire pattern
- clrlp6:
- call rotpat ;rotate pattern down to match cells
- dec bc ;decr line counter
- ld a,c
- or b ;is counter = 0?
- jr nz,clrlp5 ;loop back up for another if req'd
- pop af ;clean up stack
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Forms the color mask used in plotting points
- ;
- ; Method: The plot is divided up into 8 x 8 raster cells.
- ; For color values between 1 and 63, the cell is composed
- ; of an x pattern and a y pattern which are xor'ed with
- ; each other to form a "PLAID" pattern
- ; For color values 64 and above, ordered dithering is used
- ; Ordered dithering is a technique in which the dots in
- ; the cell are added in in a pre-arranged position based
- ; upon the "INTENSITY" of the cell. The intersection of
- ; the point and the pattern (stored in the array "DITHARR"
- ; determines whether or not the point is plotted
- ; For both methods, a color mask is created, which is
- ; all 1's if the point in the pattern plane is on, or
- ; all 0's if the point in the pattern plane is off.
- ; inputs:
- ; x coordinate in bc
- ; y coordinate in de
- ; outputs:
- ; color mask stored in cmask
- ;
- clrmsk:
- push af ;save registers
- push bc
- push de
- push hl
- ld a,c ;form x cell coordinate
- and 00000111b
- ld b,a
- ld a,e ;form y cell coordinate
- and 00000111b
- ld c,a
- ld a,(color) ;get color code
- or a ;set flags based on basic code
- jp z,whtmsk ;zero color => white mask
- jp p,posclr ;color code is positive
- cpl ;complement color
- inc a ;color code is now positive
- posclr:
- cp 64 ;is color code < 64
- jr nc,dither ;code >=64 --> dithered
- cp 49 ;is color code < 49
- jr nc,special ;code from 49 to 63 --> cifpat's else plaid
- push af ;save color code
- and 00000111b ;select lower 3 bits of color code
- exx
- ld hl,plaids ;get base address of basic pattern
- ld d,0
- ld e,a
- add hl,de ;add x code to base addr to find pattern
- ld a,(hl) ;get x pattern for cell
- exx
- inc b ;incr x coordinate to be counter
- xcellp:
- rra ;rotate pattern bit into carry
- djnz xcellp ;loop back if not done
- ld a,0ffh ;carry --> pattern bit says plot point
- jr c,savxmsk
- xor a
- savxmsk:
- ld b,a ;replace x cell coord with x color mask
- pop af ;retrieve color code
- and 00111000b ;select 2nd 3 bits for y code
- rrca ;rotate bits to low order position
- rrca
- rrca
- exx
- ld hl,plaids ;get base address of basic pattern
- ld e,a
- ld d,0
- add hl,de ;add x code to base addr to find pattern
- ld a,(hl) ;get y pattern for cell
- exx
- inc c ;incr y coordinate to be counter
- ycellp:
- rra ;rotate pattern bit into carry
- dec c ;decr counter
- jr nz,ycellp ;loop back if not done
- ld a,0ffh ;dot will be plotted if carry set
- jr c,savymsk
- xor a
- savymsk:
- xor b ;final color mask-- x patrn xor y patrn
- ld (cmask),a ;save color mask
- pop hl ;restore registers
- pop de
- pop bc
- pop af
- ret
- ;
- dither:
- push af ;save color code for future use
- ld a,c ;multiply y cell coordinate by 8
- rlca
- rlca
- rlca
- add a,b ;offset into dither table = y*8 + x
- ld hl,ditharr ;get base address of table
- ld e,a
- ld d,0
- add hl,de ;add offset to base address
- ld a,(hl) ;get dither table value
- pop de ;retrieve color code (formerly in A)
- cp d ;is dither value > color code?
- ld a,0ffh ;carry--> plot point
- jr c,savmsk
- xor a ;carry not set--> don't plot point
- savmsk:
- ld (cmask),a ;store mask for future use
- pop hl
- pop de
- pop bc
- pop af ;registers restored, stack cleaned up
- ret
- ;
- special:
- sub 49 ;code is now relative to 49
- rlca ;code * 8
- rlca
- rlca
- add a,b ;add x coord to form offset into array
- exx
- ld hl,cifpat ;get fwa of pattern array
- ld e,a
- ld d,0
- add hl,de ;add offset to fwa
- ld a,(hl) ;get pattern byte for this x coord.
- exx
- inc c ;incr y coord to form counter
- spclp:
- rra ;rotate pattern bit into carry
- dec c ;decr counter
- jr nz,spclp ;loop back until done
- ld a,0ffh ;dot will be plotted if carry set
- jr c,savmsk
- xor a ;carry not set- don't plot point
- jr savmsk
- ;
- whtmsk:
- ld a,0ffh ;for white, always modify dot
- jr savmsk ;save mask and return
- ;
- ;-----------------------------------------------------------------------
- ; Define color
- ; inputs:
- ; buffer @ tbuff
- ; outputs:
- ; color value saved for future reference
- colour:
- call byte ;get color value
- ld (color),a ;save it
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Compute the next point in a line segment.
- ; Must be used with seginit to initialize all variables first.
- ;
- ; inputs:
- ; ni counter used by calling sub. to know when done.
- ; xpos,ypos present position
- ; dx,dy size of line segment along x,y axis
- ; epslnx,epslny,sx,sy,delta3 local variables
- ;
- compseg:
- ld hl,(ni)
- inc hl ;incr. ni
- ld (ni),hl
- ld bc,(xpos)
- ld de,(ypos)
- ld hl,(epslnx)
- add hl,bc ;add epsilon x to x position
- ld (xpos),hl ;store new value
- ld hl,(epslny) ;fetch epsilon y
- add hl,de ;add epsilon y to y position
- ld (ypos),hl ;store new value of y position
- ld de,(deltay)
- ld hl,(delta3)
- add hl,de ;add delta y to delta 3
- ld (delta3),hl ;store new value of delta3
- ld de,(deltax)
- or a
- sbc hl,de
- jr c,dopt ;dx > d3- plot point
- ld (delta3),hl ;store d3=d3-dx
- ld hl,(sx) ;compute xpos=xpos+sx
- ld de,(xpos)
- add hl,de ;add sx to xpos
- ld (xpos),hl ;store result
- ld hl,(sy) ;compute ypos=ypos+sy
- ld de,(ypos)
- add hl,de ;add sy
- ld (ypos),hl ;store new y position
- dopt:
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Carriage return routine
- ; Printer carriage is returned and paper advanced
- crlf:
- push af ;save all registers
- push bc
- push de
- push hl
- ld c,5 ;list output
- ld e,CR
- call pdos
- ld c,5
- ld e,LF
- call pdos
- pop hl ;restore registers
- pop de
- pop bc
- pop af
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Form the mask for the plotting of a point
- ; digit= ycoord mod 7
- ; inputs:
- ; xcoord in bc
- ; ycoord in de
- ; xyaddr in hl
- ; outputs:
- ; contents of xyaddr in b
- ; mask (1 bit on) in c
- ; ycoord in de
- ; xyaddr in hl
- ;
- digit:
- push hl ;save xyaddress
- push de ;save ycoord
- call clrmsk ;prepare color mask for future use
- ex de,hl ;put ycoord in hl
- ld (divdnd),hl ;calculate ycoord mod 7
- ld a,7
- ld (divsor),a
- call divide ;mod is divide w/o quotient
- ld a,(rmandr) ;get result
- or a ;set flags
- call m,woops ;rmandr= -1 on overflow
- ld b,a ;move # of digit to b
- xor a
- inc b ;incr b to init for 1st dec
- scf ;clear accum, put 1 in carry
- rotmask:
- rla ;move mask bit 1 left
- djnz rotmask ;loop back
- ld c,a ;store mask temporarily
- ld a,(cmask) ;get color mask
- and c ;and bit mask with color mask- both rqd
- ld c,a ;put mask in c
- pop de ;bring back ycoord
- pop hl ;bring back (xyaddr)
- ld b,(hl) ;get byte @ (xyaddr)
- ret
- ;
- ;-----------------------------------------------------------------------
- ; 16 bit by 8 bit division routine
- ; inputs:
- ; divdnd two byte positive number
- ; divsor one byte positive number
- ; outputs:
- ; qotent one byte positive quotient
- ; rmandr one byte positive remainder or flag
- ; error conditions:
- ; rmandr=-1 if overflow occurs
- ;
- divide:
- push af ;save registers
- push bc
- push de
- push hl
- ld de,(divdnd) ;fetch dividend
- ld a,(divsor) ;fetch divsor
- ld c,a ;save in register c
- ld b,8 ;loop counter in register b
- divloop:
- and a ;clear carry
- rl e ;shift low order byte to left
- ld a,d ;fetch high order byte
- rla ;rotate bringing in high bit
- sub a,c ;subtract divisor
- jp p,setbit ;if result was positive, jump
- add a,c ;otherwise add back divisor
- ld d,a ;replace high order byte
- jr next ;go to incr phase
- setbit:
- ld d,a ;replace high order byte
- set 0,e ;set low order bit
- next:
- djnz divloop ;repeat until done
- bit 7,e ;test sign of result
- jr z,ok ;if positive result is accurate
- ld a,0ffh ;set overflow value
- ld (rmandr),a
- jr done
- ok:
- ld a,e
- ld (qotent),a ;save quotient
- ld a,d
- ld (rmandr),a ;save remainder
- done:
- pop hl
- pop de
- pop bc
- pop af
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Plots the vertical line used to fill in areas
- ; inputs:
- ; xpos,ypos current position on segment
- ; yfill horizontal level to fill to
- ; outputs:
- ; vertical line from (xpos,ypos) to (xpos,yfill)
- ; note: all coordinate values assumed to be positive
- filine:
- call stat ;update status message
- ld hl,(xpos) ;get starting coordinates of line
- ld (xdot),hl ;xpos will be x coord of all dots
- ld de,(ypos) ;get y coordinate
- push de ;save y position- plotdot will reset it
- ld hl,(yfill) ;get y fill value
- or a
- push hl
- sbc hl,de ;compare y coordinates for top and bot.
- pop hl
- jr c,contfil ;yfill definitely less than ypos
- ex de,hl ;switch ypos and yfill- larger val in de
- contfil:
- ld (ydot),hl ;y coordinate to plotdot
- push de ;save registers
- push hl
- call plotdot ;plot point
- pop hl ;retrieve registers
- pop de
- inc hl ;incr y position
- or a
- push hl
- sbc hl,de
- pop hl
- jr c,contfil ;new coordinate definitely below end
- pop hl ;retrieve line y position
- ld (ypos),hl ;restore value
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Fill an area between a line segment and a horizontal line
- ; inputs:
- ; Buffer containing coordinate pairs and y coordinate of
- ; fill level.
- ; outputs:
- ; xpos,ypos updated to end of line segment
- ; area between segment and yfill is filled with current
- ; color value
- fill:
- call readxy ;get starting coordinates
- ld hl,(x)
- ld (xpos),hl ;update x position to start of segment
- ld hl,(y)
- ld (ypos),hl ;update y position to start of segment
- call readxy ;get end coordinates
- call byte ;get first byte of fixed pt. y fill
- push af ;save first byte
- call byte ;get second byte
- ld b,a ;put high byte in B
- pop af ;get low byte
- ld c,a ;BC now contains y coord.
- ld de,maxy*2 ;maximum raster address
- call mult ;multiply y coord by no. of y rasters
- ex de,hl ;put high bytes in HL
- ld (yfill),hl ;save integer value of y fill level
- call seginit ;initialize variables for seg. interp.
- call filine ;fill area between first pt. & yfill
- strtfil:
- call compseg ;compute next point in segment
- ld hl,(deltax) ;top of loop- end when ni>dx
- ld de,(ni) ;get counter
- or a
- sbc hl,de ;compare counter w/dx
- ret c ;ni > dx
- ld de,(xdot) ;compare xdot and xpos
- ld hl,(xpos)
- or a
- sbc hl,de ;are the two exactly the same?
- jr z,strtfil ;yes- skip this position
- call filine ;fill area between segment & yfill
- jr strtfil ;loop back to top
- ;
- ;-----------------------------------------------------------------------
- ; Send a string of characters to the printer
- ; inputs:
- ; number-1 of characters to send in DE
- ; address-1 of first character in HL
- ; outputs:
- ; 0 through DE characters sent to printer
- gboloop:
- dec de ;decr counter
- inc hl ;incr address
- push de ;save counter
- push hl
- ld e,(hl) ;get character
- ld c,5 ;list output
- call pdos ;send character out
- pop hl ;retrieve address
- pop de ;retrieve counter
- ld a,e ;is counter =0?
- or d
- jr nz,gboloop ;not done: loop back
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Save a byte from bit map in graphic buffer
- ; inputs:
- ; byte in B
- ; 2 byte counter @ ngraph
- ; outputs:
- ; ngraph incremented
- ; byte stored in buffer @ gbuff
- ; buffer flushed if full
- gbufin:
- push af ;save registers
- push bc
- push de
- push hl
- ld de,(ngraph) ;get no. of bytes in buffer
- inc de ;incr ngraph
- ld (ngraph),de ;store new value
- ld hl,gbuff-1 ;get buffer base address
- add hl,de ;add counter to base address
- ld (hl),b ;store byte
- ld hl,maxx+1 ;put max no. of bytes in HL
- or a
- sbc hl,de ;compare ngraph with (max no. of bytes)
- call z,gbufout ;buffer is full- flush it to printer
- pop hl ;restore registers
- pop de
- pop bc
- pop af
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Flush the graphic buffer
- ; inputs:
- ; graphic buffer @ gbuff
- ; number of valid bytes in buffer @ ngraph
- ; "ESC K" sequence stored ahead of ngraph
- ; outputs:
- ; printer is placed in dot graphic mode
- ; graphic string transmitted byte by byte to printer
- ;
- gbufout:
- push af ;save registers
- push bc
- push de
- push hl
- ld hl,(ngraph) ;fetch buffer counter
- ld a,l ;look at low byte
- or h ;is counter=0?
- jr z,gbufret ;if buffer is empty, don't o/p anything
- ld bc,maxx+1 ;get length of buffer
- or a
- sbc hl,bc
- jr nz,gbo2 ;no match indicates something on this line
- ld hl,gbuff ;set pointer to start of buffer
- gbo1:
- ld a,(hl) ;get byte from buffer
- or a ;is it a blank stroke?
- jr nz,gbo2 ;go to output section if not blank
- inc hl ;point to new byte
- dec bc ;decr counter
- ld a,b ;check for zero
- or c
- jr nz,gbo1 ;repeat until last byte has been checked
- jr gbufret ;return w/o plotting since all were blank
- ;
- gbo2:
- ld de,(ngraph) ;number of chars to output
- inc de ;add 4 for escape sequencew
- inc de
- inc de
- inc de
- ld hl,esck-1 ;start with escape sequence
- call gboloop ;send out string of graphic characters
- gbufret:
- ld hl,0
- ld (ngraph),hl ;set ngraph=0
- pop hl ;restore registers
- pop de
- pop bc
- pop af
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Plot an incremental line segment from the present position
- ; inputs:
- ; file buffer @ tbuff
- ; present position @ xpos,ypos
- ; outputs:
- ; xpos, ypos updated to x,y
- ; visible portion of line segment drawn
- incplt:
- call readxy ;get end point values
- call seginit ;initialize segment interpolation sub.
- strtplt:
- ld de,(deltax) ;top of loop- end when ni>dx
- ld hl,(ni) ;get counter
- or a
- sbc hl,de
- ret nc ;ni >= dx e- done w/segment
- call compseg ;compute xpos and ypos at next point
- ld hl,(xpos)
- ld (xdot),hl
- ld hl,(ypos)
- ld (ydot),hl
- call plotdot ;plot it
- jr strtplt ;back to the top of the loop
- ;
- ;-----------------------------------------------------------------------
- ; Line spacing routine
- ; inputs:
- ; none
- ; outputs:
- ; ESC A 7 sent to set the printer to 7/72in line spacing
- ln772:
- ld c,5 ;list output
- ld e,ESC
- call pdos
- ld c,5
- ld e,'A'
- call pdos
- ld c,5
- ld e,7
- call pdos
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Calculate the address for an xy coordinate pair
- ; xyaddr= origin + xcoord + (maxy-ycoord)/7 * (maxx+1)
- ; inputs:
- ; xcoordinate in registers bc
- ; ycoordinate in registers de
- ; maximum y raster count in hl
- ; outputs:
- ; xcoordinate in registers bc
- ; ycoordinate in registers de
- ; address of x,y coordinates in hl
- ; address stored @ xyaddr
- locdot:
- push de ;store y coord on stack
- push bc ;store x coord on stack
- or a
- sbc hl,de ;subtract ycoord from maxy
- ld (divdnd),hl
- ld a,7
- ld (divsor),a
- call divide ;(maxy - y)/7
- ld a,(rmandr) ;rmandr is negative if overflow
- or a ;set flags
- call m,woops ;overflow in division
- ld a,(qotent) ;get result of division
- ld bc,maxx+1 ;BC now contains the max. no. of x's
- call bmult ;HL has low order bytes, A the high
- ; HL now contains (max-ycoord)/7*(max+1)
- pop bc ;put xcoord in BC
- add hl,bc ;add to x previous term
- ld de,origin ;last term
- add hl,de ;final sum is in HL
- ld (xyaddr),hl ;store result
- pop de ;retrieve y coordinate
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Output routine
- ; inputs:
- ; memory map starting @ origin
- ; outputs:
- ; map is dumped to printer 1 byte at a time
- ; mixed graphics and text are output
- mapout:
- xor a ;reset status counter
- ld (statno),a
- ld c,9 ;printing status message
- ld de,stat3
- call bdos
- call ln772 ;set printer to 7/72in line spacing
- ld hl,0
- ld (ngraph),hl ;initialize graphics counter
- ld hl,origin ;initialize start address
- ld c,[maxy+1]/7 ;initialize line counter
- linloop:
- ld de,maxx+1 ;initialize dot counter
- bytloop:
- ld b,(hl) ;get byte
- ld a,b ;put byte in A
- or a ;set flags - is it a graphic byte?
- call m,charout ;no- hi bit set therefore character
- call p,gbufin ;yes- save it in graphic buffer
- inc hl ;incr address to next x location
- dec de ;decr dot counter
- ld a,d
- or e ;is dot counter = 0?
- jr nz,bytloop ;no- so loop to top again
- call gbufout ;at end of line- flush buffer
- call crlf ;send a line feed to printer
- dec c ;decr line counter
- jr nz,linloop ;not done- repeat outer loop
- call preset ;reset printer to normal mode
- ret ;last line finished
- ;
- ;-----------------------------------------------------------------------
- ; Move to new coordinates without doing anything else
- ; inputs:
- ; coordinate pair in buffer
- ; outputs:
- ; xpos and ypos updated to new coordinates
- move:
- call readxy ;get coordinate pair
- ld hl,(x) ;get x coordinate
- ld (xpos),hl ;update x axis position
- ld hl,(y) ;get y coordinate
- ld (ypos),hl ;update y axis position
- ret ;position now updated.
- ;
- ;-----------------------------------------------------------------------
- ; Multiply BC by DE, result in DEHL
- mult:
- ld a,e ;load low byte of multiplier
- push de ;save high byte of multiplier
- call bmult ;do 1-byte multiply
- ex (sp),hl ;save low bytes product, get multiplier
- push af ;store high byte of first prod.
- ld a,h ;load high byte of multiplier
- call bmult ;do 1-byte multiply
- ld d,a ;position high byte of product
- pop af ;get high byte of first product
- add a,h ;update third byte of product
- ld e,a ;and put it in e
- jr nc,nc1 ;don't incr D if no carry
- inc d ;incr D if carry
- nc1:
- ld h,l ;relocate low bytes of 2nd prod
- ld l,0
- pop bc ;get low 2 bytes of first prod.
- add hl,bc ;get final product low 2 bytes
- ret nc ;done if no carry
- inc de ;otherwise update high 2 bytes
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Print or disk o/p routine
- ; inputs:
- ; 5 in C
- ; character in (e)
- ; buffer pointer set to last character (pointr2)
- ; o/p flag in opdisk
- ; outputs:
- ; character printed if o/p flag set
- ; character written to disk if flag is set
- pdos:
- ld a,(opdisk) ;get disk o/p flag
- or a ;is flag set?
- push af ;save flag
- call z,bdos ;print character if it is
- pop af ;retrieve flags
- ret z ;return if character was printed
- ld hl,pointr2 ;get buffer pointer
- inc (hl) ;incr pointer for new char.
- ld c,(hl) ;save pointer value in BC
- ld b,0
- ld hl,obuff-1 ;get last addr. before obuff
- add hl,bc ;calculate address of byte
- ld (hl),e ;put character in buffer
- ld a,128
- cp c ;is buffer full?
- call z,write ;write it out if it is.
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Plot a point @ xdot,ydot
- ; method:
- ; find byte containing xdot,ydot
- ; form mask eg: if xdot,ydot is in #4 bit,
- ; mask = 00010000
- ; digit= 76543210
- ; modify byte according to color & store it back
- ; inputs:
- ; 2 byte x location stored @ xdot
- ; 2 byte y location stored @ ydot
- ; outputs:
- ; xpos, ypos reset to values given in xdot, ydot
- ; appropriate dot turned on or off in memory map
- plotdot:
- ld bc,(xdot) ;get x position
- ld (xpos),bc ;update current position
- ld de,(ydot) ;get y position
- ld (ypos),de ;update current position
- ;xpos and ypos now contain last pos. attempted- may not be in window
- ld hl,maxx ;put limits of x in hl
- bit 7,b ;check for neg x-sign in hi byte
- ret nz ;xdot neg- return w/o plotting
- or a
- sbc hl,bc ;compare max & x high bytes
- ret c ;x>max- therefore return
- ld hl,maxy ;put limit of y in hl
- bit 7,d ;ydot hi byte contains sign
- ret nz ;ydot neg- return w/o plotting
- or a
- sbc hl,de ;compare max & y high bytes
- ret c ;y>max- return w/o plotting
- ld hl,maxy ;y limit
- call locdot ;get address of byte for x,ydot
- call digit ;form mask for plotting
- bit 7,b ;determine if byte is graphic
- ret nz ;minus= character: return w/o plotting
- ld a,(color) ;get color value
- or a ;set flags
- jr z,white ;0 = white
- jp m,compl ;-1 = complementary color
- ld a,b ;color is black
- or c ;modify byte by turning bit on
- ld (hl),a ;store back in memory
- ret
- ;
- white:
- ld a,b ;work w/ byte containing x,y
- cpl ;complement byte
- or c ;modify byte by turning on bit
- cpl ;complement byte back- bit off
- ld (hl),a ;store byte back in memory
- ret
- ;
- compl:
- ld a,b ;work w/ byte containing x,y
- xor c ;complement bit
- ld (hl),a ;store it
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Plot point routine
- ; inputs:
- ; buffer @ tbuff
- ; outputs:
- ; point plotted in memory
- point:
- call readxy ;read coordinates for point
- ld hl,(x)
- ld (xdot),hl
- ld hl,(y)
- ld (ydot),hl
- call plotdot ;plot point
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Quit - closes output file, terminates program
- ; inputs:
- ; fcb for output file @ fcb2
- ; disk output flag @ opdisk
- ; outputs:
- ; remainder of record set to 0, disk closed.
- quit:
- ld a,(opdisk) ;get disk output flag
- or a ;is it set?
- jp z,exit ;no, so all done
- ld e,(iy+29)
- ld c,32
- call bdos ;set o/p user #
- ld a,(pointr2) ;look @ o/p pointer
- or a ;is o/p buffer empty?
- jp z,exit ;yes- done
- ld e,a ;save pointer value in E
- ld d,0
- ld a,128 ;set max value of pointer
- sub a,e ;A= 128- pointr2
- ld c,a ;C now is count of extra buff.
- clrbuf:
- push bc ;save counter
- ld e,0 ;output a <null>
- call pdos
- pop bc ;retrieve counter
- dec c ;decr it
- jr nz,clrbuf ;loop back until buffer is full
- ld c,16 ;close file
- ld de,fcb2 ;o/p fcb
- call bdos
- jp exit
- ;
- ;-----------------------------------------------------------------------
- ; Line segment routine
- ; inputs:
- ; file buffer @ tbuff
- ; outputs:
- ; xpos, ypos updated to x2,y2
- ; visible portion of line segment plotted
- plotseg:
- call readxy ;get starting coordinates
- ld hl,(x)
- ld (xdot),hl
- ld hl,(y)
- ld (ydot),hl
- call plotdot ;plot starting point
- call incplt ;plot rest of segment
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Reset the printer to its normal mode
- preset:
- ld c,5
- ld e,ESC
- call pdos
- ld c,5
- ld e,'2'
- call pdos ;esc 2 sets line spacing to 6 lines/in.
- ld c,5
- ld e,cr ;send carriage return to reset head
- call pdos
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Read record
- ; inputs:
- ; opened file
- ; file control block @ fcb
- ; 128 char file buffer @ tbuff
- ; 1 byte character pointer @ pointer
- ; outputs:
- ; character pointer reset to 0
- ; new record in file buffer
- ; eof: jump to eofexit instead of normal return
- read:
- ld e,(iy+13)
- ld c,32
- call bdos ;set user #
- ld c,26 ;set dma
- ld de,tbuff ;buffer
- call bdos
- ld c,20 ;sequential read
- ld de,fcb
- call bdos ;read record into buffer @ tbuff
- or a ;read ok?
- jr z,setpntr ;reset pointer if not eof
- pop bc ;pop return addr off stack
- jr eofexit ;goto exit instead of normal rtn
- setpntr:
- xor a
- ld (pointer),a ;reset pointer to 0
- ret
- ;
- eofexit:
- ld c,9 ;print string
- ld de,eofmsg
- call bdos ;print eof message
- jp exit ;return
- ;
- ;-----------------------------------------------------------------------
- ; Get an xy pair and convert it to raster values.
- ;The general algorithm is:
- ;integer = (fixed point) * (number of rasters) * 2/ 2^16
- ;the fixed point number is a 15 bit value in the range 0 to 1.
- ;when viewed as an integer, the fixed point coordinates range from
- ;0 to 32767. when multiplied by the range of the raster coordinates,
- ;they must be divided by 32767 to represent the true value. this is
- ;approximated by multiplying by 2 / 65536 (2/64k). dividing by 64k
- ;is accomplished by simply disregarding the lower 2 bytes of the result
- ;
- ; inputs:
- ; 128 character buffer @ tbuff
- ; character pointer @ pointer
- ; outputs:
- ; two byte value stored @ x
- ; two byte value stored @ y
- readxy:
- call byte ;get first byte of x
- push af ;save first byte
- call byte ;get second byte
- ld b,a ;put high byte in B
- pop af ;get low byte
- ld c,a ;BC now contains x coord.
- ld de,maxx*2 ;maximum raster address
- call mult ;multiply x coord by no. of x rasters
- ex de,hl ;put high bytes in HL
- ld (x),hl ;store corresponding raster x coordinate
- call byte ;get first byte of y
- push af ;save first byte
- call byte ;get second byte
- ld b,a ;put high byte in B
- pop af ;get low byte
- ld c,a ;BC now contains y coord.
- ld de,maxy*2 ;maximum raster address
- call mult ;multiply y coord by no. of y rasters
- ex de,hl ;put high bytes in HL
- ld (y),hl ;store corresponding raster y coordinate
- ret
- ;
- ;---------------------------------------
- ; Rotates the patterns used for erasing to a color
- ; inputs:
- ; array of 8 pattern bytes stored at patrn
- ; outputs:
- ; array is rotated one bit down
- rotpat:
- exx
- ld b,8 ;initialize counter
- ld hl,patrn ;initialize address of head of array
- rotpt1:
- rrc (hl) ;rotate byte
- inc hl ;move pointer to next byte
- djnz rotpt1 ;loop back until done
- exx
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Initialize the variables used in computing a line segment
- ; inputs:
- ; xpos,ypos present position
- ; x,y end points of segment
- ; outputs:
- ; dx,dy x,y sizes of line segment
- ; epslnx,epslny,sx,sy,delta3 internal variables initialized
- ; ni counter used to determine when done
- seginit:
- ld hl,(x) ;get x
- ld de,(xpos) ;put present pos in hl
- or a
- sbc hl,de ;calculate delta x
- ld (deltax),hl
- bit 7,h ;record sign of dx
- push af ;save flags
- ld hl,(y) ;get y end point value
- ld de,(ypos) ;get present y position
- or a
- sbc hl,de ;calculate delta y (dy)
- ld (deltay),hl ;store dy
- ld hl,0 ;initialize variables
- ld (sx),hl
- ld (epslny),hl
- inc hl
- ld (sy),hl
- ld (epslnx),hl
- pop af ;recover flags
- jr z,chkdy ;if dx was positive
- ld hl,-1 ;change initialization for -dx
- ld (epslnx),hl
- ld hl,(deltax) ;change sign on dx
- ld a,h
- cpl
- ld h,a
- ld a,l
- cpl
- ld l,a
- inc hl
- ld (deltax),hl ;store now positive dx
- chkdy:
- ld hl,(deltay) ;get dy
- bit 7,h ;check if positive
- jr z,chdxdy ;dy is pos- goto transpose axes
- ld a,h ;dy is negative- change sign
- cpl
- ld h,a
- ld a,l
- cpl
- ld l,a
- inc hl
- ld (deltay),hl ;store the now pos. dy
- ld hl,-1
- ld (sy),hl ;sy= -1
- chdxdy:
- ld de,(deltax) ;transpose axes if dx<dy
- ld hl,(deltay) ;get delta y
- push hl
- or a
- sbc hl,de ;dx < dy ? (high bytes first)
- pop hl
- jr c,lstinit ;dx definitely > dy
- ld (deltax),hl ;dy was in hl- store as dx
- ld (deltay),de ;store old dx as new dy
- ld hl,(epslnx)
- ld (sx),hl ;reinitialize: sx= epsilon x
- ld hl,(sy)
- ld (epslny),hl ;epsilon y = sy
- ld hl,0
- ld (epslnx),hl ;epsilon x = 0
- ld (sy),hl ;sy = 0
- lstinit:
- or a ;clear flags
- rr d ;calculate deltax/2 by shifting 1 right
- rr e
- ld (delta3),de ;store in delta3
- ld hl,1 ;set ni=1
- ld (ni),hl
- ret
- ;
- ;------------------------------------------------------------------------
- ; Status message routine
- ; this routine displays a message to indicate that the program
- ; is working.
- ; inputs:
- ; current count stored in statno
- ; outputs:
- ; message displayed
- stat:
- push af ;save registers
- push bc
- push de
- push hl
- ;
- ld a,(statno) ;get counter
- inc a ;update counter
- ld (statno),a
- ld c,9
- cp 1
- jr nz,statm2
- ld de,stat1
- call bdos ;print message
- jr statx
- ;
- statm2:
- cp 128 ;check for other message
- jr nz,statx ;not time for either message
- ld de,stat2
- call bdos ;print other message
- statx:
- pop hl ;restore registers
- pop de
- pop bc
- pop af
- ret
- ;
- ;------------------------------------------------------------------------
- ; String plotting routine
- ; method:
- ; ASCII code is stored repeatedly in the area occupied by
- ; the character (cwidth rasters). Hi bit is set to
- ; indicate that the byte is ascii and not dot image.
- ; input:
- ; x,y in file buffer
- ; bytes read sequentially from buffer until carriage rtn
- ; is encountered.
- ; outputs:
- ; each character is stored in the byte containing the bit
- ; map coordinate indicated for the character
- ; x,y locations < 0 are reset to 0
- ; x,y locations > max are reset to 0
- string:
- call readxy ;get starting coordinates
- strng0:
- call byte ;get first character
- cp cr ;is character a carriage return?
- ret z ;yes- so return (all done)
- or 10000000b ;set high bit
- ld b,a ;save byte in B
- ld hl,(x) ;get x location
- bit 7,h ;look at msb
- jr nz,resetx ;x is negative- reset to 0
- ld de,maxx-cwidth ;get maximum x value
- or a
- sbc hl,de
- jr c,strng1 ;max definitely > x (x is ok)
- jr z,strng1 ;equal : x is barely ok
- resetx:
- ld hl,0
- ld (x),hl ;x=0
- strng1:
- ld hl,(y) ;fetch y starting location
- bit 7,h ;look at y msb
- jr nz,resety ;negative - reset to 0
- ld de,maxy ;use entire coordinate range for y
- or a
- sbc hl,de ;compare max and y high bytes
- jr c,strng2 ;y definitely ok
- jr z,strng2 ;y = max
- resety:
- ld hl,0 ;clear old value of y
- ld (y),hl ;y = 0
- strng2:
- ld de,(y) ;put y in DE
- ld hl,(x) ;fetch x
- push bc ;save byte
- push de ;save y coord
- ; make x coord. a multiple of cwidth for proper printer output
- ld (divdnd),hl ;compute x=(x/cwidth)*cwidth
- ld a,cwidth ;get cwidth for divisor
- ld (divsor),a
- call divide ;divide x by cwidth
- ld a,(qotent) ;get results (no overflow as 0<=x<1530)
- ld bc,cwidth ;pass character width
- call bmult ;HL now contains (x/cwidth)*cwidth
- ld b,h ;put x in BC
- ld c,l
- pop de ;retrieve y coordinate
- ld hl,maxy ;put max y in HL
- call locdot ;get location of byte
- pop bc ;retrieve byte
- ld (hl),b ;put byte in address containing x,y
- ; store byte repeatedly to blank out entire area occupied by it
- ld a,cwidth-1 ;initialize loop counter
- strng3:
- inc hl ;increment address
- ld (hl),b ;store byte
- dec a ;decr loop counter
- jr nz,strng3 ;loop back up until finished
- ld c,cwidth
- ld hl,(x) ;fetch x location
- ld b,0
- add hl,bc ;incr x location for next character
- ld (x),hl ;store new x location
- jr strng0 ;loop up to top
- ;
- ;-----------------------------------------------------------------------
- ; Text - outputs text immediately to the printer
- ; note: text is not put into memory map
- ; inputs:
- ; text string in file (ends with 0 byte)
- ; outputs:
- ; text string printed
- text:
- call byte ;get next character
- or a ;check for end of string
- ret z ;return if finished
- ld e,a
- ld c,5 ;lst: output
- call pdos ;print it
- jr text ;loop back until done
- ;
- ;-----------------------------------------------------------------------
- ; Upload the array defining color palette
- ; inputs:
- ; 16 bit integer specifying # of data bytes to come
- ; data bytes in input file
- ; outputs:
- ; new color values stored in appropriate arrays
- upload:
- call byte ;get low byte of integer
- ld c,a ;save in C
- call byte ;get high byte
- or a ;check value of high byte
- jr nz,upbad ;for this program, hi byte must be 0
- ld a,c ;look at low byte
- cp 7 ;7 indicates upload plaid patterns
- jr z,uplaid ;proceed to upload plaid values
- cp 64 ;64 indicates upload dither matrix
- jr z,updith ;proceed to upload dither matrix
- cp 120 ;120 indicates upload special patterns
- jr z,upcif ;proceed to upload special patterns
- upbad:
- call byte ;# has unexpected value- skip bytes
- dec bc ;decr loop counter
- ld a,c
- or b ;is counter = 0 ?
- jr nz,upbad ;loop back until finished
- ret
- ;
- uplaid:
- ld hl,plaids+1 ;point to plaid array (leave "0" alone)
- jr uplp1 ;proceed to read-store loop
- upcif:
- ld hl,cifpat ;set pointer at start of special patterns
- jr uplp1
- updith:
- ld hl,ditharr ;point to dither array
- uplp1:
- call byte ;get color pattern
- ld (hl),a ;store pattern
- inc hl ;point to next pattern slot
- dec c ;decr counter
- jr nz,uplp1 ;loop back until finished
- ret
- ;
- ;-----------------------------------------------------------------------
- ; Overflow occured in mult. or div
- ; inputs:
- ; none
- ; outputs:
- ; message "overflow"
- ; all registers pushed on stack
- ; in order: af,hl,de,bc
- ; final position of stack pointer saved in oldstk
- woops:
- push af ;save all registers
- push hl
- push de
- push bc
- ld hl,0
- add hl,sp ;get stack pointer
- ld (oldstk),hl ;save stack pointer for debug
- ld c,9 ;print
- ld de,ovflmsg
- call bdos ;print 'overflow'
- jp exit
- ovflmsg:
- db 'OVERFLOW$'
- ;
- ;-----------------------------------------------------------------------
- ; Write record
- ; inputs:
- ; opened file
- ; file control block @ fcb2
- ; buffer @ obuff
- ; buffer pointer @ pointr2
- ; outputs:
- ; buffer written to file
- ; buffer pointer reset to 0
- write:
- ld e,(iy+29)
- ld c,32
- call bdos ;set o/p user #
- ld c,26 ;set dma
- ld de,obuff ;o/p buffer
- call bdos
- ld c,21 ;write sequential
- ld de,fcb2 ;o/p fcb
- call bdos
- or a ;was write ok?
- jr nz,fullxit ;jump to error section if not
- xor a
- ld (pointr2),a ;pointr2=0
- ret ;done with successful write
-
- fullxit:
- ld c,9
- ld de,noroom ;error message
- call bdos
- jp exit
- ;
- ;-----------------------------------------------------------------------
- ; Non-standard extensions to Zplot
- ; inputs:
- ; none
- ; outputs:
- ; none
- xtend:
- push af
- push bc
- push de
- push hl
- call byte ;get low byte of number of data bytes
- ld a,c
- call byte ;get high byte of number of bytes
- ld a,b ;BC is now 16 bit integer
- or c ;is number = 0?
- jr z,xtnd2 ;finished if n = 0
- xtnd1:
- call byte ;get data byte
- dec bc ;decr counter
- ld a,c
- or b ;is counter = 0 ?
- jr nz,xtnd1 ;loop back if more to come
- xtnd2:
- pop hl ;restore registers
- pop de
- pop bc
- pop af
- ret
- ;
- ;-----------------------------------------------------------------------
- origin:
- ;start of picture map
- ;-----------------------------------------------------------------------