version: Update to 4.08, update year to 2014
[syslinux/sherbszt.git] / core / adv.inc
blob0b45a6c72be6b5cd412584d854cb4f1ddbecef64
1 ;; -----------------------------------------------------------------------
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.
11 ;; -----------------------------------------------------------------------
14 ;; adv.inc
16 ;; The auxillary data vector and its routines
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.
26 ;; Note that unlike BOOTP/DHCP, zero terminates the chain, and FF
27 ;; has no special meaning.
31 ;; List of ADV tags...
33 ADV_BOOTONCE    equ 1
36 ;; Other ADV data...
38 ADV_MAGIC1      equ 0x5a2d2fa5                  ; Head signature
39 ADV_MAGIC2      equ 0xa3041767                  ; Total checksum
40 ADV_MAGIC3      equ 0xdd28bf64                  ; Tail signature
42 ADV_LEN         equ 500                         ; Data bytes
44 adv_retries     equ 6                           ; Disk retries
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 .text16
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
70 %if IS_SYSLINUX || IS_EXTLINUX
71                 cmp word [ADVSectors],2         ; Not present?
72                 jb adv_verify
74                 mov eax,[Hidden]
75                 mov edx,[Hidden+4]
76                 add [ADVSec0],eax
77                 adc [ADVSec0+4],edx
78                 add [ADVSec1],eax
79                 adc [ADVSec1+4],edx
80                 mov al,[DriveNumber]
81                 mov [ADVDrive],al
82                 jmp adv_read
83 %endif
85                 ;
86                 ; Initialize the ADV data structure in memory
87                 ;
88 adv_verify:
89                 cmp byte [ADVDrive],-1          ; No ADV configured, still?
90                 je .reset                       ; Then unconditionally reset
92                 mov si,adv0
93                 call .check_adv
94                 jz .ok                          ; Primary ADV okay
95                 mov si,adv1
96                 call .check_adv
97                 jz .adv1ok
99                 ; Neither ADV is usable; initialize to blank
100 .reset:
101                 mov di,adv0
102                 mov eax,ADV_MAGIC1
103                 stosd
104                 mov eax,ADV_MAGIC2
105                 stosd
106                 xor eax,eax
107                 mov cx,ADV_LEN/4
108                 rep stosd
109                 mov eax,ADV_MAGIC3
110                 stosd
112 .ok:
113                 ret
115                 ; The primary ADV is bad, but the backup is OK
116 .adv1ok:
117                 mov di,adv0
118                 mov cx,512/4
119                 rep movsd
120                 ret
123                 ; SI points to the putative ADV; unchanged by routine
124                 ; ZF=1 on return if good
125 .check_adv:
126                 push si
127                 lodsd
128                 cmp eax,ADV_MAGIC1
129                 jne .done                       ; ZF=0, i.e. bad
130                 xor edx,edx
131                 mov cx,ADV_LEN/4+1              ; Remaining dwords
132 .csum:
133                 lodsd
134                 add edx,eax
135                 loop .csum
136                 cmp edx,ADV_MAGIC2
137                 jne .done
138                 lodsd
139                 cmp eax,ADV_MAGIC3
140 .done:
141                 pop si
142                 ret
145 ; adv_get: find an ADV string if present
147 ; Input:        DL      = ADV ID
148 ; Output:       CX      = byte count (zero on not found)
149 ;               SI      = pointer to data
150 ;               DL      = unchanged
152 ; Assumes CS == DS.
155 adv_get:
156                 push ax
157                 mov si,adv0.data
158                 xor ax,ax                       ; Keep AH=0 at all times
159 .loop:
160                 lodsb                           ; Read ID
161                 cmp al,dl
162                 je .found
163                 and al,al
164                 jz .end
165                 lodsb                           ; Read length
166                 add si,ax
167                 cmp si,adv0.tail
168                 jb .loop
169                 jmp .end
171 .found:
172                 lodsb
173                 mov cx,ax
174                 add ax,si                       ; Make sure it fits
175                 cmp ax,adv0.tail
176                 jbe .ok
177 .end:
178                 xor cx,cx
179 .ok:
180                 pop ax
181                 ret
184 ; adv_set: insert a string into the ADV in memory
186 ; Input:        DL      = ADV ID
187 ;               FS:BX   = input buffer
188 ;               CX      = byte count (max = 255!)
189 ; Output:       CF=1 on error
190 ;               CX      clobbered
192 ; Assumes CS == DS == ES.
194 adv_set:
195                 push ax
196                 push si
197                 push di
198                 and ch,ch
199                 jnz .overflow
201                 push cx
202                 mov si,adv0.data
203                 xor ax,ax
204 .loop:
205                 lodsb
206                 cmp al,dl
207                 je .found
208                 and al,al
209                 jz .endz
210                 lodsb
211                 add si,ax
212                 cmp si,adv0.tail
213                 jb .loop
214                 jmp .end
216 .found:         ; Found, need to delete old copy
217                 lodsb
218                 lea di,[si-2]
219                 push di
220                 add si,ax
221                 mov cx,adv0.tail
222                 sub cx,si
223                 jb .nukeit
224                 rep movsb                       ; Remove the old one
225                 mov [di],ah                     ; Termination zero
226                 pop si
227                 jmp .loop
228 .nukeit:
229                 pop si
230                 jmp .end
231 .endz:
232                 dec si
233 .end:
234                 ; Now SI points to where we want to put our data
235                 pop cx
236                 mov di,si
237                 jcxz .empty
238                 add si,cx
239                 cmp si,adv0.tail-2
240                 jae .overflow                   ; CF=0
242                 mov si,bx
243                 mov al,dl
244                 stosb
245                 mov al,cl
246                 stosb
247                 fs rep movsb
249 .empty:
250                 mov cx,adv0.tail
251                 sub cx,di
252                 xor ax,ax
253                 rep stosb                       ; Zero-fill remainder
255                 clc
256 .done:
257                 pop di
258                 pop si
259                 pop ax
260                 ret
261 .overflow:
262                 stc
263                 jmp .done
266 ; adv_cleanup:  checksum adv0 and copy to adv1
267 ;               Assumes CS == DS == ES.
269 adv_cleanup:
270                 pushad
271                 mov si,adv0.data
272                 mov cx,ADV_LEN/4
273                 xor edx,edx
274 .loop:
275                 lodsd
276                 add edx,eax
277                 loop .loop
278                 mov eax,ADV_MAGIC2
279                 sub eax,edx
280                 lea di,[si+4]                   ; adv1
281                 mov si,adv0
282                 mov [si+4],eax                  ; Store checksum
283                 mov cx,(ADV_LEN+12)/4
284                 rep movsd
285                 popad
286                 ret
289 ; adv_write:    write the ADV to disk.
291 ;               Location is in memory variables.
292 ;               Assumes CS == DS == ES.
294 ;               Returns CF=1 if the ADV cannot be written.
296 adv_write:
297                 push eax
298                 mov eax,[ADVSec0]
299                 or eax,[ADVSec0+4]
300                 je .bad
301                 mov eax,[ADVSec1]
302                 or eax,[ADVSec1+4]
303                 je .bad
304                 cmp byte [ADVDrive],-1
305                 je .bad
307                 call adv_cleanup
308                 mov ah,3                        ; Write
309                 call adv_read_write
311                 clc
312                 pop eax
313                 ret
314 .bad:                                           ; No location for ADV set
315                 stc
316                 pop eax
317                 ret
320 ; adv_read:     read the ADV from disk
322 ;               Location is in memory variables.
323 ;               Assumes CS == DS == ES.
325 adv_read:
326                 push ax
327                 mov ah,2                        ; Read
328                 call adv_read_write
329                 call adv_verify
330                 pop ax
331                 ret
334 ; adv_read_write: disk I/O for the ADV
336 ;               On input, AH=2 for read, AH=3 for write.
337 ;               Assumes CS == DS == ES.
339 adv_read_write:
340                 mov [ADVOp],ah
341                 pushad
343                 ; Check for EDD
344                 mov bx,55AAh
345                 mov ah,41h                      ; EDD existence query
346                 mov dl,[ADVDrive]
347                 int 13h
348                 mov si,.cbios
349                 jc .noedd
350                 cmp bx,0AA55h
351                 jne .noedd
352                 test cl,1
353                 jz .noedd
354                 mov si,.ebios
355 .noedd:
357                 mov eax,[ADVSec0]
358                 mov edx,[ADVSec0+4]
359                 mov bx,adv0
360                 call .doone
362                 mov eax,[ADVSec1]
363                 mov edx,[ADVSec1+4]
364                 mov bx,adv1
365                 call .doone
367                 popad
368                 ret
370 .doone:
371                 push si
372                 jmp si
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
405 .cbios:
406                 push edx
407                 push eax
408                 push bp
410                 and edx,edx                     ; > 2 TiB not possible
411                 jnz .cb_overflow
413                 mov dl,[ADVDrive]
414                 and dl,dl
415                 ; Floppies: can't trust INT 13h 08h, we better know
416                 ; the geometry a priori, which means it better be our
417                 ; boot device...
418                 jns .noparm                     ; Floppy drive... urk
420                 mov ah,08h                      ; Get disk parameters
421                 int 13h
422                 jc .noparm
423                 and ah,ah
424                 jnz .noparm
425                 shr dx,8
426                 inc dx
427                 movzx edi,dx                    ; EDI = heads
428                 and cx,3fh
429                 movzx esi,cx                    ; ESI = sectors/track
430                 jmp .parmok
432 .noparm:
433                 ; No CHS info... this better be our boot drive, then
434 %if IS_SYSLINUX || IS_EXTLINUX
435                 cmp dl,[DriveNumber]
436                 jne .cb_overflow                ; Fatal error!
437                 movzx esi,word [bsSecPerTrack]
438                 movzx edi,word [bsHeads]
439 %else
440                 ; Not a disk-based derivative... there is no hope
441                 jmp .cb_overflow
442 %endif
444 .parmok:
445                 ;
446                 ; Dividing by sectors to get (track,sector): we may have
447                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
448                 ;
449                 xor edx,edx
450                 div esi
451                 xor cx,cx
452                 xchg cx,dx              ; CX <- sector index (0-based)
453                                         ; EDX <- 0
454                 ; eax = track #
455                 div edi                 ; Convert track to head/cyl
457                 ; Watch out for overflow, we might be writing!
458                 cmp eax,1023
459                 ja .cb_overflow
461                 ;
462                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
463                 ; BP = sectors to transfer, SI = bsSecPerTrack,
464                 ; ES:BX = data target
465                 ;
467                 shl ah,6                ; Because IBM was STOOPID
468                                         ; and thought 8 bits were enough
469                                         ; then thought 10 bits were enough...
470                 inc cx                  ; Sector numbers are 1-based, sigh
471                 or cl,ah
472                 mov ch,al
473                 mov dh,dl
474                 mov dl,[ADVDrive]
475                 mov al,01h              ; Transfer one sector
476                 mov ah,[ADVOp]          ; Operation
478                 mov bp,adv_retries
479 .cb_retry:
480                 pushad
481                 int 13h
482                 popad
483                 jc .cb_error
485 .cb_done:
486                 pop bp
487                 pop eax
488                 pop edx
489                 pop si
490                 ret
492 .cb_error:
493                 dec bp
494                 jnz .cb_retry
495 .cb_overflow:
496                 stc
497                 jmp .cb_done
499                 section .data16
500                 alignz 8
501 ADVSec0         dq 0                    ; Not specified
502 ADVSec1         dq 0                    ; Not specified
503 ADVDrive        db -1                   ; No ADV defined
504 ADVCHSInfo      db -1                   ; We have CHS info for this drive
506                 section .bss16
507 ADVOp           resb 1
509                 section .text16