]> git.kernelconcepts.de Git - karo-tx-uboot.git/blob - board/MAI/bios_emulator/scitech/src/pm/dos/_pm.asm
* Patch by Thomas Frieden, 13 Nov 2002:
[karo-tx-uboot.git] / board / MAI / bios_emulator / scitech / src / pm / dos / _pm.asm
1 ;****************************************************************************
2 ;*
3 ;*                  SciTech OS Portability Manager Library
4 ;*
5 ;*  ========================================================================
6 ;*
7 ;*    The contents of this file are subject to the SciTech MGL Public
8 ;*    License Version 1.0 (the "License"); you may not use this file
9 ;*    except in compliance with the License. You may obtain a copy of
10 ;*    the License at http://www.scitechsoft.com/mgl-license.txt
11 ;*
12 ;*    Software distributed under the License is distributed on an
13 ;*    "AS IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or
14 ;*    implied. See the License for the specific language governing
15 ;*    rights and limitations under the License.
16 ;*
17 ;*    The Original Code is Copyright (C) 1991-1998 SciTech Software, Inc.
18 ;*
19 ;*    The Initial Developer of the Original Code is SciTech Software, Inc.
20 ;*    All Rights Reserved.
21 ;*
22 ;*  ========================================================================
23 ;*
24 ;* Language:    80386 Assembler, TASM 4.0 or NASM
25 ;* Environment: IBM PC Real mode and 16/32 bit protected mode
26 ;*
27 ;* Description: Low level assembly support for the PM library specific to
28 ;*              MSDOS.
29 ;*
30 ;****************************************************************************
31
32         IDEAL
33
34 include "scitech.mac"               ; Memory model macros
35
36 header      _pmdos                  ; Set up memory model
37
38 begdataseg  _pmdos
39
40 ifndef  flatmodel
41
42 struc   rmregs_s
43 ax          dw  ?
44 ax_high     dw  ?
45 bx          dw  ?
46 bx_high     dw  ?
47 cx          dw  ?
48 cx_high     dw  ?
49 dx          dw  ?
50 dx_high     dw  ?
51 si          dw  ?
52 si_high     dw  ?
53 di          dw  ?
54 di_high     dw  ?
55 cflag       dw  ?
56 cflag_high  dw  ?
57 ends    rmregs_s
58 RMREGS  = (rmregs_s PTR es:bx)
59
60 struc   rmsregs_s
61 es      dw  ?
62 cs      dw  ?
63 ss      dw  ?
64 ds      dw  ?
65 ends    rmsregs_s
66 RMSREGS = (rmsregs_s PTR es:bx)
67
68 endif   ; !flatmodel
69
70 ifdef flatmodel
71     cextern _PM_savedDS,USHORT
72     cextern _PM_VXD_off,UINT
73     cextern _PM_VXD_sel,UINT
74 ifdef   DOS4GW
75     cextern _PM_haveCauseWay,UINT
76 endif
77 endif
78 intel_id        db  "GenuineIntel"  ; Intel vendor ID
79
80 PMHELP_GETPDB       EQU 0026h
81 PMHELP_FLUSHTLB     EQU 0027h
82
83 enddataseg  _pmdos
84
85 P586
86
87 begcodeseg  _pmdos                  ; Start of code segment
88
89 ifndef  flatmodel
90
91 ;----------------------------------------------------------------------------
92 ; void PM_callRealMode(unsigned s,unsigned o, RMREGS *regs,
93 ;   RMSREGS *sregs)
94 ;----------------------------------------------------------------------------
95 ; Calls a real mode procedure, loading the appropriate registers values
96 ; from the passed in structures. Only the DS and ES register are loaded
97 ; from the SREGS structure.
98 ;----------------------------------------------------------------------------
99 cprocstart  PM_callRealMode
100
101         ARG     s:WORD, o:WORD, regs:DWORD, sregs:DWORD
102
103         LOCAL   addr:DWORD, bxVal:WORD, esVal:WORD, flags:WORD = LocalSize
104
105         enter_c
106         push    ds
107         push    es
108
109         mov     ax,[o]              ; Build the address to call in 'addr'
110         mov     [WORD addr],ax
111         mov     ax,[s]
112         mov     [WORD addr+2],ax
113
114         les     bx,[sregs]
115         mov     ax,[RMSREGS.ds]
116         mov     ds,ax               ; DS := passed in value
117         mov     ax,[RMSREGS.es]
118         mov     [esVal],ax
119         les     bx,[regs]
120         mov     ax,[RMREGS.bx]
121         mov     [bxVal],ax
122         mov     ax,[RMREGS.ax]      ; AX := passed in value
123         mov     cx,[RMREGS.cx]      ; CX := passed in value
124         mov     dx,[RMREGS.dx]      ; DX := passed in value
125         mov     si,[RMREGS.si]      ; SI := passed in value
126         mov     di,[RMREGS.di]      ; DI := passed in value
127         push    bp
128         push    [esVal]
129         pop     es                  ; ES := passed in value
130         mov     bx,[bxVal]          ; BX := passed in value
131
132         call    [addr]              ; Call the specified routine
133
134         pushf                       ; Save flags for later
135         pop     [flags]
136
137         pop     bp
138         push    es
139         pop     [esVal]
140         push    bx
141         pop     [bxVal]
142         les     bx,[sregs]
143         push    ds
144         pop     [RMSREGS.ds]        ; Save value of DS
145         push    [esVal]
146         pop     [RMSREGS.es]        ; Save value of ES
147         les     bx,[regs]
148         mov     [RMREGS.ax],ax      ; Save value of AX
149         mov     [RMREGS.cx],cx      ; Save value of CX
150         mov     [RMREGS.dx],dx      ; Save value of DX
151         mov     [RMREGS.si],si      ; Save value of SI
152         mov     [RMREGS.di],di      ; Save value of DI
153         mov     ax,[flags]          ; Return flags
154         and     ax,1h               ; Isolate carry flag
155         mov     [RMREGS.cflag],ax   ; Save carry flag status
156         mov     ax,[bxVal]
157         mov     [RMREGS.bx],ax      ; Save value of BX
158
159         pop     es
160         pop     ds
161         leave_c
162         ret
163
164 cprocend
165
166 endif
167
168 ;----------------------------------------------------------------------------
169 ; void PM_segread(PMSREGS *sregs)
170 ;----------------------------------------------------------------------------
171 ; Read the current value of all segment registers
172 ;----------------------------------------------------------------------------
173 cprocstartdll16 PM_segread
174
175         ARG     sregs:DPTR
176
177         enter_c
178
179         mov     ax,es
180         _les    _si,[sregs]
181         mov     [_ES _si],ax
182         mov     [_ES _si+2],cs
183         mov     [_ES _si+4],ss
184         mov     [_ES _si+6],ds
185         mov     [_ES _si+8],fs
186         mov     [_ES _si+10],gs
187
188         leave_c
189         ret
190
191 cprocend
192
193 ; Create a table of the 256 different interrupt calls that we can jump
194 ; into
195
196 ifdef   USE_NASM
197
198 %assign intno 0
199
200 intTable:
201 %rep    256
202         db      0CDh
203         db      intno
204 %assign intno   intno + 1
205         ret
206         nop
207 %endrep
208
209 else
210
211 intno = 0
212
213 intTable:
214         REPT    256
215         db      0CDh
216         db      intno
217 intno = intno + 1
218         ret
219         nop
220         ENDM
221
222 endif
223
224 ;----------------------------------------------------------------------------
225 ; _PM_genInt    - Generate the appropriate interrupt
226 ;----------------------------------------------------------------------------
227 cprocnear   _PM_genInt
228
229         push    _ax                     ; Save _ax
230         push    _bx                     ; Save _bx
231 ifdef flatmodel
232         mov     ebx,[UINT esp+12]       ; EBX := interrupt number
233 else
234         mov     bx,sp                   ; Make sure ESP is zeroed
235         mov     bx,[UINT ss:bx+6]       ; BX := interrupt number
236 endif
237         mov     _ax,offset intTable     ; Point to interrupt generation table
238         shl     _bx,2                   ; _BX := index into table
239         add     _ax,_bx                 ; _AX := pointer to interrupt code
240 ifdef flatmodel
241         xchg    eax,[esp+4]             ; Restore eax, and set for int
242 else
243         mov     bx,sp
244         xchg    ax,[ss:bx+2]            ; Restore ax, and set for int
245 endif
246         pop     _bx                     ; restore _bx
247         ret
248
249 cprocend
250
251 ;----------------------------------------------------------------------------
252 ; int PM_int386x(int intno, PMREGS *in, PMREGS *out,PMSREGS *sregs)
253 ;----------------------------------------------------------------------------
254 ; Issues a software interrupt in protected mode. This routine has been
255 ; written to allow user programs to load CS and DS with different values
256 ; other than the default.
257 ;----------------------------------------------------------------------------
258 cprocstartdll16 PM_int386x
259
260         ARG     intno:UINT, inptr:DPTR, outptr:DPTR, sregs:DPTR
261
262         LOCAL   flags:UINT, sv_ds:UINT, sv_esi:ULONG = LocalSize
263
264         enter_c
265         push    ds
266         push    es                  ; Save segment registers
267         push    fs
268         push    gs
269
270         _lds    _si,[sregs]         ; DS:_SI -> Load segment registers
271         mov     es,[_si]
272         mov     bx,[_si+6]
273         mov     [sv_ds],_bx         ; Save value of user DS on stack
274         mov     fs,[_si+8]
275         mov     gs,[_si+10]
276
277         _lds    _si,[inptr]         ; Load CPU registers
278         mov     eax,[_si]
279         mov     ebx,[_si+4]
280         mov     ecx,[_si+8]
281         mov     edx,[_si+12]
282         mov     edi,[_si+20]
283         mov     esi,[_si+16]
284
285         push    ds                  ; Save value of DS
286         push    _bp                 ; Some interrupts trash this!
287         clc                         ; Generate the interrupt
288         push    [UINT intno]
289         mov     ds,[WORD sv_ds]     ; Set value of user's DS selector
290         call    _PM_genInt
291         pop     _bp                 ; Pop intno from stack (flags unchanged)
292         pop     _bp                 ; Restore value of stack frame pointer
293         pop     ds                  ; Restore value of DS
294
295         pushf                       ; Save flags for later
296         pop     [UINT flags]
297         push    esi                 ; Save ESI for later
298         pop     [DWORD sv_esi]
299         push    ds                  ; Save DS for later
300         pop     [UINT sv_ds]
301
302         _lds    _si,[outptr]        ; Save CPU registers
303         mov     [_si],eax
304         mov     [_si+4],ebx
305         mov     [_si+8],ecx
306         mov     [_si+12],edx
307         push    [DWORD sv_esi]
308         pop     [DWORD _si+16]
309         mov     [_si+20],edi
310
311         mov     _bx,[flags]         ; Return flags
312         and     ebx,1h              ; Isolate carry flag
313         mov     [_si+24],ebx        ; Save carry flag status
314
315         _lds    _si,[sregs]         ; Save segment registers
316         mov     [_si],es
317         mov     _bx,[sv_ds]
318         mov     [_si+6],bx          ; Get returned DS from stack
319         mov     [_si+8],fs
320         mov     [_si+10],gs
321
322         pop     gs                  ; Restore segment registers
323         pop     fs
324         pop     es
325         pop     ds
326         leave_c
327         ret
328
329 cprocend
330
331 ifndef flatmodel
332 _PM_savedDS     dw  _DATA           ; Saved value of DS
333 endif
334
335 ;----------------------------------------------------------------------------
336 ; void PM_saveDS(void)
337 ;----------------------------------------------------------------------------
338 ; Save the value of DS into a section of the code segment, so that we can
339 ; quickly load this value at a later date in the PM_loadDS() routine from
340 ; inside interrupt handlers etc. The method to do this is different
341 ; depending on the DOS extender being used.
342 ;----------------------------------------------------------------------------
343 cprocstartdll16 PM_saveDS
344
345 ifdef flatmodel
346         mov     [_PM_savedDS],ds    ; Store away in data segment
347 endif
348         ret
349
350 cprocend
351
352 ;----------------------------------------------------------------------------
353 ; void PM_loadDS(void)
354 ;----------------------------------------------------------------------------
355 ; Routine to load the DS register with the default value for the current
356 ; DOS extender. Only the DS register is loaded, not the ES register, so
357 ; if you wish to call C code, you will need to also load the ES register
358 ; in 32 bit protected mode.
359 ;----------------------------------------------------------------------------
360 cprocstartdll16 PM_loadDS
361
362         mov     ds,[cs:_PM_savedDS] ; We can access the proper DS through CS
363         ret
364
365 cprocend
366
367 ifdef flatmodel
368
369 ;----------------------------------------------------------------------------
370 ; ibool DPMI_allocateCallback(void (*pmcode)(), void *rmregs, long *RMCB)
371 ;----------------------------------------------------------------------------
372 cprocstart  _DPMI_allocateCallback
373
374         ARG     pmcode:CPTR, rmregs:DPTR, RMCB:DPTR
375
376         enter_c
377         push    ds
378         push    es
379
380         push    cs
381         pop     ds
382         mov     esi,[pmcode]    ; DS:ESI -> protected mode code to call
383         mov     edi,[rmregs]    ; ES:EDI -> real mode register buffer
384         mov     ax,303h         ; AX := allocate realmode callback function
385         int     31h
386         mov     eax,0           ; Return failure!
387         jc      @@Fail
388
389         mov     eax,[RMCB]
390         shl     ecx,16
391         mov     cx,dx
392         mov     [es:eax],ecx    ; Return real mode address
393         mov     eax,1           ; Return success!
394
395 @@Fail: pop     es
396         pop     ds
397         leave_c
398         ret
399
400 cprocend
401
402 ;----------------------------------------------------------------------------
403 ; void DPMI_freeCallback(long RMCB)
404 ;----------------------------------------------------------------------------
405 cprocstart  _DPMI_freeCallback
406
407         ARG     RMCB:ULONG
408
409         enter_c
410
411         mov     cx,[WORD RMCB+2]
412         mov     dx,[WORD RMCB]  ; CX:DX := real mode callback
413         mov     ax,304h
414         int     31h
415
416         leave_c
417         ret
418
419 cprocend
420
421 endif
422
423 ; Macro to delay briefly to ensure that enough time has elapsed between
424 ; successive I/O accesses so that the device being accessed can respond
425 ; to both accesses even on a very fast PC.
426
427 ifdef   USE_NASM
428 %macro  DELAY 0
429         jmp     short $+2
430         jmp     short $+2
431         jmp     short $+2
432 %endmacro
433 %macro  IODELAYN 1
434 %rep    %1
435         DELAY
436 %endrep
437 %endmacro
438 else
439 macro   DELAY
440         jmp     short $+2
441         jmp     short $+2
442         jmp     short $+2
443 endm
444 macro   IODELAYN    N
445     rept    N
446         DELAY
447     endm
448 endm
449 endif
450
451 ;----------------------------------------------------------------------------
452 ; uchar _PM_readCMOS(int index)
453 ;----------------------------------------------------------------------------
454 ; Read the value of a specific CMOS register. We do this with both
455 ; normal interrupts and NMI disabled.
456 ;----------------------------------------------------------------------------
457 cprocstart  _PM_readCMOS
458
459         ARG     index:UINT
460
461         push    _bp
462         mov     _bp,_sp
463         pushfd
464         mov     al,[BYTE index]
465         or      al,80h              ; Add disable NMI flag
466         cli
467         out     70h,al
468         IODELAYN 5
469         in      al,71h
470         mov     ah,al
471         xor     al,al
472         IODELAYN 5
473         out     70h,al              ; Re-enable NMI
474         sti
475         mov     al,ah               ; Return value in AL
476         popfd
477         pop     _bp
478         ret
479
480 cprocend
481
482 ;----------------------------------------------------------------------------
483 ; void _PM_writeCMOS(int index,uchar value)
484 ;----------------------------------------------------------------------------
485 ; Read the value of a specific CMOS register. We do this with both
486 ; normal interrupts and NMI disabled.
487 ;----------------------------------------------------------------------------
488 cprocstart  _PM_writeCMOS
489
490         ARG     index:UINT, value:UCHAR
491
492         push    _bp
493         mov     _bp,_sp
494         pushfd
495         mov     al,[BYTE index]
496         or      al,80h              ; Add disable NMI flag
497         cli
498         out     70h,al
499         IODELAYN 5
500         mov     al,[value]
501         out     71h,al
502         xor     al,al
503         IODELAYN 5
504         out     70h,al              ; Re-enable NMI
505         sti
506         popfd
507         pop     _bp
508         ret
509
510 cprocend
511
512 ifdef   flatmodel
513
514 ;----------------------------------------------------------------------------
515 ; int _PM_pagingEnabled(void)
516 ;----------------------------------------------------------------------------
517 ; Returns 1 if paging is enabled, 0 if not or -1 if not at ring 0
518 ;----------------------------------------------------------------------------
519 cprocstart  _PM_pagingEnabled
520
521         mov     eax,-1
522 ifdef   DOS4GW
523         mov     cx,cs
524         and     ecx,3
525         jz      @@Ring0
526         cmp     [UINT _PM_haveCauseWay],0
527         jnz     @@Ring0
528         jmp     @@Exit
529
530 @@Ring0:
531         mov     eax,cr0                 ; Load CR0
532         shr     eax,31                  ; Isolate paging enabled bit
533 endif
534 @@Exit: ret
535
536 cprocend
537
538 ;----------------------------------------------------------------------------
539 ; _PM_getPDB - Return the Page Table Directory Base address
540 ;----------------------------------------------------------------------------
541 cprocstart  _PM_getPDB
542
543 ifdef   DOS4GW
544         mov     ax,cs
545         and     eax,3
546         jz      @@Ring0
547         cmp     [UINT _PM_haveCauseWay],0
548         jnz     @@Ring0
549 endif
550
551 ; Call VxD if running at ring 3 in a DOS box
552
553         cmp     [WORD _PM_VXD_sel],0
554         jz      @@Fail
555         mov     eax,PMHELP_GETPDB
556 ifdef   USE_NASM
557         call    far dword [_PM_VXD_off]
558 else
559         call    [FCPTR _PM_VXD_off]
560 endif
561         ret
562
563 @@Ring0:
564 ifdef   DOS4GW
565         mov     eax,cr3
566         and     eax,0FFFFF000h
567         ret
568 endif
569 @@Fail: xor     eax,eax
570         ret
571
572 cprocend
573
574 ;----------------------------------------------------------------------------
575 ; PM_flushTLB - Flush the Translation Lookaside buffer
576 ;----------------------------------------------------------------------------
577 cprocstart  PM_flushTLB
578
579         mov     ax,cs
580         and     eax,3
581         jz      @@Ring0
582 ifdef   DOS4GW
583         cmp     [UINT _PM_haveCauseWay],0
584         jnz     @@Ring0
585 endif
586
587 ; Call VxD if running at ring 3 in a DOS box
588
589         cmp     [WORD _PM_VXD_sel],0
590         jz      @@Fail
591         mov     eax,PMHELP_FLUSHTLB
592 ifdef   USE_NASM
593         call    far dword [_PM_VXD_off]
594 else
595         call    [FCPTR _PM_VXD_off]
596 endif
597         ret
598
599 @@Ring0:
600 ifdef   DOS4GW
601         wbinvd                  ; Flush the CPU cache
602         mov     eax,cr3
603         mov     cr3,eax         ; Flush the TLB
604 endif
605 @@Fail: ret
606
607 cprocend
608
609 endif
610
611 ;----------------------------------------------------------------------------
612 ; void _PM_VxDCall(VXD_regs far *r,uint off,uint sel);
613 ;----------------------------------------------------------------------------
614 cprocstart  _PM_VxDCall
615
616         ARG     r:DPTR, off:UINT, sel:UINT
617
618         enter_c
619
620 ; Load all registers from the registers structure
621
622         mov     ebx,[r]
623         mov     eax,[ebx+0]
624         mov     ecx,[ebx+8]
625         mov     edx,[ebx+12]
626         mov     esi,[ebx+16]
627         mov     edi,[ebx+20]
628         mov     ebx,[ebx+4]         ; Trashes BX structure pointer!
629
630 ; Call the VxD entry point (on stack)
631
632 ifdef   USE_NASM
633         call far dword [off]
634 else
635         call    [FCPTR off]
636 endif
637
638 ; Save all registers back in the structure
639
640         push    ebx                 ; Push EBX onto stack for later
641         mov     ebx,[r]
642         mov     [ebx+0],eax
643         mov     [ebx+8],ecx
644         mov     [ebx+12],edx
645         mov     [ebx+16],esi
646         mov     [ebx+20],edi
647         pop     [DWORD ebx+4]       ; Save value of EBX from stack
648
649         leave_c
650         ret
651
652 cprocend
653
654 endcodeseg  _pmdos
655
656         END                     ; End of module