Technical Reference

High Resolution Graphics


10.1 Introduction

In the high resolution mode, all 16 bits of each font cell word are displayed. The screen buffer is filled with pointers to successive cells in dynamic RAM and the programmer must manipulate the contents of dynamic RAM to create the required display. To set up a hi-res screen, there are 3 steps which must be performed.

  1. A 40k byte region in dynamic RAM should be chosen and cleared for use as a high-res screen area.
  2. The screen buffer is then filled with pointers to this area of dynamic RAM.
  3. The CRT controller is reprogrammed to give the correct timing for the hi-res mode.
10.2 Clearing a Hi-Res area

The starting address of the hi-res screen must be on a 32 byte boundary (ie. an address that is divisible by 32). This is because the lower 4 address bits are used by the CRT controller to address the 16 words of the font cell. The hi-res screen must be contained completely in the upper or lower 64K segment of the first 128K block of memory (0 - 1FFFFh).

As CP/M loads into the top of memory and loads programs directly below itself, a convenient place for a hi-res screen is directly above the operating system character table at location 2C00h (see Memory Allocation Map of CP/M system, section 1.6.2).

This area can also be used under MS-DOS except that this area above the character table must be claimed by the user. This is because the programs are loaded directly above the character table under MS-DOS. It is therefore necessary for the user to include a 40,000 byte buffer at the start of the software. It is also necessary for the user to ensure that the start of the buffer lies on a 32 byte boundary. This can be done by loading the ES segment register contents and ensuring that it is divisible by 32 with no remainder.

The following routine clears 40,000 bytes starting at location 2C00h.

  MOV
MOV
MOV
MOV
MOV
BX,02C0H
ES,BX
BX,0
CX,4E20H
AX,0
;ES segment points to our hi-res screen
 
;use BX to index the 40k byte RAM area
;counter for 20,000 words
;store 0 throughout the RAM area
CLEAR: MOV
INC
INC
LOOP
ES:[BX],AX
BX
BX
CLEAR
 
;next word

10.3 Setting the Screen Buffer Pointers

We have defined our high resolution screen to start at address 2C00h and so our first pointer must be 2C00h divided by 32. (ie. the word in screen RAM represents the upper 11 bits of address to dynamic RAM; the CRT controller supplies the lower 4 bits). This means the screen pointers should start at 0160h. Incrementing this number by one translates to an increment in the address of 16 (ie. one complete cell). The following routine fills the screen buffer with pointers to our high resolution screen. Note we only fill 25 rows x 50 columns = 1250 bytes of the 4096 bytes available in the buffer.

  MOV
MOV
MOV
MOV
MOV
BX,0F000H
ES,BX
BX,0
CX,0432H
AX,0160H
;address screen buffer RAM
 
;BX indexes the 4k RAM area
;1250 byte counter
;starting address of DRAM pointers
STORE:
MOV
INC
INC
INC
LOOP

ES:[BX],AX
BX
BX
AX
STORE

;store font pointer
;next word

;next DRAM pointer

10.4 Reprogramming the 6845 CRT Controller

In order to derive the correct timing from the display circuit, 16 of the internal registers should be reloaded. The correct data for both the text and high resolution modes are shown on page 99 of the Hardware Reference Manual. The following routine transfers the 16 bytes of data in the table to the 16 internal registers of the CRT controller.

  mov
mov
mov
mov
mov
mov
bx,0E800h
ex,bx
bx,0
si,0001h
cx,offset data
dl,0
;address CRT controller
 
 
 
;pointer to register string
loop: mov
inc
mov
xchg
mov
xchg
inc
mov
cmp
jnz
al, dl
dl
es:[bx],al
bx,cx
al,[bx]
bx,cx
cx
es:[bx+si],al
dl,11h
loop
;set address register AR
;address next register

;point to data
;get data byte

;address next byte
;set register
;last register ?
;no: address next register

data

db
db

3Ah,32h,34h,0C9h,19h,06h,19h
19h,03h,0Eh,20h,0Fh,20h,0,0,0

10.5 Examples 10.5.1 Microsoft MACRO-86 Assembly Language

This assembly-language routine demonstrates two things, one, interfacing an assembly-language routine to the MS-Basic interpreter and two, using the high-resolution graphics from MS-Basic.

  1. To interface an assembly-language routine to MS-Basic the routine must load itself into memory then exit and remain resident (int 27h). This is done before Basic is loaded. The routine must locate its position in memory and report this either to the programmer or to the subsequent Basic program. This example does the former. It determines the value of the CS register which is to be used in a Basic DEF SEG statement and the entry point for Basic to be used as an OFFSET.

    The program prints these values on the screen in a form which can be used by Basic directly. The form is:

    10 DEF SEG=&Hxxxx
    20 HI.RES=&Hyyyy
    30 CALL HI.RES

    where xxxx is the hexadecimal value of CS and yyyy is the hexadecimal value of the offset within the segment. A Basic program including the above code execute the code starting at location INIT: in the listing. The alternative method is for the routine to leave these values in some known memory location which can be interrogated by a Basic program. Suitable locations are to be found in the Interrupt Vector Table (see Appendix I.2), namely interrupts 80h to BFh, which are reserved for use by application programs. See the IEEE-488 Toolkit, Audio Toolkit and Network Users Guide for examples.


  2. Details of how the high-resolution screen works can be found in the Hardware Reference Manual and the Supplementary Technical Reference Manual. This program sets aside a 40k (decimal) buffer (initialised to zero) for the high- resolution screen, which must start on a 32-byte boundary. The software locates the first available 32-byte boundary and reports this to the programmer. When called from Basic the routine initialises the screen pointers and the CRT controller then returns to Basic. This routine could be extended to include specialised graphics functions for particular applications where the Grafix Kernel (found in the Graphics Toolkit) either does not provide the required functions or is too general. Provided this extended routine and the application package are not too large, they could easily run in a 128K machine.

When Basic calls an assembly-language routine it pushes the return address and the value of its CS onto the stack, then enters the called routine. This routine must save any other segment registers it intends using.

This example uses DS and ES.

code		segment
		assume	cs:code,ds:code
; Written by	Greg Johnstone and Keith Rea
;		
;		
;		16-9-83
;
; Program HI-RES
;
;
; Assemble this program as follows
;
;	MACRO86 HI-RES;
;	LINK HI-RES;
;
; Link will produce a warning - 'No stack segment', ignore it. Link
; produces a file HI-RES.EXE which will not run. You must produce a 
; .COM file as follows:
;
;	DEBUG HI-RES.EXE
;	N HI-RES.COM
;	W
;	Q
;
; The resulting program HI-RES.COM will run
;
buf_st	equ	190h		; offset to hi-res buffer
scrn_rm	equ	0f000h		; segment address of screen RAM
count	equ	1250		; no. of cell locations in hi-res mode
crt	equ	0e800h		; segment address of CRT controller
bdos	equ	21h		; MS-DOS function call
boot	equ	00h		; exit to MS-DOS function.
conout	equ	02h		; console output function.
cr	equ	0dh		; carriage return
lf	equ	0ah		; line feed
esc	equ	1bh		; escape
	org	100h
loader	proc	near
start:
	call	main		; find out where routine loaded in RAM
;
; Exit and remain resident
;
	mov	dx,offset top+1	; Set DX to the top of part to remain ..
	int	27h		; .. resident then quit.
loader	endp
basic	proc	far
; Set screen RAM pointers to font RAM work area
init:
	push	es		; save segment registers used by Basic ..
	push	ds
	mov	ax,cs		; ..and point DS to current CS
	mov	ds,ax
	mov	bx,scrn_rm	; point to screen ram
	mov	es,bx
	mov	bx,0
	mov	cx,count	; counter for 1250 cells
	mov	ax,hi_res	; starting address of pointers ..
	shr	ax,1		; .. = RAM address/2
init1:	
	mov	es:[bx],ax	; store font pointer
	inc	bx		; address next word and put ..
	inc	bx
	inc	ax		; .. next font cell
	loop	init1
; set CRT controller for high resolution
	mov	bx,crt		; point to CRT controller
	mov	es,bx
	mov	bx,0
	mov	si,1
	mov	cx,offset data	; point to register string
	mov	dl,0
init2:	
	mov	al,dl		; set address register AR
	inc	dl		; address next register
	mov	es:[bx],al
	xchg	bx,cx		; point to data
	mov	al,[bx]		; get data byte
	xchg	bx,cx
	inc	cx		; address next byte
	mov	es:[bx+si],al	; set register
	cmp	dl,11h		; last register?
	jnz	init2		; no, address next register
	pop	ds		; restore Basic's segment registers
	pop	es
	ret
data:	db	3ah,32h,34h,0c9h,19h,06h,19h
	db	19h,03h,0eh,20h,0fh,20h,0,0,0
enddata:
	org	buf_st		; start graphics buffer on 16 ..
				; .. byte boundary. Initialise to 0
				; reserve extra 16 bytes just in case ..
buff:	db	40016 dup(0)	; .. it falls on an odd boundary.
hi_res:	dw	0		; segment address of hi-res RAM
top:				; routine up to here needs to stay in RAM.
basic	endp
load2	proc	near
; Now we have to figure out where we are in memory and tell everyone
; about it.
main:
	call	msprnt		; Print the following message
	db	esc,'E','HI-RES ver. 1.0',cr,lf
	db	cr,lf,'Hi-res graphics interface for MS-Basic interpreter'
	db	cr,lf,cr,lf
	db	'Include the following statements in your program',cr,lf,cr,lf
	db	'	10 DEF SEG=&H',0
;
; get the segment address
;
	mov	ax,cs		; Get the contents of CS register ..	
	call 	hexprnt		; .. convert to hex and print it
	call	msprnt		; print next message
	
	db	cr,lf
	db	'	20 HI.RES=&H',0
;
; get the entry point for Basic
;
	mov	ax,offset init	; Get offset of the start of the ..
	call	hexprnt		; .. routine and print it.
	call	msprnt
	db	cr,lf
	db	'	30 CALL HI.RES'
	db	cr,lf
	db	'The hi-res screen starts at segment address &H',0
;
; now lets find where we put the hi-res screen
;
	mov	ax,cs		; point to CS
	add	ax,buf_st/16	; add offset to start of hi-res ram
	test	al,1		; check if on 32-byte boundary. Segment ..
	jz	main1		; .. address should be even if it is.
	inc	ax		; if odd, make it even ..
main1:
	mov	hi_res,ax	; .. and save it.
	call	hexprnt
	call	msprnt
	db	cr,lf,'Use DEF SEG to point to this location in memory and'
	db	cr,lf,'start POKEing data into hi-res RAM',cr,lf,0
	ret
;
; subroutine MSPRINT - print bytes following the CALL till zero
;
msprnt:	
	pop	bp		; get message starting address
	mov	al,cs:[bp]	; get byte pointed to by bp
	inc	bp		; next byte
	push	bp
	and	al,al		; is the byte equal to 0 ?
	jnz	msprnt1		; no: print it
	ret			; yes: end of string
msprnt1:	
	mov	dl,al		; console output routine
	mov	ah,conout
	int	bdos
	jmp	msprnt
;
; subroutine HEXPRNT - convert a byte to hex and print it
;
hexprnt:
	push	ax
	xchg	ah,al
	call	hexprnt1
	pop	ax
	call	hexprnt1
	ret
hexprnt1:	
	mov	dl,al		; save the byte
	and	al,0fh		; get lower nibble
	mov	cl,04h		; then the upper nibble
	sar	dl,cl
	and	dl,0fh
	cmp	dl,09h		; if less than 10 then get the ..
	jg	hexprnt2	; .. ASCII value of the numeric digit
	add	dl,30h
	mov	hi_byte,dl
	jmp	hexprnt3
hexprnt2:	
	add	dl,37h		; else get the ASCII value of the ..
	mov	hi_byte,dl	; .. alpha digit
hexprnt3:	
	cmp	al,09h		; repeat for upper nibble
	jg	hexprnt4
	add	al,30h
	mov	lo_byte,al
	jmp	hexprnt5
hexprnt4:	
	add	al,37h
	mov	lo_byte,al
hexprnt5:	
	mov	dl,hi_byte	; print the hex. bytes, one at a time
	mov	ah,conout
	int	bdos
	mov	dl,lo_byte
	mov	ah,conout
	int	bdos
	ret
lo_byte	db	'0'		; hex value of lower nibble (in ASCII)
hi_byte	db	'0'		; hex value of upper nibble (in ASCII)
load2	endp
code	ends
	end	start

10.5.2 Microsoft MS-BASIC Interpreter

This program calls the routine given in section 10.5.1.

100 ROUTINE=&H2C8	'Segment address of HI-RES
110 SCREEN=&H2E2	'Segment address of hi-res screen
120 PRINT CHR$(27);"z"	'Clear screen
130 PRINT CHR$(27);"x5"
140 DEF SEG=ROUTINE	'Point to start of HI-RES segment
150 HI.RES=&H108	'Offset to HI-RES
160 CALL HI.RES		'Initialise hi-res screen
170 GOSUB 250		'Throw some data in it
180 A$=""		'Hang about till someone presses a key
190 WHILE A$=""
200 A$=INKEY$
210 WEND
220 PRINT CHR$(27);"z"	'Put screen back into character mode
230 END			'And that's it folks
240 '
250 DEF SEG=SCREEN	'Point to start of hi-res screen
260 FOR I=0 TO 31 STEP 2'Start filling hi-res RAM, a word at a time
270 READ HI,LO	'Remember that the screen displays bit 0 first
280 POKE I,LO: POKE I+1,HI
290 NEXT
300 RETURN
310 'This data prints the letter G in the top left corner 315 ' of hi-res screen
320 DATA 255,255,128,1,128,1,128,1,0,1,0,1,0,1,0,1
330 DATA 0,1,255,1,128,1,128,1,128,1,128,1,128,1,255,255

10.6 Printer Configuration Tables in the Grafix Kernel
 	 	 	; Printer  configuration tables for Grafix  ver. 
                        ; 1.2.  To get addresses for Grafix ver. 1.3 add 
                        ; 10h to each address.
                        ;
			; The  printer configuration tables contain  the 
                        ; following information.
                        ;
 	 	 	; prttyp - printer  algorithm  type.  Currently, 
                        ;          all  printers use the same algorithm, 
                        ;          which is defined as type 1.   This is 
                        ;          the sequence of events:
                        ;	      1) send   initialisation    string 
                        ;                (initstr)
 	 	 	;	      2) send  beginning of line  string 
                        ;                (bolstr) 	 	 	 	
                        ;             3) send graphics string 1 (grstr1)
 	 	 	;             4) send    count    of    graphics 
                        ;                characters
 	 	 	;	      5) send graphics string 2 (grstr2)
 	 	 	;             6) send graphics characters
 	 	 	;             7) send end of line string (eolstr)
 	 	 	;             8) if more data, go to 2
 	 	 	;             9) send final string (finalstr)
 	 	 	;
 	 	 	; grcnt_typ - graphics   character  count  type. 
                        ;             There are currently 3 count  types 
                        ;             implemented.  1 = 2 hex bytes sent 
                        ;             as count.                                   
                        ;             2  =  3 ASCII  numeric  characters 
                        ;             sent as count
 	 	 	;             3 = no count is sent
                        ;
 	 	 	; eneedles -  the  number of needles used in the 
                        ;             print   head  to  print   graphics 
                        ;             characters.  This  is positive  if 
                        ;             the   top   dot   is   the   least 
                        ;             significant bit of the data  sent, 
                        ;             negative   if   it  is  the   most 
                        ;             significant bit.
 	 	 	;
 	 	 	; rtmin - the minimum number of characters  that 
                        ;         will be printed on a line. If the user 
                        ;         data  contains fewer  characters,  the 
                        ;         remainder sent will be blank (spaces).
 	 	 	
 = 0000	 	 	nul	 	equ	0
 = 0002	 	 	stx	 	equ	2
 = 0003	 	 	etx	 	equ	3
 = 000A	 	 	lf	 	equ	10
 = 000D	 	 	cr	 	equ	13
 = 000E	 	 	so	 	equ	14
 = 001B	 	 	escape	 	equ	27
 = 0020	 	 	space	 	equ	32
 = 00FF	 	 	 end_tblf	equ	0ffh	;end   of  table 
                                                        ;flag
 = 000A	 	 	 tbl_entry_lgth	equ	10 	;maximum   table 
                                                        ;string length
 	 	 	 	
 	 	 	 ;----------------------------------------------
                         ;--    Epson MX80/MX100 Configuration Data   --
 	 	 	 ;----------------------------------------------
 	 	 	 	
 = 3B41	 	 	 epson_tbl 	equ	$
 	 	 	 	 
 3B41  01	 	 ep_prttyp	db	1  ;epson algorithm typ
 3B42  01	 	 ep_grcnt_typ	db	1  ;epson format of 
                                                   ;graphics bytes
 3B43  0008	 	 ep_eneedles	dw	8  ;Epson num of scan 
                                                   ;lines/printed line
 3B45  0000	 	 ep_rtmin	dw	0  ;epson min line 
                                                   ;length to print
 3B47  04 0A 1B 41 08	 ep_initstr	db	4,lf,escape,'A',8;epson 
                                                   ;init string
 3B4C  02 1B 32	 	 ep_finalstr	db	2,escape,'2' ;epson 
                                                   ;final string
 3B4F   00  00	 	 ep_bolstr	db 	0,nul   ;epson beginning 
                                                   ;of line string
 3B51  02 0D 0A	 	 ep_eolstr	db	2,cr,lf	     ;epson end 
                                                   ;of line string
 3B54  02 1B 4C	 	 ep_grstr1	db	2,escape,'L' ;epson 
                                                   ;graphics mode
 3B57  00 00	 	 ep_grstr2	db	0,nul	     ;epson 
                                                   ;graphics mode
 3B59  FF	 	 ep_endf	db	end_tblf     ;end of 
                                                   ;table flag

 	 	 	 	
 	 	 	;-----------------------------------------------
 	 	 	;--  Tally Configuration Data	              --
 	 	 	;-----------------------------------------------
 	 	 	 	
 = 3B5A	 	 	 tally_tbl 	equ	$
 	 	 	 	
 3B5A  01	 	 t_prttyp	db	1	     ;tally 
                                                    ;algorithm type
 3B5B  01	 	 t_grcnt_typ	db	1	     ;tally 
                                                    ;format of graphics 
                                                    ;bytes
 3B5C  FFF8	 	 t_eneedles	dw	-8	     ;tally num 
                                                    ;of scan lines/printed 
                                                    ;lines
 3B5E  00C8	 	 t_rtmin	dw	200	     ;tally min 
                                                    ;line length to 
                                                    ;print
 3B60  00 00	 	 t_initstr	db	0,nul	     ;tally init 
                                                    ;string
 3B62  00 00	 	 t_finalstr	db	0,nul	     ;tally 
                                                    ;final string
 3B64  00 00	 	 t_bolstr	db	0,nul	     ;tally beg 
                                                    ;of line string
 3B66  02 0D 0A	 	 t_eolstr	db	2,cr,lf	     ;tally end 
                                                    ;of line string
 3B69  02 1B 4C	 	 t_grstr1	db	2,escape,'L' ;tally 
                                                    ;graphics mode
 3B6C  01 20	 	 t_grstr2	db	1,space	     ;tally 
                                                    ;graphics mode
 3B6E  FF	 	 t_endf	 	db	end_tblf     ;table end 
                                                    ;flag

 	 	 	;----------------------------------------------
 	 	 	;--   	 C. Itoh Configuration Data	     --
 	 	 	;----------------------------------------------
 	 	 	 	
 = 3B6F	 	 	 citoh_tbl 	equ	$
 	 	 	 	
 3B6F  01	 	 c_prttyp	db	1	     ;c.itoh 
                                                     ;algorithm type
 3B70  02	 	 c_grcnt_typ	db	2	     ;c.itoh 
                                                     ;format  of graphics 
                                                     ;bytes
 3B71  FFF8	 	 c_eneedles	dw	-8	     ;c.itoh num 
                                                     ;of scan lines/printed 
                                                     ;line
 3B73   0000 	 	 c_rtmin	 	dw 	0 	     ;c.itoh 
                                                     ;line length  to 
                                                     ;print
 3B75  08 1B 45 1B 54 31 c_initstr	db 8,escape,'E',escape,'T16',cr,lf
       36 0D 0A	 	                             ;c.itoh init string
 3B7E  04 1B 4E 1B 41	 c_finalstr	db	4,escape,'N',escape,'A'
                                                     ;c.itoh final string
 3B83  00 00	 	 c_bolstr	db	0,nul	     ;c.itoh beg 
                                                     ;of line string
 3B85  02 0D 0A	 	 c_eolstr	db	2,cr,lf	     ;c.itoh end 
                                                     ;of line string
 3B88  03 1B 53 30	 c_grstr1	db	3,escape,'S0';c.itoh 
                                                     ;graphics mode
 3B8C  00 00	 	 c_grstr2	db	0,nul	     ;c.itoh 
                                                     ;graphics mode
 3B8E  FF	 	 c_endf	 	db	end_tblf     ;table  end 
                                                     ;flag
 	 	 	 	 
 	 	 	 ;---------------------------------------------- 
 	 	 	 ;-- 	Okidata Configuration Data           --
                         ;----------------------------------------------
 	 	 	 ;
 	 	 	 ; The  Okidata printer has a 7 dot graphics head 
                         ; instead  of 8 dots.  Since our characters  are 
                         ; 10x16,  the Okidata is programmed to print the 
                         ; dots out in 4 rows of 4 dots each (instead  of 
                         ; 2 rows of 7 dots, with 2 dots left over). This 
                         ; allows  the program to use the same  algorithm 
                         ; type  for the Okidata as it uses for the other 
                         ; printers.  However,  it  is  slower  since  it 
                         ; requires 4 passes for every line of characters 
                         ; instead of two passes.
 	 	 	 	
 = 3B8F	 	 	 okidata_tbl 	equ	$
 	 	 	 	
 3B8F  01	 	 ok_prttyp	db	1            ;okidata 
                                                     ;algorithm type
 3B90  03	 	 ok_grcnt_typ	db	3	     ;okidata 
                                                     ;format of graphics 
                                                     ;bytes
 3B91  FFF9	 	 ok_eneedles	dw	-7	     ;okidata 
                                                     ;num of scan 
                                                     ;lines/printed line
 3B93  0001	 	 ok_rtmin	dw	1	     ;okidata 
                                                     ;line length to 
                                                     ;print
 3B95  01 1D	 	 ok_initstr	db	1,29	     ;okidata 
                                                     ;init string - 12 
                                                     ;chars/inch
 3B97  02 03 02	 	 ok_finalstr	db	2,etx,stx    ;okidata 
                                                     ;final string
 3B9A  00 00	 	 ok_bolstr	db	0,nul	     ;okidata 
                                                     ;beg of line string
 3B9C  02 03 0E	 	 ok_eolstr	db	2,etx,so     ;okidata 
                                                     ;end of line string
 3B9F  01 03	 	 ok_grstr1	db	1,etx	     ;okidata 
                                                     ;graphics mode
 3BA1  00 00	 	 ok_grstr2	db	0,nul	     ;okidata 
                                                     ;graphics mode
 3BA3  FF	 	 ok_endf	db	end_tblf     ;table  end 

                                                     ;flag
10.7 Patching the Grafix Kernel for the MT-180 Printer
A>DEBUG GRAFIX.COM

DEBUG-86  VERSION 1.07
>d3b00
0473:3B00 2E A0 3F 0E 2E 08 06 1A-0B C3 00 00 00 00 00 00 . ?......C......
0473:3B10 0A 00 00 00 00 00 00 00-00 00 00 00 00 00 00 00 ................
0473:3B20 00 00 00 00 00 00 00 00-00 00 00 00 00 00 00 00 ................
0473:3B30 00 00 00 00 32 00 00 00-00 00 00 00 00 00 00 00 ....2...........
0473:3B40 00 01 01 08 00 00 00 04-0A 1B 41 08 02 1B 32 00 ..........A...2.
0473:3B50 00 02 0D 0A 02 1B 4C 00-00 FF 01 01 F8 FF C8 00 ......L.....x.H.
0473:3B60 00 00 00 00 00 00 02 0D-0A 02 1B 4C 01 20 FF 01 ...........L....
0473:3B70 02 F8 FF 00 00 08 1B 45-1B 54 31 36 0D 0A 04 1B .x.....E.T16....
>e3b5c
0473:3B5C F8.08  FF.00  C8.00  00.
0473:3B60 00.01  00.0D  00.01  00.0C  00.    00.    02.    OD.
0473:3B68 OA.    O2.03  1B.    4C.25  01.34  20.00  FF.00  01.FF
>d3b00
0473:3B00 2E A0 3F 0E 2E 08 06 1A-0B C3 00 00 00 00 00 00 . ?......C......
0473:3B10 0A 00 00 00 00 00 00 00-00 00 00 00 00 00 00 00 ................
0473:3B20 00 00 00 00 00 00 00 00-00 00 00 00 00 00 00 00 ................
0473:3B30 00 00 00 00 32 00 00 00-00 00 00 00 00 00 00 00 ....2...........
0473:3B40 00 01 01 08 00 00 00 04-0A 1B 41 08 02 1B 32 00 ..........A...2.
0473:3B50 00 02 0D 0A 02 1B 4C 00-00 FF 01 01 08 00 00 00 ......L.........
0473:3B60 01 0D 01 0C 00 00 02 0D-0A 03 1B 25 34 00 00 FF ...........%4...
0473:3B70 02 F8 FF 00 00 08 1B 45-1B 54 31 36 0D 0A 04 1B .x.....E.T16....
>ngr180.com
>w
Writing 5409 bytes
>q
A>

Procedure for modifying GRAFIX Ver 1.2 to work with the Tally MT180 printer. This modifies the MT140 driver to use MT180 escape codes. To invoke the new version for BUSIGRAF, for example, type:

               GR180 $S1C3PS <cr>

NOTE that this modification clobbers the ability of GRAFIX to operate the C.ITOH printer, so you should keep your original copy of GRAFIX in case you wish to use a C.ITOH at a later date.

This modification also prints a Formfeed after the graphics dump is finished. If you do not want this feature then change bytes 3B62 and 3B63 to 00.

To patch Grafix Ver 1.3, add 10h to each of the above addresses. That is, start changing bytes at location 3B6C.

10.8 Character Printing

One of the Sirius 1's most useful graphics features seems to be greatly overlooked: its ability to do character graphics printing. If you design a keyboard file using Keygen that has special non-ASCII characters, and you try printing a document in the standard fashion, you will find that these special characters will not be printed.

Suppose, for instance, that you have loaded the future character set (FUTURE.CHR) into your system from the Graphics Toolkit. All the characters displayed on the CRT are in the future type, but when you try printing the file, you will find that the printed characters are once again the standard ASCII type. To remedy this, you must use the CHRPRINT.EXE file, also found on the Graphics Toolkit.

CHRPRINT.EXE causes documents to be printed in the same style in which they appear on the screen. This utility will work with any file, as long as the file has been saved in a standard ASCII format; thus, any file created with EDLIN, PMATE, BENCHMARK or WORDSTAR (using non-document mode), or any file just copied from the screen to a file, can be printed with a dot matrix printer in any number of character styles and scripts.

To call up CHRPRINT, type:

     CHRPRINT filename <cr>
10.9 Patching CHRPRINT for MT-180
A>ren chrprint.exe temp

A>debug temp

DEBUG-86 version 1.07
>d06c0
0473:06C0  02 0D 0A 02 1B 4C 00 00-46 01 01 F8 FF C8 00 00  .....L..F..x.H..
0473:06D0  00 00 00 00 00 02 0D 0A-02 1B 4C 01 20 46 01 02  ..........L. F..
0473:06E0  F8 FF 00 00 08 1B 45 1B-54 31 36 0D 0A 04 1B 4E  x.....E.T16....N
0473:06F0  1B 41 00 00 02 0D 0A 03-1B 53 30 00 00 46 01 03  .A.......SO..F..
0473:0700  FC FF 00 00 03 1D 0D 0A-07 1B 25 39 00 1E 0D 0A  |.........%9....
0473:0710  00 00 08 03 02 1B 25 39-08 0D 0A 01 03 00 00 46  ......%9.......F
0473:0720  00 00 00 00 00 00 00 00-00 00 00 00 00 00 00 00  ................
0473:0730  00 00 00 00 00 00 00 00-00 00 00 00 00 00 00 00  ................
>e06b
0473:06CB  F8.08   FF.00   C8.00   00.     00.01
0473:06D0  00.0d   00.01   00.0c   00.     00.     02.     0D.     0A.
0473:06D8  02.03   1B.     4C.25   01.34   20.00   46.00   01.46   02.01
0473:06E0  f8.02
>w
Writing 0980 bytes
>q

A>ren temp chrprint.exe

N.B. This fix probably clobbers other printer drivers so keep a spare copy of the original.



BACK


All contents of this website (including text, images, design, and presentation) are Copyright � 1999-2004,
ACT Sirius 1 User Group (UK) unless explicity stated otherwise. All Rights Reserved.
E-Mail: siriususer@eurobell.co.uk

Last revision 22/01/2003