core: do aligned transfers in bcopy32
[syslinux.git] / core / bcopy32.inc
blob8f36d6487b4ea40d922ccc8821069639f69fa064
1 ;; -----------------------------------------------------------------------
2 ;;
3 ;;   Copyright 1994-2008 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
75                 ; 16-bit stack segment, which may have a different
76                 ; base from DS16 (e.g. if we're booted from PXELINUX)
77         desc SS16
78                 dd 0000ffffh            ; 38h Data segment, use16, read/write,
79                 dd 00009300h            ; present, dpl 0, cover 64K
81 bcopy_gdt_size: equ $-bcopy_gdt
84 ; bcopy:
85 ;       32-bit copy, overlap safe
87 ; Inputs:
88 ;       ESI     - source pointer (-1 means do bzero rather than bcopy)
89 ;       EDI     - target pointer
90 ;       ECX     - byte count
91 ;       DF      - zero
93 ; Outputs:
94 ;       ESI     - first byte after source (garbage if ESI == -1 on entry)
95 ;       EDI     - first byte after target
97 bcopy:          jecxz .ret
98                 pushad
99                 push word pm_bcopy
100                 call simple_pm_call
101                 popad
102                 add edi,ecx
103                 add esi,ecx
104 .ret:           ret
107 ; This routine is used to invoke a simple routine in 16-bit protected
108 ; mode (with 32-bit DS and ES, and working 16-bit stack.)
109 ; Note that all segment registers including CS, except possibly SS,
110 ; are zero-based in the protected-mode routine.
112 ; No interrupt thunking services are provided; interrupts are disabled
113 ; for the duration of the routine.  Don't run for too long at a time.
115 ; Inputs:
116 ;       On stack        - pm entrypoint
117 ;       EAX, EBP preserved until real-mode exit
118 ;       EBX, ECX, EDX, ESI and EDI passed to the called routine
120 ; Outputs:
121 ;       EAX, EBP restored from real-mode entry
122 ;       All other registers as returned from called function
123 ;       PM entrypoint cleaned off stack
125 simple_pm_call:
126                 push eax
127                 push ebp
128                 mov bp,sp
129                 pushfd                  ; Saves, among others, the IF flag
130                 push ds
131                 push es
132                 push fs
133                 push gs
135                 cli
136                 call enable_a20
138                 mov byte [cs:bcopy_gdt.TSS+5],89h       ; Mark TSS unbusy
140                 ; Convert the stack segment to a base
141                 xor eax,eax
142                 mov ax,ss
143                 shl eax,4
144                 or eax,93000000h
145                 mov [cs:bcopy_gdt.SS16+2],eax
147                 push ss                 ; Save real-mode SS selector
149                 o32 lgdt [cs:bcopy_gdt]
150                 mov eax,cr0
151                 or al,1
152                 mov cr0,eax             ; Enter protected mode
153                 jmp PM_CS16:.in_pm
154 .in_pm:
155                 mov ax,PM_SS16          ; Make stack usable
156                 mov ss,ax
158                 mov al,PM_DS16_4G       ; Data segment selector
159                 mov es,ax
160                 mov ds,ax
162                 ; Set fs, gs, tr, and ldtr in case we're on a virtual
163                 ; machine running on Intel VT hardware -- it can't
164                 ; deal with a partial transition, for no good reason.
166                 mov al,PM_DS16_RM       ; Real-mode-like segment
167                 mov fs,ax
168                 mov gs,ax
169                 mov al,PM_TSS           ; Intel VT really doesn't want
170                 ltr ax                  ; an invalid TR and LDTR, so give
171                 xor ax,ax               ; it something that it can use...
172                 lldt ax                 ; (sigh)
174                 call [bp+2*4+2]         ; Call actual routine
176 .exit:
177                 mov ax,PM_DS16_RM       ; "Real-mode-like" data segment
178                 mov es,ax
179                 mov ds,ax
181                 pop bp                  ; Previous value for ss
183                 mov eax,cr0
184                 and al,~1
185                 mov cr0,eax             ; Disable protected mode
186                 jmp 0:.in_rm
188 .in_rm:         ; Back in real mode
189                 mov ss,bp
190                 pop gs
191                 pop fs
192                 pop es
193                 pop ds
194 %if DISABLE_A20
195                 call disable_a20
196 %endif
198                 popfd                   ; Re-enables interrupts
199                 pop ebp
200                 pop eax
201                 ret 2                   ; Drops the pm entry
204 ; pm_bcopy:
206 ;       This is the protected-mode core of the "bcopy" routine.
207 ;       Try to do aligned transfers; if the src and dst are relatively
208 ;       misaligned, align the dst.
210 ;       ECX is guaranteed to not be zero on entry.
212 pm_bcopy:
213                 cmp esi,-1
214                 je .bzero
216                 cmp esi,edi             ; If source < destination, we might
217                 jb .reverse             ; have to copy backwards
219 .forward:
220                 ; Initial alignment
221                 mov dx,di
222                 shr dx,1
223                 jnc .faa1
224                 a32 movsb
225                 dec ecx
226 .faa1:
227                 mov al,cl
228                 cmp ecx,2
229                 jb .f_tiny
231                 shr dx,1
232                 jnc .faa2
233                 a32 movsw
234                 sub ecx,2
235 .faa2:
237                 ; Bulk transfer
238                 mov al,cl               ; Save low bits
239                 shr ecx,2               ; Convert to dwords
240                 a32 rep movsd           ; Do our business
241                 ; At this point ecx == 0
243                 test al,2
244                 jz .fab2
245                 a32 movsw
246 .fab2:
247 .f_tiny:
248                 test al,1
249                 jz .fab1
250                 a32 movsb
251 .fab1:
252                 ret
254 .reverse:
255                 std                     ; Reverse copy
257                 lea esi,[esi+ecx-1]     ; Point to final byte
258                 lea edi,[edi+ecx-1]
260                 ; Initial alignment
261                 mov dx,di
262                 shr dx,1
263                 jnc .raa1
264                 a32 movsb
265                 dec ecx
266 .raa1:
268                 dec esi
269                 dec edi
270                 mov al,cl
271                 cmp ecx,2
272                 jb .r_tiny
273                 shr dx,1
274                 jnc .raa2
275                 a32 movsw
276                 sub ecx,2
277 .raa2:
279                 ; Bulk copy
280                 sub esi,2
281                 sub edi,2
282                 mov al,cl               ; Save low bits
283                 shr ecx,2
284                 a32 rep movsd
286                 ; Final alignment
287 .r_final:
288                 add esi,2
289                 add edi,2
290                 test al,2
291                 jz .rab2
292                 a32 movsw
293 .rab2:
294 .r_tiny:
295                 inc esi
296                 inc edi
297                 test al,1
298                 jz .rab1
299                 a32 movsb
300 .rab1:
301                 cld
302                 ret
304 .bzero:
305                 xor eax,eax
307                 ; Initial alignment
308                 mov dx,di
309                 shr dx,1
310                 jnc .zaa1
311                 a32 stosb
312                 dec ecx
313 .zaa1:
315                 mov bl,cl
316                 cmp ecx,2
317                 jb .z_tiny
318                 shr dx,1
319                 jnc .zaa2
320                 a32 stosw
321                 sub ecx,2
322 .zaa2:
324                 ; Bulk
325                 mov bl,cl               ; Save low bits
326                 shr ecx,2
327                 a32 rep stosd
329                 test bl,2
330                 jz .zab2
331                 a32 stosw
332 .zab2:
333 .z_tiny:
334                 test bl,1
335                 jz .zab1
336                 a32 stosb
337 .zab1:
338                 ret
341 ; Routines to enable and disable (yuck) A20.  These routines are gathered
342 ; from tips from a couple of sources, including the Linux kernel and
343 ; http://www.x86.org/.  The need for the delay to be as large as given here
344 ; is indicated by Donnie Barnes of RedHat, the problematic system being an
345 ; IBM ThinkPad 760EL.
347 ; We typically toggle A20 twice for every 64K transferred.
349 %define io_delay        call _io_delay
350 %define IO_DELAY_PORT   80h             ; Invalid port (we hope!)
351 %define disable_wait    32              ; How long to wait for a disable
353 ; Note the skip of 2 here
354 %define A20_DUNNO       0               ; A20 type unknown
355 %define A20_NONE        2               ; A20 always on?
356 %define A20_BIOS        4               ; A20 BIOS enable
357 %define A20_KBC         6               ; A20 through KBC
358 %define A20_FAST        8               ; A20 through port 92h
360 slow_out:       out dx, al              ; Fall through
362 _io_delay:      out IO_DELAY_PORT,al
363                 out IO_DELAY_PORT,al
364                 ret
366 enable_a20:
367                 pushad
368                 mov byte [cs:A20Tries],255 ; Times to try to make this work
370 try_enable_a20:
372 ; Flush the caches
374 %if DO_WBINVD
375                 call try_wbinvd
376 %endif
379 ; If the A20 type is known, jump straight to type
381                 mov bp,[cs:A20Type]
382                 jmp word [cs:bp+A20List]
385 ; First, see if we are on a system with no A20 gate
387 a20_dunno:
388 a20_none:
389                 mov byte [cs:A20Type], A20_NONE
390                 call a20_test
391                 jnz a20_done
394 ; Next, try the BIOS (INT 15h AX=2401h)
396 a20_bios:
397                 mov byte [cs:A20Type], A20_BIOS
398                 mov ax,2401h
399                 pushf                           ; Some BIOSes muck with IF
400                 int 15h
401                 popf
403                 call a20_test
404                 jnz a20_done
407 ; Enable the keyboard controller A20 gate
409 a20_kbc:
410                 mov dl, 1                       ; Allow early exit
411                 call empty_8042
412                 jnz a20_done                    ; A20 live, no need to use KBC
414                 mov byte [cs:A20Type], A20_KBC  ; Starting KBC command sequence
416                 mov al,0D1h                     ; Command write
417                 out 064h, al
418                 call empty_8042_uncond
420                 mov al,0DFh                     ; A20 on
421                 out 060h, al
422                 call empty_8042_uncond
424                 ; Verify that A20 actually is enabled.  Do that by
425                 ; observing a word in low memory and the same word in
426                 ; the HMA until they are no longer coherent.  Note that
427                 ; we don't do the same check in the disable case, because
428                 ; we don't want to *require* A20 masking (SYSLINUX should
429                 ; work fine without it, if the BIOS does.)
430 .kbc_wait:      push cx
431                 xor cx,cx
432 .kbc_wait_loop:
433                 call a20_test
434                 jnz a20_done_pop
435                 loop .kbc_wait_loop
437                 pop cx
439 ; Running out of options here.  Final attempt: enable the "fast A20 gate"
441 a20_fast:
442                 mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
443                 in al, 092h
444                 or al,02h
445                 and al,~01h                     ; Don't accidentally reset the machine!
446                 out 092h, al
448 .fast_wait:     push cx
449                 xor cx,cx
450 .fast_wait_loop:
451                 call a20_test
452                 jnz a20_done_pop
453                 loop .fast_wait_loop
455                 pop cx
458 ; Oh bugger.  A20 is not responding.  Try frobbing it again; eventually give up
459 ; and report failure to the user.
463                 dec byte [cs:A20Tries]
464                 jnz try_enable_a20
466                 mov si, err_a20
467                 jmp abort_load
469                 section .data
470 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
471                 section .bcopy32
474 ; A20 unmasked, proceed...
476 a20_done_pop:   pop cx
477 a20_done:       popad
478                 ret
481 ; This routine tests if A20 is enabled (ZF = 0).  This routine
482 ; must not destroy any register contents.
484 a20_test:
485                 push es
486                 push cx
487                 push ax
488                 mov cx,0FFFFh           ; HMA = segment 0FFFFh
489                 mov es,cx
490                 mov cx,32               ; Loop count
491                 mov ax,[cs:A20Test]
492 .a20_wait:      inc ax
493                 mov [cs:A20Test],ax
494                 io_delay                ; Serialize, and fix delay
495                 cmp ax,[es:A20Test+10h]
496                 loopz .a20_wait
497 .a20_done:      pop ax
498                 pop cx
499                 pop es
500                 ret
502 %if DISABLE_A20
504 disable_a20:
505                 pushad
507 ; Flush the caches
509 %if DO_WBINVD
510                 call try_wbinvd
511 %endif
513                 mov bp,[cs:A20Type]
514                 jmp word [cs:bp+A20DList]
516 a20d_bios:
517                 mov ax,2400h
518                 pushf                           ; Some BIOSes muck with IF
519                 int 15h
520                 popf
521                 jmp short a20d_snooze
524 ; Disable the "fast A20 gate"
526 a20d_fast:
527                 in al, 092h
528                 and al,~03h
529                 out 092h, al
530                 jmp short a20d_snooze
533 ; Disable the keyboard controller A20 gate
535 a20d_kbc:
536                 call empty_8042_uncond
537                 mov al,0D1h
538                 out 064h, al            ; Command write
539                 call empty_8042_uncond
540                 mov al,0DDh             ; A20 off
541                 out 060h, al
542                 call empty_8042_uncond
543                 ; Wait a bit for it to take effect
544 a20d_snooze:
545                 push cx
546                 mov cx, disable_wait
547 .delayloop:     call a20_test
548                 jz .disabled
549                 loop .delayloop
550 .disabled:      pop cx
551 a20d_dunno:
552 a20d_none:
553                 popad
554                 ret
556 %endif
559 ; Routine to empty the 8042 KBC controller.  If dl != 0
560 ; then we will test A20 in the loop and exit if A20 is
561 ; suddenly enabled.
563 empty_8042_uncond:
564                 xor dl,dl
565 empty_8042:
566                 call a20_test
567                 jz .a20_on
568                 and dl,dl
569                 jnz .done
570 .a20_on:        io_delay
571                 in al, 064h             ; Status port
572                 test al,1
573                 jz .no_output
574                 io_delay
575                 in al, 060h             ; Read input
576                 jmp short empty_8042
577 .no_output:
578                 test al,2
579                 jnz empty_8042
580                 io_delay
581 .done:          ret
584 ; Execute a WBINVD instruction if possible on this CPU
586 %if DO_WBINVD
587 try_wbinvd:
588                 wbinvd
589                 ret
590 %endif
593 ; shuffle_and_boot:
595 ; This routine is used to shuffle memory around, followed by
596 ; invoking an entry point somewhere in low memory.  This routine
597 ; can clobber any memory above 7C00h, we therefore have to move
598 ; necessary code into the trackbuf area before doing the copy,
599 ; and do adjustments to anything except BSS area references.
601 ; NOTE: Since PXELINUX relocates itself, put all these
602 ; references in the ".earlybss" segment.
604 ; After performing the copy, this routine resets the stack and
605 ; jumps to the specified entrypoint.
607 ; IMPORTANT: This routine does not canonicalize the stack or the
608 ; SS register.  That is the responsibility of the caller.
610 ; Inputs:
611 ;       DS:BX           -> Pointer to list of (dst, src, len) pairs(*)
612 ;       AX              -> Number of list entries
613 ;       [CS:EntryPoint] -> CS:IP to jump to
614 ;       On stack        - initial state (fd, ad, ds, es, fs, gs)
616 ; (*) If dst == -1, then (src, len) entry refers to a set of new
617 ;                   descriptors to load.
618 ;     If src == -1, then the memory pointed to by (dst, len) is bzeroed;
619 ;                   this is handled inside the bcopy routine.
621 shuffle_and_boot:
622 .restart:
623                 and ax,ax
624                 jz .done
625 .loop:
626                 mov edi,[bx]
627                 mov esi,[bx+4]
628                 mov ecx,[bx+8]
629                 cmp edi, -1
630                 je .reload
631                 call bcopy
632                 add bx,12
633                 dec ax
634                 jnz .loop
636 .done:
637                 pop gs
638                 pop fs
639                 pop es
640                 pop ds
641                 popad
642                 popfd
643                 jmp far [cs:EntryPoint]
645 .reload:
646                 mov bx, trackbuf        ; Next descriptor
647                 movzx edi,bx
648                 push ecx                ; Save byte count
649                 call bcopy
650                 pop eax                 ; Byte count
651                 xor edx,edx
652                 mov ecx,12
653                 div ecx                 ; Convert to descriptor count
654                 jmp .restart
657 ; trampoline_to_pm:
659 ; This routine is chained to from shuffle_and_boot to invoke a
660 ; flat 32-bit protected mode operating system.
662 trampoline_to_pm:
663                 cli
664                 call enable_a20
665                 mov byte [cs:bcopy_gdt.TSS+5],89h       ; Mark TSS unbusy
666                 o32 lgdt [cs:bcopy_gdt]
667                 mov eax,cr0
668                 or al,1
669                 mov cr0,eax             ; Enter protected mode
670                 jmp PM_CS32:.next       ; Synchronize and go to 32-bit mode
672                 bits 32
673 .next:          xor eax,eax
674                 lldt ax                 ; TR <- 0 to be nice to Intel VT
675                 mov al,PM_TSS
676                 ltr ax                  ; Bogus TSS to be nice to Intel VT
677                 mov al,PM_DS32
678                 mov es,ax               ; 32-bit data segment selector
679                 mov ds,ax
680                 mov ss,ax
681                 mov fs,ax
682                 mov gs,ax
683                 jmp word TrampolineBuf
684                 bits 16
686                 align 2
687 A20List         dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
688 %if DISABLE_A20
689 A20DList        dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
690 %endif
692 A20Type         dw A20_NONE             ; A20 type
694                 ; Total size of .bcopy32 section
695                 alignb 4, db 0          ; Even number of dwords
696 __bcopy_size    equ $-__bcopy_start
698                 section .earlybss
699                 alignb 2
700 EntryPoint      resd 1                  ; CS:IP for shuffle_and_boot
701 A20Test         resw 1                  ; Counter for testing status of A20
702 A20Tries        resb 1                  ; Times until giving up on A20
705 ; This buffer contains synthesized code for shuffle-and-boot.
706 ; For the PM case, it is 9*5 = 45 bytes long; for the RM case it is
707 ; 8*6 to set the GPRs, 6*5 to set the segment registers (including a dummy
708 ; setting of CS), 5 bytes to set CS:IP, for a total of 83 bytes.
710 TrampolineBuf   resb 83                 ; Shuffle and boot trampoline
713 ; Space for a dummy task state segment.  It should never be actually
714 ; accessed, but just in case it is, point to a chunk of memory not used
715 ; for anything real.
717                 alignb 4
718 DummyTSS        resb 104