Category : Assembly Language Source Code
Archive   : CLOK3.ZIP
Filename : CLOK3.ASM

 
Output of file : CLOK3.ASM contained in archive : CLOK3.ZIP
; RESIDENT TIME CLOCK DISPLAY with optional chime
;
; Original author unidentified
;
; Revised by Thomas A. Lundin
; Graphics Unlimited Inc.
; 3000 Second St. No.
; Minneapolis, MN 55411
; (612) 588-7571
;
; usage: clok [/c /d]
; /c to toggle chiming. No chimes by default.
; /d to force the date to be read from system
;
; Clock display can be toggled on and off by repeating 'clok'.
;
; Chimes should be toggled off when using heavy interrupt-driven
; software such as communications to avoid losing characters or
; hanging the system.
;
; 9/4/87 note:
; This version uses the clock tick to regulate the duration of the
; chimes, meaning that the chimes should be the same length from
; one system to another, no matter what the CPU speed.
; Also modified start-up routines to automatically set the time
; display background to color or monochrome.
;
; 9/21/87 note:
; This version alterates a date display with the time display, every
; two seconds. The date display is static, i.e., it is not updated
; at midnight. You must type clok/d to update the date.
;

TICKS EQU 36 ; number of ticks between updates (2 sec)
BEEPS EQU 6 ; duration of beeps in clock ticks
TONE1 EQU 7f1h ; first chime tone
TONE2 EQU 54ch ; second chime tone
TONE3 EQU 3f7h ; third chime tone

interrupts segment at 0h
org 1ch*4 ; This is to use INT 1Ch
timer_int label dword ; which is the timer interupt
interrupts ends

screen segment at 0b000h ; A dummy segment to use
screen ends ; as the Extra Segment

code_seg segment
assume cs:code_seg
org 100h ; org = 100 to make this into
; a .COM file
first: jmp load_clock

old_time_int dd ? ; The address INT 1Ch normally uses
count500 dw TICKS ; Used to update clock every nnn counts
beepticks dw 0 ; number of ticks for a BEEP
beepsleft db 0 ; number of beeps to output
cursor dw 0 ; Location of the cursor on the screen
beept db 0 ; have-we-beeped flag
inbeep db 0 ; beep-in-progress flag
flash db 1 ; flashing colon flag
spkrstat db 0 ; old speaker status
video_port dw ? ; Video status port - check for scanning

hh dw 0 ; hours
mm dw 0 ; minutes
sc dw 0 ; seconds
hhdiv dw 32771 ; hours divisor (65543/2)
mmdiv dw 546 ; minutes divisor (1092/2)
ssdiv dw 9 ; second divisor (18/2)

display dw (7020h) ; leading space
dw 5 dup(703ah) ; Initial value for the clock
dw 2 dup(7020h) ; Add 2 ' 's for am/pm.

month dw 0 ; month
day dw 0 ; day
chimon dw 0 ; flag for chime in use or not
clokon dw 1 ; flag for clok in use or not

clock proc near ; The timer INT will now come here

cmp cs:clokon,1 ; is this interrupt silent ?
jz newint ; no, go execute it
jmp dword ptr old_time_int ; silent, just execute old int
newint:
pushf ; First call old time interrupt to update count
call dword ptr old_time_int

call needbeep ; need to continue beep ?

push ax ; Save the registers - good form
push cx
push di
push si
push es

dec cs:count500 ; should recalculate the time ?
jnz dont_recalculate
xor cs:flash,1 ; toggle the flashing colon
call calc ; Recalculate the time
mov cs:count500,TICKS ; Reset Count500

dont_recalculate:
assume es:screen ; Set up screen as the Extra Segment
mov cx,screen
mov es,cx
mov dx,video_port ; This is the screen status port
mov di,cursor ; Set up cursor on screen as destination
lea si,display ; Set up the display in memory as source
mov cx,16 ; To move char and attributes

scan_low: ; Start waiting for a new horizontal scan
in al,dx ; i.e. the the vidio controller scan
test al,1 ; status is low.
jnz scan_low

mov ah,cs:[si] ; Move byte to be written into AH

scan_high: ; After port has gone low, it must go high
in al,dx ; before it is safe to write directly
test al,1 ; to the screen buffer in memory
jz scan_high

mov es:[di],ah ; Move to screen one byte at a time.
inc di ; Position to attribute byte
inc si ; on screen.

loop scan_low ; Go back foe next byte

pop es ; Here are required pops to exit
pop si
pop di
pop cx
pop ax

;;dont_recalculate:
iret ; An interrupt needs an IRET

clock endp

calc proc near ; Here we recalculate the time and store it
push ax ; Puushes to save everytheing that
push bx ; gets destroyed
push cx
push dx

cmp cs:flash,1 ; do date or time?
jz dtime ; TIME
; DATE
lea bx,display ; Set up BX as pointer to display in memory
mov byte ptr cs:[bx+12],' ' ; move space into display

mov ax,cs:month
mov cs:[bx+2],ah ; Move first month digit into display
mov cs:[bx+4],al ; Then the second digit
mov byte ptr cs:[bx+6],'-' ; a hyphen
mov ax,cs:day ; get day
mov cs:[bx+8],ah ; and move them into the display in memory
mov cs:[bx+10],al
jmp restore

dtime:
; note: Peter Norton p.223 explains that the time formula is more precisely
; shown as:
; hh = clkcount / 65543
; mm = hh.remainder / 1092
; ss = mm.remainder / 18
;
; trouble is, the 65543 value won't work as a single-word divisor,
; so our trick is to divide the clock count and divisor values in half,
; which should have no appreciable affect on the accuracy of the time.

xor ax,ax ; Set up for clock read.
INT 1Ah ; Read the clock.
mov bx,dx ; Save low(minutes) portion.
mov dx,cx ; Move high(hours) portion to AX.
mov ax,bx ; dx:ax = clock count

clc
rcr dx,1 ; div count by 2 so we can use a
rcr ax,1 ; single precision dividend

div cs:hhdiv ; compute hours
mov cs:hh,ax ; save it
mov ax,dx ; prepare remainder for minutes
xor dx,dx
div cs:mmdiv ; compute minutes

cmp ax,60 ; 60 minutes shows up sometimes
jl mm_ok ; mostly it doesn't
xor ax,ax ; but if it does, zero out the minutes
inc cs:hh ; and bump up the hour

mm_ok: mov cs:mm,ax ; save it
; mov ax,dx ; prepare remainder for seconds
; xor dx,dx
; div cs:ssdiv ; compute seconds
; mov cs:sc,ax ; save it

lea bx,display ; Set up BX as pointer to display in memory

mov ax,cs:hh
cmp ax,12 ; is it am or pm?
jl am ; am
pm: mov byte ptr cs:[bx+12],'p' ; Otherwise move 'P' into the display.
sub ax,12 ; pm, subtract 12
jmp chek12 ; Continue.

am: mov byte ptr cs:[bx+12],'a' ; Move an 'A' into the display.
chek12: or ax,ax ; Make zero hour...
jnz am_pm_done
mov ax,12 ; ...a twelve
am_pm_done:
aam ; Convert AX to BCD - a nice command
add ax,3030h ; Add '0' to both bytes in AX to make ASCII
cmp ah,'0' ; Is the 1st digit '0'?
jne dont_edit ; Then don't blank the character.
mov ah,' ' ; Otherwise, put a space in AH.
dont_edit:
mov cs:[bx+2],ah ; Move first hours digit into display
mov cs:[bx+4],al ; Then the second digit
;----------------------------------
mov byte ptr cs:[bx+6],':' ; in which case use a colon
mov ax,cs:mm ; get minutes
aam ; Again convert AX to Binary Coded Decimal
add ax,3030h ; Add to make two ASCII characters
mov cs:[bx+8],ah ; and move them into the display in memory
mov cs:[bx+10],al

;---------routine for alarm chime goes here------------------------------------
cmp cs:chimon,0 ; chimes off?
jz restore ; yes, don't beep
cmp cs:inbeep,1 ; already in a beep loop?
jz restore ; yes, don't be redundant

cmp ax,3030h ; on the hour
jz alarm3
cmp ax,3135h ; on the 1/4 hour
jz alarm1
cmp ax,3330h ; on the 1/2 hour
jz alarm2
cmp ax,3435h ; on the 3/4 hour
jz alarm1
mov cs:beept,0 ; we have not beeped
;------------------------------------------------------------------------------
restore: ; Restore registers
pop dx
pop cx
imret2: pop bx
imret1: pop ax

imret: ret
;-----------------------------------------------------------------------------
needbeep:
cmp cs:inbeep,1 ; are we beeping right now ?
jnz imret ; no, immediate return
dec cs:beepticks ; yes, done beeping?
jnz imret ; no, immediate return
push ax
mov al,cs:spkrstat ; yes, shut off speaker
out 61h,al
dec cs:beepsleft ; any more beeps waiting?
jz nobeeps ; no, go home
push bx
cmp cs:beepsleft,1 ; how many await?
jz one_left ; one
mov bx,TONE2 ; two
call tone ; start it beeping
jmp imret2 ; go home
one_left:
mov bx,TONE3
call tone ; start it beeping
jmp imret2 ; go home
nobeeps:
mov cs:beept,1 ; we have beeped
mov cs:inbeep,0 ; and we're not in one any more
jmp imret1
;------------------------------------------------------------------------------
alarm3: mov bx,TONE1 ; send tone 1
mov cs:beepsleft,3
call tone
jmp restore
alarm2: mov bx,TONE2 ; send tone 2
mov cs:beepsleft,2
call tone
jmp restore
alarm1: mov bx,TONE3 ; send tone 3
mov cs:beepsleft,1
call tone
jmp restore ; join common
;---------------------------------------
tone:
cmp cs:beept,1 ; do nothing if chime has been beeped
jz notone ; earlier in this clock update
mov cs:beepticks,BEEPS ; this long on beeps
MOV AL,0B6H ; else condition the timer
OUT 43H,AL
MOV AX,BX ; this is the freq
OUT 42H,AL
MOV AL,AH
OUT 42H,AL ; out you all go
IN AL,61H ; read spkr port
MOV cs:spkrstat,AL
OR AL,3
OUT 61H,AL ; send a beep
mov cs:inbeep,1
notone: ret
;------------------------------------------------------------------------------
calc endp


load_clock proc near ; This procedure initializes everything
assume ds:interrupts ; The Data Segment will be the interrupt area
mov ax,interrupts
mov ds,ax

MOV SI,0081H ; addr of command line arguments
NEXT: MOV AL,CS:[SI] ; get command line char
CMP AL,0DH ; Return ends it.
JZ again
CMP AL,'/' ; switch char
JZ getswitch ; see what it is
next1: INC SI ; else point to next char
JMP NEXT ; and loop
getswitch:
inc si
mov al,cs:[si]
cmp al,'c' ; chime toggle switch
jz sw_c
jmp next1 ; wrong switch

sw_c:
mov cs:togchim,1 ; toggle them chimes
jmp next1 ; get next switch if there is one

again: mov ax,cs:sig_vector ; get signature vector
cmp ax,5fh ; if less than 0x60
jg vok
jmp noload ; forget it
vok: add ax,3500h
int 21h
mov ax,es
cmp ax,434ch ; are we already loaded ?
jnz nosig ; no
cmp bx,4f4bh
jnz nosig ; and no
mov bx,word ptr timer_int ; yes
mov es,word ptr timer_int+2
call gdate ; get the system date
cmp cs:togchim,1
jnz no1 ; no toggle chimes
call toglchim ; go toggle chimes
jmp exit

no1:
mov ax,es:[bx-2]
xor ax,1 ; toggle activation mode
mov word ptr es:[bx-2],ax
exit: mov ax,4c00h ; return to DOS
int 21h

;---------------------------------------
toglchim:
mov ax,es:[bx-4] ; get the chime flag
xor ax,1 ; toggle it
mov word ptr es:[bx-4],ax
push ds
mov di,cs
mov ds,di
cmp ax,1 ; beep if it's been turned on
jz beepmsg
mov dx,offset chimoffmsg ; chimes off
jmp print
beepmsg: mov dx,offset chimonmsg ; chimes on
print: mov ah,9
int 21h
pop ds
ret
;---------------------------------------
nosig: mov ax,es ; no current signature...
or ax,bx ; ...but is it safe to load one?
jz setsig ; yes
mov ax,cs:sig_vector ; no, try another slot
dec ax
mov cs:sig_vector,ax
jmp again
;---------------------------------------
gdate:
push bx
mov ah,2ah ; call DOS GetDate command
int 21h
pop bx
mov al,dh ; month
xor ah,ah
aam ; Convert AX to BCD - a nice command
add ax,3030h ; Add '0' to both bytes in AX to make ASCII
cmp ah,'0' ; Is the 1st digit '0'?
jne gd1 ; Then don't blank the character.
mov ah,' ' ; Otherwise, put a space in AH.
gd1: mov word ptr es:[bx-8],ax
mov al,dl ; day
xor ah,ah
aam ; Convert AX to BCD - a nice command
add ax,3030h ; Add '0' to both bytes in AX to make ASCII
mov word ptr es:[bx-6],ax
ret ; go home
;---------------------------------------
noload label near
mov ax,4c01h ; abort with error
int 21h

setsig:
cli
push ds
mov ax,cs:sig_vector
add ax,2500h ; signature reads:
mov dx,434ch ; 'CL'
mov ds,dx
mov dx,4f4bh ; 'OK'
int 21h
pop ds

mov ax,word ptr timer_int ; Get the old interrupt service routine
mov word ptr old_time_int,ax ; address and put it into our location
mov ax,word ptr timer_int+2 ; OLD_TIME_INT so we can still call it
mov word ptr old_time_int+2,ax

mov word ptr timer_int,offset clock ; Now load the address of our clock
mov word ptr timer_int+2,cs ; routine into TIMER_INT so the timer
; interrupt will call CLOCK
sti

mov ah,15 ; Ask for service 15 of INT 10H
int 10h ; This tells us how the display is set up
sub ah,8 ; Move to eight places before edge
shl ah,1 ; Mult by two (char and attribute bytes)
mov byte ptr cursor,ah ; Move cursor to it's memory location
mov video_port,03bah ; Assume this is a monochrome display
test al,4 ; Is it?
jnz get_time ; Yes - jump out
add cursor,8000h ; No - set up for graphics display
mov video_port,03dah
mov cx,8
mov ax,4f20h
lea di,display
color: mov cs:[di],ax
inc di
inc di
loop color

get_time:
mov bx,offset clock ; yes ; get addr of clok
mov ax,cs
mov es,ax
cmp cs:togchim,1 ; need to toggle ?
jnz noct ; no
call toglchim
noct: call gdate

mov di,cs
mov ds,di
mov dx,offset hello ; chimes on
mov ah,9
int 21h
call calc ; This is to avoid showing 00:00 for first 500 counts
mov dx,offset load_clock ; Set up for everything but LOAD_CLOCK
int 27h ; to stay attached to DOS

sig_vector dw 67h ; signature vector
togchim db 0 ; to toggle chimes
chimonmsg db 'Chime ON',0dh,0ah,'$'
chimoffmsg db 'Chime OFF',0dh,0ah,'$'
hello db 'usage: clok [/c] (/c: toggle chimes)',0dh,0ah
db 'clok by itself toggles display',0dh,0ah
db 'CLOK INSTALLED',0dh,0ah,'$'

load_clock endp

code_seg ends

end first ; END FIRST so 8088 will go to FIRST first


  3 Responses to “Category : Assembly Language Source Code
Archive   : CLOK3.ZIP
Filename : CLOK3.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/