home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
OS/2 Shareware BBS: 10 Tools
/
10-Tools.zip
/
ddkx86v5.zip
/
DDKX86
/
SRC
/
DEV
/
CLOCK
/
CLOCKDD.ASM
< prev
next >
Wrap
Assembly Source File
|
1995-04-14
|
38KB
|
1,131 lines
;*DDK*************************************************************************/
;
; COPYRIGHT (C) Microsoft Corporation, 1989
; COPYRIGHT (C) Microsoft Corporation, 1989
; COPYRIGHT Copyright (C) 1995 IBM Corporation
;
; The following IBM OS/2 WARP source code is provided to you solely for
; the purpose of assisting you in your development of OS/2 WARP device
; drivers. You may use this code in accordance with the IBM License
; Agreement provided in the IBM Device Driver Source Kit for OS/2. This
; Copyright statement may not be removed.;
;*****************************************************************************/
; SCCSID = @(#)clockdd.asm 6.7 91/09/25
title clock device driver -- main [clockdd.asm]
; ****************************************************************************
; * *
; * *
; * *
; ****************************************************************************
PAGE 60,132
;
;********************** START OF SPECIFICATIONS *********************
;*
;* SOURCE FILE NAME: CLOCKDD.ASM
;*
;* DESCRIPTIVE NAME: CP/DOS 1.1 CLOCK DEVICE DRVIER
;*
;*
;*
;*
;* STATUS: RELEASE 1 LEVEL 1
;*
;* FUNCTION: CLOCK$ is the device driver for the RT/CMOS clock.
;*
;* NOTES:
;* DEPENDENCIES:
;* RESTRICTIONS:
;* PATCH LABEL:
;*
;* ENTRY POINTS: RTENTR
;*
;* EXTERNAL REFERENCES:
;* ROUTINES:
;* DIRECT: DevHlps: dh_GetDOSVar, dh_EOI, dh_SchedClock,
;* dh_SetIRQ, dh_PhysToVirt, dh_UnPhysToVirt
;* (NOT AT MODEL Only: dh_GetLIDEntry, dh_ABIOSCall)
;*
;* DATA AREAS:
;* MODIFIED: Global Information Segment (SysInfoSeg)
;*
;* CONTROL BLOCKS:
;* MODIFIED: Device Driver Request Block
;*
;* TABLES: none ; sparse function table, used case structure instead
;*
;*********************** END OF SPECIFICATIONS **********************
.xlist
INCLUDE mvdm.inc ; equates and data for MVDM support
purge PANIC ; prevent conflict with osmaca.inc
INCLUDE osmaca.inc
INCLUDE devhlp.inc ; the devhlp function eqs
INCLUDE infoseg.inc ; definitions of Global Info Segment
INCLUDE devsym.inc ; definition of DD Request Packet
INCLUDE clkdata.inc
INCLUDE abios.inc
INCLUDE vcmospdd.inc ; vcmos/clk shared data and equates
INCLUDE clkseg.inc ; segment definitions
INCLUDE pvwxport.inc
INCLUDE cmos.inc
INCLUDE ioctl.inc
INCLUDE vtdptd.inc
.list
;;MONITOR EQU 1 ; creates counters for monitoring
extrn RTWRIT:Near
extrn RTCINT:Near
extrn FIXISEG:Near
extrn RTINIT:far
extrn RTINIT2:far
extrn endswapcode:byte
EXTRNFAR ClkReadCMOS
; publics
PUBLIC DevHlp
PUBLIC SchedClock
PUBLIC InfSeg
PUBLIC MonTab
PUBLIC Update_Flag ; Update Interrupt Flag
PUBLIC Post_Time ; Time to call Post EOI SC
PUBLIC Int_Nested ; Number of nested Ints
PUBLIC Int_In_Progress ; Flag for presently nested
ifdef profile
PUBLIC DivDown
endif
PUBLIC ReqRTCFreq
PUBLIC CurRTCFreq
PUBLIC Hundred_Whole
PUBLIC Hundred_Frac
PUBLIC Hundred_Inc
PUBLIC MS_Fraction
PUBLIC MS_Inc_Whole
PUBLIC MS_Inc_Frac
PUBLIC MS_Delta
PUBLIC Hz128To32
PUBLIC Accum8msTicks
PUBLIC ExpectedMsCount
ifdef MONITOR
PUBLIC LagCount
PUBLIC LagTotal
ACCM8SIZE EQU 64
PUBLIC Accm
PUBLIC Accm8
PUBLIC Accm8p
PUBLIC Accm8mod4
PUBLIC Ticks8
PUBLIC Ticks32
endif
PUBLIC InSchedClk
PUBLIC TicksMissed
PUBLIC CMOS_location
PUBLIC saveDS
PUBLIC ATDataEnd
PUBLIC pqwTmrRollover
PUBLIC qwTmrRollover
PUBLIC pqwTmr
PUBLIC qwTmr
BREAK <Clock Device Driver DATA SEGMENT Declaration>
ClkData SEGMENT
START$ LABEL BYTE
dd -1
DW DEV_CHAR_DEV OR DEVLEV_3 OR DEV_CLOCK
DW offset ClkCode:ClkStrat
DW 0
DB 'CLOCK$ '
DW 4 DUP (?) ; Prot & Real mode CS & DS (filled by sysinit)
DD DEV_16MB ; device can handle > 16MB physical memory
DevHlp DD 0 ; Pointer to DOS "helper" functions
SchedClock DD 0 ; Pointer to SchedClock address pointer
InfSeg DD 0 ; Pointer to InfoSeg Address
PUBLIC szClkName,szTmrName
szClkName db CLK_NAME,0 ;CLOCK registered name
szTmrName db PTD_NAME,0 ;TIMER registered name
PUBLIC fpfnVTProc,fsPTFlags
fpfnVTProc df 0 ;vtimer entry point
fsPTFlags dw PTF_OWNT0+PTF_OWNT2;ptimer owns T0/T2 initially
MonTab DB 31 ; Days of Month Table - January
DB 28 ; - February
DB 31 ; - March
DB 30 ; - April
DB 31 ; - May
DB 30 ; - June
DB 31 ; - July
DB 31 ; - August
DB 30 ; - September
DB 31 ; - October
DB 30 ; - November
DB 31 ; - December
; The following hold the whole and fractional portions of the time in
; milliseconds that is advanced every clock tick. Since we allow the
; clock to run at either 32hz or 128hz, the increment values will be
; either 31.25ms or 7.8125ms.
ReqRTCFreq DB 0 ; Requested new RTC frequency (0 = No change)
CurRTCFreq DB 0 ; Current RTC frequency (will be initialized)
Hundred_Whole DB 0 ; Whole portion of hundreds count
Hundred_Frac DB 0 ; Fractional portion of hundreds count
Hundred_Inc DW ? ; Value to increment hundreds each tick
MS_Fraction DW 0 ; Fractional portion of milliseconds count
MS_Inc_Whole DD ? ; Whole value to increment milliseconds each tick
MS_Inc_Frac DW ? ; Fract value to increment milliseconds each tick
MS_Delta DW 0 ; Number of milliseconds since last tick
; When the frequency is switched from 128hz to 32hz, special adjustments
; must be made to keep time advancing at the correct rate. The following
; help enable those special adjustments.
Hz128To32 DB 0 ; Flag: 1 if RTC reset to 32hz since last tick
Accum8msTicks DW 0 ; Number of accumulated 8ms ticks
ExpectedMsCount DD 0 ; Millisecond count we expect 1 second from now
ifdef MONITOR
LagCount DD 0 ; how many times ms lagged.
LagTotal DD 0 ; Total lag time
ACCM8SIZE EQU 64
Accm DW -1
Accm8 DW ACCM8SIZE DUP(0)
DW -1
Accm8p DW 0
DW -1
Accm8mod4 DW 0,0,0,0
DW -1
Ticks8 DD 0
DD -1
Ticks32 DD 0
DW -1
endif
Update_Flag DB 00 ; Update Interrupt flag
; Extra Vars for Nested Int fix
Post_TIme dw 0
Int_Nested db 0
Int_In_Progress db 0
InSchedClk DB 0 ; flag to indicate entering SchedClock
TicksMissed DW 0 ; count of ticks missed in SchedClock
CMOS_location db 0 ; location of CMOS TABLE ADDR
EVEN
pqwTmrRollover dd 0 ;(16:16) ptr to PIT Ctr 0 rollover
; count in kernel address space.
qwTmrRollover qw_s <0,0> ;PIT Ctr 0 rollover count in Clock
; driver address space, where:
; qw_Lo = current rollover count.
; qw_Hi = next rollover count.
pqwTmr dd 0
qwTmr qw_s <0,0>
codelockhandle db sizeof_lockhandle_s dup(0)
; handle returned by DevHlp_VmLock
READREQ cmos_req
ATDataEnd EQU $ ; Used by Sysinit to delete remaining
; data segment.
Time_Check db 0A0h ; Used for validation
db 0A6h
db 0AAh
ClkData ENDS
BREAK <Clock Device Driver Strategy Routine>
;********************** START OF SPECIFICATIONS *********************
;*
;* MODULE NAME: RTENTR
;*
;* DESCRIPTIVE NAME: Strategy routine for Clock Device Driver
;*
;* FUNCTION: This routine is the task-time entry point to the Clock
;* Device driver. Requested functions are dispatched to
;* worker routines.
;* NOTES:
;* RTENTR provides eight functions: RTREAD(5), STREDY(5), STCOMP(6,7)
;* RTWRIT(8,9), RTINIT(27), RTINIT2(0) and BADCMD (all the rest).
;* Since a command table would be sparse (only 8 valid entries of
;* 28 options), a case control structure is used. Functions 6,7
;* and functions 8,9
;* have the same effect.
;*
;* Equivalent Command dispatch table (Highest legal function is 27):
;*
;* ClkSwap:RTINIT2 ; 0 Initialize (2nd stage, special for clock)
;* ClkSwap:BADCMD ; 1 Media Check these are unsupported
;* ClkSwap:BADCMD ; 2 Build BPB functions.
;* ClkSwap:BADCMD ; 3 IOCTL input
;* ClkSwap:RTREAD ; 4 Input (Read)
;* ClkSwap:STREDY ; 5 Non-destructive read, no wait
;* ClkSwap:STCOMP ; 6 Input status
;* ClkSwap:STCOMP ; 7 Input flush
;* ClkSwap:RTWRIT ; 8 Output (Write)
;* ClkSwap:RTWRIT ; 9 Output with verify
;* ClkSwap:BADCMD ; 10 BADCMD
;* ClkSwap:BADCMD ; 11 BADCMD
;* ClkSwap:BADCMD ; 12 BADCMD
;* ClkSwap:BADCMD ; 13 BADCMD
;* ClkSwap:BADCMD ; 14 BADCMD
;* ClkSwap:BADCMD ; 15 BADCMD
;* ClkSwap:RTIOCT ; 16 Generic IOCTL
;* ClkSwap:BADCMD ; 17 BADCMD
;* ClkSwap:BADCMD ; 18 BADCMD
;* ClkSwap:BADCMD ; 19 BADCMD
;* ClkSwap:BADCMD ; 20 BADCMD
;* ClkSwap:BADCMD ; 21 BADCMD
;* ClkSwap:BADCMD ; 22 BADCMD
;* ClkSwap:BADCMD ; 23 BADCMD
;* ClkSwap:BADCMD ; 24 BADCMD
;* ClkSwap:BADCMD ; 25 BADCMD
;* ClkSwap:BADCMD ; 26 BADCMD
;* ClkCode:RTINIT ; 27 Initialize
;* ClkSwap:BADCMD ; 28 BADCMD here at table end
;*
;* ENTRY POINT: RTENTR
;* LINKAGE: FAR
;*
;* USES: EAX, EBX, ECX, DL, EDI, ESI
;*
;* INPUT:
;* ES:BX = Address of Device Driver Request Packet
;* DS = Points to Clock Device Driver Data Segment
;*
;* WARNING: Parameter checking on input data to RTWRIT through
;* this routine must be performed by the caller!
;*
;* OUTPUT:
;* Device Driver Request Packet filled in (Status word set,
;* date/time fields, etc).
;*
;* EXIT-NORMAL:
;* Exit-Normal is via common routines STCOMP or STREDY
;* Status word set to 'BUSY' and/or 'DONE'
;*
;* EXIT-ERROR:
;* Exit-Error is via common routine BADCMD, but only if
;* invalid command is passed in Driver Request Packet.
;*
;* INTERNAL REFERENCES:
;* ROUTINES: RTREAD, RTWRIT, RTINIT, STCOMP, STREDY, BADCMD,
;* RTIOCT
;*
;* EXTERNAL REFERENCES:
;* STRUCTURES: Global Information Segment (SysInfoSeg)
;* ROUTINES: none
;*
;*********************** END OF SPECIFICATIONS **********************
page
;********************** START OF PSEUDO-CODE **********************
;
; switch( packet_command ) {
;
; 0; call RTINIT2 to grab IRQ0
; break;
;
; 4: call RTREAD to read realtime clock
; break;
;
; 5: call STREDY to do non-destructive read with no-wait
; break;
;
; 6:
; 7: call STCOMP to set status "complete" exit
; break;
;
; 8:
; 9: call RTWRIT to update the realtime clock
; break;
;
; 16: call RTIOCT to process the IOCTL request
; break;
;
; 27: call RTINIT to initialize data structures & realtime clock device
; break;
;
; default:
; call BADCMD to express that this function is unsupported
; break;
; }
;
; mark packet_status operation complete
; return
;
;*********************** END OF PSEUDO-CODE **********************
ClkSwap SEGMENT
public startswapcode
startswapcode label byte
ASSUME CS:ClkSwap,DS:ClkData,ES:NOTHING,SS:NOTHING
RTENTR PROC FAR
public RTENTR
push es
push bx
mov al,es:[bx].PktCmd ; Get device command
xor ah,ah
RTREAD?:
cmp ax,4 ; Is this RTREAD?
jl RTINIT2? ; .. No, might be RTINIT2
jg STREDY? ; .. No, try next
call LOCKSWAP ; .. Yes, try locking swappable code
jc OUTOFMEM ; .... lock failed, error out
call RTREAD ; .....lock succeeded, dispatch worker
call UNLOCKSWAP
jmp ENDCASE
STREDY?:
cmp ax,5 ; Is this STREDY?
jg STCOMP? ; .. No, try next
mov ax,(STDON+STBUI) ; .. Yes, just return flags
jmp ENDCASE
STCOMP?:
cmp ax,7 ; Is this STCOMP?
jg RTWRIT? ; .. No, try next
mov ax,STDON ; .. Yes, just return flags
jmp ENDCASE
RTWRIT?:
cmp ax,9 ; Is this RTWRIT?
jg RTIOCT? ; .. No, try next
call LOCKSWAP ; .. Yes, try locking swappable code
jc OUTOFMEM ; .... lock failed, error out
call RTWRIT ; .....lock succeeded, dispatch worker
call UNLOCKSWAP
jmp ENDCASE
RTIOCT?:
cmp ax,16 ; Is this RTIOC?
jg RTINIT? ; .. No, try next
call LOCKSWAP ; .. Yes, try locking swappable code
jc OUTOFMEM ; .... lock failed, error out
call RTIOCTL ; .....lock succeeded, dispatch worker
call UNLOCKSWAP
jmp ENDCASE
RTINIT?:
cmp ax,27 ; Is this RTINIT?
jne BADCMD ; .. No, must be a command
call RTINIT ; .. Yes, dispatch worker
jmp ENDCASE
RTINIT2?:
cmp ax,0 ; Is this RTINIT2?
jne BADCMD ; .. No, must be command
call RTINIT2 ; .. Yes, dispatch worker
jmp ENDCASE
BADCMD:
mov ax, STDON+STERR+ERRCMD ; Done + Error + command
jmp ENDCASE
OUTOFMEM:
mov ax, STDON+STERR+ERRGFAIL
; jmp ENDCASE
ENDCASE:
pop bx
pop es
mov word ptr es:[bx].PktStatus,ax ; Mark operation complete
ret
RTENTR ENDP
;********************** START OF SPECIFICATIONS *********************
;*
;* MODULE NAME: LOCKSWAP
;*
;* DESCRIPTIVE NAME: Lock Swappable Code routine
;*
;* FUNCTION: Lock the swappable code segment portion of the
;* clock device driver.
;*
;* ENTRY POINT: LOCKSWAP
;* LINKAGE: NEAR from RTENTR
;*
;* NOTE: See file ?\dos\memory\VMMISC.ASM for masm interface to
;* _DevHlp_VMLock.
;*
;* INPUT: none
;*
;* USES: EAX, ECX, DL, EDI, ESI
;*
;* EXIT-NORMAL:
;* CF = 0; [codelockhandle] saved
;*
;* EXIT-ERROR:
;* CF = 1
;*
;* INTERNAL REFERENCES:
;* STRUCTURES: ClkData:[codelockhandle]
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: DevHlp_VirtToLin, DevHlp_VMLock
;*
;*********************** END OF SPECIFICATIONS **********************
ASSUME CS:ClkSwap,DS:ClkData,ES:NOTHING,SS:NOTHING
LOCKSWAP PROC NEAR
public LOCKSWAP
.386p
push ebx ; others rely on bx,es
; do a virttolin DevHlp (linear address)
mov ax,cs
lea esi,startswapcode
mov dl,DevHlp_VirtToLin
call [DevHlp]
mov edi,eax
; do a virttolin DevHlp (lockhandle)
mov ax,ds
mov esi,offset codelockhandle
mov dl,DevHlp_VirtToLin
call [DevHlp]
; do a VMLock DevHlp
mov esi,eax ; get offset to lock handle
xor eax,eax ; short term lock, etc.
mov ebx,edi ; get offset to area to lock
mov edi,-1 ; set to no page list
lea ecx,endswapcode ; size to lock
sub ecx,offset startswapcode ; size to lock
mov dl,DevHlp_VMLock
call [DevHlp] ; CF set by DevHlp_VMLock
pop ebx
RET
LOCKSWAP ENDP
;********************** START OF SPECIFICATIONS *********************
;*
;* MODULE NAME: UNLOCKSWAP
;*
;* DESCRIPTIVE NAME: UnLock Swappable Code routine
;*
;* FUNCTION: Unlock the swappable code segment portion of the
;* clock device driver.
;*
;* ENTRY POINT: UNLOCKSWAP
;* LINKAGE: NEAR from RTENTR
;*
;* USES: DL, ESI
;*
;* EXIT: Assume success
;*
;* INTERNAL REFERENCES:
;* STRUCTURES: ClkData:[codelockhandle]
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: DevHlp_VirtToLin, DevHlp_VMUnLock
;*
;*********************** END OF SPECIFICATIONS **********************
ASSUME CS:ClkSwap,DS:ClkData,ES:NOTHING,SS:NOTHING
UNLOCKSWAP PROC NEAR
public UNLOCKSWAP
push eax
; do a virttolin DevHlp (lockhandle)
mov ax,ds
mov esi,offset codelockhandle
mov dl,DevHlp_VirtToLin
call [DevHlp]
; do a VMUnlock DevHlp using previously saved lock handle
mov esi,eax ; get offset to lock handle
mov dl,DevHlp_VMUnlock
call [DevHlp]
pop eax
RET
UNLOCKSWAP ENDP
BREAK <RealTime Clock Read Routine>
;********************** START OF SPECIFICATIONS *********************
;*
;* MODULE NAME: RTREAD
;*
;* DESCRIPTIVE NAME: Realtime Clock Read routine
;*
;* FUNCTION: Supports the device commands:
;* - READ (function 4)
;* by returning six bytes of date and time information in
;* the form Date(word), Min, Hrs, Sec/100, Sec.
;*
;* DevHlp_PhysToVirt converts the real address of the data buffer
;* in the Device Driver Request Block (PktData) to a virtual
;* address. DevHlp_UnPhysToVirt later restores the physical
;* memory address.
;*
;* NOTES:
;* For enhanced performance, RTREAD does not actually read the
;* clock, but instead gets the data from the Global InfoSeg
;* date/time data area.
;*
;* ENTRY POINT: RTREAD
;* LINKAGE: NEAR from RTENTR
;*
;* USES: AX, CX, DX, BX, ES. Preserves others.
;*
;* INPUT:
;* Interrupt is enabled
;* ES:BX = pointer to Request Block (PktData)
;* (SP+4):(SP+2) = pointer to data buffer
;*
;* OUTPUT: (RETURNED)
;* DESCRIPTION: Caller's data Buffer
;*
;* EXIT-NORMAL:
;* Exit is via return to RTENTR (Strategy routine) with
;* AX = Status word to be stored in request packet status
;* field.
;*
;* EXIT-ERROR:
;* RETURN CODE: AX = ERROR and DONE
;*
;* INTERNAL REFERENCES:
;* ROUTINES: GTDAYS
;*
;* EXTERNAL REFERENCES:
;* STRUCTURES: Global Information Segment (SysInfoSeg)
;* ROUTINES: DevHlp_PhysToVirt, DevHlp_UnPhysToVirt
;*
;*********************** END OF SPECIFICATIONS **********************
page
;********************** START OF PSEUDO-CODE **********************
;
; if requesting byte length >= 6 byte
; set requesting byte length = 6
; save flags for preserving interrupt flag
; call DevHlp_PhysToVirt to convert data buffer's physical addr to
; virtual address in ES:DI
; if DevHlp_PhysToVirt successful
; save ClkData address( save DS )
; set DS:BX = SysInfoSeg address
; disable interrupts for accessing InfoSeg
; access InfoSeg to get seconds/hundredths, hours/minutes,
; months/days, & current year to put in caller's data buffer
; restore ClkData address, DS
; call GTDAYS to get day count since 1-1-80
; save day count in caller's data buffer
; call DevHlp_UnPhysToVirt to get original address mode
; if DevHlp_UnPhysToVirt successful
; set return code "DONE" & "BUSY"
; endif
; else goto convert_fail
; endif
; else goto convert_fail
;
; restore flags for original interrupt flag
; return
; endif
; else goto RT_ERR
;
; convert_fail:
; restore flags for original interrupt flag
;
; RT_ERR:
; set requesting byte length = 0
; set return code STDON+STERR+READ FAULT
; return
;
;*********************** END OF PSEUDO-CODE **********************
ASSUME CS:ClkSwap,DS:ClkData,ES:NOTHING,SS:NOTHING
RTREAD PROC NEAR
public RTREAD
CMP ES:[BX].IOcount,RW_BYTES ; requesting 6 bytes or more
Jae READ ; yes, continue.... @3.77
RT_ERR:
mov ES:[BX].IOcount,0 ; return 0 bytes @3.77
MOV AX,(STDON+STERR)+0bh ; Else, quit w/ error. @3.77
RET
READ: PUSH BP
MOV BP,SP
;; The addresses passed in the request packets are 32-bit physical addresses.
MOV CX,6
mov ES:[BX].IOcount,cx ; return 6 bytes @3.77
MOV AX,word ptr ES:[BX].IOpData+2 ; get hi word of address
MOV BX,word ptr ES:[BX].IOpData ; get lo word of address
MOV DH,1 ; result in ES:DI
MOV DL,DevHlp_PhysToVirt ; call PhysToVirt
PUSHF ; save the flags
CALL [DevHlp] ; ES:DI points to buffer
JNC GET_DATA
CONVERT_FAIL:
POPF ; restore flags
POP BP
JMP SHORT RT_ERR
GET_DATA:
PUSH DS ; Save ClkData selector
CLI ; Disable Interrupts while
; accessing InfoSeg
LDS BX,[InfSeg] ; DS:BX = InfoSeg address
ASSUME DS:NOTHING
MOV AX,WORD PTR DS:[BX.SIS_SecTime] ; Get Secs/Hundths
XCHG AH,AL
MOV WORD PTR ES:[DI+4],AX ; Stuff Huns/Secs
MOV AX,WORD PTR DS:[BX.SIS_HrsTime] ; Get Hrs/Mins
XCHG AH,AL
MOV WORD PTR ES:[DI+2],AX ; Stuff Mins/Hrs
MOV DX,WORD PTR DS:[BX.SIS_DayDate] ; DX = Mon/Day
MOV AX,DS:[BX.SIS_YrsDate] ; Get current year
;;80291 sti ; enable interrupts
SUB AX,1980 ; Elapsed since 1-1-80
POP DS ; Restore ClkData selector
;;;;;;;;;;;;;;;;; Ray Andrade Defect# 80291 Change Team ;;;;;;;;;;;;;;;;;;;;;
sti ; enable interrupts(moved here)
ASSUME DS:ClkData ;
CALL FAR PTR GTDAYS ; Convert to day count
MOV WORD PTR ES:[DI],AX ; Stuff it in caller's buffer
MOV DL,DevHlp_UnPhysToVirt ; call UnPhysToVirt
CALL [DevHlp] ; original addr mode restored
JC CONVERT_FAIL
POPF ; restore flags
MOV AX,(STDON OR STBUI) ; No error
POP BP
readabort:
RET
RTREAD ENDP
BREAK <RealTime Clock Generic IOCTL routine>
;********************** START OF SPECIFICATIONS *********************
;*
;* MODULE NAME: RTIOCTL
;*
;* DESCRIPTIVE NAME: Realtime Clock Generic IOCTL routine
;*
;* FUNCTION: Supports the category 13 generic IOCTL commands:
;* - READ CMOS byte (function 60h)
;* by calling the appropriate worker routine.
;*
;* ENTRY POINT: RTIOCTL
;* LINKAGE: NEAR from RTENTR
;*
;* USES: AX and flags.
;*
;* INPUT:
;* ES:BX = pointer to Request Block (PktData)
;*
;* EXIT-NORMAL:
;* Exit is via return to RTENTR (Strategy routine) with
;* AX = Status word to be stored in request packet status
;* field (DONE).
;*
;* EXIT-ERROR:
;* RETURN CODE: AX = Invalid command
;*
;* INTERNAL REFERENCES:
;* ROUTINES: GTCMOS
;*
;* EXTERNAL REFERENCES:
;* STRUCTURES:
;* ROUTINES:
;*
;*********************** END OF SPECIFICATIONS **********************
page
;********************** START OF PSEUDO-CODE **********************
;
; if requesting IOCTL is supported
; call worker routine
; else
; set AX to
;
; return
;
;*********************** END OF PSEUDO-CODE **********************
ASSUME CS:ClkSwap,DS:ClkData,ES:NOTHING,SS:NOTHING
RTIOCTL PROC NEAR
public RTIOCTL
cmp byte ptr es:[bx].GIOCategory, IOC_CK ; Correct category?
jne rti10 ; no, error exit
cmp byte ptr es:[bx].GIOFunction, IOCK_RD ; Supported function?
jne rti10 ; no, error exit
call GTCMOS ; call worker routine
jmp short rti20 ; then exit
rti10:
mov ax, STDON+STERR+ERRCMD ; indicate unknown command
rti20:
ret
RTIOCTL ENDP
BREAK <RealTime Clock Get CMOS byte routine>
;********************** START OF SPECIFICATIONS *********************
;*
;* MODULE NAME: GTCMOS
;*
;* DESCRIPTIVE NAME: Realtime Clock Get CMOS byte routine
;*
;* FUNCTION: Reads a byte from standard CMOS memory location 0Ah or
;* higher.
;*
;* ENTRY POINT: GTCMOS
;* LINKAGE: NEAR from RTIOCTL
;*
;* USES: AX and flags.
;*
;* INPUT:
;* ES:BX = pointer to Request Block (PktData)
;*
;* EXIT-NORMAL:
;* Exit is via return to RTIOCTL with
;* AX = Status word to be stored in request packet status
;* field (DONE).
;*
;* EXIT-ERROR:
;* RETURN CODE: AX = Invalid parameter.
;*
;* INTERNAL REFERENCES:
;* ROUTINES: ClkReadCMOS
;*
;* EXTERNAL REFERENCES:
;* STRUCTURES:
;* ROUTINES:
;*
;*********************** END OF SPECIFICATIONS **********************
page
;********************** START OF PSEUDO-CODE **********************
;
; if can't access parameter or data
; set AX to invalid parameter
; return
; if requested byte >= 0Ah
; call worker routine
; else
; set AX to invalid parameter
;
; return
;
;*********************** END OF PSEUDO-CODE **********************
ASSUME CS:ClkSwap,DS:ClkData,ES:NOTHING,SS:NOTHING
GTCMOS PROC NEAR
public GTCMOS
push bx
push cx
push dx
push di
push si
mov ax,word ptr es:[bx].GIOParaPack + 2
mov di,word ptr es:[bx].GIOParaPack
mov cx, 2 ; parm. length
xor dh, dh ; read access
mov dl, DevHlp_VerifyAccess
call [DevHlp] ;verify access to parameter packet
jc gt10
push es
push bx
les bx, es:[bx].GIOParaPack ; get parameter address
mov al, byte ptr es:[bx] ; get the requested CMOS addr.
inc bx ; point to length byte
mov ah, byte ptr es:[bx] ; get the requested number of bytes
pop bx
pop es
cmp al, ADDR_STATUSA ; is request one of the RTC bytes?
jl gt10 ; ..yes, so exit with error
cmp al, ADDR_CMOSRAMHI ; is request past the max. value?
jg gt10 ; ..yes, so exit with error
cmp ah, 0 ; is number of bytes requested 0?
je gt10 ; ..yes, so exit with error
xor ch, ch ; clear high byte
mov cl, ah ; data length
push ax ; save CMOS request and length
mov ax,word ptr es:[bx].GIODataPack + 2
mov di,word ptr es:[bx].GIODataPack
mov dh, 1 ; read/write access
mov dl, DevHlp_VerifyAccess
call [DevHlp] ; verify access to data packet
pop ax ; restore CMOS request and length
jc gt10
les di, es:[bx].GIODataPack ; get data address
mov cmos_req.rdrq_CMOSAddr, al ; put user value in request packet
mov cmos_req.rdrq_nbCMOS, ah ; number of CMOS bytes to read
mov si, offset cmos_req ; setup calling parms
mov cx, ds ; (cx:si)->CMOS ReadReq packet
mov dx, es ; (dx:di)->byte array for result
push eax ; save 32 bit register
CALLFAR ClkReadCMOS ; get the value from CMOS
pop eax ; restore 32 bit register
mov ax, STDON ; set good return code
jmp short gt20 ; then exit
gt10:
mov ax, STDON+STERR+13h ; invalid parameter status
gt20:
pop si
pop di
pop dx
pop cx
pop bx
ret
GTCMOS ENDP
ClkSwap ENDS
BREAK <Clock Device Driver Utility Subroutines>
;********************** START OF SPECIFICATIONS *********************
;*
;* MODULE NAME: FixDayOfWeek
;*
;* DESCRIPTIVE NAME: Get the right day of week
;*
;* FUNCTION:
;* This computes the correct day of week (DOW) if the value read
;* from the clock was 0 (uninitialized). The DOW is computed based on
;* the specified date (Day/Month/Year). If the date requested is
;* invalid, the date returned is 1-1-1980 (Tues).
;*
;* NOTE:
;* ABIOS doesn't keep the DOW. On NOT AT hdwr' this routine is
;* always called with DOW = CH = 0.
;*
;* ENTRY POINT: FixDayOfWeek
;* LINKAGE: NEAR from FIXISEG
;*
;* USES: Preserves all registers except CX, Flags
;*
;* INPUT:
;* AX = Days since 1-1-80
;* DH = Month
;* DL = Day
;*
;* OUTPUT:
;* CH = Day Of Week (0-6)
;*
;* EXIT-NORMAL: CH = day of week (0-6)
;*
;* EXIT-ERROR: none
;*
;* INTERNAL REFERENCES:
;* ROUTINES: GTDAYS
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: none
;*
;*********************** END OF SPECIFICATIONS **********************
page
;********************** START OF PSEUDO-CODE **********************
;
; day_of_week = ( days + 2 ) % 7
;
;*********************** END OF PSEUDO-CODE **********************
ClkCode SEGMENT
;
; this data must be in CS for INT xx intercept to work
;
saveDS dw ? ; DS for INT xx entry
;
; The REAL strategy routine is in the swappable code segment
;
ASSUME CS:ClkCode,DS:ClkData,ES:NOTHING,SS:NOTHING
ClkStrat PROC FAR
public ClkStrat
jmp RTENTR
ClkStrat ENDP
ASSUME CS:ClkCode,DS:ClkData,ES:NOTHING,SS:NOTHING
FixDayOfWeek PROC NEAR
public FIXDAYOFWEEK
SaveReg <AX,BX,DX>
add ax,2 ; 1-1-80 was a Tuesday
mov bx,7 ; 7 days per week
xor dx,dx
div bx ; ax = # of weeks, dx = day of week
mov ch,dl
RestoreReg <DX,BX,AX>
ret
FixDayOfWeek ENDP
;********************** START OF SPECIFICATIONS *********************
;*
;* MODULE NAME: GTDAYS
;*
;* DESCRIPTIVE NAME: Calculate days since 1-1-80
;*
;* FUNCTION:
;* This routine calculates from day/month/year the number of
;* days elapsed since 1-1-80 and returns it to the caller.
;*
;*
;* ENTRY POINT: GTDAYS
;* LINKAGE: FAR from RTREAD and FIXISEG
;*
;* USES: Preserves all registers except AX
;*
;* INPUT: (PARAMETERS)
;* AX = Years since 1-1-80
;* DH = Current month
;* DL = Current day
;*
;* OUTPUT: (RETURNED)
;* AX = Days since 1-1-80
;*
;* EXIT-NORMAL: AX = 0 to 65535
;*
;* EXIT-ERROR: none
;*
;* INTERNAL REFERENCES:
;* ROUTINES: none
;*
;* EXTERNAL REFERENCES:
;* ROUTINES: none
;*
;*********************** END OF SPECIFICATIONS **********************
page
;********************** START OF PSEUDO-CODE **********************
;
; if Years is leap year
; set Feb = 29
; else
; set Feb = 28
;
; Number of 4 years group = Years / 4
; Number of non 4 years group = Years % 4
; Days = DAYSIN4YR * Number of 4 years group + 366
; + DAYSINYR * (Number of non 4 years group - 1)
; + ( days of months ) + (current day - 1)
; return( Days )
;
;*********************** END OF PSEUDO-CODE **********************
ASSUME CS:ClkCode,DS:ClkData,ES:NOTHING,SS:NOTHING
GTDAYS PROC FAR
public GTDAYS
PUSH CX ; Preserve only what we use
PUSH DX
PUSH BX
; Number of non 4 years group = Years % 4
MOV BL,AL ; Copy years to CL
AND BL,3 ; CL = Years Modulo 4
; Number of 4 years group = Years / 4
XOR AH,AH ; Insure no high byte
SHR AX,1
SHR AX,1 ; AX = # of 4 Year groups
JZ NOADD1 ; If none, skip over days calculation
; DAYSIN4YR = 5B5x = 1461 = 365 * 3 + 366
; The followings are DAYSIN4YR * Number of 4 years group + 366
MOV CX,AX ; ...and use # of 4 year groups...
XOR AX,AX ; ...as add loop counter
ADD4YR: ADD AX,DAYSIN4YR ; Add one "quadyear" of days
LOOP ADD4YR ; Loop till done
; if Years is leap year
; set Feb = 29
; else
; set Feb = 28
NOADD1: OR BL,BL ; Any modulo? (0 == Leap year)
MOV MonTab+1,29 ; Init Feb to 29 days for leap year
JZ NOADD2 ; Is leap year, leave Feb and skip add
DEC MonTab+1 ; Not leap year, DEC Feb and add rmndr
; DAYSINYR = 16Ex = 365
; The followings are DAYSIN4YR * Number of 4 years group + 366
; + DAYSINYR * (Number of non 4 years group - 1)
;
ADD AX,DAYSINYR+1 ; First add the leap year of the rmnd
ADDAGN: DEC BL ; Any more years?
JZ NOADD2 ; No, all years have been added
ADD AX,DAYSINYR ; Yes, add in one normal year
JMP SHORT ADDAGN ; Loop till remainder is zero
; The followings are DAYSIN4YR * Number of 4 years group + 366
; + DAYSINYR * (Number of non 4 years group - 1)
; + (current day - 1)
NOADD2: DEC DL ; DL = DOM, use full days only
ADD AL,DL ; Add DOM, low byte...
ADC AH,0 ; ...then high
; The followings are DAYSIN4YR * Number of 4 years group + 366
; + DAYSINYR * (Number of non 4 years group - 1)
; + ( days of months ) + (current day - 1)
;
MOV BX,OFFSET MonTab ; Point to beginning of month table
NXMNTH: DEC DH ; Out of months?
JZ GOTMOS ; Yes, don't add any(more)
ADD AL,BYTE PTR [BX] ; Add in this month's day count...
ADC AH,0 ; ...and carry to high byte
INC BX ; Point to next month
JMP SHORT NXMNTH ; Keep going
GOTMOS:
POP BX ; Give him back his stuff
POP DX
POP CX
RET
GTDAYS ENDP
ClkCode ENDS
END