home *** CD-ROM | disk | FTP | other *** search
- ;*DDK*************************************************************************/
- ;
- ; 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 = @(#)testcfga.asm 6.1 92/01/09
- page 56,79
-
- ;*** TESTCFGA.ASM - TestCFG Device Driver
- ;*
- ;*
- ;*
- ;*
- ;* DESCRIPTION
- ;*
- ;* TESTCFG assembly routines. Mostly workers for TESTCFG C code.
- ;*
- ;* MODIFICATION HISTORY
- ;*
- ;* 6.1 01/15/92 CP20 B731??? Jeff Muir Original Version
- ;* 6.2 05/12/94 R207 83779 Frank Schroeder Fixed IsAPMPresent()
- ;* 09/17/94 RBDD 98451 Jon Grimm Resource Manager
- ;*
-
- ; include definitions for DEVHLP and macros
- include testcfga.inc
-
- .286c
- ;
- ; C Startup routine for OS/2 Device Drivers
- ;
- ; 1. Provides the user's "main" routine with the address of
- ; the request packet.
- ;
- ; 2. Defines the segments in the proper order (data, then code)
- ; so if testcfga.obj is included first in the link line, the
- ; segments for the device driver will be ordered correctly.
- ;
- ; 3. Satisfies the C EXTRN for __acrtused, which prevents the startup
- ; logic from being included from the standard C library.
-
- EXTRN _main:near
- EXTRN _Device_Help:dword
- PUBLIC _STRATEGYCFG
- PUBLIC __acrtused
-
- _DATA segment word public 'DATA'
- _DATA ends
-
- CONST segment word public 'CONST'
- CONST ends
-
- _BSS segment word public 'BSS'
- _BSS ends
-
- STATICCODE segment word public 'CODE'
- STATICCODE ends
-
- _TEXT segment word public 'CODE'
- _TEXT ends
-
- INITCODE segment word public 'CODE'
- INITCODE ends
-
- SWAPCODE segment word public 'CODE'
- SWAPCODE ends
-
- DGROUP group CONST, _BSS, _DATA
-
- StaticGroup group STATICCODE, INITCODE
- SWAPGROUP group SWAPCODE, _TEXT
-
-
- STATICCODE segment word public 'CODE'
-
- assume cs:STATICCODE, ds:DGROUP, es:NOTHING
- __acrtused equ 1
-
- _STRATEGYCFG proc far
-
- push es ; &reqpacket.hi
- push bx ; &reqpacket.lo
- call _main
- pop bx
- pop es
- mov word ptr es:[bx+3],ax ; plug in status word
- ret
-
- _STRATEGYCFG endp
-
- ;----------------------------------------------------------------------------:
- ; ;
- ; BOOL ProcRun( ULONG EventId, PUSHORT AwakeCount); ;
- ; ;
- ;----------------------------------------------------------------------------;
- EventId equ word ptr [bp+nbase]
- AwakeCount equ dword ptr [bp+nbase+4]
-
- NCPROC _ProcRun
- push es
- push bx
- .386
- mov bx, EventId[0]
- mov ax, EventId[2]
-
- mov dl,DevHlp_ProcRun ; Select function
- call [_Device_Help] ; Call devhelp
-
- les bx, AwakeCount
- mov es:[bx], ax
- .286c
- pop bx
- pop es
- ENDNCPROC _ProcRun
-
-
- STATICCODE ends
-
- SWAPCODE segment word public 'CODE'
- assume cs:SWAPCODE, ds:DGROUP, es:NOTHING
-
- ;---------------------------------------------------------------------------
- ; FUNCTION : InB - input byte from port
- ;---------------------------------------------------------------------------
- NCPROC _InB
-
- push dx ; save registers
- mov dx,word ptr [bp+nbase] ; get I/O address
- in al,dx ; read from the port
- ; (AL) - Port value
- pop dx ; restore registers
-
- ENDNCPROC _InB
-
- ;---------------------------------------------------------------------------
- ; FUNCTION : OutB - Output byte to port
- ;---------------------------------------------------------------------------
- NCPROC _OutB
-
- push dx ; save registers
- mov dx,word ptr [bp+nbase] ; get I/O address
- mov al,byte ptr [bp+nbase+2] ; get I/O value
- out dx,al ; write to the port
- pop dx ; restore registers
-
- ENDNCPROC _OutB
-
- ;---------------------------------------------------------------------------
- ; FUNCTION : InW - Input word from port
- ;---------------------------------------------------------------------------
- NCPROC _InW
-
- push dx ; save registers
- mov dx,word ptr [bp+nbase] ; get I/O address
- in ax,dx ; read from the port
- ; (AX) - Port value
- pop dx ; restore registers
-
- ENDNCPROC _InW
-
- ;---------------------------------------------------------------------------
- ; FUNCTION : OutW - Output word to port
- ;---------------------------------------------------------------------------
- NCPROC _OutW
- push dx ; save registers
- mov dx,word ptr [bp+nbase] ; get I/O address
- mov ax,word ptr [bp+nbase+2] ; get I/O value
- out dx,ax ; write to the port
- pop dx ; restore registers
-
-
- ENDNCPROC _OutW
-
- ;---------------------------------------------------------------------------
- ; FUNCTION : InDW - Input DWord from port
- ;---------------------------------------------------------------------------
- NCPROC _InDW
-
- .386
- mov dx,word ptr [bp+nbase] ; get I/O address
- in eax,dx ; read from the port
- ; (EAX) - Port value
- mov edx,eax ; (AX) - low port value
- shr edx,16 ; (dx)
- .286c
-
- ENDNCPROC _InDW
-
- ;---------------------------------------------------------------------------
- ; FUNCTION : OutDW - Output DWord to port
- ;---------------------------------------------------------------------------
- NCPROC _OutDW
-
- push dx ; save registers
- mov dx,word ptr [bp+nbase] ; get I/O address
- .386
- mov eax,dword ptr [bp+nbase+2] ; get I/O value
- out dx,eax ; write to the port
- .286c
- pop dx ; restore registers
-
- ENDNCPROC _OutDW
-
- ;---------------------------------------------------------------------------
- ; FUNCTION : strlen - determine length of string
- ;---------------------------------------------------------------------------
- NCPROC _strlen
-
- push si ; save register
-
- mov si,word ptr [bp+nbase] ; (SI) String Offset
- xor ax,ax ; (AX) String Length
- sl10:
- cmp byte ptr [si],0 ; Is character zero?
- je slx ; yes, end of string
- inc ax ; increase count of chars
- inc si ; move to next char
- jmp sl10 ;
- slx:
- pop si ; restore register
-
- ENDNCPROC _strlen
-
-
- ;***************************************************************************
- ; DevHelp Code 15h
- ;
- ; FUNCTION
- ;
- ; PhysToVirt - Map Physical Address to Virtual Address
- ;
- ; DESCRIPTION
- ;
- ; In the OS/2 Mode, PhysToVirt converts a 32-bit address to a valid
- ; selector-offset pair. In the DOS mode, PhysToVirt converts a 32-bit
- ; address to a segment-offset pair.
- ;
- ; C PROTOCOL
- ;
- ; USHORT PhysToVirt(ULONG PhysAddr,USHORT Length,PULONG VirtAddr)
- ;***************************************************************************
- ; parameter equates
- PTV_PhysAddrLow equ word ptr [bp+nbase]
- PTV_PhysAddrHigh equ word ptr [bp+nbase+2]
- PTV_Length equ word ptr [bp+nbase+4]
- PTV_VirtAddr equ dword ptr [bp+nbase+6]
-
- NCPROC _PhysToVirt
- push dx ; Save registers
- push cx
- push bx
- push di
- push si
- push ds
- push es
- mov bx,PTV_PhysAddrLow ; low physical address
- mov ax,PTV_PhysAddrHigh ; high physical address
- mov cx,PTV_Length ; length
- mov dh,1 ; result
- mov dl,DevHlp_PhysToVirt ; Select function
- call [_Device_Help] ; Call devhelp
- jc ptv10
- mov dx,es
- les bx,PTV_VirtAddr ; address of VirtAddr
- mov word ptr es:[bx],di
- mov word ptr es:[bx+2],dx
- xor ax,ax
- jmp ptv20
- ptv10:
- mov ax,1
- ptv20:
- pop es
- pop ds
- pop si
- pop di
- pop bx
- pop cx
- pop dx
- ENDNCPROC _PhysToVirt
-
- ;***************************************************************************
- ; DevHelp Code 27h
- ;
- ; FUNCTION
- ;
- ; VerifyAccess - Verify Access to Memory
- ;
- ; DESCRIPTION
- ;
- ; This routine verifies that the user process has the correct access rights
- ; for the memory that it passed to the device driver. If the process does
- ; not have the needed access rights to the memory, then it will be
- ; terminated. If it does have needed access rights, these rights are
- ; guaranteed to remain valid until the device driver exits its strategy
- ; routine.
- ;
- ; C PROTOCOL
- ;
- ; USHORT VerifyAccess(PUCHAR pMem,USHORT MemLen,USHORT AccType);
- ;***************************************************************************
- ; parameter equates
- VA_pMemOff equ word ptr [bp+nbase]
- VA_pMemSeg equ word ptr [bp+nbase+2]
- VA_MemLen equ word ptr [bp+nbase+4]
- VA_AccType equ byte ptr [bp+nbase+6]
-
- NCPROC _VerifyAccess
- push dx ; Save register
- push cx
- push di
- mov ax,VA_pMemSeg ; Segment
- mov cx,VA_MemLen ; Length of memory area
- mov di,VA_pMemOff ; Offset to memory area
- mov dh,VA_AccType ; Type of Access (0 R, 1 R/W)
- mov dl,DevHlp_VerifyAccess ; Select function
- call dword ptr [_Device_Help] ; Call devhelp
- jc va10
- xor ax,ax
- jmp vax
- va10: or ax,1
- vax:
- pop di
- pop cx
- pop dx ; Restore register
- ENDNCPROC _VerifyAccess
-
-
- ;***************************************************************************
- ; DevHelp Code 32h
- ;
- ; FUNCTION
- ;
- ; UnPhysToVirt - Mark Completion of Virtual Address Use
- ;
- ; DESCRIPTION
- ;
- ; UnPhysToVirt is required to mark completion of address conversion from
- ; VirtToPhys
- ;
- ; C PROTOCOL
- ;
- ; void UnPhysToVirt(void);
- ;***************************************************************************
- NCPROC _UnPhysToVirt
- push dx ; Save register
- mov dl,DevHlp_UnPhysToVirt ; Select function
- call dword ptr [_Device_Help] ; Call devhelp
- pop dx ; Restore register
- ENDNCPROC _UnPhysToVirt
-
- ;----------------------------------------------------------------------------:
- ; ;
- ; BOOL ProcBlock( ULONG EventId, ULONG WaitTime, USHORT IntWaitFlag ); ;
- ; ;
- ;----------------------------------------------------------------------------;
- EventID equ word ptr [bp+nbase]
- WaitTime equ word ptr [bp+nbase+4]
- IntWaitFlag equ word ptr [bp+nbase+8]
-
- NCPROC _ProcBlock
- push bx
- push cx
- push dx
- push di
- push si
- .386
- mov bx, EventId[0]
- mov ax, EventId[2]
- mov cx, WaitTime[0]
- mov di, WaitTime[2]
- mov dx, IntWaitFlag
- mov dh, dl
- mov dl,DevHlp_ProcBlock ; Select function
- call [_Device_Help] ; Call devhelp
- .286c
- pop si
- pop di
- pop dx
- pop cx
- pop bx
-
- ENDNCPROC _ProcBlock
-
- ;***************************************************************************
- ;
- ; FUNCTION
- ;
- ; IsAPMPresent
- ;
- ; DESCRIPTION
- ;
- ; This routine determines if Advanced Power Management BIOS is present.
- ; This routine returns true only when either 16-bit or 32-bit protect
- ; mode APM BIOS is found. When only real mode APM BIOS is found, this
- ; routine returns false.
- ;
- ; C PROTOCOL
- ;
- ; INT IsAPMPresent(VOID);
- ;***************************************************************************
-
- FCPROC _IsAPMPresent
- push bx
- push cx
- push dx
- push ds
-
- xor cx, cx ; cx=0, just query APM,
- ; don't establish connection
- mov al, 16 ; index 16 (APM info)
- mov dl, DevHlp_GetDOSVar ; select function
- call [_Device_Help] ; call devhelp
- jc short no_apm ; error, return 0
-
- push ax
- pop ds
- test WORD PTR ds:[bx].APM_Flags, 03h ; 16-bit or 32-bit PM APM?
- jz short no_apm ; no, return 0 (no apm)
- mov ax, 1 ; otherwise return 1 (apm)
- jmp short apm_exit
-
- no_apm:
- xor ax, ax
- apm_exit:
- pop ds
- pop dx
- pop cx
- pop bx
-
- ENDFCPROC _IsAPMPresent
-
- ;***************************************************************************
- ;
- ; FUNCTION
- ;
- ; GetDCTable - Get DASD Device Class table
- ;
- ; DESCRIPTION
- ;
- ; This routine is used to get the DASD device class table.
- ;
- ; C PROTOCOL
- ;
- ; USHORT GetDCTable(PVOID &(DCPtr);
- ;***************************************************************************
- ; parameter equates
- GDV_DCPtr equ word ptr [bp+nbase] ; address to place Device Class Table
-
- NCPROC _GetDCTable
- push dx ; Save registers
- push cx
- push bx
- push es
-
- mov ax,14 ; Index (Device Class Table)
- mov cx,1 ; DASD device class
- mov dl,DevHlp_GetDosVar ; Select function
- call [_Device_Help] ; Call devhelp
- jc gdv10 ; ax:bx ptr to table
- mov dx,bx ;
- mov bx,GDV_DCPtr
- mov ds:[bx],dx ; fill in DCPtr (return it)
- mov ds:[bx+2],ax
- xor ax,ax
- jmp gdv_x
- gdv10:
- mov ax,1
- gdv_x:
- pop es
- pop bx
- pop cx
- pop dx
- ENDNCPROC _GetDCTable
-
- ;-----------------------------------------------------;
- ; VOID _ZeroCB (PBYTE ControlBlock, USHORT Length) ;
- ; ;
- ; Function: Zero fill the input control block ;
- ; ;
- ;-----------------------------------------------------;
- CtrlBlk EQU dword ptr [bp+nbase]
- BlkLen EQU word ptr [bp+nbase+4]
-
- NCPROC _ZeroCB
-
-
- push es
- push bx
- push cx
- push di
- .386
- xor eax,eax
- les di,CtrlBlk
- mov cx,BlkLen
- mov bx,cx
- and bx,3
- shr cx,2
- cmp cx,0
- je zcb_rem
- rep stosd
-
- zcb_rem:
- mov cx,bx
- cmp cx,0
- je zcb_ret
- rep stosb
-
- zcb_ret:
- .286c
- pop di
- pop cx
- pop bx
- pop es
-
- ENDNCPROC _ZeroCB
-
- ;----------------------------------------------------------;
- ; VOID _BlockCopy (PBYTE Dest, PBYTE Orig, USHORT Length ;
- ; ;
- ; Function: Copy a block of data ;
- ; ;
- ;----------------------------------------------------------;
- BlkDest EQU dword ptr [bp+nbase]
- BlkSrc EQU dword ptr [bp+nbase+4]
- BlkCLen EQU word ptr [bp+nbase+8]
-
- NCPROC _BlockCopy
-
- push ds
- push es
- push di
- push si
- push cx
- push bx
- .386
- les di,BlkDest
- lds si,BlkSrc
- mov cx,BlkCLen
-
- mov bx,cx
- and bx,3
- shr cx,2
- cmp cx,0
- je bc_rem
- rep movsd
-
- bc_rem:
- mov cx,bx
- cmp cx,0
- je bc_ret
- rep movsb
-
- bc_ret:
- .286c
- pop bx
- pop cx
- pop si
- pop di
- pop es
- pop ds
-
- ENDNCPROC _BlockCopy
-
-
- SWAPCODE ends
-
-
- INITCODE segment word public 'CODE'
-
- assume cs:INITCODE, ds:DGROUP, es:NOTHING
- ;***************************************************************************
- ; FUNCTION
- ;
- ; SegLimit - determine segment limit
- ;
- ; DESCRIPTION
- ;
- ; Returns the current limit of the requested segment.
- ;
- ;***************************************************************************
- NCPROC _SegLimit
-
- push es
- push bx
- push di
- mov ax, word ptr [bp+nbase]
- ; lsl bx, ax ; get segment limit
- db 0fh,03,0d8h
- les di, dword ptr [bp+nbase+2] ; address of limit var
- mov word ptr es:[di],bx
- xor ax,ax
-
- pop di
- pop bx
- pop es
-
- ENDNCPROC _SegLimit
-
- ;***************************************************************************
- ; DevHelp Code 16h
- ;
- ; FUNCTION
- ;
- ; VirtToPhys - Map Virtual Address to Physcial Address
- ;
- ; DESCRIPTION
- ;
- ; VirtToPhys converts a selector-offset pair to a 32-bit address.
- ;
- ; C PROTOCOL
- ;
- ; USHORT VirtToPhys(ULONG VirtAddr,PULONG pPhysAddr)
- ;***************************************************************************
- ; parameter equates
- VTP_VirtAddr equ dword ptr [bp+nbase]
- VTP_pPhysAddr equ dword ptr [bp+nbase+4]
-
- NCPROC _VirtToPhys
- push dx ; Save registers
- push cx
- push bx
- push di
- push si
- push ds
- push es
- .386
- lds si,VTP_VirtAddr
- mov dl,DevHlp_VirtToPhys ; Select function
- call [_Device_Help] ; Call devhelp
- jc vtp10
- les di,VTP_pPhysAddr ; address of PhysAddr
- mov word ptr es:[di],bx
- mov word ptr es:[di+2],ax
- xor ax,ax
- jmp vtp20
- vtp10:
- mov ax,1
- vtp20:
- .286c
- pop es
- pop ds
- pop si
- pop di
- pop bx
- pop cx
- pop dx
- ENDNCPROC _VirtToPhys
-
- ;***************************************************************************
- ; DevHelp Code 34h
- ;
- ; FUNCTION
- ;
- ; GetLIDEntry - Get a Logical ID
- ;
- ; DESCRIPTION
- ;
- ; This routine is used to obtain a Logical ID (LID) for devices that exist
- ; (that is, devices that are awake).
- ;
- ; C PROTOCOL
- ;
- ; USHORT GetLIDEntry(USHORT DeviceID,USHORT RelativeLID,USHORT DeviceState,
- ; PUSHORT pLID);
- ;***************************************************************************
- ; parameter equates
- GL_DeviceID equ byte ptr [bp+nbase]
- GL_RelID equ byte ptr [bp+nbase+2]
- GL_DevState equ byte ptr [bp+nbase+4]
- GL_pLID equ dword ptr [bp+nbase+6]
-
- NCPROC _GetLIDEntry
- push dx ; Save registers
- push es
- push bx
-
- mov al,GL_DeviceID ; DeviceID
- mov bl,GL_RelID ; Relative LID
- mov dh,GL_DevState ; Device State
- mov dl,DevHlp_GetLIDEntry ; Select function
- call [_Device_Help] ; Call devhelp
- jc gle10
- les bx,GL_pLID ; Address of Var Addr
- mov word ptr es:[bx],ax
- xor ax,ax
- gle10:
- pop bx
- pop es
- pop dx
- ENDNCPROC _GetLIDEntry
-
- ;***************************************************************************
- ; DevHelp Code 35h
- ;
- ; FUNCTION
- ;
- ; FreeLIDEntry - Release a Logical ID
- ;
- ; DESCRIPTION
- ;
- ; This routine is used to release a Logical ID. This must be done at
- ; DEINSTALL or termination time.
- ;
- ; C PROTOCOL
- ;
- ; USHORT FreeLIDEntry(USHORT LID);
- ;***************************************************************************
- ; parameter equates
- FL_LID equ word ptr [bp+nbase]
-
- NCPROC _FreeLIDEntry
- push dx ; Save registers
-
- mov ax,FL_LID ; LogicalID
- mov dl,DevHlp_FreeLIDEntry ; Select function
- call [_Device_Help] ; Call devhelp
- jc fle10
- xor ax,ax
- fle10:
- pop dx
- ENDNCPROC _FreeLIDEntry
-
- ;***************************************************************************
- ; DevHelp Code 36h
- ;
- ; FUNCTION
- ;
- ; ABIOSCall - Invoke ABIOS Function
- ;
- ; DESCRIPTION
- ;
- ; This routine is used to invoke an ABIOS service for the Operating
- ; System Transfer Convention.
- ;
- ; C PROTOCOL
- ;
- ; USHORT ABIOSCall(USHORT LID, POINTER RBOffset, USHORT Entry);
- ;***************************************************************************
- ; Parameter equates
- AB_LID equ word ptr [bp+nbase]
- AB_RBOffset equ word ptr [bp+nbase+2]
- AB_Entry equ byte ptr [bp+nbase+4]
-
- NCPROC _ABIOSCall
- push dx ; Save registers
- push si
-
- mov ax,AB_LID ; LogicalID
- mov si,AB_RBOffset ; RB Offset
- mov dh,AB_Entry ; Entry
- mov dl,DevHlp_ABIOSCall ; Select function
- call [_Device_Help] ; Call devhelp
- jc abc10
- xor ax,ax
- abc10:
- pop si
- pop dx
-
- ENDNCPROC _ABIOSCall
-
-
- INITCODE ends
-
- end
-