Makefiles: create NASMOPT variable
[syslinux.git] / bcopy32.inc
blob4eef874d10b8262ebf66a6b451802124b93e6d92
1 ;; -----------------------------------------------------------------------
2 ;;
3 ;;   Copyright 1994-2007 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 (-1 means do bzero rather than bcopy)
62 ;       EDI     - target pointer
63 ;       ECX     - byte count
64 ;       DF      - zero
66 ; Outputs:
67 ;       ESI     - first byte after source (garbage if ESI == -1 on entry)
68 ;       EDI     - first byte after target
69 ;       ECX     - zero
71 bcopy:          push eax
72                 push ebx
73                 push esi
74                 push edi
75                 push ecx
76                 pushf                   ; Saves, among others, the IF flag
77                 push ds
78                 push es
79                 push fs
80                 push gs
82                 cli
83                 call enable_a20
85                 mov bx,ss               ; Save the stack segment value!
87                 o32 lgdt [cs:bcopy_gdt]
88                 mov eax,cr0
89                 or al,1
90                 mov cr0,eax             ; Enter protected mode
91                 jmp 08h:.in_pm
93 .in_pm:         mov ax,10h              ; Data segment selector
94                 mov es,ax
95                 mov ds,ax
97                 ; Set ss, fs, and gs, in case we're on a virtual machine
98                 ; running on Intel VT hardware -- it can't deal with a
99                 ; partial transition, for no good reason.  However,
100                 ; ss is NOT zero in general, so we have to preserve
101                 ; the value.
103                 mov ax,18h              ; Real-mode-like segment
104                 mov fs,ax
105                 mov gs,ax
106                 mov ss,ax
108                 cmp esi,-1
109                 je .bzero
111                 cmp esi,edi             ; If source > destination, we might
112                 ja .reverse             ; have to copy backwards
114 .forward:
115                 mov al,cl               ; Save low bits
116                 and al,3
117                 shr ecx,2               ; Convert to dwords
118                 a32 rep movsd           ; Do our business
119                 ; At this point ecx == 0
121                 mov cl,al               ; Copy any fractional dword
122                 a32 rep movsb
123                 jmp .exit
125 .reverse:
126                 std                     ; Reverse copy
127                 lea esi,[esi+ecx-1]     ; Point to final byte
128                 lea edi,[edi+ecx-1]
129                 mov eax,ecx
130                 and ecx,3
131                 shr eax,2
132                 a32 rep movsb
134                 ; Change ESI/EDI to point to the last dword, instead
135                 ; of the last byte.
136                 sub esi,3
137                 sub edi,3
138                 mov ecx,eax
139                 a32 rep movsd
141                 cld
142                 jmp .exit
144 .bzero:
145                 xor eax,eax
146                 mov si,cx               ; Save low bits
147                 and si,3
148                 shr ecx,2
149                 a32 rep stosd
151                 mov cx,si               ; Write fractional dword
152                 a32 rep stosb
153                 ; jmp .exit
155 .exit:
156                 mov ax,18h              ; "Real-mode-like" data segment
157                 mov es,ax
158                 mov ds,ax
160                 mov eax,cr0
161                 and al,~1
162                 mov cr0,eax             ; Disable protected mode
163                 jmp 0:.in_rm
165 .in_rm:         ; Back in real mode
166                 mov ss,bx
167                 pop gs
168                 pop fs
169                 pop es
170                 pop ds
171                 call disable_a20
173                 popf                    ; Re-enables interrupts
174                 pop eax
175                 pop edi
176                 pop esi
177                 add edi,eax
178                 add esi,eax
179                 pop ebx
180                 pop eax
181                 ret
184 ; Routines to enable and disable (yuck) A20.  These routines are gathered
185 ; from tips from a couple of sources, including the Linux kernel and
186 ; http://www.x86.org/.  The need for the delay to be as large as given here
187 ; is indicated by Donnie Barnes of RedHat, the problematic system being an
188 ; IBM ThinkPad 760EL.
190 ; We typically toggle A20 twice for every 64K transferred.
192 %define io_delay        call _io_delay
193 %define IO_DELAY_PORT   80h             ; Invalid port (we hope!)
194 %define disable_wait    32              ; How long to wait for a disable
196 ; Note the skip of 2 here
197 %define A20_DUNNO       0               ; A20 type unknown
198 %define A20_NONE        2               ; A20 always on?
199 %define A20_BIOS        4               ; A20 BIOS enable
200 %define A20_KBC         6               ; A20 through KBC
201 %define A20_FAST        8               ; A20 through port 92h
203 slow_out:       out dx, al              ; Fall through
205 _io_delay:      out IO_DELAY_PORT,al
206                 out IO_DELAY_PORT,al
207                 ret
209 enable_a20:
210                 pushad
211                 mov byte [cs:A20Tries],255 ; Times to try to make this work
213 try_enable_a20:
215 ; Flush the caches
217 %if DO_WBINVD
218                 call try_wbinvd
219 %endif
222 ; If the A20 type is known, jump straight to type
224                 mov bp,[cs:A20Type]
225                 jmp word [cs:bp+A20List]
228 ; First, see if we are on a system with no A20 gate
230 a20_dunno:
231 a20_none:
232                 mov byte [cs:A20Type], A20_NONE
233                 call a20_test
234                 jnz a20_done
237 ; Next, try the BIOS (INT 15h AX=2401h)
239 a20_bios:
240                 mov byte [cs:A20Type], A20_BIOS
241                 mov ax,2401h
242                 pushf                           ; Some BIOSes muck with IF
243                 int 15h
244                 popf
246                 call a20_test
247                 jnz a20_done
250 ; Enable the keyboard controller A20 gate
252 a20_kbc:
253                 mov dl, 1                       ; Allow early exit
254                 call empty_8042
255                 jnz a20_done                    ; A20 live, no need to use KBC
257                 mov byte [cs:A20Type], A20_KBC  ; Starting KBC command sequence
259                 mov al,0D1h                     ; Command write
260                 out 064h, al
261                 call empty_8042_uncond
263                 mov al,0DFh                     ; A20 on
264                 out 060h, al
265                 call empty_8042_uncond
267                 ; Verify that A20 actually is enabled.  Do that by
268                 ; observing a word in low memory and the same word in
269                 ; the HMA until they are no longer coherent.  Note that
270                 ; we don't do the same check in the disable case, because
271                 ; we don't want to *require* A20 masking (SYSLINUX should
272                 ; work fine without it, if the BIOS does.)
273 .kbc_wait:      push cx
274                 xor cx,cx
275 .kbc_wait_loop:
276                 call a20_test
277                 jnz a20_done_pop
278                 loop .kbc_wait_loop
280                 pop cx
282 ; Running out of options here.  Final attempt: enable the "fast A20 gate"
284 a20_fast:
285                 mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
286                 in al, 092h
287                 or al,02h
288                 and al,~01h                     ; Don't accidentally reset the machine!
289                 out 092h, al
291 .fast_wait:     push cx
292                 xor cx,cx
293 .fast_wait_loop:
294                 call a20_test
295                 jnz a20_done_pop
296                 loop .fast_wait_loop
298                 pop cx
301 ; Oh bugger.  A20 is not responding.  Try frobbing it again; eventually give up
302 ; and report failure to the user.
306                 dec byte [cs:A20Tries]
307                 jnz try_enable_a20
309                 mov si, err_a20
310                 jmp abort_load
312                 section .data
313 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
314                 section .bcopy32
317 ; A20 unmasked, proceed...
319 a20_done_pop:   pop cx
320 a20_done:       popad
321                 ret
324 ; This routine tests if A20 is enabled (ZF = 0).  This routine
325 ; must not destroy any register contents.
327 a20_test:
328                 push es
329                 push cx
330                 push ax
331                 mov cx,0FFFFh           ; HMA = segment 0FFFFh
332                 mov es,cx
333                 mov cx,32               ; Loop count
334                 mov ax,[cs:A20Test]
335 .a20_wait:      inc ax
336                 mov [cs:A20Test],ax
337                 io_delay                ; Serialize, and fix delay
338                 cmp ax,[es:A20Test+10h]
339                 loopz .a20_wait
340 .a20_done:      pop ax
341                 pop cx
342                 pop es
343                 ret
345 disable_a20:
346                 pushad
348 ; Flush the caches
350 %if DO_WBINVD
351                 call try_wbinvd
352 %endif
354                 mov bp,[cs:A20Type]
355                 jmp word [cs:bp+A20DList]
357 a20d_bios:
358                 mov ax,2400h
359                 pushf                           ; Some BIOSes muck with IF
360                 int 15h
361                 popf
362                 jmp short a20d_snooze
365 ; Disable the "fast A20 gate"
367 a20d_fast:
368                 in al, 092h
369                 and al,~03h
370                 out 092h, al
371                 jmp short a20d_snooze
374 ; Disable the keyboard controller A20 gate
376 a20d_kbc:
377                 call empty_8042_uncond
378                 mov al,0D1h
379                 out 064h, al            ; Command write
380                 call empty_8042_uncond
381                 mov al,0DDh             ; A20 off
382                 out 060h, al
383                 call empty_8042_uncond
384                 ; Wait a bit for it to take effect
385 a20d_snooze:
386                 push cx
387                 mov cx, disable_wait
388 .delayloop:     call a20_test
389                 jz .disabled
390                 loop .delayloop
391 .disabled:      pop cx
392 a20d_dunno:
393 a20d_none:
394                 popad
395                 ret
398 ; Routine to empty the 8042 KBC controller.  If dl != 0
399 ; then we will test A20 in the loop and exit if A20 is
400 ; suddenly enabled.
402 empty_8042_uncond:
403                 xor dl,dl
404 empty_8042:
405                 call a20_test
406                 jz .a20_on
407                 and dl,dl
408                 jnz .done
409 .a20_on:        io_delay
410                 in al, 064h             ; Status port
411                 test al,1
412                 jz .no_output
413                 io_delay
414                 in al, 060h             ; Read input
415                 jmp short empty_8042
416 .no_output:
417                 test al,2
418                 jnz empty_8042
419                 io_delay
420 .done:          ret
423 ; Execute a WBINVD instruction if possible on this CPU
425 %if DO_WBINVD
426 try_wbinvd:
427                 wbinvd
428                 ret
429 %endif
432 ; shuffle_and_boot:
434 ; This routine is used to shuffle memory around, followed by
435 ; invoking an entry point somewhere in low memory.  This routine
436 ; can clobber any memory above 7C00h, we therefore have to move
437 ; necessary code into the trackbuf area before doing the copy,
438 ; and do adjustments to anything except BSS area references.
440 ; NOTE: Since PXELINUX relocates itself, put all these
441 ; references in the ".earlybss" segment.
443 ; After performing the copy, this routine resets the stack and
444 ; jumps to the specified entrypoint.
446 ; IMPORTANT: This routine does not canonicalize the stack or the
447 ; SS register.  That is the responsibility of the caller.
449 ; Inputs:
450 ;       DS:BX           -> Pointer to list of (dst, src, len) pairs(*)
451 ;       AX              -> Number of list entries
452 ;       [CS:EntryPoint] -> CS:IP to jump to
453 ;       On stack        - initial state (fd, ad, ds, es, fs, gs)
455 ; (*) If dst == -1, then (src, len) entry refers to a set of new
456 ;                   descriptors to load.
457 ;     If src == -1, then the memory pointed to by (dst, len) is bzeroed;
458 ;                   this is handled inside the bcopy routine.
460 shuffle_and_boot:
461 .restart:
462                 and ax,ax
463                 jz .done
464 .loop:
465                 mov edi,[bx]
466                 mov esi,[bx+4]
467                 mov ecx,[bx+8]
468                 cmp edi, -1
469                 je .reload
470                 call bcopy
471                 add bx,12
472                 dec ax
473                 jnz .loop
475 .done:
476                 pop gs
477                 pop fs
478                 pop es
479                 pop ds
480                 popad
481                 popfd
482                 jmp far [cs:EntryPoint]
484 .reload:
485                 mov bx, trackbuf        ; Next descriptor
486                 movzx edi,bx
487                 push ecx                ; Save byte count
488                 call bcopy
489                 pop eax                 ; Byte count
490                 xor edx,edx
491                 mov ecx,12
492                 div ecx                 ; Convert to descriptor count
493                 jmp .restart
496 ; trampoline_to_pm:
498 ; This routine is chained to from shuffle_and_boot to invoke a
499 ; flat 32-bit protected mode operating system.
501 trampoline_to_pm:
502                 cli
503                 call enable_a20
504                 o32 lgdt [cs:bcopy_gdt]
505                 mov eax,cr0
506                 or al,1
507                 mov cr0,eax             ; Enter protected mode
508                 mov ax,28h              ; 32-bit data segment selector
509                 mov es,ax
510                 mov ds,ax
511                 mov ss,ax
512                 mov fs,ax
513                 mov gs,ax
514                 jmp 020h:TrampolineBuf  ; 20h = 32-bit code segment
516                 align 2
517 A20List         dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
518 A20DList        dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
519 a20_adjust_cnt  equ ($-A20List)/2
521 A20Type         dw A20_NONE             ; A20 type
523                 ; Total size of .bcopy32 section
524                 alignb 4, db 0          ; Even number of dwords
525 __bcopy_size    equ $-__bcopy_start
527                 section .earlybss
528                 alignb 2
529 EntryPoint      resd 1                  ; CS:IP for shuffle_and_boot
530 A20Test         resw 1                  ; Counter for testing status of A20
531 A20Tries        resb 1                  ; Times until giving up on A20
534 ; This buffer contains synthesized code for shuffle-and-boot.
535 ; For the PM case, it is 9*5 = 45 bytes long; for the RM case it is
536 ; 8*6 to set the GPRs, 6*5 to set the segment registers (including a dummy
537 ; setting of CS), 5 bytes to set CS:IP, for a total of 83 bytes.
538 TrampolineBuf   resb 83                 ; Shuffle and boot trampoline