com32/hdt/hdt-menu-summary.c: remove variables set but not used
[syslinux.git] / core / diskstart.inc
blobf31b72231123163aece0d4992717cdaec91d5f61
1 ; -----------------------------------------------------------------------
3 ;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
4 ;   Copyright 2009-2011 Intel Corporation; author: H. Peter Anvin
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., 51 Franklin St, Fifth Floor,
9 ;   Boston MA 02110-1301, USA; either version 2 of the License, or
10 ;   (at your option) any later version; incorporated herein by reference.
12 ; -----------------------------------------------------------------------
15 ; diskstart.inc
17 ; Common early-bootstrap code for harddisk-based Syslinux derivatives.
20 Sect1Ptr0_VAL   equ 0xdeadbeef
21 Sect1Ptr1_VAL   equ 0xfeedface
23 %include "diskboot.inc"
25 ; ===========================================================================
26 ;  Start of LDLINUX.SYS
27 ; ===========================================================================
29 LDLINUX_SYS     equ ($-$$)+TEXT_START
30 ldlinux_sys:
32 syslinux_banner db CR, LF, MY_NAME, ' ', VERSION_STR, ' ', DATE_STR, ' ', 0
33                 db CR, LF, 1Ah  ; EOF if we "type" this in DOS
35                 alignz 8
36 ldlinux_magic   dd LDLINUX_MAGIC
37                 dd LDLINUX_MAGIC^HEXDATE
40 ; This area is patched by the installer.  It is found by looking for
41 ; LDLINUX_MAGIC, plus 8 bytes.
43 SUBVOL_MAX      equ 256
44 CURRENTDIR_MAX  equ FILENAME_MAX
46 patch_area:
47 DataSectors     dw 0            ; Number of sectors (not including bootsec)
48 ADVSectors      dw 0            ; Additional sectors for ADVs
49 LDLDwords       dd 0            ; Total dwords starting at ldlinux_sys,
50 CheckSum        dd 0            ; Checksum starting at ldlinux_sys
51                                 ; value = LDLINUX_MAGIC - [sum of dwords]
52 MaxTransfer     dw 127          ; Max sectors to transfer
53 EPAPtr          dw EPA - LDLINUX_SYS    ; Pointer to the extended patch area
56 ; Extended patch area -- this is in .data16 so it doesn't occupy space in
57 ; the first sector.  Use this structure for anything that isn't used by
58 ; the first sector itself.
60                 section .data16
61                 alignz 2
62 EPA:
63 ADVSecPtr       dw ADVSec0 - LDLINUX_SYS
64 CurrentDirPtr   dw CurrentDirName-LDLINUX_SYS   ; Current directory name string
65 CurrentDirLen   dw CURRENTDIR_MAX
66 SubvolPtr       dw SubvolName-LDLINUX_SYS
67 SubvolLen       dw SUBVOL_MAX
68 SecPtrOffset    dw SectorPtrs-LDLINUX_SYS
69 SecPtrCnt       dw (SectorPtrsEnd - SectorPtrs)/10
72 ; Boot sector patch pointers
74 Sect1Ptr0Ptr    dw Sect1Ptr0 - bootsec          ; Pointers to Sector 1 location
75 Sect1Ptr1Ptr    dw Sect1Ptr1 - bootsec
76 RAIDPatchPtr    dw kaboom.again - bootsec       ; Patch to INT 18h in RAID mode
79 ; Base directory name and subvolume, if applicable.
81 %define HAVE_CURRENTDIRNAME
82                 global CurrentDirName, SubvolName
83 CurrentDirName  times CURRENTDIR_MAX db 0
84 SubvolName      times SUBVOL_MAX db 0
86                 section .init
87 ldlinux_ent:
89 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
90 ; instead of 0000:7C00 and the like.  We don't want to add anything
91 ; more to the boot sector, so it is written to not assume a fixed
92 ; value in CS, but we don't want to deal with that anymore from now
93 ; on.
95                 jmp 0:.next     ; Normalize CS:IP
96 .next:          sti             ; In case of broken INT 13h BIOSes
99 ; Tell the user we got this far
101                 mov si,syslinux_banner
102                 call writestr_early
105 ; Checksum data thus far
107                 mov si,ldlinux_sys
108                 mov cx,SECTOR_SIZE >> 2
109                 mov edx,-LDLINUX_MAGIC
110 .checksum:
111                 lodsd
112                 add edx,eax
113                 loop .checksum
114                 mov [CheckSum],edx              ; Save intermediate result
117 ; Tell the user if we're using EBIOS or CBIOS
119 print_bios:
120                 mov si,cbios_name
121                 cmp byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
122                 jne .cbios
123                 mov si,ebios_name
124                 mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
125 .cbios:
126                 mov [BIOSName],si
127                 call writestr_early
129                 section .earlybss
130 %define HAVE_BIOSNAME 1
131 BIOSName        resw 1
133                 section .init
135 ; Now we read the rest of LDLINUX.SYS.
137 load_rest:
138                 lea esi,[SectorPtrs]
139                 mov ebx,TEXT_START+2*SECTOR_SIZE ; Where we start loading
140                 mov cx,[DataSectors]
141                 dec cx                          ; Minus this sector
143 .get_chunk:
144                 jcxz .done
145                 mov eax,[si]
146                 mov edx,[si+4]
147                 movzx ebp,word [si+8]
148                 sub cx,bp
149                 push ebx
150                 shr ebx,4                       ; Convert to a segment
151                 mov es,bx
152                 xor bx,bx
153                 call getlinsec
154                 pop ebx
155                 shl ebp,SECTOR_SHIFT
156                 add ebx,ebp
157                 add si,10
158                 jmp .get_chunk
160 .done:
163 ; All loaded up, verify that we got what we needed.
164 ; Note: the checksum field is embedded in the checksum region, so
165 ; by the time we get to the end it should all cancel out.
167 verify_checksum:
168                 mov si,ldlinux_sys + SECTOR_SIZE
169                 mov ecx,[LDLDwords]
170                 sub ecx,SECTOR_SIZE >> 2
171                 mov eax,[CheckSum]
172 .checksum:
173                 add eax,[si]
174                 add si,4
175                 jnz .nowrap
176                 ; Handle segment wrap
177                 mov dx,ds
178                 add dx,1000h
179                 mov ds,dx
180 .nowrap:
181                 dec ecx
182                 jnz .checksum
184                 mov ds,cx
186                 and eax,eax                     ; Should be zero
187                 jz all_read                     ; We're cool, go for it!
190 ; Uh-oh, something went bad...
192                 mov si,checksumerr_msg
193                 call writestr_early
194                 jmp kaboom
197 ; -----------------------------------------------------------------------------
198 ; Subroutines that have to be in the first sector
199 ; -----------------------------------------------------------------------------
204 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
205 ;            number in EAX into the buffer at ES:BX.  We try to optimize
206 ;            by loading up to a whole track at a time, but the user
207 ;            is responsible for not crossing a 64K boundary.
208 ;            (Yes, BP is weird for a count, but it was available...)
210 ;            On return, BX points to the first byte after the transferred
211 ;            block.
213 ;            This routine assumes CS == DS.
215                 global getlinsec
216 getlinsec:
217                 pushad
218                 add eax,[Hidden]                ; Add partition offset
219                 adc edx,[Hidden+4]
220 .jmp:           jmp strict short getlinsec_cbios
223 ; getlinsec_ebios:
225 ; getlinsec implementation for EBIOS (EDD)
227 getlinsec_ebios:
228 .loop:
229                 push bp                         ; Sectors left
230 .retry2:
231                 call maxtrans                   ; Enforce maximum transfer size
232                 movzx edi,bp                    ; Sectors we are about to read
233                 mov cx,retry_count
234 .retry:
236                 ; Form DAPA on stack
237                 push edx
238                 push eax
239                 push es
240                 push bx
241                 push di
242                 push word 16
243                 mov si,sp
244                 pushad
245                 mov ah,42h                      ; Extended Read
246                 push ds
247                 push ss
248                 pop ds
249                 call xint13
250                 pop ds
251                 popad
252                 lea sp,[si+16]                  ; Remove DAPA
253                 jc .error
254                 pop bp
255                 add eax,edi                     ; Advance sector pointer
256                 adc edx,0
257                 sub bp,di                       ; Sectors left
258                 shl di,SECTOR_SHIFT             ; 512-byte sectors
259                 add bx,di                       ; Advance buffer pointer
260                 and bp,bp
261                 jnz .loop
263                 popad
264                 ret
266 .error:
267                 ; Some systems seem to get "stuck" in an error state when
268                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
269                 ; good, since some other systems get timeout failures
270                 ; waiting for the floppy disk to spin up.
272                 pushad                          ; Try resetting the device
273                 xor ax,ax
274                 call xint13
275                 popad
276                 loop .retry                     ; CX-- and jump if not zero
278                 ;shr word [MaxTransfer],1       ; Reduce the transfer size
279                 ;jnz .retry2
281                 ; Total failure.  Try falling back to CBIOS.
282                 mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
283                 ;mov byte [MaxTransfer],63      ; Max possibe CBIOS transfer
285                 pop bp
286                 ; ... fall through ...
289 ; getlinsec_cbios:
291 ; getlinsec implementation for legacy CBIOS
293 getlinsec_cbios:
294 .loop:
295                 push edx
296                 push eax
297                 push bp
298                 push bx
300                 movzx esi,word [bsSecPerTrack]
301                 movzx edi,word [bsHeads]
302                 ;
303                 ; Dividing by sectors to get (track,sector): we may have
304                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
305                 ;
306                 div esi
307                 xor cx,cx
308                 xchg cx,dx              ; CX <- sector index (0-based)
309                                         ; EDX <- 0
310                 ; eax = track #
311                 div edi                 ; Convert track to head/cyl
313                 cmp eax,1023            ; Outside the CHS range?
314                 ja kaboom
316                 ;
317                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
318                 ; BP = sectors to transfer, SI = bsSecPerTrack,
319                 ; ES:BX = data target
320                 ;
322                 call maxtrans                   ; Enforce maximum transfer size
324                 ; Must not cross track boundaries, so BP <= SI-CX
325                 sub si,cx
326                 cmp bp,si
327                 jna .bp_ok
328                 mov bp,si
329 .bp_ok:
331                 shl ah,6                ; Because IBM was STOOPID
332                                         ; and thought 8 bits were enough
333                                         ; then thought 10 bits were enough...
334                 inc cx                  ; Sector numbers are 1-based, sigh
335                 or cl,ah
336                 mov ch,al
337                 mov dh,dl
338                 xchg ax,bp              ; Sector to transfer count
339                 mov ah,02h              ; Read sectors
340                 mov bp,retry_count
341 .retry:
342                 pushad
343                 call xint13
344                 popad
345                 jc .error
346 .resume:
347                 movzx ecx,al            ; ECX <- sectors transferred
348                 shl ax,SECTOR_SHIFT     ; Convert sectors in AL to bytes in AX
349                 pop bx
350                 add bx,ax
351                 pop bp
352                 pop eax
353                 pop edx
354                 add eax,ecx
355                 sub bp,cx
356                 jnz .loop
357                 popad
358                 ret
360 .error:
361                 dec bp
362                 jnz .retry
364                 xchg ax,bp              ; Sectors transferred <- 0
365                 shr word [MaxTransfer],1
366                 jnz .resume
367                 jmp kaboom
369 maxtrans:
370                 cmp bp,[MaxTransfer]
371                 jna .ok
372                 mov bp,[MaxTransfer]
373 .ok:            ret
377 ; writestr_early: write a null-terminated string to the console
378 ;           This assumes we're on page 0.  This is only used for early
379 ;           messages, so it should be OK.
381 writestr_early:
382                 pushad
383 .loop:          lodsb
384                 and al,al
385                 jz .return
386                 mov ah,0Eh              ; Write to screen as TTY
387                 mov bx,0007h            ; Attribute
388                 int 10h
389                 jmp short .loop
390 .return:        popad
391                 ret
394 ; Checksum error message
396 checksumerr_msg db ' Load error - ', 0  ; Boot failed appended
399 ; BIOS type string
401 cbios_name      db 'CHS', 0                     ; CHS/CBIOS
402 ebios_name      db 'EDD', 0                     ; EDD/EBIOS
405 ; Debug routine
407 %ifdef debug
408 safedumpregs:
409                 cmp word [Debug_Magic],0D00Dh
410                 jnz nc_return
411                 jmp dumpregs
412 %endif
414 rl_checkpt      equ $                           ; Must be <= 8000h
416 rl_checkpt_off  equ ($-$$)
417 %ifndef DEPEND
418  %if rl_checkpt_off > 3F6h                      ; Need one extent
419   %assign rl_checkpt_overflow rl_checkpt_off - 3F6h
420   %error Sector 1 overflow by rl_checkpt_overflow bytes
421  %endif
422 %endif
425 ; Extent pointers... each extent contains an 8-byte LBA and an 2-byte
426 ; sector count.  In most cases, we will only ever need a handful of
427 ; extents, but we have to assume a maximally fragmented system where each
428 ; extent contains only one sector.
430                 alignz 2
431 MaxInitDataSize equ 96 << 10
432 MaxLMA          equ TEXT_START+SECTOR_SIZE+MaxInitDataSize
433 SectorPtrs      zb 10*(MaxInitDataSize >> SECTOR_SHIFT)
434 SectorPtrsEnd   equ $
436 ; ----------------------------------------------------------------------------
437 ;  End of code and data that have to be in the first sector
438 ; ----------------------------------------------------------------------------
440                 section .text16
441 all_read:
442                 ; We enter here with ES scrambled...
443                 xor ax,ax
444                 mov es,ax
446 ; Let the user (and programmer!) know we got this far.  This used to be
447 ; in Sector 1, but makes a lot more sense here.
449                 mov si,copyright_str
450                 call writestr_early
454 ; Insane hack to expand the DOS superblock to dwords
456 expand_super:
457                 xor eax,eax
458                 mov si,superblock
459                 mov di,SuperInfo
460                 mov cx,superinfo_size
461 .loop:
462                 lodsw
463                 dec si
464                 stosd                           ; Store expanded word
465                 xor ah,ah
466                 stosd                           ; Store expanded byte
467                 loop .loop
471 ; Common initialization code
473 %include "init.inc"
474                 
475                 pushad
476                 mov eax,ROOT_FS_OPS
477                 movzx dx,byte [DriveNumber]
478                 ; DH = 0: we are boot from disk not CDROM
479                 mov ecx,[Hidden]
480                 mov ebx,[Hidden+4]
481                 mov si,[bsHeads]
482                 mov di,[bsSecPerTrack]
483                 movzx ebp,word [MaxTransfer]
484                 pm_call fs_init
485                 popad
487                 section .bss16
488 SuperInfo       resq 16                 ; The first 16 bytes expanded 8 times
490                 section .text16