Category : Pascal Source Code
Archive   : RLINE-OP.ZIP
Filename : RLINE.ASM

 
Output of file : RLINE.ASM contained in archive : RLINE-OP.ZIP
IDEAL

SEGMENT data word public
EXTRN FileMode:BYTE
ENDS

SEGMENT code byte public
ASSUME cs:code,ds:data

; set up a STRUCture compatible with the Pascal RFobject object.
STRUC RFrec
Handle dw ? ; File handle
BufStart dw ? ; Offset Disk buffer
BufES dw ? ; Segment Disk buffer = es
BufDI dw ? ; Current buffer position = di
BSize dw ? ; Buffer size
BufCX dw ? ; Bytes left to search = cx
NBufs dw ? ; Number of buffers read.
TotRead dw ? ; Total bytes last read into buffer.
RFerror dw ? ; Error code.
ENDS

RFWordSize equ 9 ; size of RFrec in words.
@self equ bp+6 ; Location of self on stack

MACRO BpSp
push bp
mov bp, sp
ENDM

MACRO SpBp NRet
mov sp, bp
pop bp
ifnb
ret NRet
else
ret
endif
ENDM


; FOpen and FClose. ***************************************************

PUBLIC RFobject@FOpen, RFobject@FClose

RFesdi equ (RFrec ptr es:di)

;-----------------------------------------------------------------
; Fill RFrec at es:di with 0's
;
;Registers
; ax, cx

PROC Fill0 NEAR
push di
xor ax, ax ; fill RFrec fields with 0.
mov cx, RFWordSize ; CX = #words to fill
rep stosw
pop di
ret
ENDP

;-------------------------------------------------------------------------
; PROCEDURE FOpen(Fn : Str80;
; DBsize : Word;
; VAR BufP) : Word;
; RFerror = 0 on success, DOS error code on failure.

Fn equ bp+16 ; address of filename
DBsize equ bp+14 ; requested size of buffer
BufP equ bp+10 ; Ofs of Buffer

PROC RFobject@FOpen FAR
BpSp
sub sp, 81 ; allocate local stack
mov dx, sp ; dx = offset asciiz
push ds ; save turbo's DS

mov bl, [FileMode] ; save filemode in bl
and bl, 11111000b ; make sure it's read-only

; copy Fn to stack
lds si, [Fn] ; point to Fn[0]
cld
lodsb
mov cx, 80
cmp al, cl ; check length
jae LenOK
mov cl, al
LenOK: mov di, dx ; di = offset of asciiz = dx
push ss
pop es ; es:di points to local space
rep movsb
mov [es:di], cl ; store asciiz 0
push ss
pop ds ; ds:dx points to asciiz

les di, [@self] ; es:di points to RFrec.
call Fill0 ; fill with 0
cmp [DBsize], ax ; Is requested buffer size > 0
jnz BSizeOK ; Yes.
mov ax, 12 ; No. Return invalid file access code.
jmp short OpenDone
BSizeOK:
mov al, bl ; FileMode
mov ah, 3dh ; ah=3D, DOS open file function
int 21h
jc OpenDone ; if DOS error, return with code in AX

mov [RFesdi.Handle], ax ; else set RFrec.Handle,
mov ax, [DBsize] ; and buffer size,
mov [RFesdi.BSize], ax
lds si, [BufP] ; and RF Buffer address.
mov [RFesdi.BufStart], si
mov ax, ds
mov [RFesdi.BufES], ax
xor ax, ax ; and return success.
OpenDone:
mov [RFesdi.RFerror], ax
pop ds ; restore Turbo DS
SpBp 14
ENDP


;-------------------------------------------------------------------------
; PROCEDURE FClose;
; Closes Handle if BSize > 0 and Handle > 4

PROC RFobject@FClose FAR
BpSp
les di, [@self] ; ES:DI points to RFrec

cmp [RFesdi.BSize], 0 ; Had it been opened?
jz DoneClose ; No, get out.
mov bx, [RFesdi.Handle] ; BX = RF.Handle
call Fill0

cmp bx, 4 ; If attempting to close
jbe DoneClose ; standard DOS device, DON'T.
mov ah, 3eh ; DOS close file function
int 21h
DoneClose:
SpBp 4
ENDP


; FILLBUF local proc ****************************************************
;
; Fill disk buffer. Read RF.BSize bytes from file RF.Handle to ES:[BufStart].
; On last buffer, last ^Z is stripped.
;Input:
; DS:BX points to RFrec.
; ES = segment of Buffer. ( RF.BufES )
; RFrec is at BP+10
;Output:
; If Failed, returns carry flag set, reason in AX:
; a) if a DOS error occurs, the DOS Error code is returned in ax.
; b) if end of file (0 bytes left to read), AX is set to $FFFF
;
; If Successful, returns carry flag clear and:
; a) di points to buffer start.
; b) cx = number of bytes read.
;
; Registers:
; ax, cx, di, si

RFbx equ (RFrec ptr bx)

PROC FillBuf NEAR
mov si, dx ; save Line length
mov cx, [RFbx.BSize]
mov dx, [RFbx.BufStart] ; point DX to buffer offset.
mov di, dx ; (reset BufDI for later)
mov bx, [RFbx.Handle] ; bx = Handle
mov ax, es
mov ds, ax ; set DS:dx
mov ah, 3fh ; DOS read file function.
int 21h
mov dx, si ; restore Line Length
lds bx, [@self] ; restore RFrec address
jc GetOut ; BlockRead error?

mov cx, ax ; cx = #bytes read.
jcxz EOF ; if no bytes read, we're done

; some bytes were read
inc [RFbx.NBufs] ; update file position
; remove ^Z at eof
xchg bx, cx ; save RFrec offset and index BX
cmp [byte es:di+bx-1], 26 ; end of buffer a ^Z?
xchg bx, cx ; restore RFrec ofs and cx
jne NoCtrlZ ; no, go on.
dec cx ; yes. Dec bytes read
NoCtrlZ:
mov [RFbx.TotRead], cx ; Store number bytes read.
jcxz EOF ; if cx = 0 then EOF
clc ; Return success.
ret
EOF: mov ax, 0FFFFh ; set result to EOF
stc ; Return failure.
GetOut: ret
ENDP


; RFREADLN and BUFMOVE ***********************************************

PUBLIC RFobject@FReadLn
RFbx equ (RFrec ptr bx)
RString equ bp+10 ; address of Return String

;----------------------------------------------------------------------
; BufMove -
; Appends CX number of bytes from ES:DI to RString.
; Will not move more than 255 bytes to RString. If there are more to move,
; the rest are thrown away.
; Leading ^J's are stripped.
;
; Called only by FReadln.
;
; Input
; ES:SI = address of bytes to move from.
; CX = # Bytes to move. If CX = 0, length byte is set.
; DX = current length of RString
; RString is at [BP+6]
; Direction Flag clear.
;
; Registers
; ax, cx, es, di, si
; DX updated to new length of RString

PROC BufMove NEAR
push ds ; save RF segment
jcxz LengthOK ; Any bytes to move?
cmp [byte es:si], 10 ; yes. Got a ^J?
jne NoCtrlJ
dec cx ; yes. fix cx and si
jz LengthOK ; Any bytes to move now?
inc si
NoCtrlJ:
mov ds, [RFbx.BufES] ; DS:SI = Source address.
mov ax, 255 ; ax = max length RString can be.
sub ax, dx ; ax = max length CX can be.
je BDone ; If RString = max length, get out.

cmp cx, ax ; are there more than max to move?
jbe LengthOK ; If not, go on.
mov cx, ax ; yes. set cx to ax.
LengthOK:
les di, [RString] ; es:di points to RString[0]
mov al, dl ; AL = Length(RString)
add al, cl ; Add bytes to move.
stosb ; Set RString[0]. DI = ofs Rstring[1].
jcxz BDone ; anything to move now?

add di, dx ; es:di => RString[dl+1]
mov dl, al ; update length
shr cx, 1
rep movsw ; Move cx words.
rcl cx, 1
rep movsb ; Move odd byte, if any.
BDone: pop ds ; Restore RF segment.
ret
ENDP


;-------------------------------------------------------------------------
; PROCEDURE FReadLn(VAR RString : String);
;
; If successful:
; Returns 0.
; RString = string read.
; If failed:
; Returns either DOS error code
; or $FFFF if EOF.
;
; Calls: FillBuf, BufMove.

PROC RFobject@FReadLn FAR
BpSp
push ds ; save turbo's DS
cld ; forward string operations.

xor dx, dx ; dx = string length = 0
mov cx, dx ; cx = 0.
lds bx, [@self] ; ds:bx points to RFrec
mov di, [RFbx.BufDI] ; DI = Buffer offset.
mov es, [RFbx.BufES] ; ES:DI points to buffer.

or cx, [RFbx.BufCX] ; CX = number bytes left to scan
jz FillIt ; if 0 then fill the buffer.

Scan: mov si, di ; save original buffer position
push cx ; save numbytes to scan for
mov al, 13 ; scan for CR
repne scasb
pop ax ; ax = numbytes before scasb
jz Found

; wasn't found. Restore old CX for Bufmove.
mov cx, ax ; restore cx for BufMove.
call BufMove ; move results to RString,
mov es, [RFbx.BufES] ; restore Buffer segment,
FillIt: call near FillBuf ; refill the buffer
jnc Scan ; If no error, then keep searching.

; Either EOF or DOS error occurred.
cmp ax, 0ffffh ; EOF?
jne Done ; No, DOS error. Get out.

; EOF was returned from FillBuf. If nothing has been
; stored in RString, then we're done, else return no error.
or dl, dl ; Length(RString) = 0?
jz Done ; Yes, return FillBuf's EOF.
inc ax ; report no error.
mov [RFbx.BufCX], ax ; Force FillBuf call next time.
mov cx, [RFbx.BufStart] ; make BufDI adjustment to
add cx, [RFbx.TotRead] ; make FFilePos accurate
mov [RFbx.BufDI], cx
jmp short done

Found: ; ^M was found.
mov [RFbx.BufDI], di ; Set up RFrec for next time.
mov [RFbx.BufCX], cx
sub ax, cx ; Set up to move to RString.
dec ax ; Don't count the ^M.
mov cx, ax
call BufMove
xor ax, ax ; set return code = 0.

Done: mov [RFbx.RFerror], ax
pop ds ; Restore everything and return.
SpBp 8
ENDP


; FREAD ****************************************************************
;
; PROCEDURE FRead(VAR Ch : Char);
; If successful:
; Returns 0.
; Ch = Character read from file.
; All ctrl chars pass, except ^Z at end of file, if there is one.
; If failed:
; Returns either DOS error code
; or $FFFF if EOF.
;
PUBLIC RFobject@FRead
RFbx equ (RFrec ptr bx)
RCh equ bp+10 ; address of Return Char

PROC RFobject@FRead FAR
BpSp ; set up pascal stack frame.
mov dx, ds ; save turbo's DS
cld ; all forward string operations.

lds bx, [@self] ; DS:BX points to RFrec
xor cx, cx
or cx, [RFbx.BufCX] ; CX = number of bytes left.
jz FillB
mov si, [RFbx.BufDI] ; si = Buffer offset.
dec [RFbx.BufCX] ; Set up RFrec for next time.
inc [RFbx.BufDI]
mov ds, [RFbx.BufES] ; ES:si points to buffer.
les di, [RCh] ; set VAR Ch and result.
movsb

SetCh: xor ax, ax ; set return code.
@Done: mov [RFbx.RFerror], ax
mov ds, dx ; Restore everything and return.
SpBp 8

FillB: call near FillBuf ; Fill the buffer
jc @Done ; If error or EOF, then exit.
dec cx ; the character is in ES:DI
mov [RFbx.BufCX], cx ; Set up RFrec for next time.
mov al, [es:di] ; AL = the character.
inc di
mov [RFbx.BufDI], di
les di, [RCh] ; set VAR Ch and result.
stosb
jmp short SetCh
ENDP

; FSEEK ***************************************************************
;
; PROCEDURE FSeek(FPo : LongInt);
; Seeks to FPo and fills buffer.
;
; If successful:
; Returns 0
;
; If failed:
; Returns DOS error code if DOS error occured.
; If BSize = 0, FSeek returns 200 (TP divide by zero error)
; This error won't ever occur unless the file hasn't been opened
; before calling FSeek.
;
; RFrec.NBufs is the one-based record number of the record currently in the
; buffer. Each record is RFrec.BSize large except the _last_ record in the
; file, which is usually smaller because the file isn't exactly divisible
; by BSize.
;
PUBLIC RFobject@FSeek
RFsi equ (RFrec ptr si)

PROC RFobject@FSeek FAR
BpSp
push ds ; save Turbo DS

lds si, [@self] ; ds:si points to RFrec

; make sure BSize > 0 before dividing
xor cx, cx
or cx, [RFsi.BSize] ; CX = buffer size.
jnz Divide ; Avoid divide by zero error
mov ax, 200 ; return TP divide by zero error code.
jmp short DoneFSeek

; Divide requested file position by BSize to get record number
; and offset (modulus).
Divide: mov ax, [bp+10] ; DX:AX = File position requested
mov dx, [bp+12]
div cx ; ax = zero based NBufs.
; dx = offset into buffer.
inc ax ; Adjust for one-base NBufs

; BufferNumber is now in AX, Offset in DX
cmp [RFsi.NBufs], ax ; current NBufs = one we're looking for?
jne FillerUp ; no, gotta read it.
cmp [RFsi.TotRead], 0 ; yes. Any bytes read into buffer?
jnz Filled ; Yes, we don't need to fill it.

FillerUp: ; Move DOS file pointer to proper record, and fill the buffer
push dx ; save requested buffer offset
dec ax ; adjust for zero- base.
mov [RFsi.NBufs], ax
xor dx, dx ; prepare to multiply.
mul [RFsi.BSize]

mov bx, [RFsi.Handle]
mov cx, ax ; load CX:DX with record position
xchg cx, dx
mov ax, 4200h ; DOS move file pointer.
int 21h
pop dx
jc DoneFSeek ; If DOS error, get out.

; Successful seek. Now fill the buffer.
mov es, [RFsi.BufES] ; ES = Buffer segment
mov bx, si ; BX = RFrec offset.
call FillBuf
mov si, bx
jc DoneFSeek ; If DOS error, then get out

Filled: ; Buffer is filled.
; NBufs is set to proper BufferNumber.
; dx = offset in buffer.

; Adjust RFrec to point to proper position.
; set BufCX for next scan.
mov ax, [RFsi.TotRead] ; AX = Total bytes in buffer.
cmp ax, dx ; Is dx within total bytes?
ja InBuffer ; yes, set BufCX
mov ax, 100 ; set result to Read Error.
jmp short DoneFSeek

InBuffer:
sub ax, dx
mov [RFsi.BufCX], ax ; set number bytes remaining to scan

; set BufDI for next scan.
mov ax, [RFsi.BufStart] ; AX = Starting offset of buffer.
add ax, dx ; add offset in buffer to seek to.
mov [RFsi.BufDI], ax
xor ax, ax ; return success.

DoneFSeek:
mov [RFsi.RFerror], ax
pop ds
SpBp 8
ENDP


; FFILEPOS ***************************************************************
;
; FUNCTION FFilePos : LongInt;
;
; FFilePos
; Output
; dx:ax = filpos
;
PUBLIC RFobject@FFilepos
PROC RFobject@FFilepos FAR
BpSp
les di, [@self] ; load es:bx
xor dx, dx
mov ax, [RFesdi.NBufs]
or ax, ax
jz @@Done
dec ax

mov cx, [RFesdi.BSize]
mul cx

mov cx, [RFesdi.BufDI]
sub cx, [RFesdi.BufStart]

add ax, cx
adc dx, 0
@@Done: SpBp 4
ENDP

ENDS CODE
END


  3 Responses to “Category : Pascal Source Code
Archive   : RLINE-OP.ZIP
Filename : RLINE.ASM

  1. Very nice! Thank you for this wonderful archive. I wonder why I found it only now. Long live the BBS file archives!

  2. This is so awesome! 😀 I’d be cool if you could download an entire archive of this at once, though.

  3. But one thing that puzzles me is the “mtswslnkmcjklsdlsbdmMICROSOFT” string. There is an article about it here. It is definitely worth a read: http://www.os2museum.com/wp/mtswslnk/