ZX Club #06
31 декабря 1997

Soft group - Driver input modes consistent and direct access from the file system TR-DOS. How to use driver.

<b>Soft group</b> - Driver input modes consistent and direct access from the file system TR-DOS. How to use
 driver.
Boris Kuritsyn,
Assistant Department of Computer Engineering
Cherkassy Engineering and Technological
Institute, PhD student

257010 Cherkassy, ​​PO Box 1529



         DRIVER INPUT MODE

   Sequential and direct access

         FROM THE FILES OF TR-DOS



                TABLE OF CONTENTS

Introduction ..................................
Calling System Functions TR-DOS ............
Exception Handling ......................
Driver streaming I / O
to / from files TR-DOS ........................
Using the driver from the Assembler .......
Interface Basic ...........................
Literature ................................



     The author wrote this driver (or rather,
the first part) as a basic element of a high-level language 
compiler. But it is completely standalone program which can 
directly use those who write in assembly language, and 
developed through the expander BASIC - and those who BASIC 
programmers. 


     In addition, analysis of her acquaint the reader with the 
programming of the drivers, channels and streams, the 
principles of writing BASIC extenders, syntactic analysis, with 
methods of extending the set of errors BASIC. 


     What is the purpose of writing this driver?
There is a class of programs that Simultaneity
must work with many files (and for writing, and the 
conclusion), and themselves at This takes quite a memory

so that the simultaneous loading of all
required files can not be considered.
Opening the system thread for each file,
they can work through this driver, even
10 files, length of, say, 60 KB at a time, at the rate of 
memory about 290 bytes per file. Function driver is close to

operators TR-DOS file handling
direct / sequential access, but works with CODE-files and 
similar files with non-standard types. 


     In addition, as shown by the "father of all
Programmers "Niklaus Wirth (the author of languages
Pascal, Modula-2), then the program is simple, correct and 
reliable, when the structure PROGRAM MEETS THE STRUCTURE OF THE 
DATA. To implement this principle, we need

appropriate means. One of them
is this driver, since it allows
program only work with "abstract"
aspect of the data, ie, in terms of "character", "read the 
position." 


     First, the technical aspects. Author
prefer assembler ZX Turbo Assembler
v2.4 and the listing is presented in its format.
Hopefully, users of other assemblers do not have any problems 
with the transfer of program texts. 


     The author, when writing programs that use two sub-modules:


         module access to TR-DOS
and

    module to intercept system errors.


     Module TR-DOS is very simple. This is the analogue
syscall # 3D13, which is an error
TR-DOS converts exceptions (call
RST 8) codes 100-112, which eliminates the
necessary each time to check code
system error. In addition, the call itself is done through a 
vector (dosVector), which allows you to "hang" on call TR-DOS 
additional functions at run time program by replacing the value 
at dosVector address of the additional processor.



;
; System call TR-DOS v5.0x
;
; (C) B. Kuritsyn, June 1996
;
; File: dosapi.a
; File Format: ZX TASM
;


The exception "error TR-DOS"
excDosError equ 99

; Mistakes TR-DOS
dNoFile equ 1
dFileExists equ 2
dNoSpace equ 3
dDirFull equ 4
dRecOF equ 5
dNoDisk equ 6
dStrmOpened equ 10
dNotDskFile equ 11
dVfyError equ 13

dos db # c3; it jp (dosVector)
dosVector

        dw dosIntr

; Call DOS shell functions
dosIntr push af

        ld a, c

        ld (_fncNo), a

        xor a

        ld (23823), a

        ld (23824), a

        pop af

        call # 3d13

        push af

        ld a, (_fncNo)

        Wed # a; if performed function 10

              , (File search)

        jr z, dosOk; return code - it is not

                   ; Error code

        ld a, (23823)

        or a

        jr z, dosOk; if there was a bug ini
                   ; Tsiirovat exception
; Initiation exception DOS
dosError

        add a, excDosError

        ld (_errNo), a

        rst 8
_errNo db 0
_fncNo db 0
dosOk pop af

        ret


     Interested Exception Handling
can refer to [1]. Here
I say briefly: exception - it is extremely
convenient programming technology, which allows implicit 
conversions of handling errors or exceptional situations 
without the need for regular checks flags and return codes, 
etc. When This ensures the conservation status

Some elements of the system and programs
(At least the stack). The following module supports the 
processing of multilevel Exceptions to the possibility of 
dynamic changing the set of conserved elements

and the exception handler. Interested
can simply review the text of the program. Briefly as we can 
say this: if beginning any program try to call

(See listing) including the address of your
error-handling routine, then, in the case of a call RST 8 
anywhere in the program management be passed to your handler. 
The handler must first of all cause endTry to restore the stack 
and withdrawal for themselves. The same call should be made 
before the command RET program. 

;
; Exceptions handle
; Exception Handling
; (C) 1994-96 B. Kuritsyn
; Version: 2.0 06/18/1996
; File: except.a
;

err_SP equ 23613

; External Treatment
try db # C3; a JP (tryAd)
tryAd dw mark

endTry db # C3
eTryAd dw unmark

; Continue the current exception
, (Just call the exception handler
; Team JP)

; New exception code in the A
putErr ld (iy), a

; The same exception
contErr ld sp, (err_SP)

          ret

; Change marking stack
; Entry: @ HL-new handler Try, @ DE-new
; Handler EndTry
, Output: @ HL-old handler, Try, @ DE-hundred; ry handler EndTry

chMarking ld bc, (tryAd)

          ld (tryAd), hl

          ld h, b

          ld l, c

          ld bc, (eTryAd)

          ld (eTryAd), de

          ld d, b

          ld e, c

          ret

; SALE
; Mark stack entry: @ DE-handler
; Exceptions
; Destroyed: HL, IX

mark POP IX

       LD HL, (err_SP)

       PUSH HL

       PUSH DE

       LD (err_SP), SP

       JP (IX)

; Demarcate the stack are destroyed: HL, IX

unmark POP IX

       LD SP, (err_SP)

       POP HL

       POP HL

       LD (err_SP), HL

       JP (IX)


     Necessary to stipulate that those who
do not know what a "channel" and "flow", before continuing 
reading this article should read the chapter on canals and 
streams in the famous three volumes Inforkoma Programming for 
the ZX Spectrum or an annex to user manual for a text editor BK 
Write, is spread by the author. 


     And now for the driver itself. Which set of functions it 
should perform? 


     Firstly, it is opening the file: creating a channel that 
is associated with the file and the connection of a flow to the 
channel. 


     Secondly, the driver let dozhen
Reads a byte file, not only sequentially but also rearrange the 
index of reading directly to any position in the file. 


     Thirdly, it is closing a file: the destruction of the 
channel, closing the stream. 


     And how, indeed, entering information, you ask?


     It's very simple - the system procedure
WaitKey (address # 15D4).


     Next, we consider the annotated
Text driver (note: in the driver
there are moments associated with the output to a file -
This part of the driver is not finished yet, but
order to include it in the article is not possible due to the 
large volume). 


     Immediately turn to the main idea
Driver: we must give byte file, which is offset in the file 
determined by the current position. Position can be arbitrarily

changed at any time. When reading
byte pointer is moved to
next byte. Trying to read
anything beyond the end of the file is generated
the exemption.


     To implement this in a leader tape channel
provides space for one sector
file. At any point in that buffer is loaded sector 
corresponding to the current file position. With any change in 
position number of the sector is monitored and, if necessary, 
the sector is overloaded. ; 
**************************************** * *

; * DISK STREAMABLE I / O DRIVER v1.05 *
* *
* Driver streaming I / O *
* To / from files TR-DOS. *
* *
; * (C) B. Kuritsyn, June 1996 *
* *
* File: stream.a *
* File Format: ZX Turbo Assembler *
; ****************************************


            include "dosapi.a"

The length of the sector
sectLen equ 256

; System variables
chans equ 23631; pointer to

                    ; Channels
curChl equ 23633; pointer to the current

                    ; Channel
prog equ 23635; pointer to prog; Rummy (at the end of channels)

; System variables TR-DOS
dfDrive equ # 5d19; drive by default
searchCh equ 23814; number of characters for

                    ; Name Search

; System protsedury,
And details regarding the procedures
, See [2]
makeRoom equ # 1655
reclaim2 equ # 19E8
strData equ # 171E +3
chOpen equ # 1601
callJp equ # 162C

; Channel input and output is named "F",
; That they can be distinguished,
; Established leader tape of the signature:
readSign equ # 5678
writeSign equ # 6789

; Throwing exceptions
invStream

        rst 8

        db 23, "is used incorrectly

               ; Stream
invFileName

        rst 8

        db 14, "invalid name"
invDevice

        rst 8

        db 18, "invalid device"
endOfFile

        rst 8

        db 7, 'end of file "

; Shift in the leader tape, about
; Unique structure of the leader tape see [3]
oPrint equ 0; address inference procedures
oInput equ 2; address of a procedure entry
oName equ 4; channel name
oSign equ 5; the signature of the channel
oClose equ 7; address closing procedures

              ; File
oLength equ 9; length of leader tape
oIntern equ 11; More

; Image of the leader tape channel for reading
readRecord

        DW invStream

        DW inputIn

        DB "F"

        DW readSign, noOp

        DW 1930 + sectLen; length of leader tape

        DB 0; device

            ; (Offset oIntern +0)

        DB "C"

        DS 7; directory entry (...+ 1)

        DW # FFFF; file position (...+ 17)
; Here: DS sectLen - buffer sector
; File (...+ 19)
rdRecLen equ $-readRecord + sectLen

; Procedure for entering characters from a file;
; Next byte of the file is returned to A.
; Byte is always returned, so
; State INKEY $ # 5 = "does not happen.
inputIn ld ix, (curChl); address of the leader tape

        ld l, (ix + oIntern +17); current

                         ; Position in the file

        ld h, (ix + oIntern +18)

        ld c, l

        ld b, 0

        add ix, bc

        ld a, (ix + oIntern +19); Picks
; Bytes from the current sector

        scf; Flag: Byte received

            C unit

        push af

        inc hl

        call _seekRead; transition to

                       ; The following position

        pop af
noOp ret

; Positioning in the current file
; Reading
; Input: HL-position
; --- External version, verify that the current
; Channel - F and is opened for reading, if
, No - wrong thread)
seekRead

        push hl

        call testChl

        ld l, (ix + oSign)

        ld h, (ix + oSign +1)

        ld bc, readSign

        and a

        sbc hl, bc

        jp nz, invStream

        pop hl
; --- Internal version
_seekRead

        ld ix, (curChl)
, Check to see whether an end of file

        ld c, l

        ld b, h

        ld e, (ix + oIntern +12); compared with the

                             The length of the file

        ld d, (ix + oIntern +13)

        and a

        sbc hl, de
; Position just after the last byte of the file,
, The buffer is not overloaded

        jr z, atEOF

        jp nc, endOfFile
; Establish a new position

        ld a, b

        cp (ix + oIntern +18); in the same

                           ; Sector?
atEOF ld (ix + oIntern +17), c

        ld (ix + oIntern +18), b

        ret z; yes - complete
; Not - the new position of the corresponding byte
; From another sector of the file, download a new
; Sector to clipboard

        ld l, (ix + oIntern +15)

        ld h, (ix + oIntern +16); position

                   ; Beginning of the file on disk

        call makeLog; transformation

                     , The logical sector

        ld e, b

        ld d, 0

        add hl, de; this logical number

                  ; Sector

                  ; You want to download

        call makePhis; reverse

                      ; Transformation

        ex de, hl

        push ix

        pop hl

        ld bc, oIntern +19

        add hl, bc

        push hl

        push de

        ld a, (ix + oIntern)

        ld c, a

        call dos; drive select

        pop de

        pop hl

        ld bc, # 105; boot sector

        jp dos

; Convert options
, "Sector L - track H"
; A "logical sector HL"
Remark: the transformation
; A "logical sector" makes it easy
; Calculate the position of the sector on the disk,
; As the logical sector can be
; Add and subtract like normal numbers.
; Transformation formula:
; Log. sector = track * 16 + sector
makeLog xor a

        srl h

        rr a

        srl h

        rr a

        srl h

        rr a

        srl h

        rr a

        or l

        ld l, a

        ret

; Convert options
, A "logical sector HL"
; In the sector L - track H "
makePhis

        ld a, l

        sla a

        rl h

        sla a

        rl h

        sla a

        rl h

        sla a

        rl h

        ld a, # F

        and l

        ld l, a

        ret

; Type of file to open, changing it
; Value before calling openRead
Or you can open a non-standard files
fileType db "C"

; Opening file for reading;
; Entry:
; A-number flow, @ DE/BC- name string
; (As usual: the address of DE, the length of BC)
; Specified thread will be opened on the file.
openRead

        exx

        ld (stream), a; verify that

                  ; Specified stream is closed

        call strData

        ld a, b

        or c

        ld a, dStrmOpened; if not -

                         ; Error DOS

                      , "Stream is already open"

        jp nz, dosError

        call newRdRecord; create a leader tape

                         ; Channel

        ld (record), hl

        push hl

        exx

        pop hl

        call parseName; syntactic

                       ; Parse name

        ld hl, (record)

        inc hl

        ld bc, (chans); find the offset

                    ; Leader tape in (Chans) ...

        and a

        sbc hl, bc

        push hl

        ld a, (stream)

        call strData

        pop bc

        ld (hl), c; ... and discover

            ; The requested stream to the channel

        inc hl

        ld (hl), b

        ld ix, (record)

        ld a, (ix + oIntern)

        ld c, a

        call dos; drive select

        ld c, # 18

        call dos; setting a floppy disk

        ld hl, (record)

        ld bc, oIntern +1

        add hl, bc

        push hl

        ld c, # 13

        call dos

        ld hl, searchCh

        ld (hl), 9

        ld c, # a

        call dos; search for the file, which

                 ; Open

        bit 7, c

        jr nz, noFile; if the file does not exist -
; Everything back to its original state

        ld a, c

        ld c, 8

        call dos; if the file is,
; Obtain its directory entry

        pop hl

        ld c, # 14

        call dos; and copy it to the leader tape

                 ; Channel

        ld a, (stream)

        call chOpen

        ld hl, 0

        jp _seekRead; set
; Position at top of file
, In the absence of a file all returns
, The initial state
noFile ld ix, (record)

        call freeRecord; remove the leader tape

                        ; Channel

        ld a, (stream)

        call strData

        ld (hl), 0; close of thread

        inc hl

        ld (hl), 0

        ld a, dNoFile; an error DOS

                     , "No such file"

        jp dosError
stream db 0
record dw 0

; Parsing the file name
, As "[drive:] name". If the drive
; Not specified, the drive is taken by default.
And the name and the drive is transferred to the region
; OIntern leader tape.
; Input: HL-mail leader tape to open
; Channel, @ DE/BC- name string
parseName

        push hl

        pop ix

        ld a, b; empty string name -

               , Error

        or c

        jp z, invFileName

        ld a, (dfDrive); until the drive

                       By default

        ld (ix + oIntern), a

        ld a, (fileType); set

                        ; Type

        ld (ix + oIntern +9), a

        ld hl, -3; name is longer than

                 ; Three characters?

        and a

        adc hl, bc

        jp m, nameOnly; not - hence,
; Drive in a name is not specified exactly

        inc de; check the relative

               ; Drive ...

        ld a, (de)

        dec de

        cp ":"; if the second character -

               ; Colon ...

        jr nz, nameOnly

        ld a, (de); ... then the first - the drive

        res 5, a; leads to an upper

                ; Register

        sub "A"; separate the correct

                ; Names: A, B, C, D.

        jp c, invDevice

        cp 4

        jp nc, invDevice

        ld (ix + oIntern), a; drive
; Found and installed in the leader tape

        inc de; shifts

               , To name ... (2 characters)

        inc de

        dec bc

        dec bc
nameOnly

        ld a, b

        or a

        jp nz, invFileName

        ld a, c; if the name is longer than

               ; 8 characters - a mistake

        cp 9

        jp nc, invFileName

        ld b, c; if everything is in order -

               ; Copy the name of leader tape
copyName

        ld a, (de)

        inc de

        ld (ix + oIntern +1), a

        inc ix

        djnz copyName

        ret

; Creating leader tape read channel
; Output: HL-mail created by the leader tape
newRdRecord

      ld hl, (prog); at the end of

                   ; Chans ...

      dec hl

      ld bc, rdRecLen; ... allocate memory

                     ; For the leader tape ...

      call makeRoom

      inc hl

      push hl

      ex de, hl

      ld hl, readRecord; ... and copy

                       ; There way of leader tape

      ld bc, rdRecLen-sectLen

      ldir

      pop hl

      ret

; Removing leader tape read / write channel
; Entry: IX-mail leader tape
freeRecord

       ld c, (ix + oLength); of the leader tape

                   ; Obtain its length ...

       ld b, (ix + oLength +1)

       ld (recLen), bc

       push ix

       pop hl

       jp reclaim2; ... and release

                   ; Area they occupied
recLen dw 0

, Check that the current channel -
And this channel is "F"
, Output: IX = (curChl)
testChl

      ld ix, (curChl); if the name of the current

                     ; Channel ...

      ld a, "F"

      cp (ix + oName); ... not "F" ...

      ld a, dNotDskFile

      jp nz, dosError; ... mistake DOS

                     , "Is not a disk file"

      ret

, Close the file read / write stream A
close push af

      call chOpen; makes the channel current

      call testChl; verify that this

            ; Flow associated with our channel
, Perform the procedure closing the channel

      ld l, (ix + oClose)

      ld h, (ix + oClose +1)

      call callJp; transition to execution
; Free memory

      ld ix, (curChl)

      call freeRecord; delete the current

                      ; Channel from memory
, Close the stream

      pop af

      call strData

      ld (hl), 0, 0 - stream closed

      inc hl

      ld (hl), 0
; Adjust variables to Streams
; Flows 0-15.
; The fact that after the opening of the SC; signal could be 
discovered, and others. Their pa; cords are located in memory 
after our ; Leader tape.

; With the removal of our leader tape bias
; Of Streams on a channel one hundred, if invalid, and must be 
fast; rektirovat on the length of the remote ; Leader tape.


      ld d, b; offset the already remote

             ; Leader tape

      ld e, c

      ld b, 16; scan the 16 streams
strmLoop

      push bc

      ld a, b

      dec a

      call strData; choose a value for

                   ; Flow

      push hl

      pop ix

      ld h, d

      ld l, e

      and a

      sbc hl, bc; if its offset

                ; No more of our ...

      jr nc, noCorrt; ... correction

                    ; Not required

      ld h, b

      ld l, c

      ld bc, (recLen); otherwise reduce

               , Offset by the length of leader tape

      and a

      sbc hl, bc

      ld (ix), l; and save

      ld (ix +1), h
noCorrt

      pop bc

      djnz strmLoop; cycle for all streams

      ret


     Thus, the driver is written. And how to use it? 
Elementary. First, any free flow (say, # 5) Open on file:



          org 60000

          jp start

          include "stream.a"; inclusion

                             ; Driver ...

          include "except.a"; ... and form
                        ; Processing exceptions

name db "textfile"; to name

                        ; File ...
nameLen equ $-name; ... and its length

start ld de, name

          ld bc, nameLen

          ld a, 5

          call openRead


     File is opened. Now, for example, print it on the screen. 
We will, character by character read the file and send bytes 
channel "S". Because the process is completed except for "end 
of file", catch the exception: 


          ld de, endOfPrint; address

                            ; Handler

          call try


     Now you can display the file in the "infinite" loop.

waitKey equ # 15D4
process ld a, 5; file stream

          call chOpen; chOpen = # 1601

          call waitKey; introduce the symbol

          push af

          ld a, 2; flow screen

          call chOpen

          pop af

          rst 16; derive symbol

          jr process


     At the end of a file or other exceptions, control is 
passed to here: 

endOfPrint

          call endTry; remove handler

          ld a, 7

          cp (iy); current fault -

                  And this "end of file"?

          jp nz, contErr; if not -
; Continue her spread the word, and if so -
; Everything is in order, the withdrawal is completed

          ld a, 5

          call close; close

                     ; Disk file

          ret


    What about BASIC? I would like to have
the ability to open files directly from the operators BASIC.


    Nothing could be easier. Below
BASIC interface to the driver implements it
and one more thing: it converts new DOSovskie exceptions to the 
new error BASIC, that appear in the same way as conventional.

In addition, it displays the status of the flow system on the 
screen or in any other thread. New BASIC statements are as 
follows: 

 LET d = 64000
 REM opening <flow> on <filename>
 RANDOMIZE USR d: OPEN # stream, filename $

 REM closing disk file associated

     c <thread>
 RANDOMIZE USR d: CLOSE # stream

 REM transition to  in the file

     associated with <thread>
 PRINT # thread;: RANDOMIZE USR d
 GO TO position

 REM output information

     about the state of flux at <thread>
 REM to display flow = 2
 RANDOMIZE USR d: LIST # stream


    A small remark about the operator GO TO: operator PRINT, you
see ahead, only makes the current flow, since GO TO work with 
the current thread. Note the ";" at the end operator PRINT.



    Operator LIST lists all open streams with an indication of 
the channels that they are open. 


    Direct input from a file in the usual way: the operator

 INPUT # thread; simv_peremennaya $

to enter a character string, or an operator

 LET simv_peremennaya $ = INKEY $ # stream

to enter a single character.


    The second way is preferable, since
as in the ZX Spectrum has a special feature: it is assumed that 
the operator INPUT data is entered only from the streams,

associated with the keyboard and the sound of keyboard
processed in a statement INPUT. Therefore,
input from the file, you will hear a sequence of squeaks 
"keystroke" when you enter each character. In addition, input 
line will only be completed upon receipt of symbol with a key 
code <Enter> (# 0D) and itself is a character in the string 
will not be included. 


    Throughout the program, show how
BASIC extender not only performs
actions, but also analyzes sintasis program.

;*****************************************
* *
; * BASIC INTERFACE TO *
; * DISK STREAMABLE I / O DRIVER, v1.05 *
* *
* The interface to the BASIC *
* Download streaming I / O *
* To / from files TR-DOS. *
* *
; * (C) B. Kuritsyn, June 1996 *
* *
* File: basint.a *
* File Format: ZX Turbo Assembler *
;*****************************************

; Codes tokens
t_open equ # d3
t_close equ # d4
t_goto equ # ec
t_list equ # f0

; System variables (or bias)
oFlags equ 1
oTVFlag equ 2
oFlags2 equ 48
oFlagX equ 55
oXPtrHi equ 37
defAdd equ 23563
strms_6 equ 23574

; Used semiconductor ROM.
; Details, see [2].
class06 equ # 1C82; syntax. analyzer

                     - Must be

                     ; Numeric expression
class0A equ # 1C8C; syntax. analyzer

                     - Must be

                     ; String of characters
separator equ # 1B6F; syntax. analyzer

                     - Must be

                     ; Token
stkToA equ # 1E94; stack calculator -

                     , In A
stkToBC equ # 1E99; stack calculator -

                     ; In BC
stkFetch equ # 2BF1; stack calculator -

                     ; In the A / BC / DE
clsLower equ # 0D6E
setMin equ # 16B0
copyBuff equ # 0ECD
stackA equ # 2D28; A - on the stack

                     ; Calculator
printFP equ # 2DE3; print the number of

                     ; Stack calculator
po_mess equ # 0C0A; display a message A

                     ; From the table (DE)


           org 64000
; Entry point
startUp ld de, newErrors; new

                  ; Handler issklyucheny

           call try

           ld c, ":"; this is a separator

                    ; After USR 64000
; Separator verify that the current interval; pretiruenmy 
symbol is gone. And if not - error "nonsense in BASIC"


           call separator

           ld c, a

           rst # 20; take the name of the operator ...

           ld hl, statms; ... and look for it

                        ; Table Statms

           jr compare
nextSearch inc hl

           inc hl
compare ld a, (hl)

           inc hl

           or a

           jr nz, cont_comp; if the table

                      ; Ended - error

           rst 8

           db # b; Nonsense in Basic
cont_comp cp c

           jr nz, nextSearch

           ld a, (hl); found
; Choose the address of the handler ...

           inc hl

           ld h, (hl)

           ld l, a

           call callJp; ... and run it

           call endTry; remove handler

                       ; Exceptions

           ret

; Table description operators.
; Format: token, the address of the handler
; Token, the address of the handler ,..., 0.
statms db t_open

           dw _open

           db t_close

           dw _close

           db t_goto

           dw _goto

           db t_list

           dw _list

           db 0

listStrm db 0
The text for cinematography LIST
listMess db # 80, "Streams status:", 13 + # 80

           db ": opened to", 34 + # 80

           db 34,13 + # 80

; Operator LIST # stream
_list ld c, "#"; check symbol

                    ; Flow

           call separator

           call class06; should follow

                      ; Numeric expression

           call stkToA; it -

                       ; In the battery

           call chOpen; open channel

                       ; For output

           ld de, listMess

           sub a

           ld (listStrm), a

           call po_mess; output header
listNext ld a, (listStrm); for the flow ...

           call strData; ... selected

                        ; Data from Streams

           ld a, b

           or c

           jr z, listCont; when closed -

                         ; Next thread

           ld a, "#"; print symbol

                    ; Flow ...

           push bc

           rst 16

           ld a, (listStrm)

           call stackA

           call printFP; ... and its facilities

           pop bc

           ld hl, (chans)

           add hl, bc

           inc hl

           inc hl

           inc hl; definition addresses

                  ; OName bias in the channel

           push hl

           ld a, 1

           ld de, listMess

           call po_mess; message

                        , Is open for ...

           pop hl

           ld a, (hl)

           rst 16; ... such and such a channel

           ld a, 2

           ld de, listMess

           call po_mess
listCont ld hl, listStrm

           inc (hl); next thread

           ld a, 16

           cp (hl)

           jr nz, listNext; transition to

                       ; Next thread

           ret

; Operator OPEN # stream, name $ -
; Without comments
_open exx

           push hl

           call openParams

           call openRead

           pop hl

           exx

           ret

; Parse OPEN statement
openParams call class06; should be number

                        ; Flow - on the stack

                        ; Calculator

           ld c, ","

           call separator; then a comma

           call class0A; then a character

                        ; Expression -

                        The name of the file

           rst # 28; exchange name and stream

                   ; Places on the stack

           db 1, # 38; exchange

           call stkToA; stream -

                       ; In the battery

           push af

           call stkFetch; name - in the DE / BC

           pop af

           ret

; Operator CLOSE # stream
_close call class06; should be number

                        ; Flow - on the stack

                        ; Calculator

           call stkToA; stream -

                       ; In the battery

           jp close

; Operator GO TO pos
_goto call class06; number - position

                        ; In the file

           call stkToBC; from the stack

                        ; Calculator in BC

           ld h, b

           ld l, c

           jp seekRead

; Error handler:
; Visualizes new errors
newErrors call endTry; remove handler

           halt

           ld a, (iy); error code

           cp excDosError + dNoFile

           jp m, contErr; usual errors

                  ; SOLD further
; This part almost repeats
; Of the standard error handler
; From the ROM to output error messages.
; See [3] from the address # 1303

           res 5, (iy + oFlags)

           bit 1, (iy + oFlags2)

           call nz, copyBuff

           ld hl, 0

           ld (iy + oFlagX), h

           ld (iy + oXPtrHi), h

           ld (defAdd), hl

           ld hl, 1

           ld (strms_6), hl

           call setMin

           res 5, (iy + oFlagX)

           call clsLower

           set 5, (iy + oTVFlag)

           ld a, (iy)

           sub excDosError + dNoFile

           ld b, a

           add a, "a"; new codes Posts

           rst 16

           ld a, ""; gap

           rst 16

           ld a, b

           ld de, messages; new posts

                          ; In this table

           ld (iy), # FF

           jp # 1346; further processing

                    ; Standard - in ROM

; Table text messages about new bugs
, (In the format procedure PO_MESS)
messages db # 1980, "No fil", "e" + # 80

           db "File exist", "s" + # 80

           db "Disk ful", "l" + # 80

           db "Dir ful", "l" + # 80

           db "RecNo overflo", "w" + # 80

           db "No dis", "k" + # 80

           db "(7) DOS erro", "r" + # 80

           db "(8) DOS erro", "r" + # 80

           db "(9) DOS erro", "r" + # 80

           db "Stream opene", "d" + # 80

           db "Not disk fil", "e" + # 80

           db "(1912) DOS erro", "r" + # 80

           db "Verify erro", "r" + # 80

; Enable drivers and exception handling

           include "stream.a"

           include "except.a"
; *** End of basint.a ***



     I hope that my brief (due to the large amount of assembly 
code) comments given at least a general idea of work program 
and the program will useful to you.



     If you encounter problems or specific questions, you can 
write to the author at the address above. 



                REFERENCES

1. B. Kuritsyn. Intercepting System Errors
when programming in assembler for
computers "ZX Spectrum".: ham
10'1994, p. 12 - Minsk, 1994.

2. Logan, O'Hare. Full description ZX Rom
Spectrum.: "Program-Ass" - Kharkov, 1992.

3. K. Kurylovich, D. Madej, K. Marasek. Guide to the ZX 
Spectrum.: "Program-Ass" - Kharkov, 1992.





Other articles:

From the Editor - ZX-CLUB growing and evolving.

Soft group - Driver input modes consistent and direct access from the file system TR-DOS. How to use driver.

Hard group - ZS Scorpion 2000 - on the GMX-controller.

Users group - File Compression Screen: Overview of the software. Discography. Analysis of the results of compression.

Users group - Compression code blocks - work with HRUM v3.5.

News - Barnaul Olympiad in Informatics 1997.

News - Barnaul firm Komel decided podderzhkeavtorskih programs.

News - contest for the best virus continues.

Dossier - On the activity of Barnaul programmers: Krotov Oleg Mayatsky Vitali, Rostov Alexander Kovalev Roman (DJ RUSH), Norton Commander (NC).

ZX-Potpourri - Letters from readers from Magadan and carpet, Voronezh, and Cheboksary.

Enjoy - How to Marry a programmer.

Fantasy - A Tale VA Petersburg "The Fourteenth Dimension".

Toys - Novella to the game "BISMARK".

Toys - a description of the game "BISMARK".

Toys - Dictionary of the game "BISMARK".


Темы: Игры, Программное обеспечение, Пресса, Аппаратное обеспечение, Сеть, Демосцена, Люди, Программирование

Similar articles:
attempt at writing - Short Story "The War Continues" (continued: Chapter 2,3)
Network - about the plight Zaporozhye modem network.
Premiere - a full description of the program Super Viewer to work with disks.
Advertising - advertising and announcements.

В этот день...   3 May