Move mboot documentation to the doc/ directory
[profile/ivi/syslinux.git] / bcopy32.inc
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.
10 ;;
11 ;; -----------------------------------------------------------------------
12
13 ;;
14 ;; bcopy32.inc
15 ;;
16 ;; 32-bit bcopy routine for real mode
17 ;;
18
19 ;
20 ; 32-bit bcopy routine for real mode
21 ;
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.
24 ;
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."
28 ;
29 ; NOTE: this code is relocated into low memory, just after the .earlybss
30 ; segment, in order to support to "bcopy over self" operation.
31 ;
32
33                 section .bcopy32
34                 align 8
35 __bcopy_start:
36
37                 ; This is in the .text segment since it needs to be
38                 ; contiguous with the rest of the bcopy stuff
39
40 ; GDT descriptor entry
41 %macro desc 1
42 bcopy_gdt.%1:
43 PM_%1           equ bcopy_gdt.%1-bcopy_gdt
44 %endmacro
45
46 bcopy_gdt:
47                 dw bcopy_gdt_size-1     ; Null descriptor - contains GDT
48                 dd bcopy_gdt            ; pointer for LGDT instruction
49                 dw 0
50
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
67
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
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
80
81 bcopy_gdt_size: equ $-bcopy_gdt
82
83 ;
84 ; bcopy:
85 ;       32-bit copy, overlap safe
86 ;
87 ; Inputs:
88 ;       ESI     - source pointer (-1 means do bzero rather than bcopy)
89 ;       EDI     - target pointer
90 ;       ECX     - byte count
91 ;       DF      - zero
92 ;
93 ; Outputs:
94 ;       ESI     - first byte after source (garbage if ESI == -1 on entry)
95 ;       EDI     - first byte after target
96 ;
97 bcopy:          pushad
98                 push word pm_bcopy
99                 call simple_pm_call
100                 popad
101                 add edi,ecx
102                 add esi,ecx
103                 ret
104
105 ;
106 ; This routine is used to invoke a simple routine in 16-bit protected
107 ; mode (with 32-bit DS and ES, and working 16-bit stack.)
108 ; Note that all segment registers including CS, except possibly SS,
109 ; are zero-based in the protected-mode routine.
110 ;
111 ; No interrupt thunking services are provided; interrupts are disabled
112 ; for the duration of the routine.  Don't run for too long at a time.
113 ;
114 ; Inputs:
115 ;       On stack        - pm entrypoint
116 ;       EAX, EBP preserved until real-mode exit
117 ;       EBX, ECX, EDX, ESI and EDI passed to the called routine
118 ;
119 ; Outputs:
120 ;       EAX, EBP restored from real-mode entry
121 ;       All other registers as returned from called function
122 ;       PM entrypoint cleaned off stack
123 ;
124 simple_pm_call:
125                 push eax
126                 push ebp
127                 mov bp,sp
128                 pushfd                  ; Saves, among others, the IF flag
129                 push ds
130                 push es
131                 push fs
132                 push gs
133
134                 cli
135                 call enable_a20
136
137                 mov byte [cs:bcopy_gdt.TSS+5],89h       ; Mark TSS unbusy
138
139                 ; Convert the stack segment to a base
140                 xor eax,eax
141                 mov ax,ss
142                 shl eax,4
143                 or eax,93000000h
144                 mov [cs:bcopy_gdt.SS16+2],eax
145
146                 push ss                 ; Save real-mode SS selector
147
148                 o32 lgdt [cs:bcopy_gdt]
149                 mov eax,cr0
150                 or al,1
151                 mov cr0,eax             ; Enter protected mode
152                 jmp PM_CS16:.in_pm
153 .in_pm:
154                 mov ax,PM_SS16          ; Make stack usable
155                 mov ss,ax
156
157                 mov al,PM_DS16_4G       ; Data segment selector
158                 mov es,ax
159                 mov ds,ax
160
161                 ; Set fs, gs, tr, and ldtr in case we're on a virtual
162                 ; machine running on Intel VT hardware -- it can't
163                 ; deal with a partial transition, for no good reason.
164
165                 mov al,PM_DS16_RM       ; Real-mode-like segment
166                 mov fs,ax
167                 mov gs,ax
168                 mov al,PM_TSS           ; Intel VT really doesn't want
169                 ltr ax                  ; an invalid TR and LDTR, so give
170                 xor ax,ax               ; it something that it can use...
171                 lldt ax                 ; (sigh)
172
173                 call [bp+2*4+2]         ; Call actual routine
174
175 .exit:
176                 mov ax,PM_DS16_RM       ; "Real-mode-like" data segment
177                 mov es,ax
178                 mov ds,ax
179
180                 pop bp                  ; Previous value for ss
181
182                 mov eax,cr0
183                 and al,~1
184                 mov cr0,eax             ; Disable protected mode
185                 jmp 0:.in_rm
186
187 .in_rm:         ; Back in real mode
188                 mov ss,bp
189                 pop gs
190                 pop fs
191                 pop es
192                 pop ds
193 %if DISABLE_A20
194                 call disable_a20
195 %endif
196
197                 popfd                   ; Re-enables interrupts
198                 pop ebp
199                 pop eax
200                 ret 2                   ; Drops the pm entry
201
202 ;
203 ; pm_bcopy:
204 ;
205 ;       This is the protected-mode core of the "bcopy" routine.
206 ;
207 pm_bcopy:
208                 cmp esi,-1
209                 je .bzero
210
211                 cmp esi,edi             ; If source < destination, we might
212                 jb .reverse             ; have to copy backwards
213
214 .forward:
215                 mov al,cl               ; Save low bits
216                 and al,3
217                 shr ecx,2               ; Convert to dwords
218                 a32 rep movsd           ; Do our business
219                 ; At this point ecx == 0
220
221                 mov cl,al               ; Copy any fractional dword
222                 a32 rep movsb
223                 ret
224
225 .reverse:
226                 std                     ; Reverse copy
227                 lea esi,[esi+ecx-1]     ; Point to final byte
228                 lea edi,[edi+ecx-1]
229                 mov eax,ecx
230                 and ecx,3
231                 shr eax,2
232                 a32 rep movsb
233
234                 ; Change ESI/EDI to point to the last dword, instead
235                 ; of the last byte.
236                 sub esi,3
237                 sub edi,3
238                 mov ecx,eax
239                 a32 rep movsd
240
241                 cld
242                 ret
243
244 .bzero:
245                 xor eax,eax
246                 mov si,cx               ; Save low bits
247                 and si,3
248                 shr ecx,2
249                 a32 rep stosd
250
251                 mov cx,si               ; Write fractional dword
252                 a32 rep stosb
253                 ret
254
255 ;
256 ; Routines to enable and disable (yuck) A20.  These routines are gathered
257 ; from tips from a couple of sources, including the Linux kernel and
258 ; http://www.x86.org/.  The need for the delay to be as large as given here
259 ; is indicated by Donnie Barnes of RedHat, the problematic system being an
260 ; IBM ThinkPad 760EL.
261 ;
262 ; We typically toggle A20 twice for every 64K transferred.
263 ;
264 %define io_delay        call _io_delay
265 %define IO_DELAY_PORT   80h             ; Invalid port (we hope!)
266 %define disable_wait    32              ; How long to wait for a disable
267
268 ; Note the skip of 2 here
269 %define A20_DUNNO       0               ; A20 type unknown
270 %define A20_NONE        2               ; A20 always on?
271 %define A20_BIOS        4               ; A20 BIOS enable
272 %define A20_KBC         6               ; A20 through KBC
273 %define A20_FAST        8               ; A20 through port 92h
274
275 slow_out:       out dx, al              ; Fall through
276
277 _io_delay:      out IO_DELAY_PORT,al
278                 out IO_DELAY_PORT,al
279                 ret
280
281 enable_a20:
282                 pushad
283                 mov byte [cs:A20Tries],255 ; Times to try to make this work
284
285 try_enable_a20:
286 ;
287 ; Flush the caches
288 ;
289 %if DO_WBINVD
290                 call try_wbinvd
291 %endif
292
293 ;
294 ; If the A20 type is known, jump straight to type
295 ;
296                 mov bp,[cs:A20Type]
297                 jmp word [cs:bp+A20List]
298
299 ;
300 ; First, see if we are on a system with no A20 gate
301 ;
302 a20_dunno:
303 a20_none:
304                 mov byte [cs:A20Type], A20_NONE
305                 call a20_test
306                 jnz a20_done
307
308 ;
309 ; Next, try the BIOS (INT 15h AX=2401h)
310 ;
311 a20_bios:
312                 mov byte [cs:A20Type], A20_BIOS
313                 mov ax,2401h
314                 pushf                           ; Some BIOSes muck with IF
315                 int 15h
316                 popf
317
318                 call a20_test
319                 jnz a20_done
320
321 ;
322 ; Enable the keyboard controller A20 gate
323 ;
324 a20_kbc:
325                 mov dl, 1                       ; Allow early exit
326                 call empty_8042
327                 jnz a20_done                    ; A20 live, no need to use KBC
328
329                 mov byte [cs:A20Type], A20_KBC  ; Starting KBC command sequence
330
331                 mov al,0D1h                     ; Command write
332                 out 064h, al
333                 call empty_8042_uncond
334
335                 mov al,0DFh                     ; A20 on
336                 out 060h, al
337                 call empty_8042_uncond
338
339                 ; Verify that A20 actually is enabled.  Do that by
340                 ; observing a word in low memory and the same word in
341                 ; the HMA until they are no longer coherent.  Note that
342                 ; we don't do the same check in the disable case, because
343                 ; we don't want to *require* A20 masking (SYSLINUX should
344                 ; work fine without it, if the BIOS does.)
345 .kbc_wait:      push cx
346                 xor cx,cx
347 .kbc_wait_loop:
348                 call a20_test
349                 jnz a20_done_pop
350                 loop .kbc_wait_loop
351
352                 pop cx
353 ;
354 ; Running out of options here.  Final attempt: enable the "fast A20 gate"
355 ;
356 a20_fast:
357                 mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
358                 in al, 092h
359                 or al,02h
360                 and al,~01h                     ; Don't accidentally reset the machine!
361                 out 092h, al
362
363 .fast_wait:     push cx
364                 xor cx,cx
365 .fast_wait_loop:
366                 call a20_test
367                 jnz a20_done_pop
368                 loop .fast_wait_loop
369
370                 pop cx
371
372 ;
373 ; Oh bugger.  A20 is not responding.  Try frobbing it again; eventually give up
374 ; and report failure to the user.
375 ;
376
377
378                 dec byte [cs:A20Tries]
379                 jnz try_enable_a20
380
381                 mov si, err_a20
382                 jmp abort_load
383
384                 section .data
385 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
386                 section .bcopy32
387
388 ;
389 ; A20 unmasked, proceed...
390 ;
391 a20_done_pop:   pop cx
392 a20_done:       popad
393                 ret
394
395 ;
396 ; This routine tests if A20 is enabled (ZF = 0).  This routine
397 ; must not destroy any register contents.
398 ;
399 a20_test:
400                 push es
401                 push cx
402                 push ax
403                 mov cx,0FFFFh           ; HMA = segment 0FFFFh
404                 mov es,cx
405                 mov cx,32               ; Loop count
406                 mov ax,[cs:A20Test]
407 .a20_wait:      inc ax
408                 mov [cs:A20Test],ax
409                 io_delay                ; Serialize, and fix delay
410                 cmp ax,[es:A20Test+10h]
411                 loopz .a20_wait
412 .a20_done:      pop ax
413                 pop cx
414                 pop es
415                 ret
416
417 %if DISABLE_A20
418
419 disable_a20:
420                 pushad
421 ;
422 ; Flush the caches
423 ;
424 %if DO_WBINVD
425                 call try_wbinvd
426 %endif
427
428                 mov bp,[cs:A20Type]
429                 jmp word [cs:bp+A20DList]
430
431 a20d_bios:
432                 mov ax,2400h
433                 pushf                           ; Some BIOSes muck with IF
434                 int 15h
435                 popf
436                 jmp short a20d_snooze
437
438 ;
439 ; Disable the "fast A20 gate"
440 ;
441 a20d_fast:
442                 in al, 092h
443                 and al,~03h
444                 out 092h, al
445                 jmp short a20d_snooze
446
447 ;
448 ; Disable the keyboard controller A20 gate
449 ;
450 a20d_kbc:
451                 call empty_8042_uncond
452                 mov al,0D1h
453                 out 064h, al            ; Command write
454                 call empty_8042_uncond
455                 mov al,0DDh             ; A20 off
456                 out 060h, al
457                 call empty_8042_uncond
458                 ; Wait a bit for it to take effect
459 a20d_snooze:
460                 push cx
461                 mov cx, disable_wait
462 .delayloop:     call a20_test
463                 jz .disabled
464                 loop .delayloop
465 .disabled:      pop cx
466 a20d_dunno:
467 a20d_none:
468                 popad
469                 ret
470
471 %endif
472
473 ;
474 ; Routine to empty the 8042 KBC controller.  If dl != 0
475 ; then we will test A20 in the loop and exit if A20 is
476 ; suddenly enabled.
477 ;
478 empty_8042_uncond:
479                 xor dl,dl
480 empty_8042:
481                 call a20_test
482                 jz .a20_on
483                 and dl,dl
484                 jnz .done
485 .a20_on:        io_delay
486                 in al, 064h             ; Status port
487                 test al,1
488                 jz .no_output
489                 io_delay
490                 in al, 060h             ; Read input
491                 jmp short empty_8042
492 .no_output:
493                 test al,2
494                 jnz empty_8042
495                 io_delay
496 .done:          ret
497
498 ;
499 ; Execute a WBINVD instruction if possible on this CPU
500 ;
501 %if DO_WBINVD
502 try_wbinvd:
503                 wbinvd
504                 ret
505 %endif
506
507 ;
508 ; shuffle_and_boot:
509 ;
510 ; This routine is used to shuffle memory around, followed by
511 ; invoking an entry point somewhere in low memory.  This routine
512 ; can clobber any memory above 7C00h, we therefore have to move
513 ; necessary code into the trackbuf area before doing the copy,
514 ; and do adjustments to anything except BSS area references.
515 ;
516 ; NOTE: Since PXELINUX relocates itself, put all these
517 ; references in the ".earlybss" segment.
518 ;
519 ; After performing the copy, this routine resets the stack and
520 ; jumps to the specified entrypoint.
521 ;
522 ; IMPORTANT: This routine does not canonicalize the stack or the
523 ; SS register.  That is the responsibility of the caller.
524 ;
525 ; Inputs:
526 ;       DS:BX           -> Pointer to list of (dst, src, len) pairs(*)
527 ;       AX              -> Number of list entries
528 ;       [CS:EntryPoint] -> CS:IP to jump to
529 ;       On stack        - initial state (fd, ad, ds, es, fs, gs)
530 ;
531 ; (*) If dst == -1, then (src, len) entry refers to a set of new
532 ;                   descriptors to load.
533 ;     If src == -1, then the memory pointed to by (dst, len) is bzeroed;
534 ;                   this is handled inside the bcopy routine.
535 ;
536 shuffle_and_boot:
537 .restart:
538                 and ax,ax
539                 jz .done
540 .loop:
541                 mov edi,[bx]
542                 mov esi,[bx+4]
543                 mov ecx,[bx+8]
544                 cmp edi, -1
545                 je .reload
546                 call bcopy
547                 add bx,12
548                 dec ax
549                 jnz .loop
550
551 .done:
552                 pop gs
553                 pop fs
554                 pop es
555                 pop ds
556                 popad
557                 popfd
558                 jmp far [cs:EntryPoint]
559
560 .reload:
561                 mov bx, trackbuf        ; Next descriptor
562                 movzx edi,bx
563                 push ecx                ; Save byte count
564                 call bcopy
565                 pop eax                 ; Byte count
566                 xor edx,edx
567                 mov ecx,12
568                 div ecx                 ; Convert to descriptor count
569                 jmp .restart
570
571 ;
572 ; trampoline_to_pm:
573 ;
574 ; This routine is chained to from shuffle_and_boot to invoke a
575 ; flat 32-bit protected mode operating system.
576 ;
577 trampoline_to_pm:
578                 cli
579                 call enable_a20
580                 mov byte [cs:bcopy_gdt.TSS+5],89h       ; Mark TSS unbusy
581                 o32 lgdt [cs:bcopy_gdt]
582                 mov eax,cr0
583                 or al,1
584                 mov cr0,eax             ; Enter protected mode
585                 jmp PM_CS32:.next       ; Synchronize and go to 32-bit mode
586
587                 bits 32
588 .next:          xor eax,eax
589                 lldt ax                 ; TR <- 0 to be nice to Intel VT
590                 mov al,PM_TSS
591                 ltr ax                  ; Bogus TSS to be nice to Intel VT
592                 mov al,PM_DS32
593                 mov es,ax               ; 32-bit data segment selector
594                 mov ds,ax
595                 mov ss,ax
596                 mov fs,ax
597                 mov gs,ax
598                 jmp word TrampolineBuf
599                 bits 16
600
601                 align 2
602 A20List         dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
603 %if DISABLE_A20
604 A20DList        dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
605 %endif
606
607 A20Type         dw A20_NONE             ; A20 type
608
609                 ; Total size of .bcopy32 section
610                 alignb 4, db 0          ; Even number of dwords
611 __bcopy_size    equ $-__bcopy_start
612
613                 section .earlybss
614                 alignb 2
615 EntryPoint      resd 1                  ; CS:IP for shuffle_and_boot
616 A20Test         resw 1                  ; Counter for testing status of A20
617 A20Tries        resb 1                  ; Times until giving up on A20
618
619 ;
620 ; This buffer contains synthesized code for shuffle-and-boot.
621 ; For the PM case, it is 9*5 = 45 bytes long; for the RM case it is
622 ; 8*6 to set the GPRs, 6*5 to set the segment registers (including a dummy
623 ; setting of CS), 5 bytes to set CS:IP, for a total of 83 bytes.
624 ;
625 TrampolineBuf   resb 83                 ; Shuffle and boot trampoline
626
627 ;
628 ; Space for a dummy task state segment.  It should never be actually
629 ; accessed, but just in case it is, point to a chunk of memory not used
630 ; for anything real.
631 ;
632                 alignb 4
633 DummyTSS        resb 104