home *** CD-ROM | disk | FTP | other *** search
- ; original Copyright(C) 1992 Hiroya Tsubakimoto
- ; modifications Copyright(C) 1993 Charles Sandmann
- ; Merged with GO32 V1.09+ C. Sandmann sandmann@clio.rice.edu
- ; Distributed under terms of "copying.dj" when distributed with GO32 source
- ; Distributed under terms of GPL if used in any other code
-
- .386p
- include segdefs.inc
- include tss.inc
-
- ;*--------------------------------------------------------------*
- ;DGROUP group _TEXT,_DATA,_BSS ;(tiny model only)
-
- DPMIinfo struc
- vers db ?,?
- flags dw ?
- cpu dw ?
- PIC db ?,?
- DPMIinfo ends
-
- DPMImemory struc
- address dd ?
- bytes dd ?
- handle dd ?
- DPMImemory ends
-
- regs struc
- rDI dw ?,?
- rSI dw ?,?
- rBP dw ?,?
- dd 0
- rBX dw ?,?
- rDX dw ?,?
- rCX dw ?,?
- rAX dw ?,?
- rFlags dw ?
- rES dw ?
- rDS dw ?
- rFS dw ?
- rGS dw ?
- rIP dw ?
- rCS dw ?
- rSP dw ?
- rSS dw ?
- regs ends
-
- ;*--------------------------------------------------------------*
- start_data16
-
- extrn _tss_ptr:word
- extrn _screen_seg:word
- extrn _topline_info:word
-
- goProtectMode dd ? ;Location of far call routine
- realRegs regs <>
- selfSP dw ?
- selfSS dw ?
- ss_lim dd 0
- forced db 0
-
- maxmem_buffer dw 24 dup(?)
-
- end_data16
- ;*--------------------------------------------------------------*
- start_code16
-
- assume cs:_TEXT,ds:DGROUP
-
- numberException equ 16 ;Number we ever want to handle
- selfDS dw ? ;Protected mode 16bit selector to real
-
- ;*--------------------------------------------------------------*
- ;* DPMI
- ;* Syntax:
- ;* int initDPMI(DPMIinfo* info)
- ;* Argument(s):
- ;* "info" DPMI host
- ;* Result(s):
- ;* DPMI
- ;* 1 0
- ;*--------------------------------------------------------------*
- public _initDPMI
- _initDPMI proc near
- push bp
- mov bp,sp
- push si
- push di
- mov realRegs.rCS,cs ;Remember segment registers
- mov realRegs.rDS,ds
- mov realRegs.rSS,ss
-
- mov ax,1687h ; Detect DPMI and get Real to Prot Mode Entry
- int 2fh
- and ax,ax ; DPMI successful? AX == 0 means yes
- jnz @@failed_initDPMI
- test bx,1 ; 32Bit programs supported has "1" in bit 0
- jz @@failed_initDPMI
- mov word ptr goProtectMode[0],di
- mov word ptr goProtectMode[2],es
- mov bx,si ; number of paragraphs required DPMI host data
- mov ah,48h
- int 21h
- jc @@failed_initDPMI
- mov es,ax ; Real mode segment of DPMI host data area
- mov ax,1 ; We want a 32Bit application
- call goProtectMode
- jc short @@failed_initDPMI
-
- mov bx,cs ;Protected mode cs
- mov ax,000Ah ;Create alias descriptor we can write
- int 31h
- jc short @@failed_initDPMI
- mov es,ax ;Alias for our code segment
- assume es:_TEXT
- mov es:selfDS,ds ;In protected mode can't write cs!
- assume es:nothing
- mov bx,ax ;Alias for code segment not needed
- mov ax,0001h ;Free LDT descriptor
- int 31h
- mov selfSS,ss ;Save protected mode ss selector
-
- mov ax,0400h ; get DPMI version and flags
- int 31h
- mov di,word ptr [bp][4] ; "info"
- mov word ptr [di].vers,ax
- mov [di].flags,bx
- xor ch,ch
- mov [di].cpu,cx
- mov word ptr [di].PIC,dx
-
- mov ax,0900h ;Disable virtual interrupt
- int 31h
- mov ax,1
- jmp short @@done_initDPMI
- @@failed_initDPMI:
- xor ax,ax
- @@done_initDPMI:
- pop di
- pop si
- pop bp
- ret
- _initDPMI endp
-
-
- ;*--------------------------------------------------------------*
- ;* Syntax:
- ;* void uninitDPMI(int retcode)
- ;* Argument(s):
- ;* "retcode" exit()
- ;*--------------------------------------------------------------*
- public _uninitDPMI
- _uninitDPMI proc near
- push bp
- mov bp,sp
- mov ax,0901h ; Enable virtual interrupts
- int 31h
- mov ax,word ptr [bp][4] ; "retcode"
- mov ah,4ch ; Terminate program & prot mode
- int 21h
- _uninitDPMI endp
-
- ;*--------------------------------------------------------------*
- ;* Syntax:
- ;* void DPMIrealMode(void)
- ;*--------------------------------------------------------------*
- public _DPMIrealMode
- _DPMIrealMode proc near
- pop bx ;Where to return from this procedure
- mov realRegs.rBX,bx
- mov realRegs.rSI,si
- mov realRegs.rDI,di
- mov realRegs.rBP,bp
- mov realRegs.rSP,sp
- mov realRegs.rIP,offset _TEXT:@@realModeEntry
- mov realRegs.rFlags,0202h
- xor bx,bx ;No reset of controllers or A20 line
- xor cx,cx ;Don't copy any words from prot stack
- push ds
- pop es ;ES:EDI = Selector:Offset Real mode call struct
- mov edi,offset DGROUP:realRegs
- mov ax,0301h ; far call to real mode procedure
- int 31h
- mov si,realRegs.rSI ; We have returned via DPMIprotectedMode
- mov di,realRegs.rDI
- movzx ebp,realRegs.rBP
- movzx esp,realRegs.rSP
- jmp realRegs.rBX ; stored by DPMIprotectedMode() below
- @@realModeEntry:
- pop goProtectMode ; Address to return from real mode callback
-
- cmp _topline_info,0
- je no_topline1
- push es
- push ax
- mov ax,_screen_seg
- mov es,ax
- mov word ptr es:[0], 0b00h+'R'
- mov word ptr es:[2], 0b00h+' '
- pop ax
- pop es
- no_topline1:
- push bx ; Address stored in realRegs above
- ret ; DPMIrealMode()
- _DPMIrealMode endp
-
- ;*--------------------------------------------------------------*
- ;* Syntax:
- ;* void DPMIprotectedMode(void)
- ;*--------------------------------------------------------------*
- public _DPMIprotectedMode
- _DPMIprotectedMode proc near
- cmp _topline_info,0
- je no_topline2
- push ax
- push es
- mov ax,_screen_seg
- mov es,ax
- mov word ptr es:[2], 0b00h+'P'
- mov word ptr es:[0], 0b00h+' '
- pop es
- pop ax
- no_topline2:
- pop bx ;Return point (will be used in
- mov realRegs.rBX,bx ; DPMIrealMode above)
- mov realRegs.rSI,si
- mov realRegs.rDI,di
- mov realRegs.rBP,bp
- mov realRegs.rSP,sp
- jmp goProtectMode ;Saved retf address from real mode callback
- _DPMIprotectedMode endp
-
- ;*--------------------------------------------------------------*
- ;* Syntax:
- ;* void DPMIexecute(void)
- ;* Note(s):
- ;* We will return from this call in handlerCommon
- ;*--------------------------------------------------------------*
- public _DPMIexecute
- _DPMIexecute proc near
- push bp ; These 3 registers pushed here are
- push si ; popped in handlerCommon_done
- push di
-
- mov selfSP,sp
- call _DPMIprotectedMode ; Switch to 16 bit protected mode
- mov bx,_tss_ptr
- mov ss,[bx].tss_ss
- mov esp,[bx].tss_esp
- push [bx].tss_eflags ; Flags to load (by iretd below)
- push dword ptr [bx].tss_cs ; CS to execute (32 bit)
- push [bx].tss_eip ; EIP to execute (32 bit)
- mov eax,[bx].tss_eax
- mov ecx,[bx].tss_ebx
- push ecx
- mov ecx,[bx].tss_ecx
- mov edx,[bx].tss_edx
- mov ebp,[bx].tss_ebp
- mov esi,[bx].tss_esi
- mov edi,[bx].tss_edi
- mov es,[bx].tss_es
- mov fs,[bx].tss_fs
- mov gs,[bx].tss_gs
- mov ds,[bx].tss_ds
- pop ebx
-
- push eax
- mov ax,0901h ; Enable virtual interrupts
- int 31h
- pop eax
-
- iretd ; Jump to values pushed on stack
- _DPMIexecute endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* word32 DPMImaxmem()
- ;* Result(s):
- ;* returns number of bytes of memory left
- ;*--------------------------------------------------------------*
- public _DPMImaxmem
- _DPMImaxmem proc near
- push bp
- mov bp,sp
- push si
- push di
- mov ax,0500h ; Get Free Memory Information
- mov di, offset maxmem_buffer
- int 31h
- mov di,[bp+4]
- mov si,offset maxmem_buffer
- movsd
- add si,16
- movsd
- add si,8
- movsd
- pop di
- pop si
- pop bp
- ret
- _DPMImaxmem endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* int DPMIalloc(DPMImemory* mem, word32 bytes)
- ;* Argument(s):
- ;* "mem"
- ;* "bytes"
- ;* Result(s):
- ;* returns 1 or 0 to flag success or failure
- ;* "mem"
- ;* Note(s):
- ;* DPMIfree() will release the memory
- ;*--------------------------------------------------------------*
- public _DPMIalloc
- _DPMIalloc proc near
- push bp
- mov bp,sp
- push si
- push di
- mov ax,0501h ; Allocate memory block
- alloc_common:
- mov cx,word ptr [bp][4+2][0] ; "bytes" to allocate
- mov bx,word ptr [bp][4+2][2]
- int 31h ; returns BX:CX SI:DI
- jc short @@failed_DPMIalloc
- push bx ; save til later
- mov bx,word ptr [bp][4] ; "mem" address
- mov word ptr [bx].handle[0],di
- mov word ptr [bx].handle[2],si
- mov word ptr [bx].address[0],cx
- pop ax
- mov word ptr [bx].address[2],ax
- mov ecx,dword ptr [bp][4+2] ; copy "bytes" into struct
- mov [bx].bytes,ecx
- mov ax,1 ; success
- jmp short @@done_DPMIalloc
- @@failed_DPMIalloc:
- xor ax,ax ; failure
- @@done_DPMIalloc:
- pop di
- pop si
- pop bp
- ret
- _DPMIalloc endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* int DPMIrealloc(DPMImemory* mem, word32 bytes)
- ;* Argument(s):
- ;* "mem"
- ;* "bytes"
- ;* Result(s):
- ;* returns 1 or 0 to flag success or failure
- ;* "mem"
- ;* Note(s):
- ;* DPMIfree() will release the memory
- ;*--------------------------------------------------------------*
- public _DPMIrealloc
- _DPMIrealloc proc near
- push bp
- mov bp,sp
- push si
- push di
- mov bx,word ptr [bp][4] ; "mem" address
- mov di,word ptr [bx].handle[0]
- mov si,word ptr [bx].handle[2]
- mov ax,0503h ; Resize memory block
- jmp short alloc_common
- _DPMIrealloc endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void DPMIfree(DPMImemory* mem)
- ;* Argument(s):
- ;* "mem"
- ;* Note(s):
- ;* DPMIalloc(), DPMIrealloc() allocate the memory block
- ;*--------------------------------------------------------------*
- public _DPMIfree
- _DPMIfree proc near
- push bp
- mov bp,sp
- push si
- push di
- mov bx,word ptr [bp][4] ; "mem" address
- mov di,word ptr [bx].handle[0]
- mov si,word ptr [bx].handle[2]
- mov ax,0502h ; Free memory block
- int 31h
- pop di
- pop si
- pop bp
- ret
- _DPMIfree endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* word16 DPMIselector(word16 number)
- ;* Argument(s):
- ;* "number"
- ;* Result(s):
- ;* base value of contiguous LDT desciptors
- ;*--------------------------------------------------------------*
- public _DPMIselector
- _DPMIselector proc near
- push bp
- mov bp,sp
- mov cx,word ptr [bp][4] ;"number" to allocate
- mov ax,0000h ; Allocate LDT Descriptors
- int 31h ; returns AX
- jnc short @@done_DPMIselector
- xor ax,ax
- @@done_DPMIselector:
- pop bp
- ret
- _DPMIselector endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void DPMIassignSelector(word16 selector, word16 type, word32 base, word32 limit)
- ;* Argument(s):
- ;* "selector"
- ;* "type"
- ;* "base"
- ;* "limit"
- ;*--------------------------------------------------------------*
- public _DPMIassignSelector
- _DPMIassignSelector proc near
- push bp
- mov bp,sp
- mov bx,word ptr [bp][4] ; "selector"
- mov dx,word ptr [bp][4+2+2][0]
- mov cx,word ptr [bp][4+2+2][2] ; "base"
- mov ax,0007h ; Set segment base
- int 31h
- jc short @@err_DPMIassignSelector
-
- lar ax,bx ; get priv level of selector bx
- and ah,60h ; Mask all except CPL
- mov cx,word ptr [bp][4+2] ; "type"
- and cl,9fh ; Clear passed CPL
- or cl,ah ; Insert CPL of selector
- mov ax,0009h ; Set descriptor access rights
- int 31h
- jc short @@err_DPMIassignSelector
-
- mov dx,word ptr [bp][4+2+2+4][0]
- mov cx,word ptr [bp][4+2+2+4][2] ; "limit"
- mov ax,0008h ; Set segment limit
-
- selector_common:
- int 31h
- jc short @@err_DPMIassignSelector
-
- mov ax,1
- jmp short @@done_DPMIassignSelector
- @@err_DPMIassignSelector:
- xor ax,ax
- @@done_DPMIassignSelector:
- pop bp
- ret
- _DPMIassignSelector endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void DPMISelectorBase(word16 selector, word32 base)
- ;* Argument(s):
- ;* "selector"
- ;* "base"
- ;*--------------------------------------------------------------*
- public _DPMISelectorBase
- _DPMISelectorBase proc near
- push bp
- mov bp,sp
- mov bx,word ptr [bp][4] ; "selector"
- mov dx,word ptr [bp][4+2][0]
- mov cx,word ptr [bp][4+2][2] ; "base"
- mov ax,0007h ; Set segment base
- jmp short selector_common
- _DPMISelectorBase endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void DPMIchangeException(word8 no, DPMIaddress* handler)
- ;* Argument(s):
- ;* "no"
- ;* "handler"
- ;*--------------------------------------------------------------*
- public _DPMIchangeException
- _DPMIchangeException proc near
- push bp
- mov bp,sp
- mov ax,0202h ; Get exception handler vector
- mov bx,word ptr [bp][4] ; "no"
- int 31h ; return value in CX:EDX
- mov ax,0203h ; Set exception handler vector
- change_common:
- push cx ; Save it
- push edx
- mov bx,word ptr [bp][4+2] ; "handler" struct address
- mov edx,dword ptr [bx][0]
- mov cx,word ptr [bx][4]
- mov bx,word ptr [bp][4] ; "no"
- int 31h ; Do the change!
- mov bx,word ptr [bp][4+2] ; "handler" struct address
- pop edx ; original "handler" offset
- mov dword ptr [bx][0],edx
- pop cx ; original "handler" segment
- mov word ptr [bx][4],cx
- pop bp
- ret
- _DPMIchangeException endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void DPMIchangeInterrupt(word8 no, DPMIaddress* handler)
- ;* Argument(s):
- ;* "no"
- ;* "handler"
- ;*--------------------------------------------------------------*
- public _DPMIchangeInterrupt
- _DPMIchangeInterrupt proc near
- push bp
- mov bp,sp
- mov ax,0204h ; Get protected mode interrupt vector
- mov bx,word ptr [bp][4] ; "no"
- int 31h ; return value in CX:EDX
- mov ax,0205h ; Set protected mode interrupt vector
- jmp short change_common
- _DPMIchangeInterrupt endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void DPMIhandlerNPX(DPMIaddress* handler)
- ;* Argument(s):
- ;* "handler"
- ;* Notes:
- ;* This returns the handler address "no" for NPX hardware exceptions
- ;*--------------------------------------------------------------*
- public _DPMIhandlerNPX
- _DPMIhandlerNPX proc near
- push bp
- mov bp,sp
- mov bx,word ptr [bp][4] ; "handler"
- mov dword ptr [bx][0],offset _TEXT:i75hdlr
- mov word ptr [bx][4],cs
- pop bp
- ret
- i75hdlr:
- push eax
- xor ax,ax
- out 0f0h,al
- mov al,20h
- out 0a0h,al
- out 020h,al
- mov al,75h
- call causeException
- pop eax
- sti
- iretd
- _DPMIhandlerNPX endp
-
- ; code to disable execution
- causeException proc near
- push ebx
- push cx
- push dx
- push ds
- mov ds,cs:selfDS
- mov forced,al ; Indicate a fake exception
- mov bx,_tss_ptr
- movzx ebx,[bx].tss_ss
- lsl eax,ebx
- mov ss_lim,eax
- xor cx,0fffh
- mov dx,0ffffh
- mov ax,0008h ;Set segment limit
- int 31h
- pop ds
- pop dx
- pop cx
- pop ebx
- ret
- causeException endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void DPMIehandler(word8 no, DPMIaddress* handler)
- ;* Argument(s):
- ;* "no"
- ;* "handler"
- ;* Notes:
- ;* This returns the handler address "no" for exceptions.
- ;*--------------------------------------------------------------*
- public _DPMIehandler
- _DPMIehandler proc near
- push bp
- mov bp,sp
- mov ax,word ptr [bp][4] ; "no"
- xor ah,ah
- mov dx,sizeOfeHandler
- mul dx
- add ax,offset _TEXT:ehandlerTable
- jmp short gethandleraddr
-
- ehandler macro n
- push n
- jmp short ehandlerCommon
- endm
-
- ehandlerTable:
- ehandler 0
- sizeOfeHandler equ $-offset ehandlerTable
- x = 1
- rept numberException
- ehandler x
- x = x + 1
- endm
- ehandlerCommon:
- jmp handlerCommon
- _DPMIehandler endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void DPMIhandler(word8 no, DPMIaddress* handler)
- ;* Argument(s):
- ;* "no"
- ;* "handler"
- ;* Notes:
- ;* This returns the handler address "no" for interrupts.
- ;*--------------------------------------------------------------*
- public _DPMIhandler
- _DPMIhandler proc near
- push bp
- mov bp,sp
- mov ax,word ptr [bp][4] ; "no"
- xor ah,ah
- mov dx,sizeOfHandler
- mul dx
- add ax,offset _TEXT:handlerTable
- gethandleraddr:
- mov bx,word ptr [bp][4+2] ; "handler"
- mov word ptr [bx][0],ax
- mov word ptr [bx][2],dx
- mov word ptr [bx][4],cs
- pop bp
- ret
-
- handler macro n
- push n
- jmp handlerCommon
- endm
-
- handlerTable:
- handler 256
- sizeOfHandler equ $-offset handlerTable
- x = 257
- rept 255
- handler x
- x = x + 1
- endm
- _DPMIhandler endp
-
- ;*
- ;* Note(s):
- ;* This code is called any time an interrupt or execption occurs in the
- ;* 32 bit protected mode code. The interrupt or exception number is
- ;* pushed on the stack (with the high byte being 1 for interrupt).
- ;* This is the only way code may escape the 32 bit mode entered via
- ;* DPMIexecute().
- ;*
- handlerCommon proc near
- push ax
- mov ax,0900h ;Disable virtual interrupts
- int 31h
- pop ax
- push ebx ;tss access
- push ds
- mov ds,cs:selfDS
- mov bx,_tss_ptr
- pop word ptr [bx].tss_ds
- pop [bx].tss_ebx
-
- mov [bx].tss_es,es
- mov [bx].tss_fs,fs
- mov [bx].tss_gs,gs
- mov [bx].tss_esi,esi
- mov [bx].tss_edi,edi
- mov [bx].tss_ebp,ebp
- mov [bx].tss_edx,edx
- mov [bx].tss_ecx,ecx
- mov [bx].tss_eax,eax
-
- pop ax
- mov [bx].tss_irqn,al
-
- or ah,ah
- jnz @@handlerCommon_interrupt
-
- ; Exception only code:
- push ebp
- mov ebp,esp
-
- cmp al,12 ; Stack fault?
- jne not_forced
- mov al,forced ; Did we force this in hw int?
- cmp al,0
- jz not_forced
- mov [bx].tss_irqn,al ; Real exception
- mov forced,0 ; Its handled
- call limitFix ; Fix the limit
-
- not_forced:
-
- mov eax,dword ptr [ebp][12]
- mov [bx].tss_error,eax
- mov eax,dword ptr [ebp][12+4]
- mov [bx].tss_eip,eax
- mov ax,word ptr [ebp][12+4+4]
- mov [bx].tss_cs,ax
-
- mov eax,dword ptr [ebp][12+4+4+4]
- and ax,0FEFFh ; clear trace flag
- or ax, 0200h ; set iret flag
- mov [bx].tss_eflags,eax
- mov dword ptr [ebp][12+4+4+4],eax ; put back on dpmi-stack
-
- mov eax, dword ptr [ebp+28]
- mov [bx].tss_esp, eax
- mov ax,word ptr [ebp+32]
- mov word ptr [bx].tss_ss, ax
-
- mov dword ptr [ebp][16],offset _TEXT:@@handlerCommon_exception
- mov word ptr [ebp][16+4],cs ; Set CS:EIP on stack
-
- ; Change to 16 bit stack on return from exception (may be 32bit stack exception)
- movzx eax,selfSP
- mov dword ptr [ebp+28],eax ; set ESP on stack
- mov ax,selfSS
- mov word ptr [ebp+32],ax ; set SS on stack
-
- mov eax,dword ptr [bx].tss_eax ; restore regs...
- push dword ptr [bx].tss_ebx
- push word ptr [bx].tss_ds
- pop ds
- pop ebx
-
- pop ebp
- db 66h
- retf
-
- @@handlerCommon_exception:
- mov ds,cs:selfDS
- push 0 ; Indicate exception
- jmp short @@handlerCommon_done
-
- @@handlerCommon_interrupt:
- pop [bx].tss_eip
- pop dword ptr [bx].tss_cs
- pop [bx].tss_eflags
- mov ds,cs:selfDS
- mov bx,_tss_ptr
- mov [bx].tss_ss,ss
- mov [bx].tss_esp,esp
- mov ss,selfSS
- movzx esp,selfSP
- push 1 ; Indicate interrupt
- @@handlerCommon_done:
- xor ebp,ebp
- call _DPMIrealMode
- pop ax
-
- pop di ; C needs these registers saved
- pop si
- pop bp
- ret ; DPMIexecute() return point
- handlerCommon endp
-
- ; Code to restore ss limit
- limitFix proc near
- push bx
- push cx
- push dx
- ; mov bx,[bx].tss_ss ;We didn't store it yet, but...
- mov bx,word ptr [ebp+32] ;Stack selector
- mov dx,word ptr ss_lim
- mov cx,word ptr ss_lim+2
- mov ax,0008h ;Set segment limit
- int 31h
- pop dx
- pop cx
- pop bx
- ret
- limitFix endp
-
- ;*--------------------------------------------------------------*
- ;* Syntax:
- ;* int DPMIsetBreak(word16 sizetype, word32 addr);
- ;* Argument(s):
- ;* "sizetype" contains contents of DX - both size and type of breakpoing
- ;* "addr" contains 32 bit address of breakpoint
- ;*--------------------------------------------------------------*
- public _DPMIsetBreak
- _DPMIsetBreak proc near
- push bp
- mov bp,sp
- call _DPMIprotectedMode
- mov dx,word ptr [bp][4] ; set size and type
- mov cx,word ptr [bp][4+2] ; Move 32 bit "addr" to BX:CX
- mov bx,word ptr [bp][4+2+2] ; Move 32 bit "addr" to BX:CX
- mov ax,0B00h ; Set debug watch point
- int 31h
- jnc short @@done_DPMIsetBreak
- mov bx,-1
- @@done_DPMIsetBreak:
- push bx
- call _DPMIrealMode
- pop ax
- pop bp
- ret
- _DPMIsetBreak endp
-
- ;*--------------------------------------------------------------*
- ;* Syntax:
- ;* int DPMIcancelBreak(int handle);
- ;* Argument(s):
- ;* "handle" contains handle number to cancel and return state
- ;*--------------------------------------------------------------*
- public _DPMIcancelBreak
- _DPMIcancelBreak proc near
- push bp
- mov bp,sp
- call _DPMIprotectedMode
- mov bx,word ptr [bp][4] ; watchpoint handle
- mov ax,0B02h ; Get debug watch point state
- int 31h
- jnc short @@ok_DPMIcancelBreak
- xor ax,ax ;Not active if error
- @@ok_DPMIcancelBreak:
- and ax,1 ;Clear all but low bit
- push ax ;Watch point execution state
- mov ax,0B01h ;Clear debug watch point state
- int 31h
- call _DPMIrealMode
- pop ax
- pop bp
- ret
- _DPMIcancelBreak endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void Pmemget(word16 sel, word32 off, void* addr, word16 bytes)
- ;* Argument(s):
- ;* "sel"
- ;* "off"
- ;* "addr"
- ;* "bytes"
- ;*--------------------------------------------------------------*
- public _Pmemget
- _Pmemget proc near
- push bp
- mov bp,sp
- push si
- push di
- call _DPMIprotectedMode
- push ds
- push es
- mov ax,ds ; ES = curr DS (16 bit area)
- mov es,ax
- mov ds,word ptr [bp][4] ; Move 32 bit "sel" to DS
- mov esi,dword ptr [bp][4+2] ; Move 32 bit "off" to ESI
- movzx edi,word ptr [bp][4+2+4] ; 16 bit "addr" (ES:EDI)
- move_common:
- cld
- movzx ecx,word ptr [bp][4+2+4+2] ; "bytes"
- shr cx,2 ; Get multiple of 4
- jcxz short @@little_Pmemmove
- db 67h ; Use esi, edi (32 bit)
- rep movsd
- @@little_Pmemmove:
- movzx ecx,word ptr [bp][4+2+4+2] ; "bytes"
- and cx,3 ; Get remainder of 4
- jcxz short @@done_Pmemmove
- db 67h ; Use esi, edi (32 bit)
- rep movsb
- @@done_Pmemmove:
- pop es
- pop ds
- call _DPMIrealMode
- pop di
- pop si
- pop bp
- ret
- _Pmemget endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void Pmemput(word16 sel, word32 off, const void* addr, word16 bytes)
- ;* Argument(s):
- ;* "sel"
- ;* "off"
- ;* "addr"
- ;* "bytes"
- ;*--------------------------------------------------------------*
- public _Pmemput
- _Pmemput proc near
- push bp
- mov bp,sp
- push si
- push di
- call _DPMIprotectedMode
- push ds ; Not modified but common pop
- push es
- mov es,word ptr [bp][4] ; move 32 bit "sel" to ES
- mov edi,dword ptr [bp][4+2] ; move 32 bit "off" to EDI
- movzx esi,word ptr [bp][4+2+4] ; 16 bit "addr" (DS:ESI)
- jmp short move_common
- _Pmemput endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* void Pmemset(word16 sel, word32 off, word8 value, word32 bytes)
- ;* "sel"
- ;* "off"
- ;* "value"
- ;* "bytes"
- ;*--------------------------------------------------------------*
- public _Pmemset
- _Pmemset proc near
- push bp
- mov bp,sp
- push di
- call _DPMIprotectedMode
- push es
- mov es,word ptr [bp][4] ; "sel"
- mov edi,dword ptr [bp][4+2] ; "off"
- mov ax,word ptr [bp][4+2+4] ; "value"
- mov ah,al
- push ax
- push ax
- pop eax
- cld
- mov ecx,dword ptr [bp][4+2+4+2] ; "bytes"
- shr ecx,2
- jecxz short @@little_Pmemset
- db 67h ; edi
- rep stosd
- @@little_Pmemset:
- mov ecx,dword ptr [bp][4+2+4+2] ; "bytes"
- and ecx,3
- jcxz short @@done_Pmemset
- db 67h ; edi
- rep stosb
- @@done_Pmemset:
- pop es
- call _DPMIrealMode
- pop di
- pop bp
- ret
- _Pmemset endp
-
- ;*--------------------------------------------------------------*
- ;*
- ;* Syntax:
- ;* word16 Pmemscan(word16 sel, word32 off, word8 value, word16 bytes)
- ;* "sel"
- ;* "off"
- ;* "value"
- ;* "bytes"
- ;*--------------------------------------------------------------*
- public _Pmemscan
- _Pmemscan proc near
- push bp
- mov bp,sp
- push di
- call _DPMIprotectedMode
- push es
- mov es,word ptr [bp][4] ; "sel"
- mov edi,dword ptr [bp][4+2] ; "off"
- mov ax,word ptr [bp][4+2+4] ; "value"
- cld
- movzx ecx,word ptr [bp][4+2+4+2] ; "bytes"
- db 67h ; edi
- repne scasb
- mov di,0
- jne short @@done_Pmemscan
- mov di,word ptr [bp][4+2+4+2] ; "bytes"
- sub di,cx
- @@done_Pmemscan:
- pop es
- call _DPMIrealMode
- mov ax,di
- pop di
- pop bp
- ret
- _Pmemscan endp
-
- end_code16
- ;*--------------------------------------------------------------*
- end
-