Previous Next Contents Index
The stream handling routines I

THE 'EVALUATE STREAM NUMBER' SUBROUTINE
A single numeric expression is evaluated and the result, in the range 0..15 is stored
into 'STRM_NUM1'.

109D EXPT_#_NR  RST  #28,NEXT_C_RAM      Advance CH_ADD.
109E EXPT_#_NR1 RST  #10,CALBAS          Evaluate stream number.
109F            DEFW #1C82,EXPT_1NUM
10A1            RST  #30,SYNTAX_Z        Return if syntax is being checked.
10A2            RET  Z
10A3            PUSH AF
10A4            RST  #10,CALBAS          Fetch the number.
10A5            DEFW #1E94,FIND_INT1
10A7            CP   16                  Give an error if it isn't in the range
10A9            JP   NC,#2932,REP_9      0..15. ('Invalid station' ?)
10AC            LD   (#1E03),A           Store stream number into 'STRM_NUM1'.
10AE            POP  AF
10B0            RET

THE 'MOVE' COMMAND SYNTAX ROUTINE
A 'MOVE' command requires two sets of parameters, for the 'input' channel, and for the
'output' channel. These parameters are stored into the UFIA's.

10B1 MOVE       CALL #115B,EXPT_EXP1     Evaluate stream or channel expression.
10B4            CP   204                 The keyword 'TO' must be present,
10B6            JP   NZ,#2920,REP_0      give an error if 'TO' is missing.
10B9            CALL #0AA2,SWAP_UFIAS    Exchange the UFIA's.
10BC            CALL #115B,EXPT_EXP1     Evaluate second stream or channel
                                         expression.
10BF            CALL #0AA2,SWAP_UFIAS    Exchange the UFIA's again.
10C2            CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax check.

The actual 'MOVE' command reads a byte from the source channel or stream, and then
writes it to the destination channel or stream. This is repeated until the first
channel or stream reports 'End Of File'. 'SIGN_STEAL' is called to signal to the
'D_INPUT' routine at #148A that the 'END of file' error isn't to be generated.

10C5            CALL #09D8,SIGN_STEAL    See above.
10C8            LD   A,191               This is the keyword 'IN', it is used to
10CA            LD   (#1E02),A           signal 'READ channel'.
10CD            CALL #1188,OP_MOVE       Open the source channel/stream.
10D0            LD   HL,(23631)          Save (CHANS).
10D3            PUSH HL
10D4            LD   A,(#1E02)           Save 'DIR_DESCR1' into 'DIR_DESCR2'.
10D7            LD   (#1E1E),A
10DA            CALL #0AA2,SWAP_UFIAS    Exchange the UFIA's.
10DD            LD   A,223               This is the keyword 'OUT'.
10DF            LD   (#1E02),A           Signal 'WRITE channel'.
10E2            LD   IX,#1AC3            Pointer to DFCA.
10E6            CALL #1188,OP_MOVE       Open the destination channel/stream.
10E9            JR   NC,#10F7,MOVE_RUN1  Jump if opening was successfull. I.e. file
                                         was 'new' or 'old' file was overwritten.
10EB            LD   IX,(#1E1E)          Otherwise reclaim first channel. (Second
10EF            CALL #114C,RECL_CHAN     wasn't opened so nothing to reclaim.)
10F2            POP  HL                  Drop (CHANS) address.
10F3            POP  HL                  ?? Drop what?
10F4            JP   #0419,END           Finished.

10F7 MOVE_RUN1  CALL #0AA2,SWAP_UFIAS    Exchange UFIA's again.

To my knowledge the instructions at #10D0, #10D3, #10F2 and from #10FA to #1106 aren't
needed with the DISCiPLE. With IF1 the Microdrive maps are situated between 23734 (end
of Spectrum system variables) and (CHANS). The consequence of opening a new channel
could be the creating of a new map. I.e. the channel information could move up and then
the source channels address is to be recalculated. With the DISCiPLE, however, nothing
is situated between 23734 and (CHANS).

10FA            POP  DE                  Retrieve 'old' (CHANS).
10FB            LD   HL,(23631)          Fetch 'new' (CHANS).
10FE            OR   A                   Calculate the space which was inserted
10FF            SBC  HL,DE               under (CHANS).
1101            LD   DE,(#1E05)          Adjust first channels address.
1105            ADD  HL,DE
1106            LD   (#1E05),HL
1109 MOVE_RUN2  LD   HL,(#1E05)          Make 'current' the first channel.
110C            LD   (23633),HL          (CURCHL)
110F MOVE_RUN3  RST  #10,CALBAS          Call 'INPUT_A' in the 'main' ROM to
1110            DEFW #15E6,INPUT_A       read a byte.
1112            JR   C,#1118,MOVE_RUN4   Jump with acceptable codes.
1114            JR   Z,#110F,MOVE_RUN3   Repeat if no byte read.
1116            JR   #1123,MOVE_RUN5     Jump if EOF has been reached.

An acceptable code has been found.

1118 MOVE_RUN4  LD   HL,(#1E1E)          Make 'current' the 2nd channel.
111B            LD   (23633),HL          (CURCHL)
111E            RST  #10,CALBAS          Use 'main' ROM 'PRINT_A_2' to send the
111F            DEFW #15F2,PRINT_A_2     byte to the 2nd channel.
1121            JR   #1109,MOVE_RUN2     Repeat until EOF.

EOF has been reached.

1123 MOVE_RUN5  XOR  A                   Clear FLAGS3.
1124            LD   (#1ACF),A
1127            LD   HL,(23631)          Store current (CHANS).
112A            PUSH HL
112B            CALL #0AA2,SWAP_UFIAS    Exchange the UFIA's.
112E            CALL #11C0,CL_MOVE       Close the destination channel.
1131            CALL #0AA2,SWAP_UFIAS    Exchange the UFIA's again.

Again the instructions at address #1127, #112A and from #1134 to #1140 aren't needed
with the DISCiPLE.

1134            POP  DE                  Restore initial address of CHANS.
1135            LD   HL,(23631)          Fetch current (CHANS).
1138            OR   A                   Calculate the amount of bytes reclaimed
1139            SBC  HL,DE               after the deletion of the second
                                         channel.
113B            LD   DE,(#1E05)          Calculate the new start address of the
113F            ADD  HL,DE               first channel.
1140            LD   (#1E05),HL          And store it.
1143            CALL #11C0,CL_MOVE       Close the source channel.
1146            CALL #11D6,RECL_TEMP     Reclaim temporary channels.
1149            JP   #0419,END           Finished.

THE 'RECLAIM CHANNEL' SUBROUTINE
This subroutine is used to reclaim the channel pointed to by IX.

114C RECL_CHAN  LD   C,(IX+9)            Fetch channel length.
114F            LD   B,(IX+10)
1152            PUSH BC
1153            PUSH IX                  Channel start to HL.
1155            POP  HL
1156            RST  #10,CALBAS          Call 'RECLAIM_2' in the 'main' ROM to
1157            DEFW #19E8,RECLAIM_2     reclaim the channel.
1159            POP  BC
115A            RET

THE 'EVALUATE STRM. OR EXPR.' SUBROUTINE
This subroutine is used to check the syntax of the 'MOVE' command. If the 'current'
character is a hash sign (#), then a stream number is evaluated. Otherwise a device
expression is evaluated.

115B EXPT_EXP1  RST  #28,NEXT_C_RAM      Advance CH_ADD.
115C            CP   "#"                 Jump to 'EXPT_#_NR' to evaluate stream
115E            JP   Z,#109D,EXPT_#_NR   number if character is a '#'.
1161 EXPT_EXP2  LD   (#1E04),A           Otherwise store device letter.
1164            AND  #DF                 Only capitals.
1166            CP   "D"                 If device letter isn't "D" then
1168            CALL NZ,#0A3E,MD_SYNTAX1 evaluate microdrive syntax.
116B            CALL #0A5E,EXPT_DEVN     Evaluate device number.
116E            CALL #0A1E,SEPARATOR     If there is a separator exit via
1171            JP   Z,#0ABC,EXP_F_NAME  'EXP_F_NAME' to evaluate a filename.
1174            RST  #30,SYNTAX_Z
1175            RET  Z                   Return if checking syntax.
1176            PUSH AF
1177            LD   A,(#1E04)           Fetch device letter.
117A            AND  #DF                 Only capitals.
117C            CP   "D"                 If the device is "D" or "M" then there
117E            JP   Z,#2924,REP_2       must be a name present. Give an error
1181            CP   "M"                 if no name specified.
1183            JP   Z,#2924,REP_2
1186            POP  AF
1187            RET

THE 'USE STREAM OR CHANNEL' SUBROUTINE
This subroutine is used from the 'MOVE' command routine above to fetch the start
address of the channel attached to a stream, or to open a channel and fetch its start
address.

1188 OP_MOVE    LD   A,(#1E03)           Fetch stream number.
118B            INC  A                   Jump to open a temporary channel, i.e. if
118C            JR   Z,#1199,OP_MOVE1    the stream was nonexistent.
118E            DEC  A
118F            RST  #10,CALBAS          Open the channel attached to stream A.
1190            DEFW #1601,CHAN_OPEN
1192            LD   HL,(23633)          Store the channels address (CURCHL)
1195            LD   (#1E05),HL          into UFIA1.
1198            RET                      Return.

1199 OP_MOVE1   LD   A,(#1E04)           Fetch device letter.
119C            AND  #DF                 Capitals only.
119E            CP   "M"
11A0            JR   Z,#11A6,OP_MOVE2    Jump if it's a "M".
11A2            CP   "D"
11A4            JR   NZ,#11B7,OP_MOVE3   Jump if it isn't a "D".
11A6 OP_MOVE2   CALL #2984,JTEST_DRV     Check if the drive is defined.
11A9            CALL #128D,OP_TEMP_D     Open a temporary "D" channel.
11AC            LD   A,(#1E05)           Save 'DIR_DESCR1' into 'PROG_NUM1'.
11AF            LD   (#1E02),A
11B2            LD   (#1E05),IX          Store channels address.
11B6            RET

11B7 OP_MOVE3   CP   "N"
11B9            JP   NZ,#2920,REP_0      Give an error if device isn't "N".
11BC            CALL #09DD,SIGN_NET      Otherwise signal 'using network'.
11BF            RET

THE 'CLOSE "MOVE" CHANNEL' SUBROUTINE
This is the opposite subroutine of the preceeding one, and is used to CLOSE the channel
used by the 'MOVE' command routine. If 'STRM_NUM1' denotes that a stream was used,
nothing is done.

11C0 CL_MOVE    LD   A,(#1E03)           Fetch stream number.
11C3            INC  A
11C4            RET  NZ                  Return if a stream has been used.
11C5            LD   A,(#1E04)           Otherwise fetch device letter.
11C8            AND  #DF                 Only capitals.
11CA            CP   "N"
11CC            JR   Z,#11D5,CL_MOVE1    Jump if it was "N".
11CE            LD   IX,(#1E05)          Fetch channel address.
11D2            JP   #1205,CLOSE_CHAN    Close the channel and exit.
11D5 CL_MOVE1   RET

THE 'RECLAIM TEMP. CHANNELS' SUBROUTINE
This subroutine is called to reclaim from the CHANS all 'temporary' channels (i.e. with
bit 7 of the channel specifier set).

11D6 RECL_TEMP  LD   IX,(23631)          Point to the start of the channel area.
11DA            LD   DE,20               IX now points to the first
11DD            ADD  IX,DE               'non-standard' channel.
11DF RECL_T1    LD   A,(IX+0)
11E2            CP   #80                 Return if the end marker was found, i.e.
11E4            RET  Z                   there are no more channels,
11E5            LD   A,(IX+4)            Fetch channel specifier.
11E8            CP   "D"+128
11EA            JR   NZ,#11F1,RECL_T2    Jump if not a temporary "D" channel.
11EC            CALL #1205,CLOSE_CHAN
11EF            JR   #11D6,RECL_TEMP

Permanent "D" channels mustn't be closed, except when 'CLEAR #' was given.

11F1 RECL_T2    CALL #09FB,TEST_SERV
11F4            JR   Z,#11FB,RECL_T3     Jump if not 'CLEAR # executing'.
11F6            CALL #114C,RECL_CHAN     Otherwise reclaim the channel.
11F9            JR   #11D6,RECL_TEMP

Skip this channel.

11FB RECL_T3    LD   E,(IX+9)            Fetch channel length.
11FE            LD   D,(IX+10)
1201            ADD  IX,DE               Point to the next channel.
1203            JR   #11DF,RECL_T1       Repeat for all channels.

THE 'CLOSE CHANNEL' SUBROUTINE
This subroutine closes the channel pointed to by IX.

1205 CLOSE_CHAN PUSH IX
1207            POP  HL
1208            LD   DE,(23631)          (CHANS).
120C            OR   A
120D            SBC  HL,DE               Calculate channel offset.
120F            INC  HL
1210            LD   (#1DED),HL          The channel is CLOSEd by jumping into the
1213            JP   #142E,CLOSE_0       'CLOSE' routine

THE 'OPEN' COMMAND SYNTAX ROUTINE
This routine deals with the 'OPEN #' command concerning DISCiPLE channels, Spectrum
channels are handled by the 'main' ROM.

1216 OPEN#      CALL #109D,EXPT_#_NR     Evaluate stream number.
1219            CALL #0A1E,SEPARATOR
121C            JP   NZ,#2920,REP_0      Give an error if no separator found.
121F            CALL #1161,EXPT_EXP2     Evaluate channel specifier.
1222            CP   13
1224            JR   Z,#1233,OPEN#_2     Jump if no more parameters.
1226            CP   191
1228            JR   Z,#122F,OPEN#_1     Jump if 'IN' specified.
122A            CP   223
122C            JP   NZ,#2924,REP_2      Give error if no 'OUT' specified.
122F OPEN#_1    LD   (#1E02),A           Store the channel type (IN or OUT) in
                                         'PROG_NUM1'.
1232            RST  #28,NEXT_C_RAM      Advance CH_ADD.
1233 OPEN#_2    CALL #0409,ST_END_RAM    Confirm end of statement and exit
                                         during syntax checking.
1236            LD   A,(#1E03)           Fetch stream number.
1239            RST  #10,CALBAS          Call 'main' ROM 'STR_DATA1' routine; on
123A            DEFW #1727,STR_DATA1     exit, BC holds 'stream data'.
123C            LD   HL,17
123F            AND  A
1240            SBC  HL,BC               Give an error if the current stream was
1242            JP   C,#295C,REP_30      already used by the DISCiPLE.
1245            LD   A,(#1E04)           Fetch channel specifier.
1248            AND  #DF                 Only capitals.
124A            CP   "D"
124C            JR   Z,#1253,OPEN#_3     Jump if opening a "D" channel.
124E            CP   "M"                 Give an error if not opening a "M"
1250            JP   NZ,#2920,REP_0      channel.
1253 OPEN#_3    CALL #2984,JTEST_DRV     See if the drive is defined.
1256            LD   A,10                Signal 'OPENTYPE file'.
1258            LD   (#1E05),A
125B            CALL #1261,OPEN_CHAN     Open the channel.
125E            JP   #0419,END           Finished.

THE 'OPEN "D" CHANNEL' SUBROUTINE
This is the actual OPEN routine referred to the "D" channel.

1261 OPEN_CHAN  LD   A,(#1E03)           Fetch stream number.
1264            ADD  A,A                 The streams area entries are two bytes
                                         each.
1265            LD   HL,23574            Address of data for stream 0.
1268            LD   E,A
1269            LD   D,0
126B            ADD  HL,DE               Index into STRMS area.
126C            PUSH HL
126D            CALL #128D,OP_TEMP_D     Open a temporary "D" channel. On return HL
1270            POP  DE                  holds new channel offset.
1271            RET  C                   Return when an error occurred.
1272            BIT  0,(IX+12)
1276            JR   Z,#1284,MAKE_PERM   Jump if this is a 'read' file.
1278            IN   A,(27)              Read Floppy Disk Controller status.
127A            BIT  6,A                 Test the 'write protect' bit.
127C            JR   Z,#1284,MAKE_PERM   Jump if disk isn't write protected.

NOTE: This doesn't work, the write protect bit of the FDC's status register is not
adjusted with read commands. So the jump is always made.

127E            CALL #114C,RECL_CHAN     Otherwise reclaim the channel.
1281            JP   #294E,REP_23        And give an error.
1284 MAKE_PERM  RES  7,(IX+4)            Make the channel permanent by resetting
                                         bit 7 of the channel specifier.
1288            EX   DE,HL               DE holds new channel offset.
1289            LD   (HL),E              Store it into the STRMS area.
128A            INC  HL
128B            LD   (HL),D
128C            RET                      Finished.

THE 'OPEN TEMP. "D" CHANNEL' SUBROUTINE
This subroutine is used to open a temporary "D" channel in the CHANS area.

128D OP_TEMP_D  LD   IX,(23631)          Start of channel area (CHANS).
1291            LD   DE,20               Point to the first 'non-standard'
1294            ADD  IX,DE               channel.
1296 OP_TEMP1   LD   A,(IX+0)
1299            CP   #80
129B            JR   Z,#12D2,OP_TEMP4    Jump if end of CHANS area is reached.
129D            LD   A,(IX+4)            Otherwise fetch channel specifier.
12A0            AND  #5F                 Clear bit 7 and make capital.
12A2            CP   "D"
12A4            JR   NZ,#12C8,OP_TEMP3   Jump if this isn't a "D" channel.
12A6            LD   A,(#1E01)           Fetch drive number.
12A9            CP   (IX+11)             Jump if this channel uses a different
12AC            JR   NZ,#12C8,OP_TEMP3   drive.
12AE            PUSH IX
12B0            POP  HL                  Start of channel to HL.
12B1            LD   DE,20               Filename offset.
12B4            ADD  HL,DE
12B5            EX   DE,HL               DE points to the name of this channel.
12B6            LD   HL,#1E06            HL points to the name of the channel to
12B9            LD   B,10                be opened.
12BB OP_TEMP2   LD   A,(DE)
12BC            XOR  (HL)
12BD            AND  #DF                 Capitalize.
12BF            JR   NZ,#12C8,OP_TEMP3   Jump if not the same file.
12C1            INC  HL
12C2            INC  DE
12C3            DJNZ #12BB,OP_TEMP2      Repeat for all 10 characters.
12C5            JP   #295E,REP_31        Give an error if the channel already
                                         exists.
12C8 OP_TEMP3   LD   E,(IX+9)            Fetch the length of the channel.
12CB            LD   D,(IX+10)
12CE            ADD  IX,DE               Point to the next channel.
12D0            JR   #1296,OP_TEMP1      Repeat for all channels.

The channel wasn't already present in memory so it can be opened.

12D2 OP_TEMP4   PUSH IX
12D4            LD   A,#10               Scan the CATalogue for a matching
12D6            CALL #2993,JSCAN_CAT     filename.
12D9            LD   A,(#1E02)           Get channel type (read/write).
12DC            JP   NZ,#1338,OP_TEMP5   Jump if file not found.
12DF            CP   223
12E1            JP   Z,#1600,OP_T_PATCH  Jump if OUTput channel.
12E4            LD   BC,551              Length of INput channel.
12E7            CALL #13A1,CHAN_SPC      Create the room for the channel.
12EA            CALL #29B4,JRPT_HL       Make HL point to the CAT entry.
12ED            POP  IX
12EF            CALL #2984,JTEST_DRV     See if the drive is defined.
12F2            NOP
12F3            NOP
12F4            NOP
12F5            LD   A,0                 Signal 'READing'.
12F7            LD   (IX+12),A
12FA            LD   BC,39               Offset of buffer from start of channel.
12FD            LD   (IX+15),C
1300            LD   (IX+16),B
1303            PUSH HL                  HL points to the CATalogue entry.
1304            PUSH IX                  IX points to the start of the channel.
1306            POP  HL
1307            LD   DE,19               Offset of directory description.
130A            ADD  HL,DE
130B            EX   DE,HL
130C            POP  HL                  Pointer to CAT entry.
130D            LD   BC,11               Move the directory description and the
1310            LD   A,(HL)              filename to the channel.
1311            LD   (#1E05),A           Store dir. descr. in UFIA1.
1314            LDIR
1316            INC  HL                  Skip length in sectors, i.e. point to
1317            INC  HL                  track and sector bytes.
1318            LD   B,(HL)              Fetch first track and sector.
1319            INC  HL
131A            LD   C,(HL)
131B            PUSH BC
131C            LD   BC,196
131F            ADD  HL,BC               HL points to file header - 1 in CAT
1320            LD   A,(HL)              entry. That is the MSB of the file
1321            LD   (IX+18),A           length (number of 64K blocks).
1324            INC  HL
1325            LD   BC,9
1328            LDIR                     Copy the file header to the channel.
132A            LD   DE,#1FEA
132D            LD   BC,22               Copy the SNAP registers (?).
1330            LDIR
1332            POP  DE                  Get track and sector in DE.
1333            CALL #29BD,JRSAD         Load the sector at DE.
1336            JR   #138A,OP_TEMP8

The file was not found, so if the channel isn't for OUTput give an error.

1338 OP_TEMP5   CP   191
133A            JP   Z,#2954,REP_26      Give error if it is an INput channel.
133D OP_TEMP6   LD   BC,787              Length of OUTput channel.
1340            CALL #13A1,CHAN_SPC      Create the room for the channel.
1343            POP  IX
1345            CALL #2984,JTEST_DRV     See if the drive is defined.
1348            NOP
1349            NOP
134A            NOP
134B            LD   A,1                 Signal 'WRITEing'.
134D            LD   (IX+12),A
1350            LD   BC,275              Offset of databuffer from the start of
1353            LD   (IX+15),C           the channel.
1356            LD   (IX+16),B
1359            CALL #29A8,JOFSM_2       Open the file.
135C            JR   Z,#1369,OP_TEMP7    Jump if file doesn't exist (anymore).
135E            LD   BC,787              Length of an OUTput channel.
1361            PUSH IX                  Start of the channel to HL.
1363            POP  HL
1364            RST  #10,CALBAS          Reclaim the channel.
1365            DEFW #19E8,RECLAIM_2
1367            SCF                      Signal 'error'.
1368            RET                      Finished.

1369 OP_TEMP7   JR   #138A,OP_TEMP8      Jump forward.
Previous Next Contents Index