Initial commit

This commit is contained in:
Michael Reber 2019-11-15 12:59:38 +01:00
parent 40a414d210
commit b880c3ccde
6814 changed files with 379441 additions and 0 deletions

View File

@ -0,0 +1,136 @@
;
; This program reads text from the standard input device and writes
; filtered and transformed text to the standard output device.
;
; 1. High bit of all characters is stripped off.
; 2. Tabs are expanded.
; 3. Removes all control codes except for line
; feeds, carriage returns, and form feeds.
; 4. Appends an end-of-file mark to the text, if
; none was present in the input stream.
;
; Can be used to make a WordStar file acceptable for
; other screen or line editors, and vice versa.
;
;
cr equ 0dh ; ASCII carriage return
lf equ 0ah ; ASCII line feed
ff equ 0ch ; ASCII form feed
eof equ 01ah ; End-of-file marker
tab equ 09h ; ASCII tab code
command equ 80h ; buffer for command tail
; DOS 2.0 Pre-Defined Handles
stdin equ 0000 ; standard input file
stdout equ 0001 ; standard output file
stderr equ 0002 ; standard error file
stdaux equ 0003 ; standard auxilliary file
stdprn equ 0004 ; standard printer file
cseg segment para public 'CODE'
assume cs:cseg,ds:cseg
org 100H ; start .COM at 100H
clean proc far ; entry point from PC-DOS.
push ds ; push a long return back
xor ax,ax ; to DOS onto the stack.
push ax
clean3: call get_char ; get a character from input.
and al,7fh ; turn off the high bit.
cmp al,20h ; is it a control char?
jae clean4 ; no. write it to output.
cmp al,eof ; is it end of file?
je clean6 ; yes, go write EOF mark and exit.
cmp al,tab ; is it a tab?
je clean5 ; yes, go expand it to spaces.
cmp al,cr ; is it a carriage return?
je clean35 ; yes, go process it.
cmp al,lf ; is it a line feed?
je clean35 ; yes, go process it.
cmp al,ff ; is it a form feed?
jne clean3 ; no. discard it.
clean35:
mov column,0 ; if it's a legit ctrl char,
jmp clean45 ; we should be back at column 0.
clean4: inc column ; if it's a non-ctrl char,
clean45: ; col = col + 1.
call put_char ; write the char to output.
jnc clean3 ; if OK, go back for another char.
mov bx,stderr ; not OK. Set up to show error.
mov dx,offset err_msg
mov cx,err_msg_len ; error = Disk full.
mov ah,40h ; write the error message
int 21h ; to the standard error device. (CON:)
ret ; back to DOS.
clean5: mov ax,column ; tab code detected, must expand
cwd ; expand tabs to spaces.
mov cx,8 ; divide the current column counter
idiv cx ; by eight...
sub cx,dx ; eight minus the remainder is the
add column,cx ; number of spaces to send out to
clean55: ; move to the next tab position.
push cx
mov al,20h
call put_char ; send an ASCII blank
pop cx
loop clean55
jmp clean3
clean6: call put_char ; write out the EOF mark,
ret ; and return to DOS.
clean endp
get_char proc near
mov bx,stdin ; get chars from std. input
mov cx,1 ; # of chars to get = 1
mov dx,offset input_buffer ; location = input_buffer
mov ah,3fh
int 21h ; do the function call
or ax,ax ; test # of chars returned
jz get_char1 ; if none, return EOF
mov al,input_buffer ; else, return the char in AL
ret
get_char1:
mov al,eof ; no chars read, return
ret ; an End-of-File (EOF) mark.
get_char endp
put_char proc near
mov output_buffer,al ; put char to write in buffer.
mov bx,stdout ; write to std. output
mov cx,1 ; # of chars = 1
mov dx,offset output_buffer ; location = output_buffer
mov ah,40h
int 21h ; do the function call
cmp ax,1 ; check to see it was really done.
jne put_char1
clc ; really done. return carry = 0
ret ; as success signal.
put_char1:
stc ; not really done. return carry = 1
ret ; as error signal (device is full).
put_char endp
input_buffer db 0
output_buffer db 0
column dw 0
err_msg db cr,lf
db 'clean: Disk is full.'
db cr,lf
err_msg_len equ (this byte)-(offset err_msg)
cseg ends
end clean

View File

@ -0,0 +1,310 @@
;
; Macro file for MSDOS.
;
SUBTTL BREAK a listing into pages and give new subtitles
PAGE
BREAK MACRO subtitle
SUBTTL subtitle
PAGE
ENDM
BREAK <I_NEED: declare a variable external, if necessary, and allocate a size>
;
; declare a variable external and allocate a size
;
I_NEED MACRO sym,len
CODE ENDS
DATA SEGMENT BYTE PUBLIC 'DATA'
IFIDN <len>,<WORD>
EXTRN &sym:WORD
ELSE
IFIDN <len>,<DWORD>
EXTRN &sym:DWORD
ELSE
EXTRN &sym:BYTE
ENDIF
ENDIF
DATA ENDS
CODE SEGMENT BYTE PUBLIC 'CODE'
ENDM
;
; call a procedure that may be external. The call will be short.
;
invoke MACRO name
&.xcref
add_ext name,near
&.cref
CALL name
ENDM
PAGE
;
; jump to a label that may be external. The call will be near.
;
transfer MACRO name
&.xcref
add_ext name,near
&.cref
JUMP name
ENDM
;
; get a short address in a word
;
short_addr MACRO name
IFDIF <name>,<?>
&.xcref
add_ext name,near
&.cref
DW OFFSET DOSGROUP:name
ELSE
DW ?
ENDIF
ENDM
;
; get a long address in a dword
;
long_addr MACRO name
&.xcref
add_ext name,far
&.cref
DD name
ENDM
;
; declare a PROC near or far but PUBLIC nonetheless
;
procedure MACRO name,distance
PUBLIC name
name PROC distance
ENDM
PAGE
;
; define a data item to be public and of an appropriate size/type
;
I_AM MACRO name,size
PUBLIC name
IFIDN <size>,<WORD>
name DW ?
ELSE
IFIDN <size>,<DWORD>
name DD ?
ELSE
IFIDN <size>,<BYTE>
name DB ?
ELSE
name DB size DUP (?)
ENDIF
ENDIF
ENDIF
ENDM
PAGE
;
; play games with a possible external. Create a new
; macro for the symbol and text, and string it together
; with a central invoker
;
.xcref
.xcref ?i
.xcref def_mac
.xcref ?z0
.xcref add_ext
.cref
IF1
?i=0
ENDIF
?z0 macro
endm
;
; add an external declaration to s with type t if it is not defined
;
add_ext macro s,t
&.xcref
&.xcref ?&s
&.cref
IFNDEF ?&s
?i = ?i + 1
def_mac ?z&%?i,?z&%(?i-1),s,t
ENDIF
endm
;
; define a macro called that possibly externals s:t and then calls macro n
;
def_mac macro m,n,s,t
&.xcref
&.xcref ?&s
&.xcref m
&.cref
m macro
ifndef s
extrn s:&t
endif
purge m
purge ?&s
n
endm
?&s macro
&endm
endm
;
; call the macro chain
;
do_ext macro
&.xcref
expand_mac ?z%?i
&.cref
endm
PAGE
expand_mac macro m
m
endm
;
; define an entry in a procedure
;
entry macro name
PUBLIC name
name:
endm
BREAK <ERROR - print a message and then jump to a label>
error macro code
local a
.xcref
MOV AL,code
transfer SYS_RET_ERR
.cref
ENDM
BREAK <JUMP - real jump that links up shortwise>
;
; given a label <lbl> either 2 byte jump to another label <lbl>_J
; if it is near enough or 3 byte jump to <lbl>
;
jump macro lbl
local a
.xcref
a:
ifndef lbl&_J ; is this the first invocation
JMP lbl
ELSE
IF lbl&_J GE $
JMP lbl
ELSE
IF ($-lbl&_J) GT 126 ; is the jump too far away?
JMP lbl
ELSE ; do the short one...
JMP lbl&_J
ENDIF
ENDIF
ENDIF
endm
BREAK <RETURN - return from a function>
return macro
local a
.xcref
a:
RET
ret_l = a
endm
BREAK <CONDRET - conditional return>
makelab macro l,cc,ncc
j&ncc a ; j<NCC> a:
return ; return
a: ; a:
ret_&cc = ret_l ; define ret_<CC> to be ret_l
endm
condret macro cc,ncc
local a,b
ifdef ret_l ; if ret_l is defined
if (($ - ret_l) le 126) and ($ gt ret_l)
; if ret_l is near enough then
a: j&cc ret_l ; a: j<CC> to ret_l
ret_&cc = a ; define ret_<CC> to be a:
else
makelab a,cc,ncc
endif
else
ifdef ret_&cc ; if ret_<CC> defined
if (($ - ret_&cc) le 126) and ($ gt ret_&cc)
; if ret_<CC> is near enough
a: j&cc ret_&cc ; a: j<CC> to ret_<CC>
ret_&cc = a ; define ret_<CC> to be a:
else
makelab a,cc,ncc
endif
else
makelab a,cc,ncc
endif
endif
endm
;condret macro cc,ncc
; local a,b
; ifdef ret_l ; if ret_l is defined
; if (($ - ret_l) le 126) and ($ gt ret_l)
; ; if ret_l is near enough then
; a: j&cc ret_l ; a: j<CC> to ret_l
; ret_&cc = a ; define ret_<CC> to be a:
; exitm
; endif
; endif
; ifdef ret_&cc ; if ret_<CC> defined
; if (($ - ret_&cc) le 126) and ($ gt ret_&cc)
; ; if ret_<CC> is near enough
; a: j&cc ret_&cc ; a: j<CC> to ret_<CC>
; ret_&cc = a ; define ret_<CC> to be a:
; exitm
; endif
; endif
; j&ncc a ; j<NCC> a:
; return ; return
; a: ; a:
; ret_&cc = ret_l ; define ret_<CC> to be ret_l
;endm
BREAK <RETZ - return if zero, links up shortwise if necessary>
retz macro
condret z,nz
endm
BREAK <RETNZ - return if not zero, links up shortwise if necessary>
retnz macro
condret nz,z
endm
BREAK <RETC - return if carry set, links up shortwise if necessary>
retc macro
condret c,nc
endm
BREAK <RETNC - return if not carry, links up shortwise if necessary>
retnc macro
condret nc,c
endm

View File

@ -0,0 +1,261 @@
; fibo.asm
; assemble using nasm:
; nasm -o fibo.com -f bin fibo.asm
;
;****************************************************************************
; Alterable Constant
;****************************************************************************
; You can adjust this upward but the upper limit is around 150000 terms.
; the limitation is due to the fact that we can only address 64K of memory
; in a DOS com file, and the program is about 211 bytes long and the
; address space starts at 100h. So that leaves roughly 65000 bytes to
; be shared by the two terms (num1 and num2 at the end of this file). Since
; they're of equal size, that's about 32500 bytes each, and the 150000th
; term of the Fibonacci sequence is 31349 digits long.
;
maxTerms equ 15000 ; number of terms of the series to calculate
;****************************************************************************
; Number digits to use. This is based on a little bit of tricky math.
; One way to calculate F(n) (i.e. the nth term of the Fibonacci seeries)
; is to use the equation int(phi^n/sqrt(5)) where ^ means exponentiation
; and phi = (1 + sqrt(5))/2, the "golden number" which is a constant about
; equal to 1.618. To get the number of decimal digits, we just take the
; base ten log of this number. We can very easily see how to get the
; base phi log of F(n) -- it's just n*lp(phi)+lp(sqrt(5)), where lp means
; a base phi log. To get the base ten log of this we just divide by the
; base ten log of phi. If we work through all that math, we get:
;
; digits = terms * log(phi) + log(sqrt(5))/log(phi)
;
; the constants below are slightly high to assure that we always have
; enough room. As mentioned above the 150000th term has 31349 digits,
; but this formula gives 31351. Not too much waste there, but I'd be
; a little concerned about the stack!
;
digits equ (maxTerms*209+1673)/1000
; this is just the number of digits for the term counter
cntDigits equ 6 ; number of digits for counter
org 100h ; this is a DOS com file
;****************************************************************************
;****************************************************************************
main:
; initializes the two numbers and the counter. Note that this assumes
; that the counter and num1 and num2 areas are contiguous!
;
mov ax,'00' ; initialize to all ASCII zeroes
mov di,counter ; including the counter
mov cx,digits+cntDigits/2 ; two bytes at a time
cld ; initialize from low to high memory
rep stosw ; write the data
inc ax ; make sure ASCII zero is in al
mov [num1 + digits - 1],al ; last digit is one
mov [num2 + digits - 1],al ;
mov [counter + cntDigits - 1],al
jmp .bottom ; done with initialization, so begin
.top
; add num1 to num2
mov di,num1+digits-1
mov si,num2+digits-1
mov cx,digits ;
call AddNumbers ; num2 += num1
mov bp,num2 ;
call PrintLine ;
dec dword [term] ; decrement loop counter
jz .done ;
; add num2 to num1
mov di,num2+digits-1
mov si,num1+digits-1
mov cx,digits ;
call AddNumbers ; num1 += num2
.bottom
mov bp,num1 ;
call PrintLine ;
dec dword [term] ; decrement loop counter
jnz .top ;
.done
call CRLF ; finish off with CRLF
mov ax,4c00h ; terminate
int 21h ;
;****************************************************************************
;
; PrintLine
; prints a single line of output containing one term of the
; Fibonacci sequence. The first few lines look like this:
;
; Fibonacci(1): 1
; Fibonacci(2): 1
; Fibonacci(3): 2
; Fibonacci(4): 3
;
; INPUT: ds:bp ==> number string, cx = max string length
; OUTPUT: CF set on error, AX = error code if carry set
; DESTROYED: ax, bx, cx, dx, di
;
;****************************************************************************
PrintLine:
mov dx,eol ; print combined CRLF and msg1
mov cx,msg1len+eollen ;
call PrintString ;
mov di,counter ; print counter
mov cx,cntDigits ;
call PrintNumericString
call IncrementCount ; also increment the counter
mov dx,msg2 ; print msg2
mov cx,msg2len ;
call PrintString ;
mov di,bp ; recall address of number
mov cx,digits ;
; deliberately fall through to PrintNumericString
;****************************************************************************
;
; PrintNumericString
; prints the numeric string at DS:DI, suppressing leading zeroes
; max length is CX
;
; INPUT: ds:di ==> number string, cx = max string length
; OUTPUT: CF set on error, AX = error code if carry set
; DESTROYED: ax, bx, cx, dx, di
;
;****************************************************************************
PrintNumericString:
; first scan for the first non-zero byte
mov al,'0' ; look for ASCII zero
cld ; scan from MSD to LSD
repe scasb ;
mov dx,di ; points to one byte after
dec dx ; back up one character
inc cx ;
; deliberately fall through to PrintString
;****************************************************************************
;
; PrintString
; prints the string at DS:DX with length CX to stdout
;
; INPUT: ds:dx ==> string, cx = string length
; OUTPUT: CF set on error, AX = error code if carry set
; DESTROYED: ax, bx
;
;****************************************************************************
PrintString:
mov bx, 1 ; write to stdout
mov ah, 040h ; write to file handle
int 21h ; ignore return value
ret ;
;****************************************************************************
;
; AddNumbers
; add number 2 at ds:si to number 1 at es:di of width cx
;
;
; INPUT: es:di ==> number1, ds:si ==> number2, cx= max width
; OUTPUT: CF set on overflow
; DESTROYED: ax, si, di
;
;****************************************************************************
AddNumbers:
std ; go from LSB to MSB
clc ;
pushf ; save carry flag
.top
mov ax,0f0fh ; convert from ASCII BCD to BCD
and al,[si] ; get next digit of number2 in al
and ah,[di] ; get next digit of number1 in ah
popf ; recall carry flag
adc al,ah ; add these digits
aaa ; convert to BCD
pushf ;
add al,'0' ; convert back to ASCII BCD digit
stosb ; save it and increment both counters
dec si ;
loop .top ; keep going until we've got them all
popf ; recall carry flag
ret ;
;****************************************************************************
;
; IncrementCount
; increments a multidigit term counter by one
;
; INPUT: none
; OUTPUT: CF set on overflow
; DESTROYED: ax, cx, di
;
;****************************************************************************
IncrementCount:
mov cx,cntDigits ;
mov di,counter+cntDigits-1
std ; go from LSB to MSB
stc ; this is our increment
pushf ; save carry flag
.top
mov ax,000fh ; convert from ASCII BCD to BCD
and al,[di] ; get next digit of counter in al
popf ; recall carry flag
adc al,ah ; add these digits
aaa ; convert to BCD
pushf ;
add al,'0' ; convert back to ASCII BCD digit
stosb ; save and increment counter
loop .top ;
popf ; recall carry flag
ret ;
;****************************************************************************
;
; CRLF
; prints carriage return, line feed pair to stdout
;
; INPUT: none
; OUTPUT: CF set on error, AX = error code if carry set
; DESTROYED: ax, bx, cx, dx
;
;****************************************************************************
CRLF: mov dx,eol ;
mov cx,eollen ;
jmp PrintString ;
;****************************************************************************
; static data
;****************************************************************************
eol db 13,10 ; DOS-style end of line
eollen equ $ - eol
msg1 db 'Fibonacci(' ;
msg1len equ $ - msg1
msg2 db '): ' ;
msg2len equ $ - msg2
;****************************************************************************
; initialized data
;****************************************************************************
term dd maxTerms ;
;****************************************************************************
; unallocated data
;
; A better way to do this would be to actually ask for a memory
; allocation and use that memory space, but this is a DOS COM file
; and so we are given the entire 64K of space. Technically, this
; could fail since we *might* be running on a machine which doesn't
; have 64K free. If you're running on such a memory poor machine,
; my advice would be to not run this program.
;
;****************************************************************************
; static data
counter: ;
num1 equ counter+cntDigits ;
num2 equ num1+digits ;

View File

@ -0,0 +1,207 @@
name free
page 60,132
title 'FREE --- Report free space on disk'
; FREE --- a utility to report free space on
; the default or selected disk drive.
;
; Requires PC-DOS or MS-DOS 2.0.
;
; Used in the form:
; A> FREE [unit:]
; (item in square brackets is optional)
;
cr equ 0dh ;ASCII carriage return
lf equ 0ah ;ASCII line feed
blank equ 20h ;ASCII space code
eom equ '$' ;end of string marker
; Here we define a dummy segment containing labels
; for the default file control block and the command tail buffer,
; so that the main program can access those locations.
;
psp segment para public 'PSP'
org 05ch
fcb label byte ;default file control block
org 080h
command label byte ;default command buffer
psp ends
cseg segment para public 'CODE'
assume cs:cseg,ds:psp,es:data,ss:stack
get_drive proc near ;get drive selection, if any,
;otherwise obtain the identity
;of the current disk drive.
;Return drive (1=A, 2=B, etc) in AL.
;
mov al,fcb ;Pick up the drive code, parsed
;by DOS into the default file
;control block.
or al,al ;Is it the default?
jnz get_drive1 ;no, use it
mov ah,19h ;Yes, get the actual current
int 21h ;drive from PC-DOS.
inc al ;Increment to match FCB code.
get_drive1: ;Return drive code in AL.
ret
get_drive endp
free proc far ;entry point from PC-DOS
push ds ;save DS:0000 for final
xor ax,ax ;return to PC-DOS
push ax
mov ax,data ;make our data segment
mov es,ax ;addressable via ES register.
mov ah,30h ;check version of PC-DOS.
int 21h
cmp al,2
jae free1 ;proceed, DOS 2.0 or greater.
mov dx,offset msg2 ;DOS 1.x --- print error message
mov ax,es ;and exit. First fix up DS register
mov ds,ax ;so error message is addressable.
jmp free4
free1: call get_drive ;get drive selection into DL.
push es ;copy ES to DS for remainder
pop ds ;of the program...
assume ds:data ;and tell assembler about it.
mov dl,al
add al,'A'-1 ;form drive letter from drive code,
mov outputb,al ;and put it into the output string.
mov ah,36h ;now call DOS to get free disk space.
int 21h
cmp ax,-1 ;was drive invalid?
je free3 ;yes,go print error message
;drive was ok, so now registers are...
;AX=number of sectors per cluster
;BX=available clusters,
;CX=number of bytes per sector,
;DX=total clusters per drive.
;calculate free space:
mul cx ;sectors per cluster * bytes per sector
;(we assume this won't overflow into DX)
mul bx ;then * available clusters
;DX:AX now contains free space in bytes.
;SI = last byte address for converted string.
mov si,offset (outputa+9)
mov cx,10 ;CX = 10, radix for conversion
call bin_to_asc ;convert free space value to ASCII,
mov dx,offset output
jmp free4 ;and print it out.
free3: mov dx,offset msg1 ;illegal drive, print error
free4: mov ah,9 ;print the string whose address
int 21h ;is in DX.
ret ;then return to DOS.
free endp
; Convert 32 bit binary value to ASCII string.
;
; Call with DX:AX = signed 32 bit value
; CX = radix
; SI = last byte of area to store resulting string
; (make sure enough room is available to store
; the string in the radix you have selected.)
;
; Destroys AX, BX, CX, DX, and SI.
;
bin_to_asc proc near ;convert DX:AX to ASCII.
;force storage of at least 1 digit.
mov byte ptr [si],'0'
or dx,dx ;test sign of 32 bit value,
pushf ;and save sign on stack.
jns bin1 ;jump if it was positive.
not dx ;it was negative, take 2's complement
not ax ;of the value.
add ax,1
adc dx,0
bin1: ;divide the 32 bit value by the radix
;to extract the next digit for the
;forming string.
mov bx,ax ;is the value zero yet?
or bx,dx
jz bin3 ;yes, we are done converting.
call divide ;no, divide by radix.
add bl,'0' ;convert the remainder to an ASCII digit.
cmp bl,'9' ;we might be converting to hex ASCII,
jle bin2 ;jump if in range 0-9,
add bl,'A'-'9'-1 ;correct it if in range A-F.
bin2: mov [si],bl ;store this character into string.
dec si ;back up through string,
jmp bin1 ;and do it again.
bin3: ;restore sign flag,
popf ;was original value negative?
jns bin4 ;no, jump
;yes,store sign into output string.
mov byte ptr [si],'-'
bin4: ret ;back to caller.
bin_to_asc endp
; General purpose 32 bit by 16 bit unsigned divide.
; This must be used instead of the plain machine unsigned divide
; for cases where the quotient may overflow 16 bits (for example,
; dividing 100,000 by 2). If called with a zero divisor, this
; routine returns the dividend unchanged and gives no warning.
;
; Call with DX:AX = 32 bit dividend
; CX = divisor
;
; Returns DX:AX = quotient
; BX = remainder
; CX = divisor (unchanged)
;
divide proc near ; Divide DX:AX by CX
jcxz div1 ; exit if divide by zero
push ax ; 0:dividend_upper/divisor
mov ax,dx
xor dx,dx
div cx
mov bx,ax ; BX = quotient1
pop ax ; remainder1:dividend_lower/divisor
div cx
xchg bx,dx ; DX:AX = quotient1:quotient2
div1: ret ; BX = remainder2
divide endp
cseg ends
data segment para public 'DATA'
output db cr,lf
outputa db 10 dup (blank)
db ' bytes free on drive '
outputb db 'x:',cr,lf,eom
msg1 db cr,lf
db 'That disk drive does not exist.'
db cr,lf,eom
msg2 db cr,lf
db 'Requires DOS version 2 or greater.'
db cr,lf,eom
data ends
stack segment para stack 'STACK'
db 64 dup (?)
stack ends
end free

View File

@ -0,0 +1,55 @@
;
; Synopsis: int getsec(drive,numsec,begsec,buffer)
; unsigned int drive; /* 0=A, 1=B, etc. */
; unsigned int numsec; /* Number of sectors to read */
; unsigned int begsec; /* Beginning logical sector */
; char *buffer; /* Transfer address */
;
; Function: The number of sectors specified are transferred
; between the given drive and the transfer address.
; LOGICAL SECTOR NUMBERS are obtained by numbering
; each sector sequentially starting from track 0, head 0,
; sector 1 (logical sector 0) and continuing along the
; same head, then to the next head until the last sector
; on the last head of the track is counted. Thus,
; logical sector 1 is track 0, head 0, sector 2,
; logical sector 2 is track 0, head 0, sector 3, & so on.
;
; Returns: NULL if the operation is successful.
; otherwise, error codes are as follows:
;
; hex 80 Attachment failed to respond.
; hex 40 SEEK operation failed.
; hex 20 Controller failure.
; hex 10 Bad CRC on diskette read.
; hex 08 DMA overrun on operation.
; hex 04 Requested sector not found.
; hex 03 Write attempt on write-protected diskette.
; hex 02 Address mark not found.
; hex FF Unspecified (error other than those above).
;
code segment byte public ;segment registers remain intact
assume cs:code ;all other registers will be destroyed
public getsec
getsec: push bp ;save old frame pointer
mov bp,sp ;get new frame pointer
mov ax,4[bp] ;put drive number into AL
xor ah,ah
mov cx,6[bp] ;number of sectors to fetch
mov dx,8[bp] ;logical record number of 1st sector
mov bx,10[bp] ;pointer to transfer address
int 25h ;BIOS call
jc error ;error has occurred if carry flag = 1
mov al,00H ;NULL to indicate sucessful completion
jmp done
error: cmp al,00H ;detect unspecified error code 00H
jne done ;...change to 0FFh if found to
mov al,0FFH ;...differentiate it from success code
done: xor ah,ah ;return AL only
popf ;remove flags int 0x25 left on stack
pop bp ;restore original frame pointer
ret ;all done
code ends
end

373
assembly/Alarm.asm Normal file
View File

@ -0,0 +1,373 @@
cseg segment para public 'code'
org 100h
alarm proc far
; Memory-resident program to intercept the timer interrupt and display the
; system time in the upper right-hand corner of the display.
; This program is run as 'ALARM hh:mm x', where hh:mm is the alarm time and
; x is '-' to turn the display off. Any other value of x or no value will
; turn the clock on
intaddr equ 1ch*4 ; interrupt address
segaddr equ 62h*4 ; segment address of first copy
mfactor equ 17478 ; minute conversion factor * 16
whozat equ 1234h ; signature
color equ 14h ; color attribute
assume cs:cseg,ds:cseg,ss:nothing,es:nothing
jmp p150 ; start-up code
jumpval dd 0 ; address of prior interrupt
signature dw whozat ; program signature
state db 0 ; '-' = off, all else = on
wait dw 18 ; wait time - 1 second or 18 ticks
hour dw 0 ; hour of the day
atime dw 0ffffh ; minutes past midnite for alarm
acount dw 0 ; alarm beep counter - number of seconds (5)
atone db 5 ; alarm tone - may be from 1 to 255 - the
; higher the number, the lower the frequency
aleng dw 8080h ; alarm length (loop count) may be from 1-FFFF
dhours dw 0 ; display hours
db ':'
dmins dw 0 ; display minutes
db ':'
dsecs dw 0 ; display seconds
db '-'
ampm db 0 ; 'A' or 'P' for am or pm
db 'm'
tstack db 16 dup('stack ') ; temporary stack
estack db 0 ; end of stack
holdsp dw 0 ; original sp
holdss dw 0 ; original ss
p000: ; interrupt code
push ax ; save registers
push ds
pushf
push cs
pop ds ; make ds=cs
mov ax,wait ; check wait time
dec ax ; zero?
jz p010 ; yes - 1 second has elapsed
mov wait,ax ; not this time
jmp p080 ; return
p010: cli ; disable interrupts
mov ax,ss ; save stack
mov holdss,ax
mov holdsp,sp
mov ax,ds
mov ss,ax ; point to internal stack
mov sp,offset estack
sti ; allow interrupts
push bx ; save other registers
push cx
push dx
push es
push si
push di
push bp
mov ax,18 ; reset wait time
mov wait,ax
mov al,state ; are we disabled?
cmp al,'-'
jnz p015 ; no
jmp p070
p015: mov ah,0 ; read time
int 1ah ; get time of day
mov ax,dx ; low part
mov dx,cx ; high part
mov cl,4
shl dx,cl ; multiply by 16
mov bx,ax
mov cl,12
shr bx,cl ; isolate top 4 bits of ax
add dx,bx ; now in upper
mov cl,4
shl ax,cl ; multiply by 16
mov bx,mfactor ; compute minutes
div bx ; minutes in ax, remainder in dx
cmp ax,atime ; time to sound the alarm?
jnz p020 ; no
call p100 ; yes - beep the speaker twice
push ax
mov ax,acount ; get beep count
dec ax ; down by 1
mov acount,ax ; save beep count
cmp ax,0 ; is it zero?
jnz p018 ; no - keep alarm on
mov ax,0ffffh ; turn off alarm
mov atime,ax
p018: pop ax
p020: mov dsecs,dx ; save remainder
mov bx,60 ; compute hours
xor dx,dx ; zero it
div bx ; hours in ax, minutes in dx
mov dmins,dx ; save minutes
cmp ax,0 ; midnight?
jnz p030 ; no
mov ax,12 ; yes
jmp p040a ; set am
p030: cmp ax,12 ; before noon?
jb p040a ; yes - set am
jz p040p ; noon - set pm
sub ax,12 ; convert the rest
p040p: mov bl,'p'
jmp p040x
p040a: mov bl,'a'
p040x: mov ampm,bl
aam ; fix up hour
cmp ax,hour ; top of the hour?
jz p060 ; no
mov hour,ax
call p120 ; beep the speaker once
p060: add ax,3030h ; convert hours to ascii
xchg ah,al
mov dhours,ax
mov ax,dmins ; get minutes
aam
add ax,3030h ; convert to ascii
xchg ah,al
mov dmins,ax
mov ax,dsecs ; get seconds (remainder)
xor dx,dx
mov bx,60
mul bx
mov bx,mfactor
div bx ; seconds in ax
aam
add ax,3030h
xchg ah,al
mov dsecs,ax
xor ax,ax ; check monitor type
mov es,ax
mov ax,es:[410h] ; get config byte
and al,30h ; isolate monitor type
cmp al,30h ; color?
mov ax,0b000h ; assume mono
jz p061 ; its mono
mov ax,0b800h ; color screen address
p061: mov dx,es:[463h] ; point to 6845 base port
add dx,6 ; point to status port
mov es,ax ; point to monitor
mov bh,color ; color in bh
mov si,offset dhours ; point to time
mov di,138 ; row 1, col 69
cld
mov cx,11 ; loop count
p062: mov bl,[si] ; get next character
p063: in al,dx ; get crt status
test al,1 ; is it low?
jnz p063 ; no - wait
cli ; no interrupts
p064: in al,dx ; get crt status
test al,1 ; is it high?
jz p064 ; no - wait
mov ax,bx ; move color & character
stosw ; move color & character again
sti ; interrupts back on
inc si ; point to next character
loop p062 ; done?
p070: pop bp ; restore registers
pop di
pop si
pop es
pop dx
pop cx
pop bx
cli ; no interrupts
mov ax,holdss
mov ss,ax
mov sp,holdsp
sti ; allow interrupts
p080: popf
pop ds
pop ax
jmp cs:[jumpval]
p100 proc near ; beep the speaker twice
call p120
push cx
mov cx,20000
p105: loop p105 ; wait around
pop cx
call p120
push cx
mov cx,20000
p106: loop p106 ; wait around
pop cx
call p120
ret
p100 endp
p120 proc near ; beep the speaker once
push ax
push cx
mov al,182
out 43h,al ; setup for sound
mov al,0
out 42h,al ; low part
mov al,atone ; get alarm tone
out 42h,al ; high part
in al,61h
push ax ; save port value
or al,3
out 61h,al ; turn speaker on
mov cx,aleng ; get loop count
p125: loop p125 ; wait around
pop ax ; restore original port value
out 61h,al ; turn speaker off
pop cx
pop ax
ret
p120 endp
p150: ; start of transient code
mov dx,offset copyr
call p220 ; print copyright
mov ax,0
mov es,ax ; segment 0
mov di,segaddr+2 ; this program's prior location
mov ax,es:[di] ; get prior code segment
mov es,ax ; point to prior program segment
mov di,offset signature
mov cx,es:[di] ; is it this program?
cmp cx,whozat
jnz p160 ; no - install it
call p200 ; set state & alarm
int 20h ; terminate
p160: mov di,segaddr+2 ; point to int 62h
mov ax,0
mov es,ax ; segment 0
mov ax,ds ; get current ds
mov es:[di],ax ; set int 62h
mov si,offset jumpval
mov di,intaddr ; point to timer interrupt
mov bx,es:[di] ; get timer ip
mov ax,es:[di+2] ; and cs
mov [si],bx ; save prior ip
mov [si+2],ax ; and cs
mov bx,offset p000
mov ax,ds
cli ; clear interrupts
mov es:[di],bx ; set new timer interrupt
mov es:[di+2],ax
sti ; set interrupts
push ds
pop es
call p200 ; set state & alarm
mov dx,offset p150 ; last byte of resident portion
inc dx
int 27h ; terminate
p200 proc near ; set state & alarm
mov si,80h ; point to command line
mov ax,0
mov di,0ffffh ; init hours
mov bh,0
mov ch,0
mov dh,0 ; : counter
mov es:[state],bh ; turn clock on
mov cl,[si] ; get length
jcxz p210 ; it's zero
p203: inc si ; point to next char
mov bl,[si] ; get it
cmp bl,'-' ; is it a minus?
jnz p204 ; no
mov es:[state],bl ; turn clock off
push dx
mov dx,offset msg3 ; print msg
call p220
pop dx
jmp p206
p204: cmp dh,2 ; seen 2nd colon?
jz p206 ; yes - ignore seconds
cmp bl,':' ; colon?
jnz p205 ; no
inc dh
cmp dh,2 ; second colon?
jz p206 ; yes - ignore seconds
push cx
push dx
mov cx,60
mul cx ; multiply current ax by 60
pop dx
pop cx
mov di,ax ; save hours
mov ax,0
jmp p206
p205: cmp bl,'0'
jb p206 ; too low
cmp bl,'9'
ja p206 ; too high - can be a problem
sub bl,'0' ; convert it to binary
push cx
push dx
mov cx,10
mul cx ; multiply current value by 10
add ax,bx ; and add latest digit
pop dx
pop cx
p206: loop p203 ; done yet?
cmp di,0ffffh ; any time to set?
jz p210 ; no
add ax,di ; add hours
cmp ax,24*60
jb p209 ; ok
mov dx,offset msg1 ; print error message
call p220
jmp p210
p209: mov es:[atime],ax ; save minutes past midnight
mov ax,5
mov es:[acount],ax ; set alarm count
mov dx,offset msg2 ; print set msg
call p220
p210: ret
p200 endp
p220 proc near ; print message
push ax
mov ah,9
int 21h
pop ax
ret
p220 endp
copyr db 'Alarm - Clock',10,13,'$'
msg1 db 'Invalid time - must be from 00:00 to 23:59',10,13,'$'
msg2 db 'Resetting alarm time',10,13,'$'
msg3 db 'Turning clock display off',10,13,'$'
alarm endp
cseg ends
end alarm

View File

@ -0,0 +1,147 @@
; slip.asm
;
; This is an 8086+ implementation of SLIP (RFC 1055)
;
; It may be assembled using Microsoft's MASM using the command line:
; ml -Fl -c slip.asm
;
; or using Borland's TASM using the command line:
; tasm -la -m2 -jLOCALS slip.asm
;
.model small
.stack 100h
.data
SLIP_END equ 0C0h
SLIP_ESC equ 0DBh
SLIP_ESC_END equ 0DCh
SLIP_ESC_ESC equ 0DDh
; note that these are both sample macros and are very simple
; In both cases, DX is assumed to already be pointing to the
; appropriate I/O port and a character is always assumed to
; be ready.
SEND_CHAR macro char
IFDIFI <char>, <al>
mov al,char
ENDIF
out dx,al
endm
RECV_CHAR macro
in al,dx
endm
.code
;****************************************************************************
; send_packet
;
; sends the passed packet (which is in a memory buffer) to the output
; device by using the macro SEND_CHAR() which must be defined by the
; user. A sample SEND_CHAR() is defined above.
;
; Entry:
; DS:SI ==> raw packet to be sent
; CX = length of raw packet to be sent
; direction flag is assumed to be cleared (incrementing)
;
; Exit:
;
;
; Trashed:
; none
;
;****************************************************************************
send_packet proc
push cx
push si
SEND_CHAR SLIP_END ; send an end char to flush any garbage
jcxz @@bailout ; if zero length packet, bail out now
@@nextchar:
lodsb ; load next char
cmp al,SLIP_END ; Q: is it the special END char?
jne @@check_esc ; N: check for ESC
SEND_CHAR SLIP_ESC ; Y: send ESC + ESC_END instead
mov al,SLIP_ESC_END ;
jmp @@ordinary ;
@@check_esc:
cmp al,SLIP_ESC ; Q: is it the special ESC char?
jne @@ordinary ; N: send ordinary char
SEND_CHAR SLIP_ESC ; Y: send ESC + ESC_END instead
mov al,SLIP_ESC_ESC ;
; fall through to ordinary character
@@ordinary:
SEND_CHAR al ;
loop @@nextchar ; keep going until we've sent all chars
@@bailout:
SEND_CHAR SLIP_END ; send an end char to signal end of packet
pop si
pop cx
ret
send_packet endp
;****************************************************************************
; recv_packet
;
; receives a packet using the macro RECV_CHAR() which must be defined by
; the user and places the received packet into the memory buffer pointed
; to by ES:DI. The final length is returned in BX.
;
; Note that in the case of a buffer overrun, the portion of the packet
; that fit into the buffer is returned and BX and CX are equal. There
; is no way to tell the difference between a packet that just exactly
; fit and one which was truncated due to buffer overrun, so it is
; important to assure that the buffer is big enough to ALWAYS contain
; at least one spare byte.
;
; A sample RECV_CHAR() is defined above.
;
; Entry:
; ES:DI ==> packet buffer
; CX = length of buffer
; direction flag is assumed to be cleared (incrementing)
;
; Exit:
; BX = length of packet received
;
; Trashed:
; none
;
;****************************************************************************
recv_packet proc
push cx
push di
xor bx,bx ; zero received byte count
jcxz @@bailout ; if zero length packet, bail out now
@@nextchar:
RECV_CHAR ; fetch a character into al
cmp al,SLIP_END ; Q: is it the special END char?
jne @@check_esc ; N: check for ESC
or bx,bx ; YQ: is it the beginning of packet?
jz @@nextchar ; Y: keep looking
jmp @@bailout ; N: end of packet, so return it
@@check_esc:
cmp al,SLIP_ESC ; Q: is it the special ESC char?
jne @@ordinary ; N: it's an ordinary char
RECV_CHAR ; Y: get another character
cmp al,SLIP_ESC_END ; Q: is it ESC_END?
jne @@check_esc_esc ; N: check for ESC_ESC
mov al,SLIP_END ; Y: convert to ordinary END char
jmp @@ordinary ;
@@check_esc_esc:
cmp al,SLIP_ESC_ESC ; Q: is it ESC_ESC?
mov al,SLIP_ESC ; Y: convert to ordinary ESC char
; protocol violation! fall through to ordinary character
@@ordinary:
stosb ; store character in buffer
inc bx ; got another char
loop @@nextchar ; keep going until we've sent all chars
@@bailout:
pop di
pop cx
ret
recv_packet endp
END

View File

@ -0,0 +1,325 @@
; showdate.asm
;
; prints the date and time to stdout
; equivalent to the following C++ program:
;
;#include <iostream.h>
;#include <time.h>
;
;int main()
;{
; time_t t;
; time(&t); // get the current time
; cout << ctime(&t); // convert to string and print
; return 0;
;}
;
; This code may be assembled and linked using Borland's TASM:
; tasm /la /m2 showdate
; tlink /Tdc showdate
;
STDOUT equ 01h ; handle of standard output device
DOS_GET_DATE equ 02ah ; get system date
DOS_GET_TIME equ 02ch ; get system time
DOS_WRITE_HANDLE equ 040h ; write to handle
DOS_TERMINATE equ 04ch ; terminate with error code
DOSINT macro function, subfunction
IFB <subfunction>
mov ah,(function AND 0ffh)
ELSE
mov ax,(function SHL 8) OR (subfunction AND 0ffh)
ENDIF
int 21h ; invoke DOS function
endm
MODEL tiny
;.STACK 100h
.CODE
;****************************************************************************
; main
;
; calls showdate routne and exists with 00 error code
;
; Entry:
;
; Exit:
;
; Trashed:
; none
;
;****************************************************************************
main proc far
.STARTUP ; sets up DS and stack
call showdate ;
.EXIT 0 ; return with errcode=0
main endp
;****************************************************************************
; showdate
;
; fetches the DOS system date, prints it to stdout and exits
; the format of the output is identical to that of the Posix ctime()
; function:
;
; Thu May 11 16:11:30 2000
;
; The day of week and month are always 3 characters long. The time of
; day is in 24hour form (e.g. 16:11:30 is a few minutes after four in
; the afternoon) and the year is always four digits. The whole thing is
; followed by a newline character (line feed = 0ah), making 25
; characters total.
;
; Note that ctime() returns 26 characters which is all of the above,
; followed by a terminating NUL char but this program does not emit a
; NUL.)
;
; Entry:
; DS points to segment for our data tables
;
; Exit:
; carry may be set if last write failed
;
; Trashed:
; none
;
;****************************************************************************
showdate proc
push ax bx cx dx ;
DOSINT DOS_GET_DATE ;
; returns the following
; cx = year (1980-2099)
; dh = month (1-12) == (Jan..Dec)
; dl = day (1-31)
; al = day of week (0-6) == (Sun..Sat)
push cx ;
push dx ; save the return values
; write the day of week
mov dx, offset dayname ;
mov cx,3 ; number of bytes to write
call WriteSubstring ;
; write the month
pop ax ; recall month/day
push ax ; and save it again
mov al,ah ; isolate just month
mov dx, offset monthname - 3 ; monthname array is 1-based
mov cx,3 ; number of bytes to write
call WriteSubstring ;
; write the day of the month
pop ax ;
call WriteNumber ;
call WriteSpace ;
; write the hour
DOSINT DOS_GET_TIME ; ch = hour, cl = min,
; dh = sec, dl = hundredths
push dx ; save seconds
push cx ; save minutes
mov al,ch ;
call WriteNumber ;
call WriteColon ;
; write the minutes
pop ax ;
call WriteNumber ;