Magellan Linux

Annotation of /trunk/mkinitrd-magellan/isolinux/adv.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: 9302 byte(s)
-updated to isolinux-3.86
1 niro 1133 ;; -----------------------------------------------------------------------
2     ;;
3     ;; Copyright 2007-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., 51 Franklin St, Fifth Floor,
8     ;; Boston MA 02110-1301, USA; either version 2 of the License, or
9     ;; (at your option) any later version; incorporated herein by reference.
10     ;;
11     ;; -----------------------------------------------------------------------
12    
13     ;;
14     ;; adv.inc
15     ;;
16     ;; The auxillary data vector and its routines
17     ;;
18     ;; The auxillary data vector is a 512-byte aligned block that on the
19     ;; disk-based derivatives can be part of the syslinux file itself. It
20     ;; exists in two copies; when written, both copies are written (with a
21     ;; sync in between, if from the operating system.) The first two
22     ;; dwords are magic number and inverse checksum, then follows the data
23     ;; area as a tagged array similar to BOOTP/DHCP, finally a tail
24     ;; signature.
25     ;;
26     ;; Note that unlike BOOTP/DHCP, zero terminates the chain, and FF
27     ;; has no special meaning.
28     ;;
29    
30     ;;
31     ;; List of ADV tags...
32     ;;
33     ADV_BOOTONCE equ 1
34    
35     ;;
36     ;; Other ADV data...
37     ;;
38     ADV_MAGIC1 equ 0x5a2d2fa5 ; Head signature
39     ADV_MAGIC2 equ 0xa3041767 ; Total checksum
40     ADV_MAGIC3 equ 0xdd28bf64 ; Tail signature
41    
42     ADV_LEN equ 500 ; Data bytes
43    
44     adv_retries equ 6 ; Disk retries
45    
46     section .adv
47     ; Introduce the ADVs to valid but blank
48     adv0:
49     .head resd 1
50     .csum resd 1
51     .data resb ADV_LEN
52     .tail resd 1
53     .end equ $
54     adv1:
55     .head resd 1
56     .csum resd 1
57     .data resb ADV_LEN
58     .tail resd 1
59     .end equ $
60     section .text
61    
62     ;
63     ; This is called after config file parsing, so we know
64     ; the intended location of the ADV
65     ;
66     adv_init:
67     cmp byte [ADVDrive],-1
68     jne adv_read
69    
70     ;%if IS_SYSLINUX || IS_MDSLINUX || IS_EXTLINUX
71     %if IS_EXTLINUX ; Not yet implemented for the other derivatives
72     ;
73     ; Update pointers to default ADVs...
74     ;
75     mov bx,[LDLSectors]
76     shl bx,2
77     mov ecx,[bsHidden]
78     mov eax,[bx+SectorPtrs-8]
79     mov edx,[bx+SectorPtrs-4]
80     add eax,ecx
81     add edx,ecx
82     mov [ADVSec0],eax
83     mov [ADVSec1],edx
84     mov al,[DriveNumber]
85     mov [ADVDrive],al
86     %endif
87     ; ** fall through to adv_verify **
88    
89     ;
90     ; Initialize the ADV data structure in memory
91     ;
92     adv_verify:
93     cmp byte [ADVDrive],-1 ; No ADV configured, still?
94     je .reset ; Then unconditionally reset
95    
96     mov si,adv0
97     call .check_adv
98     jz .ok ; Primary ADV okay
99     mov si,adv1
100     call .check_adv
101     jz .adv1ok
102    
103     ; Neither ADV is usable; initialize to blank
104     .reset:
105     mov di,adv0
106     mov eax,ADV_MAGIC1
107     stosd
108     mov eax,ADV_MAGIC2
109     stosd
110     xor eax,eax
111     mov cx,ADV_LEN/4
112     rep stosd
113     mov eax,ADV_MAGIC3
114     stosd
115    
116     .ok:
117     ret
118    
119     ; The primary ADV is bad, but the backup is OK
120     .adv1ok:
121     mov di,adv0
122     mov cx,512/4
123     rep movsd
124     ret
125    
126    
127     ; SI points to the putative ADV; unchanged by routine
128     ; ZF=1 on return if good
129     .check_adv:
130     push si
131     lodsd
132     cmp eax,ADV_MAGIC1
133     jne .done ; ZF=0, i.e. bad
134     xor edx,edx
135     mov cx,ADV_LEN/4+1 ; Remaining dwords
136     .csum:
137     lodsd
138     add edx,eax
139     loop .csum
140     cmp edx,ADV_MAGIC2
141     jne .done
142     lodsd
143     cmp eax,ADV_MAGIC3
144     .done:
145     pop si
146     ret
147    
148     ;
149     ; adv_get: find an ADV string if present
150     ;
151     ; Input: DL = ADV ID
152     ; Output: CX = byte count (zero on not found)
153     ; SI = pointer to data
154     ; DL = unchanged
155     ;
156     ; Assumes CS == DS.
157     ;
158    
159     adv_get:
160     push ax
161     mov si,adv0.data
162     xor ax,ax ; Keep AH=0 at all times
163     .loop:
164     lodsb ; Read ID
165     cmp al,dl
166     je .found
167     and al,al
168     jz .end
169     lodsb ; Read length
170     add si,ax
171     cmp si,adv0.tail
172     jb .loop
173     jmp .end
174    
175     .found:
176     lodsb
177     mov cx,ax
178     add ax,si ; Make sure it fits
179     cmp ax,adv0.tail
180     jbe .ok
181     .end:
182     xor cx,cx
183     .ok:
184     pop ax
185     ret
186    
187     ;
188     ; adv_set: insert a string into the ADV in memory
189     ;
190     ; Input: DL = ADV ID
191     ; FS:BX = input buffer
192     ; CX = byte count (max = 255!)
193     ; Output: CF=1 on error
194     ; CX clobbered
195     ;
196     ; Assumes CS == DS == ES.
197     ;
198     adv_set:
199     push ax
200     push si
201     push di
202     and ch,ch
203     jnz .overflow
204    
205     push cx
206     mov si,adv0.data
207     xor ax,ax
208     .loop:
209     lodsb
210     cmp al,dl
211     je .found
212     and al,al
213     jz .endz
214     lodsb
215     add si,ax
216     cmp si,adv0.tail
217     jb .loop
218     jmp .end
219    
220     .found: ; Found, need to delete old copy
221     lodsb
222     lea di,[si-2]
223     push di
224     add si,ax
225     mov cx,adv0.tail
226     sub cx,si
227     jb .nukeit
228     rep movsb ; Remove the old one
229     mov [di],ah ; Termination zero
230     pop si
231     jmp .loop
232     .nukeit:
233     pop si
234     jmp .end
235     .endz:
236     dec si
237     .end:
238     ; Now SI points to where we want to put our data
239     pop cx
240     mov di,si
241     jcxz .empty
242     add si,cx
243     cmp si,adv0.tail-2
244     jae .overflow ; CF=0
245    
246     mov si,bx
247     mov al,dl
248     stosb
249     mov al,cl
250     stosb
251     fs rep movsb
252    
253     .empty:
254     mov cx,adv0.tail
255     sub cx,di
256     xor ax,ax
257     rep stosb ; Zero-fill remainder
258    
259     clc
260     .done:
261     pop di
262     pop si
263     pop ax
264     ret
265     .overflow:
266     stc
267     jmp .done
268    
269     ;
270     ; adv_cleanup: checksum adv0 and copy to adv1
271     ; Assumes CS == DS == ES.
272     ;
273     adv_cleanup:
274     pushad
275     mov si,adv0.data
276     mov cx,ADV_LEN/4
277     xor edx,edx
278     .loop:
279     lodsd
280     add edx,eax
281     loop .loop
282     mov eax,ADV_MAGIC2
283     sub eax,edx
284     lea di,[si+4] ; adv1
285     mov si,adv0
286     mov [si+4],eax ; Store checksum
287     mov cx,(ADV_LEN+12)/4
288     rep movsd
289     popad
290     ret
291    
292     ;
293     ; adv_write: write the ADV to disk.
294     ;
295     ; Location is in memory variables.
296     ; Assumes CS == DS == ES.
297     ;
298     ; Returns CF=1 if the ADV cannot be written.
299     ;
300     adv_write:
301     cmp dword [ADVSec0],0
302     je .bad
303     cmp dword [ADVSec1],0
304     je .bad
305     cmp byte [ADVDrive],-1
306     je .bad
307    
308     push ax
309     call adv_cleanup
310     mov ah,3 ; Write
311     call adv_read_write
312     pop ax
313    
314     clc
315     ret
316     .bad: ; No location for ADV set
317     stc
318     ret
319    
320     ;
321     ; adv_read: read the ADV from disk
322     ;
323     ; Location is in memory variables.
324     ; Assumes CS == DS == ES.
325     ;
326     adv_read:
327     push ax
328     mov ah,2 ; Read
329     call adv_read_write
330     call adv_verify
331     pop ax
332     ret
333    
334     ;
335     ; adv_read_write: disk I/O for the ADV
336     ;
337     ; On input, AH=2 for read, AH=3 for write.
338     ; Assumes CS == DS == ES.
339     ;
340     adv_read_write:
341     mov [ADVOp],ah
342     pushad
343    
344     ; Check for EDD
345     mov bx,55AAh
346     mov ah,41h ; EDD existence query
347     mov dl,[ADVDrive]
348     int 13h
349     mov si,.cbios
350     jc .noedd
351     cmp bx,0AA55h
352     jne .noedd
353     test cl,1
354     jz .noedd
355     mov si,.ebios
356     .noedd:
357    
358     mov eax,[ADVSec0]
359     mov bx,adv0
360     call .doone
361    
362     mov eax,[ADVSec1]
363     mov bx,adv1
364     call .doone
365    
366     popad
367     ret
368    
369     .doone:
370     xor edx,edx ; Zero-extend LBA
371     push si
372     jmp si
373    
374     .ebios:
375     mov cx,adv_retries
376     .eb_retry:
377     ; Form DAPA on stack
378     push edx
379     push eax
380     push es
381     push bx
382     push word 1 ; Sector count
383     push word 16 ; DAPA size
384     mov si,sp
385     pushad
386     mov dl,[ADVDrive]
387     mov ax,4000h
388     or ah,[ADVOp]
389     push ds
390     push ss
391     pop ds
392     int 13h
393     pop ds
394     popad
395     lea sp,[si+16] ; Remove DAPA
396     jc .eb_error
397     pop si
398     ret
399     .eb_error:
400     loop .eb_retry
401     stc
402     pop si
403     ret
404    
405     .cbios:
406     push edx
407     push eax
408     push bp
409    
410     mov dl,[ADVDrive]
411     and dl,dl
412     ; Floppies: can't trust INT 13h 08h, we better know
413     ; the geometry a priori, which means it better be our
414     ; boot device...
415     jns .noparm ; Floppy drive... urk
416    
417     mov ah,08h ; Get disk parameters
418     int 13h
419     jc .noparm
420     and ah,ah
421     jnz .noparm
422     shr dx,8
423     inc dx
424     movzx edi,dx ; EDI = heads
425     and cx,3fh
426     movzx esi,cx ; ESI = sectors/track
427     jmp .parmok
428    
429     .noparm:
430     ; No CHS info... this better be our boot drive, then
431     %if IS_SYSLINUX || IS_EXTLINUX
432     cmp dl,[DriveNumber]
433     jne .cb_overflow ; Fatal error!
434     movzx esi,word [bsSecPerTrack]
435     movzx edi,word [bsHeads]
436     %else
437     ; Not a disk-based derivative... there is no hope
438     jmp .cb_overflow
439     %endif
440    
441     .parmok:
442     ;
443     ; Dividing by sectors to get (track,sector): we may have
444     ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
445     ;
446     div esi
447     xor cx,cx
448     xchg cx,dx ; CX <- sector index (0-based)
449     ; EDX <- 0
450     ; eax = track #
451     div edi ; Convert track to head/cyl
452    
453     ; Watch out for overflow, we might be writing!
454     cmp eax,1023
455     ja .cb_overflow
456    
457     ;
458     ; Now we have AX = cyl, DX = head, CX = sector (0-based),
459     ; BP = sectors to transfer, SI = bsSecPerTrack,
460     ; ES:BX = data target
461     ;
462    
463     shl ah,6 ; Because IBM was STOOPID
464     ; and thought 8 bits were enough
465     ; then thought 10 bits were enough...
466     inc cx ; Sector numbers are 1-based, sigh
467     or cl,ah
468     mov ch,al
469     mov dh,dl
470     mov dl,[ADVDrive]
471     mov al,01h ; Transfer one sector
472     mov ah,[ADVOp] ; Operation
473    
474     mov bp,adv_retries
475     .cb_retry:
476     pushad
477     int 13h
478     popad
479     jc .cb_error
480    
481     .cb_done:
482     pop bp
483     pop eax
484     pop edx
485     pop si
486     ret
487    
488     .cb_error:
489     dec bp
490     jnz .cb_retry
491     .cb_overflow:
492     stc
493     jmp .cb_done
494    
495     section .data
496     alignz 4
497     ADVSec0 dd 0 ; Not specified
498     ADVSec1 dd 0 ; Not specified
499     ADVDrive db -1 ; No ADV defined
500     ADVCHSInfo db -1 ; We have CHS info for this drive
501    
502     section .bss
503     ADVOp resb 1