Previous Next Contents Index
The printer routines

THE 'COPY SCREEN' ROUTINE
This routine has two entry points. The first one, #161E, is used with the BASIC
commands 'SAVE/LOAD/VERIFY/MERGE SCREEN$'. The second entry point (#1621) is used for
the 'COPY' command itself. Depending on the parameter following the 'SCREEN$', the
normal or the grey scale screen dump is used.

161E DUMP_SCR$  POP  HL                  Drop the return address (within the
                                         routine which called 'EXPT_PARMS').
161F            JR   #1627,COPY_1        Jump forward.

1621 COPY       RST  #28,NEXT_C_RAM      Advance CH_ADD.
1622            CP   170                 Give 'Nonsense in GDOS' error if
1624            JP   NZ,#2920,REP_0      command isn't followed by 'SCREEN$'.
1627 COPY_1     LD   A,"1"               Default is '1' for 'normal' dump.
1629            LD   (#1E00),A
162C            RST  #28,NEXT_C_RAM      Advance CH_ADD
162D            CP   13
162F            JR   Z,#1639,COPY_2      Jump with ENTER.
1631            CP   ":"
1633            JR   Z,#1639,COPY_2      Also jump with ':'.
1635            LD   (#1E00),A           Otherwise store character.
1638            RST  #28,NEXT_C_RAM      Update CH_ADD again.
1639 COPY_2     CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax checking.
163C            LD   A,(#1E00)
163F            CP   "1"                 Normal screendump if '1' followed the
1641            CALL Z,#164C,COPS        'SCREEN$'.
1644            CP   "2"                 Grey scale in case of a '2'.
1646            CALL Z,#16B2,COPS2       Ignore other values.
1649            JP   #0419,END           Finished.

THE 'NORMAL SCREENDUMP' SUBROUTINE
This routine dumps a normal screendump to the printer. It can be called also by using
command code 58 (#3A).

164C COPS       LD   HL,16384            Start of screen.
164F            LD   DE,#02BA            Print the escape sequence for n/72 inch
1652            CALL #1779,PO_ESC_SEQ    line feeds.
1655            LD   A,8                 Make it 8/72.
1657            CALL #1944,PNTP
165A C1_LINE    LD   DE,#02C2            Print the escape sequence for a normal
165D            CALL #1779,PO_ESC_SEQ    screendump. (60 dpi)
1660            LD   A,0                 Signal '256 dot columns will follow' to
1662            CALL #1944,PNTP          the printer.
1665            LD   A,1
1667            CALL #1944,PNTP
166A            PUSH HL
166B C1_CHAR    LD   B,8                 Eight pixels in each byte.
166D C1_PIXEL   PUSH HL
166E C1_PIXROW  CALL #1751,PIXEL_COL     Get pixel colour.
1671            AND  #04
1673            JR   NZ,#1676,C1_ADD_DOT Jump with colour codes 4-7 (no dot).
1675            SCF                      Set a dot for colour codes 0-3.
1676 C1_ADD_DOT LD   A,(#1978)           Incorporate one dot in dot column.
1679            RLA
167A            LD   (#1978),A
167D            INC  H                   Next pixel row.
167E            LD   A,H
167F            AND  #07
1681            JR   NZ,#166E,C1_PIXROW  Repeat until all eight pixelrows have
                                         been 'scanned'.
1683            LD   A,(#1978)
1686            CALL #1944,PNTP          Print the dot column.
1689            POP  HL                  Repeat until all eight pixels in a byte
168A            DJNZ #166D,C1_PIXEL      have been printed. One character cell (64
                                         pixels) has been printed now.
168C            INC  L                   Next character position.
168D            LD   A,L
168E            AND  #1F
1690            JR   NZ,#166B,C1_CHAR    Loop for all 32 character columns.
1692            CALL #16A2,ADV_PAPER     Advance printer paper one line.
1695            POP  HL
1696            LD   A,H
1697            ADD  A,8                 Make HL point to the next screen third.
1699            LD   H,A                 'N_CHARROW' will adjust HL if necessary.
169A            CALL #176C,N_CHARROW     Calculate the address of the next
169D            JR   NZ,#165A,C1_LINE    characterrow and loop until end of
                                         pixel area reached.
169F            JP   #1745,DUMP_EXIT     Exit via 'DUMP_EXIT' to reset printer.

THE 'ADVANCE PRINTER PAPER' SUBROUTINE
This subroutine advances the paper by sending a CR (carriage return) and (when needed)
a LF (line feed) to the printer.

16A2 ADV_PAPER  LD   A,13                Send a CR to the printer.
16A4            CALL #1944,PNTP
16A7            LD   A,(#02A0)           This is 'LFEED'.
16AA            AND  A
16AB            RET  Z                   Return if no LF has to be printed.
16AC            LD   A,10                Otherwise send a LF.
16AE            CALL #1944,PNTP
16B1            RET                      Finished.

THE 'GREYSCALE SCREENDUMP' SUBROUTINE
This routine prints a large screendump. It can also be called by using
command code 66 (#42).
NOTE: With System 3b this routine printed a greyscale dump but with the System 3c
'improvement' of the 'PIXEL_CLR' subroutine the greyscales have been limited to black
and white only. The routine now just produces a larger screendump (3*3 dots for each
pixel).

16B2 COPS2      LD   HL,#57E0            Address of the lowest pixelrow of the
                                         charactersquare in the bottom left corner.
16B5            LD   DE,#02BA            Print the escape sequence for n/72 inch
16B8            CALL #1779,PO_ESC_SEQ    line feeds.
16BB            LD   A,6                 Make it 6/72.
16BD            CALL #1944,PNTP
16C0            LD   B,128               There are 128 2-pixel columns.
16C2            LD   C,8                 8 pixels make one byte. Start with
                                         leftmost bit in a byte.
16C4 C2_2PIXCOL PUSH BC
16C5            PUSH HL
16C6            LD   DE,#02EA            Print the escape sequence for the
16C9            CALL #1779,PO_ESC_SEQ    greyscale bitimage mode.
16CC            LD   B,24                There are 24 characterrows.
16CE C2_SCRROW  PUSH BC
16CF            PUSH HL
16D0            LD   B,8                 A character has 8 pixelrows.
16D2 C2_PIXROW  PUSH BC
16D3            PUSH HL
16D4            LD   DE,#1BD6            Clear the buffer for the 2 pixels.
16D7            LD   B,3
16D9 C2_CLRBUF  XOR  A
16DA            LD   (DE),A
16DB            INC  DE
16DC            DJNZ #16D9,C2_CLRBUF
16DE            LD   B,2                 The dot columns for 2 pixels are build
                                         up each time.
16E0 C2_2PIX    PUSH BC
16E1            PUSH HL
16E2            LD   B,C
16E3            CALL #1751,PIXEL_COL     Get the colour of the (B-1)th pixel.
16E6            AND  #07                 Keep only the least significant 3 bits.
16E8            INC  A                   Make the range 1..8.
16E9            LD   B,A
16EA            LD   C,0                 Set the bit in the C register which
16EC            SCF                      corresponds to the colour.
16ED C2_MK_MASK RL   C
16EF            DJNZ #16ED,C2_MK_MASK
16F1            LD   DE,#02F2            DE points to the 'GREYSCALE' table.
16F4            LD   HL,#1BD6            HL points to the 2-pixel buffer.
16F7            LD   B,3                 Each pixel is printed as 3*3 dots.
16F9 C2_DOTCOL  PUSH BC
16FA            LD   B,3
16FC C2_DOTROW  LD   A,(DE)              Get colour pattern.
16FD            AND  C                   Only keep the bit with the right colour.
16FE            LD   A,(HL)
16FF            JR   Z,#1702,C2_ADD_DOT  Jump if bit isn't set.
1701            SCF                      Otherwise set this dot.
1702 C2_ADD_DOT RL   A                   Incorporate this dot.
1704            LD   (HL),A
1705            INC  DE                  Next entry in 'GREYSCALE' table.
1706            DJNZ #16FC,C2_DOTROW     Repeat for 3 dotrows.
1708            INC  HL
1709            POP  BC
170A            DJNZ #16F9,C2_DOTCOL     Repeat for 3 dotcolumns.
170C            POP  HL
170D            POP  BC
170E            DEC  C                   Next pixel.
170F            DJNZ #16E0,C2_2PIX       Two pixels are handled at a time.
1711            LD   B,3                 Three dotcolumns are to be printed.
1713            LD   HL,#1BD6
1716 C2_PRT3X3  LD   A,(HL)              Print each dotcolumn in turn.
1717            CALL #1944,PNTP
171A            INC  HL
171B            DJNZ #1716,C2_PRT3X3     Repeat for all three.
171D            POP  HL
171E            DEC  H                   Next pixelrow.
171F            POP  BC                  Repeat for the eight pixelrows in a
1720            DJNZ #16D2,C2_PIXROW     character square.
1722            POP  HL
1723            LD   A,L                 One character row up.
1724            SUB  32
1726            LD   L,A
1727            JR   NC,#172D,C2_CHRROW  Jump if still within the same third.
1729            LD   A,H                 Otherwise update MSB of address.
172A            SUB  8
172C            LD   H,A
172D C2_CHRROW  POP  BC
172E            DJNZ #16CE,C2_SCRROW     Repeat for the 24 rows on the screen.
1730            CALL #16A2,ADV_PAPER     Advance the paper.
1733            POP  HL
1734            POP  BC
1735            DEC  C                   Skip the two pixels which have already
1736            DEC  C                   been printed.
1737            JR   NZ,#173C,C2_BYTE    Jump if not all pixels within this byte
                                         have been printed.
1739            LD   C,8                 Otherwise reset 'pixels in a byte' counter
173B            INC  HL                  and point to the next character position
                                         to the right.
173C C2_BYTE    DJNZ #16C4,C2_2PIXCOL    Repeat for the 128 2-pixelcolumns.
173E            LD   B,4                 Advance the paper for four lines.
1740 C2_ADVPAP  CALL #16A2,ADV_PAPER
1743            DJNZ #1740,C2_ADVPAP
1745 DUMP_EXIT  LD   DE,#02BA            Print the escape sequence for n/72 inch
1748            CALL #1779,PO_ESC_SEQ    line feeds.
174B            LD   A,(#029F)           Make it (LSPCE)/72.
174E            JP   #1944,PNTP          Exit via 'PNTP'.

THE 'PIXEL COLOUR' SUBROUTINE
In System 3b this routine returned with the low 3 bits of the A register holding the
colour of the Bth pixel from address HL (i.e. the paper colour for an 'off' pixel and
the ink colour for an 'on' pixel). Because some normal screen dumps came out as a solid
black mess the routine was somewhat changed in System 3c (from #1762-#1764). The
routine now returns with %111 for an on pixel and with %000 for an off pixel. However
now the greyscale dump is reduced to a 'no more greyscales' large screendump.

1751 PIXEL_COL  PUSH HL                  Save address of current 8-pixels.
1752            PUSH BC                  Save pixel number (range 1..8).
1753            XOR  A
1754            SCF
1755 PIXEL_COL1 RLA                      Now set (B-1)th bit of A (range 0..7).
1756            DJNZ #1755,PIXEL_COL1
1758            AND  (HL)                Zero flag now reflects state of pixel
                                         (i.e. set means pixel set).
1759            PUSH AF                  These seven instructions don't serve
175A            LD   A,H                 any purpose anymore. They were used in
175B            RRCA                     Sys 3b to calculate the attribute
175C            RRCA                     address.
175D            RRCA
175E            AND  #03
1760            OR   #58
1762            POP  AF                  Restore flags.
1763            LD   A,#38               PAPER 7, INK 0.
1765            POP  BC
1766            POP  HL
1767            RET  NZ                  Return with %000 if pixel was set.
1768            RRCA                     Otherwise move bit3-5 to bit0-2.
1769            RRCA
176A            RRCA
176B            RET                      Return with %111.

THE 'NEXT CHAR. ROW ADDRESS' SUBROUTINE
This subroutine calculates the address of the next characterrow, if the end of the
pixel area is reached a return with Zero set will be made.

176C N_CHARROW  LD   A,L                 Update low address byte to next character
                                         row.
176D            ADD  A,32                The carry will be reset within display
176F            LD   L,A                 thirds.
1770            CCF                      Invert carry.
1771            SBC  A,A                 A holds #FF within same third, 0 else.
1772            AND  #F8                 A will hold #F8 (i.e. -8) within a
1774            ADD  A,H                 third, but 0 when a new third is
1775            LD   H,A                 reached. Update high byte (which was
                                         already incremented by 8).
1776            CP   #58                 Return with the Zero flag set if
1778            RET                      attributes reached.

THE 'PRINT ESCAPE SEQUENCE' SUBROUTINE
This subroutine is used to send escape sequences to the printer. The start of the
sequence is held in the DE register, a sequence ends with a CHR$ 128.

1779 PO_ESC_SEQ LD   A,(DE)              Fetch a code.
177A            CP   128
177C            RET  Z                   Exit if it's 128.
177D            CALL #1944,PNTP          Otherwise send it to the printer.
1780            INC  DE
1781            JR   #1779,PO_ESC_SEQ    Continue until the sequence is finished.

THE '"P" CHANNEL OUTPUT' ROUTINE
This routine handles the DISCiPLE's "P" channel, the @6 system variable (PCODE) signals
if it's to be handled as a "t" or a "b" channel. (As with the Opus Discovery and the
ZX Interface 1.) This routine handles also the sending of the CATalogue over the network
whenever a pupil gives the 'CAT' command.

1783 PCHAN_OUT  LD   (#1978),A
1786            CALL #09FB,TEST_SERV
1789            JR   Z,#1796,PCHAN_OUT1  Jump if not serving the network.
178B            PUSH IX                  When serving the network the byte to be
178D            LD   A,(#1978)           printed is send over the network.
1790            CALL #2966,JN_OUTPUT
1793            POP  IX
1795            RET

1796 PCHAN_OUT1 LD   A,(#029E)           This is PCODE.
1799            AND  A
179A            LD   A,(#1978)           Fetch the code to be send to the
179D            JP   NZ,#1944,PNTP       printer, send it right away if
                                         (PCODE)=1, i.e. when the DISCiPLE
                                         mustn't interfere.
17A0            LD   HL,(#1974)          Jump to the appropriate 'output'
17A3            JP   (HL)                routine.

This is the normal 'output' routine, but a few (control) characters are followed by
one or two operands, these have to be handled different. This is done by altering the
'output' routine address.

17A4 P_ALL      LD   HL,#029D            This is 'WIDTH'.
17A7            CP   32
17A9            JP   NC,#1892,P_NOCTRL   Jump if not a control code (>=32).
17AC            CP   6                   This is the "PRINT comma" code.
17AE            JP   C,#184D,P_ESCAPE    Jump with codes < 6.
17B1            JR   NZ,#17C1,P_NOCOMMA  Jump with codes > 6.
17B3            LD   A,(HL)              Fetch the number of characters per
17B4            SRL  A                   line, divide it by two.
17B6            LD   B,A
17B7            LD   HL,#1976            #1976 holds the position on the current
                                         line (i.e. the number of characters
                                         already printed on this line).
17BA            SUB  (HL)
17BB            JR   C,#17E2,P_NEWLINE   Jump if already on 2nd half of line.
17BD            LD   H,B                 Otherwise jump with H holding the
17BE            JP   #1864,P_TAB         center position of the line.

17C1 P_NOCOMMA  CP   8                   This is "cursor left" or "backspace".
17C3            JP   C,#184D,P_ESCAPE    Jump with codes < 8.
17C6            JR   NZ,#17D4,P_NOBACK   Jump with codes > 8 (examine further).
17C8            LD   HL,#1976            Get current position.
17CB            LD   A,(HL)
17CC            AND  A
17CD            RET  Z                   Return if already on leftmost position.
17CE            DEC  (HL)                Otherwise decrement current position.
17CF            LD   A,127               This isn't "BACKSPACE", this is
                                         "DELETE" !
17D1            JP   #1944,PNTP          Print a "DELETE".

17D4 P_NOBACK   CP   13                  This is "ENTER" or "CARRIAGE RETURN".
17D6            JR   C,#184D,P_ESCAPE    Jump with codes < 13.
17D8            JR   NZ,#180E,P_NOENTER  Jump with codes > 13.
17DA            LD   HL,#1977            This flag, when set, indicates that a
17DD            BIT  0,(HL)              newline has already been send to the
                                         printer. I.e. the previous line was full
                                         (see #19EB).
17DF            RES  0,(HL)              Reset the flag.
17E1            RET  NZ                  Return if this newline has been send
                                         already.
17E2 P_NEWLINE  LD   HL,#1977            Signal 'newline has been send'.
17E5            RES  0,(HL)
17E7            LD   HL,#1976
17EA            LD   (HL),0              Set current position to 0.
17EC            LD   A,(#02A0)           Fetch (LFEED), the number of line feeds
17EF            AND  A                   needed after a carriage return.
17F0            JR   Z,#17FA,P_CARRET    Jump if it is 0.
17F2            LD   B,A                 Otherwise send the line feeds.
17F3 P_LFEED    LD   A,10                CHR$ 10 is line feed.
17F5            CALL #1944,PNTP
17F8            DJNZ #17F3,P_LFEED       Loop until (LFEED) line feeds send.
17FA P_CARRET   LD   A,13                Now send the carriage return.
17FC            CALL #1944,PNTP
17FF            LD   A,(#02A1)           Fetch (LMARG), that is the left margin.
1802            AND  A
1803            RET  Z                   Return if it is 0.
1804            LD   B,A                 Otherwise send (LMARG) spaces.
1805            LD   (HL),A              Adjust current print position.
1806 P_LMARG    LD   A,32
1808            CALL #1944,PNTP
180B            DJNZ #1806,P_LMARG       Loop until (LMARG) spaces send.
180D            RET                      Finished.

Now the control codes with operands are handled. The control codes from INK to OVER
(16..21) and ESC (27) require a single operand, whereas the control characters AT & TAB
are required to be followed by two operands. The following routines leads to the control
character code being stored in TVDATA-lo, the first operand in TVDATA-hi or the A
register if there is only a single operand required, and the second operand in the
A register. The ESC control code is handled separately, the single operand is send
directly to the printer.

180E P_NOENTER  CP   16                  This is "INK control".
1810            JR   C,#184D,P_ESCAPE    Jump with codes < 16.
1812            CP   24                  This is "TAB control"+1.
1814            JR   NC,#184D,P_ESCAPE   Jump with codes >= 24.
1816            CP   22                  This is "AT control".
1818            JR   NC,#1848,P_2_OPER   Jump with AT & TAB.
181A            LD   DE,#1827,P_CONT     Otherwise the '"P" channel output'
                                         routine is to be changed to 'P_CONT'.
181D P_TV_1     LD   (23566),A           Store the control character code in
                                         (TVDATA-lo).

The current 'output' routine address is changed temporarily.

1820 P_CHANGE   LD   HL,#1974            HL points to the 'output' routine
1823            LD   (HL),E              address. Enter the new 'output' routine
1824            INC  HL                  address and thereby force the next
1825            LD   (HL),D              character to be considered as an
1826            RET                      operand.

Once the operands have been collected the routine continues.

1827 P_CONT     LD   DE,#17A4,P_ALL      Restore the original address for
182A            CALL #1820,P_CHANGE      'P_ALL'.
182D            LD   HL,(23566)          Fetch the control code and the first
                                         operand if there are indeed two
                                         operands (TVDATA).
1830            LD   D,A                 The 'last' operand and the control code
1831            LD   A,L                 are moved.
1832            CP   22
1834            JR   C,#183A,P_CO_TEMPS  Jump if handling INK to OVER.
1836            JR   NZ,#1864,P_TAB      Jump if handling TAB.
1838            JR   #188F,P_AT          Jump if handling AT.

The control codes INK to OVER are handled by the 'main' ROM 'CO_TEMP' routine. It is
entered with the control code in the A register and the parameter in the D register.
Note that all changes are to the 'temporary' system variables.

183A P_CO_TEMPS LD   HL,#2211,CO_TEMP_5  Return via the calling routine to
183D            EX   (SP),HL             'CO_TEMP' in the 'main' ROM.
183E            PUSH HL
183F            RET

1840 P_TV_2     LD   DE,#1827,P_CONT     Store the first operand in TVDATA-hi
1843            LD   (23567),A           and change the address of the 'output'
1846            JR   #1820,P_CHANGE      routine to 'P_CONT'.

Enter here when handling the control codes AT & TAB.

1848 P_2_OPER   LD   DE,#1840,P_TV_2     The control code will be stored in
184B            JR   #181D,P_TV_1        TVDATA-lo and the address of the
                                         'output' routine changed to 'P_TV_2'.

184D P_ESCAPE   CP   27
184F            JR   NZ,#1860,P_QUEST    Print a '?' if it isn't ESC.
1851            LD   DE,#1857,P_ESC      Otherwise change the address of the
1854            JP   #1820,P_CHANGE      'output' routine to 'P_ESC'.

Enter here when handling the ESC control code, the character code following the ESC
is send directly to the printer.

1857 P_ESC      LD   DE,#17A4,P_ALL      Restore the original address for
185A            CALL #1820,P_CHANGE      'P_ALL'.
185D            JP   #1944,PNTP          Send the code following the ESC to the
                                         printer.

A question mark is printed whenever an attempt is made to print an unprintable
character code.

1860 P_QUEST    LD   A,63                The character '?'.
1862            JR   #1892,P_NOCTRL      Send it to the printer.

Now deal with the TAB control code.

1864 P_TAB      LD   A,(#029D)           Fetch (WIDTH), that is the line length.
1867            LD   B,A
1868            LD   A,H                 Fetch the position where to TAB (or AT)
1869            SUB  B                   to.
186A            JR   C,#1872,P_INRANGE   Jump if position is on this line.
186C            LD   HL,#046C,REPORT_B   Otherwise return to 'REPORT_B' in the
186F            EX   (SP),HL             'main' ROM ('Integer out of range').
1870            PUSH HL
1871            RET
1872 P_INRANGE  LD   A,(#1976)           Fetch current position.
1875            LD   B,A
1876            LD   A,H
1877            SUB  B
1878            PUSH HL                  Print on a new line if print position
1879            CALL C,#17E2,P_NEWLINE   exceeds TAB position.
187C            POP  HL
187D            LD   A,(#1976)           Fetch the current position again.
1880            SUB  H                   Calculate the number of spaces wanted.
1881            RET  Z                   Return if already there.
1882            CPL                      The number is negative so make it
1883            INC  A                   positive.
1884            LD   B,A                 Print the needed spaces.
1885 P_SPACE    LD   A,32
1887            PUSH BC
1888            CALL #17A4,P_ALL
188B            POP  BC
188C            DJNZ #1885,P_SPACE
188E            RET

Enter here when handling AT.

188F P_AT       LD   H,D                 Store the second operand and continue
1890            JR   #1864,P_TAB         in the TAB routine.

The 'not control' characters are divided into four groups: the ordinary characters,
the tokens, the graphics and the user-defined graphics.

1892 P_NOCTRL   CP   128                 This is the first graphic.
1894            JR   C,#18FD,P_ASCII     Jump with ASCII characters (< 128).
1896            CP   144                 This is the first UDG.
1898            JR   NC,#18A3,P_TOK&UDG  Jump with UDG's and tokens.
189A            LD   B,A                 Construct the graphic in the
189B            RST  #10,CALBAS          calculator's memory area by calling
189C            DEFW #0B38,PO_GR_1       'PO_GR_1' in the 'main' ROM.
189E            LD   HL,23698            HL points to the start of the graphic
                                         form; i.e. MEMBOT.
18A1            JR   #18BA,P_GRAPH       Jump to print the graphic character.

18A3 P_TOK&UDG  SUB  165                 This is the RND token.
18A5            JR   C,#18AD,P_UDGS      Jump with UDG's (< 165).
18A7            LD   HL,#0C10,PO_TOKENS  The routine indirectly jumps to the
18AA            EX   (SP),HL             'PO_TOKENS' routine in the 'main' ROM
18AB            PUSH HL                  to expand the token. That routine then
18AC            RET                      calls recursively the 'P_ALL' routine
                                         above for each character of the token.

18AD P_UDGS     ADD  A,21                Adjust range, UDG's now from 0..20.
18AF            LD   BC,(23675)          BC points to the start of the UDG area
18B3            LD   H,0                 (UDG).
18B5            LD   L,A                 Pass the code to HL.
18B6            ADD  HL,HL               Each UDG is made by eight bytes, so
18B7            ADD  HL,HL               multiply the code by eight.
18B8            ADD  HL,HL
18B9            ADD  HL,BC
18BA P_GRAPH    LD   DE,#1964            Move the eight bytes to the DISCiPLEs
18BD            LD   BC,8                internal printerbuffer.
18C0            LDIR

Now the eight pixelrows are converted to eight dotcolumns.

18C2            PUSH IX
18C4            LD   IX,#1973            The last address of the dotcolumns.
18C8            LD   B,8                 Each graphic has eight pixelrows.
18CA P_GRAPH1   LD   HL,#1964            Address of the graphic's pixelrows.
18CD            LD   C,8                 Each pixelrow has eight pixels.
18CF P_GRAPH2   LD   D,(HL)              Each bit is moved in turn into the E
18D0            RR   D                   register.
18D2            LD   (HL),D
18D3            RL   E
18D5            INC  HL
18D6            DEC  C
18D7            JR   NZ,#18CF,P_GRAPH2   Repeat for the eight pixels.
18D9            LD   (IX+0),E            Store the dotcolumn.
18DC            DEC  IX
18DE            DJNZ #18CA,P_GRAPH1      Repeat for the eight rows.
18E0            POP  IX
18E2            LD   DE,#02C2            Print the escape sequence for 60 dpi.
18E5            CALL #1779,PO_ESC_SEQ
18E8            LD   A,8                 Signal to the printer 'there follow
18EA            CALL #1944,PNTP          eight bytes of bitimage data'.
18ED            LD   A,0
18EF            CALL #1944,PNTP
18F2            LD   B,8                 Send the eight bytes to the printer.
18F4 P_GRAPH3   LD   A,(HL)
18F5            CALL #1944,PNTP
18F8            INC  HL
18F9            DJNZ #18F4,P_GRAPH3
18FB            JR   #192F,P_UP_POS      Update the current position.

Now deal with the printing of normal ASCII characters.

18FD P_ASCII    LD   HL,#1977
1900            RES  0,(HL)              Reset 'newline already send' flag.
1902            LD   (#1978),A
1905            LD   A,(#02A2)           Fetch (GRAPH), when it's 1 the DISCiPLE
1908            AND  A                   has to generate the graphic
1909            LD   A,(#1978)           representation of some characters.
190C            JR   Z,#192C,P_OTHERS    Jump if the normal code has to be send.

Because some Spectrum characters aren't supported by all printers the DISCiPLE can
send the graphic representation of those characters instead of the original character
code. The characters supported by System 3d are £, # and ©.

190E            CP   "£"
1910            JR   NZ,#1918,P_NOPOUND  Jump if it isn't '£'.
1912            LD   HL,#02D2            Point to the bitimage data for £.
1915            JP   #18BA,P_GRAPH       Handle it as an ordinary graphic.
1918 P_NOPOUND  CP   "#"
191A            JR   NZ,#1922,P_NOPOWER  Jump if it isn't '#'.
191C            LD   HL,#02DA            Point to the bitimage data for #.
191F            JP   #18BA,P_GRAPH       Handle it as a graphic.
1922 P_NOPOWER  CP   "©"
1924            JR   NZ,#192C,P_OTHERS   Jump to handle all non '©' characters.
1926            LD   HL,#02E2            Point to the bitimage data for ©.
1929            JP   #18BA,P_GRAPH       Handle it as a graphic.

Finally the normal characters can be send to the printer.

192C P_OTHERS   CALL #1944,PNTP          Send the character to the printer.
192F P_UP_POS   LD   A,(#1976)           Update the current position.
1932            INC  A
1933            LD   (#1976),A
1936            LD   HL,#029D            HL points to WIDTH.
1939            SUB  (HL)
193A            RET  C                   Return if the line isn't full yet.
193B            CALL #17E2,P_NEWLINE     Otherwise someone has forgotten that
193E            LD   HL,#1977            printer lines aren't endless, so print
1941            SET  0,(HL)              a 'NEWLINE' and signal 'ignore next
1943            RET                      character if it is a CR'.

THE 'SEND A BYTE TO PRINTER' SUBROUTINE
This routine is also called by using command code 57 (#39). It sends the 8 bit code in
the A register to the printer port, after checking if the printer is busy. The BREAK
key is tested.

1944 PNTP       LD   (#1978),A           Store the code temporarily.
1947 PNTP_1     CALL #03FA,TEST_BREAK    Exit if the BREAK key is pressed.
194A            IN   A,(31)              Test the BUSY line of the printer.
194C            BIT  6,A
194E            JR   Z,#1947,PNTP_1      Wait until printer isn't BUSY.
1950            LD   A,(#1978)           Send the code to the printer port.
1953            OUT  (251),A
1955            LD   A,(#1DDA)           Fetch current control port status.
1958            OR   #40                 Give a STROBE.
195A            OUT  (31),A
195C            AND  #BF                 Reset STROBE.
195E            OUT  (31),A
1960            LD   A,(#1978)           Return with the A register holding the
1963            RET                      outputted byte.

THE 'PRINTER WORKSPACE'
Here follows the workspace used by the printer routines.

1964            DEFS 8
196C            DEFS 8
1974            DEFW #17A4               Address of 'output' routine for "P".
1976            DEFB 0                   Holds the current print position.
1977            DEFB 0                   The 'ENTER' flag.
1978            DEFB 0                   Temporary store for byte to be send.
Previous Next Contents Index