Previous Next Contents Index
The Printer routines 

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

12D2 COPS       CALL #0527,SYSTEM_Z      If a system file has been loaded
12D5            CALL Z,#2080,JCOPS       call it's screendump routine.
12D8            LD   HL,16384            Start of screen.
12DB            LD   DE,#2022,N/72_LSPC  Print the escape sequence for n/72 inch
12DE            CALL #140B,PO_ESC_SEQ    line feeds.
12E1            LD   A,8                 Make it 8/72.
12E3            CALL #15C9,PNTP
12E6 C1_LINE    LD   DE,#202A,GRAPH_DPI  Print the escape sequence for a normal
12E9            CALL #140B,PO_ESC_SEQ    screendump. (60 dpi)
12EC            LD   A,0                 Signal '256 dot columns will follow'
12EE            CALL #15C9,PNTP          to the printer.
12F1            LD   A,1
12F3            CALL #15C9,PNTP
12F6            PUSH HL
12F7 C1_CHAR    LD   B,8                 Eight pixels in each byte.
12F9 C1_PIXEL   PUSH HL
12FA C1_PIXROW  CALL #13E3,PIXEL_COL     Get pixel colour.
12FD            AND  #04
12FF            JR   NZ,#1302,C1_ADDDOT  Jump with colour codes 4-7 (no dot).
1301            SCF                      Set a dot for colour codes 0-3.
1302 C1_ADDDOT  LD   A,(#3E4F)           Incorporate one dot in dot column.
1305            RLA
1306            LD   (#3E4F),A
1309            INC  H                   Next pixel row.
130A            LD   A,H
130B            AND  #07
130D            JR   NZ,#12FA,C1_PIXROW  Repeat until all eight pixelrows have
                                         been 'scanned'.
130F            LD   A,(#3E4F)
1312            CALL #15C9,PNTP          Print the dot column.
1315            POP  HL                  Repeat until all eight pixels in a byte
1316            DJNZ #12F9,C1_PIXEL      have been printed. One character cell
                                         (64 pixels) has been printed now.
1318            INC  L                   Next character position.
1319            LD   A,L
131A            AND  #1F
131C            JR   NZ,#12F7,C1_CHAR    Loop for all 32 character columns.
131E            CALL #132E,ADV_PAPER     Advance printer paper one line.
1321            POP  HL
1322            LD   A,H                 Make HL point to the next screen third
1323            ADD  A,8                 'N_CHARROW' will adjust HL if 
1325            LD   H,A                 necessary.
1326            CALL #13FE,N_CHARROW     Calculate the address of the next
1329            JR   NZ,#12E6,C1_LINE    characterrow and loop until end of
                                         pixel area reached.
132B            JP   #13D7,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.

132E ADV_PAPER  LD   A,13                Send a CR to the printer.
1330            CALL #15C9,PNTP
1333            LD   A,(#2008)           This is 'LFEED'.
1336            AND  A
1337            RET  Z                   Return if no LF has to be printed.
1338            LD   A,10                Otherwise send a LF.
133A            CALL #15C9,PNTP
133D            RET                      Finished.

THE 'GREYSCALE SCREENDUMP' SUBROUTINE
This routine prints a large screendump. It can also be called by using command code 66
(#42).

133E COPS2      CALL #0527,SYSTEM_Z      If a system file has been loaded
1341            CALL Z,#2083,JCOPS2      call it's screendump routine.
1344            LD   HL,#57E0            Address of the lowest pixelrow of the
                                         charactersquare in bottom left corner.
1347            LD   DE,#2022,N/72_LSPC  Print the escape sequence for n/72
134A            CALL #140B,PO_ESC_SEQ    inch line feeds.
134D            LD   A,6                 Make it 6/72.
134F            CALL #15C9,PNTP
1352            LD   B,128               There are 128 2-pixel columns.
1354            LD   C,8                 8 pixels make one byte. Start with
                                         leftmost bit in a byte.
1356 C2_2PIXCOL PUSH BC
1357            PUSH HL
1358            LD   DE,#2052,GREY_BITIM Print the escape sequence for the
135B            CALL #140B,PO_ESC_SEQ    greyscale bitimage mode.
135E            LD   B,24                There are 24 characterrows.
1360 C2_SCRROW  PUSH BC
1361            PUSH HL
1362            LD   B,8                 A character has 8 pixelrows.
1364 C2_PIXROW  PUSH BC
1365            PUSH HL
1366            LD   DE,#3BD6            Clear the buffer for the 2 pixels.
1369            LD   B,3
136B C2_CLRBUF  XOR  A
136C            LD   (DE),A
136D            INC  DE
136E            DJNZ #136B,C2_CLRBUF
1370            LD   B,2                 The dot columns for 2 pixels are build
                                         up each time.
1372 C2_2PIX    PUSH BC
1373            PUSH HL
1374            LD   B,C
1375            CALL #13E3,PIXEL_COL     Get the colour of the (B-1)th pixel.
1378            AND  #07                 Keep only the least significant 3 bits
137A            INC  A                   Make the range 1..8.
137B            LD   B,A
137C            LD   C,0                 Set the bit in the C register which
137E            SCF                      corresponds to the colour.
137F C2_MK_MASK RL   C
1381            DJNZ #137F,C2_MK_MASK
1383            LD   DE,#205A,GREYSCALE  DE points to the 'GREYSCALE' table.
1386            LD   HL,#3BD6            HL points to the 2-pixel buffer.
1389            LD   B,3                 Each pixel is printed as 3*3 dots.
138B C2_DOTCOL  PUSH BC
138C            LD   B,3
138E C2_DOTROW  LD   A,(DE)              Get colour pattern.
138F            AND  C                   Only keep the bit with the right 
1390            LD   A,(HL)              colour.
1391            JR   Z,#1394,C2_ADD_DOT  Jump if bit isn't set.
1393            SCF                      Otherwise set this dot.
1394 C2_ADD_DOT RL   A                   Incorporate this dot.
1396            LD   (HL),A
1397            INC  DE                  Next entry in 'GREYSCALE' table.
1398            DJNZ #138E,C2_DOTROW     Repeat for 3 dotrows.
139A            INC  HL
139B            POP  BC
139C            DJNZ #138B,C2_DOTCOL     Repeat for 3 dotcolumns.
139E            POP  HL
139F            POP  BC
13A0            DEC  C                   Next pixel.
13A1            DJNZ #1372,C2_2PIX       Two pixels are handled at a time.
13A3            LD   B,3                 Three dotcolumns are to be printed.
13A5            LD   HL,#3BD6
13A8 C2_PRT3X3  LD   A,(HL)              Print each dotcolumn in turn.
13A9            CALL #15C9,PNTP
13AC            INC  HL
13AD            DJNZ #13A8,C2_PRT3X3     Repeat for all three.
13AF            POP  HL
13B0            DEC  H                   Next pixelrow.
13B1            POP  BC                  Repeat for the eight pixelrows in a
13B2            DJNZ #1364,C2_PIXROW     character square.
13B4            POP  HL
13B5            LD   A,L                 One character row up.
13B6            SUB  32
13B8            LD   L,A
13B9            JR   NC,#13BF,C2_CHRROW  Jump if still within the same third.
13BB            LD   A,H                 Otherwise update MSB of address.
13BC            SUB  8
13BE            LD   H,A
13BF C2_CHRROW  POP  BC
13C0            DJNZ #1360,C2_SCRROW     Repeat for the 24 rows on the screen.
13C2            CALL #132E,ADV_PAPER     Advance the paper.
13C5            POP  HL
13C6            POP  BC
13C7            DEC  C                   Skip the two pixels which have already
13C8            DEC  C                   been printed.
13C9            JR   NZ,#13CE,C2_BYTE    Jump if not all pixels within this
                                         byte have been printed.
13CB            LD   C,8                 Otherwise reset 'pixels in a byte'
13CD            INC  HL                  counter and point to the next
                                         character position to the right.
13CE C2_BYTE    DJNZ #1356,C2_2PIXCOL    Repeat for the 128 2-pixelcolumns.
13D0            LD   B,4                 Advance the paper for four lines.
13D2 C2_ADVPAP  CALL #132E,ADV_PAPER
13D5            DJNZ #13D2,C2_ADVPAP
13D7 DUMP_EXIT  LD   DE,#2022,N/72_LSPC  Print the escape sequence for n/72 inch
13DA            CALL #140B,PO_ESC_SEQ    line feeds.
13DD            LD   A,(#2007)           Make it (LSPCE)/72.
13E0            JP   #15C9,PNTP          Exit via 'PNTP'.

THE 'PIXEL COLOUR' SUBROUTINE
This routine returns 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). 

13E3 PIXEL_COL  PUSH HL                  Save address of current 8-pixels.
13E4            PUSH BC                  Save pixel number (range 1..8).
13E5            XOR  A
13E6            SCF
13E7 PIXEL_COL1 RLA                      Now set (B-1)th bit of A (range 0..7).
13E8            DJNZ #13E7,PIXEL_COL1
13EA            AND  (HL)                Zero flag now reflects state of pixel
13EB            PUSH AF                  (i.e. set means pixel set).
13EC            LD   A,H                 Calculate attribute address.
13ED            RRCA
13EE            RRCA
13EF            RRCA
13F0            AND  #03
13F2            OR   #58
13F4            LD   H,A
13F5            POP  AF
13F6            LD   A,(HL)              Fetch the attribute.
13F7            POP  BC
13F8            POP  HL
13F9            RET  NZ                  Return if ink colour is to be used.
13FA            RRCA                     Otherwise move paper colour
13FB            RRCA                     to the lower three bits.
13FC            RRCA
13FD            RET

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.

13FE N_CHARROW  LD   A,L                 Update low address byte to next
                                         character row.
13FF            ADD  A,32                The carry will be reset within display
1401            LD   L,A                 thirds.
1402            CCF                      Invert carry.
1403            SBC  A,A                 A holds #FF within same third, 0 else.
1404            AND  #F8                 A will hold #F8 (i.e. -8) within a
1406            ADD  A,H                 third, but 0 when a new third is
1407            LD   H,A                 reached. Update high byte (which was
                                         already incremented by 8).
1408            CP   #58                 Return with the Zero flag set if
140A            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.

140B PO_ESC_SEQ LD   A,(DE)              Fetch a code.
140C            CP   128
140E            RET  Z                   Exit if it's 128.
140F            CALL #15C9,PNTP          Otherwise send it to the printer.
1412            INC  DE                  Continue until the sequence is
1413            JR   #140B,PO_ESC_SEQ    finished.

THE '"P" CHANNEL OUTPUT' ROUTINE
This routine handles the +D'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.) 

1415 PCHAN_OUT  CALL #0527,SYSTEM_Z      If the system file is loaded call the
1418            CALL Z,#2086,JPCHAN      alternative routine.
141B            LD   A,(#2006)           This is PCODE.
141E            AND  A
141F            LD   A,(#3E4F)           Fetch the code to be send to the
1422            JP   NZ,#15C9,PNTP       printer, send it right away if
                                         (PCODE)=1, i.e. when the +D
                                         mustn't interfere.
1425            LD   HL,(#2063)          Jump to the appropriate 'output'
1428            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.

1429 P_ALL      LD   HL,#2005            This is 'WIDTH'.
142C            CP   32
142E            JP   NC,#1517,P_NOCTRL   Jump if not a control code (>=32).
1431            CP   6                   This is the "PRINT comma" code.
1433            JP   C,#14D2,P_ESCAPE    Jump with codes < 6.
1436            JR   NZ,#1446,P_NOCOMMA  Jump with codes > 6.
1438            LD   A,(HL)              Fetch the number of characters per
1439            SRL  A                   line, divide it by two.
143B            LD   B,A
143C            LD   HL,#3E4E            #3E4E holds the position on the
                                         current line (i.e. the number of
                                         characters already printed on this
143F            SUB  (HL)                line).
1440            JR   C,#1467,P_NEWLINE   Jump if already on 2nd half of line.
1442            LD   H,B                 Otherwise jump with H holding the
1443            JP   #14E9,P_TAB         center position of the line.

1446 P_NOCOMMA  CP   8                   This is "cursor left" or "backspace".
1448            JP   C,#14D2,P_ESCAPE    Jump with codes < 8.
144B            JR   NZ,#1459,P_NOBACK   Jump with codes > 8 (examine further).
144D            LD   HL,#3E4E            Get current position.
1450            LD   A,(HL)
1451            AND  A
1452            RET  Z                   Return if already on leftmost position
1453            DEC  (HL)                Otherwise decrement current position.
1454            LD   A,127               This isn't "BACKSPACE", this is
                                         "DELETE" !
1456            JP   #15C9,PNTP          Print a "DELETE".

1459 P_NOBACK   CP   13                  This is "ENTER" or "CARRIAGE RETURN".
145B            JR   C,#14D2,P_ESCAPE    Jump with codes < 13.
145D            JR   NZ,#1493,P_NOENTER  Jump with codes > 13.
145F            LD   HL,#2065            This flag, when set, indicates that a
1462            BIT  1,(HL)              newline has already been send to the
                                         printer. I.e. the previous line was
                                         full (see #15C0).
1464            RES  1,(HL)              Reset the flag.
1466            RET  NZ                  Return if this newline has been send
                                         already.
1467 P_NEWLINE  LD   HL,#2065            Signal 'newline has been send'.
146A            RES  1,(HL)
146C            LD   HL,#3E4E
146F            LD   (HL),0              Set current position to 0.
1471            LD   A,(#2008)           Fetch (LFEED), the number of line
1474            AND  A                   feeds needed after a carriage return.
1475            JR   Z,#147F,P_CARRET    Jump if it is 0.
1477            LD   B,A                 Otherwise send the line feeds.
1478 P_LFEED    LD   A,10                CHR$ 10 is line feed.
147A            CALL #15C9,PNTP
147D            DJNZ #1478,P_LFEED       Loop until (LFEED) line feeds send.
147F P_CARRET   LD   A,13                Now send the carriage return.
1481            CALL #15C9,PNTP
1484            LD   A,(#2009)           Fetch (LMARG), that is the left margin
1487            AND  A
1488            RET  Z                   Return if it is 0.
1489            LD   B,A                 Otherwise send (LMARG) spaces.
148A            LD   (HL),A              Adjust current print position.
148B P_LMARGE   LD   A,32
148D            CALL #15C9,PNTP
1490            DJNZ #148B,P_LMARGE      Loop until (LMARG) spaces send.
1492            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.

1493 P_NOENTER  CP   16                  This is "INK control".
1495            JR   C,#14D2,P_ESCAPE    Jump with codes < 16.
1497            CP   24                  This is "TAB control"+1.
1499            JR   NC,#14D2,P_ESCAPE   Jump with codes >= 24.
149B            CP   22                  This is "AT control".
149D            JR   NC,#14CD,P_2_OPER   Jump with AT & TAB.
149F            LD   DE,#14AC,P_CONT     Otherwise the '"P" channel output'
                                         routine is to be changed to 'P_CONT'.
14A2 P_TV_1     LD   (23566),A           Store the control character code in
                                         (TVDATA-lo).

The current 'output' routine address is changed temporarily.

14A5 P_CHANGE   LD   HL,#2063            HL points to the 'output' routine
14A8            LD   (HL),E              address. Enter the new 'output'
14A9            INC  HL                  routine address and thereby force the
14AA            LD   (HL),D              next character to be considered as an
14AB            RET                      operand.

Once the operands have been collected the routine continues.

14AC P_CONT     LD   DE,#1429,P_ALL      Restore the original address for
14AF            CALL #14A5,P_CHANGE      'P_ALL'.
14B2            LD   HL,(23566)          Fetch the control code and the first
                                         operand if there are indeed two
                                         operands (TVDATA).
14B5            LD   D,A                 The 'last' operand and the control
14B6            LD   A,L                 code are moved.
14B7            CP   22
14B9            JR   C,#14BF,P_CO_TEMPS  Jump if handling INK to OVER.
14BB            JR   NZ,#14E9,P_TAB      Jump if handling TAB.
14BD            JR   #1514,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.

14BF P_CO_TEMPS LD   HL,#2211,CO_TEMP_5  Return via the calling routine to
14C2            EX   (SP),HL             'CO_TEMP' in the 'main' ROM.
14C3            PUSH HL
14C4            RET

14C5 P_TV_2     LD   DE,#14AC,P_CONT     Store the first operand in TVDATA-hi
14C8            LD   (23567),A           and change the address of the 'output'
14CB            JR   #14A5,P_CHANGE      routine to 'P_CONT'.

Enter here when handling the control codes AT & TAB.

14CD P_2_OPER   LD   DE,#14C5,P_TV_2     The control code will be stored in
14D0            JR   #14A2,P_TV_1        TVDATA-lo and the address of the
                                         'output' routine changed to 'P_TV_2'.

14D2 P_ESCAPE   CP   27
14D4            JR   NZ,#14E5,P_QUEST    Print a '?' if it isn't ESC.
14D6            LD   DE,#14DC,P_ESC      Otherwise change the address of the
14D9            JP   #14A5,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.

14DC P_ESC      LD   DE,#1429,P_ALL      Restore the original address for
14DF            CALL #14A5,P_CHANGE      'P_ALL'.
14E2            JP   #15C9,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.

14E5 P_QUEST    LD   A,63,"?"            The character '?'.
14E7            JR   #1517,P_NOCTRL      Send it to the printer.

Now deal with the TAB control code.

14E9 P_TAB      LD   A,(#2005)           Fetch (WIDTH), that is the line length
14EC            LD   B,A
14ED            LD   A,H                 Fetch the position where to TAB
14EE            SUB  B                   (or AT) to.
14EF            JR   C,#14F7,P_INRANGE   Jump if position is on this line.
14F1            LD   HL,#046C,REPORT_B   Otherwise return to 'REPORT_B' in the
14F4            EX   (SP),HL             'main' ROM ('Integer out of range').
14F5            PUSH HL
14F6            RET
14F7 P_INRANGE  LD   A,(#3E4E)           Fetch current position.
14FA            LD   B,A
14FB            LD   A,H
14FC            SUB  B
14FD            PUSH HL                  Print on a new line if print position
14FE            CALL C,#1467,P_NEWLINE   exceeds TAB position.
1501            POP  HL
1502            LD   A,(#3E4E)           Fetch the current position again.
1505            SUB  H                   Calculate the number of spaces wanted.
1506            RET  Z                   Return if already there.
1507            CPL                      The number is negative so make it
1508            INC  A                   positive.
1509            LD   B,A                 Print the needed spaces.
150A P_SPACE    LD   A,32
150C            PUSH BC
150D            CALL #1429,P_ALL
1510            POP  BC
1511            DJNZ #150A,P_SPACE
1513            RET

Enter here when handling AT.

1514 P_AT       LD   H,D                 Store the second operand and continue
1515            JR   #14E9,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.

1517 P_NOCTRL   CP   128                 This is the first graphic.
1519            JR   C,#1582,P_ASCII     Jump with ASCII characters (< 128).
151B            CP   144                 This is the first UDG.
151D            JR   NC,#1528,P_TOK&UDG  Jump with UDG's and tokens.
151F            LD   B,A                 Construct the graphic in the
1520            RST  #10,CALBAS          calculator's memory area by calling
1521            DEFW #0B38,PO_GR_1       'PO_GR_1' in the 'main' ROM.
1523            LD   HL,23698            HL points to the start of the graphic
                                         form; i.e. MEMBOT.
1526            JR   #153F,P_GRAPH       Jump to print the graphic character.

1528 P_TOK&UDG  SUB  165                 This is the RND token.
152A            JR   C,P_UDGS            Jump with UDG's (< 165).
152C            LD   HL,#0C10,PO_TOKENS  The routine indirectly jumps to the
152F            EX   (SP),HL             'PO_TOKENS' routine in the 'main' ROM
1530            PUSH HL                  to expand the token. That routine then
1531            RET                      calls recursively the 'P_ALL' routine
                                         above for each character of the token.

1532 P_UDGS     ADD  A,21                Adjust range, UDG's now from 0..20.
1534            LD   BC,(23675)          BC points to the start of the UDG area
1538            LD   H,0                 (UDG).
153A            LD   L,A                 Pass the code to HL.
153B            ADD  HL,HL               Each UDG is made by eight bytes, so
153C            ADD  HL,HL               multiply the code by eight.
153D            ADD  HL,HL
153E            ADD  HL,BC
153F P_GRAPH    LD   DE,#3E3D            Move the eight bytes to the +Ds
1542            LD   BC,8                internal printerbuffer.
1545            LDIR

Now the eight pixelrows are converted to eight dotcolumns.

1547            PUSH IX
1549            LD   IX,#3E4C            The last address of the dotcolumns.
154D            LD   B,8                 Each graphic has eight pixelrows.
154F P_GRAPH1   LD   HL,#3E3D            Address of the graphic's pixelrows.
1552            LD   C,8                 Each pixelrow has eight pixels.
1554 P_GRAPH2   LD   D,(HL)              Each bit is moved in turn into the E
1555            RR   D                   register.
1557            LD   (HL),D
1558            RL   E
155A            INC  HL
155B            DEC  C
155C            JR   NZ,#1554,P_GRAPH2   Repeat for the eight pixels.
155E            LD   (IX+0),E            Store the dotcolumn.
1561            DEC  IX
1563            DJNZ #154F,P_GRAPH1      Repeat for the eight rows.
1565            POP  IX
1567            LD   DE,#202A,GRAPH_DPI  Print the escape sequence for
156A            CALL #140B,PO_ESC_SEQ    graphic images.
156D            LD   A,8                 Signal to the printer 'there follow
156F            CALL #15C9,PNTP          eight bytes of bitimage data'.
1572            LD   A,0
1574            CALL #15C9,PNTP
1577            LD   B,8                 Send the eight bytes to the printer.
1579 P_GRAPH3   LD   A,(HL)
157A            CALL #15C9,PNTP
157D            INC  HL
157E            DJNZ #1579,P_GRAPH3
1580            JR   #15B4,P_UP_POS      Update the current position.

Now deal with the printing of normal ASCII characters.

1582 P_ASCII    LD   HL,#2065
1585            RES  1,(HL)              Reset 'newline already send' flag.
1587            LD   (#3E4F),A
158A            LD   A,(#200A)           Fetch (GRAPH), when it's 1 the +D
158D            AND  A                   has to generate the graphic
158E            LD   A,(#3E4F)           representation of some characters.
1591            JR   Z,#15B1,P_OTHERS    Jump if the normal code has to be send

Because some Spectrum characters aren't supported by all printers the +D can send the
graphic representation of those characters instead of the original character code. The
characters supported £, # and (c).

1593            CP   96,"£"
1595            JR   NZ,#159D,P_NOPOUND  Jump if it isn't '£'.
1597            LD   HL,#203A,£_SIGN     Point to the bitimage data for £.
159A            JP   #153F,P_GRAPH       Handle it as an ordinary graphic.
159D P_NOPOUND  CP   35,"#"
159F            JR   NZ,#15A7,P_NOHASH   Jump if it isn't '#'.
15A1            LD   HL,#2042,#_SIGN     Point to the bitimage data for #.
15A4            JP   #153F,P_GRAPH       Handle it as a graphic.
15A7 P_NOHASH   CP   127,"(c)"
15A9            JR   NZ,#15B1,P_OTHERS   Jump to handle all non '(c)' characters.
15AB            LD   HL,#204A,(c)_SIGN     Point to the bitimage data for (c).
15AE            JP   #153F,P_GRAPH       Handle it as a graphic.

Finally the normal characters can be send to the printer.

15B1 P_OTHERS   CALL #15C9,PNTP          Send the character to the printer.
15B4 P_UP_POS   LD   A,(#3E4E)           Update the current position.
15B7            INC  A
15B8            LD   (#3E4E),A
15BB            LD   HL,#2005            HL points to WIDTH.
15BE            SUB  (HL)
15BF            RET  C                   Return if the line isn't full yet.
15C0            CALL #1467,P_NEWLINE     Otherwise someone has forgotten that
15C3            LD   HL,#2065            printer lines aren't endless, so print
15C6            SET  1,(HL)              a 'NEWLINE' and signal 'ignore next
15C8            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.

15C9 PNTP       LD   (#3E4F),A           Store the code temporarily.
15CC PNTP_1     CALL #0497,TST_BREAK     Exit if the BREAK key is pressed.
15CF            IN   A,(247)             Test the BUSY line of the printer.
15D1            BIT  7,A
15D3            JR   NZ,#15CC,PNTP_1     Wait until printer isn't BUSY.
15D5            IN   A,(247)
15D7            BIT  7,A
15D9            JR   NZ,#15CC,PNTP_1
15DB            IN   A,(247)
15DD            BIT  7,A
15DF            JR   NZ,#15CC,PNTP_1
15E1            LD   A,(#3E4F)           Send the code to the printer port.
15E4            OUT  (247),A
15E6            LD   A,(#3DDA)           Fetch current control port status.
15E9            OR   #40                 Give a STROBE.
15EB            OUT  (239),A
15ED            AND  #BF                 Reset STROBE.
15EF            OUT  (239),A
15F1            LD   A,(#3E4F)           Return with the A register holding the
                                         outputted byte, 'RET' forgotten?

Previous Next Contents Index