Category : C++ Source Code
Archive   : VCCRT2.ZIP
Filename : FWRITE.ASM

 
Output of file : FWRITE.ASM contained in archive : VCCRT2.ZIP
page ,132
title fwrite - write to a stream
;***
;fwrite.asm - write to a stream
;
; Copyright (c) 1988-1992, Microsoft Corporation. All rights reserved.
;
;Purpose:
; Write to the specified stream from the user's buffer.
;
;*******************************************************************************

.xlist
include version.inc
include cmacros.inc
include stdio.inc
.list

if sizeD
extrn __AHINCR:ABS
endif ;sizeD

externNP _flush ; single stream, lock assumed flush

externP _flsbuf ; fill stream buffer
externP memcpy ; buffer copy
externP _write ; LOWIO's write function



sBegin data
assumes ds,data

externW _iob
externW _iob2

sEnd data

sBegin code
assumes cs,code
assumes ds,data

;***
;size_t fwrite ( void *buffer, size_t size, size_t count, FILE *stream ) -
; write to the specified stream from the specified buffer.
;
;Purpose:
; Write 'count' items of size 'size' to the specified stream from
; the specified buffer. Return when 'count' items have been written
; or no more items can be written to the stream.
;
;Entry:
; buffer - pointer to user's buffer
; size - size of the item to write
; count - number of items to write
; stream - stream to write to
;
;Exit:
; Returns the number of (whole) items that were written to the stream.
; This may be less than 'count' if an error or eof occurred. In this
; case, ferror() or feof() should be used to distinguish between the
; two conditions.
;
;Notes:
; fwrite will attempt to buffer the stream (side effect of the _flsbuf
; call) if necessary.
;
; No more than 0xFFFE bytes may be written out at a time by a call to
; write(). Further, write() does not handle huge buffers. Therefore,
; in large data models, the write request is broken down into chunks
; that do not violate these considerations. Each of these chunks is
; processed much like an fwrite() call in a small data model (by a
; call to _nfwrite()).
;
; This code depends on _iob[] and _iob2[] both being near arrays
; and having the same element size.
;
; MTHREAD/DLL - Handled in three layers. The outer layer, fwrite(),
; takes care of the stream locking/unlocking, saving/loading/restoring
; of DS (if required) and calls _fwrite_lk() to do the work. In turn,
; _fwrite_lk() breaks the write request down into suitably sized chunks
; and calls _nfwrite() to do the write (i.e., _fwrite_lk() is the same
; as the single-thread, large data model fwrite()).
;
;*******************************************************************************


if sizeD


;**
; Single thread version

cProc fwrite,,


parmDP buffer
parmW itemsize
parmW count
parmDP stream

localD ltotal

cBegin

;**
; Set:
; ltotal = dx:ax = number of chars to be written

mov ax,[itemsize]
mul [count]
mov cx,ax
or cx,dx
jz farfinish
mov word ptr [ltotal],ax
mov word ptr [ltotal + 2],dx

;**
; Set:
; es:bx = pointer to user's buffer
; si = pointer to _iob entry

les bx,[buffer]
mov si,word ptr [stream] ; _iob[] is a near array!

loopstart:

;**
; If we're writing 64 Kb or more, or the target portion of the user's buffer
; crosses a segment boundary, then we must do a partial write.

or dx,dx
jnz partialwrt
cmp ax,0FFFFh
je partialwrt
mov cx,bx
add cx,ax
jcxz fullwrt ; to the very last byte of the segment
; but not beyond
jc partialwrt

;**
; We have less that 0xFFFF bytes to write and it all lies in one segment of
; the user's buffer. One (more) call to _nfwrite and we're done!

fullwrt:
push ax ; save regs
push bx
push dx
mov cx,ax ; cx = num of chars to write
call _nfwrite
mov cx,ax ; cx = return value
pop dx ; restore saved regs
pop bx
pop ax
sub ax,cx ; update num of chars to be write
sbb dx,0
jmp short setupret ; we're finished, go set up return

;**
; Do a partial write. Write out the contents of the current segment of the
; user's buffer, if no more than 0FFFEh bytes are required. Otherwise, write
; out 08000h bytes (32 Kb).

partialwrt:
cmp bx,1 ; more than 0FFFEh to write whole seg?
ja writeseg ; no, go write out 64 Kb - bx chars
mov cx,08000h ; ask for 32 Kb
jmp short donfwrite

writeseg:
mov cx,bx
neg cx ; ask for 64 Kb - bx

donfwrite:
push cx ; save amount being requested
push ax ; save regs
push bx
push dx
call _nfwrite
mov cx,ax ; cx = return value
pop dx ; restore saved regs
pop bx
pop ax
pop di ; di = request amount given to _nfwrite
sub ax,cx ; update number of chars to be written
sbb dx,0
cmp cx,di ; did we get less than we requested?
jb setupret ; yep, we're kaput

; Update es:bx. Note that it is a huge pointer.

add bx,cx ; update es:bx
jnc looptest
mov cx,es
add cx,__AHINCR
mov es,cx
jmp short looptest

;**
; Do a short jump to finish. This has nothing whatsoever to do with the
; surrounding loop and does not lie in its control flow. It is just a
; bridge for the conditional jump near the beginning of this function.


farfinish:
jmp short finish

;**
; Test whether or not there are more characters to be written. If so, jump
; to the beginning of the loop.

looptest:
mov cx,ax
or cx,dx
jnz loopstart
jmp short setupret

;** We're finished, set up the return value and return.

setupret:
mov cx,ax
or cx,dx ; did we fulfill user's request?
jz easyret ; yes, go set ax = count
mov cx,word ptr [ltotal]
sub cx,ax
mov ax,cx
mov cx,word ptr [ltotal] + 2
sbb cx,dx
mov dx,cx ; dx:ax = number of chars written out
div [itemsize] ; ax = number of items written out
jmp short finish

easyret:
mov ax,[count]

finish:
cEnd

else ;not sizeD (near data)

cProc fwrite,,

parmDP buffer
parmW itemsize
parmW count
parmDP stream

localW total
localW bufsize

cBegin

;**
; Set:
; total = cx = number of bytes to be written

mov ax,itemsize
mul count
mov cx,ax
jcxz fardone ; do we have anything to do?
mov total,ax

;**
; Set:
; bx = pointer to user's buffer
; si = stream = pointer to _iob entry

mov bx,buffer
mov si,stream

endif ;sizeD

if sizeD

;***
;_nfwrite - core routine that writes to a stream in large data models
;
;Purpose:
; This is the core routine that writes data to a stream in large data
; models. It is basically the same as the small data model version of
; fwrite, though some of the details (e.g., computing the number of
; bytes to write) are handled by the high-level, large data model
; fwrite code.
;
;Entry:
; cx = number of bytes to write
; ds:si = stream pointer = pointer to _iob entry
; es:bx = pointer to user's buffer
;
;Exit:
; ax = number of bytes written out
; es:bx = pointer to the first byte after the portion of the buffer
; which was written out
;
;Uses:
; ax, bx, cx, dx, di
;
;Preserves:
; si, ds, es
;
;*******************************************************************************

cProc _nfwrite,,<>

localW total
localW bufsize

cBegin

;**
; Set:
; total = cx = number of bytes to be written

mov total,cx

endif ;sizeD

;**
; Set:
; di = pointer to _iob2 entry

mov di,dataOFFSET _iob2
mov ax,si
sub ax,dataOFFSET _iob
add di,ax

;**
; Set bufsize to the proper value. Use [di]._bufsiz if there is a buffer.
; Otherwise, use BUFSIZ (i.e., assume that when a buffer is attached, its
; size will be BUFSIZ).

test [si]._flag,_IOMYBUF OR _IONBF
jnz havebuf
test [di]._flag2,_IOYOURBUF
jz nobuf

havebuf:
mov ax,[di]._bufsiz
jmp short setbufsize
nobuf:
mov ax,BUFSIZ
setbufsize:
mov bufsize,ax

loopbegin:

;**
; Check if the stream has a big buffer (i.e., more than 1 char buffer) and
; if there is room in the buffer. If so, fill it.

test [si]._flag,_IOMYBUF
jnz testcnt
test [di]._flag2,_IOYOURBUF
jz dowrite

testcnt:
mov ax,[si]._cnt
or ax,ax
jz dowrite

; Fill the stream buffer.

cmp ax,cx
jbe copybuf
mov ax,cx

copybuf:
push ax ; save regs
push bx
push cx

if sizeD
push es ; save es
push ax ; push args
push es
push bx
push word ptr [si]._ptr + 2
push word ptr [si]._ptr
else ;not sizeD
push ax ; push args
push bx
push [si]._ptr
endif ;sizeD

callcrt memcpy ; memcpy(stream->_ptr, bx, ax)

if sizeD
add sp,10
pop es ; restore es
else ;not sizeD
add sp,6
endif ;sizeD

pop cx ; restore saved regs
pop bx
pop ax

sub cx,ax ; update num of chars to be written
sub [si]._cnt,ax ; update num of chars in stream buffer
add bx,ax ; advance pointer to user buffer
add word ptr [si]._ptr,ax ; advance stream buffer pointer
jmp short loopcond

ife sizeD

;**
; Jump to done. This has nothing to do with the surrounding loop and does not
; lie in its control flow. It is just a bridge for the conditional jump near
; the beginning of this function.

fardone:
jmp done

endif ;sizeD

;**
; Test cx to see if we have any more characters to write out. If so, jump to
; the start of the loop. Otherwise, go set up the return to the caller.

loopcond:
or cx,cx
jnz loopbegin
if sizeD
jmp doret
else
jmp short doret
endif

;**
; Check to see if a call to lowio's write is appropriate and, if so, do it.
; Note that if we reach here and the stream has a big buffer, it must be
; full and needs to be _flush()-ed.

dowrite:
cmp cx,bufsize ; more than bufsize chars to write?
jb doflsbuf

; If there is a big buffer, it must be flushed with _flush().

test [si]._flag,_IOMYBUF
jnz doflush
test [di]._flag2,_IOYOURBUF
jz dowrite2

doflush:
push bx ; save regs
push cx

if sizeD
push es ; save es
push ds ; push arg
push si
else ;not sizeD
push si ; push arg
endif ;sizeD

call _flush ; _flush(stream)

if sizeD
add sp,4 ; clean off arg
pop es ; restore es
else ;not sizeD
pop dx ; clean off arg
endif ;sizeD

pop cx ; restore saved regs
pop bx

or ax,ax ; did an error occur?
jnz short doret ; yes

; Compute the number bytes to write out = (cx/bufsize)*bufsize.

dowrite2:
xor dx,dx ; zero out dx
mov ax,cx
div bufsize
mov ax,cx
sub ax,dx ; ax = (cx/bufsize)*bufsize

; Set up and issue call to lowio's write().

push ax ; save requested count
push bx ; save regs
push cx

if sizeD
push es ; save es
push ax ; push args
push es
push bx
xor ax,ax
mov al,[si]._file
push ax
else ;not sizeD
push ax ; push args
push bx
xor ax,ax
mov al,[si]._file
push ax
endif ;sizeD

callcrt _write ; write(fileno(stream), bx, ax)

if sizeD
add sp,8 ; clean off args
pop es ; restore es
else ;not sizeD
add sp,6 ; clean off args
endif ;sizeD

pop cx ; restore saved regs
pop bx
pop dx ; requested count

cmp ax, -1 ; did write() return error?
je writerr ; yes - goto error
sub cx,ax ; update num of chars to be written

cmp ax,dx ; was everything written out?
jne writerr ; no, must be an error

add bx,ax ; advance pointer to user's buffer
jmp short loopcond

;**
; Stream buffer is full (or the stream is not yet buffered) and they're not
; enough characters to be written to warrant a direct call to write().
; Therefore, do a _flsbuf().

doflsbuf:
xor ax,ax
if sizeD
mov al,byte ptr es:[bx] ; ax = next char to be written
else ;not sizeD
mov al,byte ptr [bx] ; ax = next char to be written
endif ;sizeD

push bx ; save regs
push cx

if sizeD
push es ; save es
push ds ; push args
push si
push ax
else ;not sizeD
push si ; push args
push ax
endif ;sizeD

callcrt _flsbuf ; _flsbuf(ax, stream)

if sizeD
add sp,6 ; clean off args
pop es ; restore es
else ;not sizeD
add sp,4 ; clean off args
endif ;sizeD

pop cx ; restore saved regs
pop bx

cmp ax,EOF ; error?
je doret ; yep, we're kaput

inc bx ; advance pointer to user's buffer
dec cx ; update num of chars to be written
mov ax,[di]._bufsiz ; update bufsize
or ax,ax ; is _bufsiz still 0
jnz noinc ; no
inc ax ; yes, set bufsize to 1

noinc:
mov bufsize,ax
jmp loopcond

;**
; An error occurred during the write(). Set the stream error bit.

writerr:
or [si]._flag,_IOERR

;**
; We're finished, compute the return value. Note that if we've completely
; fulfilled the user's request, we need only return count.

doret:

ife sizeD
jcxz quickret
endif ;sizeD

mov ax,total
sub ax,cx

ife sizeD
xor dx,dx ; zero out dx
div itemsize
jmp short done

quickret:
mov ax,count
endif ;sizeD

done:
cEnd

sEnd code
end


  3 Responses to “Category : C++ Source Code
Archive   : VCCRT2.ZIP
Filename : FWRITE.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/