com32: mark the invalid SEG() as __unlikely()
[syslinux/sherbszt.git] / core / pm.inc
blobc6f3c52bcd9cebe92affa4856ba7bfd2d866908b
1 ;; -----------------------------------------------------------------------
2 ;;
3 ;;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
4 ;;   Copyright 2009 Intel Corporation; author: H. Peter Anvin
5 ;;
6 ;;   This program is free software; you can redistribute it and/or modify
7 ;;   it under the terms of the GNU General Public License as published by
8 ;;   the Free Software Foundation, Inc., 53 Temple Place Ste 330,
9 ;;   Boston MA 02111-1307, USA; either version 2 of the License, or
10 ;;   (at your option) any later version; incorporated herein by reference.
12 ;; -----------------------------------------------------------------------
15 ;; pm.inc
17 ;; Functions to enter and exit 32-bit protected mode, handle interrupts
18 ;; and cross-mode calls.
20 ;; PM refers to 32-bit flat protected mode; RM to 16-bit real mode.
23                 bits 16
24                 section .text16
26 ; _pm_call: call PM routine in low memory from RM
28 ;       on stack        = PM routine to call (a 32-bit address)
30 ;       ECX, ESI, EDI passed to the called function;
31 ;       EAX = EBP in the called function points to the stack frame
32 ;       which includes all registers (which can be changed if desired.)
34 ;       All registers and the flags saved/restored
36 ;       This routine is invoked by the pm_call macro.
38 _pm_call:
39                 pushfd
40                 pushad
41                 push ds
42                 push es
43                 push fs
44                 push gs
45                 mov bp,sp
46                 mov ax,cs
47                 mov ebx,.pm
48                 mov ds,ax
49                 jmp enter_pm
51                 bits 32
52                 section .textnr
53 .pm:
54                 ; EAX points to the top of the RM stack, which is EFLAGS
55                 test RM_FLAGSH,02h              ; RM EFLAGS.IF
56                 jz .no_sti
57                 sti
58 .no_sti:
59                 call [ebp+4*2+9*4+2]            ; Entrypoint on RM stack
60                 mov bx,.rm
61                 jmp enter_rm
63                 bits 16
64                 section .text16
65 .rm:
66                 pop gs
67                 pop fs
68                 pop es
69                 pop ds
70                 popad
71                 popfd
72                 ret 4           ; Drop entrypoint
75 ; enter_pm: Go to PM with interrupt service configured
76 ;       EBX       = PM entry point
77 ;       EAX = EBP = on exit, points to the RM stack as a 32-bit value
78 ;       ECX, EDX, ESI, EDI preserved across this routine
80 ;       Assumes CS == DS
82 ; This routine doesn't enable interrupts, but the target routine
83 ; can enable interrupts by executing STI.
85                 bits 16
86                 section .text16
87 enter_pm:
88                 cli
89                 xor eax,eax
90                 mov ds,ax
91                 mov ax,ss
92                 mov [RealModeSSSP],sp
93                 mov [RealModeSSSP+2],ax
94                 movzx ebp,sp
95                 shl eax,4
96                 add ebp,eax             ; EBP -> top of real-mode stack
97                 cld
98                 call enable_a20
100 .a20ok:
101                 mov byte [bcopy_gdt.TSS+5],89h  ; Mark TSS unbusy
103                 lgdt [bcopy_gdt]        ; We can use the same GDT just fine
104                 lidt [PM_IDT_ptr]       ; Set up the IDT
105                 mov eax,cr0
106                 or al,1
107                 mov cr0,eax             ; Enter protected mode
108                 jmp PM_CS32:.in_pm
110                 bits 32
111                 section .textnr
112 .in_pm:
113                 xor eax,eax             ; Available for future use...
114                 mov fs,eax
115                 mov gs,eax
116                 lldt ax
118                 mov al,PM_DS32          ; Set up data segments
119                 mov es,eax
120                 mov ds,eax
121                 mov ss,eax
123                 mov al,PM_TSS           ; Be nice to Intel's VT by
124                 ltr ax                  ; giving it a valid TR
126                 mov esp,[PMESP]         ; Load protmode %esp
127                 mov eax,ebp             ; EAX -> top of real-mode stack
128                 jmp ebx                 ; Go to where we need to go
131 ; enter_rm: Return to RM from PM
133 ;       BX      = RM entry point (CS = 0)
134 ;       ECX, EDX, ESI, EDI preserved across this routine
135 ;       EAX     clobbered
136 ;       EBP     reserved
138 ; This routine doesn't enable interrupts, but the target routine
139 ; can enable interrupts by executing STI.
141                 bits 32
142                 section .textnr
143 enter_rm:
144                 cli
145                 cld
146                 mov [PMESP],esp         ; Save exit %esp
147                 jmp PM_CS16:.in_pm16    ; Return to 16-bit mode first
149                 bits 16
150                 section .text16
151 .in_pm16:
152                 mov ax,PM_DS16          ; Real-mode-like segment
153                 mov es,ax
154                 mov ds,ax
155                 mov ss,ax
156                 mov fs,ax
157                 mov gs,ax
159                 lidt [RM_IDT_ptr]       ; Real-mode IDT (rm needs no GDT)
160                 xor dx,dx
161                 mov eax,cr0
162                 and al,~1
163                 mov cr0,eax
164                 jmp 0:.in_rm
166 .in_rm:                                 ; Back in real mode
167                 lss sp,[cs:RealModeSSSP]        ; Restore stack
168                 movzx esp,sp            ; Make sure the high bits are zero
169                 mov ds,dx               ; Set up sane segments
170                 mov es,dx
171                 mov fs,dx
172                 mov gs,dx
173                 jmp bx                  ; Go to whereever we need to go...
175                 section .data16
176                 alignz 4
178                 extern __stack_end
179 PMESP           dd __stack_end          ; Protected-mode ESP
181 PM_IDT_ptr:     dw 8*256-1              ; Length
182                 dd IDT                  ; Offset
185 ; This is invoked on getting an interrupt in protected mode.  At
186 ; this point, we need to context-switch to real mode and invoke
187 ; the interrupt routine.
189 ; When this gets invoked, the registers are saved on the stack and
190 ; AL contains the register number.
192                 bits 32
193                 section .textnr
194 pm_irq:
195                 pushad
196                 movzx esi,byte [esp+8*4] ; Interrupt number
197                 mov ebx,.rm
198                 jmp enter_rm            ; Go to real mode
200                 bits 16
201                 section .text16
202 .rm:
203                 pushf                   ; Flags on stack
204                 call far [cs:esi*4]     ; Call IVT entry
205                 mov ebx,.pm
206                 jmp enter_pm            ; Go back to PM
208                 bits 32
209                 section .textnr
210 .pm:
211                 popad
212                 add esp,4               ; Drop interrupt number
213                 iretd
215                 bits 16
216                 section .text16
218 ; Routines to enable and disable (yuck) A20.  These routines are gathered
219 ; from tips from a couple of sources, including the Linux kernel and
220 ; http://www.x86.org/.  The need for the delay to be as large as given here
221 ; is indicated by Donnie Barnes of RedHat, the problematic system being an
222 ; IBM ThinkPad 760EL.
225                 section .data16
226                 alignz 2
227 A20Ptr          dw a20_dunno
229                 section .bss16
230                 alignb 4
231 A20Test         resd 1                  ; Counter for testing A20 status
232 A20Tries        resb 1                  ; Times until giving up on A20
234                 section .text16
235 enable_a20:
236                 pushad
237                 mov byte [cs:A20Tries],255 ; Times to try to make this work
239 try_enable_a20:
242 ; First, see if we are on a system with no A20 gate, or the A20 gate
243 ; is already enabled for us...
245 a20_none:
246                 call a20_test
247                 jnz a20_done
248                 ; Otherwise, see if we had something memorized...
249                 jmp word [cs:A20Ptr]
252 ; Next, try the BIOS (INT 15h AX=2401h)
254 a20_dunno:
255 a20_bios:
256                 mov word [cs:A20Ptr], a20_bios
257                 mov ax,2401h
258                 pushf                           ; Some BIOSes muck with IF
259                 int 15h
260                 popf
262                 call a20_test
263                 jnz a20_done
266 ; Enable the keyboard controller A20 gate
268 a20_kbc:
269                 mov dl, 1                       ; Allow early exit
270                 call empty_8042
271                 jnz a20_done                    ; A20 live, no need to use KBC
273                 mov word [cs:A20Ptr], a20_kbc   ; Starting KBC command sequence
275                 mov al,0D1h                     ; Write output port
276                 out 064h, al
277                 call empty_8042_uncond
279                 mov al,0DFh                     ; A20 on
280                 out 060h, al
281                 call empty_8042_uncond
283                 ; Apparently the UHCI spec assumes that A20 toggle
284                 ; ends with a null command (assumed to be for sychronization?)
285                 ; Put it here to see if it helps anything...
286                 mov al,0FFh                     ; Null command
287                 out 064h, al
288                 call empty_8042_uncond
290                 ; Verify that A20 actually is enabled.  Do that by
291                 ; observing a word in low memory and the same word in
292                 ; the HMA until they are no longer coherent.  Note that
293                 ; we don't do the same check in the disable case, because
294                 ; we don't want to *require* A20 masking (SYSLINUX should
295                 ; work fine without it, if the BIOS does.)
296 .kbc_wait:      push cx
297                 xor cx,cx
298 .kbc_wait_loop:
299                 call a20_test
300                 jnz a20_done_pop
301                 loop .kbc_wait_loop
303                 pop cx
305 ; Running out of options here.  Final attempt: enable the "fast A20 gate"
307 a20_fast:
308                 mov word [cs:A20Ptr], a20_fast
309                 in al, 092h
310                 or al,02h
311                 and al,~01h                     ; Don't accidentally reset the machine!
312                 out 092h, al
314 .fast_wait:     push cx
315                 xor cx,cx
316 .fast_wait_loop:
317                 call a20_test
318                 jnz a20_done_pop
319                 loop .fast_wait_loop
321                 pop cx
324 ; Oh bugger.  A20 is not responding.  Try frobbing it again; eventually give up
325 ; and report failure to the user.
327                 dec byte [cs:A20Tries]
328                 jnz a20_dunno           ; Did we get the wrong type?
330                 mov si, err_a20
331                 pm_call pm_writestr
332                 jmp kaboom
334                 section .data16
335 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
336                 section .text16
339 ; A20 unmasked, proceed...
341 a20_done_pop:   pop cx
342 a20_done:       popad
343                 ret
346 ; This routine tests if A20 is enabled (ZF = 0).  This routine
347 ; must not destroy any register contents.
349 ; The no-write early out avoids the io_delay in the (presumably common)
350 ; case of A20 already enabled (e.g. from a previous call.)
352 a20_test:
353                 push es
354                 push cx
355                 push eax
356                 mov cx,0FFFFh                   ; HMA = segment 0FFFFh
357                 mov es,cx
358                 mov eax,[cs:A20Test]
359                 mov cx,32                       ; Loop count
360                 jmp .test                       ; First iteration = early out
361 .wait:          add eax,0x430aea41              ; A large prime number
362                 mov [cs:A20Test],eax
363                 io_delay                        ; Serialize, and fix delay
364 .test:          cmp eax,[es:A20Test+10h]
365                 loopz .wait
366 .done:          pop eax
367                 pop cx
368                 pop es
369                 ret
372 ; Routine to empty the 8042 KBC controller.  If dl != 0
373 ; then we will test A20 in the loop and exit if A20 is
374 ; suddenly enabled.
376 empty_8042_uncond:
377                 xor dl,dl
378 empty_8042:
379                 call a20_test
380                 jz .a20_on
381                 and dl,dl
382                 jnz .done
383 .a20_on:        io_delay
384                 in al, 064h             ; Status port
385                 test al,1
386                 jz .no_output
387                 io_delay
388                 in al, 060h             ; Read input
389                 jmp short empty_8042
390 .no_output:
391                 test al,2
392                 jnz empty_8042
393                 io_delay
394 .done:          ret
397 ; This initializes the protected-mode interrupt thunk set
399                 section .text16
400 pm_init:
401                 xor edi,edi
402                 mov bx,IDT
403                 mov di,IRQStubs
405                 mov eax,7aeb006ah       ; push byte .. jmp short ..
407                 mov cx,8                ; 8 groups of 32 IRQs
408 .gloop:
409                 push cx
410                 mov cx,32               ; 32 entries per group
411 .eloop:
412                 mov [bx],di             ; IDT offset [15:0]
413                 mov word [bx+2],PM_CS32 ; IDT segment
414                 mov dword [bx+4],08e00h ; IDT offset [31:16], 32-bit interrupt
415                                         ; gate, CPL 0 (we don't have a TSS
416                                         ; set up...)
417                 add bx,8
419                 stosd
420                 ; Increment IRQ, decrement jmp short offset
421                 add eax,(-4 << 24)+(1 << 8)
423                 loop .eloop
425                 ; At the end of each group, replace the EBxx with
426                 ; the final E9xxxxxxxx
427                 add di,3
428                 mov byte [di-5],0E9h    ; JMP NEAR
429                 mov edx,pm_irq
430                 sub edx,edi
431                 mov [di-4],edx
433                 add eax,(0x80 << 24)    ; Proper offset for the next one
434                 pop cx
435                 loop .gloop
437                 ret
439                 ; pm_init is called before bss clearing, so put these
440                 ; in .earlybss!
441                 section .earlybss
442                 alignb 8
443 IDT:            resq 256
444 RealModeSSSP    resd 1                  ; Real-mode SS:SP
446                 section .gentextnr      ; Autogenerated 32-bit code
447 IRQStubs:       resb 4*256+3*8
449                 section .text16
451 %include "callback.inc"                 ; Real-mode callbacks