A DOS 2.0 filter for word processing document files
;
; 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
BIOS-based disk I-O to access MS-DOS file structure

; rawread.asm
;
; this program reads a DOS cluster using only BIOS disk calls. All
; of the tasks usually done by DOS, e.g. FAT lookup, cluster to
; logical sector translation, logical to physical translation, are
; all done by this program instead. The idea is to be able to create
; a program that can access DOS disks from a bootable floppy without
; having to have DOS.
;
; well, that's what it used to do. Now it's supposed to do something
; completely different. Its job is to scan the entire surface of the
; hard drive, looking for the specified string. If that string is
; found, it is to print the full path and directory entry, including
; the file date and time.
;
; but wait! There's more. Now what we have is a number of raw
; routines which could prove useful for manipulating a DOS file
; structure outside of the DOS environment. The main routine still
; should be kept (if renamed), since the order in which these things
; are done is important (e.g. later calls depend on data set up by
; earlier calls).
;
; get filename
; parse filename into subdirs
; locate root dir and cluster size
; follow subdir routing to filename
; report file size, date & time
;
.MODEL small
.STACK 0200h
.586P

.DATA
PartEntry STRUC
Bootable db ? ;80h = bootable, 00h = nonbootable
BeginHead db ? ;beginning head
BeginSector db ? ;beginning sector
BeginCylinder db ? ;beginning cylinder
FileSystem db ? ;name of file system
EndHead db ? ;ending head
EndSector db ? ;ending sector
EndCylinder db ? ;ending cylinder
StartSector dd ? ;starting sector (relative to beg. of disk)
PartSectors dd ? ;number of sectors in partition
PartEntry ENDS

BootSector STRUC
Jump db ? ;E9 xx xx or EB xx 90
JumpTarget dw ? ;E9 xx xx or EB xx 90
OemName db '????????' ;OEM name & version
;Start of BIOS parameter block
BytesPerSec dw ? ;bytes per sector
SecPerClust db ? ;sectors per cluster
ResSectors dw ? ;number of reserved sectors
FATs db ? ;number of file allocation tables
RootDirEnts dw ? ;number of root-dir entries
Sectors dw ? ;total number of sectors
Media db ? ;media descriptor byte
FATsecs dw ? ;number of sectors per FAT
SecPerTrack dw ? ;sectors per track
Heads dw ? ;number of heads
HiddenSecs dd ? ;number of hidden sectors
HugeSectors dd ? ;num sectors if Sectors==0
;End of BIOS parameter block
BootSector ENDS

DirEntry STRUC
FileName db '????????' ;name
Extension db '???' ;extension
Attributes db ? ;attributes
Reserved db 10 dup (?) ;reserved
Time dw ? ;time stamp
Date dw ? ;date stamp
StartCluster dw ? ;starting cluster
FileSize dd ? ;file size
DirEntry ENDS

BootFileName db "CONFIG SYS" ;the boot loader for this OS
MBR DB 0200h DUP (?)
buff DB 0200h * 40h DUP (?)
ClustOffs dd ?

CR EQU 0DH
LF EQU 0AH

.CODE
main PROC
STARTUPCODE ;initialize stuff
call FetchMBR C ;fetch the master boot record
jc @@exit
mov cx,4 ;search up to four partitions
add bx,01aeh ;point to partition table (-10h)
@@FindBootable:
add bx,10h ;point to next entry
cmp BYTE ptr [bx],80h ;is it a bootable partition?
loopnz @@FindBootable
call FetchSector C, \
WORD ptr [(PartEntry PTR bx).BeginHead], \
WORD ptr [(PartEntry PTR bx).BeginSector], \
WORD ptr [(PartEntry PTR bx).BeginCylinder], \
OFFSET MBR, ds ;SEG MBR
;
; here's the point at which our OS loader would begin, with the
; BootSector structure in memory.
;
mov bx, OFFSET MBR
call CalcClustOff C, \
WORD ptr [(BootSector PTR bx).ResSectors], \
WORD ptr [(BootSector PTR bx).FATsecs], \
WORD ptr [(BootSector PTR bx).FATs], \
WORD ptr [(BootSector PTR bx).RootDirEnts], \
WORD ptr [(BootSector PTR bx).BytesPerSec], \
WORD ptr [(BootSector PTR bx).SecPerClust]
mov WORD ptr [ClustOffs],ax
mov WORD ptr [ClustOffs+2],dx
call CalcClust2 C, \
WORD ptr [(BootSector PTR bx).ResSectors], \
WORD ptr [(BootSector PTR bx).FATsecs], \
WORD ptr [(BootSector PTR bx).FATs]
; now dx:ax contains the logical sector for cluster 2
call LsectToGeom C, \
ax, dx, \
WORD ptr [(BootSector PTR bx).HiddenSecs] , \
WORD ptr [((BootSector PTR bx).HiddenSecs)+2],\
[(BootSector PTR bx).Heads], \
[(BootSector PTR bx).SecPerTrack]

mov dl,80h
mov bx,offset buff
mov al,[(BootSector PTR MBR).SecPerClust]
mov ah,2h ; get ready to read
int 13h
; now find our desired filename within buffer (which has the root dir)

call FindFile C, \
bx, 200h * 40h, offset BootFileName
xor dh,dh
mov dl,[(BootSector PTR MBR).SecPerClust]
mov si,ax
mov ax,[(DirEntry PTR si).StartCluster]
mul dx
add ax,WORD ptr [ClustOffs]
adc dx,WORD ptr [ClustOffs+2]
; now dx:ax contains logical sector number for start of file

call LsectToGeom C, \
ax, dx, \
WORD ptr [(BootSector PTR MBR).HiddenSecs] , \
WORD ptr [((BootSector PTR MBR).HiddenSecs)+2],\
[(BootSector PTR MBR).Heads], \
[(BootSector PTR MBR).SecPerTrack]
mov dl,80h
mov ax,204h ; read in 2k worth of data
int 13h

@@exit:
EXITCODE ;exit to DOS
ENDP main

;
; FetchMBR - fetches the Master Boot Record from the first physical
; hard disk and stores it in the location MBR.
;
; INPUT: none
; OUTPUT: AX is error code if CY set, ES:BX ==> MBR
; DESTROYED: none
;
FetchMBR PROC C
USES cx, dx ;save registers we'll use
mov dx,80h ;first physical disk
mov cx,1 ;head 1, sector 0
mov bx,ds ;
mov es,bx ;point to boot record buffer
mov bx,OFFSET MBR ;read into boot record
mov ax,0201h ;read one sector
int 13h ;BIOS read
ret ;return to main
FetchMBR ENDP

;
; FetchSector - fetches the physical sector described by the passed
; parameters and stores it in the named buffer
;
; INPUT: head, sector, cylinder, buffer
; OUTPUT: AX is error code if CY set, ES:BX ==> Boot
; DESTROYED: none
;
FetchSector PROC C head:BYTE, sector:BYTE, cylinder:BYTE, buffer:DWORD
USES cx, dx ;save registers we'll use
mov ch, [cylinder] ;
mov cl, [sector] ;
mov dh, [head] ;
mov dl, 80h ;first physical hard drive
les bx, [buffer] ;
mov ax,0201h ;read one sector
int 13h ;BIOS read
ret ;return to main
FetchSector ENDP

;
; GeomToLsect - converts to logical sector number from the physical
; geometry (head, cylinder, track). See LsectToGeom.
;
; INPUT: cx, dx are set with cylinder/track, and head respectively
; HiddenSecs, Heads, SecPerTrack
; OUTPUT: lsect
; DESTROYED: none
;
GeomToLsect PROC C lsect:DWORD, dHiddenSecs:DWORD, \
dHeads:WORD, dSecPerTrack:WORD, buffer:DWORD
USES ax ;save registers we'll use
mov ax, WORD ptr [lsect] ;load lsect into DX:AX
mov dx, WORD ptr [lsect+2] ;
stc ;add one additional
adc ax, WORD ptr [dHiddenSecs] ;add starting sector
adc dx, WORD ptr [dHiddenSecs+2] ;
div [dSecPerTrack] ;
mov cl,dl ;store sector in cl
xor dx,dx ;
div [dHeads] ;
mov dh,dl ;store head in dh
mov ch,al ;store low 8 bits of cylinder in ch
shr ax,1 ;
shr ax,1 ;
and al,0c0h ;pass through two hi bits only
or cl,ah ;mov bits into location
ret ;
GeomToLsect ENDP

;
; LsectToGeom - converts from logical sector number to the physical
; geometry (head, cylinder, track) in the form required
; by the BIOS (Int 13h) disk read and write calls.
;
; INPUT: lsect, HiddenSecs, Heads, SecPerTrack
; OUTPUT: cx, dx are set with cylinder/track, and head respectively
; DESTROYED: none
;
LsectToGeom PROC C lsect:DWORD, lHiddenSecs:DWORD, \
lHeads:WORD, lSecPerTrack:WORD, buffer:DWORD
USES ax ;save registers we'll use
mov ax, WORD ptr [lsect] ;load lsect into DX:AX
mov dx, WORD ptr [lsect+2] ;
stc ;add one additional
adc ax, WORD ptr [lHiddenSecs] ;add starting sector
adc dx, WORD ptr [lHiddenSecs+2] ;
div [lSecPerTrack] ;
mov cl,dl ;store sector in cl
xor dx,dx ;
div [lHeads] ;
mov dh,dl ;store head in dh
mov ch,al ;store low 8 bits of cylinder in ch
shr ax,1 ;
shr ax,1 ;
and al,0c0h ;pass through two hi bits only
or cl,ah ;mov bits into location
ret ;
LsectToGeom ENDP

;
; CalcClust2 - calculates the starting logical sector number of
; cluster 2, (the beginning of data space for
; partitions).
;
; INPUT: ResSectors, FATsecs, FATs
; OUTPUT: dx:ax contains the starting logical sector number
; DESTROYED: none
;
CalcClust2 PROC C cResSectors:WORD, cFATsecs:WORD, cFATs:BYTE
xor dx,dx ;
mov ax,[cFATsecs] ;
mul [cFATs] ;
add ax,[cResSectors] ;
adc dx,0 ;
ret
CalcClust2 ENDP

;
; CalcClustOff - calculates the starting logical sector number of
; cluster 0, which isn't really a cluster, but the
; number returned is useful for calculations converting
; cluster number to logical sector
;
; INPUT: ResSectors, FATsecs, FATs
; OUTPUT: dx:ax contains the starting logical sector number
; DESTROYED: none
;
CalcClustOff PROC C dResSectors:WORD, dFATsecs:WORD, dFATs:BYTE, \
dRootDirEnts:WORD, dBytesPerSec:WORD, dSecPerClust:BYTE
LOCAL clustLo:WORD, clustHi:WORD
xor dh,dh
mov ax,[dFatSecs]
mov dl,[dFATs]
mul dx
add ax,[dResSectors]
adc dx,0
; call CalcClust2 C, [dResSectors], [dFATsecs], [dFATs]
; now dx:ax = FATs * FATsecs + ResSectors
mov [clustLo],ax
mov [clustHi],dx
mov dx,20h ; bytes per dir entry
mov ax,[dRootDirEnts] ;
mul dx ; multiply 'em out
div [dBytesPerSec] ; and divide by bytes/sec
add [clustLo],ax ;
adc [clustHi],dx ; create the aggregate
mov al,[dSecPerClust] ;
xor ah,ah ;
shl ax,1 ; AX = SecPerClust * 2
sub [clustLo],ax ;
sbb [clustHi],0 ; propagate carry flag
mov ax,[clustLo] ;
mov dx,[clustHi] ;
ret
CalcClustOff ENDP

;
; FindFile - given a memory buffer containing the directory data
; and a static file name for which to search, this routine
; finds the file and returns a pointer to its directory
; entry in ds:si
;
; INPUT: dirbuffer, filespec
; OUTPUT: ax contains pointer to directory entry (or NULL)
; DESTROYED: none
;
FindFile PROC C dirbuffer:WORD, limit:WORD, filespec:WORD
USES cx, dx, di, si, es
mov cx,ds ;
mov es,cx ; es and ds point to same segment
cld ; always count forward
mov ax,[dirbuffer] ; load 'em up
add [limit],ax
mov dx,[filespec] ;
keepsearching:
mov cx,11 ; size of dos filename (8.3)
mov si,dx ;
mov di,ax ;
repe cmpsb ; compare 'em
jz foundit ;
add ax,20h ; size of directory entry
cmp ax,[limit]
jb keepsearching
xor ax,ax

foundit:
ret
FindFile ENDP
END
Multi-function fractal demonstration program which results in 255 byte program

; teeny program displays the Mandelbrot set.
;
; Home Up PgUp
; Left Right correspond to 8 obvious directions
; End Dn PgDn
;

.model TINY
;JUMPS ; without this, see caveat under 8086 above

NONE = 00h ; use this for no features
PRINTZOOM = 01h ; printout and beep features
MODECHANGE = 02h ; support video mode change?
SPEED = 04h ; use 386 instructions for speed
STARTCOORDS = 08h ; use starting coordinates (instead of 0,0)
HIRES = 10h ; use hi resolution (single mode version only)

; choose the desired features from the feature list above, and OR them
; all together as shown below:

FEATURES = PRINTZOOM OR MODECHANGE OR STARTCOORDS OR SPEED OR HIRES

if (FEATURES AND SPEED)
.386
endif

ifdef (FEATURES AND HIRES)
VIDMODE = 12h ; use mode 12h
PIXWIDTH = 640 ; ... which is 640x480
PIXHEIGHT = 480
else
VIDMODE = 13h ; use mode 13h
PIXWIDTH = 320 ; ... which is 320x200
PIXHEIGHT = 200
endif
TEXTMODE = 3 ; our exit video mode (80x25 color text mode)
ZOOMLIMIT = 13 ; can change to up to 13 for extended zoom in

VIDEO_INT = 10h ; BIOS video services interrupt
WRITE_PIXEL = 0Ch ; write pixel video service
WRITE_CHAR = 0eh ; write char in TTY mode video service
CHANGE_MODE = 00h ; change mode video service

KEYBD_INT = 16h ; BIOS keyboard services interrupt

; ASCII codes
EXTENDED = 000h ; no ASCII code for extended key codes
BELL = 007h ; the ASCII bell char to make a beep
CR = 00dh ; a carriage return character
ESCAPE = 01bh ; the escape key
PLUS = 02bh ; ASCII code for '+' key
V_KEY = 'v' ; ASCII code for video mode switch

; keyboard scan codes
MINUS = 04ah ; scan code for gray '-' key

; feel free to experiment with the following constants:

DELTA = 100 ; the unit of pan movement in pixels
THRESHOLD = 4 ; must be in the range of (0,255)
STARTSCALE = 7 ; a number from 0 to ZOOMLIMIT, inclusive
STARTX =-DELTA ; to the right by 1 delta unit (STARTCOORDS feature)
STARTY =-DELTA ; down by 1 delta unit (STARTCOORDS feature)
CHAR_COLOR = 0fh ; white on black background (for PRINTZOOM feature)

.code
org 100h
;****************************************************************************
;
; Here's the main routine, and it's a bit convoluted.
;
;****************************************************************************
Start proc
ife (FEATURES AND MODECHANGE)
mov ax,VIDMODE
int VIDEO_INT
endif
if (FEATURES AND STARTCOORDS)
mov bp,STARTX
mov di,STARTY
else
xor bp,bp ; zero initial X offset
xor di,di ; initial Y offset is identical
endif
if (FEATURES AND MODECHANGE)
mov si,offset VidTbl; point to default video table
jmp @@ChgMode

video STRUC
ScrnMode dw ? ; the mode number for BIOS' purposes
ScrnWidth dw ? ; pixel width of screen minus one
ScrnHeight dw ? ; full height of screen in pixels
NextMode dw ? ; pointer to next video structure
video ENDS

VidTbl video <54h, 800-1, 600, ($ + 2)> ; highest res
video <13h, 320-1, 200, ($ + 2)> ; lowest res
video <12h, 640-1, 480, offset VidTbl> ; next to lowest res

else
jmp @@Render ; leap right in there and draw
endif
@@TryPlus:
cmp al,PLUS ; Q: gray + key?
mov al,[scale] ; get the scale factor in al now
jnz @@TryMinus ; N: maybe it's something else
dec al ; Y: it's plus so zoom out
js @@beep ; if AL<0, balk - can't zoom that far
sar bp,1 ; adjust offsets for new scale so
sar di,1 ; we stay in the same place
jmp @@AdjustScale
@@TryMinus:
cmp ah,MINUS ; Q: gray - key?
jnz @@ReadKey ; N: it's not a valid key
inc al ; Y: zoom in
cmp al,ZOOMLIMIT ; Q: have we zoomed too far?
ja @@beep ; Y: yes, so just beep and don't adjust
sal bp,1 ; adjust offsets for new scale so
sal di,1 ; we stay in the same place

@@AdjustScale:
mov [scale],al ; update the scale value
@@Render:
if (FEATURES AND PRINTZOOM)
mov al,'0'+ZOOMLIMIT; maximum printable character
sub al,[scale] ; invert the sense
call PrintChar ; show the character
mov al,CR ; print a carriage return (no line feed -
call PrintChar ; we don't want to advance to next line)
endif
;****************************************************************************
; Draw
; This routine is the fractal drawing engine. It has been
; optimized for size, sacrificing speed.
;
;****************************************************************************
if (FEATURES AND MODECHANGE)
mov cx,(video ptr [si]).ScrnHeight
push si ; we do this because it's very slow
; if we read the Width from memory
; every inner loop iteration
mov si,(video ptr [si]).ScrnWidth
else
mov cx, PIXHEIGHT ; height of screen in pixels
endif
sub di,cx ; adjust our Y offset
@@CalcRow:
push cx ; save the row pointer on the stack
if (FEATURES AND MODECHANGE)
mov cx,si ; fetch the screen width
else
mov cx, PIXWIDTH-1 ; width of screen in pixels
endif
sub bp,cx ;
@@CalcPixel:
push cx ; save the column counter on stack
xor cx, cx ; clear out color loop counter
xor bx, bx ; zero i coefficient
xor dx, dx ; zero j coefficient
@@CycleColors:
push dx ; save j value for later
mov ax, bx ; ax = i
sub ax, dx ; ax = i - j
add dx, bx ; dx = i + j
stc ; one additional shift, please
call Shifty ; ax = ((i+j)*(i-j)) shifted right
pop dx ; retrieve our saved value for j
add ax,bp ; account for base offset...
cmp ah,THRESHOLD ; Q: is i > THRESHOLD * 256?
xchg bx,ax ; now swap new i with old i
jg @@draw ; Y: draw this pixel
clc ; no additional shifts here, please
call Shifty ; now dx:ax = old i * j
xchg dx,ax ;
add dx,di ; account for base offset...
inc cl ; increment color
jnz @@CycleColors ; keep going until we're done
@@draw:
xchg ax, cx ; mov color into al
pop cx ; retrieve our column counter
pop dx ; fetch row (column already in cx)
push dx ; must leave a copy on the stack
xor bx,bx ; write to video page zero
mov ah,WRITE_PIXEL ; write pixel command
int VIDEO_INT ; video BIOS call
inc bp ; adjust our X base value
loop @@CalcPixel ; keep going until we've done a line
inc di ; adjust our Y base value
pop cx ; keep going until we've done 'em all
loop @@CalcRow ; more rows?

if (FEATURES AND MODECHANGE)
pop si ; restore vid ptr if we use one
endif
@@beep:
if (FEATURES AND PRINTZOOM)
mov al,BELL ;
call PrintChar ;
else
mov ax,((WRITE_CHAR SHL 8) OR BELL) ; make a beep
int VIDEO_INT ; (bx=0 -- any video page, any char attr)
endif
@@ReadKey:
xor ax,ax ; fetch a keystroke
int KEYBD_INT ; keyboard request
cmp al,ESCAPE ; Q: does the user want to exit?
jz @@exit ; Y: do so immediately
if (FEATURES AND MODECHANGE)
cmp al,V_KEY ; request for video mode change?
jnz @@TestExt ; if not, go on
@@ChgMode:
mov si,(video PTR [si]).NextMode ; change pointers
mov ax,(video PTR [si]).ScrnMode ; load new video mode
int VIDEO_INT ; change modes
jmp @@Render ; draw new screen
@@TestExt:
endif
cmp al,EXTENDED ; Q: is it an extended key code?
jnz @@TryPlus ; N: it's not so see if it's '+'
@@ArrowKey:
inc ah ; increment it to make indexing easier
add ah,ah ; multiply by two
mov bl,6 ; fix template (bh is already zero)
and bl,ah ; now bx contains address of delta
if (FEATURES AND MODECHANGE)
push si ; save video ptr if we're using one
endif
mov si,offset Deltas; fetch the delta value
add bp,[bx+si] ; add it to the X offset
shr ah,2 ; now look at the Y value of keystroke
mov bl,6 ; turn it into a table offset
and bl,ah ; do it now
sub di,[bx+si] ; and subtract from Y offset
if (FEATURES AND MODECHANGE)
pop si ; restore video ptr if we're using one
endif
jmp @@Render ; go draw this thing.
@@exit:
mov ax,TEXTMODE ; back to normal now
int VIDEO_INT ; change modes
ret ; and exit via old style
Start endp

Deltas dw +DELTA,0,-DELTA,0 ; handy table for calculating
; changes in X and Y offsets

;****************************************************************************
; Shifty
;
; This routine multiplies AX by DX and shifts the result (in
; DX:AX) to the right by scale bits (or scale+1 bits if CY is
; set). The resulting value is left in AX. DX is destroyed.
;
;****************************************************************************
Shifty proc near
push cx ; save middle bits (i*i - j*j)
db 0b1h ; code for mov cl,immed8
scale db STARTSCALE
adc cl,0 ; adjust per CY flag
imul dx ; do the multiply
if (@Cpu AND 8) ; is is a 386 or better?
xchg ax,dx ;
shl eax,16 ; put hi part in hi 16 bits
xchg ax,dx
shr eax,cl ;
else
@@Rotate:
rcr dx,1 ;
rcr ax,1 ;
loop @@Rotate ; ch is always zero so this is OK
endif
pop cx ;
ret ;
Shifty endp

if (FEATURES AND PRINTZOOM)
;****************************************************************************
; PrintChar
;
; This simple subroutine prints a single character (in AL) to the
; screen using a BIOS call. AH and BX are destroyed.
;
;****************************************************************************
PrintChar proc
mov ah,WRITE_CHAR ; write a character in TTY mode
mov bx,CHAR_COLOR AND 07fh ; use page 0 (bh), non-xor color (bl)
int VIDEO_INT ; do it up
ret
PrintChar endp
endif

end Start

loading....
Click here to load faster!