More fixes to the extlinux installer; change back to writable types
[profile/ivi/syslinux.git] / bcopy32.inc
1 ;; $Id$
2 ;; -----------------------------------------------------------------------
3 ;;   
4 ;;   Copyright 1994-2004 H. Peter Anvin - All Rights Reserved
5 ;;
6 ;;   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 ;; 
17 ;; 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 ; IMPORTANT: This code must be capable of operating when copied to the
31 ; trackbuf area (1000h).  The routine bcopy_over_self handles this mode
32 ; of operation, including any necessary adjustments.
33 ;
34                 section .text
35                 align 8
36 __bcopy_start:
37
38                 ; This is in the .text segment since it needs to be
39                 ; contiguous with the rest of the bcopy stuff
40
41 bcopy_gdt:      dw bcopy_gdt_size-1     ; Null descriptor - contains GDT
42 .adj1:          dd bcopy_gdt            ; pointer for LGDT instruction
43                 dw 0
44                 dd 0000ffffh            ; Code segment, use16, readable,
45                 dd 00009b00h            ; present, dpl 0, cover 64K
46                 dd 0000ffffh            ; Data segment, use16, read/write,
47                 dd 008f9300h            ; present, dpl 0, cover all 4G
48                 dd 0000ffffh            ; Data segment, use16, read/write,
49                 dd 00009300h            ; present, dpl 0, cover 64K
50                 ; The rest are used for COM32 only
51                 dd 0000ffffh            ; Code segment, use32, readable,
52                 dd 00cf9b00h            ; present, dpl 0, cover all 4G
53                 dd 0000ffffh            ; Data segment, use32, read/write,
54                 dd 00cf9300h            ; present, dpl 0, cover all 4G
55 bcopy_gdt_size: equ $-bcopy_gdt
56
57 ;
58 ; bcopy:
59 ;       32-bit copy
60 ;
61 ; Inputs:
62 ;       ESI     - source pointer
63 ;       EDI     - target pointer
64 ;       ECX     - byte count
65 ;       DF      - zero
66 ;
67 ; Outputs:
68 ;       ESI     - first byte after source
69 ;       EDI     - first byte after target
70 ;       ECX     - zero
71 ;
72 bcopy:          push eax
73                 pushf                   ; Saves, among others, the IF flag
74                 push gs
75                 push fs
76                 push ds
77                 push es
78                 mov [cs:SavedSSSP],sp
79                 mov [cs:SavedSSSP+2],ss
80
81                 cli
82                 call enable_a20
83
84 .adj2:          o32 lgdt [cs:bcopy_gdt]
85                 mov eax,cr0
86                 or al,1
87                 mov cr0,eax             ; Enter protected mode
88 .adj3a:         jmp 08h:.in_pm
89
90 .in_pm:         mov ax,10h              ; Data segment selector
91                 mov es,ax
92                 mov ds,ax
93
94                 mov al,18h              ; "Real-mode-like" data segment
95                 mov ss,ax
96                 mov fs,ax
97                 mov gs,ax       
98
99                 mov al,cl               ; Save low bits
100                 shr ecx,2               ; Convert to dwords
101                 a32 rep movsd           ; Do our business
102                 ; At this point ecx == 0
103
104                 mov cl,al               ; Copy any fractional dword
105                 and cl,3
106                 a32 rep movsb
107
108                 mov al,18h              ; "Real-mode-like" data segment
109                 mov es,ax
110                 mov ds,ax
111
112                 mov eax,cr0
113                 and al,~1
114                 mov cr0,eax             ; Disable protected mode
115 .adj3b:         jmp 0:.in_rm
116
117 .in_rm:         ; Back in real mode
118                 lss sp,[cs:SavedSSSP]
119                 pop es
120                 pop ds
121                 pop fs
122                 pop gs
123                 call disable_a20
124
125                 popf                    ; Re-enables interrupts
126                 pop eax
127                 ret
128
129 ;
130 ; Routines to enable and disable (yuck) A20.  These routines are gathered
131 ; from tips from a couple of sources, including the Linux kernel and
132 ; http://www.x86.org/.  The need for the delay to be as large as given here
133 ; is indicated by Donnie Barnes of RedHat, the problematic system being an
134 ; IBM ThinkPad 760EL.
135 ;
136 ; We typically toggle A20 twice for every 64K transferred.
137
138 %define io_delay        call _io_delay
139 %define IO_DELAY_PORT   80h             ; Invalid port (we hope!)
140 %define disable_wait    32              ; How long to wait for a disable
141
142 %define A20_DUNNO       0               ; A20 type unknown
143 %define A20_NONE        1               ; A20 always on?
144 %define A20_BIOS        2               ; A20 BIOS enable
145 %define A20_KBC         3               ; A20 through KBC
146 %define A20_FAST        4               ; A20 through port 92h
147
148                 align 2
149 A20List         dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
150 A20DList        dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
151 a20_adjust_cnt  equ ($-A20List)/2
152
153 slow_out:       out dx, al              ; Fall through
154
155 _io_delay:      out IO_DELAY_PORT,al
156                 out IO_DELAY_PORT,al
157                 ret
158
159 enable_a20:
160                 pushad
161                 mov byte [cs:A20Tries],255 ; Times to try to make this work
162
163 try_enable_a20:
164 ;
165 ; Flush the caches
166 ;
167 %if DO_WBINVD
168                 call try_wbinvd
169 %endif
170
171 ;
172 ; If the A20 type is known, jump straight to type
173 ;
174                 mov bp,[cs:A20Type]
175                 add bp,bp                       ; Convert to word offset
176 .adj4:          jmp word [cs:bp+A20List]
177
178 ;
179 ; First, see if we are on a system with no A20 gate
180 ;
181 a20_dunno:
182 a20_none:
183                 mov byte [cs:A20Type], A20_NONE
184                 call a20_test
185                 jnz a20_done
186
187 ;
188 ; Next, try the BIOS (INT 15h AX=2401h)
189 ;
190 a20_bios:
191                 mov byte [cs:A20Type], A20_BIOS
192                 mov ax,2401h
193                 pushf                           ; Some BIOSes muck with IF
194                 int 15h
195                 popf
196
197                 call a20_test
198                 jnz a20_done
199
200 ;
201 ; Enable the keyboard controller A20 gate
202 ;
203 a20_kbc:
204                 mov dl, 1                       ; Allow early exit
205                 call empty_8042
206                 jnz a20_done                    ; A20 live, no need to use KBC
207
208                 mov byte [cs:A20Type], A20_KBC  ; Starting KBC command sequence
209
210                 mov al,0D1h                     ; Command write
211                 out 064h, al
212                 call empty_8042_uncond
213
214                 mov al,0DFh                     ; A20 on
215                 out 060h, al
216                 call empty_8042_uncond
217
218                 ; Verify that A20 actually is enabled.  Do that by
219                 ; observing a word in low memory and the same word in
220                 ; the HMA until they are no longer coherent.  Note that
221                 ; we don't do the same check in the disable case, because
222                 ; we don't want to *require* A20 masking (SYSLINUX should
223                 ; work fine without it, if the BIOS does.)
224 .kbc_wait:      push cx
225                 xor cx,cx
226 .kbc_wait_loop:
227                 call a20_test
228                 jnz a20_done_pop
229                 loop .kbc_wait_loop
230
231                 pop cx
232 ;
233 ; Running out of options here.  Final attempt: enable the "fast A20 gate"
234 ;
235 a20_fast:
236                 mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
237                 in al, 092h
238                 or al,02h
239                 and al,~01h                     ; Don't accidentally reset the machine!
240                 out 092h, al
241
242 .fast_wait:     push cx
243                 xor cx,cx
244 .fast_wait_loop:
245                 call a20_test
246                 jnz a20_done_pop
247                 loop .fast_wait_loop
248
249                 pop cx
250
251 ;
252 ; Oh bugger.  A20 is not responding.  Try frobbing it again; eventually give up
253 ; and report failure to the user.
254 ;
255
256
257                 dec byte [cs:A20Tries]
258                 jnz try_enable_a20
259
260                 mov si, err_a20
261                 jmp abort_load
262 ;
263 ; A20 unmasked, proceed...
264 ;
265 a20_done_pop:   pop cx
266 a20_done:       popad
267                 ret
268
269 ;
270 ; This routine tests if A20 is enabled (ZF = 0).  This routine
271 ; must not destroy any register contents.
272 ;
273 a20_test:
274                 push es
275                 push cx
276                 push ax
277                 mov cx,0FFFFh           ; HMA = segment 0FFFFh
278                 mov es,cx
279                 mov cx,32               ; Loop count
280                 mov ax,[cs:A20Test]
281 .a20_wait:      inc ax
282                 mov [cs:A20Test],ax
283                 io_delay                ; Serialize, and fix delay
284                 cmp ax,[es:A20Test+10h]
285                 loopz .a20_wait
286 .a20_done:      pop ax
287                 pop cx
288                 pop es
289                 ret
290
291 disable_a20:
292                 pushad
293 ;
294 ; Flush the caches
295 ;
296 %if DO_WBINVD
297                 call try_wbinvd
298 %endif
299
300                 mov bp,[cs:A20Type]
301                 add bp,bp                       ; Convert to word offset
302 .adj5:          jmp word [cs:bp+A20DList]
303
304 a20d_bios:
305                 mov ax,2400h
306                 pushf                           ; Some BIOSes muck with IF
307                 int 15h
308                 popf
309                 jmp short a20d_snooze
310
311 ;
312 ; Disable the "fast A20 gate"
313 ;
314 a20d_fast:
315                 in al, 092h
316                 and al,~03h
317                 out 092h, al
318                 jmp short a20d_snooze
319
320 ;
321 ; Disable the keyboard controller A20 gate
322 ;
323 a20d_kbc:
324                 call empty_8042_uncond
325                 mov al,0D1h
326                 out 064h, al            ; Command write
327                 call empty_8042_uncond
328                 mov al,0DDh             ; A20 off
329                 out 060h, al
330                 call empty_8042_uncond
331                 ; Wait a bit for it to take effect
332 a20d_snooze:
333                 push cx
334                 mov cx, disable_wait
335 .delayloop:     call a20_test
336                 jz .disabled
337                 loop .delayloop
338 .disabled:      pop cx
339 a20d_dunno:
340 a20d_none:
341                 popad
342                 ret
343
344 ;
345 ; Routine to empty the 8042 KBC controller.  If dl != 0
346 ; then we will test A20 in the loop and exit if A20 is
347 ; suddenly enabled.
348 ;
349 empty_8042_uncond:
350                 xor dl,dl
351 empty_8042:
352                 call a20_test
353                 jz .a20_on
354                 and dl,dl
355                 jnz .done
356 .a20_on:        io_delay
357                 in al, 064h             ; Status port
358                 test al,1
359                 jz .no_output
360                 io_delay
361                 in al, 060h             ; Read input
362                 jmp short empty_8042
363 .no_output:
364                 test al,2
365                 jnz empty_8042
366                 io_delay
367 .done:          ret     
368
369 ;
370 ; Execute a WBINVD instruction if possible on this CPU
371 ;
372 %if DO_WBINVD
373 try_wbinvd:
374                 wbinvd
375                 ret
376 %endif
377
378 ;
379 ; bcopy_over_self:
380 ;
381 ; This routine is used to copy large blocks of code on top of
382 ; conventional memory (to 0:7c00).  We therefore have to move
383 ; necessary code into the trackbuf area before doing the copy,
384 ; and do adjustments to anything except BSS area references.
385 ;
386 ; After performing the copy, this routine resets the stack and
387 ; jumps to 0:7c00.
388 ;
389 ; IMPORTANT: This routine does not canonicalize the stack or the
390 ; SS register.  That is the responsibility of the caller.
391 ;
392 ; Inputs:
393 ;       ESI, EDI, ECX   - same as bcopy
394 ;       On stack        - initial state (fd, ad, ds, es, fs, gs)
395 ;
396 ADJUST          equ (__bcopy_start - $$) + 7C00h - BSS_START
397
398                 align 2
399 adjlist         dw bcopy_gdt.adj1 - ADJUST
400                 dw bcopy.adj2 + 5 - ADJUST
401                 dw bcopy.adj3a + 1 - ADJUST
402                 dw bcopy.adj3b + 1 - ADJUST
403                 dw try_enable_a20.adj4 + 3 - ADJUST
404                 dw disable_a20.adj5 + 3 - ADJUST
405 adjlist_cnt     equ ($-adjlist)/2
406
407 bcopy_over_self:
408                 push esi        
409                 push edi
410                 push ecx
411
412                 xor bx,bx
413                 mov es,bx
414                 mov ds,bx
415
416                 mov si,__bcopy_start
417                 mov di,trackbuf         ; == BSS_START
418                 mov cx,(__bcopy_end - __bcopy_start + 3) >> 2
419                 rep movsd
420
421                 mov si,A20List - ADJUST
422                 mov cx,a20_adjust_cnt
423 .adjust1:
424                 sub word [si], ADJUST
425                 inc si
426                 inc si
427                 loop .adjust1
428
429                 mov si, adjlist
430                 mov cx, adjlist_cnt
431 .adjust2:
432                 lodsw
433                 xchg di,ax
434                 sub word [di], ADJUST
435                 loop .adjust2
436
437                 jmp .next-ADJUST
438 .next:
439                 pop ecx
440                 pop edi
441                 pop esi
442                 call bcopy
443                 
444                 pop gs
445                 pop fs
446                 pop es
447                 pop ds
448                 popad
449                 popfd
450                 jmp 0:7c00h
451 __bcopy_end:
452
453                 section .bss
454 A20Test         resw 1                  ; Counter for testing status of A20
455 A20Type         resw 1                  ; A20 type
456 A20Tries        resb 1                  ; Times until giving up on A20