]> git.kernelconcepts.de Git - karo-tx-uboot.git/blob - board/MAI/bios_emulator/scitech/src/pm/smx/_pm.asm
* Patch by Thomas Frieden, 13 Nov 2002:
[karo-tx-uboot.git] / board / MAI / bios_emulator / scitech / src / pm / smx / _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: 32-bit SMX embedded systems development
26 ;*
27 ;* Description: Low level assembly support for the PM library specific to
28 ;*              SMX.
29 ;*
30 ;****************************************************************************
31
32         IDEAL
33
34 include "scitech.mac"               ; Memory model macros
35
36 header      _pm                     ; Set up memory model
37
38 begdataseg  _pm
39
40     cextern _PM_savedDS,USHORT
41
42 intel_id        db  "GenuineIntel"  ; Intel vendor ID
43
44 enddataseg  _pm
45
46 begcodeseg  _pm                 ; Start of code segment
47
48 ;----------------------------------------------------------------------------
49 ; void PM_segread(PMSREGS *sregs)
50 ;----------------------------------------------------------------------------
51 ; Read the current value of all segment registers
52 ;----------------------------------------------------------------------------
53 cprocstartdll16 PM_segread
54
55         ARG     sregs:DPTR
56
57         enter_c
58
59         mov     ax,es
60         _les    _si,[sregs]
61         mov     [_ES _si],ax
62         mov     [_ES _si+2],cs
63         mov     [_ES _si+4],ss
64         mov     [_ES _si+6],ds
65         mov     [_ES _si+8],fs
66         mov     [_ES _si+10],gs
67
68         leave_c
69         ret
70
71 cprocend
72
73 ; Create a table of the 256 different interrupt calls that we can jump
74 ; into
75
76 ifdef   USE_NASM
77
78 %assign intno 0
79
80 intTable:
81 %rep    256
82         db      0CDh
83         db      intno
84 %assign intno   intno + 1
85         ret
86         nop
87 %endrep
88
89 else
90
91 intno = 0
92
93 intTable:
94         REPT    256
95         db      0CDh
96         db      intno
97 intno = intno + 1
98         ret
99         nop
100         ENDM
101
102 endif
103
104 ;----------------------------------------------------------------------------
105 ; _PM_genInt    - Generate the appropriate interrupt
106 ;----------------------------------------------------------------------------
107 cprocnear   _PM_genInt
108
109         push    _ax                     ; Save _ax
110         push    _bx                     ; Save _bx
111         mov     ebx,[UINT esp+12]       ; EBX := interrupt number
112         mov     _ax,offset intTable     ; Point to interrupt generation table
113         shl     _bx,2                   ; _BX := index into table
114         add     _ax,_bx                 ; _AX := pointer to interrupt code
115         xchg    eax,[esp+4]             ; Restore eax, and set for int
116         pop     _bx                     ; restore _bx
117         ret
118
119 cprocend
120
121 ;----------------------------------------------------------------------------
122 ; int PM_int386x(int intno, PMREGS *in, PMREGS *out,PMSREGS *sregs)
123 ;----------------------------------------------------------------------------
124 ; Issues a software interrupt in protected mode. This routine has been
125 ; written to allow user programs to load CS and DS with different values
126 ; other than the default.
127 ;----------------------------------------------------------------------------
128 cprocstartdll16 PM_int386x
129
130         ARG     intno:UINT, inptr:DPTR, outptr:DPTR, sregs:DPTR
131
132         LOCAL   flags:UINT, sv_ds:UINT, sv_esi:ULONG = LocalSize
133
134         enter_c
135         push    ds
136         push    es                  ; Save segment registers
137         push    fs
138         push    gs
139
140         _lds    _si,[sregs]         ; DS:_SI -> Load segment registers
141         mov     es,[_si]
142         mov     bx,[_si+6]
143         mov     [sv_ds],_bx         ; Save value of user DS on stack
144         mov     fs,[_si+8]
145         mov     gs,[_si+10]
146
147         _lds    _si,[inptr]         ; Load CPU registers
148         mov     eax,[_si]
149         mov     ebx,[_si+4]
150         mov     ecx,[_si+8]
151         mov     edx,[_si+12]
152         mov     edi,[_si+20]
153         mov     esi,[_si+16]
154
155         push    ds                  ; Save value of DS
156         push    _bp                 ; Some interrupts trash this!
157         clc                         ; Generate the interrupt
158         push    [UINT intno]
159         mov     ds,[WORD sv_ds]     ; Set value of user's DS selector
160         call    _PM_genInt
161         pop     _bp                 ; Pop intno from stack (flags unchanged)
162         pop     _bp                 ; Restore value of stack frame pointer
163         pop     ds                  ; Restore value of DS
164
165         pushf                       ; Save flags for later
166         pop     [UINT flags]
167         push    esi                 ; Save ESI for later
168         pop     [DWORD sv_esi]
169         push    ds                  ; Save DS for later
170         pop     [UINT sv_ds]
171
172         _lds    _si,[outptr]        ; Save CPU registers
173         mov     [_si],eax
174         mov     [_si+4],ebx
175         mov     [_si+8],ecx
176         mov     [_si+12],edx
177         push    [DWORD sv_esi]
178         pop     [DWORD _si+16]
179         mov     [_si+20],edi
180
181         mov     _bx,[flags]         ; Return flags
182         and     ebx,1h              ; Isolate carry flag
183         mov     [_si+24],ebx        ; Save carry flag status
184
185         _lds    _si,[sregs]         ; Save segment registers
186         mov     [_si],es
187         mov     _bx,[sv_ds]
188         mov     [_si+6],bx          ; Get returned DS from stack
189         mov     [_si+8],fs
190         mov     [_si+10],gs
191
192         pop     gs                  ; Restore segment registers
193         pop     fs
194         pop     es
195         pop     ds
196         leave_c
197         ret
198
199 cprocend
200
201 ;----------------------------------------------------------------------------
202 ; void PM_saveDS(void)
203 ;----------------------------------------------------------------------------
204 ; Save the value of DS into a section of the code segment, so that we can
205 ; quickly load this value at a later date in the PM_loadDS() routine from
206 ; inside interrupt handlers etc. The method to do this is different
207 ; depending on the DOS extender being used.
208 ;----------------------------------------------------------------------------
209 cprocstartdll16 PM_saveDS
210
211         mov     [_PM_savedDS],ds    ; Store away in data segment
212         ret
213
214 cprocend
215
216 ;----------------------------------------------------------------------------
217 ; void PM_loadDS(void)
218 ;----------------------------------------------------------------------------
219 ; Routine to load the DS register with the default value for the current
220 ; DOS extender. Only the DS register is loaded, not the ES register, so
221 ; if you wish to call C code, you will need to also load the ES register
222 ; in 32 bit protected mode.
223 ;----------------------------------------------------------------------------
224 cprocstartdll16 PM_loadDS
225
226         mov     ds,[cs:_PM_savedDS] ; We can access the proper DS through CS
227         ret
228
229 cprocend
230
231 ;----------------------------------------------------------------------------
232 ; void PM_setBankA(int bank)
233 ;----------------------------------------------------------------------------
234 cprocstart      PM_setBankA
235
236         ARG     bank:UINT
237
238         push    ebp
239         mov     ebp,esp
240         push    ebx
241         mov     _bx,0
242         mov     _ax,4F05h
243         mov     _dx,[bank]
244         int     10h
245         pop     ebx
246         pop     ebp
247         ret
248
249 cprocend
250
251 ;----------------------------------------------------------------------------
252 ; void PM_setBankAB(int bank)
253 ;----------------------------------------------------------------------------
254 cprocstart      PM_setBankAB
255
256         ARG     bank:UINT
257
258         push    ebp
259         mov     ebp,esp
260         push    ebx
261         mov     _bx,0
262         mov     _ax,4F05h
263         mov     _dx,[bank]
264         int     10h
265         mov     _bx,1
266         mov     _ax,4F05h
267         mov     _dx,[bank]
268         int     10h
269         pop     ebx
270         pop     ebp
271         ret
272
273 cprocend
274
275 ;----------------------------------------------------------------------------
276 ; void PM_setCRTStart(int x,int y,int waitVRT)
277 ;----------------------------------------------------------------------------
278 cprocstart      PM_setCRTStart
279
280         ARG     x:UINT, y:UINT, waitVRT:UINT
281
282         push    ebp
283         mov     ebp,esp
284         push    ebx
285         mov     _bx,[waitVRT]
286         mov     _cx,[x]
287         mov     _dx,[y]
288         mov     _ax,4F07h
289         int     10h
290         pop     ebx
291         pop     ebp
292         ret
293
294 cprocend
295
296 ;----------------------------------------------------------------------------
297 ; int _PM_inp(int port)
298 ;----------------------------------------------------------------------------
299 ; Reads a byte from the specified port
300 ;----------------------------------------------------------------------------
301 cprocstart  _PM_inp
302
303         ARG     port:UINT
304
305         push    _bp
306         mov     _bp,_sp
307         xor     _ax,_ax
308         mov     _dx,[port]
309         in      al,dx
310         pop     _bp
311         ret
312
313 cprocend
314
315 ;----------------------------------------------------------------------------
316 ; void _PM_outp(int port,int value)
317 ;----------------------------------------------------------------------------
318 ; Write a byte to the specified port.
319 ;----------------------------------------------------------------------------
320 cprocstart  _PM_outp
321
322         ARG     port:UINT, value:UINT
323
324         push    _bp
325         mov     _bp,_sp
326         mov     _dx,[port]
327         mov     _ax,[value]
328         out     dx,al
329         pop     _bp
330         ret
331
332 cprocend
333
334 ; Macro to delay briefly to ensure that enough time has elapsed between
335 ; successive I/O accesses so that the device being accessed can respond
336 ; to both accesses even on a very fast PC.
337
338 ifdef   USE_NASM
339 %macro  DELAY 0
340         jmp     short $+2
341         jmp     short $+2
342         jmp     short $+2
343 %endmacro
344 %macro  IODELAYN 1
345 %rep    %1
346         DELAY
347 %endrep
348 %endmacro
349 else
350 macro   DELAY
351         jmp     short $+2
352         jmp     short $+2
353         jmp     short $+2
354 endm
355 macro   IODELAYN    N
356     rept    N
357         DELAY
358     endm
359 endm
360 endif
361
362 ;----------------------------------------------------------------------------
363 ; uchar _PM_readCMOS(int index)
364 ;----------------------------------------------------------------------------
365 ; Read the value of a specific CMOS register. We do this with both
366 ; normal interrupts and NMI disabled.
367 ;----------------------------------------------------------------------------
368 cprocstart  _PM_readCMOS
369
370         ARG     index:UINT
371
372         push    _bp
373         mov     _bp,_sp
374         pushfd
375         mov     al,[BYTE index]
376         or      al,80h              ; Add disable NMI flag
377         cli
378         out     70h,al
379         IODELAYN 5
380         in      al,71h
381         mov     ah,al
382         xor     al,al
383         IODELAYN 5
384         out     70h,al              ; Re-enable NMI
385         sti
386         mov     al,ah               ; Return value in AL
387         popfd
388         pop     _bp
389         ret
390
391 cprocend
392
393 ;----------------------------------------------------------------------------
394 ; void _PM_writeCMOS(int index,uchar value)
395 ;----------------------------------------------------------------------------
396 ; Read the value of a specific CMOS register. We do this with both
397 ; normal interrupts and NMI disabled.
398 ;----------------------------------------------------------------------------
399 cprocstart  _PM_writeCMOS
400
401         ARG     index:UINT, value:UCHAR
402
403         push    _bp
404         mov     _bp,_sp
405         pushfd
406         mov     al,[BYTE index]
407         or      al,80h              ; Add disable NMI flag
408         cli
409         out     70h,al
410         IODELAYN 5
411         mov     al,[value]
412         out     71h,al
413         xor     al,al
414         IODELAYN 5
415         out     70h,al              ; Re-enable NMI
416         sti
417         popfd
418         pop     _bp
419         ret
420
421 cprocend
422
423 ;----------------------------------------------------------------------------
424 ; _PM_getPDB - Return the Page Table Directory Base address
425 ;----------------------------------------------------------------------------
426 cprocstart  _PM_getPDB
427
428         mov     eax,cr3
429         and     eax,0FFFFF000h
430         ret
431
432 cprocend
433
434 ;----------------------------------------------------------------------------
435 ; _PM_flushTLB - Flush the Translation Lookaside buffer
436 ;----------------------------------------------------------------------------
437 cprocstart  PM_flushTLB
438
439         wbinvd                  ; Flush the CPU cache
440         mov     eax,cr3         
441         mov     cr3,eax         ; Flush the TLB
442         ret
443
444 cprocend
445
446 endcodeseg  _pm
447
448         END                     ; End of module