summaryrefslogtreecommitdiffstats
path: root/board/MAI/bios_emulator/scitech/src/pm/dos
diff options
context:
space:
mode:
Diffstat (limited to 'board/MAI/bios_emulator/scitech/src/pm/dos')
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/_event.asm194
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/_lztimer.asm438
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/_pm.asm656
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/_pmdos.asm1105
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/_vflat.asm652
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/cpuinfo.c72
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/event.c494
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/oshdr.h29
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/pm.c2243
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/pmdos.c1637
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/vflat.c251
-rw-r--r--board/MAI/bios_emulator/scitech/src/pm/dos/ztimer.c111
12 files changed, 0 insertions, 7882 deletions
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/_event.asm b/board/MAI/bios_emulator/scitech/src/pm/dos/_event.asm
deleted file mode 100644
index 36dcaab67b..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/_event.asm
+++ /dev/null
@@ -1,194 +0,0 @@
-;****************************************************************************
-;*
-;* SciTech Multi-platform Graphics Library
-;*
-;* ========================================================================
-;*
-;* The contents of this file are subject to the SciTech MGL Public
-;* License Version 1.0 (the "License"); you may not use this file
-;* except in compliance with the License. You may obtain a copy of
-;* the License at http://www.scitechsoft.com/mgl-license.txt
-;*
-;* Software distributed under the License is distributed on an
-;* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-;* implied. See the License for the specific language governing
-;* rights and limitations under the License.
-;*
-;* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-;*
-;* The Initial Developer of the Original Code is SciTech Software, Inc.
-;* All Rights Reserved.
-;*
-;* ========================================================================
-;*
-;* Language: 80386 Assembler
-;* Environment: IBM PC (MS DOS)
-;*
-;* Description: Assembly language support routines for the event module.
-;*
-;****************************************************************************
-
- ideal
-
-include "scitech.mac" ; Memory model macros
-
-ifdef flatmodel
-
-header _event ; Set up memory model
-
-begdataseg _event
-
- cextern _EVT_biosPtr,DPTR
-
-ifdef USE_NASM
-%define KB_HEAD WORD esi+01Ah ; Keyboard buffer head in BIOS data area
-%define KB_TAIL WORD esi+01Ch ; Keyboard buffer tail in BIOS data area
-%define KB_START WORD esi+080h ; Start of keyboard buffer in BIOS data area
-%define KB_END WORD esi+082h ; End of keyboard buffer in BIOS data area
-else
-KB_HEAD EQU WORD esi+01Ah ; Keyboard buffer head in BIOS data area
-KB_TAIL EQU WORD esi+01Ch ; Keyboard buffer tail in BIOS data area
-KB_START EQU WORD esi+080h ; Start of keyboard buffer in BIOS data area
-KB_END EQU WORD esi+082h ; End of keyboard buffer in BIOS data area
-endif
-
-enddataseg _event
-
-begcodeseg _event ; Start of code segment
-
- cpublic _EVT_codeStart
-
-;----------------------------------------------------------------------------
-; int _EVT_getKeyCode(void)
-;----------------------------------------------------------------------------
-; Returns the key code for the next available key by extracting it from
-; the BIOS keyboard buffer.
-;----------------------------------------------------------------------------
-cprocstart _EVT_getKeyCode
-
- enter_c
-
- mov esi,[_EVT_biosPtr]
- xor ebx,ebx
- xor eax,eax
- mov bx,[KB_HEAD]
- cmp bx,[KB_TAIL]
- jz @@Done
- xor eax,eax
- mov ax,[esi+ebx] ; EAX := character from keyboard buffer
- inc _bx
- inc _bx
- cmp bx,[KB_END] ; Hit the end of the keyboard buffer?
- jl @@1
- mov bx,[KB_START]
-@@1: mov [KB_HEAD],bx ; Update keyboard buffer head pointer
-
-@@Done: leave_c
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void _EVT_pumpMessages(void)
-;----------------------------------------------------------------------------
-; This function would normally do nothing, however due to strange bugs
-; in the Windows 3.1 and OS/2 DOS boxes, we don't get any hardware keyboard
-; interrupts unless we periodically call the BIOS keyboard functions. Hence
-; this function gets called every time that we check for events, and works
-; around this problem (in essence it tells the DOS VDM to pump the
-; keyboard events to our program ;-).
-;
-; Note that this bug is not present under Win 9x DOS boxes.
-;----------------------------------------------------------------------------
-cprocstart _EVT_pumpMessages
-
- mov ah,11h ; Function - Check keyboard status
- int 16h ; Call BIOS
-
- mov ax, 0Bh ; Reset Move Mouse
- int 33h
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; int _EVT_disableInt(void);
-;----------------------------------------------------------------------------
-; Return processor interrupt status and disable interrupts.
-;----------------------------------------------------------------------------
-cprocstart _EVT_disableInt
-
- pushf ; Put flag word on stack
- cli ; Disable interrupts!
- pop eax ; deposit flag word in return register
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void _EVT_restoreInt(int ps);
-;----------------------------------------------------------------------------
-; Restore processor interrupt status.
-;----------------------------------------------------------------------------
-cprocstart _EVT_restoreInt
-
- ARG ps:UINT
-
- push ebp
- mov ebp,esp ; Set up stack frame
- push [DWORD ps]
- popf ; Restore processor status (and interrupts)
- pop ebp
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; int EVT_rdinx(int port,int index)
-;----------------------------------------------------------------------------
-; Reads an indexed register value from an I/O port.
-;----------------------------------------------------------------------------
-cprocstart EVT_rdinx
-
- ARG port:UINT, index:UINT
-
- push ebp
- mov ebp,esp
- mov edx,[port]
- mov al,[BYTE index]
- out dx,al
- inc dx
- in al,dx
- movzx eax,al
- pop ebp
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void EVT_wrinx(int port,int index,int value)
-;----------------------------------------------------------------------------
-; Writes an indexed register value to an I/O port.
-;----------------------------------------------------------------------------
-cprocstart EVT_wrinx
-
- ARG port:UINT, index:UINT, value:UINT
-
- push ebp
- mov ebp,esp
- mov edx,[port]
- mov al,[BYTE index]
- mov ah,[BYTE value]
- out dx,ax
- pop ebp
- ret
-
-cprocend
-
- cpublic _EVT_codeEnd
-
-endcodeseg _event
-
-endif
-
- END ; End of module
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/_lztimer.asm b/board/MAI/bios_emulator/scitech/src/pm/dos/_lztimer.asm
deleted file mode 100644
index a4a9c7916e..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/_lztimer.asm
+++ /dev/null
@@ -1,438 +0,0 @@
-;****************************************************************************
-;*
-;* SciTech OS Portability Manager Library
-;*
-;* ========================================================================
-;*
-;* The contents of this file are subject to the SciTech MGL Public
-;* License Version 1.0 (the "License"); you may not use this file
-;* except in compliance with the License. You may obtain a copy of
-;* the License at http://www.scitechsoft.com/mgl-license.txt
-;*
-;* Software distributed under the License is distributed on an
-;* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-;* implied. See the License for the specific language governing
-;* rights and limitations under the License.
-;*
-;* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-;*
-;* The Initial Developer of the Original Code is SciTech Software, Inc.
-;* All Rights Reserved.
-;*
-;* ========================================================================
-;*
-;* Language: NASM or TASM Assembler
-;* Environment: IBM PC (MS DOS)
-;*
-;* Description: Uses the 8253 timer and the BIOS time-of-day count to time
-;* the performance of code that takes less than an hour to
-;* execute.
-;*
-;* The routines in this package only works with interrupts
-;* enabled, and in fact will explicitly turn interrupts on
-;* in order to ensure we get accurate results from the timer.
-;*
-;* Externally 'C' callable routines:
-;*
-;* LZ_timerOn: Saves the BIOS time of day count and starts the
-;* long period Zen Timer.
-;*
-;* LZ_timerLap: Latches the current count, and keeps the timer running
-;*
-;* LZ_timerOff: Stops the long-period Zen Timer and saves the timer
-;* count and the BIOS time of day count.
-;*
-;* LZ_timerCount: Returns an unsigned long representing the timed count
-;* in microseconds. If more than an hour passed during
-;* the timing interval, LZ_timerCount will return the
-;* value 0xFFFFFFFF (an invalid count).
-;*
-;* Note: If either more than an hour passes between calls to LZ_timerOn
-;* and LZ_timerOff, an error is reported. For timing code that takes
-;* more than a few minutes to execute, use the low resolution
-;* Ultra Long Period Zen Timer code, which should be accurate
-;* enough for most purposes.
-;*
-;* Note: Each block of code being timed should ideally be run several
-;* times, with at least two similar readings required to
-;* establish a true measurement, in order to eliminate any
-;* variability caused by interrupts.
-;*
-;* Note: Interrupts must not be disabled for more than 54 ms at a
-;* stretch during the timing interval. Because interrupts are
-;* enabled, key, mice, and other devices that generate interrupts
-;* should not be used during the timing interval.
-;*
-;* Note: Any extra code running off the timer interrupt (such as
-;* some memory resident utilities) will increase the time
-;* measured by the Zen Timer.
-;*
-;* Note: These routines can introduce inaccuracies of up to a few
-;* tenths of a second into the system clock count for each
-;* code section being timed. Consequently, it's a good idea to
-;* reboot at the conclusion of timing sessions. (The
-;* battery-backed clock, if any, is not affected by the Zen
-;* timer.)
-;*
-;* All registers and all flags are preserved by all routines, except
-;* interrupts which are always turned on
-;*
-;****************************************************************************
-
- IDEAL
-
-include "scitech.mac"
-
-;****************************************************************************
-;
-; Equates used by long period Zen Timer
-;
-;****************************************************************************
-
-; Base address of 8253 timer chip
-
-BASE_8253 equ 40h
-
-; The address of the timer 0 count registers in the 8253
-
-TIMER_0_8253 equ BASE_8253 + 0
-
-; The address of the mode register in the 8253
-
-MODE_8253 equ BASE_8253 + 3
-
-; The address of the BIOS timer count variable in the BIOS data area.
-
-TIMER_COUNT equ 6Ch
-
-; Macro to delay briefly to ensure that enough time has elapsed between
-; successive I/O accesses so that the device being accessed can respond
-; to both accesses even on a very fast PC.
-
-ifdef USE_NASM
-%macro DELAY 0
- jmp short $+2
- jmp short $+2
- jmp short $+2
-%endmacro
-else
-macro DELAY
- jmp short $+2
- jmp short $+2
- jmp short $+2
-endm
-endif
-
-header _lztimer
-
-begdataseg _lztimer
-
- cextern _ZTimerBIOSPtr,DPTR
-
-StartBIOSCount dd 0 ; Starting BIOS count dword
-EndBIOSCount dd 0 ; Ending BIOS count dword
-EndTimedCount dw 0 ; Timer 0 count at the end of timing period
-
-enddataseg _lztimer
-
-begcodeseg _lztimer ; Start of code segment
-
-;----------------------------------------------------------------------------
-; void LZ_timerOn(void);
-;----------------------------------------------------------------------------
-; Starts the Long period Zen timer counting.
-;----------------------------------------------------------------------------
-cprocstart LZ_timerOn
-
-; Set the timer 0 of the 8253 to mode 2 (divide-by-N), to cause
-; linear counting rather than count-by-two counting. Also stops
-; timer 0 until the timer count is loaded, except on PS/2 computers.
-
- mov al,00110100b ; mode 2
- out MODE_8253,al
-
-; Set the timer count to 0, so we know we won't get another timer
-; interrupt right away. Note: this introduces an inaccuracy of up to 54 ms
-; in the system clock count each time it is executed.
-
- DELAY
- sub al,al
- out TIMER_0_8253,al ; lsb
- DELAY
- out TIMER_0_8253,al ; msb
-
-; Store the timing start BIOS count
-
- use_es
-ifdef flatmodel
- mov ebx,[_ZTimerBIOSPtr]
-else
- les bx,[_ZTimerBIOSPtr]
-endif
- cli ; No interrupts while we grab the count
- mov eax,[_ES _bx+TIMER_COUNT]
- sti
- mov [StartBIOSCount],eax
- unuse_es
-
-; Set the timer count to 0 again to start the timing interval.
-
- mov al,00110100b ; set up to load initial
- out MODE_8253,al ; timer count
- DELAY
- sub al,al
- out TIMER_0_8253,al ; load count lsb
- DELAY
- out TIMER_0_8253,al ; load count msb
-
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void LZ_timerOff(void);
-;----------------------------------------------------------------------------
-; Stops the long period Zen timer and saves count.
-;----------------------------------------------------------------------------
-cprocstart LZ_timerOff
-
-; Latch the timer count.
-
- mov al,00000000b ; latch timer 0
- out MODE_8253,al
- cli ; Stop the BIOS count
-
-; Read the BIOS count. (Since interrupts are disabled, the BIOS
-; count won't change).
-
- use_es
-ifdef flatmodel
- mov ebx,[_ZTimerBIOSPtr]
-else
- les bx,[_ZTimerBIOSPtr]
-endif
- mov eax,[_ES _bx+TIMER_COUNT]
- mov [EndBIOSCount],eax
- unuse_es
-
-; Read out the count we latched earlier.
-
- in al,TIMER_0_8253 ; least significant byte
- DELAY
- mov ah,al
- in al,TIMER_0_8253 ; most significant byte
- xchg ah,al
- neg ax ; Convert from countdown remaining
- ; to elapsed count
- mov [EndTimedCount],ax
- sti ; Let the BIOS count continue
-
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; unsigned long LZ_timerLap(void)
-;----------------------------------------------------------------------------
-; Latches the current count and converts it to a microsecond timing value,
-; but leaves the timer still running. We dont check for and overflow,
-; where the time has gone over an hour in this routine, since we want it
-; to execute as fast as possible.
-;----------------------------------------------------------------------------
-cprocstart LZ_timerLap
-
- push ebx ; Save EBX for 32 bit code
-
-; Latch the timer count.
-
- mov al,00000000b ; latch timer 0
- out MODE_8253,al
- cli ; Stop the BIOS count
-
-; Read the BIOS count. (Since interrupts are disabled, the BIOS
-; count wont change).
-
- use_es
-ifdef flatmodel
- mov ebx,[_ZTimerBIOSPtr]
-else
- les bx,[_ZTimerBIOSPtr]
-endif
- mov eax,[_ES _bx+TIMER_COUNT]
- mov [EndBIOSCount],eax
- unuse_es
-
-; Read out the count we latched earlier.
-
- in al,TIMER_0_8253 ; least significant byte
- DELAY
- mov ah,al
- in al,TIMER_0_8253 ; most significant byte
- xchg ah,al
- neg ax ; Convert from countdown remaining
- ; to elapsed count
- mov [EndTimedCount],ax
- sti ; Let the BIOS count continue
-
-; See if a midnight boundary has passed and adjust the finishing BIOS
-; count by the number of ticks in 24 hours. We wont be able to detect
-; more than 24 hours, but at least we can time across a midnight
-; boundary
-
- mov eax,[EndBIOSCount] ; Is end < start?
- cmp eax,[StartBIOSCount]
- jae @@CalcBIOSTime ; No, calculate the time taken
-
-; Adjust the finishing time by adding the number of ticks in 24 hours
-; (1573040).
-
- add [DWORD EndBIOSCount],1800B0h
-
-; Convert the BIOS time to microseconds
-
-@@CalcBIOSTime:
- mov ax,[WORD EndBIOSCount]
- sub ax,[WORD StartBIOSCount]
- mov dx,54925 ; Number of microseconds each
- ; BIOS count represents.
- mul dx
- mov bx,ax ; set aside BIOS count in
- mov cx,dx ; microseconds
-
-; Convert timer count to microseconds
-
- push _si
- mov ax,[EndTimedCount]
- mov si,8381
- mul si
- mov si,10000
- div si ; * 0.8381 = * 8381 / 10000
- pop _si
-
-; Add the timer and BIOS counts together to get an overall time in
-; microseconds.
-
- add ax,bx
- adc cx,0
-ifdef flatmodel
- shl ecx,16
- mov cx,ax
- mov eax,ecx ; EAX := timer count
-else
- mov dx,cx
-endif
- pop ebx ; Restore EBX for 32 bit code
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; unsigned long LZ_timerCount(void);
-;----------------------------------------------------------------------------
-; Returns an unsigned long representing the net time in microseconds.
-;
-; If an hour has passed while timing, we return 0xFFFFFFFF as the count
-; (which is not a possible count in itself).
-;----------------------------------------------------------------------------
-cprocstart LZ_timerCount
-
- push ebx ; Save EBX for 32 bit code
-
-; See if a midnight boundary has passed and adjust the finishing BIOS
-; count by the number of ticks in 24 hours. We wont be able to detect
-; more than 24 hours, but at least we can time across a midnight
-; boundary
-
- mov eax,[EndBIOSCount] ; Is end < start?
- cmp eax,[StartBIOSCount]
- jae @@CheckForHour ; No, check for hour passing
-
-; Adjust the finishing time by adding the number of ticks in 24 hours
-; (1573040).
-
- add [DWORD EndBIOSCount],1800B0h
-
-; See if more than an hour passed during timing. If so, notify the user.
-
-@@CheckForHour:
- mov ax,[WORD StartBIOSCount+2]
- cmp ax,[WORD EndBIOSCount+2]
- jz @@CalcBIOSTime ; Hour count didn't change, so
- ; everything is fine
-
- inc ax
- cmp ax,[WORD EndBIOSCount+2]
- jnz @@TestTooLong ; Two hour boundaries passed, so the
- ; results are no good
- mov ax,[WORD EndBIOSCount]
- cmp ax,[WORD StartBIOSCount]
- jb @@CalcBIOSTime ; a single hour boundary passed. That's
- ; OK, so long as the total time wasn't
- ; more than an hour.
-
-; Over an hour elapsed passed during timing, which renders
-; the results invalid. Notify the user. This misses the case where a
-; multiple of 24 hours has passed, but we'll rely on the perspicacity of
-; the user to detect that case :-).
-
-@@TestTooLong:
-ifdef flatmodel
- mov eax,0FFFFFFFFh
-else
- mov ax,0FFFFh
- mov dx,0FFFFh
-endif
- jmp short @@Done
-
-; Convert the BIOS time to microseconds
-
-@@CalcBIOSTime:
- mov ax,[WORD EndBIOSCount]
- sub ax,[WORD StartBIOSCount]
- mov dx,54925 ; Number of microseconds each
- ; BIOS count represents.
- mul dx
- mov bx,ax ; set aside BIOS count in
- mov cx,dx ; microseconds
-
-; Convert timer count to microseconds
-
- push _si
- mov ax,[EndTimedCount]
- mov si,8381
- mul si
- mov si,10000
- div si ; * 0.8381 = * 8381 / 10000
- pop _si
-
-; Add the timer and BIOS counts together to get an overall time in
-; microseconds.
-
- add ax,bx
- adc cx,0
-ifdef flatmodel
- shl ecx,16
- mov cx,ax
- mov eax,ecx ; EAX := timer count
-else
- mov dx,cx
-endif
-
-@@Done: pop ebx ; Restore EBX for 32 bit code
- ret
-
-cprocend
-
-cprocstart LZ_disable
- cli
- ret
-cprocend
-
-cprocstart LZ_enable
- sti
- ret
-cprocend
-
-endcodeseg _lztimer
-
- END
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/_pm.asm b/board/MAI/bios_emulator/scitech/src/pm/dos/_pm.asm
deleted file mode 100644
index 42b5cf3692..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/_pm.asm
+++ /dev/null
@@ -1,656 +0,0 @@
-;****************************************************************************
-;*
-;* SciTech OS Portability Manager Library
-;*
-;* ========================================================================
-;*
-;* The contents of this file are subject to the SciTech MGL Public
-;* License Version 1.0 (the "License"); you may not use this file
-;* except in compliance with the License. You may obtain a copy of
-;* the License at http://www.scitechsoft.com/mgl-license.txt
-;*
-;* Software distributed under the License is distributed on an
-;* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-;* implied. See the License for the specific language governing
-;* rights and limitations under the License.
-;*
-;* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-;*
-;* The Initial Developer of the Original Code is SciTech Software, Inc.
-;* All Rights Reserved.
-;*
-;* ========================================================================
-;*
-;* Language: 80386 Assembler, TASM 4.0 or NASM
-;* Environment: IBM PC Real mode and 16/32 bit protected mode
-;*
-;* Description: Low level assembly support for the PM library specific to
-;* MSDOS.
-;*
-;****************************************************************************
-
- IDEAL
-
-include "scitech.mac" ; Memory model macros
-
-header _pmdos ; Set up memory model
-
-begdataseg _pmdos
-
-ifndef flatmodel
-
-struc rmregs_s
-ax dw ?
-ax_high dw ?
-bx dw ?
-bx_high dw ?
-cx dw ?
-cx_high dw ?
-dx dw ?
-dx_high dw ?
-si dw ?
-si_high dw ?
-di dw ?
-di_high dw ?
-cflag dw ?
-cflag_high dw ?
-ends rmregs_s
-RMREGS = (rmregs_s PTR es:bx)
-
-struc rmsregs_s
-es dw ?
-cs dw ?
-ss dw ?
-ds dw ?
-ends rmsregs_s
-RMSREGS = (rmsregs_s PTR es:bx)
-
-endif ; !flatmodel
-
-ifdef flatmodel
- cextern _PM_savedDS,USHORT
- cextern _PM_VXD_off,UINT
- cextern _PM_VXD_sel,UINT
-ifdef DOS4GW
- cextern _PM_haveCauseWay,UINT
-endif
-endif
-intel_id db "GenuineIntel" ; Intel vendor ID
-
-PMHELP_GETPDB EQU 0026h
-PMHELP_FLUSHTLB EQU 0027h
-
-enddataseg _pmdos
-
-P586
-
-begcodeseg _pmdos ; Start of code segment
-
-ifndef flatmodel
-
-;----------------------------------------------------------------------------
-; void PM_callRealMode(unsigned s,unsigned o, RMREGS *regs,
-; RMSREGS *sregs)
-;----------------------------------------------------------------------------
-; Calls a real mode procedure, loading the appropriate registers values
-; from the passed in structures. Only the DS and ES register are loaded
-; from the SREGS structure.
-;----------------------------------------------------------------------------
-cprocstart PM_callRealMode
-
- ARG s:WORD, o:WORD, regs:DWORD, sregs:DWORD
-
- LOCAL addr:DWORD, bxVal:WORD, esVal:WORD, flags:WORD = LocalSize
-
- enter_c
- push ds
- push es
-
- mov ax,[o] ; Build the address to call in 'addr'
- mov [WORD addr],ax
- mov ax,[s]
- mov [WORD addr+2],ax
-
- les bx,[sregs]
- mov ax,[RMSREGS.ds]
- mov ds,ax ; DS := passed in value
- mov ax,[RMSREGS.es]
- mov [esVal],ax
- les bx,[regs]
- mov ax,[RMREGS.bx]
- mov [bxVal],ax
- mov ax,[RMREGS.ax] ; AX := passed in value
- mov cx,[RMREGS.cx] ; CX := passed in value
- mov dx,[RMREGS.dx] ; DX := passed in value
- mov si,[RMREGS.si] ; SI := passed in value
- mov di,[RMREGS.di] ; DI := passed in value
- push bp
- push [esVal]
- pop es ; ES := passed in value
- mov bx,[bxVal] ; BX := passed in value
-
- call [addr] ; Call the specified routine
-
- pushf ; Save flags for later
- pop [flags]
-
- pop bp
- push es
- pop [esVal]
- push bx
- pop [bxVal]
- les bx,[sregs]
- push ds
- pop [RMSREGS.ds] ; Save value of DS
- push [esVal]
- pop [RMSREGS.es] ; Save value of ES
- les bx,[regs]
- mov [RMREGS.ax],ax ; Save value of AX
- mov [RMREGS.cx],cx ; Save value of CX
- mov [RMREGS.dx],dx ; Save value of DX
- mov [RMREGS.si],si ; Save value of SI
- mov [RMREGS.di],di ; Save value of DI
- mov ax,[flags] ; Return flags
- and ax,1h ; Isolate carry flag
- mov [RMREGS.cflag],ax ; Save carry flag status
- mov ax,[bxVal]
- mov [RMREGS.bx],ax ; Save value of BX
-
- pop es
- pop ds
- leave_c
- ret
-
-cprocend
-
-endif
-
-;----------------------------------------------------------------------------
-; void PM_segread(PMSREGS *sregs)
-;----------------------------------------------------------------------------
-; Read the current value of all segment registers
-;----------------------------------------------------------------------------
-cprocstartdll16 PM_segread
-
- ARG sregs:DPTR
-
- enter_c
-
- mov ax,es
- _les _si,[sregs]
- mov [_ES _si],ax
- mov [_ES _si+2],cs
- mov [_ES _si+4],ss
- mov [_ES _si+6],ds
- mov [_ES _si+8],fs
- mov [_ES _si+10],gs
-
- leave_c
- ret
-
-cprocend
-
-; Create a table of the 256 different interrupt calls that we can jump
-; into
-
-ifdef USE_NASM
-
-%assign intno 0
-
-intTable:
-%rep 256
- db 0CDh
- db intno
-%assign intno intno + 1
- ret
- nop
-%endrep
-
-else
-
-intno = 0
-
-intTable:
- REPT 256
- db 0CDh
- db intno
-intno = intno + 1
- ret
- nop
- ENDM
-
-endif
-
-;----------------------------------------------------------------------------
-; _PM_genInt - Generate the appropriate interrupt
-;----------------------------------------------------------------------------
-cprocnear _PM_genInt
-
- push _ax ; Save _ax
- push _bx ; Save _bx
-ifdef flatmodel
- mov ebx,[UINT esp+12] ; EBX := interrupt number
-else
- mov bx,sp ; Make sure ESP is zeroed
- mov bx,[UINT ss:bx+6] ; BX := interrupt number
-endif
- mov _ax,offset intTable ; Point to interrupt generation table
- shl _bx,2 ; _BX := index into table
- add _ax,_bx ; _AX := pointer to interrupt code
-ifdef flatmodel
- xchg eax,[esp+4] ; Restore eax, and set for int
-else
- mov bx,sp
- xchg ax,[ss:bx+2] ; Restore ax, and set for int
-endif
- pop _bx ; restore _bx
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; int PM_int386x(int intno, PMREGS *in, PMREGS *out,PMSREGS *sregs)
-;----------------------------------------------------------------------------
-; Issues a software interrupt in protected mode. This routine has been
-; written to allow user programs to load CS and DS with different values
-; other than the default.
-;----------------------------------------------------------------------------
-cprocstartdll16 PM_int386x
-
- ARG intno:UINT, inptr:DPTR, outptr:DPTR, sregs:DPTR
-
- LOCAL flags:UINT, sv_ds:UINT, sv_esi:ULONG = LocalSize
-
- enter_c
- push ds
- push es ; Save segment registers
- push fs
- push gs
-
- _lds _si,[sregs] ; DS:_SI -> Load segment registers
- mov es,[_si]
- mov bx,[_si+6]
- mov [sv_ds],_bx ; Save value of user DS on stack
- mov fs,[_si+8]
- mov gs,[_si+10]
-
- _lds _si,[inptr] ; Load CPU registers
- mov eax,[_si]
- mov ebx,[_si+4]
- mov ecx,[_si+8]
- mov edx,[_si+12]
- mov edi,[_si+20]
- mov esi,[_si+16]
-
- push ds ; Save value of DS
- push _bp ; Some interrupts trash this!
- clc ; Generate the interrupt
- push [UINT intno]
- mov ds,[WORD sv_ds] ; Set value of user's DS selector
- call _PM_genInt
- pop _bp ; Pop intno from stack (flags unchanged)
- pop _bp ; Restore value of stack frame pointer
- pop ds ; Restore value of DS
-
- pushf ; Save flags for later
- pop [UINT flags]
- push esi ; Save ESI for later
- pop [DWORD sv_esi]
- push ds ; Save DS for later
- pop [UINT sv_ds]
-
- _lds _si,[outptr] ; Save CPU registers
- mov [_si],eax
- mov [_si+4],ebx
- mov [_si+8],ecx
- mov [_si+12],edx
- push [DWORD sv_esi]
- pop [DWORD _si+16]
- mov [_si+20],edi
-
- mov _bx,[flags] ; Return flags
- and ebx,1h ; Isolate carry flag
- mov [_si+24],ebx ; Save carry flag status
-
- _lds _si,[sregs] ; Save segment registers
- mov [_si],es
- mov _bx,[sv_ds]
- mov [_si+6],bx ; Get returned DS from stack
- mov [_si+8],fs
- mov [_si+10],gs
-
- pop gs ; Restore segment registers
- pop fs
- pop es
- pop ds
- leave_c
- ret
-
-cprocend
-
-ifndef flatmodel
-_PM_savedDS dw _DATA ; Saved value of DS
-endif
-
-;----------------------------------------------------------------------------
-; void PM_saveDS(void)
-;----------------------------------------------------------------------------
-; Save the value of DS into a section of the code segment, so that we can
-; quickly load this value at a later date in the PM_loadDS() routine from
-; inside interrupt handlers etc. The method to do this is different
-; depending on the DOS extender being used.
-;----------------------------------------------------------------------------
-cprocstartdll16 PM_saveDS
-
-ifdef flatmodel
- mov [_PM_savedDS],ds ; Store away in data segment
-endif
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void PM_loadDS(void)
-;----------------------------------------------------------------------------
-; Routine to load the DS register with the default value for the current
-; DOS extender. Only the DS register is loaded, not the ES register, so
-; if you wish to call C code, you will need to also load the ES register
-; in 32 bit protected mode.
-;----------------------------------------------------------------------------
-cprocstartdll16 PM_loadDS
-
- mov ds,[cs:_PM_savedDS] ; We can access the proper DS through CS
- ret
-
-cprocend
-
-ifdef flatmodel
-
-;----------------------------------------------------------------------------
-; ibool DPMI_allocateCallback(void (*pmcode)(), void *rmregs, long *RMCB)
-;----------------------------------------------------------------------------
-cprocstart _DPMI_allocateCallback
-
- ARG pmcode:CPTR, rmregs:DPTR, RMCB:DPTR
-
- enter_c
- push ds
- push es
-
- push cs
- pop ds
- mov esi,[pmcode] ; DS:ESI -> protected mode code to call
- mov edi,[rmregs] ; ES:EDI -> real mode register buffer
- mov ax,303h ; AX := allocate realmode callback function
- int 31h
- mov eax,0 ; Return failure!
- jc @@Fail
-
- mov eax,[RMCB]
- shl ecx,16
- mov cx,dx
- mov [es:eax],ecx ; Return real mode address
- mov eax,1 ; Return success!
-
-@@Fail: pop es
- pop ds
- leave_c
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void DPMI_freeCallback(long RMCB)
-;----------------------------------------------------------------------------
-cprocstart _DPMI_freeCallback
-
- ARG RMCB:ULONG
-
- enter_c
-
- mov cx,[WORD RMCB+2]
- mov dx,[WORD RMCB] ; CX:DX := real mode callback
- mov ax,304h
- int 31h
-
- leave_c
- ret
-
-cprocend
-
-endif
-
-; Macro to delay briefly to ensure that enough time has elapsed between
-; successive I/O accesses so that the device being accessed can respond
-; to both accesses even on a very fast PC.
-
-ifdef USE_NASM
-%macro DELAY 0
- jmp short $+2
- jmp short $+2
- jmp short $+2
-%endmacro
-%macro IODELAYN 1
-%rep %1
- DELAY
-%endrep
-%endmacro
-else
-macro DELAY
- jmp short $+2
- jmp short $+2
- jmp short $+2
-endm
-macro IODELAYN N
- rept N
- DELAY
- endm
-endm
-endif
-
-;----------------------------------------------------------------------------
-; uchar _PM_readCMOS(int index)
-;----------------------------------------------------------------------------
-; Read the value of a specific CMOS register. We do this with both
-; normal interrupts and NMI disabled.
-;----------------------------------------------------------------------------
-cprocstart _PM_readCMOS
-
- ARG index:UINT
-
- push _bp
- mov _bp,_sp
- pushfd
- mov al,[BYTE index]
- or al,80h ; Add disable NMI flag
- cli
- out 70h,al
- IODELAYN 5
- in al,71h
- mov ah,al
- xor al,al
- IODELAYN 5
- out 70h,al ; Re-enable NMI
- sti
- mov al,ah ; Return value in AL
- popfd
- pop _bp
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void _PM_writeCMOS(int index,uchar value)
-;----------------------------------------------------------------------------
-; Read the value of a specific CMOS register. We do this with both
-; normal interrupts and NMI disabled.
-;----------------------------------------------------------------------------
-cprocstart _PM_writeCMOS
-
- ARG index:UINT, value:UCHAR
-
- push _bp
- mov _bp,_sp
- pushfd
- mov al,[BYTE index]
- or al,80h ; Add disable NMI flag
- cli
- out 70h,al
- IODELAYN 5
- mov al,[value]
- out 71h,al
- xor al,al
- IODELAYN 5
- out 70h,al ; Re-enable NMI
- sti
- popfd
- pop _bp
- ret
-
-cprocend
-
-ifdef flatmodel
-
-;----------------------------------------------------------------------------
-; int _PM_pagingEnabled(void)
-;----------------------------------------------------------------------------
-; Returns 1 if paging is enabled, 0 if not or -1 if not at ring 0
-;----------------------------------------------------------------------------
-cprocstart _PM_pagingEnabled
-
- mov eax,-1
-ifdef DOS4GW
- mov cx,cs
- and ecx,3
- jz @@Ring0
- cmp [UINT _PM_haveCauseWay],0
- jnz @@Ring0
- jmp @@Exit
-
-@@Ring0:
- mov eax,cr0 ; Load CR0
- shr eax,31 ; Isolate paging enabled bit
-endif
-@@Exit: ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; _PM_getPDB - Return the Page Table Directory Base address
-;----------------------------------------------------------------------------
-cprocstart _PM_getPDB
-
-ifdef DOS4GW
- mov ax,cs
- and eax,3
- jz @@Ring0
- cmp [UINT _PM_haveCauseWay],0
- jnz @@Ring0
-endif
-
-; Call VxD if running at ring 3 in a DOS box
-
- cmp [WORD _PM_VXD_sel],0
- jz @@Fail
- mov eax,PMHELP_GETPDB
-ifdef USE_NASM
- call far dword [_PM_VXD_off]
-else
- call [FCPTR _PM_VXD_off]
-endif
- ret
-
-@@Ring0:
-ifdef DOS4GW
- mov eax,cr3
- and eax,0FFFFF000h
- ret
-endif
-@@Fail: xor eax,eax
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; PM_flushTLB - Flush the Translation Lookaside buffer
-;----------------------------------------------------------------------------
-cprocstart PM_flushTLB
-
- mov ax,cs
- and eax,3
- jz @@Ring0
-ifdef DOS4GW
- cmp [UINT _PM_haveCauseWay],0
- jnz @@Ring0
-endif
-
-; Call VxD if running at ring 3 in a DOS box
-
- cmp [WORD _PM_VXD_sel],0
- jz @@Fail
- mov eax,PMHELP_FLUSHTLB
-ifdef USE_NASM
- call far dword [_PM_VXD_off]
-else
- call [FCPTR _PM_VXD_off]
-endif
- ret
-
-@@Ring0:
-ifdef DOS4GW
- wbinvd ; Flush the CPU cache
- mov eax,cr3
- mov cr3,eax ; Flush the TLB
-endif
-@@Fail: ret
-
-cprocend
-
-endif
-
-;----------------------------------------------------------------------------
-; void _PM_VxDCall(VXD_regs far *r,uint off,uint sel);
-;----------------------------------------------------------------------------
-cprocstart _PM_VxDCall
-
- ARG r:DPTR, off:UINT, sel:UINT
-
- enter_c
-
-; Load all registers from the registers structure
-
- mov ebx,[r]
- mov eax,[ebx+0]
- mov ecx,[ebx+8]
- mov edx,[ebx+12]
- mov esi,[ebx+16]
- mov edi,[ebx+20]
- mov ebx,[ebx+4] ; Trashes BX structure pointer!
-
-; Call the VxD entry point (on stack)
-
-ifdef USE_NASM
- call far dword [off]
-else
- call [FCPTR off]
-endif
-
-; Save all registers back in the structure
-
- push ebx ; Push EBX onto stack for later
- mov ebx,[r]
- mov [ebx+0],eax
- mov [ebx+8],ecx
- mov [ebx+12],edx
- mov [ebx+16],esi
- mov [ebx+20],edi
- pop [DWORD ebx+4] ; Save value of EBX from stack
-
- leave_c
- ret
-
-cprocend
-
-endcodeseg _pmdos
-
- END ; End of module
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/_pmdos.asm b/board/MAI/bios_emulator/scitech/src/pm/dos/_pmdos.asm
deleted file mode 100644
index 5c741f346c..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/_pmdos.asm
+++ /dev/null
@@ -1,1105 +0,0 @@
-;****************************************************************************
-;*
-;* SciTech OS Portability Manager Library
-;*
-;* ========================================================================
-;*
-;* The contents of this file are subject to the SciTech MGL Public
-;* License Version 1.0 (the "License"); you may not use this file
-;* except in compliance with the License. You may obtain a copy of
-;* the License at http://www.scitechsoft.com/mgl-license.txt
-;*
-;* Software distributed under the License is distributed on an
-;* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-;* implied. See the License for the specific language governing
-;* rights and limitations under the License.
-;*
-;* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-;*
-;* The Initial Developer of the Original Code is SciTech Software, Inc.
-;* All Rights Reserved.
-;*
-;* ========================================================================
-;*
-;* Language: 80386 Assembler, TASM 4.0 or NASM
-;* Environment: IBM PC Real mode and 16/32 bit protected mode
-;*
-;* Description: Low level assembly support for the PM library specific to
-;* MSDOS interrupt handling.
-;*
-;****************************************************************************
-
- IDEAL
-
-include "scitech.mac" ; Memory model macros
-
-header _pmdos ; Set up memory model
-
-; Define the size of our local stacks. For real mode code they cant be
-; that big, but for 32 bit protected mode code we can make them nice and
-; large so that complex C functions can be used.
-
-ifdef flatmodel
-MOUSE_STACK EQU 4096
-TIMER_STACK EQU 4096
-KEY_STACK EQU 1024
-INT10_STACK EQU 1024
-IRQ_STACK EQU 1024
-else
-MOUSE_STACK EQU 1024
-TIMER_STACK EQU 512
-KEY_STACK EQU 256
-INT10_STACK EQU 256
-IRQ_STACK EQU 256
-endif
-
-ifdef USE_NASM
-
-; Macro to load DS and ES registers with correct value.
-
-%imacro LOAD_DS 0
-%ifdef flatmodel
- mov ds,[cs:_PM_savedDS]
- mov es,[cs:_PM_savedDS]
-%else
- push ax
- mov ax,_DATA
- mov ds,ax
- pop ax
-%endif
-%endmacro
-
-; Note that interrupts we disable interrupts during the following stack
-; %imacro for correct operation, but we do not enable them again. Normally
-; these %imacros are used within interrupt handlers so interrupts should
-; already be off. We turn them back on explicitly later if the user code
-; needs them to be back on.
-
-; Macro to switch to a new local stack.
-
-%imacro NEWSTK 1
- cli
- mov [seg_%1],ss
- mov [ptr_%1],_sp
- mov [TempSeg],ds
- mov ss,[TempSeg]
- mov _sp,offset %1
-%endmacro
-
-; %imacro to switch back to the old stack.
-
-%imacro RESTSTK 1
- cli
- mov ss,[seg_%1]
- mov _sp,[ptr_%1]
-%endmacro
-
-; %imacro to swap the current stack with the one saved away.
-
-%imacro SWAPSTK 1
- cli
- mov ax,ss
- xchg ax,[seg_%1]
- mov ss,ax
- xchg _sp,[ptr_%1]
-%endmacro
-
-else
-
-; Macro to load DS and ES registers with correct value.
-
-MACRO LOAD_DS
-ifdef flatmodel
- mov ds,[cs:_PM_savedDS]
- mov es,[cs:_PM_savedDS]
-else
- push ax
- mov ax,_DATA
- mov ds,ax
- pop ax
-endif
-ENDM
-
-; Note that interrupts we disable interrupts during the following stack
-; macro for correct operation, but we do not enable them again. Normally
-; these macros are used within interrupt handlers so interrupts should
-; already be off. We turn them back on explicitly later if the user code
-; needs them to be back on.
-
-; Macro to switch to a new local stack.
-
-MACRO NEWSTK stkname
- cli
- mov [seg_&stkname&],ss
- mov [ptr_&stkname&],_sp
- mov [TempSeg],ds
- mov ss,[TempSeg]
- mov _sp,offset stkname
-ENDM
-
-; Macro to switch back to the old stack.
-
-MACRO RESTSTK stkname
- cli
- mov ss,[seg_&stkname&]
- mov _sp,[ptr_&stkname&]
-ENDM
-
-; Macro to swap the current stack with the one saved away.
-
-MACRO SWAPSTK stkname
- cli
- mov ax,ss
- xchg ax,[seg_&stkname&]
- mov ss,ax
- xchg _sp,[ptr_&stkname&]
-ENDM
-
-endif
-
-begdataseg _pmdos
-
-ifdef flatmodel
- cextern _PM_savedDS,USHORT
-endif
- cextern _PM_critHandler,CPTR
- cextern _PM_breakHandler,CPTR
- cextern _PM_timerHandler,CPTR
- cextern _PM_rtcHandler,CPTR
- cextern _PM_keyHandler,CPTR
- cextern _PM_key15Handler,CPTR
- cextern _PM_mouseHandler,CPTR
- cextern _PM_int10Handler,CPTR
-
- cextern _PM_ctrlCPtr,DPTR
- cextern _PM_ctrlBPtr,DPTR
- cextern _PM_critPtr,DPTR
-
- cextern _PM_prevTimer,FCPTR
- cextern _PM_prevRTC,FCPTR
- cextern _PM_prevKey,FCPTR
- cextern _PM_prevKey15,FCPTR
- cextern _PM_prevBreak,FCPTR
- cextern _PM_prevCtrlC,FCPTR
- cextern _PM_prevCritical,FCPTR
- cextern _PM_prevRealTimer,ULONG
- cextern _PM_prevRealRTC,ULONG
- cextern _PM_prevRealKey,ULONG
- cextern _PM_prevRealKey15,ULONG
- cextern _PM_prevRealInt10,ULONG
-
-cpublic _PM_pmdosDataStart
-
-; Allocate space for all of the local stacks that we need. These stacks
-; are not very large, but should be large enough for most purposes
-; (generally you want to handle these interrupts quickly, simply storing
-; the information for later and then returning). If you need bigger
-; stacks then change the appropriate value in here.
-
- ALIGN 4
- dclb MOUSE_STACK ; Space for local stack (small)
-MsStack: ; Stack starts at end!
-ptr_MsStack DUINT 0 ; Place to store old stack offset
-seg_MsStack dw 0 ; Place to store old stack segment
-
- ALIGN 4
- dclb INT10_STACK ; Space for local stack (small)
-Int10Stack: ; Stack starts at end!
-ptr_Int10Stack DUINT 0 ; Place to store old stack offset
-seg_Int10Stack dw 0 ; Place to store old stack segment
-
- ALIGN 4
- dclb TIMER_STACK ; Space for local stack (small)
-TmStack: ; Stack starts at end!
-ptr_TmStack DUINT 0 ; Place to store old stack offset
-seg_TmStack dw 0 ; Place to store old stack segment
-
- ALIGN 4
- dclb TIMER_STACK ; Space for local stack (small)
-RtcStack: ; Stack starts at end!
-ptr_RtcStack DUINT 0 ; Place to store old stack offset
-seg_RtcStack dw 0 ; Place to store old stack segment
-RtcInside dw 0 ; Are we still handling current interrupt
-
- ALIGN 4
- dclb KEY_STACK ; Space for local stack (small)
-KyStack: ; Stack starts at end!
-ptr_KyStack DUINT 0 ; Place to store old stack offset
-seg_KyStack dw 0 ; Place to store old stack segment
-KyInside dw 0 ; Are we still handling current interrupt
-
- ALIGN 4
- dclb KEY_STACK ; Space for local stack (small)
-Ky15Stack: ; Stack starts at end!
-ptr_Ky15Stack DUINT 0 ; Place to store old stack offset
-seg_Ky15Stack dw 0 ; Place to store old stack segment
-
-TempSeg dw 0 ; Place to store stack segment
-
-cpublic _PM_pmdosDataEnd
-
-enddataseg _pmdos
-
-begcodeseg _pmdos ; Start of code segment
-
-cpublic _PM_pmdosCodeStart
-
-;----------------------------------------------------------------------------
-; PM_mouseISR - Mouse interrupt subroutine dispatcher
-;----------------------------------------------------------------------------
-; Interrupt subroutine called by the mouse driver upon interrupts, to
-; dispatch control to high level C based subroutines. Interrupts are on
-; when we call the user code.
-;
-; It is _extremely_ important to save the state of the extended registers
-; as these may well be trashed by the routines called from here and not
-; restored correctly by the mouse interface module.
-;
-; NOTE: This routine switches to a local stack before calling any C code,
-; and hence is _not_ re-entrant. For mouse handlers this is not a
-; problem, as the mouse driver arbitrates calls to the user mouse
-; handler for us.
-;
-; Entry: AX - Condition mask giving reason for call
-; BX - Mouse button state
-; CX - Horizontal cursor coordinate
-; DX - Vertical cursor coordinate
-; SI - Horizontal mickey value
-; DI - Vertical mickey value
-;
-;----------------------------------------------------------------------------
-ifdef DJGPP
-cprocstart _PM_mouseISR
-else
-cprocfar _PM_mouseISR
-endif
-
- push ds ; Save value of DS
- push es
- pushad ; Save _all_ extended registers
- cld ; Clear direction flag
-
- LOAD_DS ; Load DS register
- NEWSTK MsStack ; Switch to local stack
-
-; Call the installed high level C code routine
-
- clrhi dx ; Clear out high order values
- clrhi cx
- clrhi bx
- clrhi ax
- sgnhi si
- sgnhi di
-
- push _di
- push _si
- push _dx
- push _cx
- push _bx
- push _ax
- sti ; Enable interrupts
- call [CPTR _PM_mouseHandler]
- _add sp,12,24
-
- RESTSTK MsStack ; Restore previous stack
-
- popad ; Restore all extended registers
- pop es
- pop ds
- ret ; We are done!!
-
-cprocend
-
-;----------------------------------------------------------------------------
-; PM_timerISR - Timer interrupt subroutine dispatcher
-;----------------------------------------------------------------------------
-; Hardware interrupt handler for the timer interrupt, to dispatch control
-; to high level C based subroutines. We save the state of all registers
-; in this routine, and switch to a local stack. Interrupts are *off*
-; when we call the user code.
-;
-; NOTE: This routine switches to a local stack before calling any C code,
-; and hence is _not_ re-entrant. Make sure your C code executes as
-; quickly as possible, since a timer overrun will simply hang the
-; system.
-;----------------------------------------------------------------------------
-cprocfar _PM_timerISR
-
- push ds ; Save value of DS
- push es
- pushad ; Save _all_ extended registers
- cld ; Clear direction flag
-
- LOAD_DS ; Load DS register
-
- NEWSTK TmStack ; Switch to local stack
- call [CPTR _PM_timerHandler]
- RESTSTK TmStack ; Restore previous stack
-
- popad ; Restore all extended registers
- pop es
- pop ds
- iret ; Return from interrupt
-
-cprocend
-
-;----------------------------------------------------------------------------
-; PM_chainPrevTimer - Chain to previous timer interrupt and return
-;----------------------------------------------------------------------------
-; Chains to the previous timer interrupt routine and returns control
-; back to the high level interrupt handler.
-;----------------------------------------------------------------------------
-cprocstart PM_chainPrevTimer
-
-ifdef TNT
- push eax
- push ebx
- push ecx
- pushfd ; Push flags on stack to simulate interrupt
- mov ax,250Eh ; Call real mode procedure function
- mov ebx,[_PM_prevRealTimer]
- mov ecx,1 ; Copy real mode flags to real mode stack
- int 21h ; Call the real mode code
- popfd
- pop ecx
- pop ebx
- pop eax
- ret
-else
- SWAPSTK TmStack ; Swap back to previous stack
- pushf ; Save state of interrupt flag
- pushf ; Push flags on stack to simulate interrupt
-ifdef USE_NASM
- call far dword [_PM_prevTimer]
-else
- call [_PM_prevTimer]
-endif
- popf ; Restore state of interrupt flag
- SWAPSTK TmStack ; Swap back to C stack again
- ret
-endif
-
-cprocend
-
-; Macro to delay briefly to ensure that enough time has elapsed between
-; successive I/O accesses so that the device being accessed can respond
-; to both accesses even on a very fast PC.
-
-ifdef USE_NASM
-%macro DELAY 0
- jmp short $+2
- jmp short $+2
- jmp short $+2
-%endmacro
-%macro IODELAYN 1
-%rep %1
- DELAY
-%endrep
-%endmacro
-else
-macro DELAY
- jmp short $+2
- jmp short $+2
- jmp short $+2
-endm
-macro IODELAYN N
- rept N
- DELAY
- endm
-endm
-endif
-
-;----------------------------------------------------------------------------
-; PM_rtcISR - Real time clock interrupt subroutine dispatcher
-;----------------------------------------------------------------------------
-; Hardware interrupt handler for the timer interrupt, to dispatch control
-; to high level C based subroutines. We save the state of all registers
-; in this routine, and switch to a local stack. Interrupts are *off*
-; when we call the user code.
-;
-; NOTE: This routine switches to a local stack before calling any C code,
-; and hence is _not_ re-entrant. Make sure your C code executes as
-; quickly as possible, since a timer overrun will simply hang the
-; system.
-;----------------------------------------------------------------------------
-cprocfar _PM_rtcISR
-
- push ds ; Save value of DS
- push es
- pushad ; Save _all_ extended registers
- cld ; Clear direction flag
-
-; Clear priority interrupt controller and re-enable interrupts so we
-; dont lock things up for long.
-
- mov al,20h
- out 0A0h,al
- out 020h,al
-
-; Clear real-time clock timeout
-
- in al,70h ; Read CMOS index register
- push _ax ; and save for later
- IODELAYN 3
- mov al,0Ch
- out 70h,al
- IODELAYN 5
- in al,71h
-
-; Call the C interrupt handler function
-
- LOAD_DS ; Load DS register
- cmp [BYTE RtcInside],1 ; Check for mutual exclusion
- je @@Exit
- mov [BYTE RtcInside],1
- NEWSTK RtcStack ; Switch to local stack
- sti ; Re-enable interrupts
- call [CPTR _PM_rtcHandler]
- RESTSTK RtcStack ; Restore previous stack
- mov [BYTE RtcInside],0
-
-@@Exit: pop _ax
- out 70h,al ; Restore CMOS index register
- popad ; Restore all extended registers
- pop es
- pop ds
- iret ; Return from interrupt
-
-cprocend
-
-ifdef flatmodel
-;----------------------------------------------------------------------------
-; PM_irqISRTemplate - Hardware interrupt handler IRQ template
-;----------------------------------------------------------------------------
-; Hardware interrupt handler for any interrupt, to dispatch control
-; to high level C based subroutines. We save the state of all registers
-; in this routine, and switch to a local stack. Interrupts are *off*
-; when we call the user code.
-;
-; NOTE: This routine switches to a local stack before calling any C code,
-; and hence is _not_ re-entrant. Make sure your C code executes as
-; quickly as possible.
-;----------------------------------------------------------------------------
-cprocfar _PM_irqISRTemplate
-
- push ebx
- mov ebx,0 ; Relocation adjustment factor
- jmp __IRQEntry
-
-; Global variables stored in the IRQ thunk code segment
-
-_CHandler dd 0 ; Pointer to C interrupt handler
-_PrevIRQ dd 0 ; Previous IRQ handler
- dd 0
-_IRQ dd 0 ; IRQ we are hooked for
-ptr_IRQStack DUINT 0 ; Place to store old stack offset
-seg_IRQStack dw 0 ; Place to store old stack segment
-_Inside db 0 ; Mutual exclusion flag
- ALIGN 4
- dclb IRQ_STACK ; Space for local stack
-_IRQStack: ; Stack starts at end!
-
-; Check for and reject spurious IRQ 7 signals
-
-__IRQEntry:
- cmp [BYTE cs:ebx+_IRQ],7 ; Spurious IRQs occur only on IRQ 7
- jmp @@ValidIRQ
- push eax
- mov al,1011b ; OCW3: read ISR
- out 20h,al ; (Intel Peripheral Components, 1991,
- in al,20h ; p. 3-188)
- shl al,1 ; Set C = bit 7 (IRQ 7) of ISR register
- pop eax
- jc @@ValidIRQ
- iret ; Return from interrupt
-
-; Save all registers for duration of IRQ handler
-
-@@ValidIRQ:
- push ds ; Save value of DS
- push es
- pushad ; Save _all_ extended registers
- cld ; Clear direction flag
- LOAD_DS ; Load DS register
-
-; Send an EOI to the PIC
-
- mov al,20h ; Send EOI to PIC
- cmp [BYTE ebx+_IRQ],8 ; Clear PIC1 first if IRQ >= 8
- jb @@1
- out 0A0h,al
-@@1: out 20h,al
-
-; Check for mutual exclusion
-
- cmp [BYTE ebx+_Inside],1
- je @@ChainOldHandler
- mov [BYTE ebx+_Inside],1
-
-; Call the C interrupt handler function
-
- mov [ebx+seg_IRQStack],ss ; Switch to local stack
- mov [ebx+ptr_IRQStack],esp
- mov [TempSeg],ds
- mov ss,[TempSeg]
- lea esp,[ebx+_IRQStack]
- sti ; Re-enable interrupts
- push ebx
- call [DWORD ebx+_CHandler]
- pop ebx
- cli
- mov ss,[ebx+seg_IRQStack] ; Restore previous stack
- mov esp,[ebx+ptr_IRQStack]
- or eax,eax
- jz @@ChainOldHandler ; Chain if not handled for shared IRQ
-
-@@Exit: mov [BYTE ebx+_Inside],0
- popad ; Restore all extended registers
- pop es
- pop ds
- pop ebx
- iret ; Return from interrupt
-
-@@ChainOldHandler:
- cmp [DWORD ebx+_PrevIRQ],0
- jz @@Exit
- mov [BYTE ebx+_Inside],0
- mov eax,[DWORD ebx+_PrevIRQ]
- mov ebx,[DWORD ebx+_PrevIRQ+4]
- mov [DWORD _PrevIRQ],eax
- mov [DWORD _PrevIRQ+4],ebx
- popad ; Restore all extended registers
- pop es
- pop ds
- pop ebx
- jmp [cs:_PrevIRQ] ; Chain to previous IRQ handler
-
-cprocend
-cpublic _PM_irqISRTemplateEnd
-endif
-
-;----------------------------------------------------------------------------
-; PM_keyISR - keyboard interrupt subroutine dispatcher
-;----------------------------------------------------------------------------
-; Hardware interrupt handler for the keyboard interrupt, to dispatch control
-; to high level C based subroutines. We save the state of all registers
-; in this routine, and switch to a local stack. Interrupts are *off*
-; when we call the user code.
-;
-; NOTE: This routine switches to a local stack before calling any C code,
-; and hence is _not_ re-entrant. However we ensure within this routine
-; mutual exclusion to the keyboard handling routine.
-;----------------------------------------------------------------------------
-cprocfar _PM_keyISR
-
- push ds ; Save value of DS
- push es
- pushad ; Save _all_ extended registers
- cld ; Clear direction flag
-
- LOAD_DS ; Load DS register
-
- cmp [BYTE KyInside],1 ; Check for mutual exclusion
- je @@Reissued
-
- mov [BYTE KyInside],1
- NEWSTK KyStack ; Switch to local stack
- call [CPTR _PM_keyHandler] ; Call C code
- RESTSTK KyStack ; Restore previous stack
- mov [BYTE KyInside],0
-
-@@Exit: popad ; Restore all extended registers
- pop es
- pop ds
- iret ; Return from interrupt
-
-; When the BIOS keyboard handler needs to change the SHIFT status lights
-; on the keyboard, in the process of doing this the keyboard controller
-; re-issues another interrupt, while the current handler is still executing.
-; If we recieve another interrupt while still handling the current one,
-; then simply chain directly to the previous handler.
-;
-; Note that for most DOS extenders, the real mode interrupt handler that we
-; install takes care of this for us.
-
-@@Reissued:
-ifdef TNT
- push eax
- push ebx
- push ecx
- pushfd ; Push flags on stack to simulate interrupt
- mov ax,250Eh ; Call real mode procedure function
- mov ebx,[_PM_prevRealKey]
- mov ecx,1 ; Copy real mode flags to real mode stack
- int 21h ; Call the real mode code
- popfd
- pop ecx
- pop ebx
- pop eax
-else
- pushf
-ifdef USE_NASM
- call far dword [_PM_prevKey]
-else
- call [_PM_prevKey]
-endif
-endif
- jmp @@Exit
-
-cprocend
-
-;----------------------------------------------------------------------------
-; PM_chainPrevkey - Chain to previous key interrupt and return
-;----------------------------------------------------------------------------
-; Chains to the previous key interrupt routine and returns control
-; back to the high level interrupt handler.
-;----------------------------------------------------------------------------
-cprocstart PM_chainPrevKey
-
-ifdef TNT
- push eax
- push ebx
- push ecx
- pushfd ; Push flags on stack to simulate interrupt
- mov ax,250Eh ; Call real mode procedure function
- mov ebx,[_PM_prevRealKey]
- mov ecx,1 ; Copy real mode flags to real mode stack
- int 21h ; Call the real mode code
- popfd
- pop ecx
- pop ebx
- pop eax
- ret
-else
-
-; YIKES! For some strange reason, when execution returns from the
-; previous keyboard handler, interrupts are re-enabled!! Since we expect
-; interrupts to remain off during the duration of our handler, this can
-; cause havoc. However our stack macros always turn off interrupts, so they
-; will be off when we exit this routine. Obviously there is a tiny weeny
-; window when interrupts will be enabled, but there is nothing we can
-; do about this.
-
- SWAPSTK KyStack ; Swap back to previous stack
- pushf ; Push flags on stack to simulate interrupt
-ifdef USE_NASM
- call far dword [_PM_prevKey]
-else
- call [_PM_prevKey]
-endif
- SWAPSTK KyStack ; Swap back to C stack again
- ret
-endif
-
-cprocend
-
-;----------------------------------------------------------------------------
-; PM_key15ISR - Int 15h keyboard interrupt subroutine dispatcher
-;----------------------------------------------------------------------------
-; This routine gets called if we have been called to handle the Int 15h
-; keyboard interrupt callout from real mode.
-;
-; Entry: AX - Hardware scan code to process
-; Exit: AX - Hardware scan code to process (0 to ignore)
-;----------------------------------------------------------------------------
-cprocfar _PM_key15ISR
-
- push ds
- push es
- LOAD_DS
- cmp ah,4Fh
- jnz @@NotOurs ; Quit if not keyboard callout
-
- pushad
- cld ; Clear direction flag
- xor ah,ah ; AX := scan code
- NEWSTK Ky15Stack ; Switch to local stack
- push _ax
- call [CPTR _PM_key15Handler] ; Call C code
- _add sp,2,4
- RESTSTK Ky15Stack ; Restore previous stack
- test ax,ax
- jz @@1
- stc ; Set carry to process as normal
- jmp @@2
-@@1: clc ; Clear carry to ignore scan code
-@@2: popad
- jmp @@Exit ; We are done
-
-@@NotOurs:
-ifdef TNT
- push eax
- push ebx
- push ecx
- pushfd ; Push flags on stack to simulate interrupt
- mov ax,250Eh ; Call real mode procedure function
- mov ebx,[_PM_prevRealKey15]
- mov ecx,1 ; Copy real mode flags to real mode stack
- int 21h ; Call the real mode code
- popfd
- pop ecx
- pop ebx
- pop eax
-else
- pushf
-ifdef USE_NASM
- call far dword [_PM_prevKey15]
-else
- call [_PM_prevKey15]
-endif
-endif
-@@Exit: pop es
- pop ds
-ifdef flatmodel
- retf 4
-else
- retf 2
-endif
-
-cprocend
-
-;----------------------------------------------------------------------------
-; PM_breakISR - Control Break interrupt subroutine dispatcher
-;----------------------------------------------------------------------------
-; Hardware interrupt handler for the Ctrl-Break interrupt. We simply set
-; the Ctrl-Break flag to a 1 and leave (note that this is accessed through
-; a far pointer, as it may well be located in conventional memory).
-;----------------------------------------------------------------------------
-cprocfar _PM_breakISR
-
- sti
- push ds ; Save value of DS
- push es
- push _bx
-
- LOAD_DS ; Load DS register
-ifdef flatmodel
- mov ebx,[_PM_ctrlBPtr]
-else
- les bx,[_PM_ctrlBPtr]
-endif
- mov [UINT _ES _bx],1
-
-; Run alternate break handler code if installed
-
- cmp [CPTR _PM_breakHandler],0
- je @@Exit
-
- pushad
- mov _ax,1
- push _ax
- call [CPTR _PM_breakHandler] ; Call C code
- pop _ax
- popad
-
-@@Exit: pop _bx
- pop es
- pop ds
- iret ; Return from interrupt
-
-cprocend
-
-;----------------------------------------------------------------------------
-; int PM_ctrlBreakHit(int clearFlag)
-;----------------------------------------------------------------------------
-; Returns the current state of the Ctrl-Break flag and possibly clears it.
-;----------------------------------------------------------------------------
-cprocstart PM_ctrlBreakHit
-
- ARG clearFlag:UINT
-
- enter_c
- pushf ; Save interrupt status
- push es
-ifdef flatmodel
- mov ebx,[_PM_ctrlBPtr]
-else
- les bx,[_PM_ctrlBPtr]
-endif
- cli ; No interrupts thanks!
- mov _ax,[_ES _bx]
- test [BYTE clearFlag],1
- jz @@Done
- mov [UINT _ES _bx],0
-
-@@Done: pop es
- popf ; Restore interrupt status
- leave_c
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; PM_ctrlCISR - Control Break interrupt subroutine dispatcher
-;----------------------------------------------------------------------------
-; Hardware interrupt handler for the Ctrl-C interrupt. We simply set
-; the Ctrl-C flag to a 1 and leave (note that this is accessed through
-; a far pointer, as it may well be located in conventional memory).
-;----------------------------------------------------------------------------
-cprocfar _PM_ctrlCISR
-
- sti
- push ds ; Save value of DS
- push es
- push _bx
-
- LOAD_DS ; Load DS register
-ifdef flatmodel
- mov ebx,[_PM_ctrlCPtr]
-else
- les bx,[_PM_ctrlCPtr]
-endif
- mov [UINT _ES _bx],1
-
-; Run alternate break handler code if installed
-
- cmp [CPTR _PM_breakHandler],0
- je @@Exit
-
- pushad
- mov _ax,0
- push _ax
- call [CPTR _PM_breakHandler] ; Call C code
- pop _ax
- popad
-
-@@Exit: pop _bx
- pop es
- pop ds
- iret ; Return from interrupt
- iretd
-
-cprocend
-
-;----------------------------------------------------------------------------
-; int PM_ctrlCHit(int clearFlag)
-;----------------------------------------------------------------------------
-; Returns the current state of the Ctrl-C flag and possibly clears it.
-;----------------------------------------------------------------------------
-cprocstart PM_ctrlCHit
-
- ARG clearFlag:UINT
-
- enter_c
- pushf ; Save interrupt status
- push es
-ifdef flatmodel
- mov ebx,[_PM_ctrlCPtr]
-else
- les bx,[_PM_ctrlCPtr]
-endif
- cli ; No interrupts thanks!
- mov _ax,[_ES _bx]
- test [BYTE clearFlag],1
- jz @@Done
- mov [UINT _ES _bx],0
-
-@@Done:
- pop es
- popf ; Restore interrupt status
- leave_c
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; PM_criticalISR - Control Error handler interrupt subroutine dispatcher
-;----------------------------------------------------------------------------
-; Interrupt handler for the MSDOS Critical Error interrupt, to dispatch
-; control to high level C based subroutines. We save the state of all
-; registers in this routine, and switch to a local stack. We also pass
-; the values of the AX and DI registers to the as pointers, so that the
-; values can be modified before returning to MSDOS.
-;----------------------------------------------------------------------------
-cprocfar _PM_criticalISR
-
- sti
- push ds ; Save value of DS
- push es
- push _bx ; Save register values changed
- cld ; Clear direction flag
-
- LOAD_DS ; Load DS register
-ifdef flatmodel
- mov ebx,[_PM_critPtr]
-else
- les bx,[_PM_critPtr]
-endif
- mov [_ES _bx],ax
- mov [_ES _bx+2],di
-
-; Run alternate critical handler code if installed
-
- cmp [CPTR _PM_critHandler],0
- je @@NoAltHandler
-
- pushad
- push _di
- push _ax
- call [CPTR _PM_critHandler] ; Call C code
- _add sp,4,8
- popad
-
- pop _bx
- pop es
- pop ds
- iret ; Return from interrupt
-
-@@NoAltHandler:
- mov ax,3 ; Tell MSDOS to fail the operation
- pop _bx
- pop es
- pop ds
- iret ; Return from interrupt
-
-cprocend
-
-;----------------------------------------------------------------------------
-; int PM_criticalError(int *axVal,int *diVal,int clearFlag)
-;----------------------------------------------------------------------------
-; Returns the current state of the critical error flags, and the values that
-; MSDOS passed in the AX and DI registers to our handler.
-;----------------------------------------------------------------------------
-cprocstart PM_criticalError
-
- ARG axVal:DPTR, diVal:DPTR, clearFlag:UINT
-
- enter_c
- pushf ; Save interrupt status
- push es
-ifdef flatmodel
- mov ebx,[_PM_critPtr]
-else
- les bx,[_PM_critPtr]
-endif
- cli ; No interrupts thanks!
- xor _ax,_ax
- xor _di,_di
- mov ax,[_ES _bx]
- mov di,[_ES _bx+2]
- test [BYTE clearFlag],1
- jz @@NoClear
- mov [ULONG _ES _bx],0
-@@NoClear:
- _les _bx,[axVal]
- mov [_ES _bx],_ax
- _les _bx,[diVal]
- mov [_ES _bx],_di
- pop es
- popf ; Restore interrupt status
- leave_c
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void PM_setMouseHandler(int mask, PM_mouseHandler mh)
-;----------------------------------------------------------------------------
-cprocstart _PM_setMouseHandler
-
- ARG mouseMask:UINT
-
- enter_c
- push es
-
- mov ax,0Ch ; AX := Function 12 - install interrupt sub
- mov _cx,[mouseMask] ; CX := mouse mask
- mov _dx,offset _PM_mouseISR
- push cs
- pop es ; ES:_DX -> mouse handler
- int 33h ; Call mouse driver
-
- pop es
- leave_c
- ret
-
-cprocend
-
-ifdef flatmodel
-
-;----------------------------------------------------------------------------
-; void PM_mousePMCB(void)
-;----------------------------------------------------------------------------
-; Mouse realmode callback routine. Upon entry to this routine, we recieve
-; the following from the DPMI server:
-;
-; Entry: DS:_SI -> Real mode stack at time of call
-; ES:_DI -> Real mode register data structure
-; SS:_SP -> Locked protected mode stack to use
-;----------------------------------------------------------------------------
-cprocfar _PM_mousePMCB
-
- pushad
- mov eax,[es:_di+1Ch] ; Load register values from real mode
- mov ebx,[es:_di+10h]
- mov ecx,[es:_di+18h]
- mov edx,[es:_di+14h]
- mov esi,[es:_di+04h]
- mov edi,[es:_di]
- call _PM_mouseISR ; Call the mouse handler
- popad
-
- mov ax,[ds:_si]
- mov [es:_di+2Ah],ax ; Plug in return IP address
- mov ax,[ds:_si+2]
- mov [es:_di+2Ch],ax ; Plug in return CS value
- add [WORD es:_di+2Eh],4 ; Remove return address from stack
- iret ; Go back to real mode!
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void PM_int10PMCB(void)
-;----------------------------------------------------------------------------
-; int10 realmode callback routine. Upon entry to this routine, we recieve
-; the following from the DPMI server:
-;
-; Entry: DS:ESI -> Real mode stack at time of call
-; ES:EDI -> Real mode register data structure
-; SS:ESP -> Locked protected mode stack to use
-;----------------------------------------------------------------------------
-cprocfar _PM_int10PMCB
-
- pushad
- push ds
- push es
- push fs
-
- pushfd
- pop eax
- mov [es:edi+20h],ax ; Save return flag status
- mov ax,[ds:esi]
- mov [es:edi+2Ah],ax ; Plug in return IP address
- mov ax,[ds:esi+2]
- mov [es:edi+2Ch],ax ; Plug in return CS value
- add [WORD es:edi+2Eh],4 ; Remove return address from stack
-
-; Call the install int10 handler in protected mode. This function gets called
-; with DS set to the current data selector, and ES:EDI pointing the the
-; real mode DPMI register structure at the time of the interrupt. The
-; handle must be written in assembler to be able to extract the real mode
-; register values from the structure
-
- push es
- pop fs ; FS:EDI -> real mode registers
- LOAD_DS
- NEWSTK Int10Stack ; Switch to local stack
-
- call [_PM_int10Handler]
-
- RESTSTK Int10Stack ; Restore previous stack
- pop fs
- pop es
- pop ds
- popad
- iret ; Go back to real mode!
-
-cprocend
-
-endif
-
-cpublic _PM_pmdosCodeEnd
-
-endcodeseg _pmdos
-
- END ; End of module
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/_vflat.asm b/board/MAI/bios_emulator/scitech/src/pm/dos/_vflat.asm
deleted file mode 100644
index 34985a9d8b..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/_vflat.asm
+++ /dev/null
@@ -1,652 +0,0 @@
-;****************************************************************************
-;*
-;* SciTech OS Portability Manager Library
-;*
-;* ========================================================================
-;*
-;* The contents of this file are subject to the SciTech MGL Public
-;* License Version 1.0 (the "License"); you may not use this file
-;* except in compliance with the License. You may obtain a copy of
-;* the License at http://www.scitechsoft.com/mgl-license.txt
-;*
-;* Software distributed under the License is distributed on an
-;* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-;* implied. See the License for the specific language governing
-;* rights and limitations under the License.
-;*
-;* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-;*
-;* The Initial Developer of the Original Code is SciTech Software, Inc.
-;* All Rights Reserved.
-;*
-;* ========================================================================
-;*
-;* Based on original code Copyright 1994 Otto Chrons
-;*
-;* Language: 80386 Assembler, TASM 4.0 or later
-;* Environment: IBM PC 32 bit protected mode
-;*
-;* Description: Low level page fault handler for virtual linear framebuffers.
-;*
-;****************************************************************************
-
- IDEAL
- JUMPS
-
-include "scitech.mac" ; Memory model macros
-
-header _vflat ; Set up memory model
-
-VFLAT_START EQU 0F0000000h
-VFLAT_END EQU 0F03FFFFFh
-PAGE_PRESENT EQU 1
-PAGE_NOTPRESENT EQU 0
-PAGE_READ EQU 0
-PAGE_WRITE EQU 2
-
-ifdef DOS4GW
-
-;----------------------------------------------------------------------------
-; DOS4G/W flat linear framebuffer emulation.
-;----------------------------------------------------------------------------
-
-begdataseg _vflat
-
-; Near pointers to the page directory base and our page tables. All of
-; this memory is always located in the first Mb of DOS memory.
-
-PDBR dd 0 ; Page directory base register (CR3)
-accessPageAddr dd 0
-accessPageTable dd 0
-
-; CauseWay page directory & 1st page table linear addresses.
-
-CauseWayDIRLinear dd 0
-CauseWay1stLinear dd 0
-
-; Place to store a copy of the original Page Table Directory before we
-; intialised our virtual buffer code.
-
-pageDirectory: resd 1024 ; Saved page table directory
-
-ValidCS dw 0 ; Valid CS for page faults
-Ring0CS dw 0 ; Our ring 0 code selector
-LastPage dd 0 ; Last page we mapped in
-BankFuncBuf: resb 101 ; Place to store bank switch code
-BankFuncPtr dd offset BankFuncBuf
-
-INT14Gate:
-INT14Offset dd 0 ; eip of original vector
-INT14Selector dw 0 ; cs of original vector
-
- cextern _PM_savedDS,USHORT
- cextern VF_haveCauseWay,BOOL
-
-enddataseg _vflat
-
-begcodeseg _vflat ; Start of code segment
-
- cextern VF_malloc,FPTR
-
-;----------------------------------------------------------------------------
-; PF_handler64k - Page fault handler for 64k banks
-;----------------------------------------------------------------------------
-; The handler below is a 32 bit ring 0 page fault handler. It receives
-; control immediately after any page fault or after an IRQ6 (hardware
-; interrupt). This provides the fastest possible handling of page faults
-; since it jump directly here. If this is a page fault, the number
-; immediately on the stack will be an error code, at offset 4 will be
-; the eip of the faulting instruction, at offset 8 will be the cs of the
-; faulting instruction. If it is a hardware interrupt, it will not have
-; the error code and the eflags will be at offset 8.
-;----------------------------------------------------------------------------
-cprocfar PF_handler64k
-
-; Check if this is a processor exeception or a page fault
-
- push eax
- mov ax,[cs:ValidCS] ; Use CS override to access data
- cmp [ss:esp+12],ax ; Is this a page fault?
- jne @@ToOldHandler ; Nope, jump to the previous handler
-
-; Get address of page fault and check if within our handlers range
-
- mov eax,cr2 ; EBX has page fault linear address
- cmp eax,VFLAT_START ; Is the fault less than ours?
- jb @@ToOldHandler ; Yep, go to previous handler
- cmp eax,VFLAT_END ; Is the fault more than ours?
- jae @@ToOldHandler ; Yep, go to previous handler
-
-; This is our page fault, so we need to handle it
-
- pushad
- push ds
- push es
- mov ebx,eax ; EBX := page fault address
- and ebx,invert 0FFFFh ; Mask to 64k bank boundary
- mov ds,[cs:_PM_savedDS]; Load segment registers
- mov es,[cs:_PM_savedDS]
-
-; Map in the page table for our virtual framebuffer area for modification
-
- mov edi,[PDBR] ; EDI points to page directory
- mov edx,ebx ; EDX = linear address
- shr edx,22 ; EDX = offset to page directory
- mov edx,[edx*4+edi] ; EDX = physical page table address
- mov eax,edx
- mov edx,[accessPageTable]
- or eax,7
- mov [edx],eax
- mov eax,cr3
- mov cr3,eax ; Update page table cache
-
-; Mark all pages valid for the new page fault area
-
- mov esi,ebx ; ESI := linear address for page
- shr esi,10
- and esi,0FFFh ; Offset into page table
- add esi,[accessPageAddr]
-ifdef USE_NASM
-%assign off 0
-%rep 16
- or [DWORD esi+off],0000000001h ; Enable pages
-%assign off off+4
-%endrep
-else
-off = 0
-REPT 16
- or [DWORD esi+off],0000000001h ; Enable pages
-off = off+4
-ENDM
-endif
-
-; Mark all pages invalid for the previously mapped area
-
- xchg esi,[LastPage] ; Save last page for next page fault
- test esi,esi
- jz @@DoneMapping ; Dont update if first time round
-ifdef USE_NASM
-%assign off 0
-%rep 16
- or [DWORD esi+off],0FFFFFFFEh ; Disable pages
-%assign off off+4
-%endrep
-else
-off = 0
-REPT 16
- and [DWORD esi+off],0FFFFFFFEh ; Disable pages
-off = off+4
-ENDM
-endif
-
-@@DoneMapping:
- mov eax,cr3
- mov cr3,eax ; Flush the TLB
-
-; Now program the new SuperVGA starting bank address
-
- mov eax,ebx ; EAX := page fault address
- shr eax,16
- and eax,0FFh ; Mask to 0-255
- call [BankFuncPtr] ; Call the bank switch function
-
- pop es
- pop ds
- popad
- pop eax
- add esp,4 ; Pop the error code from stack
- iretd ; Return to faulting instruction
-
-@@ToOldHandler:
- pop eax
-ifdef USE_NASM
- jmp far dword [cs:INT14Gate]; Chain to previous handler
-else
- jmp [FWORD cs:INT14Gate]; Chain to previous handler
-endif
-
-cprocend
-
-;----------------------------------------------------------------------------
-; PF_handler4k - Page fault handler for 4k banks
-;----------------------------------------------------------------------------
-; The handler below is a 32 bit ring 0 page fault handler. It receives
-; control immediately after any page fault or after an IRQ6 (hardware
-; interrupt). This provides the fastest possible handling of page faults
-; since it jump directly here. If this is a page fault, the number
-; immediately on the stack will be an error code, at offset 4 will be
-; the eip of the faulting instruction, at offset 8 will be the cs of the
-; faulting instruction. If it is a hardware interrupt, it will not have
-; the error code and the eflags will be at offset 8.
-;----------------------------------------------------------------------------
-cprocfar PF_handler4k
-
-; Fill in when we have tested all the 64Kb code
-
-ifdef USE_NASM
- jmp far dword [cs:INT14Gate]; Chain to previous handler
-else
- jmp [FWORD cs:INT14Gate]; Chain to previous handler
-endif
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void InstallFaultHandler(void *baseAddr,int bankSize)
-;----------------------------------------------------------------------------
-; Installes the page fault handler directly int the interrupt descriptor
-; table for maximum performance. This of course requires ring 0 access,
-; but none of this stuff will run without ring 0!
-;----------------------------------------------------------------------------
-cprocstart InstallFaultHandler
-
- ARG baseAddr:ULONG, bankSize:UINT
-
- enter_c
-
- mov [DWORD LastPage],0 ; No pages have been mapped
- mov ax,cs
- mov [ValidCS],ax ; Save CS value for page faults
-
-; Put address of our page fault handler into the IDT directly
-
- sub esp,6 ; Allocate space on stack
-ifdef USE_NASM
- sidt [ss:esp] ; Store pointer to IDT
-else
- sidt [FWORD ss:esp] ; Store pointer to IDT
-endif
- pop ax ; add esp,2
- pop eax ; Absolute address of IDT
- add eax,14*8 ; Point to Int #14
-
-; Note that Interrupt gates do not have the high and low word of the
-; offset in adjacent words in memory, there are 4 bytes separating them.
-
- mov ecx,[eax] ; Get cs and low 16 bits of offset
- mov edx,[eax+6] ; Get high 16 bits of offset in dx
- shl edx,16
- mov dx,cx ; edx has offset
- mov [INT14Offset],edx ; Save offset
- shr ecx,16
- mov [INT14Selector],cx ; Save original cs
- mov [eax+2],cs ; Install new cs
- mov edx,offset PF_handler64k
- cmp [UINT bankSize],4
- jne @@1
- mov edx,offset PF_handler4k
-@@1: mov [eax],dx ; Install low word of offset
- shr edx,16
- mov [eax+6],dx ; Install high word of offset
-
- leave_c
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void RemoveFaultHandler(void)
-;----------------------------------------------------------------------------
-; Closes down the virtual framebuffer services and restores the previous
-; page fault handler.
-;----------------------------------------------------------------------------
-cprocstart RemoveFaultHandler
-
- enter_c
-
-; Remove page fault handler from IDT
-
- sub esp,6 ; Allocate space on stack
-ifdef USE_NASM
- sidt [ss:esp] ; Store pointer to IDT
-else
- sidt [FWORD ss:esp] ; Store pointer to IDT
-endif
-
- pop ax ; add esp,2
- pop eax ; Absolute address of IDT
- add eax,14*8 ; Point to Int #14
- mov cx,[INT14Selector]
- mov [eax+2],cx ; Restore original CS
- mov edx,[INT14Offset]
- mov [eax],dx ; Install low word of offset
- shr edx,16
- mov [eax+6],dx ; Install high word of offset
-
- leave_c
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void InstallBankFunc(int codeLen,void *bankFunc)
-;----------------------------------------------------------------------------
-; Installs the bank switch function by relocating it into our data segment
-; and making it into a callable function. We do it this way to make the
-; code identical to the way that the VflatD devices work under Windows.
-;----------------------------------------------------------------------------
-cprocstart InstallBankFunc
-
- ARG codeLen:UINT, bankFunc:DPTR
-
- enter_c
-
- mov esi,[bankFunc] ; Copy the code into buffer
- mov edi,offset BankFuncBuf
- mov ecx,[codeLen]
- rep movsb
- mov [BYTE edi],0C3h ; Terminate the function with a near ret
-
- leave_c
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; int InitPaging(void)
-;----------------------------------------------------------------------------
-; Initializes paging system. If paging is not enabled, builds a page table
-; directory and page tables for physical memory
-;
-; Exit: 0 - Successful
-; -1 - Couldn't initialize paging mechanism
-;----------------------------------------------------------------------------
-cprocstart InitPaging
-
- push ebx
- push ecx
- push edx
- push esi
- push edi
-
-; Are we running under CauseWay?
-
- mov ax,0FFF9h
- int 31h
- jc @@NotCauseway
- cmp ecx,"CAUS"
- jnz @@NotCauseway
- cmp edx,"EWAY"
- jnz @@NotCauseway
-
- mov [BOOL VF_haveCauseWay],1
- mov [CauseWayDIRLinear],esi
- mov [CauseWay1stLinear],edi
-
-; Check for DPMI
-
- mov ax,0ff00h
- push es
- int 31h
- pop es
- shr edi,2
- and edi,3
- cmp edi,2
- jz @@ErrExit ; Not supported under DPMI
-
- mov eax,[CauseWayDIRLinear]
- jmp @@CopyCR3
-
-@@NotCauseway:
- mov ax,cs
- test ax,3 ; Which ring are we running
- jnz @@ErrExit ; Needs zero ring to access
- ; page tables (CR3)
- mov eax,cr0 ; Load CR0
- test eax,80000000h ; Is paging enabled?
- jz @@ErrExit ; No, we must have paging!
-
- mov eax,cr3 ; Load directory address
- and eax,0FFFFF000h
-
-@@CopyCR3:
- mov [PDBR],eax ; Save it
- mov esi,eax
- mov edi,offset pageDirectory
- mov ecx,1024
- cld
- rep movsd ; Copy the original page table directory
- cmp [DWORD accessPageAddr],0; Check if we have allocated page
- jne @@HaveRealMem ; table already (we cant free it)
-
- mov eax,0100h ; DPMI DOS allocate
- mov ebx,8192/16
- int 31h ; Allocate 8192 bytes
- and eax,0FFFFh
- shl eax,4 ; EAX points to newly allocated memory
- add eax,4095
- and eax,0FFFFF000h ; Page align
- mov [accessPageAddr],eax
-
-@@HaveRealMem:
- mov eax,[accessPageAddr] ; EAX -> page table in 1st Mb
- shr eax,12
- and eax,3FFh ; Page table offset
- shl eax,2
- cmp [BOOL VF_haveCauseWay],0
- jz @@NotCW0
- mov ebx,[CauseWay1stLinear]
- jmp @@Put1st
-
-@@NotCW0:
- mov ebx,[PDBR]
- mov ebx,[ebx]
- and ebx,0FFFFF000h ; Page table for 1st megabyte
-
-@@Put1st:
- add eax,ebx
- mov [accessPageTable],eax
- sub eax,eax ; No error
- jmp @@Exit
-
-@@ErrExit:
- mov eax,-1
-
-@@Exit: pop edi
- pop esi
- pop edx
- pop ecx
- pop ebx
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void ClosePaging(void)
-;----------------------------------------------------------------------------
-; Closes the paging system
-;----------------------------------------------------------------------------
-cprocstart ClosePaging
-
- push eax
- push ecx
- push edx
- push esi
- push edi
-
- mov eax,[accessPageAddr]
- call AccessPage ; Restore AccessPage mapping
- mov edi,[PDBR]
- mov esi,offset pageDirectory
- mov ecx,1024
- cld
- rep movsd ; Restore the original page table directory
-
-@@Exit: pop edi
- pop esi
- pop edx
- pop ecx
- pop eax
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; long AccessPage(long phys)
-;----------------------------------------------------------------------------
-; Maps a known page to given physical memory
-; Entry: EAX - Physical memory
-; Exit: EAX - Linear memory address of mapped phys mem
-;----------------------------------------------------------------------------
-cprocstatic AccessPage
-
- push edx
- mov edx,[accessPageTable]
- or eax,7
- mov [edx],eax
- mov eax,cr3
- mov cr3,eax ; Update page table cache
- mov eax,[accessPageAddr]
- pop edx
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; long GetPhysicalAddress(long linear)
-;----------------------------------------------------------------------------
-; Returns the physical address of linear address
-; Entry: EAX - Linear address to convert
-; Exit: EAX - Physical address
-;----------------------------------------------------------------------------
-cprocstatic GetPhysicalAddress
-
- push ebx
- push edx
- mov edx,eax
- shr edx,22 ; EDX is the directory offset
- mov ebx,[PDBR]
- mov edx,[edx*4+ebx] ; Load page table address
- push eax
- mov eax,edx
- call AccessPage ; Access the page table
- mov edx,eax
- pop eax
- shr eax,12
- and eax,03FFh ; EAX offset into page table
- mov eax,[edx+eax*4] ; Load physical address
- and eax,0FFFFF000h
- pop edx
- pop ebx
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void CreatePageTable(long pageDEntry)
-;----------------------------------------------------------------------------
-; Creates a page table for specific address (4MB)
-; Entry: EAX - Page directory entry (top 10-bits of address)
-;----------------------------------------------------------------------------
-cprocstatic CreatePageTable
-
- push ebx
- push ecx
- push edx
- push edi
- mov ebx,eax ; Save address
- mov eax,8192
- push eax
- call VF_malloc ; Allocate page table directory
- add esp,4
- add eax,0FFFh
- and eax,0FFFFF000h ; Page align (4KB)
- mov edi,eax ; Save page table linear address
- sub eax,eax ; Fill with zero
- mov ecx,1024
- cld
- rep stosd ; Clear page table
- sub edi,4096
- mov eax,edi
- call GetPhysicalAddress
- mov edx,[PDBR]
- or eax,7 ; Present/write/user bit
- mov [edx+ebx*4],eax ; Save physical address into page directory
- mov eax,cr3
- mov cr3,eax ; Update page table cache
- pop edi
- pop edx
- pop ecx
- pop ebx
- ret
-
-cprocend
-
-;----------------------------------------------------------------------------
-; void MapPhysical2Linear(ulong pAddr, ulong lAddr, int pages, int flags);
-;----------------------------------------------------------------------------
-; Maps physical memory into linear memory
-; Entry: pAddr - Physical address
-; lAddr - Linear address
-; pages - Number of 4K pages to map
-; flags - Page flags
-; bit 0 = present
-; bit 1 = Read(0)/Write(1)
-;----------------------------------------------------------------------------
-cprocstart MapPhysical2Linear
-
- ARG pAddr:ULONG, lAddr:ULONG, pages:UINT, pflags:UINT
-
- enter_c
-
- and [ULONG pAddr],0FFFFF000h; Page boundary
- and [ULONG lAddr],0FFFFF000h; Page boundary
- mov ecx,[pflags]
- and ecx,11b ; Just two bits
- or ecx,100b ; Supervisor bit
- mov [pflags],ecx
-
- mov edx,[lAddr]
- shr edx,22 ; EDX = Directory
- mov esi,[PDBR]
- mov edi,[pages] ; EDI page count
- mov ebx,[lAddr]
-
-@@CreateLoop:
- mov ecx,[esi+edx*4] ; Load page table address
- test ecx,1 ; Is it present?
- jnz @@TableOK
- mov eax,edx
- call CreatePageTable ; Create a page table
-@@TableOK:
- mov eax,ebx
- shr eax,12
- and eax,3FFh
- sub eax,1024
- neg eax ; EAX = page count in this table
- inc edx ; Next table
- mov ebx,0 ; Next time we'll map 1K pages
- sub edi,eax ; Subtract mapped pages from page count
- jns @@CreateLoop ; Create more tables if necessary
-
- mov ecx,[pages] ; ECX = Page count
- mov esi,[lAddr]
- shr esi,12 ; Offset part isn't needed
- mov edi,[pAddr]
-@@MappingLoop:
- mov eax,esi
- shr eax,10 ; EAX = offset to page directory
- mov ebx,[PDBR]
- mov eax,[eax*4+ebx] ; EAX = page table address
- call AccessPage
- mov ebx,esi
- and ebx,3FFh ; EBX = offset to page table
- mov edx,edi
- add edi,4096 ; Next physical address
- inc esi ; Next linear page
- or edx,[pflags] ; Update flags...
- mov [eax+ebx*4],edx ; Store page table entry
- loop @@MappingLoop
- mov eax,cr3
- mov cr3,eax ; Update page table cache
-
- leave_c
- ret
-
-cprocend
-
-endcodeseg _vflat
-
-endif
-
- END ; End of module
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/cpuinfo.c b/board/MAI/bios_emulator/scitech/src/pm/dos/cpuinfo.c
deleted file mode 100644
index ee117c78e9..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/cpuinfo.c
+++ /dev/null
@@ -1,72 +0,0 @@
-/****************************************************************************
-*
-* Ultra Long Period Timer
-*
-* ========================================================================
-*
-* The contents of this file are subject to the SciTech MGL Public
-* License Version 1.0 (the "License"); you may not use this file
-* except in compliance with the License. You may obtain a copy of
-* the License at http://www.scitechsoft.com/mgl-license.txt
-*
-* Software distributed under the License is distributed on an
-* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-* implied. See the License for the specific language governing
-* rights and limitations under the License.
-*
-* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-*
-* The Initial Developer of the Original Code is SciTech Software, Inc.
-* All Rights Reserved.
-*
-* ========================================================================
-*
-* Language: ANSI C
-* Environment: DOS
-*
-* Description: MSDOS specific code for the CPU detection module.
-*
-****************************************************************************/
-
-/*----------------------------- Implementation ----------------------------*/
-
-/* External timing function */
-
-void __ZTimerInit(void);
-
-/****************************************************************************
-REMARKS:
-Do nothing for DOS because we don't have thread priorities.
-****************************************************************************/
-#define SetMaxThreadPriority() 0
-
-/****************************************************************************
-REMARKS:
-Do nothing for DOS because we don't have thread priorities.
-****************************************************************************/
-#define RestoreThreadPriority(i) (void)(i)
-
-/****************************************************************************
-REMARKS:
-Initialise the counter and return the frequency of the counter.
-****************************************************************************/
-static void GetCounterFrequency(
- CPU_largeInteger *freq)
-{
- ulong resolution;
-
- __ZTimerInit();
- ULZTimerResolution(&resolution);
- freq->low = (ulong)(10000000000.0 / resolution);
- freq->high = 0;
-}
-
-/****************************************************************************
-REMARKS:
-Read the counter and return the counter value.
-****************************************************************************/
-#define GetCounter(t) \
-{ \
- (t)->low = ULZReadTime() * 10000L; \
- (t)->high = 0; \
-}
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/event.c b/board/MAI/bios_emulator/scitech/src/pm/dos/event.c
deleted file mode 100644
index a969d111b4..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/event.c
+++ /dev/null
@@ -1,494 +0,0 @@
-/****************************************************************************
-*
-* SciTech OS Portability Manager Library
-*
-* ========================================================================
-*
-* The contents of this file are subject to the SciTech MGL Public
-* License Version 1.0 (the "License"); you may not use this file
-* except in compliance with the License. You may obtain a copy of
-* the License at http://www.scitechsoft.com/mgl-license.txt
-*
-* Software distributed under the License is distributed on an
-* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-* implied. See the License for the specific language governing
-* rights and limitations under the License.
-*
-* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-*
-* The Initial Developer of the Original Code is SciTech Software, Inc.
-* All Rights Reserved.
-*
-* ========================================================================
-*
-* Language: ANSI C
-* Environment: 32-bit DOS
-*
-* Description: 32-bit DOS implementation for the SciTech cross platform
-* event library.
-*
-****************************************************************************/
-
-/*--------------------------- Global variables ----------------------------*/
-
-ibool _VARAPI _EVT_useEvents = true; /* True to use event handling */
-ibool _VARAPI _EVT_installed = 0; /* Event handers installed? */
-uchar _VARAPI *_EVT_biosPtr = NULL; /* Pointer to the BIOS data area */
-static ibool haveMouse = false; /* True if we have a mouse */
-
-/*---------------------------- Implementation -----------------------------*/
-
-/* External assembler functions */
-
-void EVTAPI _EVT_pollJoystick(void);
-uint EVTAPI _EVT_disableInt(void);
-uint EVTAPI _EVT_restoreInt(uint flags);
-void EVTAPI _EVT_codeStart(void);
-void EVTAPI _EVT_codeEnd(void);
-void EVTAPI _EVT_cCodeStart(void);
-void EVTAPI _EVT_cCodeEnd(void);
-int EVTAPI _EVT_getKeyCode(void);
-void EVTAPI _EVT_pumpMessages(void);
-int EVTAPI EVT_rdinx(int port,int index);
-void EVTAPI EVT_wrinx(int port,int index,int value);
-
-#ifdef NO_KEYBOARD_INTERRUPT
-/****************************************************************************
-REMARKS:
-This function is used to pump all keyboard messages from the BIOS keyboard
-handler into our event queue. This can be used to avoid using the
-installable keyboard handler if this is causing problems.
-****************************************************************************/
-static void EVTAPI _EVT_pumpMessages(void)
-{
- RMREGS regs;
- uint key,ps;
-
- /* Since the keyboard ISR has not been installed if NO_IDE_BUG has
- * been defined, we first check for any pending keyboard events
- * here, and if there are some insert them into the event queue to
- * be picked up later - what a kludge.
- */
- while ((key = _EVT_getKeyCode()) != 0) {
- ps = _EVT_disableInt();
- addKeyEvent(EVT_KEYDOWN, key);
- _EVT_restoreInt(ps);
- }
-
- regs.x.ax = 0x0B; /* Reset Move Mouse */
- PM_int86(0x33,&regs,&regs);
-}
-#endif
-
-/****************************************************************************
-REMARKS:
-This function is used to return the number of ticks since system
-startup in milliseconds. This should be the same value that is placed into
-the time stamp fields of events, and is used to implement auto mouse down
-events.
-****************************************************************************/
-ulong _EVT_getTicks(void)
-{
- return (ulong)PM_getLong(_EVT_biosPtr+0x6C) * 55UL;
-}
-
-/****************************************************************************
-REMARKS:
-Reboots the machine from DOS (warm boot)
-****************************************************************************/
-static void Reboot(void)
-{
- PMREGS regs;
- PMSREGS sregs;
-
- ushort *rebootType = PM_mapRealPointer(0x40,0x72);
- *rebootType = 0x1234;
- PM_callRealMode(0xFFFF,0x0000,&regs,&sregs);
-}
-
-/****************************************************************************
-REMARKS:
-Include generic raw scancode keyboard module.
-****************************************************************************/
-#define SUPPORT_CTRL_ALT_DEL
-#include "common/keyboard.c"
-
-/****************************************************************************
-REMARKS:
-This function fools the DOS mouse driver into thinking that it is running
-in graphics mode, rather than text mode so we always get virtual coordinates
-correctly rather than character coordinates.
-****************************************************************************/
-int _EVT_foolMouse(void)
-{
- int oldmode = PM_getByte(_EVT_biosPtr+0x49);
- PM_setByte(_EVT_biosPtr+0x49,0x10);
- oldmode |= (EVT_rdinx(0x3C4,0x2) << 8);
- return oldmode;
-}
-
-/****************************************************************************
-REMARKS:
-This function unfools the DOS mouse driver after we have finished calling it.
-****************************************************************************/
-void _EVT_unfoolMouse(
- int oldmode)
-{
- PM_setByte(_EVT_biosPtr+0x49,oldmode);
-
- /* Some mouse drivers reset the plane mask register for VGA plane 4
- * modes, which screws up the display on some VGA compatible controllers
- * in SuperVGA modes. We reset the value back again in here to solve
- * the problem.
- */
- EVT_wrinx(0x3C4,0x2,oldmode >> 8);
-}
-
-/****************************************************************************
-REMARKS:
-Determines if we have a mouse attached and functioning.
-****************************************************************************/
-static ibool detectMouse(void)
-{
- RMREGS regs;
- RMSREGS sregs;
- uchar *p;
- ibool retval;
-
- regs.x.ax = 0x3533; /* Get interrupt vector 0x33 */
- PM_int86x(0x21,&regs,&regs,&sregs);
-
- /* Check that interrupt vector 0x33 is not a zero, and that the first
- * instruction in the interrupt vector is not an IRET instruction
- */
- p = PM_mapRealPointer(sregs.es, regs.x.bx);
- retval = ((sregs.es != 0) || (regs.x.bx != 0)) && (PM_getByte(p) != 207);
- return retval;
-}
-
-/****************************************************************************
-PARAMETERS:
-what - Event code
-message - Event message
-x,y - Mouse position at time of event
-but_stat - Mouse button status at time of event
-
-REMARKS:
-Adds a new mouse event to the event queue. This routine is called from within
-the mouse interrupt subroutine, so it must be efficient.
-
-NOTE: Interrupts MUST be OFF while this routine is called to ensure we have
- mutually exclusive access to our internal data structures for
- interrupt driven systems (like under DOS).
-****************************************************************************/
-static void addMouseEvent(
- uint what,
- uint message,
- int x,
- int y,
- int mickeyX,
- int mickeyY,
- uint but_stat)
-{
- event_t evt;
-
- if (EVT.count < EVENTQSIZE) {
- /* Save information in event record. */
- evt.when = _EVT_getTicks();
- evt.what = what;
- evt.message = message;
- evt.modifiers = but_stat;
- evt.where_x = x; /* Save mouse event position */
- evt.where_y = y;
- evt.relative_x = mickeyX;
- evt.relative_y = mickeyY;
- evt.modifiers |= EVT.keyModifiers;
- addEvent(&evt); /* Add to tail of event queue */
- }
-}
-
-/****************************************************************************
-PARAMETERS:
-mask - Event mask
-butstate - Button state
-x - Mouse x coordinate
-y - Mouse y coordinate
-
-REMARKS:
-Mouse event handling routine. This gets called when a mouse event occurs,
-and we call the addMouseEvent() routine to add the appropriate mouse event
-to the event queue.
-
-Note: Interrupts are ON when this routine is called by the mouse driver code.
-****************************************************************************/
-static void EVTAPI mouseISR(
- uint mask,
- uint butstate,
- int x,
- int y,
- int mickeyX,
- int mickeyY)
-{
- uint ps;
- uint buttonMask;
-
- if (mask & 1) {
- /* Save the current mouse coordinates */
- EVT.mx = x; EVT.my = y;
-
- /* If the last event was a movement event, then modify the last
- * event rather than post a new one, so that the queue will not
- * become saturated. Before we modify the data structures, we
- * MUST ensure that interrupts are off.
- */
- ps = _EVT_disableInt();
- if (EVT.oldMove != -1) {
- EVT.evtq[EVT.oldMove].where_x = x; /* Modify existing one */
- EVT.evtq[EVT.oldMove].where_y = y;
- EVT.evtq[EVT.oldMove].relative_x += mickeyX;
- EVT.evtq[EVT.oldMove].relative_y += mickeyY;
- }
- else {
- EVT.oldMove = EVT.freeHead; /* Save id of this move event */
- addMouseEvent(EVT_MOUSEMOVE,0,x,y,mickeyX,mickeyY,butstate);
- }
- _EVT_restoreInt(ps);
- }
- if (mask & 0x2A) {
- ps = _EVT_disableInt();
- buttonMask = 0;
- if (mask & 2) buttonMask |= EVT_LEFTBMASK;
- if (mask & 8) buttonMask |= EVT_RIGHTBMASK;
- if (mask & 32) buttonMask |= EVT_MIDDLEBMASK;
- addMouseEvent(EVT_MOUSEDOWN,buttonMask,x,y,0,0,butstate);
- EVT.oldMove = -1;
- _EVT_restoreInt(ps);
- }
- if (mask & 0x54) {
- ps = _EVT_disableInt();
- buttonMask = 0;
- if (mask & 2) buttonMask |= EVT_LEFTBMASK;
- if (mask & 8) buttonMask |= EVT_RIGHTBMASK;
- if (mask & 32) buttonMask |= EVT_MIDDLEBMASK;
- addMouseEvent(EVT_MOUSEUP,buttonMask,x,y,0,0,butstate);
- EVT.oldMove = -1;
- _EVT_restoreInt(ps);
- }
- EVT.oldKey = -1;
-}
-
-/****************************************************************************
-REMARKS:
-Keyboard interrupt handler function.
-
-NOTE: Interrupts are OFF when this routine is called by the keyboard ISR,
- and we leave them OFF the entire time.
-****************************************************************************/
-static void EVTAPI keyboardISR(void)
-{
- processRawScanCode(PM_inpb(0x60));
- PM_outpb(0x20,0x20);
-}
-
-/****************************************************************************
-REMARKS:
-Safely abort the event module upon catching a fatal error.
-****************************************************************************/
-void _EVT_abort()
-{
- EVT_exit();
- PM_fatalError("Unhandled exception!");
-}
-
-/****************************************************************************
-PARAMETERS:
-mouseMove - Callback function to call wheneve the mouse needs to be moved
-
-REMARKS:
-Initiliase the event handling module. Here we install our mouse handling ISR
-to be called whenever any button's are pressed or released. We also build
-the free list of events in the event queue.
-
-We use handler number 2 of the mouse libraries interrupt handlers for our
-event handling routines.
-****************************************************************************/
-void EVTAPI EVT_init(
- _EVT_mouseMoveHandler mouseMove)
-{
- int i;
-
- PM_init();
- EVT.mouseMove = mouseMove;
- _EVT_biosPtr = PM_getBIOSPointer();
- EVT_resume();
-
- /* Grab all characters pending in the keyboard buffer and stuff
- * them into our event buffer. This allows us to pick up any keypresses
- * while the program is initialising.
- */
- while ((i = _EVT_getKeyCode()) != 0)
- addKeyEvent(EVT_KEYDOWN,i);
-}
-
-/****************************************************************************
-REMARKS:
-Initiailises the internal event handling modules. The EVT_suspend function
-can be called to suspend event handling (such as when shelling out to DOS),
-and this function can be used to resume it again later.
-****************************************************************************/
-void EVTAPI EVT_resume(void)
-{
- static int locked = 0;
- int stat;
- uchar mods;
- PM_lockHandle lh; /* Unused in DOS */
-
- if (_EVT_useEvents) {
- /* Initialise the event queue and enable our interrupt handlers */
- initEventQueue();
-#ifndef NO_KEYBOARD_INTERRUPT
- PM_setKeyHandler(keyboardISR);
-#endif
-#ifndef NO_MOUSE_INTERRUPT
- if ((haveMouse = detectMouse()) != 0) {
- int oldmode = _EVT_foolMouse();
- PM_setMouseHandler(0xFFFF,mouseISR);
- _EVT_unfoolMouse(oldmode);
- }
-#endif
-
- /* Read the keyboard modifier flags from the BIOS to get the
- * correct initialisation state. The only state we care about is
- * the correct toggle state flags such as SCROLLLOCK, NUMLOCK and
- * CAPSLOCK.
- */
- EVT.keyModifiers = 0;
- mods = PM_getByte(_EVT_biosPtr+0x17);
- if (mods & 0x10)
- EVT.keyModifiers |= EVT_SCROLLLOCK;
- if (mods & 0x20)
- EVT.keyModifiers |= EVT_NUMLOCK;
- if (mods & 0x40)
- EVT.keyModifiers |= EVT_CAPSLOCK;
-
- /* Lock all of the code and data used by our protected mode interrupt
- * handling routines, so that it will continue to work correctly
- * under real mode.
- */
- if (!locked) {
- /* It is difficult to ensure that we lock our global data, so we
- * do this by taking the address of a variable locking all data
- * 2Kb on either side. This should properly cover the global data
- * used by the module (the other alternative is to declare the
- * variables in assembler, in which case we know it will be
- * correct).
- */
- stat = !PM_lockDataPages(&EVT,sizeof(EVT),&lh);
- stat |= !PM_lockDataPages(&_EVT_biosPtr,sizeof(_EVT_biosPtr),&lh);
- stat |= !PM_lockCodePages((__codePtr)_EVT_cCodeStart,(int)_EVT_cCodeEnd-(int)_EVT_cCodeStart,&lh);
- stat |= !PM_lockCodePages((__codePtr)_EVT_codeStart,(int)_EVT_codeEnd-(int)_EVT_codeStart,&lh);
- if (stat) {
- PM_fatalError("Page locking services failed - interrupt handling not safe!");
- exit(1);
- }
- locked = 1;
- }
-
- /* Catch program termination signals so we can clean up properly */
- signal(SIGABRT, _EVT_abort);
- signal(SIGFPE, _EVT_abort);
- signal(SIGINT, _EVT_abort);
- _EVT_installed = true;
- }
-}
-
-/****************************************************************************
-REMARKS
-Changes the range of coordinates returned by the mouse functions to the
-specified range of values. This is used when changing between graphics
-modes set the range of mouse coordinates for the new display mode.
-****************************************************************************/
-void EVTAPI EVT_setMouseRange(
- int xRes,
- int yRes)
-{
- RMREGS regs;
-
- if (haveMouse) {
- int oldmode = _EVT_foolMouse();
- PM_resetMouseDriver(1);
- regs.x.ax = 7; /* Mouse function 7 - Set horizontal min and max */
- regs.x.cx = 0;
- regs.x.dx = xRes;
- PM_int86(0x33,&regs,&regs);
- regs.x.ax = 8; /* Mouse function 8 - Set vertical min and max */
- regs.x.cx = 0;
- regs.x.dx = yRes;
- PM_int86(0x33,&regs,&regs);
- _EVT_unfoolMouse(oldmode);
- }
-}
-
-/****************************************************************************
-REMARKS
-Modifes the mouse coordinates as necessary if scaling to OS coordinates,
-and sets the OS mouse cursor position.
-****************************************************************************/
-void _EVT_setMousePos(
- int *x,
- int *y)
-{
- RMREGS regs;
-
- if (haveMouse) {
- int oldmode = _EVT_foolMouse();
- regs.x.ax = 4; /* Mouse function 4 - Set mouse position */
- regs.x.cx = *x; /* New horizontal coordinate */
- regs.x.dx = *y; /* New vertical coordinate */
- PM_int86(0x33,&regs,&regs);
- _EVT_unfoolMouse(oldmode);
- }
-}
-
-/****************************************************************************
-REMARKS
-Suspends all of our event handling operations. This is also used to
-de-install the event handling code.
-****************************************************************************/
-void EVTAPI EVT_suspend(void)
-{
- uchar mods;
-
- if (_EVT_installed) {
- /* Restore the interrupt handlers */
- PM_restoreKeyHandler();
- if (haveMouse)
- PM_restoreMouseHandler();
- signal(SIGABRT, SIG_DFL);
- signal(SIGFPE, SIG_DFL);
- signal(SIGINT, SIG_DFL);
-
- /* Set the keyboard modifier flags in the BIOS to our values */
- EVT_allowLEDS(true);
- mods = PM_getByte(_EVT_biosPtr+0x17) & ~0x70;
- if (EVT.keyModifiers & EVT_SCROLLLOCK)
- mods |= 0x10;
- if (EVT.keyModifiers & EVT_NUMLOCK)
- mods |= 0x20;
- if (EVT.keyModifiers & EVT_CAPSLOCK)
- mods |= 0x40;
- PM_setByte(_EVT_biosPtr+0x17,mods);
-
- /* Flag that we are no longer installed */
- _EVT_installed = false;
- }
-}
-
-/****************************************************************************
-REMARKS
-Exits the event module for program terminatation.
-****************************************************************************/
-void EVTAPI EVT_exit(void)
-{
- EVT_suspend();
-}
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/oshdr.h b/board/MAI/bios_emulator/scitech/src/pm/dos/oshdr.h
deleted file mode 100644
index 35e8e00f72..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/oshdr.h
+++ /dev/null
@@ -1,29 +0,0 @@
-/****************************************************************************
-*
-* SciTech OS Portability Manager Library
-*
-* ========================================================================
-*
-* The contents of this file are subject to the SciTech MGL Public
-* License Version 1.0 (the "License"); you may not use this file
-* except in compliance with the License. You may obtain a copy of
-* the License at http://www.scitechsoft.com/mgl-license.txt
-*
-* Software distributed under the License is distributed on an
-* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-* implied. See the License for the specific language governing
-* rights and limitations under the License.
-*
-* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-*
-* The Initial Developer of the Original Code is SciTech Software, Inc.
-* All Rights Reserved.
-*
-* ========================================================================
-*
-* Language: ANSI C
-* Environment: 32-bit DOS
-*
-* Description: Include file to include all OS specific header files.
-*
-****************************************************************************/
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/pm.c b/board/MAI/bios_emulator/scitech/src/pm/dos/pm.c
deleted file mode 100644
index 2ad9e34f91..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/pm.c
+++ /dev/null
@@ -1,2243 +0,0 @@
-/****************************************************************************
-*
-* SciTech OS Portability Manager Library
-*
-* ========================================================================
-*
-* The contents of this file are subject to the SciTech MGL Public
-* License Version 1.0 (the "License"); you may not use this file
-* except in compliance with the License. You may obtain a copy of
-* the License at http://www.scitechsoft.com/mgl-license.txt
-*
-* Software distributed under the License is distributed on an
-* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-* implied. See the License for the specific language governing
-* rights and limitations under the License.
-*
-* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-*
-* The Initial Developer of the Original Code is SciTech Software, Inc.
-* All Rights Reserved.
-*
-* ========================================================================
-*
-* Language: ANSI C
-* Environment: 16/32 bit DOS
-*
-* Description: Implementation for the OS Portability Manager Library, which
-* contains functions to implement OS specific services in a
-* generic, cross platform API. Porting the OS Portability
-* Manager library is the first step to porting any SciTech
-* products to a new platform.
-*
-****************************************************************************/
-
-#include "pmapi.h"
-#include "drvlib/os/os.h"
-#include "ztimerc.h"
-#include "mtrr.h"
-#include "pm_help.h"
-#include <stdio.h>
-#include <stdlib.h>
-#include <string.h>
-#include <dos.h>
-#include <conio.h>
-#ifdef __GNUC__
-#include <unistd.h>
-#include <sys/nearptr.h>
-#include <sys/stat.h>
-#else
-#include <direct.h>
-#endif
-#ifdef __BORLANDC__
-#pragma warn -par
-#endif
-
-/*--------------------------- Global variables ----------------------------*/
-
-typedef struct {
- int oldMode;
- int old50Lines;
- } DOS_stateBuf;
-
-#define MAX_RM_BLOCKS 10
-
-static struct {
- void *p;
- uint tag;
- } rmBlocks[MAX_RM_BLOCKS];
-
-static uint VESABuf_len = 1024; /* Length of the VESABuf buffer */
-static void *VESABuf_ptr = NULL; /* Near pointer to VESABuf */
-static uint VESABuf_rseg; /* Real mode segment of VESABuf */
-static uint VESABuf_roff; /* Real mode offset of VESABuf */
-static void (PMAPIP fatalErrorCleanup)(void) = NULL;
-ushort _VARAPI _PM_savedDS = 0;
-#ifdef DOS4GW
-static ulong PDB = 0,*pPDB = NULL;
-#endif
-#ifndef REALMODE
-static char VXD_name[] = PMHELP_NAME;
-static char VXD_module[] = PMHELP_MODULE;
-static char VXD_DDBName[] = PMHELP_DDBNAME;
-static uint VXD_version = -1;
-static uint VXD_loadOff = 0;
-static uint VXD_loadSel = 0;
-uint _VARAPI _PM_VXD_off = 0;
-uint _VARAPI _PM_VXD_sel = 0;
-int _VARAPI _PM_haveCauseWay = -1;
-
-/* Memory mapping cache */
-
-#define MAX_MEMORY_MAPPINGS 100
-typedef struct {
- ulong physical;
- ulong linear;
- ulong limit;
- } mmapping;
-static mmapping maps[MAX_MEMORY_MAPPINGS] = {0};
-static int numMaps = 0;
-
-/* Page sized block cache */
-
-#define PAGES_PER_BLOCK 100
-#define FREELIST_NEXT(p) (*(void**)(p))
-typedef struct pageblock {
- struct pageblock *next;
- struct pageblock *prev;
- void *freeListStart;
- void *freeList;
- void *freeListEnd;
- int freeCount;
- } pageblock;
-static pageblock *pageBlocks = NULL;
-#endif
-
-/* Start of all page tables in CauseWay */
-
-#define CW_PAGE_TABLE_START (1024UL*4096UL*1023UL)
-
-/*----------------------------- Implementation ----------------------------*/
-
-/* External assembler functions */
-
-ulong _ASMAPI _PM_getPDB(void);
-int _ASMAPI _PM_pagingEnabled(void);
-void _ASMAPI _PM_VxDCall(VXD_regs *regs,uint off,uint sel);
-
-#ifndef REALMODE
-/****************************************************************************
-REMARKS:
-Exit function to unload the dynamically loaded VxD
-****************************************************************************/
-static void UnloadVxD(void)
-{
- PMSREGS sregs;
- VXD_regs r;
-
- r.eax = 2;
- r.ebx = 0;
- r.edx = (uint)VXD_module;
- PM_segread(&sregs);
-#ifdef __16BIT__
- r.ds = ((ulong)VXD_module) >> 16;
-#else
- r.ds = sregs.ds;
-#endif
- r.es = sregs.es;
- _PM_VxDCall(&r,VXD_loadOff,VXD_loadSel);
-}
-
-/****************************************************************************
-REMARKS:
-External function to call the PMHELP helper VxD.
-****************************************************************************/
-void PMAPI PM_VxDCall(
- VXD_regs *regs)
-{
- if (_PM_VXD_sel != 0 || _PM_VXD_off != 0)
- _PM_VxDCall(regs,_PM_VXD_off,_PM_VXD_sel);
-}
-
-/****************************************************************************
-RETURNS:
-BCD coded version number of the VxD, or 0 if not loaded (ie: 0x202 - 2.2)
-
-REMARKS:
-This function gets the version number for the VxD that we have connected to.
-****************************************************************************/
-uint PMAPI PMHELP_getVersion(void)
-{
- VXD_regs r;
-
- /* Call the helper VxD to determine the version number */
- if (_PM_VXD_sel != 0 || _PM_VXD_off != 0) {
- memset(&r,0,sizeof(r));
- r.eax = API_NUM(PMHELP_GETVER);
- _PM_VxDCall(&r,_PM_VXD_off,_PM_VXD_sel);
- return VXD_version = (uint)r.eax;
- }
- return VXD_version = 0;
-}
-
-/****************************************************************************
-DESCRIPTION:
-Connects to the helper VxD and returns the version number
-
-RETURNS:
-True if the VxD was found and loaded, false otherwise.
-
-REMARKS:
-This function connects to the VxD (loading it if it is dynamically loadable)
-and returns the version number of the VxD.
-****************************************************************************/
-static ibool PMHELP_connect(void)
-{
- PMREGS regs;
- PMSREGS sregs;
- VXD_regs r;
-
- /* Bail early if we have alread connected */
- if (VXD_version != -1)
- return VXD_version != 0;
-
- /* Get the static SDDHELP.VXD entry point if available */
- PM_segread(&sregs);
- regs.x.ax = 0x1684;
- regs.x.bx = SDDHELP_DeviceID;
- regs.x.di = 0;
- sregs.es = 0;
- PM_int386x(0x2F,&regs,&regs,&sregs);
- _PM_VXD_sel = sregs.es;
- _PM_VXD_off = regs.x.di;
- if (_PM_VXD_sel != 0 || _PM_VXD_off != 0) {
- if (PMHELP_getVersion() >= PMHELP_VERSION)
- return true;
- }
-
- /* If we get here, then either SDDHELP.VXD is not loaded, or it is an
- * earlier version. In this case try to dynamically load the PMHELP.VXD
- * helper VxD instead.
- */
- PM_segread(&sregs);
- regs.x.ax = 0x1684;
- regs.x.bx = VXDLDR_DeviceID;
- regs.x.di = 0;
- sregs.es = 0;
- PM_int386x(0x2F,&regs,&regs,&sregs);
- VXD_loadSel = sregs.es;
- VXD_loadOff = regs.x.di;
- if (VXD_loadSel == 0 && VXD_loadOff == 0)
- return VXD_version = 0;
- r.eax = 1;
- r.ebx = 0;
- r.edx = (uint)VXD_name;
- PM_segread(&sregs);
- r.ds = sregs.ds;
- r.es = sregs.es;
- _PM_VxDCall(&r,VXD_loadOff,VXD_loadSel);
- if (r.eax != 0)
- return VXD_version = 0;
-
- /* Get the dynamic VxD entry point so we can call it */
- atexit(UnloadVxD);
- PM_segread(&sregs);
- regs.x.ax = 0x1684;
- regs.x.bx = 0;
- regs.e.edi = (uint)VXD_DDBName;
- PM_int386x(0x2F,&regs,&regs,&sregs);
- _PM_VXD_sel = sregs.es;
- _PM_VXD_off = regs.x.di;
- if (_PM_VXD_sel == 0 && _PM_VXD_off == 0)
- return VXD_version = 0;
- if (PMHELP_getVersion() >= PMHELP_VERSION)
- return true;
- return VXD_version = 0;
-}
-#endif
-
-/****************************************************************************
-REMARKS:
-Initialise the PM library. First we try to connect to a static SDDHELP.VXD
-helper VxD, and check that it is a version we can use. If not we try to
-dynamically load the PMHELP.VXD helper VxD
-****************************************************************************/
-void PMAPI PM_init(void)
-{
-#ifndef REALMODE
- PMREGS regs;
-
- /* Check if we are running under CauseWay under real DOS */
- if (_PM_haveCauseWay == -1) {
- /* Check if we are running under DPMI in which case we will not be
- * able to use our special ring 0 CauseWay functions.
- */
- _PM_haveCauseWay = false;
- regs.x.ax = 0xFF00;
- PM_int386(0x31,&regs,&regs);
- if (regs.x.cflag || !(regs.e.edi & 8)) {
- /* We are not under DPMI, so now check if CauseWay is active */
- regs.x.ax = 0xFFF9;
- PM_int386(0x31,&regs,&regs);
- if (!regs.x.cflag && regs.e.ecx == 0x43415553 && regs.e.edx == 0x45574159)
- _PM_haveCauseWay = true;
- }
-
- /* Now connect to PMHELP.VXD and initialise MTRR module */
- if (!PMHELP_connect())
- MTRR_init();
- }
-#endif
-}
-
-/****************************************************************************
-PARAMETERS:
-base - The starting physical base address of the region
-size - The size in bytes of the region
-type - Type to place into the MTRR register
-
-RETURNS:
-Error code describing the result.
-
-REMARKS:
-Function to enable write combining for the specified region of memory.
-****************************************************************************/
-int PMAPI PM_enableWriteCombine(
- ulong base,
- ulong size,
- uint type)
-{
-#ifndef REALMODE
- VXD_regs regs;
-
- if (PMHELP_connect()) {
- memset(&regs,0,sizeof(regs));
- regs.eax = API_NUM(PMHELP_ENABLELFBCOMB);
- regs.ebx = base;
- regs.ecx = size;
- regs.edx = type;
- _PM_VxDCall(&regs,_PM_VXD_off,_PM_VXD_sel);
- return regs.eax;
- }
- return MTRR_enableWriteCombine(base,size,type);
-#else
- return PM_MTRR_NOT_SUPPORTED;
-#endif
-}
-
-ibool PMAPI PM_haveBIOSAccess(void)
-{ return true; }
-
-long PMAPI PM_getOSType(void)
-{ return _OS_DOS; }
-
-int PMAPI PM_getModeType(void)
-{
-#if defined(REALMODE)
- return PM_realMode;
-#elif defined(PM286)
- return PM_286;
-#elif defined(PM386)
- return PM_386;
-#endif
-}
-
-void PMAPI PM_backslash(char *s)
-{
- uint pos = strlen(s);
- if (s[pos-1] != '\\') {
- s[pos] = '\\';
- s[pos+1] = '\0';
- }
-}
-
-void PMAPI PM_setFatalErrorCleanup(
- void (PMAPIP cleanup)(void))
-{
- fatalErrorCleanup = cleanup;
-}
-
-void PMAPI PM_fatalError(const char *msg)
-{
- if (fatalErrorCleanup)
- fatalErrorCleanup();
- fprintf(stderr,"%s\n", msg);
- exit(1);
-}
-
-static void ExitVBEBuf(void)
-{
- if (VESABuf_ptr)
- PM_freeRealSeg(VESABuf_ptr);
- VESABuf_ptr = 0;
-}
-
-void * PMAPI PM_getVESABuf(uint *len,uint *rseg,uint *roff)
-{
- if (!VESABuf_ptr) {
- /* Allocate a global buffer for communicating with the VESA VBE */
- if ((VESABuf_ptr = PM_allocRealSeg(VESABuf_len, &VESABuf_rseg, &VESABuf_roff)) == NULL)
- return NULL;
- atexit(ExitVBEBuf);
- }
- *len = VESABuf_len;
- *rseg = VESABuf_rseg;
- *roff = VESABuf_roff;
- return VESABuf_ptr;
-}
-
-int PMAPI PM_int386(int intno, PMREGS *in, PMREGS *out)
-{
- PMSREGS sregs;
- PM_segread(&sregs);
- return PM_int386x(intno,in,out,&sregs);
-}
-
-/* Routines to set and get the real mode interrupt vectors, by making
- * direct real mode calls to DOS and bypassing the DOS extenders API.
- * This is the safest way to handle this, as some servers try to be
- * smart about changing real mode vectors.
- */
-
-void PMAPI _PM_getRMvect(int intno, long *realisr)
-{
- RMREGS regs;
- RMSREGS sregs;
-
- PM_saveDS();
- regs.h.ah = 0x35;
- regs.h.al = intno;
- PM_int86x(0x21, &regs, &regs, &sregs);
- *realisr = ((long)sregs.es << 16) | regs.x.bx;
-}
-
-void PMAPI _PM_setRMvect(int intno, long realisr)
-{
- RMREGS regs;
- RMSREGS sregs;
-
- PM_saveDS();
- regs.h.ah = 0x25;
- regs.h.al = intno;
- sregs.ds = (int)(realisr >> 16);
- regs.x.dx = (int)(realisr & 0xFFFF);
- PM_int86x(0x21, &regs, &regs, &sregs);
-}
-
-void PMAPI _PM_addRealModeBlock(void *mem,uint tag)
-{
- int i;
-
- for (i = 0; i < MAX_RM_BLOCKS; i++) {
- if (rmBlocks[i].p == NULL) {
- rmBlocks[i].p = mem;
- rmBlocks[i].tag = tag;
- return;
- }
- }
- PM_fatalError("To many real mode memory block allocations!");
-}
-
-uint PMAPI _PM_findRealModeBlock(void *mem)
-{
- int i;
-
- for (i = 0; i < MAX_RM_BLOCKS; i++) {
- if (rmBlocks[i].p == mem)
- return rmBlocks[i].tag;
- }
- PM_fatalError("Could not find prior real mode memory block allocation!");
- return 0;
-}
-
-char * PMAPI PM_getCurrentPath(
- char *path,
- int maxLen)
-{
- return getcwd(path,maxLen);
-}
-
-char PMAPI PM_getBootDrive(void)
-{ return 'C'; }
-
-const char * PMAPI PM_getVBEAFPath(void)
-{ return "c:\\"; }
-
-const char * PMAPI PM_getNucleusPath(void)
-{
- static char path[256];
- char *env;
-
- if ((env = getenv("NUCLEUS_PATH")) != NULL)
- return env;
- if ((env = getenv("WINBOOTDIR")) != NULL) {
- /* Running in a Windows 9x DOS box or DOS mode */
- strcpy(path,env);
- strcat(path,"\\system\\nucleus");
- return path;
- }
- if ((env = getenv("SystemRoot")) != NULL) {
- /* Running in an NT/2K DOS box */
- strcpy(path,env);
- strcat(path,"\\system32\\nucleus");
- return path;
- }
- return "c:\\nucleus";
-}
-
-const char * PMAPI PM_getNucleusConfigPath(void)
-{
- static char path[256];
- strcpy(path,PM_getNucleusPath());
- PM_backslash(path);
- strcat(path,"config");
- return path;
-}
-
-const char * PMAPI PM_getUniqueID(void)
-{ return "DOS"; }
-
-const char * PMAPI PM_getMachineName(void)
-{ return "DOS"; }
-
-int PMAPI PM_kbhit(void)
-{
- return kbhit();
-}
-
-int PMAPI PM_getch(void)
-{
- return getch();
-}
-
-PM_HWND PMAPI PM_openConsole(PM_HWND hwndUser,int device,int xRes,int yRes,int bpp,ibool fullScreen)
-{
- /* Not used for DOS */
- (void)hwndUser;
- (void)device;
- (void)xRes;
- (void)yRes;
- (void)bpp;
- (void)fullScreen;
- return 0;
-}
-
-int PMAPI PM_getConsoleStateSize(void)
-{
- return sizeof(DOS_stateBuf);
-}
-
-void PMAPI PM_saveConsoleState(void *stateBuf,PM_HWND hwndConsole)
-{
- RMREGS regs;
- DOS_stateBuf *sb = stateBuf;
-
- /* Save the old video mode state */
- regs.h.ah = 0x0F;
- PM_int86(0x10,&regs,&regs);
- sb->oldMode = regs.h.al & 0x7F;
- sb->old50Lines = false;
- if (sb->oldMode == 0x3) {
- regs.x.ax = 0x1130;
- regs.x.bx = 0;
- regs.x.dx = 0;
- PM_int86(0x10,&regs,&regs);
- sb->old50Lines = (regs.h.dl == 42 || regs.h.dl == 49);
- }
- (void)hwndConsole;
-}
-
-void PMAPI PM_setSuspendAppCallback(int (_ASMAPIP saveState)(int flags))
-{
- /* Not used for DOS */
- (void)saveState;
-}
-
-void PMAPI PM_restoreConsoleState(const void *stateBuf,PM_HWND hwndConsole)
-{
- RMREGS regs;
- const DOS_stateBuf *sb = stateBuf;
-
- /* Retore 50 line mode if set */
- if (sb->old50Lines) {
- regs.x.ax = 0x1112;
- regs.x.bx = 0;
- PM_int86(0x10,&regs,&regs);
- }
- (void)hwndConsole;
-}
-
-void PMAPI PM_closeConsole(PM_HWND hwndConsole)
-{
- /* Not used for DOS */
- (void)hwndConsole;
-}
-
-void PMAPI PM_setOSCursorLocation(int x,int y)
-{
- uchar *_biosPtr = PM_getBIOSPointer();
- PM_setByte(_biosPtr+0x50,x);
- PM_setByte(_biosPtr+0x51,y);
-}
-
-void PMAPI PM_setOSScreenWidth(int width,int height)
-{
- uchar *_biosPtr = PM_getBIOSPointer();
- PM_setWord(_biosPtr+0x4A,width);
- PM_setWord(_biosPtr+0x4C,width*2);
- PM_setByte(_biosPtr+0x84,height-1);
- if (height > 25) {
- PM_setWord(_biosPtr+0x60,0x0607);
- PM_setByte(_biosPtr+0x85,0x08);
- }
- else {
- PM_setWord(_biosPtr+0x60,0x0D0E);
- PM_setByte(_biosPtr+0x85,0x016);
- }
-}
-
-void * PMAPI PM_mallocShared(long size)
-{
- return PM_malloc(size);
-}
-
-void PMAPI PM_freeShared(void *ptr)
-{
- PM_free(ptr);
-}
-
-#define GetRMVect(intno,isr) *(isr) = ((ulong*)rmZeroPtr)[intno]
-#define SetRMVect(intno,isr) ((ulong*)rmZeroPtr)[intno] = (isr)
-
-ibool PMAPI PM_doBIOSPOST(
- ushort axVal,
- ulong BIOSPhysAddr,
- void *mappedBIOS,
- ulong BIOSLen)
-{
- static int firstTime = true;
- static uchar *rmZeroPtr;
- long Current10,Current6D,Current42;
- RMREGS regs;
- RMSREGS sregs;
-
- /* Create a zero memory mapping for us to use */
- if (firstTime) {
- rmZeroPtr = PM_mapPhysicalAddr(0,0x7FFF,true);
- firstTime = false;
- }
-
- /* Remap the secondary BIOS to 0xC0000 physical */
- if (BIOSPhysAddr != 0xC0000L || BIOSLen > 32768) {
- /* DOS cannot virtually remap the BIOS, so we can only work if all
- * the secondary controllers are identical, and we then use the
- * BIOS on the first controller for all the remaining controllers.
- *
- * For OS'es that do virtual memory, and remapping of 0xC0000
- * physical (perhaps a copy on write mapping) should be all that
- * is needed.
- */
- return false;
- }
-
- /* Save current handlers of int 10h and 6Dh */
- GetRMVect(0x10,&Current10);
- GetRMVect(0x6D,&Current6D);
-
- /* POST the secondary BIOS */
- GetRMVect(0x42,&Current42);
- SetRMVect(0x10,Current42); /* Restore int 10h to STD-BIOS */
- regs.x.ax = axVal;
- PM_callRealMode(0xC000,0x0003,&regs,&sregs);
-
- /* Restore current handlers */
- SetRMVect(0x10,Current10);
- SetRMVect(0x6D,Current6D);
-
- /* Second the primary BIOS mappin 1:1 for 0xC0000 physical */
- if (BIOSPhysAddr != 0xC0000L) {
- /* DOS does not support this */
- (void)mappedBIOS;
- }
- return true;
-}
-
-void PMAPI PM_sleep(ulong milliseconds)
-{
- ulong microseconds = milliseconds * 1000L;
- LZTimerObject tm;
-
- LZTimerOnExt(&tm);
- while (LZTimerLapExt(&tm) < microseconds)
- ;
- LZTimerOffExt(&tm);
-}
-
-int PMAPI PM_getCOMPort(int port)
-{
- switch (port) {
- case 0: return 0x3F8;
- case 1: return 0x2F8;
- }
- return 0;
-}
-
-int PMAPI PM_getLPTPort(int port)
-{
- switch (port) {
- case 0: return 0x3BC;
- case 1: return 0x378;
- case 2: return 0x278;
- }
- return 0;
-}
-
-PM_MODULE PMAPI PM_loadLibrary(
- const char *szDLLName)
-{
- (void)szDLLName;
- return NULL;
-}
-
-void * PMAPI PM_getProcAddress(
- PM_MODULE hModule,
- const char *szProcName)
-{
- (void)hModule;
- (void)szProcName;
- return NULL;
-}
-
-void PMAPI PM_freeLibrary(
- PM_MODULE hModule)
-{
- (void)hModule;
-}
-
-int PMAPI PM_setIOPL(
- int level)
-{
- return level;
-}
-
-/****************************************************************************
-REMARKS:
-Internal function to convert the find data to the generic interface.
-****************************************************************************/
-static void convertFindData(
- PM_findData *findData,
- struct find_t *blk)
-{
- ulong dwSize = findData->dwSize;
-
- memset(findData,0,findData->dwSize);
- findData->dwSize = dwSize;
- if (blk->attrib & _A_RDONLY)
- findData->attrib |= PM_FILE_READONLY;
- if (blk->attrib & _A_SUBDIR)
- findData->attrib |= PM_FILE_DIRECTORY;
- if (blk->attrib & _A_ARCH)
- findData->attrib |= PM_FILE_ARCHIVE;
- if (blk->attrib & _A_HIDDEN)
- findData->attrib |= PM_FILE_HIDDEN;
- if (blk->attrib & _A_SYSTEM)
- findData->attrib |= PM_FILE_SYSTEM;
- findData->sizeLo = blk->size;
- strncpy(findData->name,blk->name,PM_MAX_PATH);
- findData->name[PM_MAX_PATH-1] = 0;
-}
-
-#define FIND_MASK (_A_RDONLY | _A_ARCH | _A_SUBDIR | _A_HIDDEN | _A_SYSTEM)
-
-/****************************************************************************
-REMARKS:
-Function to find the first file matching a search criteria in a directory.
-****************************************************************************/
-void * PMAPI PM_findFirstFile(
- const char *filename,
- PM_findData *findData)
-{
- struct find_t *blk;
-
- if ((blk = PM_malloc(sizeof(*blk))) == NULL)
- return PM_FILE_INVALID;
- if (_dos_findfirst((char*)filename,FIND_MASK,blk) == 0) {
- convertFindData(findData,blk);
- return blk;
- }
- return PM_FILE_INVALID;
-}
-
-/****************************************************************************
-REMARKS:
-Function to find the next file matching a search criteria in a directory.
-****************************************************************************/
-ibool PMAPI PM_findNextFile(
- void *handle,
- PM_findData *findData)
-{
- struct find_t *blk = handle;
-
- if (_dos_findnext(blk) == 0) {
- convertFindData(findData,blk);
- return true;
- }
- return false;
-}
-
-/****************************************************************************
-REMARKS:
-Function to close the find process
-****************************************************************************/
-void PMAPI PM_findClose(
- void *handle)
-{
- PM_free(handle);
-}
-
-/****************************************************************************
-REMARKS:
-Function to determine if a drive is a valid drive or not. Under Unix this
-function will return false for anything except a value of 3 (considered
-the root drive, and equivalent to C: for non-Unix systems). The drive
-numbering is:
-
- 1 - Drive A:
- 2 - Drive B:
- 3 - Drive C:
- etc
-
-****************************************************************************/
-ibool PMAPI PM_driveValid(
- char drive)
-{
- RMREGS regs;
- regs.h.dl = (uchar)(drive - 'A' + 1);
- regs.h.ah = 0x36; /* Get disk information service */
- PM_int86(0x21,&regs,&regs);
- return regs.x.ax != 0xFFFF; /* AX = 0xFFFF if disk is invalid */
-}
-
-/****************************************************************************
-REMARKS:
-Function to get the current working directory for the specififed drive.
-Under Unix this will always return the current working directory regardless
-of what the value of 'drive' is.
-****************************************************************************/
-void PMAPI PM_getdcwd(
- int drive,
- char *dir,
- int len)
-{
- uint oldDrive,maxDrives;
- _dos_getdrive(&oldDrive);
- _dos_setdrive(drive,&maxDrives);
- getcwd(dir,len);
- _dos_setdrive(oldDrive,&maxDrives);
-}
-
-/****************************************************************************
-REMARKS:
-Function to change the file attributes for a specific file.
-****************************************************************************/
-void PMAPI PM_setFileAttr(
- const char *filename,
- uint attrib)
-{
-#if defined(TNT) && defined(_MSC_VER)
- DWORD attr = 0;
-
- if (attrib & PM_FILE_READONLY)
- attr |= FILE_ATTRIBUTE_READONLY;
- if (attrib & PM_FILE_ARCHIVE)
- attr |= FILE_ATTRIBUTE_ARCHIVE;
- if (attrib & PM_FILE_HIDDEN)
- attr |= FILE_ATTRIBUTE_HIDDEN;
- if (attrib & PM_FILE_SYSTEM)
- attr |= FILE_ATTRIBUTE_SYSTEM;
- SetFileAttributes((LPSTR)filename, attr);
-#else
- uint attr = 0;
-
- if (attrib & PM_FILE_READONLY)
- attr |= _A_RDONLY;
- if (attrib & PM_FILE_ARCHIVE)
- attr |= _A_ARCH;
- if (attrib & PM_FILE_HIDDEN)
- attr |= _A_HIDDEN;
- if (attrib & PM_FILE_SYSTEM)
- attr |= _A_SYSTEM;
- _dos_setfileattr(filename,attr);
-#endif
-}
-
-/****************************************************************************
-REMARKS:
-Function to create a directory.
-****************************************************************************/
-ibool PMAPI PM_mkdir(
- const char *filename)
-{
-#ifdef __GNUC__
- return mkdir(filename,S_IRUSR) == 0;
-#else
- return mkdir(filename) == 0;
-#endif
-}
-
-/****************************************************************************
-REMARKS:
-Function to remove a directory.
-****************************************************************************/
-ibool PMAPI PM_rmdir(
- const char *filename)
-{
- return rmdir(filename) == 0;
-}
-
-/*-------------------------------------------------------------------------*/
-/* Generic DPMI routines common to 16/32 bit code */
-/*-------------------------------------------------------------------------*/
-
-#ifndef REALMODE
-ulong PMAPI DPMI_mapPhysicalToLinear(ulong physAddr,ulong limit)
-{
- PMREGS r;
- int i;
- ulong baseAddr,baseOfs,roundedLimit;
-
- /* We can't map memory below 1Mb, but the linear address are already
- * mapped 1:1 for this memory anyway so we just return the base address.
- */
- if (physAddr < 0x100000L)
- return physAddr;
-
- /* Search table of existing mappings to see if we have already mapped
- * a region of memory that will serve this purpose. We do this because
- * DPMI 0.9 does not allow us to free physical memory mappings, and if
- * the mappings get re-used in the program we want to avoid allocating
- * more mappings than necessary.
- */
- for (i = 0; i < numMaps; i++) {
- if (maps[i].physical == physAddr && maps[i].limit == limit)
- return maps[i].linear;
- }
-
- /* Find a free slot in our physical memory mapping table */
- for (i = 0; i < numMaps; i++) {
- if (maps[i].limit == 0)
- break;
- }
- if (i == numMaps) {
- i = numMaps++;
- if (i == MAX_MEMORY_MAPPINGS)
- return NULL;
- }
-
- /* Round the physical address to a 4Kb boundary and the limit to a
- * 4Kb-1 boundary before passing the values to DPMI as some extenders
- * will fail the calls unless this is the case. If we round the
- * physical address, then we also add an extra offset into the address
- * that we return.
- */
- baseOfs = physAddr & 4095;
- baseAddr = physAddr & ~4095;
- roundedLimit = ((limit+baseOfs+1+4095) & ~4095)-1;
- r.x.ax = 0x800;
- r.x.bx = baseAddr >> 16;
- r.x.cx = baseAddr & 0xFFFF;
- r.x.si = roundedLimit >> 16;
- r.x.di = roundedLimit & 0xFFFF;
- PM_int386(0x31, &r, &r);
- if (r.x.cflag)
- return 0xFFFFFFFFUL;
- maps[i].physical = physAddr;
- maps[i].limit = limit;
- maps[i].linear = ((ulong)r.x.bx << 16) + r.x.cx + baseOfs;
- return maps[i].linear;
-}
-
-int PMAPI DPMI_setSelectorBase(ushort sel,ulong linAddr)
-{
- PMREGS r;
-
- r.x.ax = 7; /* DPMI set selector base address */
- r.x.bx = sel;
- r.x.cx = linAddr >> 16;
- r.x.dx = linAddr & 0xFFFF;
- PM_int386(0x31, &r, &r);
- if (r.x.cflag)
- return 0;
- return 1;
-}
-
-ulong PMAPI DPMI_getSelectorBase(ushort sel)
-{
- PMREGS r;
-
- r.x.ax = 6; /* DPMI get selector base address */
- r.x.bx = sel;
- PM_int386(0x31, &r, &r);
- return ((ulong)r.x.cx << 16) + r.x.dx;
-}
-
-int PMAPI DPMI_setSelectorLimit(ushort sel,ulong limit)
-{
- PMREGS r;
-
- r.x.ax = 8; /* DPMI set selector limit */
- r.x.bx = sel;
- r.x.cx = limit >> 16;
- r.x.dx = limit & 0xFFFF;
- PM_int386(0x31, &r, &r);
- if (r.x.cflag)
- return 0;
- return 1;
-}
-
-uint PMAPI DPMI_createSelector(ulong base,ulong limit)
-{
- uint sel;
- PMREGS r;
-
- /* Allocate 1 descriptor */
- r.x.ax = 0;
- r.x.cx = 1;
- PM_int386(0x31, &r, &r);
- if (r.x.cflag) return 0;
- sel = r.x.ax;
-
- /* Set the descriptor access rights (for a 32 bit page granular
- * segment).
- */
- if (limit >= 0x10000L) {
- r.x.ax = 9;
- r.x.bx = sel;
- r.x.cx = 0x40F3;
- PM_int386(0x31, &r, &r);
- }
-
- /* Map physical memory and create selector */
- if ((base = DPMI_mapPhysicalToLinear(base,limit)) == 0xFFFFFFFFUL)
- return 0;
- if (!DPMI_setSelectorBase(sel,base))
- return 0;
- if (!DPMI_setSelectorLimit(sel,limit))
- return 0;
- return sel;
-}
-
-void PMAPI DPMI_freeSelector(uint sel)
-{
- PMREGS r;
-
- r.x.ax = 1;
- r.x.bx = sel;
- PM_int386(0x31, &r, &r);
-}
-
-int PMAPI DPMI_lockLinearPages(ulong linear,ulong len)
-{
- PMREGS r;
-
- r.x.ax = 0x600; /* DPMI Lock Linear Region */
- r.x.bx = (linear >> 16); /* Linear address in BX:CX */
- r.x.cx = (linear & 0xFFFF);
- r.x.si = (len >> 16); /* Length in SI:DI */
- r.x.di = (len & 0xFFFF);
- PM_int386(0x31, &r, &r);
- return (!r.x.cflag);
-}
-
-int PMAPI DPMI_unlockLinearPages(ulong linear,ulong len)
-{
- PMREGS r;
-
- r.x.ax = 0x601; /* DPMI Unlock Linear Region */
- r.x.bx = (linear >> 16); /* Linear address in BX:CX */
- r.x.cx = (linear & 0xFFFF);
- r.x.si = (len >> 16); /* Length in SI:DI */
- r.x.di = (len & 0xFFFF);
- PM_int386(0x31, &r, &r);
- return (!r.x.cflag);
-}
-
-/****************************************************************************
-REMARKS:
-Adjust the page table caching bits directly. Requires ring 0 access and
-only works with DOS4GW and compatible extenders (CauseWay also works since
-it has direct support for the ring 0 instructions we need from ring 3). Will
-not work in a DOS box, but we call into the ring 0 helper VxD so we should
-never get here in a DOS box anyway (assuming the VxD is present). If we
-do get here and we are in windows, this code will be skipped.
-****************************************************************************/
-static void PM_adjustPageTables(
- ulong linear,
- ulong limit,
- ibool isCached)
-{
-#ifdef DOS4GW
- int startPDB,endPDB,iPDB,startPage,endPage,start,end,iPage;
- ulong andMask,orMask,pageTable,*pPageTable;
-
- andMask = ~0x18;
- orMask = (isCached) ? 0x00 : 0x18;
- if (_PM_pagingEnabled() == 1 && (PDB = _PM_getPDB()) != 0) {
- if (_PM_haveCauseWay) {
- /* CauseWay is a little different in the page table handling.
- * The code that we use for DOS4G/W does not appear to work
- * with CauseWay correctly as it does not appear to allow us
- * to map the page tables directly. Instead we can directly
- * access the page table entries in extended memory where
- * CauseWay always locates them (starting at 1024*4096*1023)
- */
- startPage = (linear >> 12);
- endPage = ((linear+limit) >> 12);
- pPageTable = (ulong*)CW_PAGE_TABLE_START;
- for (iPage = startPage; iPage <= endPage; iPage++)
- pPageTable[iPage] = (pPageTable[iPage] & andMask) | orMask;
- }
- else {
- pPDB = (ulong*)DPMI_mapPhysicalToLinear(PDB,0xFFF);
- if (pPDB) {
- startPDB = (linear >> 22) & 0x3FF;
- startPage = (linear >> 12) & 0x3FF;
- endPDB = ((linear+limit) >> 22) & 0x3FF;
- endPage = ((linear+limit) >> 12) & 0x3FF;
- for (iPDB = startPDB; iPDB <= endPDB; iPDB++) {
- pageTable = pPDB[iPDB] & ~0xFFF;
- pPageTable = (ulong*)DPMI_mapPhysicalToLinear(pageTable,0xFFF);
- start = (iPDB == startPDB) ? startPage : 0;
- end = (iPDB == endPDB) ? endPage : 0x3FF;
- for (iPage = start; iPage <= end; iPage++)
- pPageTable[iPage] = (pPageTable[iPage] & andMask) | orMask;
- }
- }
- }
- PM_flushTLB();
- }
-#endif
-}
-
-void * PMAPI DPMI_mapPhysicalAddr(ulong base,ulong limit,ibool isCached)
-{
- PMSREGS sregs;
- ulong linAddr;
- ulong DSBaseAddr;
-
- /* Get the base address for the default DS selector */
- PM_segread(&sregs);
- DSBaseAddr = DPMI_getSelectorBase(sregs.ds);
- if ((base < 0x100000) && (DSBaseAddr == 0)) {
- /* DS is zero based, so we can directly access the first 1Mb of
- * system memory (like under DOS4GW).
- */
- return (void*)base;
- }
-
- /* Map the memory to a linear address using DPMI function 0x800 */
- if ((linAddr = DPMI_mapPhysicalToLinear(base,limit)) == 0xFFFFFFFF) {
- if (base >= 0x100000)
- return NULL;
- /* If the linear address mapping fails but we are trying to
- * map an area in the first 1Mb of system memory, then we must
- * be running under a Windows or OS/2 DOS box. Under these
- * environments we can use the segment wrap around as a fallback
- * measure, as this does work properly.
- */
- linAddr = base;
- }
-
- /* Now expand the default DS selector to 4Gb so we can access it */
- if (!DPMI_setSelectorLimit(sregs.ds,0xFFFFFFFFUL))
- return NULL;
-
- /* Finally enable caching for the page tables that we just mapped in,
- * since DOS4GW and PMODE/W create the page table entries without
- * caching enabled which hurts the performance of the linear framebuffer
- * as it disables write combining on Pentium Pro and above processors.
- *
- * For those processors cache disabling is better handled through the
- * MTRR registers anyway (we can write combine a region but disable
- * caching) so that MMIO register regions do not screw up.
- */
- if (DSBaseAddr == 0)
- PM_adjustPageTables(linAddr,limit,isCached);
-
- /* Now return the base address of the memory into the default DS */
- return (void*)(linAddr - DSBaseAddr);
-}
-
-#if defined(PM386)
-
-/* Some DOS extender implementations do not directly support calling a
- * real mode procedure from protected mode. However we can simulate what
- * we need temporarily hooking the INT 6Ah vector with a small real mode
- * stub that will call our real mode code for us.
- */
-
-static uchar int6AHandler[] = {
- 0x00,0x00,0x00,0x00, /* __PMODE_callReal variable */
- 0xFB, /* sti */
- 0x2E,0xFF,0x1E,0x00,0x00, /* call [cs:__PMODE_callReal] */
- 0xCF, /* iretf */
- };
-static uchar *crPtr = NULL; /* Pointer to of int 6A handler */
-static uint crRSeg,crROff; /* Real mode seg:offset of handler */
-
-void PMAPI PM_callRealMode(uint seg,uint off, RMREGS *in,
- RMSREGS *sregs)
-{
- uchar *p;
- uint oldSeg,oldOff;
-
- if (!crPtr) {
- /* Allocate and copy the memory block only once */
- crPtr = PM_allocRealSeg(sizeof(int6AHandler), &crRSeg, &crROff);
- memcpy(crPtr,int6AHandler,sizeof(int6AHandler));
- }
- PM_setWord(crPtr,off); /* Plug in address to call */
- PM_setWord(crPtr+2,seg);
- p = PM_mapRealPointer(0,0x6A * 4);
- oldOff = PM_getWord(p); /* Save old handler address */
- oldSeg = PM_getWord(p+2);
- PM_setWord(p,crROff+4); /* Hook 6A handler */
- PM_setWord(p+2,crRSeg);
- PM_int86x(0x6A, in, in, sregs); /* Call real mode code */
- PM_setWord(p,oldOff); /* Restore old handler */
- PM_setWord(p+2,oldSeg);
-}
-
-#endif /* PM386 */
-
-#endif /* !REALMODE */
-
-/****************************************************************************
-REMARKS:
-Allocates a block of locked, physically contiguous memory. The memory
-may be required to be below the 16Meg boundary.
-****************************************************************************/
-void * PMAPI PM_allocLockedMem(
- uint size,
- ulong *physAddr,
- ibool contiguous,
- ibool below16Meg)
-{
- uchar *p,*roundedP;
- uint r_seg,r_off;
- uint roundedSize = (size + 4 + 0xFFF) & ~0xFFF;
- PM_lockHandle lh; /* Unused in DOS */
-#ifndef REALMODE
- VXD_regs regs;
-
- /* If we have connected to our helper VxD in a Windows DOS box, use the
- * helper VxD services to allocate the memory that we need.
- */
- if (VXD_version) {
- memset(&regs,0,sizeof(regs));
- regs.eax = API_NUM(PMHELP_ALLOCLOCKED);
- regs.ebx = size;
- regs.ecx = (ulong)physAddr;
- regs.edx = contiguous | (below16Meg << 8);
- _PM_VxDCall(&regs,_PM_VXD_off,_PM_VXD_sel);
- return (void*)regs.eax;
- }
-
- /* If the memory is not contiguous, we simply need to allocate it
- * using regular memory allocation services, and lock it down
- * in memory.
- *
- * For contiguous memory blocks, the only way to guarantee contiguous physical
- * memory addresses under DOS is to allocate the memory below the
- * 1Meg boundary as real mode memory.
- *
- * Note that we must page align the memory block, and we also must
- * keep track of the non-aligned pointer so we can properly free
- * it later. Hence we actually allocate 4 bytes more than the
- * size rounded up to the next 4K boundary.
- */
- if (!contiguous)
- p = PM_malloc(roundedSize);
- else
-#endif
- p = PM_allocRealSeg(roundedSize,&r_seg,&r_off);
- if (p == NULL)
- return NULL;
- roundedP = (void*)(((ulong)p + 0xFFF) & ~0xFFF);
- *((ulong*)(roundedP + size)) = (ulong)p;
- PM_lockDataPages(roundedP,size,&lh);
- if ((*physAddr = PM_getPhysicalAddr(roundedP)) == 0xFFFFFFFF) {
- PM_freeLockedMem(roundedP,size,contiguous);
- return NULL;
- }
-
- /* Disable caching for the memory since it is probably a DMA buffer */
-#ifndef REALMODE
- PM_adjustPageTables((ulong)roundedP,size-1,false);
-#endif
- return roundedP;
-}
-
-/****************************************************************************
-REMARKS:
-Free a block of locked memory.
-****************************************************************************/
-void PMAPI PM_freeLockedMem(void *p,uint size,ibool contiguous)
-{
-#ifndef REALMODE
- VXD_regs regs;
- PM_lockHandle lh; /* Unused in DOS */
-
- if (!p)
- return;
- if (VXD_version) {
- memset(&regs,0,sizeof(regs));
- regs.eax = API_NUM(PMHELP_FREELOCKED);
- regs.ebx = (ulong)p;
- regs.ecx = size;
- regs.edx = contiguous;
- _PM_VxDCall(&regs,_PM_VXD_off,_PM_VXD_sel);
- return;
- }
- PM_unlockDataPages(p,size,&lh);
- if (!contiguous)
- free(*((void**)((uchar*)p + size)));
- else
-#endif
- PM_freeRealSeg(*((void**)((char*)p + size)));
-}
-
-#ifndef REALMODE
-/****************************************************************************
-REMARKS:
-Allocates a new block of pages for the page block manager.
-****************************************************************************/
-static pageblock *PM_addNewPageBlock(void)
-{
- int i,size;
- pageblock *newBlock;
- char *p,*next;
-
- /* Allocate memory for the new page block, and add to head of list */
- size = PAGES_PER_BLOCK * PM_PAGE_SIZE + (PM_PAGE_SIZE-1) + sizeof(pageblock);
- if ((newBlock = PM_malloc(size)) == NULL)
- return NULL;
- newBlock->prev = NULL;
- newBlock->next = pageBlocks;
- if (pageBlocks)
- pageBlocks->prev = newBlock;
- pageBlocks = newBlock;
-
- /* Initialise the page aligned free list for the page block */
- newBlock->freeCount = PAGES_PER_BLOCK;
- newBlock->freeList = p = (char*)(((ulong)(newBlock + 1) + (PM_PAGE_SIZE-1)) & ~(PM_PAGE_SIZE-1));
- newBlock->freeListStart = newBlock->freeList;
- newBlock->freeListEnd = p + (PAGES_PER_BLOCK-1) * PM_PAGE_SIZE;
- for (i = 0; i < PAGES_PER_BLOCK; i++,p = next)
- FREELIST_NEXT(p) = next = p + PM_PAGE_SIZE;
- FREELIST_NEXT(p - PM_PAGE_SIZE) = NULL;
- return newBlock;
-}
-#endif
-
-/****************************************************************************
-REMARKS:
-Allocates a page aligned and page sized block of memory
-****************************************************************************/
-void * PMAPI PM_allocPage(
- ibool locked)
-{
-#ifndef REALMODE
- VXD_regs regs;
- pageblock *block;
- void *p;
- PM_lockHandle lh; /* Unused in DOS */
-
- /* Call the helper VxD for this service if we are running in a DOS box */
- if (VXD_version) {
- memset(&regs,0,sizeof(regs));
- regs.eax = API_NUM(PMHELP_ALLOCPAGE);
- regs.ebx = locked;
- _PM_VxDCall(&regs,_PM_VXD_off,_PM_VXD_sel);
- return (void*)regs.eax;
- }
-
- /* Scan the block list looking for any free blocks. Allocate a new
- * page block if no free blocks are found.
- */
- for (block = pageBlocks; block != NULL; block = block->next) {
- if (block->freeCount)
- break;
- }
- if (block == NULL && (block = PM_addNewPageBlock()) == NULL)
- return NULL;
- block->freeCount--;
- p = block->freeList;
- block->freeList = FREELIST_NEXT(p);
- if (locked)
- PM_lockDataPages(p,PM_PAGE_SIZE,&lh);
- return p;
-#else
- return NULL;
-#endif
-}
-
-/****************************************************************************
-REMARKS:
-Free a page aligned and page sized block of memory
-****************************************************************************/
-void PMAPI PM_freePage(
- void *p)
-{
-#ifndef REALMODE
- VXD_regs regs;
- pageblock *block;
-
- /* Call the helper VxD for this service if we are running in a DOS box */
- if (VXD_version) {
- memset(&regs,0,sizeof(regs));
- regs.eax = API_NUM(PMHELP_FREEPAGE);
- regs.ebx = (ulong)p;
- _PM_VxDCall(&regs,_PM_VXD_off,_PM_VXD_sel);
- return;
- }
-
- /* First find the page block that this page belongs to */
- for (block = pageBlocks; block != NULL; block = block->next) {
- if (p >= block->freeListStart && p <= block->freeListEnd)
- break;
- }
- CHECK(block != NULL);
-
- /* Now free the block by adding it to the free list */
- FREELIST_NEXT(p) = block->freeList;
- block->freeList = p;
- if (++block->freeCount == PAGES_PER_BLOCK) {
- /* If all pages in the page block are now free, free the entire
- * page block itself.
- */
- if (block == pageBlocks) {
- /* Delete from head */
- pageBlocks = block->next;
- if (block->next)
- block->next->prev = NULL;
- }
- else {
- /* Delete from middle of list */
- CHECK(block->prev != NULL);
- block->prev->next = block->next;
- if (block->next)
- block->next->prev = block->prev;
- }
- PM_free(block);
- }
-#else
- (void)p;
-#endif
-}
-
-/*-------------------------------------------------------------------------*/
-/* DOS Real Mode support. */
-/*-------------------------------------------------------------------------*/
-
-#ifdef REALMODE
-
-#ifndef MK_FP
-#define MK_FP(s,o) ( (void far *)( ((ulong)(s) << 16) + \
- (ulong)(o) ))
-#endif
-
-void * PMAPI PM_mapRealPointer(uint r_seg,uint r_off)
-{ return MK_FP(r_seg,r_off); }
-
-void * PMAPI PM_getBIOSPointer(void)
-{
- return MK_FP(0x40,0);
-}
-
-void * PMAPI PM_getA0000Pointer(void)
-{
- return MK_FP(0xA000,0);
-}
-
-void * PMAPI PM_mapPhysicalAddr(ulong base,ulong limit,ibool isCached)
-{
- uint sel = base >> 4;
- uint off = base & 0xF;
- limit = limit;
- return MK_FP(sel,off);
-}
-
-void PMAPI PM_freePhysicalAddr(void *ptr,ulong limit)
-{ ptr = ptr; }
-
-ulong PMAPI PM_getPhysicalAddr(void *p)
-{
- return ((((ulong)p >> 16) << 4) + (ushort)p);
-}
-
-ibool PMAPI PM_getPhysicalAddrRange(void *p,ulong length,ulong *physAddress)
-{ return false; }
-
-void * PMAPI PM_mapToProcess(void *base,ulong limit)
-{ return (void*)base; }
-
-void * PMAPI PM_allocRealSeg(uint size,uint *r_seg,uint *r_off)
-{
- /* Call malloc() to allocate the memory for us */
- void *p = PM_malloc(size);
- *r_seg = FP_SEG(p);
- *r_off = FP_OFF(p);
- return p;
-}
-
-void PMAPI PM_freeRealSeg(void *mem)
-{
- if (mem) PM_free(mem);
-}
-
-int PMAPI PM_int86(int intno, RMREGS *in, RMREGS *out)
-{
- return PM_int386(intno,in,out);
-}
-
-int PMAPI PM_int86x(int intno, RMREGS *in, RMREGS *out,
- RMSREGS *sregs)
-{
- return PM_int386x(intno,in,out,sregs);
-}
-
-void PMAPI PM_availableMemory(ulong *physical,ulong *total)
-{
- PMREGS regs;
-
- regs.h.ah = 0x48;
- regs.x.bx = 0xFFFF;
- PM_int86(0x21,&regs,&regs);
- *physical = *total = regs.x.bx * 16UL;
-}
-
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* Phar Lap TNT DOS Extender support. */
-/*-------------------------------------------------------------------------*/
-
-#ifdef TNT
-
-#include <pldos32.h>
-#include <pharlap.h>
-#include <hw386.h>
-
-static uchar *zeroPtr = NULL;
-
-void * PMAPI PM_getBIOSPointer(void)
-{
- if (!zeroPtr)
- zeroPtr = PM_mapPhysicalAddr(0,0xFFFFF,true);
- return (void*)(zeroPtr + 0x400);
-}
-
-void * PMAPI PM_getA0000Pointer(void)
-{
- static void *bankPtr;
- if (!bankPtr)
- bankPtr = PM_mapPhysicalAddr(0xA0000,0xFFFF,true);
- return bankPtr;
-}
-
-void * PMAPI PM_mapPhysicalAddr(ulong base,ulong limit,ibool isCached)
-{
- CONFIG_INF config;
- ULONG offset;
- int err;
- ulong baseAddr,baseOfs,newLimit;
- VXD_regs regs;
-
- /* If we have connected to our helper VxD in a Windows DOS box, use
- * the helper VxD services to map memory instead of the DPMI services.
- * We do this because the helper VxD can properly disable caching
- * where necessary, which we can only do directly here if we are
- * running at ring 0 (ie: under real DOS).
- */
- if (VXD_version == -1)
- PM_init();
- if (VXD_version) {
- memset(&regs,0,sizeof(regs));
- regs.eax = API_NUM(PMHELP_MAPPHYS);
- regs.ebx = base;
- regs.ecx = limit;
- regs.edx = isCached;
- _PM_VxDCall(&regs,_PM_VXD_off,_PM_VXD_sel);
- return (void*)regs.eax;
- }
-
- /* Round the physical address to a 4Kb boundary and the limit to a
- * 4Kb-1 boundary before passing the values to TNT. If we round the
- * physical address, then we also add an extra offset into the address
- * that we return.
- */
- baseOfs = base & 4095;
- baseAddr = base & ~4095;
- newLimit = ((limit+baseOfs+1+4095) & ~4095)-1;
- _dx_config_inf(&config, (UCHAR*)&config);
- err = _dx_map_phys(config.c_ds_sel,baseAddr,(newLimit + 4095) / 4096,&offset);
- if (err == 130) {
- /* If the TNT function failed, we are running in a DPMI environment
- * and this function does not work. However we know how to handle
- * DPMI properly, so we use our generic DPMI functions to do
- * what the TNT runtime libraries can't.
- */
- return DPMI_mapPhysicalAddr(base,limit,isCached);
- }
- if (err == 0)
- return (void*)(offset + baseOfs);
- return NULL;
-}
-
-void PMAPI PM_freePhysicalAddr(void *ptr,ulong limit)
-{
-}
-
-ulong PMAPI PM_getPhysicalAddr(void *p)
-{ return 0xFFFFFFFFUL; }
-
-ibool PMAPI PM_getPhysicalAddrRange(void *p,ulong length,ulong *physAddress)
-{ return false; }
-
-void * PMAPI PM_mapToProcess(void *base,ulong limit)
-{ return (void*)base; }
-
-void * PMAPI PM_mapRealPointer(uint r_seg,uint r_off)
-{
- if (!zeroPtr)
- zeroPtr = PM_mapPhysicalAddr(0,0xFFFFF);
- return (void*)(zeroPtr + MK_PHYS(r_seg,r_off));
-}
-
-void * PMAPI PM_allocRealSeg(uint size,uint *r_seg,uint *r_off)
-{
- USHORT addr,t;
- void *p;
-
- if (_dx_real_alloc((size + 0xF) >> 4,&addr,&t) != 0)
- return 0;
- *r_seg = addr; /* Real mode segment address */
- *r_off = 0; /* Real mode segment offset */
- p = PM_mapRealPointer(*r_seg,*r_off);
- _PM_addRealModeBlock(p,addr);
- return p;
-}
-
-void PMAPI PM_freeRealSeg(void *mem)
-{
- if (mem) _dx_real_free(_PM_findRealModeBlock(mem));
-}
-
-#define INDPMI(reg) rmregs.reg = regs->reg
-#define OUTDPMI(reg) regs->reg = rmregs.reg
-
-void PMAPI DPMI_int86(int intno, DPMI_regs *regs)
-{
- SWI_REGS rmregs;
-
- memset(&rmregs, 0, sizeof(rmregs));
- INDPMI(eax); INDPMI(ebx); INDPMI(ecx); INDPMI(edx); INDPMI(esi); INDPMI(edi);
-
- _dx_real_int(intno,&rmregs);
-
- OUTDPMI(eax); OUTDPMI(ebx); OUTDPMI(ecx); OUTDPMI(edx); OUTDPMI(esi); OUTDPMI(edi);
- regs->flags = rmregs.flags;
-}
-
-#define IN(reg) rmregs.reg = in->e.reg
-#define OUT(reg) out->e.reg = rmregs.reg
-
-int PMAPI PM_int86(int intno, RMREGS *in, RMREGS *out)
-{
- SWI_REGS rmregs;
-
- memset(&rmregs, 0, sizeof(rmregs));
- IN(eax); IN(ebx); IN(ecx); IN(edx); IN(esi); IN(edi);
-
- _dx_real_int(intno,&rmregs);
-
- OUT(eax); OUT(ebx); OUT(ecx); OUT(edx); OUT(esi); OUT(edi);
- out->x.cflag = rmregs.flags & 0x1;
- return out->x.ax;
-}
-
-int PMAPI PM_int86x(int intno, RMREGS *in, RMREGS *out,
- RMSREGS *sregs)
-{
- SWI_REGS rmregs;
-
- memset(&rmregs, 0, sizeof(rmregs));
- IN(eax); IN(ebx); IN(ecx); IN(edx); IN(esi); IN(edi);
- rmregs.es = sregs->es;
- rmregs.ds = sregs->ds;
-
- _dx_real_int(intno,&rmregs);
-
- OUT(eax); OUT(ebx); OUT(ecx); OUT(edx); OUT(esi); OUT(edi);
- sregs->es = rmregs.es;
- sregs->cs = rmregs.cs;
- sregs->ss = rmregs.ss;
- sregs->ds = rmregs.ds;
- out->x.cflag = rmregs.flags & 0x1;
- return out->x.ax;
-}
-
-void PMAPI PM_availableMemory(ulong *physical,ulong *total)
-{
- PMREGS r;
- uint data[25];
-
- r.x.ax = 0x2520; /* Get free memory info */
- r.x.bx = 0;
- r.e.edx = (uint)data;
- PM_int386(0x21, &r, &r);
- *physical = data[21] * 4096;
- *total = data[23] * 4096;
-}
-
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* Symantec C++ DOSX and FlashTek X-32/X-32VM support */
-/*-------------------------------------------------------------------------*/
-
-#if defined(DOSX) || defined(X32VM)
-
-#ifdef X32VM
-#include <x32.h>
-
-#define _x386_mk_protected_ptr(p) _x32_mk_protected_ptr((void*)p)
-#define _x386_free_protected_ptr(p) _x32_free_protected_ptr(p)
-#define _x386_zero_base_ptr _x32_zero_base_ptr
-#else
-extern void *_x386_zero_base_ptr;
-#endif
-
-void * PMAPI PM_mapRealPointer(uint r_seg,uint r_off)
-{
- return (void*)((ulong)_x386_zero_base_ptr + MK_PHYS(r_seg,r_off));
-}
-
-void * PMAPI PM_allocRealSeg(uint size,uint *r_seg,uint *r_off)
-{
- PMREGS r;
-
- r.h.ah = 0x48; /* DOS function 48h - allocate mem */
- r.x.bx = (size + 0xF) >> 4; /* Number of paragraphs to allocate */
- PM_int386(0x21, &r, &r); /* Call DOS extender */
- if (r.x.cflag)
- return 0; /* Could not allocate the memory */
- *r_seg = r.e.eax;
- *r_off = 0;
- return PM_mapRealPointer(*r_seg,*r_off);
-}
-
-void PMAPI PM_freeRealSeg(void *mem)
-{
- /* Cannot de-allocate this memory */
- mem = mem;
-}
-
-#pragma pack(1)
-
-typedef struct {
- ushort intno;
- ushort ds;
- ushort es;
- ushort fs;
- ushort gs;
- ulong eax;
- ulong edx;
- } _RMREGS;
-
-#pragma pack()
-
-#define IN(reg) regs.e.reg = in->e.reg
-#define OUT(reg) out->e.reg = regs.e.reg
-
-int PMAPI PM_int86(int intno, RMREGS *in, RMREGS *out)
-{
- _RMREGS rmregs;
- PMREGS regs;
- PMSREGS pmsregs;
-
- rmregs.intno = intno;
- rmregs.eax = in->e.eax;
- rmregs.edx = in->e.edx;
- IN(ebx); IN(ecx); IN(esi); IN(edi);
- regs.x.ax = 0x2511;
- regs.e.edx = (uint)(&rmregs);
- PM_segread(&pmsregs);
- PM_int386x(0x21,&regs,&regs,&pmsregs);
-
- OUT(eax); OUT(ebx); OUT(ecx); OUT(esi); OUT(edi);
- out->x.dx = rmregs.edx;
- out->x.cflag = regs.x.cflag;
- return out->x.ax;
-}
-
-int PMAPI PM_int86x(int intno, RMREGS *in, RMREGS *out, RMSREGS *sregs)
-{
- _RMREGS rmregs;
- PMREGS regs;
- PMSREGS pmsregs;
-
- rmregs.intno = intno;
- rmregs.eax = in->e.eax;
- rmregs.edx = in->e.edx;
- rmregs.es = sregs->es;
- rmregs.ds = sregs->ds;
- IN(ebx); IN(ecx); IN(esi); IN(edi);
- regs.x.ax = 0x2511;
- regs.e.edx = (uint)(&rmregs);
- PM_segread(&pmsregs);
- PM_int386x(0x21,&regs,&regs,&pmsregs);
-
- OUT(eax); OUT(ebx); OUT(ecx); OUT(esi); OUT(edi);
- sregs->es = rmregs.es;
- sregs->ds = rmregs.ds;
- out->x.dx = rmregs.edx;
- out->x.cflag = regs.x.cflag;
- return out->x.ax;
-}
-
-void * PMAPI PM_getBIOSPointer(void)
-{
- return (void*)((ulong)_x386_zero_base_ptr + 0x400);
-}
-
-void * PMAPI PM_getA0000Pointer(void)
-{
- return (void*)((ulong)_x386_zero_base_ptr + 0xA0000);
-}
-
-void * PMAPI PM_mapPhysicalAddr(ulong base,ulong limit,ibool isCached)
-{
- VXD_regs regs;
-
- /* If we have connected to our helper VxD in a Windows DOS box, use
- * the helper VxD services to map memory instead of the DPMI services.
- * We do this because the helper VxD can properly disable caching
- * where necessary, which we can only do directly here if we are
- * running at ring 0 (ie: under real DOS).
- */
- if (VXD_version == -1)
- PM_init();
- if (VXD_version) {
- memset(&regs,0,sizeof(regs));
- regs.eax = API_NUM(PMHELP_MAPPHYS);
- regs.ebx = base;
- regs.ecx = limit;
- regs.edx = isCached;
- _PM_VxDCall(&regs,_PM_VXD_off,_PM_VXD_sel);
- return (void*)regs.eax;
- }
-
- if (base > 0x100000)
- return _x386_map_physical_address((void*)base,limit);
- return (void*)((ulong)_x386_zero_base_ptr + base);
-}
-
-void PMAPI PM_freePhysicalAddr(void *ptr,ulong limit)
-{
- /* Mapping cannot be freed */
-}
-
-ulong PMAPI PM_getPhysicalAddr(void *p)
-{ return 0xFFFFFFFFUL; }
-
-ibool PMAPI PM_getPhysicalAddrRange(void *p,ulong length,ulong *physAddress)
-{ return false; }
-
-void * PMAPI PM_mapToProcess(void *base,ulong limit)
-{ return (void*)base; }
-
-ulong _cdecl _X32_getPhysMem(void);
-
-void PMAPI PM_availableMemory(ulong *physical,ulong *total)
-{
- PMREGS regs;
-
- /* Get total memory available, including virtual memory */
- regs.x.ax = 0x350B;
- PM_int386(0x21,&regs,&regs);
- *total = regs.e.eax;
-
- /* Get physical memory available */
- *physical = _X32_getPhysMem();
- if (*physical > *total)
- *physical = *total;
-}
-
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* Borland's DPMI32, Watcom DOS4GW and DJGPP DPMI support routines */
-/*-------------------------------------------------------------------------*/
-
-#if defined(DPMI32) || defined(DOS4GW) || defined(DJGPP)
-
-void * PMAPI PM_getBIOSPointer(void)
-{
- return PM_mapPhysicalAddr(0x400,0xFFFF,true);
-}
-
-void * PMAPI PM_getA0000Pointer(void)
-{
- return PM_mapPhysicalAddr(0xA0000,0xFFFF,true);
-}
-
-void * PMAPI PM_mapPhysicalAddr(ulong base,ulong limit,ibool isCached)
-{
- VXD_regs regs;
-
-#ifdef DJGPP
- /* Enable near pointers for DJGPP V2 */
- __djgpp_nearptr_enable();
-#endif
- /* If we have connected to our helper VxD in a Windows DOS box, use
- * the helper VxD services to map memory instead of the DPMI services.
- * We do this because the helper VxD can properly disable caching
- * where necessary, which we can only do directly here if we are
- * running at ring 0 (ie: under real DOS).
- */
- if (VXD_version == -1)
- PM_init();
- if (VXD_version) {
- memset(&regs,0,sizeof(regs));
- regs.eax = API_NUM(PMHELP_MAPPHYS);
- regs.ebx = base;
- regs.ecx = limit;
- regs.edx = isCached;
- _PM_VxDCall(&regs,_PM_VXD_off,_PM_VXD_sel);
- return (void*)regs.eax;
- }
- return DPMI_mapPhysicalAddr(base,limit,isCached);
-}
-
-void PMAPI PM_freePhysicalAddr(void *ptr,ulong limit)
-{
- /* Mapping cannot be freed */
- (void)ptr;
- (void)limit;
-}
-
-ulong PMAPI PM_getPhysicalAddr(void *p)
-{
- ulong physAddr;
- if (!PM_getPhysicalAddrRange(p,1,&physAddr))
- return 0xFFFFFFFF;
- return physAddr | ((ulong)p & 0xFFF);
-}
-
-ibool PMAPI PM_getPhysicalAddrRange(
- void *p,
- ulong length,
- ulong *physAddress)
-{
- VXD_regs regs;
- ulong pte;
- PMSREGS sregs;
- ulong DSBaseAddr;
-
- /* If we have connected to our helper VxD in a Windows DOS box, use the
- * helper VxD services to find the physical address of an address.
- */
- if (VXD_version) {
- memset(&regs,0,sizeof(regs));
- regs.eax = API_NUM(PMHELP_GETPHYSICALADDRRANGE);
- regs.ebx = (ulong)p;
- regs.ecx = (ulong)length;
- regs.edx = (ulong)physAddress;
- _PM_VxDCall(&regs,_PM_VXD_off,_PM_VXD_sel);
- return regs.eax;
- }
-
- /* Find base address for default DS selector */
- PM_segread(&sregs);
- DSBaseAddr = DPMI_getSelectorBase(sregs.ds);
-
- /* Otherwise directly access the page tables to determine the
- * physical memory address. Note that we touch the memory before
- * calling, otherwise the memory may not be paged in correctly.
- */
- pte = *((ulong*)p);
-#ifdef DOS4GW
- if (_PM_pagingEnabled() == 0) {
- int count;
- ulong linAddr = (ulong)p;
-
- /* When paging is disabled physical=linear */
- for (count = (length+0xFFF) >> 12; count > 0; count--) {
- *physAddress++ = linAddr;
- linAddr += 4096;
- }
- return true;
- }
- else if ((PDB = _PM_getPDB()) != 0 && DSBaseAddr == 0) {
- int startPDB,endPDB,iPDB,startPage,endPage,start,end,iPage;
- ulong pageTable,*pPageTable,linAddr = (ulong)p;
- ulong limit = length-1;
-
- pPDB = (ulong*)DPMI_mapPhysicalToLinear(PDB,0xFFF);
- if (pPDB) {
- startPDB = (linAddr >> 22) & 0x3FFL;
- startPage = (linAddr >> 12) & 0x3FFL;
- endPDB = ((linAddr+limit) >> 22) & 0x3FFL;
- endPage = ((linAddr+limit) >> 12) & 0x3FFL;
- for (iPDB = startPDB; iPDB <= endPDB; iPDB++) {
- pageTable = pPDB[iPDB] & ~0xFFFL;
- pPageTable = (ulong*)DPMI_mapPhysicalToLinear(pageTable,0xFFF);
- start = (iPDB == startPDB) ? startPage : 0;
- end = (iPDB == endPDB) ? endPage : 0x3FFL;
- for (iPage = start; iPage <= end; iPage++)
- *physAddress++ = (pPageTable[iPage] & ~0xFFF);
- }
- return true;
- }
- }
-#endif
- return false;
-}
-
-void * PMAPI PM_mapToProcess(void *base,ulong limit)
-{
- (void)limit;
- return (void*)base;
-}
-
-void * PMAPI PM_mapRealPointer(uint r_seg,uint r_off)
-{
- static uchar *zeroPtr = NULL;
-
- if (!zeroPtr)
- zeroPtr = PM_mapPhysicalAddr(0,0xFFFFF,true);
- return (void*)(zeroPtr + MK_PHYS(r_seg,r_off));
-}
-
-void * PMAPI PM_allocRealSeg(uint size,uint *r_seg,uint *r_off)
-{
- PMREGS r;
- void *p;
-
- r.x.ax = 0x100; /* DPMI allocate DOS memory */
- r.x.bx = (size + 0xF) >> 4; /* number of paragraphs */
- PM_int386(0x31, &r, &r);
- if (r.x.cflag)
- return NULL; /* DPMI call failed */
- *r_seg = r.x.ax; /* Real mode segment */
- *r_off = 0;
- p = PM_mapRealPointer(*r_seg,*r_off);
- _PM_addRealModeBlock(p,r.x.dx);
- return p;
-}
-
-void PMAPI PM_freeRealSeg(void *mem)
-{
- PMREGS r;
-
- if (mem) {
- r.x.ax = 0x101; /* DPMI free DOS memory */
- r.x.dx = _PM_findRealModeBlock(mem);/* DX := selector from 0x100 */
- PM_int386(0x31, &r, &r);
- }
-}
-
-static DPMI_handler_t DPMI_int10 = NULL;
-
-void PMAPI DPMI_setInt10Handler(DPMI_handler_t handler)
-{
- DPMI_int10 = handler;
-}
-
-void PMAPI DPMI_int86(int intno, DPMI_regs *regs)
-{
- PMREGS r;
- PMSREGS sr;
-
- if (intno == 0x10 && DPMI_int10) {
- if (DPMI_int10(regs))
- return;
- }
- PM_segread(&sr);
- r.x.ax = 0x300; /* DPMI issue real interrupt */
- r.h.bl = intno;
- r.h.bh = 0;
- r.x.cx = 0;
- sr.es = sr.ds;
- r.e.edi = (uint)regs;
- PM_int386x(0x31, &r, &r, &sr); /* Issue the interrupt */
-}
-
-#define IN(reg) rmregs.reg = in->e.reg
-#define OUT(reg) out->e.reg = rmregs.reg
-
-int PMAPI PM_int86(int intno, RMREGS *in, RMREGS *out)
-{
- DPMI_regs rmregs;
-
- memset(&rmregs, 0, sizeof(rmregs));
- IN(eax); IN(ebx); IN(ecx); IN(edx); IN(esi); IN(edi);
-
- DPMI_int86(intno,&rmregs); /* DPMI issue real interrupt */
-
- OUT(eax); OUT(ebx); OUT(ecx); OUT(edx); OUT(esi); OUT(edi);
- out->x.cflag = rmregs.flags & 0x1;
- return out->x.ax;
-}
-
-int PMAPI PM_int86x(int intno, RMREGS *in, RMREGS *out,
- RMSREGS *sregs)
-{
- DPMI_regs rmregs;
-
- memset(&rmregs, 0, sizeof(rmregs));
- IN(eax); IN(ebx); IN(ecx); IN(edx); IN(esi); IN(edi);
- rmregs.es = sregs->es;
- rmregs.ds = sregs->ds;
-
- DPMI_int86(intno,&rmregs); /* DPMI issue real interrupt */
-
- OUT(eax); OUT(ebx); OUT(ecx); OUT(edx); OUT(esi); OUT(edi);
- sregs->es = rmregs.es;
- sregs->cs = rmregs.cs;
- sregs->ss = rmregs.ss;
- sregs->ds = rmregs.ds;
- out->x.cflag = rmregs.flags & 0x1;
- return out->x.ax;
-}
-
-#pragma pack(1)
-
-typedef struct {
- uint LargestBlockAvail;
- uint MaxUnlockedPage;
- uint LargestLockablePage;
- uint LinAddrSpace;
- uint NumFreePagesAvail;
- uint NumPhysicalPagesFree;
- uint TotalPhysicalPages;
- uint FreeLinAddrSpace;
- uint SizeOfPageFile;
- uint res[3];
- } MemInfo;
-
-#pragma pack()
-
-void PMAPI PM_availableMemory(ulong *physical,ulong *total)
-{
- PMREGS r;
- PMSREGS sr;
- MemInfo memInfo;
-
- PM_segread(&sr);
- r.x.ax = 0x500; /* DPMI get free memory info */
- sr.es = sr.ds;
- r.e.edi = (uint)&memInfo;
- PM_int386x(0x31, &r, &r, &sr); /* Issue the interrupt */
- *physical = memInfo.NumPhysicalPagesFree * 4096;
- *total = memInfo.LargestBlockAvail;
- if (*total < *physical)
- *physical = *total;
-}
-
-#endif
-
-#ifndef __16BIT__
-
-/****************************************************************************
-REMARKS:
-Call the VBE/Core software interrupt to change display banks.
-****************************************************************************/
-void PMAPI PM_setBankA(
- int bank)
-{
- DPMI_regs regs;
- memset(&regs, 0, sizeof(regs));
- regs.eax = 0x4F05;
- regs.ebx = 0x0000;
- regs.edx = bank;
- DPMI_int86(0x10,&regs);
-}
-
-/****************************************************************************
-REMARKS:
-Call the VBE/Core software interrupt to change display banks.
-****************************************************************************/
-void PMAPI PM_setBankAB(
- int bank)
-{
- DPMI_regs regs;
- memset(&regs, 0, sizeof(regs));
- regs.eax = 0x4F05;
- regs.ebx = 0x0000;
- regs.edx = bank;
- DPMI_int86(0x10,&regs);
- regs.eax = 0x4F05;
- regs.ebx = 0x0001;
- regs.edx = bank;
- DPMI_int86(0x10,&regs);
-}
-
-/****************************************************************************
-REMARKS:
-Call the VBE/Core software interrupt to change display start address.
-****************************************************************************/
-void PMAPI PM_setCRTStart(
- int x,
- int y,
- int waitVRT)
-{
- DPMI_regs regs;
- memset(&regs, 0, sizeof(regs));
- regs.eax = 0x4F07;
- regs.ebx = waitVRT;
- regs.ecx = x;
- regs.edx = y;
- DPMI_int86(0x10,&regs);
-}
-
-#endif
-
-/****************************************************************************
-REMARKS:
-Function to get the file attributes for a specific file.
-****************************************************************************/
-uint PMAPI PM_getFileAttr(
- const char *filename)
-{
- /* TODO: Implement this! */
- return 0;
-}
-
-/****************************************************************************
-REMARKS:
-Function to get the file time and date for a specific file.
-****************************************************************************/
-ibool PMAPI PM_getFileTime(
- const char *filename,
- ibool gmTime,
- PM_time *time)
-{
- /* TODO: Implement this! */
- return false;
-}
-
-/****************************************************************************
-REMARKS:
-Function to set the file time and date for a specific file.
-****************************************************************************/
-ibool PMAPI PM_setFileTime(
- const char *filename,
- ibool gmTime,
- PM_time *time)
-{
- /* TODO: Implement this! */
- return false;
-}
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/pmdos.c b/board/MAI/bios_emulator/scitech/src/pm/dos/pmdos.c
deleted file mode 100644
index eecc2daede..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/pmdos.c
+++ /dev/null
@@ -1,1637 +0,0 @@
-/****************************************************************************
-*
-* SciTech OS Portability Manager Library
-*
-* ========================================================================
-*
-* The contents of this file are subject to the SciTech MGL Public
-* License Version 1.0 (the "License"); you may not use this file
-* except in compliance with the License. You may obtain a copy of
-* the License at http://www.scitechsoft.com/mgl-license.txt
-*
-* Software distributed under the License is distributed on an
-* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-* implied. See the License for the specific language governing
-* rights and limitations under the License.
-*
-* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-*
-* The Initial Developer of the Original Code is SciTech Software, Inc.
-* All Rights Reserved.
-*
-* ========================================================================
-*
-* Language: ANSI C
-* Environment: 16/32 bit DOS
-*
-* Description: Implementation for the OS Portability Manager Library, which
-* contains functions to implement OS specific services in a
-* generic, cross platform API. Porting the OS Portability
-* Manager library is the first step to porting any SciTech
-* products to a new platform.
-*
-****************************************************************************/
-
-#include "pmapi.h"
-#include <stdio.h>
-#include <stdlib.h>
-#include <string.h>
-#include <dos.h>
-
-/*--------------------------- Global variables ----------------------------*/
-
-#ifndef REALMODE
-static int globalDataStart;
-#endif
-
-PM_criticalHandler _VARAPI _PM_critHandler = NULL;
-PM_breakHandler _VARAPI _PM_breakHandler = NULL;
-PM_intHandler _VARAPI _PM_timerHandler = NULL;
-PM_intHandler _VARAPI _PM_rtcHandler = NULL;
-PM_intHandler _VARAPI _PM_keyHandler = NULL;
-PM_key15Handler _VARAPI _PM_key15Handler = NULL;
-PM_mouseHandler _VARAPI _PM_mouseHandler = NULL;
-PM_intHandler _VARAPI _PM_int10Handler = NULL;
-int _VARAPI _PM_mouseMask;
-
-uchar * _VARAPI _PM_ctrlCPtr; /* Location of Ctrl-C flag */
-uchar * _VARAPI _PM_ctrlBPtr; /* Location of Ctrl-Break flag */
-uchar * _VARAPI _PM_critPtr; /* Location of Critical error Bf*/
-PMFARPTR _VARAPI _PM_prevTimer = PMNULL; /* Previous timer handler */
-PMFARPTR _VARAPI _PM_prevRTC = PMNULL; /* Previous RTC handler */
-PMFARPTR _VARAPI _PM_prevKey = PMNULL; /* Previous key handler */
-PMFARPTR _VARAPI _PM_prevKey15 = PMNULL; /* Previous key15 handler */
-PMFARPTR _VARAPI _PM_prevBreak = PMNULL; /* Previous break handler */
-PMFARPTR _VARAPI _PM_prevCtrlC = PMNULL; /* Previous CtrlC handler */
-PMFARPTR _VARAPI _PM_prevCritical = PMNULL; /* Previous critical handler */
-long _VARAPI _PM_prevRealTimer; /* Previous real mode timer */
-long _VARAPI _PM_prevRealRTC; /* Previous real mode RTC */
-long _VARAPI _PM_prevRealKey; /* Previous real mode key */
-long _VARAPI _PM_prevRealKey15; /* Previous real mode key15 */
-long _VARAPI _PM_prevRealInt10; /* Previous real mode int 10h */
-static uchar _PM_oldCMOSRegA; /* CMOS register A contents */
-static uchar _PM_oldCMOSRegB; /* CMOS register B contents */
-static uchar _PM_oldRTCPIC2; /* Mask value for RTC IRQ8 */
-
-/* Structure to maintain information about hardware interrupt handlers,
- * include a copy of the hardware IRQ assembler thunk (one for each
- * hooked interrupt handler).
- */
-
-typedef struct {
- uchar IRQ;
- uchar IRQVect;
- uchar prevPIC;
- uchar prevPIC2;
- PMFARPTR prevHandler;
- long prevRealhandler;
- uchar thunk[1];
- /* IRQ assembler thunk follows ... */
- } _PM_IRQHandle;
-
-/*----------------------------- Implementation ----------------------------*/
-
-/* Globals for locking interrupt handlers in _pmdos.asm */
-
-#ifndef REALMODE
-extern int _VARAPI _PM_pmdosDataStart;
-extern int _VARAPI _PM_pmdosDataEnd;
-extern int _VARAPI _PM_DMADataStart;
-extern int _VARAPI _PM_DMADataEnd;
-void _ASMAPI _PM_pmdosCodeStart(void);
-void _ASMAPI _PM_pmdosCodeEnd(void);
-void _ASMAPI _PM_DMACodeStart(void);
-void _ASMAPI _PM_DMACodeEnd(void);
-#endif
-
-/* Protected mode interrupt handlers, also called by PM callbacks below */
-
-void _ASMAPI _PM_timerISR(void);
-void _ASMAPI _PM_rtcISR(void);
-void _ASMAPI _PM_irqISRTemplate(void);
-void _ASMAPI _PM_irqISRTemplateEnd(void);
-void _ASMAPI _PM_keyISR(void);
-void _ASMAPI _PM_key15ISR(void);
-void _ASMAPI _PM_breakISR(void);
-void _ASMAPI _PM_ctrlCISR(void);
-void _ASMAPI _PM_criticalISR(void);
-void _ASMAPI _PM_mouseISR(void);
-void _ASMAPI _PM_int10PMCB(void);
-
-/* Protected mode DPMI callback handlers */
-
-void _ASMAPI _PM_mousePMCB(void);
-
-/* Routine to install a mouse handler function */
-
-void _ASMAPI _PM_setMouseHandler(int mask);
-
-/* Routine to allocate DPMI real mode callback routines */
-
-ibool _ASMAPI _DPMI_allocateCallback(void (_ASMAPI *pmcode)(),void *rmregs,long *RMCB);
-void _ASMAPI _DPMI_freeCallback(long RMCB);
-
-/* DPMI helper functions in PMLITE.C */
-
-ulong PMAPI DPMI_mapPhysicalToLinear(ulong physAddr,ulong limit);
-int PMAPI DPMI_setSelectorBase(ushort sel,ulong linAddr);
-ulong PMAPI DPMI_getSelectorBase(ushort sel);
-int PMAPI DPMI_setSelectorLimit(ushort sel,ulong limit);
-uint PMAPI DPMI_createSelector(ulong base,ulong limit);
-void PMAPI DPMI_freeSelector(uint sel);
-int PMAPI DPMI_lockLinearPages(ulong linear,ulong len);
-int PMAPI DPMI_unlockLinearPages(ulong linear,ulong len);
-
-/* Functions to read and write CMOS registers */
-
-uchar PMAPI _PM_readCMOS(int index);
-void PMAPI _PM_writeCMOS(int index,uchar value);
-
-/*-------------------------------------------------------------------------*/
-/* Generic routines common to all environments */
-/*-------------------------------------------------------------------------*/
-
-void PMAPI PM_resetMouseDriver(int hardReset)
-{
- RMREGS regs;
- PM_mouseHandler oldHandler = _PM_mouseHandler;
-
- PM_restoreMouseHandler();
- regs.x.ax = hardReset ? 0 : 33;
- PM_int86(0x33, &regs, &regs);
- if (oldHandler)
- PM_setMouseHandler(_PM_mouseMask, oldHandler);
-}
-
-void PMAPI PM_setRealTimeClockFrequency(int frequency)
-{
- static short convert[] = {
- 8192,
- 4096,
- 2048,
- 1024,
- 512,
- 256,
- 128,
- 64,
- 32,
- 16,
- 8,
- 4,
- 2,
- -1,
- };
- int i;
-
- /* First clear any pending RTC timeout if not cleared */
- _PM_readCMOS(0x0C);
- if (frequency == 0) {
- /* Disable RTC timout */
- _PM_writeCMOS(0x0A,_PM_oldCMOSRegA);
- _PM_writeCMOS(0x0B,_PM_oldCMOSRegB & 0x0F);
- }
- else {
- /* Convert frequency value to RTC clock indexes */
- for (i = 0; convert[i] != -1; i++) {
- if (convert[i] == frequency)
- break;
- }
-
- /* Set RTC timout value and enable timeout */
- _PM_writeCMOS(0x0A,0x20 | (i+3));
- _PM_writeCMOS(0x0B,(_PM_oldCMOSRegB & 0x0F) | 0x40);
- }
-}
-
-#ifndef REALMODE
-
-static void PMAPI lockPMHandlers(void)
-{
- static int locked = 0;
- int stat;
- PM_lockHandle lh; /* Unused in DOS */
-
- /* Lock all of the code and data used by our protected mode interrupt
- * handling routines, so that it will continue to work correctly
- * under real mode.
- */
- if (!locked) {
- PM_saveDS();
- stat = !PM_lockDataPages(&globalDataStart-2048,4096,&lh);
- stat |= !PM_lockDataPages(&_PM_pmdosDataStart,(int)&_PM_pmdosDataEnd - (int)&_PM_pmdosDataStart,&lh);
- stat |= !PM_lockCodePages((__codePtr)_PM_pmdosCodeStart,(int)_PM_pmdosCodeEnd-(int)_PM_pmdosCodeStart,&lh);
- stat |= !PM_lockDataPages(&_PM_DMADataStart,(int)&_PM_DMADataEnd - (int)&_PM_DMADataStart,&lh);
- stat |= !PM_lockCodePages((__codePtr)_PM_DMACodeStart,(int)_PM_DMACodeEnd-(int)_PM_DMACodeStart,&lh);
- if (stat) {
- printf("Page locking services failed - interrupt handling not safe!\n");
- exit(1);
- }
- locked = 1;
- }
-}
-
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* DOS Real Mode support. */
-/*-------------------------------------------------------------------------*/
-
-#ifdef REALMODE
-
-#ifndef MK_FP
-#define MK_FP(s,o) ( (void far *)( ((ulong)(s) << 16) + \
- (ulong)(o) ))
-#endif
-
-int PMAPI PM_setMouseHandler(int mask, PM_mouseHandler mh)
-{
- PM_saveDS();
- _PM_mouseHandler = mh;
- _PM_setMouseHandler(_PM_mouseMask = mask);
- return 1;
-}
-
-void PMAPI PM_restoreMouseHandler(void)
-{
- union REGS regs;
-
- if (_PM_mouseHandler) {
- regs.x.ax = 33;
- int86(0x33, &regs, &regs);
- _PM_mouseHandler = NULL;
- }
-}
-
-void PMAPI PM_setTimerHandler(PM_intHandler th)
-{
- _PM_getRMvect(0x8, (long*)&_PM_prevTimer);
- _PM_timerHandler = th;
- _PM_setRMvect(0x8, (long)_PM_timerISR);
-}
-
-void PMAPI PM_restoreTimerHandler(void)
-{
- if (_PM_timerHandler) {
- _PM_setRMvect(0x8, (long)_PM_prevTimer);
- _PM_timerHandler = NULL;
- }
-}
-
-ibool PMAPI PM_setRealTimeClockHandler(PM_intHandler th,int frequency)
-{
- /* Save the old CMOS real time clock values */
- _PM_oldCMOSRegA = _PM_readCMOS(0x0A);
- _PM_oldCMOSRegB = _PM_readCMOS(0x0B);
-
- /* Set the real time clock interrupt handler */
- _PM_getRMvect(0x70, (long*)&_PM_prevRTC);
- _PM_rtcHandler = th;
- _PM_setRMvect(0x70, (long)_PM_rtcISR);
-
- /* Program the real time clock default frequency */
- PM_setRealTimeClockFrequency(frequency);
-
- /* Unmask IRQ8 in the PIC2 */
- _PM_oldRTCPIC2 = PM_inpb(0xA1);
- PM_outpb(0xA1,_PM_oldRTCPIC2 & 0xFE);
- return true;
-}
-
-void PMAPI PM_restoreRealTimeClockHandler(void)
-{
- if (_PM_rtcHandler) {
- /* Restore CMOS registers and mask RTC clock */
- _PM_writeCMOS(0x0A,_PM_oldCMOSRegA);
- _PM_writeCMOS(0x0B,_PM_oldCMOSRegB);
- PM_outpb(0xA1,(PM_inpb(0xA1) & 0xFE) | (_PM_oldRTCPIC2 & ~0xFE));
-
- /* Restore the interrupt vector */
- _PM_setRMvect(0x70, (long)_PM_prevRTC);
- _PM_rtcHandler = NULL;
- }
-}
-
-void PMAPI PM_setKeyHandler(PM_intHandler kh)
-{
- _PM_getRMvect(0x9, (long*)&_PM_prevKey);
- _PM_keyHandler = kh;
- _PM_setRMvect(0x9, (long)_PM_keyISR);
-}
-
-void PMAPI PM_restoreKeyHandler(void)
-{
- if (_PM_keyHandler) {
- _PM_setRMvect(0x9, (long)_PM_prevKey);
- _PM_keyHandler = NULL;
- }
-}
-
-void PMAPI PM_setKey15Handler(PM_key15Handler kh)
-{
- _PM_getRMvect(0x15, (long*)&_PM_prevKey15);
- _PM_key15Handler = kh;
- _PM_setRMvect(0x15, (long)_PM_key15ISR);
-}
-
-void PMAPI PM_restoreKey15Handler(void)
-{
- if (_PM_key15Handler) {
- _PM_setRMvect(0x15, (long)_PM_prevKey15);
- _PM_key15Handler = NULL;
- }
-}
-
-void PMAPI PM_installAltBreakHandler(PM_breakHandler bh)
-{
- static int ctrlCFlag,ctrlBFlag;
-
- _PM_ctrlCPtr = (uchar*)&ctrlCFlag;
- _PM_ctrlBPtr = (uchar*)&ctrlBFlag;
- _PM_getRMvect(0x1B, (long*)&_PM_prevBreak);
- _PM_getRMvect(0x23, (long*)&_PM_prevCtrlC);
- _PM_breakHandler = bh;
- _PM_setRMvect(0x1B, (long)_PM_breakISR);
- _PM_setRMvect(0x23, (long)_PM_ctrlCISR);
-}
-
-void PMAPI PM_installBreakHandler(void)
-{
- PM_installAltBreakHandler(NULL);
-}
-
-void PMAPI PM_restoreBreakHandler(void)
-{
- if (_PM_prevBreak) {
- _PM_setRMvect(0x1B, (long)_PM_prevBreak);
- _PM_setRMvect(0x23, (long)_PM_prevCtrlC);
- _PM_prevBreak = NULL;
- _PM_breakHandler = NULL;
- }
-}
-
-void PMAPI PM_installAltCriticalHandler(PM_criticalHandler ch)
-{
- static short critBuf[2];
-
- _PM_critPtr = (uchar*)critBuf;
- _PM_getRMvect(0x24, (long*)&_PM_prevCritical);
- _PM_critHandler = ch;
- _PM_setRMvect(0x24, (long)_PM_criticalISR);
-}
-
-void PMAPI PM_installCriticalHandler(void)
-{
- PM_installAltCriticalHandler(NULL);
-}
-
-void PMAPI PM_restoreCriticalHandler(void)
-{
- if (_PM_prevCritical) {
- _PM_setRMvect(0x24, (long)_PM_prevCritical);
- _PM_prevCritical = NULL;
- _PM_critHandler = NULL;
- }
-}
-
-int PMAPI PM_lockDataPages(void *p,uint len,PM_lockHandle *lh)
-{
- p = p; len = len; /* Do nothing for real mode */
- return 1;
-}
-
-int PMAPI PM_unlockDataPages(void *p,uint len,PM_lockHandle *lh)
-{
- p = p; len = len; /* Do nothing for real mode */
- return 1;
-}
-
-int PMAPI PM_lockCodePages(void (*p)(),uint len,PM_lockHandle *lh)
-{
- p = p; len = len; /* Do nothing for real mode */
- return 1;
-}
-
-int PMAPI PM_unlockCodePages(void (*p)(),uint len,PM_lockHandle *lh)
-{
- p = p; len = len; /* Do nothing for real mode */
- return 1;
-}
-
-void PMAPI PM_getPMvect(int intno, PMFARPTR *isr)
-{
- long t;
- _PM_getRMvect(intno,&t);
- *isr = (void*)t;
-}
-
-void PMAPI PM_setPMvect(int intno, PM_intHandler isr)
-{
- PM_saveDS();
- _PM_setRMvect(intno,(long)isr);
-}
-
-void PMAPI PM_restorePMvect(int intno, PMFARPTR isr)
-{
- _PM_setRMvect(intno,(long)isr);
-}
-
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* Phar Lap TNT DOS Extender support. */
-/*-------------------------------------------------------------------------*/
-
-#ifdef TNT
-
-#include <pldos32.h>
-#include <pharlap.h>
-#include <hw386.h>
-
-static long prevRealBreak; /* Previous real mode break handler */
-static long prevRealCtrlC; /* Previous real mode CtrlC handler */
-static long prevRealCritical; /* Prev real mode critical handler */
-static uchar *mousePtr;
-
-/* The following real mode routine is used to call a 32 bit protected
- * mode FAR function from real mode. We use this for passing up control
- * from the real mode mouse callback to our protected mode code.
- */
-
-static UCHAR realHandler[] = { /* Real mode code generic handler */
- 0x00,0x00,0x00,0x00, /* __PM_callProtp */
- 0x00,0x00, /* __PM_protCS */
- 0x00,0x00,0x00,0x00, /* __PM_protHandler */
- 0x66,0x60, /* pushad */
- 0x1E, /* push ds */
- 0x6A,0x00, /* push 0 */
- 0x6A,0x00, /* push 0 */
- 0x2E,0xFF,0x36,0x04,0x00, /* push [cs:__PM_protCS] */
- 0x66,0x2E,0xFF,0x36,0x06,0x00, /* push [cs:__PM_protHandler] */
- 0x2E,0xFF,0x1E,0x00,0x00, /* call [cs:__PM_callProtp] */
- 0x83,0xC4,0x0A, /* add sp,10 */
- 0x1F, /* pop ds */
- 0x66,0x61, /* popad */
- 0xCB, /* retf */
- };
-
-/* The following functions installs the above realmode callback mechanism
- * in real mode memory for calling the protected mode routine.
- */
-
-uchar * installCallback(void (PMAPI *pmCB)(),uint *rseg, uint *roff)
-{
- CONFIG_INF config;
- REALPTR realBufAdr,callProtp;
- ULONG bufSize;
- FARPTR protBufAdr;
- uchar *p;
-
- /* Get address of real mode routine to call up to protected mode */
- _dx_rmlink_get(&callProtp, &realBufAdr, &bufSize, &protBufAdr);
- _dx_config_inf(&config, (UCHAR*)&config);
-
- /* Fill in the values in the real mode code segment so that it will
- * call the correct routine.
- */
- *((REALPTR*)&realHandler[0]) = callProtp;
- *((USHORT*)&realHandler[4]) = config.c_cs_sel;
- *((ULONG*)&realHandler[6]) = (ULONG)pmCB;
-
- /* Copy the real mode handler to real mode memory */
- if ((p = PM_allocRealSeg(sizeof(realHandler),rseg,roff)) == NULL)
- return NULL;
- memcpy(p,realHandler,sizeof(realHandler));
-
- /* Skip past global variabls in real mode code segment */
- *roff += 0x0A;
- return p;
-}
-
-int PMAPI PM_setMouseHandler(int mask, PM_mouseHandler mh)
-{
- RMREGS regs;
- RMSREGS sregs;
- uint rseg,roff;
-
- lockPMHandlers(); /* Ensure our handlers are locked */
-
- if ((mousePtr = installCallback(_PM_mouseISR, &rseg, &roff)) == NULL)
- return 0;
- _PM_mouseHandler = mh;
-
- /* Install the real mode mouse handler */
- sregs.es = rseg;
- regs.x.dx = roff;
- regs.x.cx = _PM_mouseMask = mask;
- regs.x.ax = 0xC;
- PM_int86x(0x33, &regs, &regs, &sregs);
- return 1;
-}
-
-void PMAPI PM_restoreMouseHandler(void)
-{
- RMREGS regs;
-
- if (_PM_mouseHandler) {
- regs.x.ax = 33;
- PM_int86(0x33, &regs, &regs);
- PM_freeRealSeg(mousePtr);
- _PM_mouseHandler = NULL;
- }
-}
-
-void PMAPI PM_getPMvect(int intno, PMFARPTR *isr)
-{
- FARPTR ph;
-
- _dx_pmiv_get(intno, &ph);
- isr->sel = FP_SEL(ph);
- isr->off = FP_OFF(ph);
-}
-
-void PMAPI PM_setPMvect(int intno, PM_intHandler isr)
-{
- CONFIG_INF config;
- FARPTR ph;
-
- PM_saveDS();
- _dx_config_inf(&config, (UCHAR*)&config);
- FP_SET(ph,(uint)isr,config.c_cs_sel);
- _dx_pmiv_set(intno,ph);
-}
-
-void PMAPI PM_restorePMvect(int intno, PMFARPTR isr)
-{
- FARPTR ph;
-
- FP_SET(ph,isr.off,isr.sel);
- _dx_pmiv_set(intno,ph);
-}
-
-static void getISR(int intno, PMFARPTR *pmisr, long *realisr)
-{
- PM_getPMvect(intno,pmisr);
- _PM_getRMvect(intno, realisr);
-}
-
-static void restoreISR(int intno, PMFARPTR pmisr, long realisr)
-{
- _PM_setRMvect(intno,realisr);
- PM_restorePMvect(intno,pmisr);
-}
-
-static void setISR(int intno, void (PMAPI *isr)())
-{
- CONFIG_INF config;
- FARPTR ph;
-
- lockPMHandlers(); /* Ensure our handlers are locked */
-
- _dx_config_inf(&config, (UCHAR*)&config);
- FP_SET(ph,(uint)isr,config.c_cs_sel);
- _dx_apmiv_set(intno,ph);
-}
-
-void PMAPI PM_setTimerHandler(PM_intHandler th)
-{
- getISR(0x8, &_PM_prevTimer, &_PM_prevRealTimer);
- _PM_timerHandler = th;
- setISR(0x8, _PM_timerISR);
-}
-
-void PMAPI PM_restoreTimerHandler(void)
-{
- if (_PM_timerHandler) {
- restoreISR(0x8, _PM_prevTimer, _PM_prevRealTimer);
- _PM_timerHandler = NULL;
- }
-}
-
-ibool PMAPI PM_setRealTimeClockHandler(PM_intHandler th,int frequency)
-{
- /* Save the old CMOS real time clock values */
- _PM_oldCMOSRegA = _PM_readCMOS(0x0A);
- _PM_oldCMOSRegB = _PM_readCMOS(0x0B);
-
- /* Set the real time clock interrupt handler */
- getISR(0x70, &_PM_prevRTC, &_PM_prevRealRTC);
- _PM_rtcHandler = th;
- setISR(0x70, _PM_rtcISR);
-
- /* Program the real time clock default frequency */
- PM_setRealTimeClockFrequency(frequency);
-
- /* Unmask IRQ8 in the PIC2 */
- _PM_oldRTCPIC2 = PM_inpb(0xA1);
- PM_outpb(0xA1,_PM_oldRTCPIC2 & 0xFE);
- return true;
-}
-
-void PMAPI PM_restoreRealTimeClockHandler(void)
-{
- if (_PM_rtcHandler) {
- /* Restore CMOS registers and mask RTC clock */
- _PM_writeCMOS(0x0A,_PM_oldCMOSRegA);
- _PM_writeCMOS(0x0B,_PM_oldCMOSRegB);
- PM_outpb(0xA1,(PM_inpb(0xA1) & 0xFE) | (_PM_oldRTCPIC2 & ~0xFE));
-
- /* Restore the interrupt vector */
- restoreISR(0x70, _PM_prevRTC, _PM_prevRealRTC);
- _PM_rtcHandler = NULL;
- }
-}
-
-void PMAPI PM_setKeyHandler(PM_intHandler kh)
-{
- getISR(0x9, &_PM_prevKey, &_PM_prevRealKey);
- _PM_keyHandler = kh;
- setISR(0x9, _PM_keyISR);
-}
-
-void PMAPI PM_restoreKeyHandler(void)
-{
- if (_PM_keyHandler) {
- restoreISR(0x9, _PM_prevKey, _PM_prevRealKey);
- _PM_keyHandler = NULL;
- }
-}
-
-void PMAPI PM_setKey15Handler(PM_key15Handler kh)
-{
- getISR(0x15, &_PM_prevKey15, &_PM_prevRealKey15);
- _PM_key15Handler = kh;
- setISR(0x15, _PM_key15ISR);
-}
-
-void PMAPI PM_restoreKey15Handler(void)
-{
- if (_PM_key15Handler) {
- restoreISR(0x15, _PM_prevKey15, _PM_prevRealKey15);
- _PM_key15Handler = NULL;
- }
-}
-
-void PMAPI PM_installAltBreakHandler(PM_breakHandler bh)
-{
- static int ctrlCFlag,ctrlBFlag;
-
- _PM_ctrlCPtr = (uchar*)&ctrlCFlag;
- _PM_ctrlBPtr = (uchar*)&ctrlBFlag;
- getISR(0x1B, &_PM_prevBreak, &prevRealBreak);
- getISR(0x23, &_PM_prevCtrlC, &prevRealCtrlC);
- _PM_breakHandler = bh;
- setISR(0x1B, _PM_breakISR);
- setISR(0x23, _PM_ctrlCISR);
-}
-
-void PMAPI PM_installBreakHandler(void)
-{
- PM_installAltBreakHandler(NULL);
-}
-
-void PMAPI PM_restoreBreakHandler(void)
-{
- if (_PM_prevBreak.sel) {
- restoreISR(0x1B, _PM_prevBreak, prevRealBreak);
- restoreISR(0x23, _PM_prevCtrlC, prevRealCtrlC);
- _PM_prevBreak.sel = 0;
- _PM_breakHandler = NULL;
- }
-}
-
-void PMAPI PM_installAltCriticalHandler(PM_criticalHandler ch)
-{
- static short critBuf[2];
-
- _PM_critPtr = (uchar*)critBuf;
- getISR(0x24, &_PM_prevCritical, &prevRealCritical);
- _PM_critHandler = ch;
- setISR(0x24, _PM_criticalISR);
-}
-
-void PMAPI PM_installCriticalHandler(void)
-{
- PM_installAltCriticalHandler(NULL);
-}
-
-void PMAPI PM_restoreCriticalHandler(void)
-{
- if (_PM_prevCritical.sel) {
- restoreISR(0x24, _PM_prevCritical, prevRealCritical);
- _PM_prevCritical.sel = 0;
- _PM_critHandler = NULL;
- }
-}
-
-int PMAPI PM_lockDataPages(void *p,uint len,PM_lockHandle *lh)
-{
- return (_dx_lock_pgsn(p,len) == 0);
-}
-
-int PMAPI PM_unlockDataPages(void *p,uint len,PM_lockHandle *lh)
-{
- return (_dx_ulock_pgsn(p,len) == 0);
-}
-
-int PMAPI PM_lockCodePages(void (*p)(),uint len,PM_lockHandle *lh)
-{
- CONFIG_INF config;
- FARPTR fp;
-
- _dx_config_inf(&config, (UCHAR*)&config);
- FP_SET(fp,p,config.c_cs_sel);
- return (_dx_lock_pgs(fp,len) == 0);
-}
-
-int PMAPI PM_unlockCodePages(void (*p)(),uint len,PM_lockHandle *lh)
-{
- CONFIG_INF config;
- FARPTR fp;
-
- _dx_config_inf(&config, (UCHAR*)&config);
- FP_SET(fp,p,config.c_cs_sel);
- return (_dx_ulock_pgs(fp,len) == 0);
-}
-
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* Symantec C++ DOSX and FlashTek X-32/X-32VM support */
-/*-------------------------------------------------------------------------*/
-
-#if defined(DOSX) || defined(X32VM)
-
-#ifdef X32VM
-#include <x32.h>
-#endif
-
-static long prevRealBreak; /* Previous real mode break handler */
-static long prevRealCtrlC; /* Previous real mode CtrlC handler */
-static long prevRealCritical; /* Prev real mode critical handler */
-
-static uint mouseSel = 0,mouseOff;
-
-/* The following real mode routine is used to call a 32 bit protected
- * mode FAR function from real mode. We use this for passing up control
- * from the real mode mouse callback to our protected mode code.
- */
-
-static char realHandler[] = { /* Real mode code generic handler */
- 0x00,0x00,0x00,0x00, /* __PM_callProtp */
- 0x00,0x00, /* __PM_protCS */
- 0x00,0x00,0x00,0x00, /* __PM_protHandler */
- 0x1E, /* push ds */
- 0x6A,0x00, /* push 0 */
- 0x6A,0x00, /* push 0 */
- 0x2E,0xFF,0x36,0x04,0x00, /* push [cs:__PM_protCS] */
- 0x66,0x2E,0xFF,0x36,0x06,0x00, /* push [cs:__PM_protHandler] */
- 0x2E,0xFF,0x1E,0x00,0x00, /* call [cs:__PM_callProtp] */
- 0x83,0xC4,0x0A, /* add sp,10 */
- 0x1F, /* pop ds */
- 0xCB, /* retf */
- };
-
-/* The following functions installs the above realmode callback mechanism
- * in real mode memory for calling the protected mode routine.
- */
-
-int installCallback(void (PMAPI *pmCB)(),uint *psel, uint *poff,
- uint *rseg, uint *roff)
-{
- PMREGS regs;
- PMSREGS sregs;
-
- regs.x.ax = 0x250D;
- PM_segread(&sregs);
- PM_int386x(0x21,&regs,&regs,&sregs); /* Get RM callback address */
-
- /* Fill in the values in the real mode code segment so that it will
- * call the correct routine.
- */
- *((ulong*)&realHandler[0]) = regs.e.eax;
- *((ushort*)&realHandler[4]) = sregs.cs;
- *((ulong*)&realHandler[6]) = (ulong)pmCB;
-
- /* Copy the real mode handler to real mode memory (only allocate the
- * buffer once since we cant dealloate it with X32).
- */
- if (*psel == 0) {
- if (!PM_allocRealSeg(sizeof(realHandler),psel,poff,rseg,roff))
- return 0;
- }
- PM_memcpyfn(*psel,*poff,realHandler,sizeof(realHandler));
-
- /* Skip past global variables in real mode code segment */
- *roff += 0x0A;
- return 1;
-}
-
-int PMAPI PM_setMouseHandler(int mask, PM_mouseHandler mh)
-{
- RMREGS regs;
- RMSREGS sregs;
- uint rseg,roff;
-
- lockPMHandlers(); /* Ensure our handlers are locked */
-
- if (!installCallback(_PM_mouseISR, &mouseSel, &mouseOff, &rseg, &roff))
- return 0;
- _PM_mouseHandler = mh;
-
- /* Install the real mode mouse handler */
- sregs.es = rseg;
- regs.x.dx = roff;
- regs.x.cx = _PM_mouseMask = mask;
- regs.x.ax = 0xC;
- PM_int86x(0x33, &regs, &regs, &sregs);
- return 1;
-}
-
-void PMAPI PM_restoreMouseHandler(void)
-{
- RMREGS regs;
-
- if (_PM_mouseHandler) {
- regs.x.ax = 33;
- PM_int86(0x33, &regs, &regs);
- _PM_mouseHandler = NULL;
- }
-}
-
-void PMAPI PM_getPMvect(int intno, PMFARPTR *isr)
-{
- PMREGS regs;
- PMSREGS sregs;
-
- PM_segread(&sregs);
- regs.x.ax = 0x2502; /* Get PM interrupt vector */
- regs.x.cx = intno;
- PM_int386x(0x21, &regs, &regs, &sregs);
- isr->sel = sregs.es;
- isr->off = regs.e.ebx;
-}
-
-void PMAPI PM_setPMvect(int intno, PM_intHandler isr)
-{
- PMFARPTR pmisr;
- PMSREGS sregs;
-
- PM_saveDS();
- PM_segread(&sregs);
- pmisr.sel = sregs.cs;
- pmisr.off = (uint)isr;
- PM_restorePMvect(intno, pmisr);
-}
-
-void PMAPI PM_restorePMvect(int intno, PMFARPTR isr)
-{
- PMREGS regs;
- PMSREGS sregs;
-
- PM_segread(&sregs);
- regs.x.ax = 0x2505; /* Set PM interrupt vector */
- regs.x.cx = intno;
- sregs.ds = isr.sel;
- regs.e.edx = isr.off;
- PM_int386x(0x21, &regs, &regs, &sregs);
-}
-
-static void getISR(int intno, PMFARPTR *pmisr, long *realisr)
-{
- PM_getPMvect(intno,pmisr);
- _PM_getRMvect(intno,realisr);
-}
-
-static void restoreISR(int intno, PMFARPTR pmisr, long realisr)
-{
- PMREGS regs;
- PMSREGS sregs;
-
- PM_segread(&sregs);
- regs.x.ax = 0x2507; /* Set real and PM vectors */
- regs.x.cx = intno;
- sregs.ds = pmisr.sel;
- regs.e.edx = pmisr.off;
- regs.e.ebx = realisr;
- PM_int386x(0x21, &regs, &regs, &sregs);
-}
-
-static void setISR(int intno, void *isr)
-{
- PMREGS regs;
- PMSREGS sregs;
-
- lockPMHandlers(); /* Ensure our handlers are locked */
-
- PM_segread(&sregs);
- regs.x.ax = 0x2506; /* Hook real and protected vectors */
- regs.x.cx = intno;
- sregs.ds = sregs.cs;
- regs.e.edx = (uint)isr;
- PM_int386x(0x21, &regs, &regs, &sregs);
-}
-
-void PMAPI PM_setTimerHandler(PM_intHandler th)
-{
- getISR(0x8, &_PM_prevTimer, &_PM_prevRealTimer);
- _PM_timerHandler = th;
- setISR(0x8, _PM_timerISR);
-}
-
-void PMAPI PM_restoreTimerHandler(void)
-{
- if (_PM_timerHandler) {
- restoreISR(0x8, _PM_prevTimer, _PM_prevRealTimer);
- _PM_timerHandler = NULL;
- }
-}
-
-ibool PMAPI PM_setRealTimeClockHandler(PM_intHandler th,int frequency)
-{
- /* Save the old CMOS real time clock values */
- _PM_oldCMOSRegA = _PM_readCMOS(0x0A);
- _PM_oldCMOSRegB = _PM_readCMOS(0x0B);
-
- /* Set the real time clock interrupt handler */
- getISR(0x70, &_PM_prevRTC, &_PM_prevRealRTC);
- _PM_rtcHandler = th;
- setISR(0x70, _PM_rtcISR);
-
- /* Program the real time clock default frequency */
- PM_setRealTimeClockFrequency(frequency);
-
- /* Unmask IRQ8 in the PIC2 */
- _PM_oldRTCPIC2 = PM_inpb(0xA1);
- PM_outpb(0xA1,_PM_oldRTCPIC2 & 0xFE);
- return true;
-}
-
-void PMAPI PM_restoreRealTimeClockHandler(void)
-{
- if (_PM_rtcHandler) {
- /* Restore CMOS registers and mask RTC clock */
- _PM_writeCMOS(0x0A,_PM_oldCMOSRegA);
- _PM_writeCMOS(0x0B,_PM_oldCMOSRegB);
- PM_outpb(0xA1,(PM_inpb(0xA1) & 0xFE) | (_PM_oldRTCPIC2 & ~0xFE));
-
- /* Restore the interrupt vector */
- restoreISR(0x70, _PM_prevRTC, _PM_prevRealRTC);
- _PM_rtcHandler = NULL;
- }
-}
-
-void PMAPI PM_setKeyHandler(PM_intHandler kh)
-{
- getISR(0x9, &_PM_prevKey, &_PM_prevRealKey);
- _PM_keyHandler = kh;
- setISR(0x9, _PM_keyISR);
-}
-
-void PMAPI PM_restoreKeyHandler(void)
-{
- if (_PM_keyHandler) {
- restoreISR(0x9, _PM_prevKey, _PM_prevRealKey);
- _PM_keyHandler = NULL;
- }
-}
-
-void PMAPI PM_setKey15Handler(PM_key15Handler kh)
-{
- getISR(0x15, &_PM_prevKey15, &_PM_prevRealKey15);
- _PM_key15Handler = kh;
- setISR(0x15, _PM_key15ISR);
-}
-
-void PMAPI PM_restoreKey15Handler(void)
-{
- if (_PM_key15Handler) {
- restoreISR(0x15, _PM_prevKey15, _PM_prevRealKey15);
- _PM_key15Handler = NULL;
- }
-}
-
-void PMAPI PM_installAltBreakHandler(PM_breakHandler bh)
-{
- static int ctrlCFlag,ctrlBFlag;
-
- _PM_ctrlCPtr = (uchar*)&ctrlCFlag;
- _PM_ctrlBPtr = (uchar*)&ctrlBFlag;
- getISR(0x1B, &_PM_prevBreak, &prevRealBreak);
- getISR(0x23, &_PM_prevCtrlC, &prevRealCtrlC);
- _PM_breakHandler = bh;
- setISR(0x1B, _PM_breakISR);
- setISR(0x23, _PM_ctrlCISR);
-}
-
-void PMAPI PM_installBreakHandler(void)
-{
- PM_installAltBreakHandler(NULL);
-}
-
-void PMAPI PM_restoreBreakHandler(void)
-{
- if (_PM_prevBreak.sel) {
- restoreISR(0x1B, _PM_prevBreak, prevRealBreak);
- restoreISR(0x23, _PM_prevCtrlC, prevRealCtrlC);
- _PM_prevBreak.sel = 0;
- _PM_breakHandler = NULL;
- }
-}
-
-void PMAPI PM_installAltCriticalHandler(PM_criticalHandler ch)
-{
- static short critBuf[2];
-
- _PM_critPtr = (uchar*)critBuf;
- getISR(0x24, &_PM_prevCritical, &prevRealCritical);
- _PM_critHandler = ch;
- setISR(0x24, _PM_criticalISR);
-}
-
-void PMAPI PM_installCriticalHandler(void)
-{
- PM_installAltCriticalHandler(NULL);
-}
-
-void PMAPI PM_restoreCriticalHandler(void)
-{
- if (_PM_prevCritical.sel) {
- restoreISR(0x24, _PM_prevCritical, prevRealCritical);
- _PM_prevCritical.sel = 0;
- _PM_critHandler = NULL;
- }
-}
-
-int PMAPI PM_lockDataPages(void *p,uint len,PM_lockHandle *lh)
-{
- return (_x386_memlock(p,len) == 0);
-}
-
-int PMAPI PM_unlockDataPages(void *p,uint len,PM_lockHandle *lh)
-{
- return (_x386_memunlock(p,len) == 0);
-}
-
-int PMAPI PM_lockCodePages(void (*p)(),uint len,PM_lockHandle *lh)
-{
- return (_x386_memlock(p,len) == 0);
-}
-
-int PMAPI PM_unlockCodePages(void (*p)(),uint len,PM_lockHandle *lh)
-{
- return (_x386_memunlock(p,len) == 0);
-}
-
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* Borland's DPMI32 DOS Power Pack Extender support. */
-/*-------------------------------------------------------------------------*/
-
-#ifdef DPMI32
-#define GENERIC_DPMI32 /* Use generic 32 bit DPMI routines */
-
-void PMAPI PM_getPMvect(int intno, PMFARPTR *isr)
-{
- PMREGS regs;
-
- regs.x.ax = 0x204;
- regs.h.bl = intno;
- PM_int386(0x31,&regs,&regs);
- isr->sel = regs.x.cx;
- isr->off = regs.e.edx;
-}
-
-void PMAPI PM_setPMvect(int intno, PM_intHandler isr)
-{
- PMSREGS sregs;
- PMREGS regs;
-
- PM_saveDS();
- regs.x.ax = 0x205; /* Set protected mode vector */
- regs.h.bl = intno;
- PM_segread(&sregs);
- regs.x.cx = sregs.cs;
- regs.e.edx = (uint)isr;
- PM_int386(0x31,&regs,&regs);
-}
-
-void PMAPI PM_restorePMvect(int intno, PMFARPTR isr)
-{
- PMREGS regs;
-
- regs.x.ax = 0x205;
- regs.h.bl = intno;
- regs.x.cx = isr.sel;
- regs.e.edx = isr.off;
- PM_int386(0x31,&regs,&regs);
-}
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* Watcom C/C++ with Rational DOS/4GW support. */
-/*-------------------------------------------------------------------------*/
-
-#ifdef DOS4GW
-#define GENERIC_DPMI32 /* Use generic 32 bit DPMI routines */
-
-#define MOUSE_SUPPORTED /* DOS4GW directly supports mouse */
-
-/* We use the normal DOS services to save and restore interrupts handlers
- * for Watcom C++, because using the direct DPMI functions does not
- * appear to work properly. At least if we use the DPMI functions, we
- * dont get the auto-passup feature that we need to correctly trap
- * real and protected mode interrupts without installing Bi-model
- * interrupt handlers.
- */
-
-void PMAPI PM_getPMvect(int intno, PMFARPTR *isr)
-{
- PMREGS regs;
- PMSREGS sregs;
-
- PM_segread(&sregs);
- regs.h.ah = 0x35;
- regs.h.al = intno;
- PM_int386x(0x21,&regs,&regs,&sregs);
- isr->sel = sregs.es;
- isr->off = regs.e.ebx;
-}
-
-void PMAPI PM_setPMvect(int intno, PM_intHandler isr)
-{
- PMREGS regs;
- PMSREGS sregs;
-
- PM_saveDS();
- PM_segread(&sregs);
- regs.h.ah = 0x25;
- regs.h.al = intno;
- sregs.ds = sregs.cs;
- regs.e.edx = (uint)isr;
- PM_int386x(0x21,&regs,&regs,&sregs);
-}
-
-void PMAPI PM_restorePMvect(int intno, PMFARPTR isr)
-{
- PMREGS regs;
- PMSREGS sregs;
-
- PM_segread(&sregs);
- regs.h.ah = 0x25;
- regs.h.al = intno;
- sregs.ds = isr.sel;
- regs.e.edx = isr.off;
- PM_int386x(0x21,&regs,&regs,&sregs);
-}
-
-int PMAPI PM_setMouseHandler(int mask, PM_mouseHandler mh)
-{
- lockPMHandlers(); /* Ensure our handlers are locked */
-
- _PM_mouseHandler = mh;
- _PM_setMouseHandler(_PM_mouseMask = mask);
- return 1;
-}
-
-void PMAPI PM_restoreMouseHandler(void)
-{
- PMREGS regs;
-
- if (_PM_mouseHandler) {
- regs.x.ax = 33;
- PM_int386(0x33, &regs, &regs);
- _PM_mouseHandler = NULL;
- }
-}
-
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* DJGPP port of GNU C++ support. */
-/*-------------------------------------------------------------------------*/
-
-#ifdef DJGPP
-#define GENERIC_DPMI32 /* Use generic 32 bit DPMI routines */
-
-void PMAPI PM_getPMvect(int intno, PMFARPTR *isr)
-{
- PMREGS regs;
-
- regs.x.ax = 0x204;
- regs.h.bl = intno;
- PM_int386(0x31,&regs,&regs);
- isr->sel = regs.x.cx;
- isr->off = regs.e.edx;
-}
-
-void PMAPI PM_setPMvect(int intno, PM_intHandler isr)
-{
- PMSREGS sregs;
- PMREGS regs;
-
- PM_saveDS();
- regs.x.ax = 0x205; /* Set protected mode vector */
- regs.h.bl = intno;
- PM_segread(&sregs);
- regs.x.cx = sregs.cs;
- regs.e.edx = (uint)isr;
- PM_int386(0x31,&regs,&regs);
-}
-
-void PMAPI PM_restorePMvect(int intno, PMFARPTR isr)
-{
- PMREGS regs;
-
- regs.x.ax = 0x205;
- regs.h.bl = intno;
- regs.x.cx = isr.sel;
- regs.e.edx = isr.off;
- PM_int386(0x31,&regs,&regs);
-}
-
-#endif
-
-/*-------------------------------------------------------------------------*/
-/* Generic 32 bit DPMI routines */
-/*-------------------------------------------------------------------------*/
-
-#if defined(GENERIC_DPMI32)
-
-static long prevRealBreak; /* Previous real mode break handler */
-static long prevRealCtrlC; /* Previous real mode CtrlC handler */
-static long prevRealCritical; /* Prev real mode critical handler */
-
-#ifndef MOUSE_SUPPORTED
-
-/* The following real mode routine is used to call a 32 bit protected
- * mode FAR function from real mode. We use this for passing up control
- * from the real mode mouse callback to our protected mode code.
- */
-
-static long mouseRMCB; /* Mouse real mode callback address */
-static uchar *mousePtr;
-static char mouseRegs[0x32]; /* Real mode regs for mouse callback */
-static uchar mouseHandler[] = {
- 0x00,0x00,0x00,0x00, /* _realRMCB */
- 0x2E,0xFF,0x1E,0x00,0x00, /* call [cs:_realRMCB] */
- 0xCB, /* retf */
- };
-
-int PMAPI PM_setMouseHandler(int mask, PM_mouseHandler mh)
-{
- RMREGS regs;
- RMSREGS sregs;
- uint rseg,roff;
-
- lockPMHandlers(); /* Ensure our handlers are locked */
-
- /* Copy the real mode handler to real mode memory */
- if ((mousePtr = PM_allocRealSeg(sizeof(mouseHandler),&rseg,&roff)) == NULL)
- return 0;
- memcpy(mousePtr,mouseHandler,sizeof(mouseHandler));
- if (!_DPMI_allocateCallback(_PM_mousePMCB, mouseRegs, &mouseRMCB))
- PM_fatalError("Unable to allocate real mode callback!\n");
- PM_setLong(mousePtr,mouseRMCB);
-
- /* Install the real mode mouse handler */
- _PM_mouseHandler = mh;
- sregs.es = rseg;
- regs.x.dx = roff+4;
- regs.x.cx = _PM_mouseMask = mask;
- regs.x.ax = 0xC;
- PM_int86x(0x33, &regs, &regs, &sregs);
- return 1;
-}
-
-void PMAPI PM_restoreMouseHandler(void)
-{
- RMREGS regs;
-
- if (_PM_mouseHandler) {
- regs.x.ax = 33;
- PM_int86(0x33, &regs, &regs);
- PM_freeRealSeg(mousePtr);
- _DPMI_freeCallback(mouseRMCB);
- _PM_mouseHandler = NULL;
- }
-}
-
-#endif
-
-static void getISR(int intno, PMFARPTR *pmisr, long *realisr)
-{
- PM_getPMvect(intno,pmisr);
- _PM_getRMvect(intno,realisr);
-}
-
-static void restoreISR(int intno, PMFARPTR pmisr, long realisr)
-{
- _PM_setRMvect(intno,realisr);
- PM_restorePMvect(intno,pmisr);
-}
-
-static void setISR(int intno, void (* PMAPI pmisr)())
-{
- lockPMHandlers(); /* Ensure our handlers are locked */
- PM_setPMvect(intno,pmisr);
-}
-
-void PMAPI PM_setTimerHandler(PM_intHandler th)
-{
- getISR(0x8, &_PM_prevTimer, &_PM_prevRealTimer);
- _PM_timerHandler = th;
- setISR(0x8, _PM_timerISR);
-}
-
-void PMAPI PM_restoreTimerHandler(void)
-{
- if (_PM_timerHandler) {
- restoreISR(0x8, _PM_prevTimer, _PM_prevRealTimer);
- _PM_timerHandler = NULL;
- }
-}
-
-ibool PMAPI PM_setRealTimeClockHandler(PM_intHandler th,int frequency)
-{
- /* Save the old CMOS real time clock values */
- _PM_oldCMOSRegA = _PM_readCMOS(0x0A);
- _PM_oldCMOSRegB = _PM_readCMOS(0x0B);
-
- /* Set the real time clock interrupt handler */
- getISR(0x70, &_PM_prevRTC, &_PM_prevRealRTC);
- _PM_rtcHandler = th;
- setISR(0x70, _PM_rtcISR);
-
- /* Program the real time clock default frequency */
- PM_setRealTimeClockFrequency(frequency);
-
- /* Unmask IRQ8 in the PIC2 */
- _PM_oldRTCPIC2 = PM_inpb(0xA1);
- PM_outpb(0xA1,_PM_oldRTCPIC2 & 0xFE);
- return true;
-}
-
-void PMAPI PM_restoreRealTimeClockHandler(void)
-{
- if (_PM_rtcHandler) {
- /* Restore CMOS registers and mask RTC clock */
- _PM_writeCMOS(0x0A,_PM_oldCMOSRegA);
- _PM_writeCMOS(0x0B,_PM_oldCMOSRegB);
- PM_outpb(0xA1,(PM_inpb(0xA1) & 0xFE) | (_PM_oldRTCPIC2 & ~0xFE));
-
- /* Restore the interrupt vector */
- restoreISR(0x70, _PM_prevRTC, _PM_prevRealRTC);
- _PM_rtcHandler = NULL;
- }
-}
-
-PM_IRQHandle PMAPI PM_setIRQHandler(
- int IRQ,
- PM_irqHandler ih)
-{
- int thunkSize,PICmask,chainPrevious;
- ulong offsetAdjust;
- _PM_IRQHandle *handle;
-
- thunkSize = (ulong)_PM_irqISRTemplateEnd - (ulong)_PM_irqISRTemplate;
- if ((handle = PM_malloc(sizeof(_PM_IRQHandle) + thunkSize)) == NULL)
- return NULL;
- handle->IRQ = IRQ;
- handle->prevPIC = PM_inpb(0x21);
- handle->prevPIC2 = PM_inpb(0xA1);
- if (IRQ < 8) {
- handle->IRQVect = (IRQ + 8);
- PICmask = (1 << IRQ);
- chainPrevious = ((handle->prevPIC & PICmask) == 0);
- }
- else {
- handle->IRQVect = (0x60 + IRQ + 8);
- PICmask = ((1 << IRQ) | 0x4);
- chainPrevious = ((handle->prevPIC2 & (PICmask >> 8)) == 0);
- }
-
- /* Copy and setup the assembler thunk */
- offsetAdjust = (ulong)handle->thunk - (ulong)_PM_irqISRTemplate;
- memcpy(handle->thunk,_PM_irqISRTemplate,thunkSize);
- *((ulong*)&handle->thunk[2]) = offsetAdjust;
- *((ulong*)&handle->thunk[11+0]) = (ulong)ih;
- if (chainPrevious) {
- *((ulong*)&handle->thunk[11+4]) = handle->prevHandler.off;
- *((ulong*)&handle->thunk[11+8]) = handle->prevHandler.sel;
- }
- else {
- *((ulong*)&handle->thunk[11+4]) = 0;
- *((ulong*)&handle->thunk[11+8]) = 0;
- }
- *((ulong*)&handle->thunk[11+12]) = IRQ;
-
- /* Set the real time clock interrupt handler */
- getISR(handle->IRQVect, &handle->prevHandler, &handle->prevRealhandler);
- setISR(handle->IRQVect, (PM_intHandler)handle->thunk);
-
- /* Unmask the IRQ in the PIC */
- PM_outpb(0xA1,handle->prevPIC2 & ~(PICmask >> 8));
- PM_outpb(0x21,handle->prevPIC & ~PICmask);
- return handle;
-}
-
-void PMAPI PM_restoreIRQHandler(
- PM_IRQHandle irqHandle)
-{
- int PICmask;
- _PM_IRQHandle *handle = irqHandle;
-
- /* Restore PIC mask for the interrupt */
- if (handle->IRQ < 8)
- PICmask = (1 << handle->IRQ);
- else
- PICmask = ((1 << handle->IRQ) | 0x4);
- PM_outpb(0xA1,(PM_inpb(0xA1) & ~(PICmask >> 8)) | (handle->prevPIC2 & (PICmask >> 8)));
- PM_outpb(0x21,(PM_inpb(0x21) & ~PICmask) | (handle->prevPIC & PICmask));
-
- /* Restore the interrupt vector */
- restoreISR(handle->IRQVect, handle->prevHandler, handle->prevRealhandler);
-
- /* Finally free the thunk */
- PM_free(handle);
-}
-
-void PMAPI PM_setKeyHandler(PM_intHandler kh)
-{
- getISR(0x9, &_PM_prevKey, &_PM_prevRealKey);
- _PM_keyHandler = kh;
- setISR(0x9, _PM_keyISR);
-}
-
-void PMAPI PM_restoreKeyHandler(void)
-{
- if (_PM_keyHandler) {
- restoreISR(0x9, _PM_prevKey, _PM_prevRealKey);
- _PM_keyHandler = NULL;
- }
-}
-
-void PMAPI PM_setKey15Handler(PM_key15Handler kh)
-{
- getISR(0x15, &_PM_prevKey15, &_PM_prevRealKey15);
- _PM_key15Handler = kh;
- setISR(0x15, _PM_key15ISR);
-}
-
-void PMAPI PM_restoreKey15Handler(void)
-{
- if (_PM_key15Handler) {
- restoreISR(0x15, _PM_prevKey15, _PM_prevRealKey15);
- _PM_key15Handler = NULL;
- }
-}
-
-/* Real mode Ctrl-C and Ctrl-Break handler. This handler simply sets a
- * flag in the real mode code segment and exit. We save the location
- * of this flag in real mode memory so that both the real mode and
- * protected mode code will be modifying the same flags.
- */
-
-#ifndef DOS4GW
-static uchar ctrlHandler[] = {
- 0x00,0x00,0x00,0x00, /* ctrlBFlag */
- 0x66,0x2E,0xC7,0x06,0x00,0x00,
- 0x01,0x00,0x00,0x00, /* mov [cs:ctrlBFlag],1 */
- 0xCF, /* iretf */
- };
-#endif
-
-void PMAPI PM_installAltBreakHandler(PM_breakHandler bh)
-{
-#ifndef DOS4GW
- uint rseg,roff;
-#else
- static int ctrlCFlag,ctrlBFlag;
-
- _PM_ctrlCPtr = (uchar*)&ctrlCFlag;
- _PM_ctrlBPtr = (uchar*)&ctrlBFlag;
-#endif
-
- getISR(0x1B, &_PM_prevBreak, &prevRealBreak);
- getISR(0x23, &_PM_prevCtrlC, &prevRealCtrlC);
- _PM_breakHandler = bh;
- setISR(0x1B, _PM_breakISR);
- setISR(0x23, _PM_ctrlCISR);
-
-#ifndef DOS4GW
- /* Hook the real mode vectors for these handlers, as these are not
- * normally reflected by the DPMI server up to protected mode
- */
- _PM_ctrlBPtr = PM_allocRealSeg(sizeof(ctrlHandler)*2, &rseg, &roff);
- memcpy(_PM_ctrlBPtr,ctrlHandler,sizeof(ctrlHandler));
- memcpy(_PM_ctrlBPtr+sizeof(ctrlHandler),ctrlHandler,sizeof(ctrlHandler));
- _PM_ctrlCPtr = _PM_ctrlBPtr + sizeof(ctrlHandler);
- _PM_setRMvect(0x1B,((long)rseg << 16) | (roff+4));
- _PM_setRMvect(0x23,((long)rseg << 16) | (roff+sizeof(ctrlHandler)+4));
-#endif
-}
-
-void PMAPI PM_installBreakHandler(void)
-{
- PM_installAltBreakHandler(NULL);
-}
-
-void PMAPI PM_restoreBreakHandler(void)
-{
- if (_PM_prevBreak.sel) {
- restoreISR(0x1B, _PM_prevBreak, prevRealBreak);
- restoreISR(0x23, _PM_prevCtrlC, prevRealCtrlC);
- _PM_prevBreak.sel = 0;
- _PM_breakHandler = NULL;
-#ifndef DOS4GW
- PM_freeRealSeg(_PM_ctrlBPtr);
-#endif
- }
-}
-
-/* Real mode Critical Error handler. This handler simply saves the AX and
- * DI values in the real mode code segment and exits. We save the location
- * of this flag in real mode memory so that both the real mode and
- * protected mode code will be modifying the same flags.
- */
-
-#ifndef DOS4GW
-static uchar criticalHandler[] = {
- 0x00,0x00, /* axCode */
- 0x00,0x00, /* diCode */
- 0x2E,0xA3,0x00,0x00, /* mov [cs:axCode],ax */
- 0x2E,0x89,0x3E,0x02,0x00, /* mov [cs:diCode],di */
- 0xB8,0x03,0x00, /* mov ax,3 */
- 0xCF, /* iretf */
- };
-#endif
-
-void PMAPI PM_installAltCriticalHandler(PM_criticalHandler ch)
-{
-#ifndef DOS4GW
- uint rseg,roff;
-#else
- static short critBuf[2];
-
- _PM_critPtr = (uchar*)critBuf;
-#endif
-
- getISR(0x24, &_PM_prevCritical, &prevRealCritical);
- _PM_critHandler = ch;
- setISR(0x24, _PM_criticalISR);
-
-#ifndef DOS4GW
- /* Hook the real mode vector, as this is not normally reflected by the
- * DPMI server up to protected mode.
- */
- _PM_critPtr = PM_allocRealSeg(sizeof(criticalHandler)*2, &rseg, &roff);
- memcpy(_PM_critPtr,criticalHandler,sizeof(criticalHandler));
- _PM_setRMvect(0x24,((long)rseg << 16) | (roff+4));
-#endif
-}
-
-void PMAPI PM_installCriticalHandler(void)
-{
- PM_installAltCriticalHandler(NULL);
-}
-
-void PMAPI PM_restoreCriticalHandler(void)
-{
- if (_PM_prevCritical.sel) {
- restoreISR(0x24, _PM_prevCritical, prevRealCritical);
- PM_freeRealSeg(_PM_critPtr);
- _PM_prevCritical.sel = 0;
- _PM_critHandler = NULL;
- }
-}
-
-int PMAPI PM_lockDataPages(void *p,uint len,PM_lockHandle *lh)
-{
- PMSREGS sregs;
- PM_segread(&sregs);
- return DPMI_lockLinearPages((uint)p + DPMI_getSelectorBase(sregs.ds),len);
-}
-
-int PMAPI PM_unlockDataPages(void *p,uint len,PM_lockHandle *lh)
-{
- PMSREGS sregs;
- PM_segread(&sregs);
- return DPMI_unlockLinearPages((uint)p + DPMI_getSelectorBase(sregs.ds),len);
-}
-
-int PMAPI PM_lockCodePages(void (*p)(),uint len,PM_lockHandle *lh)
-{
- PMSREGS sregs;
- PM_segread(&sregs);
- return DPMI_lockLinearPages((uint)p + DPMI_getSelectorBase(sregs.cs),len);
-}
-
-int PMAPI PM_unlockCodePages(void (*p)(),uint len,PM_lockHandle *lh)
-{
- PMSREGS sregs;
- PM_segread(&sregs);
- return DPMI_unlockLinearPages((uint)p + DPMI_getSelectorBase(sregs.cs),len);
-}
-
-#endif
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/vflat.c b/board/MAI/bios_emulator/scitech/src/pm/dos/vflat.c
deleted file mode 100644
index c3e9b6c33f..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/vflat.c
+++ /dev/null
@@ -1,251 +0,0 @@
-/****************************************************************************
-*
-* SciTech OS Portability Manager Library
-*
-* ========================================================================
-*
-* The contents of this file are subject to the SciTech MGL Public
-* License Version 1.0 (the "License"); you may not use this file
-* except in compliance with the License. You may obtain a copy of
-* the License at http://www.scitechsoft.com/mgl-license.txt
-*
-* Software distributed under the License is distributed on an
-* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-* implied. See the License for the specific language governing
-* rights and limitations under the License.
-*
-* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-*
-* The Initial Developer of the Original Code is SciTech Software, Inc.
-* All Rights Reserved.
-*
-* ========================================================================
-*
-* Language: ANSI C
-* Environment: 32-bit DOS
-*
-* Description: Main C module for the VFlat framebuffer routines. The page
-* fault handler is always installed to handle up to a 4Mb
-* framebuffer with a window size of 4Kb or 64Kb in size.
-*
-****************************************************************************/
-
-#include "pmapi.h"
-#include <stdlib.h>
-#include <dos.h>
-
-/*-------------------------------------------------------------------------*/
-/* DOS4G/W, PMODE/W and CauseWay support. */
-/*-------------------------------------------------------------------------*/
-
-#if defined(DOS4GW)
-
-#define VFLAT_START_ADDR 0xF0000000U
-#define VFLAT_END_ADDR 0xF03FFFFFU
-#define VFLAT_LIMIT (VFLAT_END_ADDR - VFLAT_START_ADDR)
-#define PAGE_PRESENT 1
-#define PAGE_NOTPRESENT 0
-#define PAGE_READ 0
-#define PAGE_WRITE 2
-
-PRIVATE ibool installed = false;
-PRIVATE ibool haveDPMI = false;
-PUBLIC ibool _ASMAPI VF_haveCauseWay = false;
-PUBLIC uchar * _ASMAPI VF_zeroPtr = NULL;
-
-/* Low level assembler code */
-
-int _ASMAPI InitPaging(void);
-void _ASMAPI ClosePaging(void);
-void _ASMAPI MapPhysical2Linear(ulong pAddr, ulong lAddr, int pages, int flags);
-void _ASMAPI InstallFaultHandler(ulong baseAddr,int bankSize);
-void _ASMAPI RemoveFaultHandler(void);
-void _ASMAPI InstallBankFunc(int codeLen,void *bankFunc);
-
-void * _ASMAPI VF_malloc(uint size)
-{ return PM_malloc(size); }
-
-void _ASMAPI VF_free(void *p)
-{ PM_free(p); }
-
-PRIVATE ibool CheckDPMI(void)
-/****************************************************************************
-*
-* Function: CheckDPMI
-* Returns: True if we are running under DPMI
-*
-****************************************************************************/
-{
- PMREGS regs;
-
- if (haveDPMI)
- return true;
-
- /* Check if we are running under DPMI in which case we will not be
- * able to install our page fault handlers. We can however use the
- * DVA.386 or VFLATD.386 virtual device drivers if they are present.
- */
- regs.x.ax = 0xFF00;
- PM_int386(0x31,&regs,&regs);
- if (!regs.x.cflag && (regs.e.edi & 8))
- return (haveDPMI = true);
- return false;
-}
-
-ibool PMAPI VF_available(void)
-/****************************************************************************
-*
-* Function: VF_available
-* Returns: True if virtual buffer is available, false if not.
-*
-****************************************************************************/
-{
- if (!VF_zeroPtr)
- VF_zeroPtr = PM_mapPhysicalAddr(0,0xFFFFFFFF,true);
- if (CheckDPMI())
- return false;
-
- /* Standard DOS4GW, PMODE/W and Causeway */
- if (InitPaging() == -1)
- return false;
- ClosePaging();
- return true;
-}
-
-void * PMAPI InitDPMI(ulong baseAddr,int bankSize,int codeLen,void *bankFunc)
-/****************************************************************************
-*
-* Function: InitDOS4GW
-* Parameters: baseAddr - Base address of framebuffer bank window
-* bankSize - Physical size of banks in Kb (4 or 64)
-* codeLen - Length of 32 bit bank switch function
-* bankFunc - Pointer to protected mode bank function
-* Returns: Near pointer to virtual framebuffer, or NULL on failure.
-*
-* Description: Installs the virtual linear framebuffer handling for
-* DPMI environments. This requires the DVA.386 or VFLATD.386
-* virtual device drivers to be installed and functioning.
-*
-****************************************************************************/
-{
- (void)baseAddr;
- (void)bankSize;
- (void)codeLen;
- (void)bankFunc;
- return NULL;
-}
-
-void * PMAPI InitDOS4GW(ulong baseAddr,int bankSize,int codeLen,void *bankFunc)
-/****************************************************************************
-*
-* Function: InitDOS4GW
-* Parameters: baseAddr - Base address of framebuffer bank window
-* bankSize - Physical size of banks in Kb (4 or 64)
-* codeLen - Length of 32 bit bank switch function
-* bankFunc - Pointer to protected mode bank function
-* Returns: Near pointer to virtual framebuffer, or NULL on failure.
-*
-* Description: Installs the virtual linear framebuffer handling for
-* the DOS4GW extender.
-*
-****************************************************************************/
-{
- int i;
-
- if (InitPaging() == -1)
- return NULL; /* Cannot do hardware paging! */
-
- /* Map 4MB of video memory into linear address space (read/write) */
- if (bankSize == 64) {
- for (i = 0; i < 64; i++) {
- MapPhysical2Linear(baseAddr,VFLAT_START_ADDR+(i<<16),16,
- PAGE_WRITE | PAGE_NOTPRESENT);
- }
- }
- else {
- for (i = 0; i < 1024; i++) {
- MapPhysical2Linear(baseAddr,VFLAT_START_ADDR+(i<<12),1,
- PAGE_WRITE | PAGE_NOTPRESENT);
- }
- }
-
- /* Install our page fault handler and banks switch function */
- InstallFaultHandler(baseAddr,bankSize);
- InstallBankFunc(codeLen,bankFunc);
- installed = true;
- return (void*)VFLAT_START_ADDR;
-}
-
-void * PMAPI VF_init(ulong baseAddr,int bankSize,int codeLen,void *bankFunc)
-/****************************************************************************
-*
-* Function: VF_init
-* Parameters: baseAddr - Base address of framebuffer bank window
-* bankSize - Physical size of banks in Kb (4 or 64)
-* codeLen - Length of 32 bit bank switch function
-* bankFunc - Pointer to protected mode bank function
-* Returns: Near pointer to virtual framebuffer, or NULL on failure.
-*
-* Description: Installs the virtual linear framebuffer handling.
-*
-****************************************************************************/
-{
- if (installed)
- return (void*)VFLAT_START_ADDR;
- if (codeLen > 100)
- return NULL; /* Bank function is too large! */
- if (!VF_zeroPtr)
- VF_zeroPtr = PM_mapPhysicalAddr(0,0xFFFFFFFF,true);
- if (CheckDPMI())
- return InitDPMI(baseAddr,bankSize,codeLen,bankFunc);
- return InitDOS4GW(baseAddr,bankSize,codeLen,bankFunc);
-}
-
-void PMAPI VF_exit(void)
-/****************************************************************************
-*
-* Function: VF_exit
-*
-* Description: Closes down the virtual framebuffer services and
-* restores the previous page fault handler.
-*
-****************************************************************************/
-{
- if (installed) {
- if (haveDPMI) {
- /* DPMI support */
- }
- else {
- /* Standard DOS4GW and PMODE/W support */
- RemoveFaultHandler();
- ClosePaging();
- }
- installed = false;
- }
-}
-
-/*-------------------------------------------------------------------------*/
-/* Support mapped out for other compilers. */
-/*-------------------------------------------------------------------------*/
-
-#else
-
-ibool PMAPI VF_available(void)
-{
- return false;
-}
-
-void * PMAPI VF_init(ulong baseAddr,int bankSize,int codeLen,void *bankFunc)
-{
- (void)baseAddr;
- (void)bankSize;
- (void)codeLen;
- (void)bankFunc;
- return NULL;
-}
-
-void PMAPI VF_exit(void)
-{
-}
-
-#endif
diff --git a/board/MAI/bios_emulator/scitech/src/pm/dos/ztimer.c b/board/MAI/bios_emulator/scitech/src/pm/dos/ztimer.c
deleted file mode 100644
index 53ab16cf40..0000000000
--- a/board/MAI/bios_emulator/scitech/src/pm/dos/ztimer.c
+++ /dev/null
@@ -1,111 +0,0 @@
-/****************************************************************************
-*
-* Ultra Long Period Timer
-*
-* ========================================================================
-*
-* The contents of this file are subject to the SciTech MGL Public
-* License Version 1.0 (the "License"); you may not use this file
-* except in compliance with the License. You may obtain a copy of
-* the License at http://www.scitechsoft.com/mgl-license.txt
-*
-* Software distributed under the License is distributed on an
-* "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
-* implied. See the License for the specific language governing
-* rights and limitations under the License.
-*
-* The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
-*
-* The Initial Developer of the Original Code is SciTech Software, Inc.
-* All Rights Reserved.
-*
-* ========================================================================
-*
-* Language: ANSI C
-* Environment: MSDOS
-*
-* Description: OS specific implementation for the Zen Timer functions.
-*
-****************************************************************************/
-
-
-/*---------------------------- Global variables ---------------------------*/
-
-uchar * _VARAPI _ZTimerBIOSPtr;
-
-/*----------------------------- Implementation ----------------------------*/
-
-/* External assembler functions */
-
-void _ASMAPI LZ_timerOn(void);
-ulong _ASMAPI LZ_timerLap(void);
-void _ASMAPI LZ_timerOff(void);
-ulong _ASMAPI LZ_timerCount(void);
-void _ASMAPI LZ_disable(void);
-void _ASMAPI LZ_enable(void);
-
-/****************************************************************************
-REMARKS:
-Initialise the Zen Timer module internals.
-****************************************************************************/
-void __ZTimerInit(void)
-{
- _ZTimerBIOSPtr = PM_getBIOSPointer();
-}
-
-/****************************************************************************
-REMARKS:
-Call the assembler Zen Timer functions to do the timing.
-****************************************************************************/
-#define __LZTimerOn(tm) LZ_timerOn()
-
-/****************************************************************************
-REMARKS:
-Call the assembler Zen Timer functions to do the timing.
-****************************************************************************/
-#define __LZTimerLap(tm) LZ_timerLap()
-
-/****************************************************************************
-REMARKS:
-Call the assembler Zen Timer functions to do the timing.
-****************************************************************************/
-#define __LZTimerOff(tm) LZ_timerOff()
-
-/****************************************************************************
-REMARKS:
-Call the assembler Zen Timer functions to do the timing.
-****************************************************************************/
-#define __LZTimerCount(tm) LZ_timerCount()
-
-/****************************************************************************
-REMARKS:
-Define the resolution of the long period timer as microseconds per timer tick.
-****************************************************************************/
-#define ULZTIMER_RESOLUTION 54925
-
-/****************************************************************************
-REMARKS:
-Read the Long Period timer value from the BIOS timer tick.
-****************************************************************************/
-static ulong __ULZReadTime(void)
-{
- ulong ticks;
- LZ_disable(); /* Turn of interrupts */
- ticks = PM_getLong(_ZTimerBIOSPtr+0x6C);
- LZ_enable(); /* Turn on interrupts again */
- return ticks;
-}
-
-/****************************************************************************
-REMARKS:
-Compute the elapsed time from the BIOS timer tick. Note that we check to see
-whether a midnight boundary has passed, and if so adjust the finish time to
-account for this. We cannot detect if more that one midnight boundary has
-passed, so if this happens we will be generating erronous results.
-****************************************************************************/
-ulong __ULZElapsedTime(ulong start,ulong finish)
-{
- if (finish < start)
- finish += 1573040L; /* Number of ticks in 24 hours */
- return finish - start;
-}
OpenPOWER on IntegriCloud