isolinux: protect bss variables clobbered due to final sector load
[syslinux.git] / bcopy32.inc
blob4df5e435de5428fdc5bb5444313501ae284394c9
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 ; GDT descriptor entry
41 %macro desc 1
42 bcopy_gdt.%1:
43 PM_%1           equ bcopy_gdt.%1-bcopy_gdt
44 %endmacro
46 bcopy_gdt:
47                 dw bcopy_gdt_size-1     ; Null descriptor - contains GDT
48                 dd bcopy_gdt            ; pointer for LGDT instruction
49                 dw 0
51         desc CS16
52                 dd 0000ffffh            ; 08h Code segment, use16, readable,
53                 dd 00009b00h            ; present, dpl 0, cover 64K
54         desc DS16_4G
55                 dd 0000ffffh            ; 10h Data segment, use16, read/write,
56                 dd 008f9300h            ; present, dpl 0, cover all 4G
57         desc DS16_RM
58                 dd 0000ffffh            ; 18h Data segment, use16, read/write,
59                 dd 00009300h            ; present, dpl 0, cover 64K
60                 ; The next two segments are used for COM32 only
61         desc CS32
62                 dd 0000ffffh            ; 20h Code segment, use32, readable,
63                 dd 00cf9b00h            ; present, dpl 0, cover all 4G
64         desc DS32
65                 dd 0000ffffh            ; 28h Data segment, use32, read/write,
66                 dd 00cf9300h            ; present, dpl 0, cover all 4G
68                 ; TSS segment to keep Intel VT happy.  Intel VT is
69                 ; unhappy about anything that doesn't smell like a
70                 ; full-blown 32-bit OS.
71         desc TSS
72                 dw 104-1, DummyTSS      ; 30h 32-bit task state segment
73                 dd 00008900h            ; present, dpl 0, 104 bytes @DummyTSS
74 bcopy_gdt_size: equ $-bcopy_gdt
77 ; bcopy:
78 ;       32-bit copy, overlap safe
80 ; Inputs:
81 ;       ESI     - source pointer (-1 means do bzero rather than bcopy)
82 ;       EDI     - target pointer
83 ;       ECX     - byte count
84 ;       DF      - zero
86 ; Outputs:
87 ;       ESI     - first byte after source (garbage if ESI == -1 on entry)
88 ;       EDI     - first byte after target
89 ;       ECX     - zero
91 bcopy:          push eax
92                 push ebx
93                 push esi
94                 push edi
95                 push ecx
96                 pushf                   ; Saves, among others, the IF flag
97                 push ds
98                 push es
99                 push fs
100                 push gs
102                 cli
103                 call enable_a20
105                 mov byte [bcopy_gdt.TSS+5],89h  ; Mark TSS unbusy
107                 mov bx,ss               ; Save the stack segment value!
109                 o32 lgdt [cs:bcopy_gdt]
110                 mov eax,cr0
111                 or al,1
112                 mov cr0,eax             ; Enter protected mode
113                 jmp PM_CS16:.in_pm
115 .in_pm:         mov ax,PM_DS16_4G       ; Data segment selector
116                 mov es,ax
117                 mov ds,ax
119                 ; Set ss, fs, and gs, in case we're on a virtual machine
120                 ; running on Intel VT hardware -- it can't deal with a
121                 ; partial transition, for no good reason.  However,
122                 ; ss is NOT zero in general, so we have to preserve
123                 ; the value.
125                 mov al,PM_DS16_RM       ; Real-mode-like segment
126                 mov fs,ax
127                 mov gs,ax
128                 mov ss,ax
130                 mov al,PM_TSS           ; Intel VT really doesn't want
131                 ltr ax                  ; an invalid TR and LDTR, so give
132                 xor ax,ax               ; it something that it can use...
133                 lldt ax                 ; (sigh)
135                 cmp esi,-1
136                 je .bzero
138                 cmp esi,edi             ; If source > destination, we might
139                 ja .reverse             ; have to copy backwards
141 .forward:
142                 mov al,cl               ; Save low bits
143                 and al,3
144                 shr ecx,2               ; Convert to dwords
145                 a32 rep movsd           ; Do our business
146                 ; At this point ecx == 0
148                 mov cl,al               ; Copy any fractional dword
149                 a32 rep movsb
150                 jmp .exit
152 .reverse:
153                 std                     ; Reverse copy
154                 lea esi,[esi+ecx-1]     ; Point to final byte
155                 lea edi,[edi+ecx-1]
156                 mov eax,ecx
157                 and ecx,3
158                 shr eax,2
159                 a32 rep movsb
161                 ; Change ESI/EDI to point to the last dword, instead
162                 ; of the last byte.
163                 sub esi,3
164                 sub edi,3
165                 mov ecx,eax
166                 a32 rep movsd
168                 cld
169                 jmp .exit
171 .bzero:
172                 xor eax,eax
173                 mov si,cx               ; Save low bits
174                 and si,3
175                 shr ecx,2
176                 a32 rep stosd
178                 mov cx,si               ; Write fractional dword
179                 a32 rep stosb
180                 ; jmp .exit
182 .exit:
183                 mov ax,PM_DS16_RM       ; "Real-mode-like" data segment
184                 mov es,ax
185                 mov ds,ax
187                 mov eax,cr0
188                 and al,~1
189                 mov cr0,eax             ; Disable protected mode
190                 jmp 0:.in_rm
192 .in_rm:         ; Back in real mode
193                 mov ss,bx
194                 pop gs
195                 pop fs
196                 pop es
197                 pop ds
198                 call disable_a20
200                 popf                    ; Re-enables interrupts
201                 pop eax
202                 pop edi
203                 pop esi
204                 add edi,eax
205                 add esi,eax
206                 pop ebx
207                 pop eax
208                 ret
211 ; Routines to enable and disable (yuck) A20.  These routines are gathered
212 ; from tips from a couple of sources, including the Linux kernel and
213 ; http://www.x86.org/.  The need for the delay to be as large as given here
214 ; is indicated by Donnie Barnes of RedHat, the problematic system being an
215 ; IBM ThinkPad 760EL.
217 ; We typically toggle A20 twice for every 64K transferred.
219 %define io_delay        call _io_delay
220 %define IO_DELAY_PORT   80h             ; Invalid port (we hope!)
221 %define disable_wait    32              ; How long to wait for a disable
223 ; Note the skip of 2 here
224 %define A20_DUNNO       0               ; A20 type unknown
225 %define A20_NONE        2               ; A20 always on?
226 %define A20_BIOS        4               ; A20 BIOS enable
227 %define A20_KBC         6               ; A20 through KBC
228 %define A20_FAST        8               ; A20 through port 92h
230 slow_out:       out dx, al              ; Fall through
232 _io_delay:      out IO_DELAY_PORT,al
233                 out IO_DELAY_PORT,al
234                 ret
236 enable_a20:
237                 pushad
238                 mov byte [cs:A20Tries],255 ; Times to try to make this work
240 try_enable_a20:
242 ; Flush the caches
244 %if DO_WBINVD
245                 call try_wbinvd
246 %endif
249 ; If the A20 type is known, jump straight to type
251                 mov bp,[cs:A20Type]
252                 jmp word [cs:bp+A20List]
255 ; First, see if we are on a system with no A20 gate
257 a20_dunno:
258 a20_none:
259                 mov byte [cs:A20Type], A20_NONE
260                 call a20_test
261                 jnz a20_done
264 ; Next, try the BIOS (INT 15h AX=2401h)
266 a20_bios:
267                 mov byte [cs:A20Type], A20_BIOS
268                 mov ax,2401h
269                 pushf                           ; Some BIOSes muck with IF
270                 int 15h
271                 popf
273                 call a20_test
274                 jnz a20_done
277 ; Enable the keyboard controller A20 gate
279 a20_kbc:
280                 mov dl, 1                       ; Allow early exit
281                 call empty_8042
282                 jnz a20_done                    ; A20 live, no need to use KBC
284                 mov byte [cs:A20Type], A20_KBC  ; Starting KBC command sequence
286                 mov al,0D1h                     ; Command write
287                 out 064h, al
288                 call empty_8042_uncond
290                 mov al,0DFh                     ; A20 on
291                 out 060h, al
292                 call empty_8042_uncond
294                 ; Verify that A20 actually is enabled.  Do that by
295                 ; observing a word in low memory and the same word in
296                 ; the HMA until they are no longer coherent.  Note that
297                 ; we don't do the same check in the disable case, because
298                 ; we don't want to *require* A20 masking (SYSLINUX should
299                 ; work fine without it, if the BIOS does.)
300 .kbc_wait:      push cx
301                 xor cx,cx
302 .kbc_wait_loop:
303                 call a20_test
304                 jnz a20_done_pop
305                 loop .kbc_wait_loop
307                 pop cx
309 ; Running out of options here.  Final attempt: enable the "fast A20 gate"
311 a20_fast:
312                 mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
313                 in al, 092h
314                 or al,02h
315                 and al,~01h                     ; Don't accidentally reset the machine!
316                 out 092h, al
318 .fast_wait:     push cx
319                 xor cx,cx
320 .fast_wait_loop:
321                 call a20_test
322                 jnz a20_done_pop
323                 loop .fast_wait_loop
325                 pop cx
328 ; Oh bugger.  A20 is not responding.  Try frobbing it again; eventually give up
329 ; and report failure to the user.
333                 dec byte [cs:A20Tries]
334                 jnz try_enable_a20
336                 mov si, err_a20
337                 jmp abort_load
339                 section .data
340 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
341                 section .bcopy32
344 ; A20 unmasked, proceed...
346 a20_done_pop:   pop cx
347 a20_done:       popad
348                 ret
351 ; This routine tests if A20 is enabled (ZF = 0).  This routine
352 ; must not destroy any register contents.
354 a20_test:
355                 push es
356                 push cx
357                 push ax
358                 mov cx,0FFFFh           ; HMA = segment 0FFFFh
359                 mov es,cx
360                 mov cx,32               ; Loop count
361                 mov ax,[cs:A20Test]
362 .a20_wait:      inc ax
363                 mov [cs:A20Test],ax
364                 io_delay                ; Serialize, and fix delay
365                 cmp ax,[es:A20Test+10h]
366                 loopz .a20_wait
367 .a20_done:      pop ax
368                 pop cx
369                 pop es
370                 ret
372 disable_a20:
373                 pushad
375 ; Flush the caches
377 %if DO_WBINVD
378                 call try_wbinvd
379 %endif
381                 mov bp,[cs:A20Type]
382                 jmp word [cs:bp+A20DList]
384 a20d_bios:
385                 mov ax,2400h
386                 pushf                           ; Some BIOSes muck with IF
387                 int 15h
388                 popf
389                 jmp short a20d_snooze
392 ; Disable the "fast A20 gate"
394 a20d_fast:
395                 in al, 092h
396                 and al,~03h
397                 out 092h, al
398                 jmp short a20d_snooze
401 ; Disable the keyboard controller A20 gate
403 a20d_kbc:
404                 call empty_8042_uncond
405                 mov al,0D1h
406                 out 064h, al            ; Command write
407                 call empty_8042_uncond
408                 mov al,0DDh             ; A20 off
409                 out 060h, al
410                 call empty_8042_uncond
411                 ; Wait a bit for it to take effect
412 a20d_snooze:
413                 push cx
414                 mov cx, disable_wait
415 .delayloop:     call a20_test
416                 jz .disabled
417                 loop .delayloop
418 .disabled:      pop cx
419 a20d_dunno:
420 a20d_none:
421                 popad
422                 ret
425 ; Routine to empty the 8042 KBC controller.  If dl != 0
426 ; then we will test A20 in the loop and exit if A20 is
427 ; suddenly enabled.
429 empty_8042_uncond:
430                 xor dl,dl
431 empty_8042:
432                 call a20_test
433                 jz .a20_on
434                 and dl,dl
435                 jnz .done
436 .a20_on:        io_delay
437                 in al, 064h             ; Status port
438                 test al,1
439                 jz .no_output
440                 io_delay
441                 in al, 060h             ; Read input
442                 jmp short empty_8042
443 .no_output:
444                 test al,2
445                 jnz empty_8042
446                 io_delay
447 .done:          ret
450 ; Execute a WBINVD instruction if possible on this CPU
452 %if DO_WBINVD
453 try_wbinvd:
454                 wbinvd
455                 ret
456 %endif
459 ; shuffle_and_boot:
461 ; This routine is used to shuffle memory around, followed by
462 ; invoking an entry point somewhere in low memory.  This routine
463 ; can clobber any memory above 7C00h, we therefore have to move
464 ; necessary code into the trackbuf area before doing the copy,
465 ; and do adjustments to anything except BSS area references.
467 ; NOTE: Since PXELINUX relocates itself, put all these
468 ; references in the ".earlybss" segment.
470 ; After performing the copy, this routine resets the stack and
471 ; jumps to the specified entrypoint.
473 ; IMPORTANT: This routine does not canonicalize the stack or the
474 ; SS register.  That is the responsibility of the caller.
476 ; Inputs:
477 ;       DS:BX           -> Pointer to list of (dst, src, len) pairs(*)
478 ;       AX              -> Number of list entries
479 ;       [CS:EntryPoint] -> CS:IP to jump to
480 ;       On stack        - initial state (fd, ad, ds, es, fs, gs)
482 ; (*) If dst == -1, then (src, len) entry refers to a set of new
483 ;                   descriptors to load.
484 ;     If src == -1, then the memory pointed to by (dst, len) is bzeroed;
485 ;                   this is handled inside the bcopy routine.
487 shuffle_and_boot:
488 .restart:
489                 and ax,ax
490                 jz .done
491 .loop:
492                 mov edi,[bx]
493                 mov esi,[bx+4]
494                 mov ecx,[bx+8]
495                 cmp edi, -1
496                 je .reload
497                 call bcopy
498                 add bx,12
499                 dec ax
500                 jnz .loop
502 .done:
503                 pop gs
504                 pop fs
505                 pop es
506                 pop ds
507                 popad
508                 popfd
509                 jmp far [cs:EntryPoint]
511 .reload:
512                 mov bx, trackbuf        ; Next descriptor
513                 movzx edi,bx
514                 push ecx                ; Save byte count
515                 call bcopy
516                 pop eax                 ; Byte count
517                 xor edx,edx
518                 mov ecx,12
519                 div ecx                 ; Convert to descriptor count
520                 jmp .restart
523 ; trampoline_to_pm:
525 ; This routine is chained to from shuffle_and_boot to invoke a
526 ; flat 32-bit protected mode operating system.
528 trampoline_to_pm:
529                 cli
530                 call enable_a20
531                 o32 lgdt [cs:bcopy_gdt]
532                 mov eax,cr0
533                 or al,1
534                 mov cr0,eax             ; Enter protected mode
535                 jmp .next               ; Near jump to synchronize on 386/486
536 .next:          mov ax,PM_DS32          ; 32-bit data segment selector
537                 mov es,ax
538                 mov ds,ax
539                 mov ss,ax
540                 mov fs,ax
541                 mov gs,ax
542                 jmp PM_CS32:TrampolineBuf
544                 align 2
545 A20List         dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
546 A20DList        dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
547 a20_adjust_cnt  equ ($-A20List)/2
549 A20Type         dw A20_NONE             ; A20 type
551                 ; Total size of .bcopy32 section
552                 alignb 4, db 0          ; Even number of dwords
553 __bcopy_size    equ $-__bcopy_start
555                 section .earlybss
556                 alignb 2
557 EntryPoint      resd 1                  ; CS:IP for shuffle_and_boot
558 A20Test         resw 1                  ; Counter for testing status of A20
559 A20Tries        resb 1                  ; Times until giving up on A20
562 ; This buffer contains synthesized code for shuffle-and-boot.
563 ; For the PM case, it is 9*5 = 45 bytes long; for the RM case it is
564 ; 8*6 to set the GPRs, 6*5 to set the segment registers (including a dummy
565 ; setting of CS), 5 bytes to set CS:IP, for a total of 83 bytes.
567 TrampolineBuf   resb 83                 ; Shuffle and boot trampoline
570 ; Space for a dummy task state segment.  It should never be actually
571 ; accessed, but just in case it is, point to a chunk of memory not used
572 ; for anything real.
574                 alignb 4
575 DummyTSS        resb 104