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