Allow specifying * instead of any of the MENU COLOR fields.
[syslinux.git] / bcopy32.inc
blobd98785c49f0dd63491c211816d393b4725f7da82
1 ;; -----------------------------------------------------------------------
2 ;;
3 ;;   Copyright 1994-2005 H. Peter Anvin - All Rights Reserved
4 ;;
5 ;;   This program is free software; you can redistribute it and/or modify
6 ;;   it under the terms of the GNU General Public License as published by
7 ;;   the Free Software Foundation, Inc., 53 Temple Place Ste 330,
8 ;;   Boston MA 02111-1307, USA; either version 2 of the License, or
9 ;;   (at your option) any later version; incorporated herein by reference.
11 ;; -----------------------------------------------------------------------
14 ;; bcopy32.inc
16 ;; 32-bit bcopy routine for real mode
20 ; 32-bit bcopy routine for real mode
22 ; We enter protected mode, set up a flat 32-bit environment, run rep movsd
23 ; and then exit.  IMPORTANT: This code assumes cs == 0.
25 ; This code is probably excessively anal-retentive in its handling of
26 ; segments, but this stuff is painful enough as it is without having to rely
27 ; on everything happening "as it ought to."
29 ; NOTE: this code is relocated into low memory, just after the .earlybss
30 ; segment, in order to support to "bcopy over self" operation.
33                 section .bcopy32
34                 align 8
35 __bcopy_start:
37                 ; This is in the .text segment since it needs to be
38                 ; contiguous with the rest of the bcopy stuff
40 bcopy_gdt:      dw bcopy_gdt_size-1     ; Null descriptor - contains GDT
41                 dd bcopy_gdt            ; pointer for LGDT instruction
42                 dw 0
43                 dd 0000ffffh            ; Code segment, use16, readable,
44                 dd 00009b00h            ; present, dpl 0, cover 64K
45                 dd 0000ffffh            ; Data segment, use16, read/write,
46                 dd 008f9300h            ; present, dpl 0, cover all 4G
47                 dd 0000ffffh            ; Data segment, use16, read/write,
48                 dd 00009300h            ; present, dpl 0, cover 64K
49                 ; The rest are used for COM32 only
50                 dd 0000ffffh            ; Code segment, use32, readable,
51                 dd 00cf9b00h            ; present, dpl 0, cover all 4G
52                 dd 0000ffffh            ; Data segment, use32, read/write,
53                 dd 00cf9300h            ; present, dpl 0, cover all 4G
54 bcopy_gdt_size: equ $-bcopy_gdt
57 ; bcopy:
58 ;       32-bit copy, overlap safe
60 ; Inputs:
61 ;       ESI     - source pointer
62 ;       EDI     - target pointer
63 ;       ECX     - byte count
64 ;       DF      - zero
66 ; Outputs:
67 ;       ESI     - first byte after source
68 ;       EDI     - first byte after target
69 ;       ECX     - zero
71 bcopy:          push eax
72                 push esi
73                 push edi
74                 push ecx
75                 pushf                   ; Saves, among others, the IF flag
76                 push ds
77                 push es
79                 cli
80                 call enable_a20
82                 o32 lgdt [cs:bcopy_gdt]
83                 mov eax,cr0
84                 or al,1
85                 mov cr0,eax             ; Enter protected mode
86                 jmp 08h:.in_pm
88 .in_pm:         mov ax,10h              ; Data segment selector
89                 mov es,ax
90                 mov ds,ax
92                 ; Don't mess with ss, fs, and gs.  They are never changed
93                 ; and should be able to make it back out of protected mode.
94                 ; This works because (and only because) we don't take
95                 ; interrupt in protected mode.
97                 cmp esi,edi             ; If source > destination, we might
98                 ja .reverse             ; have to copy backwards
100 .forward:
101                 mov al,cl               ; Save low bits
102                 and al,3
103                 shr ecx,2               ; Convert to dwords
104                 a32 rep movsd           ; Do our business
105                 ; At this point ecx == 0
107                 mov cl,al               ; Copy any fractional dword
108                 a32 rep movsb
109                 jmp .exit
111 .reverse:
112                 std                     ; Reverse copy
113                 lea esi,[esi+ecx-1]     ; Point to final byte
114                 lea edi,[edi+ecx-1]
115                 mov eax,ecx
116                 and ecx,3
117                 shr eax,2
118                 a32 rep movsb
120                 ; Change ESI/EDI to point to the last dword, instead
121                 ; of the last byte.
122                 sub esi,3
123                 sub edi,3
124                 mov ecx,eax
125                 a32 rep movsd
127                 cld
129 .exit:
130                 mov ax,18h              ; "Real-mode-like" data segment
131                 mov es,ax
132                 mov ds,ax
134                 mov eax,cr0
135                 and al,~1
136                 mov cr0,eax             ; Disable protected mode
137                 jmp 0:.in_rm
139 .in_rm:         ; Back in real mode
140                 pop es
141                 pop ds
142                 call disable_a20
144                 popf                    ; Re-enables interrupts
145                 pop eax
146                 pop edi
147                 pop esi
148                 add edi,eax
149                 add esi,eax
150                 pop eax
151                 ret
154 ; Routines to enable and disable (yuck) A20.  These routines are gathered
155 ; from tips from a couple of sources, including the Linux kernel and
156 ; http://www.x86.org/.  The need for the delay to be as large as given here
157 ; is indicated by Donnie Barnes of RedHat, the problematic system being an
158 ; IBM ThinkPad 760EL.
160 ; We typically toggle A20 twice for every 64K transferred.
162 %define io_delay        call _io_delay
163 %define IO_DELAY_PORT   80h             ; Invalid port (we hope!)
164 %define disable_wait    32              ; How long to wait for a disable
166 ; Note the skip of 2 here
167 %define A20_DUNNO       0               ; A20 type unknown
168 %define A20_NONE        2               ; A20 always on?
169 %define A20_BIOS        4               ; A20 BIOS enable
170 %define A20_KBC         6               ; A20 through KBC
171 %define A20_FAST        8               ; A20 through port 92h
173 slow_out:       out dx, al              ; Fall through
175 _io_delay:      out IO_DELAY_PORT,al
176                 out IO_DELAY_PORT,al
177                 ret
179 enable_a20:
180                 pushad
181                 mov byte [cs:A20Tries],255 ; Times to try to make this work
183 try_enable_a20:
185 ; Flush the caches
187 %if DO_WBINVD
188                 call try_wbinvd
189 %endif
192 ; If the A20 type is known, jump straight to type
194                 mov bp,[cs:A20Type]
195                 jmp word [cs:bp+A20List]
198 ; First, see if we are on a system with no A20 gate
200 a20_dunno:
201 a20_none:
202                 mov byte [cs:A20Type], A20_NONE
203                 call a20_test
204                 jnz a20_done
207 ; Next, try the BIOS (INT 15h AX=2401h)
209 a20_bios:
210                 mov byte [cs:A20Type], A20_BIOS
211                 mov ax,2401h
212                 pushf                           ; Some BIOSes muck with IF
213                 int 15h
214                 popf
216                 call a20_test
217                 jnz a20_done
220 ; Enable the keyboard controller A20 gate
222 a20_kbc:
223                 mov dl, 1                       ; Allow early exit
224                 call empty_8042
225                 jnz a20_done                    ; A20 live, no need to use KBC
227                 mov byte [cs:A20Type], A20_KBC  ; Starting KBC command sequence
229                 mov al,0D1h                     ; Command write
230                 out 064h, al
231                 call empty_8042_uncond
233                 mov al,0DFh                     ; A20 on
234                 out 060h, al
235                 call empty_8042_uncond
237                 ; Verify that A20 actually is enabled.  Do that by
238                 ; observing a word in low memory and the same word in
239                 ; the HMA until they are no longer coherent.  Note that
240                 ; we don't do the same check in the disable case, because
241                 ; we don't want to *require* A20 masking (SYSLINUX should
242                 ; work fine without it, if the BIOS does.)
243 .kbc_wait:      push cx
244                 xor cx,cx
245 .kbc_wait_loop:
246                 call a20_test
247                 jnz a20_done_pop
248                 loop .kbc_wait_loop
250                 pop cx
252 ; Running out of options here.  Final attempt: enable the "fast A20 gate"
254 a20_fast:
255                 mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
256                 in al, 092h
257                 or al,02h
258                 and al,~01h                     ; Don't accidentally reset the machine!
259                 out 092h, al
261 .fast_wait:     push cx
262                 xor cx,cx
263 .fast_wait_loop:
264                 call a20_test
265                 jnz a20_done_pop
266                 loop .fast_wait_loop
268                 pop cx
271 ; Oh bugger.  A20 is not responding.  Try frobbing it again; eventually give up
272 ; and report failure to the user.
276                 dec byte [cs:A20Tries]
277                 jnz try_enable_a20
279                 mov si, err_a20
280                 jmp abort_load
282 ; A20 unmasked, proceed...
284 a20_done_pop:   pop cx
285 a20_done:       popad
286                 ret
289 ; This routine tests if A20 is enabled (ZF = 0).  This routine
290 ; must not destroy any register contents.
292 a20_test:
293                 push es
294                 push cx
295                 push ax
296                 mov cx,0FFFFh           ; HMA = segment 0FFFFh
297                 mov es,cx
298                 mov cx,32               ; Loop count
299                 mov ax,[cs:A20Test]
300 .a20_wait:      inc ax
301                 mov [cs:A20Test],ax
302                 io_delay                ; Serialize, and fix delay
303                 cmp ax,[es:A20Test+10h]
304                 loopz .a20_wait
305 .a20_done:      pop ax
306                 pop cx
307                 pop es
308                 ret
310 disable_a20:
311                 pushad
313 ; Flush the caches
315 %if DO_WBINVD
316                 call try_wbinvd
317 %endif
319                 mov bp,[cs:A20Type]
320                 jmp word [cs:bp+A20DList]
322 a20d_bios:
323                 mov ax,2400h
324                 pushf                           ; Some BIOSes muck with IF
325                 int 15h
326                 popf
327                 jmp short a20d_snooze
330 ; Disable the "fast A20 gate"
332 a20d_fast:
333                 in al, 092h
334                 and al,~03h
335                 out 092h, al
336                 jmp short a20d_snooze
339 ; Disable the keyboard controller A20 gate
341 a20d_kbc:
342                 call empty_8042_uncond
343                 mov al,0D1h
344                 out 064h, al            ; Command write
345                 call empty_8042_uncond
346                 mov al,0DDh             ; A20 off
347                 out 060h, al
348                 call empty_8042_uncond
349                 ; Wait a bit for it to take effect
350 a20d_snooze:
351                 push cx
352                 mov cx, disable_wait
353 .delayloop:     call a20_test
354                 jz .disabled
355                 loop .delayloop
356 .disabled:      pop cx
357 a20d_dunno:
358 a20d_none:
359                 popad
360                 ret
363 ; Routine to empty the 8042 KBC controller.  If dl != 0
364 ; then we will test A20 in the loop and exit if A20 is
365 ; suddenly enabled.
367 empty_8042_uncond:
368                 xor dl,dl
369 empty_8042:
370                 call a20_test
371                 jz .a20_on
372                 and dl,dl
373                 jnz .done
374 .a20_on:        io_delay
375                 in al, 064h             ; Status port
376                 test al,1
377                 jz .no_output
378                 io_delay
379                 in al, 060h             ; Read input
380                 jmp short empty_8042
381 .no_output:
382                 test al,2
383                 jnz empty_8042
384                 io_delay
385 .done:          ret
388 ; Execute a WBINVD instruction if possible on this CPU
390 %if DO_WBINVD
391 try_wbinvd:
392                 wbinvd
393                 ret
394 %endif
397 ; bcopy_over_self:
399 ; This routine is used to shuffle memory around, followed by
400 ; invoking an entry point somewhere in low memory.  This routine
401 ; can clobber any memory above 7C00h, we therefore have to move
402 ; necessary code into the trackbuf area before doing the copy,
403 ; and do adjustments to anything except BSS area references.
405 ; NOTE: Since PXELINUX relocates itself, put all these
406 ; references in the ".earlybss" segment.
408 ; After performing the copy, this routine resets the stack and
409 ; jumps to the specified entrypoint.
411 ; IMPORTANT: This routine does not canonicalize the stack or the
412 ; SS register.  That is the responsibility of the caller.
414 ; Inputs:
415 ;       DS:BX           -> Pointer to list of (dst, src, len) pairs
416 ;       AX              -> Number of list entries
417 ;       [CS:EntryPoint] -> CS:IP to jump to
418 ;       On stack        - initial state (fd, ad, ds, es, fs, gs)
420 shuffle_and_boot:
421                 and ax,ax
422                 jz .done
423 .loop:
424                 mov edi,[bx]
425                 mov esi,[bx+4]
426                 mov ecx,[bx+8]
427                 call bcopy
428                 add bx,12
429                 dec ax
430                 jnz .loop
432 .done:
433                 pop gs
434                 pop fs
435                 pop es
436                 pop ds
437                 popad
438                 popfd
439                 jmp far [cs:EntryPoint]
441                 align 2
442 A20List         dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
443 A20DList        dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
444 a20_adjust_cnt  equ ($-A20List)/2
446 A20Type         dw A20_NONE             ; A20 type
448                 ; Total size of .bcopy32 section
449                 alignb 4, db 0          ; Even number of dwords
450 __bcopy_size    equ $-__bcopy_start
452                 section .earlybss
453                 alignb 2
454 EntryPoint      resd 1                  ; CS:IP for shuffle_and_boot
455 A20Test         resw 1                  ; Counter for testing status of A20
456 A20Tries        resb 1                  ; Times until giving up on A20