Previous Next Contents Index
The 'Hook code' routines

The following routines are called by the 'hook and command code' routine at #04C3 (in
RAM) whenever a hook code was used.

THE 'HOOK CODE ADDRESSES' TABLE
This jump table consists of the 24 addresses of the routines called by using the
various 'hook codes' in the range #1B..#32 (27..50).

29D2            DEFW #2A03,CONS_IN       Hook code #1B, 27.
29D4            DEFW #2A16,CONS_OUT      Hook code #1C, 28.
29D6            DEFW #2A02,BCHAN_IN      Hook code #1D, 29.
29D8            DEFW #2A02,BCHAN_OUT     Hook code #1E, 30.
29DA            DEFW #2A26,PRT_OUT       Hook code #1F, 31.
29DC            DEFW #2A2B,KBD_TEST      Hook code #20, 32.
29DE            DEFW #2A33,SEL_DRIVE     Hook code #21, 33.
29E0            DEFW #2A4F,OP_TEMP_M     Hook code #22, 34.
29E2            DEFW #2CFF,CLOSE_M2      Hook code #23, 35.
29E4            DEFW #2D1B,ERASE         Hook code #24, 36.
29E6            DEFW #2D9E,READ_SEQ      Hook code #25, 37.
29E8            DEFW #2DDE,WR_RECD       Hook code #26, 38.
29EA            DEFW #2DAA,RD_RANDOM     Hook code #27, 39.
29EC            DEFW #2E66,RD_SECTOR     Hook code #28, 40.
29EE            DEFW #2E67,RD_NEXT       Hook code #29, 41.
29F0            DEFW #2E68,WR_SECTOR     Hook code #2A, 42.
29F2            DEFW #2AF1,SET_T_MCH     Hook code #2B, 43.
29F4            DEFW #2E69,DEL_M_BUF     Hook code #2C, 44.
29F6            DEFW #2E73,OP_TEMP_N     Hook code #2D, 45.
29F8            DEFW #2E74,CLOSE_NET     Hook code #2E, 46.
29FA            DEFW #2E75,GET_PACK      Hook code #2F, 47.
29FC            DEFW #2E76,SEND_PACK     Hook code #30, 48.
29FE            DEFW #2E77,HOOK_31       Hook code #31, 49.
2A00            DEFW #2EBE,HOOK_32       Hook code #32, 50.

THE 'RS232 NOT SUPPORTED' SUBROUTINE
The 'BCHAN_IN' and 'BCHAN_OUT' 'hook codes' are not supported (the DISCiPLE has no
RS232 link).

2A02 UNDEFINED1 RET

THE 'CONSOLE INPUT' SUBROUTINE
Called by using 'hook code' 27 (#1B), it simply waits until a key is pressed. A return
is made with the A register holding the character code.

2A03 CONS_IN    RES  5,(IY+1)            Signal 'ready for a new key'.
2A07 WTKEY      EI                       Enable interrupts.
2A08            HALT                     Wait for an interrupt.
2A09            RST  #10,CALBAS          Call the keyboard scan routine in the
2A0A            DEFW #02BF,KEYBOARD      'main' ROM.
2A0C            BIT  5,(IY+1)            Repeat the scan until a key has been
2A10            JR   Z,#2A03,WTKEY       pressed.
2A12            LD   A,(23560)           Fetch the character code from (LAST_K).
2A15            RET

THE 'CONSOLE OUTPUT' SUBROUTINE
By using 'hook code' 28 (#1C) the character held in the A register is printed on the
screen, with scroll suppressed.

2A16 CONS_OUT   PUSH AF
2A17            LD   A,254               Use stream '-2' (attached to "S" the
                                         channel).
2A19 OUT_CODE   LD   HL,23692            This is SCR_CT.
2A1C            LD   (HL),255            Set scroll counter.
2A1E            RST  #10,CALBAS          Call 'CHAN_OPEN' in the 'main' ROM to
2A1F            DEFW #1601,CHAN_OPEN     make stream -2 the current.
2A21            POP  AF
2A22            RST  #10,CALBAS          Print the character to the current
2A23            DEFW #0010,PRINT_A_1     stream.
2A25            RET

THE 'PRINTER OUTPUT' SUBROUTINE
This subroutine is called by using 'hook code' 31 (#1F). It is identical to the
preceding one, but the output is directed to stream 3 (normally the printer).

2A26 PRT_OUT    PUSH AF
2A27            LD   A,3                 Select stream 3.
2A29            JR   #2A19,OUT_CODE

THE 'KEYBOARD TEST' SUBROUTINE
This is called using 'hook code' 32 (#20). A return is made with the Zero flag reset if
a key is pressed.

2A2B KBD_TEST   XOR  A                   Clear A, allowing for the whole
                                         keyboard to be examined.
2A2C            IN   A,(254)             Read the keyboard.
2A2E            AND  #1F                 Keep only the keyboard bits.
2A30            SUB  #1F                 Return with sign negative and Zero flag
2A32            RET                      reset if a key is pressed.

THE 'SELECT DRIVE' SUBROUTINE
This subroutine is called by using 'hook code' 33 (#21). On entry, A holds the drive
number; if A isn't equal to 1 or 2 nothing is done.

2A33 SEL_DRIVE  CP   1
2A35            JR   Z,#2A3D,SEL_DRIVE1  Jump if drive 1 is to be selected.
2A37            CP   2
2A39            JR   Z,#2A3D,SEL_DRIVE1  Jump if drive 2 is to be selected.
2A3B            XOR  A
2A3C            RET                      Otherwise exit.
2A3D SEL_DRIVE1 AND  #01                 Keep only bit 0.
2A3F            LD   B,A
2A40            LD   (#1ACE),A
2A43            LD   A,(#1DDA)           Fetch current control port state.
2A46            AND  #FE                 Drop the drive select bit.
2A48            OR   B                   Use the new drive.
2A49            LD   (#1DDA),A           Exit setting both current control port
2A4C            OUT  (31),A              state and the control port itself.
2A4E            RET

THE 'OPEN TEMP. "M" CHANNEL' SUBROUTINE
This subroutine is used to open a temporary "M" channel in the CHANS area. It is called
by using 'hook code' 34 (#22). First a temporary "M" channel is created, then the drive
whose number is held into 'D_STR1' is searched for a file whose name is held into
'N_STR1'. A sector map is created with each reset bit indicating a free sector. Various
flags are returned as follows:
    - bit 0 of CHFLAG                    set with 'write' files.
    - bit 1 of RECFLG                    set with 'EOF' block.
    - bit 2 of RECFLG                    set with PRINT-type files.
On exit, HL holds a 'stream data' displacement that may be used to attach the channel
to a stream.

2A4F OP_TEMP_M  CALL #2AF1,SET_T_MCH     Create a temporary "M" channel.
2A52            PUSH HL                  Save 'stream displacement'.
2A53            LD   A,(IX+25)           Fetch the drive number (CHDRIV).
2A56            CALL #2A33,SEL_DRIVE     Select the drive.
2A59            PUSH IX
2A5B            LD   DE,14               Make IX point to CHNAME, the name of
2A5E            ADD  IX,DE               the wanted file.
2A60            CALL #2D43,FIND_FILE     Search for the filename.
2A63            JR   NZ,#2A95,OP_T_2     Jump if not found.
2A65            INC  HL                  Skip number of sectors used.
2A66            INC  HL
2A67            LD   D,(HL)              Fetch first track and sector.
2A68            INC  HL
2A69            LD   E,(HL)
2A6A            LD   IX,#1AC3            Point to the DRAM channel.
2A6E            CALL #2F4F,RSAD          Read the first sector.
2A71            POP  IX                  Restore channel pointer (in 'main'
2A73            PUSH IX                  RAM).
2A75            LD   DE,540              Microdrive type files consist of
                                         records with a length of 540 bytes
                                         each.
2A78 OP_T_1     PUSH IX                  Store data buffer pointer (in 'main'
                                         RAM).
2A7A            LD   IX,#1AC3            Point to the DRAM channel again.
2A7E            CALL #3126,LBYT          Fetch a byte.
2A81            POP  IX                  Restore data buffer pointer.
2A83            LD   (IX+55),A           Loading starts with the data block
                                         preamble (offset 55).
2A86            INC  IX
2A88            CALL #2E62,DEC_DE        Decrement DE.
2A8B            JR   NZ,#2A78,OP_T_1     Repeat until DE=0.
2A8D            POP  IX
2A8F            RES  0,(IX+24)           Signal 'read file'.
2A93            POP  HL                  Restore stream 'stream data'.
2A94            RET                      Finished.

2A95 OP_T_2     LD   HL,#1A00            Clear the disk bitmap.
2A98            LD   B,195
2A9A OP_T_3     LD   (HL),0
2A9C            INC  HL
2A9D            DJNZ #2A9A,OP_T_3
2A9F            LD   A,#20               Make new disk bitmap.
2AA1            CALL #335B,SCAN_CAT
2AA4            POP  IX
2AA6            PUSH IX
2AA8            LD   HL,#1AD6            Points to dir. descr. of DFCA.
2AAB            LD   (HL),6              File is a 'Microdrive file'.
2AAD            INC  HL
2AAE            LD   B,10                Copy the 10 characters of the name.
2AB0 OP_T_4     LD   A,(IX+14)
2AB3            LD   (HL),A
2AB4            INC  IX
2AB6            INC  HL
2AB7            DJNZ #2AB0,OP_T_4
2AB9            LD   B,245               Clear the rest of the CATalogue entry
2ABB OP_T_5     LD   (HL),0              of this file.
2ABD            INC  HL
2ABE            DJNZ #2ABB,OP_T_5
2AC0            LD   HL,#0000            Reset RPT.
2AC3            LD   (#1AD0),HL
2AC6            LD   HL,#1BD6            Clear the first 256 bytes of the data
2AC9            LD   B,0                 buffer.
2ACB OP_T_6     LD   (HL),0
2ACD            INC  HL
2ACE            DJNZ #2ACB,OP_T_6
2AD0            LD   IX,#1AC3
2AD4            CALL #32DE,MK_ALLOC      Allocate the first free sector.
2AD7            LD   (#1AD4),DE          Store the track and sector number.
2ADB            LD   IX,#1AD6            Store them also into the CATalogue
2ADF            LD   (IX+13),D           entry.
2AE2            LD   (IX+14),E
2AE5            POP  IX
2AE7            RES  1,(IX+67)           Signal 'Not the EOF block' (RECFLG).
2AEB            RES  2,(IX+67)           Signal 'PRINT-type file' (opened for
2AEF            POP  HL                  writing). Restore stream 'stream data'.
2AF0            RET                      Finished.

THE 'SET A TEMP. "M" CHANNEL' SUBROUTINE
This subroutine is also called by using 'hook code' 43 (#2B). It sets a temporary "M"
channel in the CHANS area. The subroutine returns with IX pointing to the start of the
channel and HL holding a suitable displacement to be eventually inserted in the STRMS
area to attach the channel to a stream.

2AF1 SET_T_MCH  LD   IX,(23631)          Fetch (CHANS), the start of the channel
                                         area.
2AF5            LD   DE,20               Make IX point to the start of the 'new'
2AF8            ADD  IX,DE               channels.
2AFA SET_T_1    LD   A,(IX+0)
2AFD            CP   128
2AFF            JR   Z,#2B31,SET_T_3     Jump if the CHANS area is finished.
2B01            LD   A,(IX+4)            Fetch the channel specifier.
2B04            AND  #7F                 Clear bit 7 (drop temporary/permanent
                                         flag).
2B06            CP   "M"
2B08            JR   NZ,#2B27,SET_T_2    Jump if not a "M" channel.
2B0A            LD   A,(23766)           Fetch drive number (D_STR1).
2B0D            CP   (IX+25)             Compare it with (CHDRIV).
2B10            JR   NZ,#2B27,SET_T_2    Jump if this channel uses a different
                                         drive.
2B12            LD   BC,(23770)          Fetch length of filename (NSTR_1).
2B16            LD   HL,(23772)          And its startaddress (NSTR_1+2).
2B19            CALL #2BC9,CHK_NAME      Check name against 'CHNAME' of this
                                         channel.
2B1C            JR   NZ,#2B27,SET_T_2    Jump if not the same file.
2B1E            BIT  0,(IX+24)
2B22            JR   Z,#2B27,SET_T_2     Jump if it's a 'read file'.
2B24            JP   #2EBF,MD_ERROR      Exit if the file is already opened for
                                         writing.
2B27 SET_T_2    LD   E,(IX+9)            Fetch the length of the channel.
2B2A            LD   D,(IX+10)
2B2D            ADD  IX,DE               Point to the next channel.
2B2F            JR   #2AFA,SET_T_1       Check next channel.

Now the space for the new channel is created at the end of the CHANS area.

2B31 SET_T_3    LD   HL,(23635)          Calculate end of CHANS area ((PROG)-1),
2B34            DEC  HL                  i.e. the start of the channel.
2B35            PUSH HL
2B36            LD   BC,595              Length is '595' bytes.
2B39            RST  #10,CALBAS          Create the required space by calling
2B3A            DEFW #1655,MAKE_ROOM     'MAKE_ROOM'.
2B3C            POP  DE                  Restore start address of the channel.
2B3D            PUSH DE
2B3E            LD   HL,#2CE6            Start of "M" channel data.
2B41            LD   BC,25
2B44            LDIR                     Store channel data into the channel.
2B46            LD   A,(23766)           Fetch drive number (D_STR1).
2B49            LD   (IX+25),A           Store it into the channel (CHDRIV).
2B4C            LD   BC,595              Length of the channel.
2B4F            PUSH IX                  Make HL point to the start of the
2B51            POP  HL                  channel.
2B52            CALL #2BA0,REST_F_AD     Restore 'start of filename' possibly
                                         moved during the 'insertion' of the
                                         channel.
2B55            EX   DE,HL               The start address of the filename goes
                                         to HL.
2B56            LD   BC,(23770)          Fetch length of filename (N_STR1).
2B5A            BIT  7,B                 Jump if the name doesn't exist
2B5C            JR   NZ,#2B6C,SET_T_6    (N_STR1 = #FFFF).

The channel name is transferred into CHNAME.

2B5E SET_T_5    LD   A,B
2B5F            OR   C
2B60            JR   Z,#2B6C,SET_T_6     Jump if no more bytes left.
2B62            LD   A,(HL)              Transfer a character of the name into
2B63            LD   (IX+14),A           (CHNAME).
2B66            INC  HL                  Point to next locations.
2B67            INC  IX
2B69            DEC  BC                  One byte less.
2B6A            JR   #2B5E,SET_T_5       Continue with next character.

Now the 'preambles' are stored into the channel.

2B6C SET_T_6    POP  IX                  Restore start address of channel.
2B6E            LD   DE,28               Offset for header block preamble.
2B71            CALL #2B86,SETUP_PRE     Set-up header preamble.
2B74            LD   DE,55               Offset for data block preamble.
2B77            CALL #2B86,SETUP_PRE     Set-up data block preamble.
2B7A            PUSH IX                  Make HL point to the start of the
2B7C            POP  HL                  channel.
2B7D            LD   DE,(23631)          Calculate the required 'stream offset'
2B81            OR   A                   into HL (i.e. channel start-(CHANS)+1).
2B82            SBC  HL,DE
2B84            INC  HL
2B85            RET                      Finished.

THE 'SET-UP A PREAMBLE' SUBROUTINE
The following subroutine passes a preamble to the specified channel position. On entry
IX points to the start of the channel and DE holds the required offset.

2B86 SETUP_PRE  PUSH IX                  Pass start of channel to HL.
2B88            POP  HL
2B89            ADD  HL,DE               Add the offset.
2B8A            EX   DE,HL               DE now points to the preamble area.
2B8B            LD   HL,#2B94            Start of 'preamble' data.
2B8E            LD   BC,12               Preamble is 12 bytes long.
2B91            LDIR
2B93            RET

THE 'PREAMBLE DATA' TABLE
The header and data block preambles consist of the following bytes:

2B94            DEFB #00,#00,#00,#00,#00
2B99            DEFB #00,#00,#00,#00,#00
2B9E            DEFB #FF,#FF

The Microdrive needs these bytes to fetch the start of a block of bytes when reading
a cartridge.

THE 'RESTORE FILENAME ADDRESS' ROUTINE
After the 'insertion' of some space, the 'filename' whose start addresses are held
into (N_STR1+2) and (N_STR2+2) have been moved up in the workspace area. This routine
is entered with HL holding the channel start address, and with BC holding the number
of 'inserted' bytes. The addresses held into (N_STR1+2) and (N_STR2+2) are then updated,
unless the filenames are stored into 'no-dynamic' areas (i.e. before the channel or
after STKEND).

2BA0 REST_F_AD  PUSH HL                  Save 'start of channel' twice.
2BA1            PUSH HL
2BA2            LD   DE,(23780)          Restore start address of the second
2BA6            CALL #2BBB,TST_PLACE     filename.
2BA9            LD   (23780),DE
2BAD            POP  HL                  Restore channel start address.
2BAE            LD   DE,(23772)          Restore start address of the first
2BB2            CALL #2BBB,TST_PLACE     filename.
2BB5            LD   (23772),DE
2BB9            POP  HL                  Restore channel start address.
2BBA            RET                      Finished.

The following subroutine calculates the new filename address.

2BBB TST_PLACE  SCF                      Allow for a further byte.
2BBC            SBC  HL,DE               No action is made if the filename is
2BBE            RET  NC                  before the channel.
2BBF            LD   HL,(23653)          Or if it is after (STKEND).
2BC2            SBC  HL,DE
2BC4            RET  C
2BC5            EX   DE,HL               Add to DE the number of 'inserted'
2BC6            ADD  HL,BC               bytes, so returning the new filename
2BC7            EX   DE,HL               address.
2BC8            RET                      Finished.

THE 'CHECK NAME' SUBROUTINE
Whenever a 'filename' is to be compared against the channel name CHNAME, this
subroutine is called. On entry, HL must point to the filename to be compared, while C
must contain its length. If the comparision is succesful, the Zero flag is returned set.

2BC9 CHK_NAME   PUSH IX                  Save start of channel.
2BCB            LD   B,10                Length of a filename.
2BCD CHK_NAME1  LD   A,(HL)              Fetch a byte from the name.
2BCE            CP   (IX+14)
2BD1            JR   NZ,#2BE9,CHK_NAME3  Jump if it doesn't match.
2BD3            INC  HL                  Point to the next character.
2BD4            INC  IX
2BD6            DEC  B                   One byte less.
2BD7            DEC  C                   Repeat until all bytes of the name have
2BD8            JR   NZ,#2BCD,CHK_NAME1  been matched.
2BDA            LD   A,B                 CHNAME remaining length.
2BDB            OR   A
2BDC            JR   Z,#2BE9,CHK_NAME3   Exit if all bytes of CHNAME matched.
2BDE CHK_NAME2  LD   A,(IX+14)           Otherwise the remaining characters of
2BE1            CP   32                  CHNAME have to be spaces.
2BE3            JR   NZ,#2BE9,CHK_NAME3  Exit if not a space.
2BE5            INC  IX                  Repeat until all bytes of CHNAME have
2BE7            DJNZ #2BDE,CHK_NAME2     been examined.
2BE9 CHK_NAME3  POP  IX                  Restore channel start address.
2BEB            RET                      Finished.

THE 'CALL INP' ROUTINE
This routine is the same as the Interface 1 'CALL_INP' routine which handles all IF1's
channels. The DISCiPLE uses this routine only for "M" channels, for "D" channels a
similar routine located in RAM is used. (The only difference is the test of FLAGS3,
i.e. IY+124 while emulating the IF1, #1ACF otherwise.) On entry HL holds the address of
the service 'input' routine. The routine handles both INPUT and INKEY$ commands.

2BEC CALL_INP   RES  3,(IY+2)            Signal 'the mode is to be considered as
                                         being unchanged'.
2BF0            PUSH HL                  Store address of service routine.
2BF1            LD   HL,(23613)          HL points to error address (ERR_SP).
2BF4            LD   E,(HL)              Fetch the error address.
2BF5            INC  HL
2BF6            LD   D,(HL)
2BF7            AND  A
2BF8            LD   HL,#107F,ED_ERROR   If the error address is 'ED_ERROR'
2BFB            SBC  HL,DE               ('main' ROM) then an INPUT command was
2BFD            JR   NZ,#2C28,INKEY$     used. Jump if unequal to 'ED_ERROR'.

Now deal with an 'INPUT #' command referring to a "M" channel.

2BFF            POP  HL                  Restore address of service routine.
2C00            LD   SP,(23613)          Clear the machine stack (ERR_SP).
2C04            POP  DE                  Remove 'ED_ERROR'.
2C05            POP  DE
2C06            LD   (23613),DE          Restore the old value of ERR_SP.
2C0A IN_AGAIN   PUSH HL                  Store address of service routine.
2C0B            LD   DE,#2C10,INPUT_END  Return address is 'INPUT_END' below.
2C0E            PUSH DE
2C0F            JP   (HL)                Jump to the service routine.

When the byte has been read from the required channel, a return is made here to add
the byte to the INPUT line, or to return if the byte is equal to CHR$ 13, i.e. ENTER.

2C10 INPUT_END  JR   C,#2C1A,ACC_CODE    Jump with acceptable codes.
2C12            JR   Z,#2C17,NO_READ     Jump with no data read.
2C14 INPUT_ERR  JP   #2EBF,MD_ERROR      Otherwise jump to the 'hook code' error
                                         routine.
2C17 NO_READ    POP  HL                  Restore address of service routine and
2C18            JR   #2C0A,IN_AGAIN      try again.

An acceptable code was received, it is added to the INPUT line.

2C1A ACC_CODE   CP   13
2C1C            JR   Z,#2C24,END_INPUT   Jump if the code is ENTER.
2C1E            RST  #10,CALBAS          Otherwise the byte is to be added to
2C1F            DEFW #0F85,ADD_CHAR0     the INPUT line. This is done by calling
                                         into the 'ADD_CHAR' subroutine.
2C21            POP  HL                  Restore address of the service routine
2C22            JR   #2C0A,IN_AGAIN      and read the next byte.

2C24 END_INPUT  POP  HL                  Drop the address of the service routine
2C25            JP   #0050,UNPAGE_1      and page-out the DISCiPLE.

Enter here to deal with the INKEY$ function (a single character is returned).

2C28 INKEY$     POP  HL                  Restore address of the service routine.
2C29            LD   DE,#2C2E,INK$_END   Return address is 'INK$_END' below.
2C2C            PUSH DE
2C2D            JP   (HL)                Jump to the service routine.

2C2E INK$_END   RET  C                   Return with acceptable codes or
2C2F            RET  Z                   with no byte read.
2C30            BIT  4,(IY+124)          Otherwise EOF was reached, so jump to
2C34            JR   Z,#2C14,INPUT_ERR   the error routine except when executing
                                         a 'MOVE' command.
2C36            OR   1                   Then return with Zero and Carry flags
2C38            RET                      both reset.

THE '"M" CHANNEL INPUT' ROUTINE
The actual 'input' is handled via 'CALL_INP' above. The service routine is 'MCHAN_IN'
below.

2C39 M_INPUT    LD   IX,(23633)          Make IX point to start of channel.
2C3D            LD   HL,#2C43,MCHAN_IN   Address of the service routine.
2C40            JP   #2BEC,CALL_INP      Jump to the control routine.

THE '"M" CHANNEL INPUT' SERVICE ROUTINE
This is the actual read a byte from the "M" channel routine. The byte is read from the
data buffer in the channel, if it is empty the next sector is loaded from disk (provided
that the 'current' data block is not the EOF one) before reading the byte.

2C43 MCHAN_IN   BIT  0,(IX+24)           Jump to the 'hook code' error routine
2C47            JP   NZ,#2EBF,MD_ERROR   if (CHFLAG) indicates 'read' file.
2C4A TEST_M_BUF LD   E,(IX+11)           Fetch current byte counter from
2C4D            LD   D,(IX+12)           (CHBYTE).
2C50            LD   L,(IX+69)           Fetch record length from (RECLEN).
2C53            LD   H,(IX+70)
2C56            SCF                      Include byte to be read.
2C57            SBC  HL,DE
2C59            JR   C,#2C6E,CHK_M_EOF   Jump if all bytes have been read.
2C5B            INC  DE                  Include byte to be read in the byte
                                         counter.
2C5C            LD   (IX+11),E           And store it.
2C5F            LD   (IX+12),D
2C62            DEC  DE                  Position of character to be read.
2C63            PUSH IX                  Save start address of channel.
2C65            ADD  IX,DE               IX now points to 'byte to be
                                         read - 82'.
2C67            LD   A,(IX+82)           Fetch the byte.
2C6A            POP  IX                  Restore start of channel.
2C6C            SCF                      Signal 'acceptable code'.
2C6D            RET                      Finished.

If all bytes in the data block have been read, a check is made to see if it is the
'end of file' block, i.e. the last one.

2C6E CHK_M_EOF  BIT  1,(IX+67)           Jump if (RECFLG) indicates 'not the End
2C72            JR   Z,#2C78,NEW_BUFF    Of File' block.
2C74            XOR  A                   Otherwise Zero and Carry flag are reset
                                         to signal 'EOF'.
2C75            ADD  A,13                Returned byte is CHR$ 13, i.e. ENTER.
2C77            RET                      Finished.

A new data block is now read from the disk drive.

2C78 NEW_BUFF   LD   DE,0                Clear the byte counter.
2C7B            LD   (IX+11),E
2C7E            LD   (IX+12),D
2C81            INC  (IX+13)             Increment (CHREC), i.e. record number.
2C84            CALL #2C89,GET_RECD      Fetch a new data block.
2C87            JR   #2C4A,TEST_M_BUF    Read the byte.

THE 'GET A RECORD' SUBROUTINE
This subroutine is used to load a record of a 'MICRODRIVE'-type file.

2C89 GET_RECD   LD   C,3                 Three retries will be made before the
                                         routine is exitted when an error
                                         occurs.
2C8B            BIT  1,(IX+67)
2C8F            JR   NZ,#2CBA,GET_R3     Jump if (RECFLG) indicates 'EOF' block.
2C91 GET_R1     PUSH IX                  Store channel pointer (in 'main' RAM).
2C93            LD   DE,540              Microdrive file records have 540 bytes
                                         each.
2C96 GET_R2     PUSH IX                  Store data buffer pointer.
2C98            LD   IX,#1AC3            Point to the DRAM channel.
2C9C            CALL #3126,LBYT          Fetch a byte.
2C9F            POP  IX                  Restore data buffer pointer.
2CA1            LD   (IX+55),A           Loading starts with the data block
                                         preamble (offset 55).
2CA4            INC  IX
2CA6            CALL #2E62,DEC_DE        Decrement DE.
2CA9            JR   NZ,#2C96,GET_R2     Repeat until DE=0.
2CAB            POP  IX                  Restore channel pointer.
2CAD            LD   A,(IX+68)           Fetch number of this record (RECNUM).
2CB0            CP   (IX+13)             Test it against wanted record number
2CB3            RET  Z                   (CHREC), exit if they are equal.
2CB4            BIT  1,(IX+67)           Jump to load the next record if
2CB8            JR   Z,#2C91,GET_R1      (RECFLG) indicates that this isn't the
                                         EOF one.
2CBA GET_R3     DEC  C                   Decrement retry counter.
2CBB            JR   Z,#2CE3,MD_ERROR1   Exit via the 'hook code' error routine
                                         when three retries have been made.

Now the routine reloads the first sector of the file. With 'MICRODRIVE'-type files it
is possible to have a 'read' channel attached to a file to which is also a 'write'
channel attached. So the last record could have been read into the 'read' channels data
buffer after which a new record was added by the 'write' channel. The reason why three
retries are made is probably because of the ignoring of errors, signalled by a set
Carry flag (remember this is a 'hook code' executing), reported by 'LBYT' and 'RSAD'.
The routine does some retrying before quitting.

2CBD            PUSH HL                  Store the registers needed by the
2CBE            PUSH IX                  routine above.
2CC0            PUSH BC
2CC1            LD   A,(IX+25)           Fetch the drive number from CHDRIV.
2CC4            CALL #2A33,SEL_DRIVE     Select the drive.
2CC7            LD   DE,14               Make IX point to CHNAME, the name of
2CCA            ADD  IX,DE               the requested file.
2CCC            CALL #2D43,FIND_FILE     Search for the filename.
2CCF            JR   NZ,#2CE3,MD_ERROR1  Jump if not found.
2CD1            INC  HL                  Skip 'number of sectors used'.
2CD2            INC  HL
2CD3            LD   D,(HL)              Fetch first track and sector.
2CD4            INC  HL
2CD5            LD   E,(HL)
2CD6            LD   IX,#1AC3            Point to the DRAM channel.
2CDA            CALL #2F4F,RSAD          Read the first sector.
2CDD            POP  BC                  Restore registers.
2CDE            POP  IX
2CE0            POP  HL
2CE1            JR   #2C91,GET_R1        Try to find the right record again.

THE 'JUMP TO ERROR ROUTINE'
Because this jump is only two times 'jump relatived to', it wastes one byte.

2CE3 MD_ERROR1  JP   #2EBF,MD_ERROR      Jump to the 'hook code' error routine.

THE '"M" CHANNEL DATA' TABLE
The '25' bytes that compose the initial part of an "M" channel are as follows:

2CE6            DEFW #0008               Main ROM 'output' routine.
2CE8            DEFW #0008               Main ROM 'input' routine.
2CEA            DEFB "M"+128             Channel specifier.
2CEB            DEFW #2DB8               DISCiPLE ROM 'output' routine.
2CED            DEFW #2C39               DISCiPLE ROM 'input' routine.
2CEF            DEFW 595                 Channel length.
2CF1            DEFW 0                   Default for CHBYTE.
2CF3            DEFB 0                   Default for CHREC.
2CF4            DEFM "          "        Default for CHNAME (10 spaces).
2CFE            DEFB 255                 Default for CHFLAG ('write' channel).

THE 'CLOSE FILE' SUBROUTINE
By using 'hook code' 35 (#23) the following subroutine is called. It CLOSEs an "M"
channel which start adddress is held in the IX register. If the channel is used for
reading, then it is reclaimed; but if it is used for writing, any unsent data in the
buffer is written to disk before reclaiming the channel.

2CFF CLOSE_M2   BIT  0,(IX+24)           Jump if (CHFLAG) indicates that this is
2D03            JR   Z,#2D17,CLOSE_M1    a 'read' channel.
2D05            SET  1,(IX+67)           Otherwise signal 'EOF record',
2D09            CALL #2DDE,WR_RECD       and save it on disk.
2D0C            PUSH IX                  Save channel pointer.
2D0E            LD   IX,#1AC3            Point to the DRAM channel.
2D12            CALL #353C,CFSM          Close the File Sector Map.
2D15            POP  IX                  Restore channel pointer.
2D17 CLOSE_M1   CALL #2E69,DEL_M_BUF     Reclaim the channel.
2D1A            RET

THE 'ERASE' SUBROUTINE
This subroutine is called using 'hook code' 36 (#24). It deals with the ERASEing of all
file types. It differs from the DISCiPLE's ERASE 'command code': this routine uses a
temporary channel and the IF1's extra system variables to ERASE a file. On entry
'D_STR1' must hold the drive number and 'N_STR1' the length and the start of the
filename.

2D1B ERASE      CALL #2AF1,SET_T_MCH     Create a temporary "M" channel.
2D1E            PUSH IX                  Store channel pointer.
2D20            LD   DE,14               Make IX point to CHNAME, the name of
2D23            ADD  IX,DE               the file to be ERASEd.
2D25            CALL #2D43,FIND_FILE     Search for the file.
2D28            POP  IX                  Restore channel pointer.
2D2A            PUSH AF                  Save flags.
2D2B            JR   NZ,#2D3E,ERASE_1    Jump if the file wasn't found.
2D2D            LD   HL,#1BD6            Point to the start of the disk buffer.
2D30            ADD  HL,BC               BC holds the directory entries offset
                                         (i.e. 0 for first, 256 for second).
2D31            LD   (HL),0              Signal 'ERASEd file'.
2D33            PUSH IX                  Store channel pointer.
2D35            LD   IX,#1AC3            Point to the DRAM channel.
2D39            CALL #2F04,WSAD          Write sector DE.
2D3C            POP  IX                  Restore channel pointer.
2D3E ERASE_1    CALL #2E69,DEL_M_BUF     Reclaim the channel.
2D41            POP  AF                  Exit with Zero reset indicating 'file
2D42            RET                      not found'.

THE 'FIND A FILE' SUBROUTINE
This routine searches the disk CATalogue for the filename pointed to by the IX
register. On exit, Zero reset signals 'file not found'.

2D43 FIND_FILE  CALL #3030,REST          Reset drive to track 0.
2D46            LD   (#1ACA),IX          Store the pointer to filename
                                         requested.
2D4A FIND_FILE1 LD   IX,#1AC3            Point to the DRAM channel.
2D4E            CALL #2F4F,RSAD          Load a sector to the disk buffer.
2D51            LD   BC,0                First entry's offset.
2D54 FIND_FILE2 LD   HL,#1BD6            Point to the start of the disk buffer.
2D57            ADD  HL,BC               Point to directory entry.
2D58            LD   A,(HL)
2D59            CP   0
2D5B            JR   Z,#2D7C,FIND_FILE4  Jump if the file is ERASEd.
2D5D            INC  HL                  Point to the filename.
2D5E            LD   IX,(#1ACA)          Fetch pointer to filename requested.
2D62            LD   A,10                Length of filename.
2D64            LD   (#1DEA),A
2D67 FIND_FILE3 LD   A,(IX+0)            Fetch a byte from requested name.
2D6A            XOR  (HL)                Compare against found name.
2D6B            AND  #DF                 Capitalize.
2D6D            JR   NZ,#2D7C,FIND_FILE4 Jump if they don't match.
2D6F            INC  IX                  Next characters.
2D71            INC  HL
2D72            LD   A,(#1DEA)
2D75            DEC  A
2D76            LD   (#1DEA),A
2D79            JR   NZ,#2D67,FIND_FILE3 Repeat for all characters in the name.
2D7B            RET                      Return with Zero set to indicate 'file
                                         found'.

The requested filename wasn't found yet, so examine the next file.

2D7C FIND_FILE4 LD   A,B
2D7D            CP   1
2D7F            JR   Z,#2D8D,FIND_FILE5  Jump if second entry handled.
2D81            LD   A,(#1DDA)
2D84            AND  #04                 Jump if using single density, i.e. each
2D86            JR   NZ,#2D8D,FIND_FILE5 sector holds one entry.
2D88            LD   BC,256              Otherwise examine second entry.
2D8B            JR   #2D54,FIND_FILE2

The next CATalogue sector has to be loaded, if present.

2D8D FIND_FILE5 INC  E                   Next sector.
2D8E            LD   A,E
2D8F            CP   11                  Jump if last sector on current track
2D91            JR   NZ,#2D4A,FIND_FILE1 hasn't been loaded yet.
2D93            LD   E,1                 Otherwise start with sector 1
2D95            INC  D                   on the next track.
2D96            LD   A,D
2D97            CP   4                   Jump if last track in CATalogue hasn't
2D99            JR   NZ,#2D4A,FIND_FILE1 been handled yet.
2D9B            CP   0                   Otherwise reset Zero flag to signal
2D9D            RET                      'file not found' and exit.

THE 'READ SEQUENTIAL' SUBROUTINE
This is called by using 'hook code' 37 (#25). The subroutine reads into the data block
of the current "M" channel, the next record of a named PRINT-type file. On entry IX
must hold the "M" channel start address, and CHREC the number of the current record.
CHREC will be automatically incremented. CHDRIV must hold the drive number and CHNAME
must hold the filename.

2D9E READ_SEQ   BIT  1,(IX+67)           Jump if (RECFLG) indicates that the
2DA2            JR   Z,#2DA7,INCREC      current record isn't the EOF one.
2DA4            JP   #2EBF,MD_ERROR      Otherwise exit via the 'hook code'
                                         error routine.
2DA7 INCREC     INC  (IX+13)             Increment the record number (CHREC) and
                                         continue into 'RD_RANDOM'.

THE 'READ RANDOM' SUBROUTINE
This subroutine is called by using 'hook code' 39 (#27). The record number CHREC of a
PRINT-type file is loaded into the data block. The other variables are to be set as for
'READ_SEQ' above.

2DAA RD_RANDOM  CALL #2C89,GET_RECD      Load CHREC record.
2DAD            BIT  2,(IX+67)           Return only if (RECFLG) indicates that
2DB1            RET  Z                   it is a PRINT-type file.
2DB2            CALL #2E69,DEL_M_BUF     Otherwise reclaim the channel and exit
2DB5            JP   #2EBF,MD_ERROR      via the 'hook code' error routine.

THE '"M" CHANNEL OUTPUT' ROUTINE
This routine handles the "M" channel output. The byte stored in the A register is
stored into the 512-byte buffer. When it is filled, the record is written onto disk.

2DB8 MCHAN_OUT  LD   IX,#FFFA            This is -6.
2DBC            ADD  IX,DE               Point to the start of the channel.
2DBE            BIT  0,(IX+24)           Continue only if (CHFLAG) indicates
2DC2            JP   Z,#2EBF,MD_ERROR    that this is a 'write' file.
2DC5            LD   E,(IX+11)           Fetch the byte pointer (CHBYTE).
2DC8            LD   D,(IX+12)
2DCB            PUSH IX                  Save start address of channel.
2DCD            ADD  IX,DE               Point to 'first free byte in
                                         buffer'-82.
2DCF            LD   (IX+82),A           Store the byte into the buffer.
2DD2            POP  IX                  Restore start of channel.
2DD4            INC  DE                  Update (CHBYTE).
2DD5            LD   (IX+11),E
2DD8            LD   (IX+12),D
2DDB            BIT  1,D                 Return if the buffer is not filled
2DDD            RET  Z                   (position 512 has not been reached).

If the buffer is filled, the routine continues into 'WR_RECD' below.

THE 'WRITE RECORD' SUBROUTINE
This subroutine is called by using 'hook code' 38 (#26). The record held in the "M"
channel pointed by the IX register (with name CHNAME and number CHREC), is written
onto the disk inserted into drive CHDRIV.

2DDE WR_RECD    LD   A,(IX+25)           Fetch the drive number (CHDRIV).
2DE1            CALL #2A33,SEL_DRIVE     Select the drive.
2DE4            PUSH IX                  Save start address of channel.
2DE6            LD   B,10                Counts ten characters.
2DE8 CP_NAME    LD   A,(IX+14)           Copy CHNAME into RECNAM.
2DEB            LD   (IX+71),A
2DEE            INC  IX
2DF0            DJNZ #2DE8,CP_NAME
2DF2            POP  IX                  Restore start of channel.
2DF4            LD   C,(IX+11)           Copy CHBYTE into RECLEN.
2DF7            LD   (IX+69),C
2DFA            LD   A,(IX+12)
2DFD            LD   (IX+70),A
2E00            LD   A,(IX+13)           Copy CHREC into RECNUM.
2E03            LD   (IX+68),A
2E06            PUSH IX                  Make HL point to the start of the data
2E08            POP  HL                  workspace,
2E09            LD   DE,67               i.e. RECFLG.
2E0C            ADD  HL,DE
2E0D            CALL #2E27,CHKS_HD_R     Calculate DESCHK checksum.
2E10            LD   DE,15               Make HL point to the start of the
2E13            ADD  HL,DE               512-byte buffer.
2E14            CALL #2E2C,CHKS_BUFF     Calculate DCHK checksum.
2E17            CALL #2E45,SAVE_RECD     Save the record to disk.
2E1A            LD   DE,0                Clear CHBYTE.
2E1D            LD   (IX+11),E
2E20            LD   (IX+12),D
2E23            INC  (IX+13)             Increment the record number (CHREC).
2E26            RET                      Finished.

THE 'CALCULATE/COMPARE CHECKSUM' ROUTINE
This routine is used to calculate DESCHK and DCHK checksums, or to compare the previous
checksum against the current one; the Zero flag is returned set if the checksums match.
The entry point is CHK_HD_R for DESCHK, or CHKS_BUFF for DCHK checksum. On entry in
both cases HL must contain the start address of the block for which the checksum is to
be obtained.

2E27 CHKS_HD_R  LD   BC,14               The block length.
2E2A            JR   #2E2F,CHKS_ALL      Calculate checksum for the block.

2E2C CHKS_BUFF  LD   BC,512              The block length.
2E2F CHKS_ALL   PUSH HL                  The start address is preserved.
2E30            LD   E,0                 Clear checksum.
2E32 CHKS_1     LD   A,E                 Add the current byte to the previous
2E33            ADD  A,(HL)              sum.
2E34            INC  HL                  Point to next location.
2E35            ADC  A,1                 Include also the carry + 1.
2E37            JR   Z,#2E3A,CHKS_2      Jump if A reaches zero.
2E39            DEC  A                   Otherwise balance the 'ADC' above.
2E3A CHKS_2     LD   E,A                 Update sum.
2E3B            DEC  BC                  One byte less to add.
2E3C            LD   A,B
2E3D            OR   C
2E3E            JR   NZ,#2E32,CHKS_1     Repeat until all bytes have been added.
2E40            LD   A,E
2E41            CP   (HL)                Compare with previous checksum.
2E42            LD   (HL),A              Store the new one.
2E43            POP  HL                  Restore start address.
2E44            RET                      Finished.

THE 'SAVE A RECORD' SUBROUTINE
This subroutine saves the 540 byte Microdrive-file record to disk.

2E45 SAVE_RECD  PUSH IX                  Save the channel pointer.
2E47            PUSH IX
2E49            POP  HL                  Calculate the address of the first byte
2E4A            LD   DE,55               to SAVE, i.e. the data block preamble
2E4D            ADD  HL,DE               (offset 55).
2E4E            LD   DE,540              Length of the record to be written.
2E51            LD   IX,#1AC3            Point to the DRAM channel.
2E55 SAVE_REC1  LD   A,(HL)              Fetch a byte.
2E56            CALL #3108,SBYT          Save it to disk.
2E59            INC  HL
2E5A            CALL #2E62,DEC_DE        Decrement DE.
2E5D            JR   NZ,#2E55,SAVE_REC1  Repeat until DE=0.
2E5F            POP  IX                  Restore the channel pointer.
2E61            RET                      Finished.

THE 'DECREMENT DE' SUBROUTINE
This very small subroutine decrements DE and returns with the Zero flag indicating if
DE holds zero on exit. The purpose of this three-byte subroutine is unclear, it doesn't
save a single byte (a CALL instruction takes also three bytes so this subroutine makes
the code only longer), and the readability of the code (or the source) doesn't improve
really.

2E62 DEC_DE     DEC  DE                  DE=DE-1.
2E63            LD   A,D
2E64            OR   E                   Set Zero flag if DE=0.
2E65            RET                      Finished.

THE 'READ SECTOR' SUBROUTINE
This subroutine is not implemented, it is called by using 'hook code' 40  (#28). When
used with an IF1 the sector, which number is held in CHREC, is read into the channel
area. If the sector doesn't belong to a PRINT-type file the data buffer is cleared
before returning. On entry the required drive motor has to be turned on.

2E66 RD_SECTOR  RET

THE 'READ NEXT SECTOR' SUBROUTINE
This subroutine called by using 'hook code' 41 (#29) isn't implemented either. It
should load into the channel area the first header and data block that pass through the
Microdrive head. The required drive motor has to be started before calling this routine.

2E67 RD_NEXT    RET

THE 'WRITE SECTOR' SUBROUTINE
Another unimplemented subroutine, called by using 'hook code' 42 (#2A) it writes the
data block in the current channel (pointed to by IX) to the sector specified by CHREC.
The required Microdrive has to be started and all channel variables, such as CHNAME, are
to be set as required before calling the routine.

2E68 WR_SECTOR  RET

THE 'RECLAIM "M" CHANNEL' SUBROUTINE
This subroutine (also called by using 'hook code' 44 (#2C)) is used to reclaim the "M"
channel pointed by the IX register. Unlike the IF1 routine this routine neither closes
the stream(s) attached to this channel, nor updates the stream data for channels moved
down after the reclaiming.

2E69 DEL_M_BUF  PUSH IX                  Make HL point to the start of the
2E6B            POP  HL                  channel.
2E6C            LD   BC,595              Length of the channel.
2E6F            RST  #10,CALBAS          Delete the channel area by calling
2E70            DEFW #19E8,RECLAIM_2     'RECLAIM_2' in the 'main' ROM.
2E72            RET                      Finished.

THE 'OPEN TEMP. "N" CHANNEL' SUBROUTINE
The DISCiPLE doesn't support the use of "N" channels, temporary or permanent, by the
user. This routine is called by using 'hook code' 45 (#2D).

2E73 OP_TEMP_N  RET

THE 'CLOSE NETWORK CHANNEL' SUBROUTINE
Because the DISCiPLE doesn't support "N" channels, the CLOSEing of them isn't supported
either ('hook code' 46 (#2E)).

2E74 CLOSE_NET  RET

THE 'GET PACKET FROM NETWORK' SUBROUTINE
Called by using 'hook code' 47 (#2F), this subroutine to fetch a header and data block
from the network isn't implemented.

2E75 GET_PACK   RET

THE 'SEND PACKET' SUBROUTINE
The DISCiPLE doesn't support the sending of a header and data block over the network
('hook code' 48 (#30)).

2E76 SEND_PACK  RET

THE 'CREATE IF1 VARIABLES' SUBROUTINE
This subroutine (called by using 'hook code' 49 (#31)) has the task of creating the
IF1's new system variables if nonexistent. Many variables are initialised to their
default values.

2E77 HOOK_31    LD   HL,(23631)          Fetch start of channel area (CHANS).
2E7A            LD   DE,#A349            This is -23735.
2E7D            ADD  HL,DE               The Carry flag is now set if the CHANS
                                         area starts after address 23734, i.e.
                                         the 'new' variables exist already.
2E7E            JR   C,#2EA6,VAR_EXIST   Jump if they exist already.
2E80            LD   HL,(23651)          Clear the calculator stack by copying
2E83            LD   (23653),HL          (STKBOT) into (STKEND).
2E86            LD   HL,23698            Set (MEM) with the address of the
2E89            LD   (23656),HL          MEMBOT area.
2E8C            LD   HL,23733            One location before the new space is
                                         needed.
2E8F            LD   BC,58               There are 58 new variables.
2E92            RST  #10,CALBAS          Use 'main' ROM 'MAKE_ROOM' to create
2E93            DEFW #1655,MAKE_ROOM     the space.
2E95            LD   HL,#2EAB            Address of 'default values' table.
2E98            LD   BC,19               There are 19 default values.
2E9B            LD   DE,23734            Start of 'new' variables area.
2E9E            LDIR                     Store default values.
2EA0            LD   A,1                 Set (COPIES) to 1.
2EA2            LD   (23791),A
2EA5            RET                      Finished.

2EA6 VAR_EXIST  RES  1,(IY+124)          Signal 'new variables already exist'.
2EAA            RET

THE 'SYSTEM VARS DEFAULT VALUES' TABLE
This table contains the default values of all the 'new' IF1 system variables from
FLAGS3 to SER_FL.

2EAB            DEFB #02                 Default for FLAGS3 (bit 1 is set to
                                         signal that the shadow ROM has been
                                         paged in for the first time).
2EAC            DEFW #01F0               Default for VECTOR is the IF1's 'ERR_6'
                                         address (nonsense for DISCiPLE).
2EAE            LD   HL,0                This short subroutine is used to call
2EB1            CALL 0                   'main' ROM routines from the IF1 ROM,
2EB4            LD   (23738),HL          it isn't used with the DISCiPLE.
2EB7            RET
2EB8            DEFW 12                  Default for BAUD, i.e. 9600 baud.
2EBA            DEFB 1                   Default for NSTAT.
2EBB            DEFB 0                   Default for IOBORD, the colour during
                                         IF1 I/O (black).
2EBC            DEFW 0                   Default for SER_FL.

THE 'CALL IF1 SUBROUTINE' SUBROUTINE
Not supported by the DISCiPLE this subroutine, called by using 'hook code' 50 (#32),
is designed to call IF1 ROM-routines when the 'main' ROM is paged in.

2EBE HOOK_32    RET

THE 'HOOK CODE ERROR' ROUTINE
Whenever an error is encountered in the 'hook code' routines a jump is made here to
signal the error and clear the machine stack when necessary.

2EBF MD_ERROR   CALL #3B21,BORD_REST     Restore the border colour.
2EC2            LD   HL,(#0296)
2EC5            LD   A,H
2EC6            OR   L
2EC7            JR   Z,#2ECA,MD_ERR1     Jump if the stack isn't to be cleared.
2EC9            LD   SP,HL               Otherwise clear the stack.
2ECA MD_ERR1    XOR  A
2ECB            DEC  A
2ECC            SCF                      Exit with A holding 255 and Carry flag
2ECD            RET                      set.
Previous Next Contents Index