Magellan Linux

Annotation of /trunk/mkinitrd-magellan/isolinux/bcopy32.inc

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1133 - (hide annotations) (download)
Thu Aug 19 09:50:43 2010 UTC (13 years, 8 months ago) by niro
File size: 8427 byte(s)
-updated to isolinux-3.86
1 niro 532 ;; -----------------------------------------------------------------------
2     ;;
3 niro 1133 ;; Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
4     ;; Copyright 2009 Intel Corporation; author: H. Peter Anvin
5     ;;
6 niro 532 ;; This program is free software; you can redistribute it and/or modify
7     ;; it under the terms of the GNU General Public License as published by
8     ;; the Free Software Foundation, Inc., 53 Temple Place Ste 330,
9     ;; Boston MA 02111-1307, USA; either version 2 of the License, or
10     ;; (at your option) any later version; incorporated herein by reference.
11     ;;
12     ;; -----------------------------------------------------------------------
13    
14     ;;
15     ;; bcopy32.inc
16 niro 1133 ;;
17 niro 532 ;; 32-bit bcopy routine for real mode
18     ;;
19    
20     ;
21     ; 32-bit bcopy routine for real mode
22     ;
23     ; We enter protected mode, set up a flat 32-bit environment, run rep movsd
24     ; and then exit. IMPORTANT: This code assumes cs == 0.
25     ;
26     ; This code is probably excessively anal-retentive in its handling of
27     ; segments, but this stuff is painful enough as it is without having to rely
28     ; on everything happening "as it ought to."
29     ;
30    
31 niro 1133 bits 16
32     section .text
33 niro 532
34     ;
35     ; bcopy:
36     ; 32-bit copy, overlap safe
37     ;
38     ; Inputs:
39 niro 1133 ; ESI - source pointer (-1 means do bzero rather than bcopy)
40 niro 532 ; EDI - target pointer
41     ; ECX - byte count
42     ; DF - zero
43     ;
44     ; Outputs:
45 niro 1133 ; ESI - first byte after source (garbage if ESI == -1 on entry)
46 niro 532 ; EDI - first byte after target
47     ;
48 niro 1133 bcopy: jecxz .ret
49     pushad
50     push word pm_bcopy
51     call simple_pm_call
52     popad
53     add edi,ecx
54     add esi,ecx
55     .ret: ret
56    
57     ;
58     ; shuffle_and_boot_raw:
59     ; The new version of shuffle and boot.
60     ; Inputs:
61     ; ESI -> Pointer to list of (dst, src, len) pairs(*)
62     ; EDI -> Pointer to safe area for list + shuffler
63     ; (must not overlap this code nor the RM stack)
64     ; ECX -> Byte count of list area (for initial copy)
65     ;
66     ; If src == -1: then the memory pointed to by (dst, len) is bzeroed;
67     ; this is handled inside the bcopy routine.
68     ;
69     ; If len == 0: this marks the end of the list; dst indicates
70     ; the entry point and src the mode (0 = pm, 1 = rm)
71     ;
72     shuffle_and_boot_raw:
73     push word pm_shuffle
74     call simple_pm_call
75     ; Never returns...
76     jmp kaboom
77    
78     ;
79     ; This routine is used to invoke a simple routine in 32-bit protected
80     ; mode (with 32-bit zero-based CS, DS, ES, and SS, with ESP pointing to the
81     ; real-mode stack even if the real-mode stack was in a nonzero SS.)
82     ;
83     ; No interrupt thunking services are provided; interrupts are disabled
84     ; for the duration of the routine. Don't run for too long at a time
85     ; unless you really mean it.
86     ;
87     ; Inputs:
88     ; On stack - pm entrypoint (IP only)
89     ; EAX, EBP preserved until real-mode exit
90     ; EBX, ECX, EDX, ESI and EDI passed to the called routine
91     ;
92     ; Outputs:
93     ; EAX, EBP restored from real-mode entry
94     ; All other registers as returned from called function
95     ; PM entrypoint cleaned off stack
96     ;
97     simple_pm_call:
98     push eax
99     push ebp
100     movzx ebp,sp ; BP is used as frame pointer
101     pushfd ; Saves, among others, the IF flag
102 niro 532 push ds
103     push es
104 niro 1133 push fs
105     push gs
106 niro 532
107     cli
108     call enable_a20
109    
110 niro 1133 mov byte [cs:bcopy_gdt.TSS+5],89h ; Mark TSS unbusy
111    
112     ; Convert the stack segment to a base
113     xor eax,eax
114     mov ax,ss
115     shl eax,4
116     add ebp,eax ; EBP is now an absolute frame ptr
117    
118     ; Save the old segmented stack pointer
119     mov [cs:.rm_esp],esp
120     mov [cs:.rm_ss],ss
121    
122 niro 532 o32 lgdt [cs:bcopy_gdt]
123     mov eax,cr0
124     or al,1
125     mov cr0,eax ; Enter protected mode
126 niro 1133 jmp PM_CS32:.in_pm
127 niro 532
128 niro 1133 bits 32
129     .in_pm:
130     mov ax,PM_DS32
131     mov ss,eax
132     lea esp,[ebp-8*4-2*4] ; Flat mode stack
133     mov es,eax
134     mov ds,eax
135 niro 532
136 niro 1133 ; Set fs, gs, tr, and ldtr in case we're on a virtual
137     ; machine running on Intel VT hardware -- it can't
138     ; deal with a partial transition, for no good reason.
139 niro 532
140 niro 1133 mov al,PM_DS16 ; Real-mode-like segment
141     mov fs,eax
142     mov gs,eax
143     mov al,PM_TSS ; Intel VT really doesn't want
144     ltr ax ; an invalid TR and LDTR, so give
145     xor eax,eax ; it something that it can use...
146     lldt ax ; (sigh)
147 niro 532
148 niro 1133 movzx eax,word [ebp+2*4+2]
149     call eax ; Call actual routine
150 niro 532
151 niro 1133 jmp PM_CS16:.exit
152     bits 16
153 niro 532 .exit:
154 niro 1133 mov ax,PM_DS16 ; "Real-mode-like" data segment
155     mov es,eax
156     mov ds,eax
157     mov ss,eax
158 niro 532
159     mov eax,cr0
160     and al,~1
161     mov cr0,eax ; Disable protected mode
162     jmp 0:.in_rm
163    
164     .in_rm: ; Back in real mode
165 niro 1133 lss esp,[cs:.rm_esp] ; Restore the stack
166     pop gs
167     pop fs
168 niro 532 pop es
169     pop ds
170    
171 niro 1133 popfd ; Re-enables interrupts
172     pop ebp
173 niro 532 pop eax
174 niro 1133 ret 2 ; Drops the pm entry
175 niro 532
176 niro 1133 section .bss
177     alignb 4
178     .rm_esp resd 1
179     .rm_ss resw 1
180    
181    
182     section .text
183 niro 532 ;
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.
189     ;
190    
191 niro 1133 section .data
192     alignz 2
193     A20Ptr dw a20_dunno
194 niro 532
195 niro 1133 section .bss
196     alignb 4
197     A20Test resd 1 ; Counter for testing A20 status
198     A20Tries resb 1 ; Times until giving up on A20
199 niro 532
200 niro 1133 section .text
201 niro 532 enable_a20:
202     pushad
203     mov byte [cs:A20Tries],255 ; Times to try to make this work
204    
205     try_enable_a20:
206    
207     ;
208 niro 1133 ; First, see if we are on a system with no A20 gate, or the A20 gate
209     ; is already enabled for us...
210 niro 532 ;
211     a20_none:
212     call a20_test
213     jnz a20_done
214 niro 1133 ; Otherwise, see if we had something memorized...
215     jmp word [cs:A20Ptr]
216 niro 532
217     ;
218     ; Next, try the BIOS (INT 15h AX=2401h)
219     ;
220 niro 1133 a20_dunno:
221 niro 532 a20_bios:
222 niro 1133 mov word [cs:A20Ptr], a20_bios
223 niro 532 mov ax,2401h
224     pushf ; Some BIOSes muck with IF
225     int 15h
226     popf
227    
228     call a20_test
229     jnz a20_done
230    
231     ;
232     ; Enable the keyboard controller A20 gate
233     ;
234     a20_kbc:
235     mov dl, 1 ; Allow early exit
236     call empty_8042
237     jnz a20_done ; A20 live, no need to use KBC
238    
239 niro 1133 mov word [cs:A20Ptr], a20_kbc ; Starting KBC command sequence
240 niro 532
241 niro 1133 mov al,0D1h ; Write output port
242 niro 532 out 064h, al
243     call empty_8042_uncond
244    
245     mov al,0DFh ; A20 on
246     out 060h, al
247     call empty_8042_uncond
248    
249 niro 1133 ; Apparently the UHCI spec assumes that A20 toggle
250     ; ends with a null command (assumed to be for sychronization?)
251     ; Put it here to see if it helps anything...
252     mov al,0FFh ; Null command
253     out 064h, al
254     call empty_8042_uncond
255    
256 niro 532 ; Verify that A20 actually is enabled. Do that by
257     ; observing a word in low memory and the same word in
258     ; the HMA until they are no longer coherent. Note that
259     ; we don't do the same check in the disable case, because
260     ; we don't want to *require* A20 masking (SYSLINUX should
261     ; work fine without it, if the BIOS does.)
262     .kbc_wait: push cx
263     xor cx,cx
264     .kbc_wait_loop:
265     call a20_test
266     jnz a20_done_pop
267     loop .kbc_wait_loop
268    
269     pop cx
270     ;
271     ; Running out of options here. Final attempt: enable the "fast A20 gate"
272     ;
273     a20_fast:
274 niro 1133 mov word [cs:A20Ptr], a20_fast
275 niro 532 in al, 092h
276     or al,02h
277     and al,~01h ; Don't accidentally reset the machine!
278     out 092h, al
279    
280     .fast_wait: push cx
281     xor cx,cx
282     .fast_wait_loop:
283     call a20_test
284     jnz a20_done_pop
285     loop .fast_wait_loop
286    
287     pop cx
288    
289     ;
290     ; Oh bugger. A20 is not responding. Try frobbing it again; eventually give up
291     ; and report failure to the user.
292     ;
293     dec byte [cs:A20Tries]
294 niro 1133 jnz a20_dunno ; Did we get the wrong type?
295 niro 532
296     mov si, err_a20
297     jmp abort_load
298 niro 1133
299     section .data
300     err_a20 db CR, LF, 'A20 gate not responding!', CR, LF, 0
301     section .text
302    
303 niro 532 ;
304     ; A20 unmasked, proceed...
305     ;
306     a20_done_pop: pop cx
307     a20_done: popad
308     ret
309    
310     ;
311     ; This routine tests if A20 is enabled (ZF = 0). This routine
312     ; must not destroy any register contents.
313     ;
314 niro 1133 ; The no-write early out avoids the io_delay in the (presumably common)
315     ; case of A20 already enabled (e.g. from a previous call.)
316     ;
317 niro 532 a20_test:
318     push es
319     push cx
320 niro 1133 push eax
321     mov cx,0FFFFh ; HMA = segment 0FFFFh
322 niro 532 mov es,cx
323 niro 1133 mov eax,[cs:A20Test]
324     mov cx,32 ; Loop count
325     jmp .test ; First iteration = early out
326     .wait: add eax,0x430aea41 ; A large prime number
327     mov [cs:A20Test],eax
328     io_delay ; Serialize, and fix delay
329     .test: cmp eax,[es:A20Test+10h]
330     loopz .wait
331     .done: pop eax
332 niro 532 pop cx
333     pop es
334     ret
335    
336     ;
337     ; Routine to empty the 8042 KBC controller. If dl != 0
338     ; then we will test A20 in the loop and exit if A20 is
339     ; suddenly enabled.
340     ;
341     empty_8042_uncond:
342     xor dl,dl
343     empty_8042:
344     call a20_test
345     jz .a20_on
346     and dl,dl
347     jnz .done
348     .a20_on: io_delay
349     in al, 064h ; Status port
350     test al,1
351     jz .no_output
352     io_delay
353     in al, 060h ; Read input
354     jmp short empty_8042
355     .no_output:
356     test al,2
357     jnz empty_8042
358     io_delay
359 niro 1133 .done: ret
360 niro 532
361     ;
362 niro 1133 ; The 32-bit copy and shuffle code is "special", so it is in its own file
363 niro 532 ;
364 niro 1133 %include "bcopyxx.inc"