home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Chestnut's Multimedia Mania
/
MM_MANIA.ISO
/
midi
/
cmtcmu
/
timdif.asm
< prev
next >
Wrap
Assembly Source File
|
1990-06-28
|
14KB
|
417 lines
;version 1 released 6-10-86
title timdif - real time at different than clock rate
debug=-1 ;set to -1 to turn on debugging code
;written by Aaron Wohl
; for Roger Dannerberg
; at The Center for the Arts and technolagy
; Carnegie Mellon University
; 5000 Forbes Ave
; Pittsburgh, PA 15xxx
;
;change log:
; Jun 10 86 avw - release version 1
; Jun 04 86 avw - create from wohl's personal timer.asm
;
;this module provides a 32bit timer that counts at a rate different than
;the ~54ms time provided by the bios. It is currently configured to
;count in 10ms tics.
;
;The idea is to do subtractions and keep a remainder instead of dividing
;the bios and timer chip time to save divide or multiply instructions.
;This is probably only a good idea if the rate you want is near the
;bios rate.
;
;things to do:
; change dodiv to be alot smarter and faster. it currently loops
; subtracting divr from rem, instead subtract 3*divr and see if there
; is a borrow and go from there. this will decrease the maximum divide time.
;************************************************************************
;* *
;* Module interface specifications *
;* *
;************************************************************************
; ibm_time - this routine is the reason this module exists, it returns the
; current time in 10ms tics.
; note:ibm_time() may not be called with interupts disabled
;usage: unsigned long i,ibm_time(); i=ibm_time();
;
; cletime - stop our timer. crash the system if timer not currently running.
;usage: cletime();
;
; settime - zero our timer and start counting. crash the system if our timer
; is already running.
; if debbuging, also zero the value gettic() returns (see gettic)
;usage: settime();
;
; overall usage:
; a) call settime() to start the timer
; b) call ibm_time() as many times as you like to get the time.
; c) call cletime() to stop timing
; d) exit the program, or if you like, goto step a)
;************************************************************************
;* *
;* Module debug interface specifications *
;* *
;************************************************************************
; gettic - return high precision (8253 counter 0) reading from when
; the latest interupt happened. latest meaning the most late, the
; interupt delayed for the longest time. usefull for debugging to see
; if someone is leaving the interups off for too long.
; note:we must be called with debug on for gettic to function, always
; returns zero otherwise
; usage: int i,getic(); i=gettic();
;
; getbtim - return the 32bit bios time (it counts in ~54ms tics).
; usefull for debugging. since the rest of this module runs
; off the same clock, this time (when converted to 10ms ticks)
; should never be more then 6 (10ms) ticks different.
;usage: unsigned long i,getbtim(); i=getbtim();
;
;************************************************************************
;* *
;* Timeing constants, linkages, libraries *
;* *
;************************************************************************
divr equ 3054545 ;divider for 11931.81667 to get 10ms
divlow equ 09bd1h ;low word of divr
divhig equ 0002eh ;high word of divr
include macsym.lib ;control constructs
include prcsym.lib ;procedure data declarators
cmods_ ;set linkage mode to c small model
;************************************************************************
;* *
;* data global to timdif *
;* *
;************************************************************************
;define memory location of timer interupt vector
ivec segment at 0
org 8h*4
timvec label word
ivec ends
dseg timdat
if debug
tictim dw 0 ;remeber when ticks happen
endif
;remainder from previous divisions as a 32 bit number low byte to high byte
;also, used to remember part of current second already used
rem label dword
rem0w label word ;a few names for things since we
rem0b db 0 ; sometimes do byte operations and sometimes
rem1w label word ; do word operations
rem1b db 0
rem2w label word
rem2b db 0
rem3b db 0
now label dword ;current time in our units
now0w dw 0 ;for returning result to user
now2w dw 0
endds
pseg prog
;************************************************************************
;* *
;* dodiv - divide bx(low word) ax(high word) *
;* by tivr *
;* result in cx, remainder in ax,bx
;* *
;* *
;************************************************************************
;do divide
dodiv proc near
mov cx,0 ;initilize result of division
do_
inc cx ;divide happend one more time
sub bx,divlow
sbb ax,divhig
jnc top_ ;loop till we borrow
od_
dec cx ;correct for going once to many times
add bx,divlow ;undo last subtract
adc ax,divhig
ret
dodiv endp
;************************************************************************
;* *
;* Timer routine to piggy back on bios timer interupt *
;* data addressed by cs for interupt routine *
;* *
;************************************************************************
romwd label word ;word address of rom tim
romtim dd ? ;rom timer interupt address
timds dw ? ;data segment for timer routines
;************************************************************************
;* *
;* Macro to read time into ax *
;* This is not a routine to save the subroutine call overhead *
;* *
;************************************************************************
timprt equ 040h ;timer 0 port
timcmd equ (timprt+3) ;timer control port
latcmd equ 000h ;command to latch a time, timer 0
modcmd equ 034h ;set to mode 2 instead of mode 3
;************************************************************************
;* *
;* Routine to return to user, when the latest timer tick happened *
;* *
;************************************************************************
public gettic
prcent gettic
if debug
mov ax,tictim
else
xor ax,ax
endif
prcexi gettic ;return the tic time to lattice c
;************************************************************************
;* *
;* Routine for returning the current bios time *
;* getbtim - return a 32bit time in our bios tics *
;* only used to check our accuracy *
;* *
;************************************************************************
public getbtim
prcent getbtim,,,<,ds>
mov ax,040h ;address of rom data
mov ds,ax
cli
mov bx,ds:[06ch] ;get high and low words of the time
mov ax,ds:[06eh]
sti
prcexi getbtim ;return the time to lattice c
;read a latched time into cx cl=low, cx=high
REDTIM macro
mov al,latcmd ;latch a timer
out timcmd,al ;send command to 8153
in al,timprt ;get low byte of time
mov cl,al ;save it
in al,timprt ;get high byte of the time
mov ch,al
neg cx
endm
;************************************************************************
;* *
;* Routine for returning the current time *
;* ibm_time - return a 32bit time in our units *
;* *
;************************************************************************
public ibm_time
prcent ibm_time
do_
push es ;free up es to point to
mov ax,040h ;address of rom data
mov es,ax
cli
REDTIM ;read timer into ax
sti ;do next instruction, then ints on
mov bx,es:[06ch] ;(interupts off here, see sti def) get time
cli
cmp bx,es:[06ch] ;time change? set z flag if ok
pop es
jnz top_ ;if time changed then counter is wrong
od_
;note: interupts are off when exiting the loop! so that now doesn't
; get bashed on by the timer interupt code while we are updating it
;note: the 8253 timer counts down, so ax has the negative of the part of
; the tick
mov bx,rem0w ;get low word of remainder
mov ax,rem2w ;get high word
add bh,cl
adc al,ch
adc ah,0
call dodiv ;fixup now to be correct
add cx,now0w ;get now plus part of tick
mov ax,0
adc ax,now2w
sti ;done, allow interupts now
mov bx,cx ;put low bits where lattice c wants them
prcexi ibm_time ;return bx,ax (current time)
;************************************************************************
;* *
;* Routine for stopping our timer *
;* cletime - stop timer remove patch into bios timer *
;* *
;************************************************************************
;clear the timer interupt routine
public cletime
prcent cletime,,,<,ds>
assume ds:ivec ;address current vectors
mov ax,ivec
mov ds,ax
cli
mov ax,romwd
mov timvec,ax ;restore original interupt vector
mov ax,romwd[2]
mov timvec[2],ax
sti
assume ds:dgroup
prcexi cletime
;************************************************************************
;* *
;* Routine for starting our timer *
;* settime - zero now (time starts from zero), also patch into *
;* bios timer interupt so we can call timint on each *
;* timer tick *
;* *
;************************************************************************
public settime
prcent settime,,,<,ds>
xor ax,ax ;get a zero
if debug
mov tictim,ax ;clear latest tick time
endif
mov now0w,ax ;clear now
mov now2w,ax
mov rem0w,ax ;clear remainder
mov rem2w,ax
;change the timer to mode 2 (rate generator ) so we can see what part of the
;current tick we are in. the rom sets it to mode 3 (square wave). mode 3
;counts by two then twidiles the counter output line. thus if read the
;timer you can't tell which half of the tick you are in. mode 2 counts
;by one then gives a one clock pulse tick, which is just fine with
;the 8259 interupt controller chip.
mov al,034h ;set timer mode
cli ;lets not mess with the time interupt routine
out timcmd,al
xor al,al ;something to send to timer for time
out timprt,al ;after setting mode need to send a time
out timprt,al ;to restart the timer
sti
mov ax,ds ;save stack segment
mov timds,ax
assume ds:ivec ;address current vectors
mov ax,ivec
mov ds,ax
mov ax,timvec ;save original interupt vector
mov romwd,ax
mov ax,timvec[2]
mov romwd[2],ax
mov ax,cs ;get new code segment
mov bx,offset timint ;code routine
cli
mov timvec,bx ;set new timer offset
mov timvec[2],ax ;set new timer segment
sti
assume ds:dgroup
prcexi settime
;************************************************************************
;* *
;* More timer routine to piggy back on bios timer interupt *
;* This page has the code that gets called by the hardware *
;* Instead of the bios code *
;* It saves AX,BX,CX,DS then falls into the next page of code *
;* on the users stack. *
;* *
;************************************************************************
;new timer interupt
public timint;for debugging only
timint proc far
assume ds:nothing,es:nothing,ss:nothing ;we know nothing, nothing
;note: it is safe to use 5 stack levels in a timer routine since the
; bios interupt we replace does. (save 4 regs, allowing one stack
; level left for the call to dodiv)
push ax
push bx
push cx
push ds
mov ax,timds ;set new ss and sp
mov ds,ax ;set ds for user routine
assume ds:dgroup,ss:dgroup
;************************************************************************
;* *
;* More timer routine to piggy back on bios timer interupt *
;* We take care of keeping our time up to date *
;* *
;* Debugging code, remember what part of a tick interupts happen *
;* *
;************************************************************************
if debug
REDTIM ;see when it is
cmp tictim,cx ;later than before?
ifskp_ nc ;remember time if yes
mov tictim,cx ;remember it
endif_
endif
;************************************************************************
;* *
;* More timer routine to piggy back on bios timer interupt *
;* We take care of keeping our time up to date *
;* *
;************************************************************************
;get number to divide
mov bx,rem0w ;get low word of remainder
mov ax,rem2w ;get high word
inc ah ;one more tick has passed
call dodiv ;update now accordingly
;put back current remainder
mov rem0w,bx
mov rem2w,ax
;add result into now
add now0w,cx ;move the time forward
ifskp_ nc ;carry out of low word?
inc now2w ;had a carry, propagate it
endif_
;************************************************************************
;* *
;* NOTE: execution runs into this page from above (save call/ret) *
;* More timer routine to piggy back on bios timer interupt *
;* This page restores AX,BX,CX,DS,SS,SP then jumps to the normal *
;* bios code. *
;* *
;************************************************************************
assume ds:nothing,ss:nothing
pop ds
pop cx
pop bx
pop ax
jmp romtim
timint endp
endps
end