version: Update to 4.08, update year to 2014
[syslinux/sherbszt.git] / core / diskstart.inc
blobb2ef2b6368788ec342a112929a3df6dfe4afc657
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 ;  Padding after the (minimum) 512-byte boot sector so that the rest of
27 ;  the file has aligned sectors, even if they are larger than 512 bytes.
28 ; ===========================================================================
30                 section .init
31 align_pad       zb 512
33 ; ===========================================================================
34 ;  Start of LDLINUX.SYS
35 ; ===========================================================================
37 LDLINUX_SYS     equ ($-$$)+TEXT_START
38 ldlinux_sys:
40 early_banner    db CR, LF, MY_NAME, ' ', VERSION_STR, ' ', 0
41                 db CR, LF, 1Ah  ; EOF if we "type" this in DOS
43                 alignz 8
44 ldlinux_magic   dd LDLINUX_MAGIC
45                 dd LDLINUX_MAGIC^HEXDATE
48 ; This area is patched by the installer.  It is found by looking for
49 ; LDLINUX_MAGIC, plus 8 bytes.
51 SUBVOL_MAX      equ 256
52 CURRENTDIR_MAX  equ FILENAME_MAX
54 patch_area:
55 DataSectors     dw 0            ; Number of sectors (not including bootsec)
56 ADVSectors      dw 0            ; Additional sectors for ADVs
57 LDLDwords       dd 0            ; Total dwords starting at ldlinux_sys,
58 CheckSum        dd 0            ; Checksum starting at ldlinux_sys
59                                 ; value = LDLINUX_MAGIC - [sum of dwords]
60 MaxTransfer     dw 127          ; Max sectors to transfer
61 EPAPtr          dw EPA - LDLINUX_SYS    ; Pointer to the extended patch area
64 ; Extended patch area -- this is in .data16 so it doesn't occupy space in
65 ; the first sector.  Use this structure for anything that isn't used by
66 ; the first sector itself.
68                 section .data16
69                 alignz 2
70 EPA:
71 ADVSecPtr       dw ADVSec0 - LDLINUX_SYS
72 CurrentDirPtr   dw CurrentDirName-LDLINUX_SYS   ; Current directory name string
73 CurrentDirLen   dw CURRENTDIR_MAX
74 SubvolPtr       dw SubvolName-LDLINUX_SYS
75 SubvolLen       dw SUBVOL_MAX
76 SecPtrOffset    dw SectorPtrs-LDLINUX_SYS
77 SecPtrCnt       dw (SectorPtrsEnd - SectorPtrs)/10
80 ; Boot sector patch pointers
82 Sect1Ptr0Ptr    dw Sect1Ptr0 - bootsec          ; Pointers to Sector 1 location
83 Sect1Ptr1Ptr    dw Sect1Ptr1 - bootsec
84 RAIDPatchPtr    dw kaboom.again - bootsec       ; Patch to INT 18h in RAID mode
87 ; Pointer to the Syslinux banner
89 BannerPtr       dw syslinux_banner - LDLINUX_SYS
92 ; Base directory name and subvolume, if applicable.
94 %define HAVE_CURRENTDIRNAME
95                 global CurrentDirName, SubvolName
96 CurrentDirName  times CURRENTDIR_MAX db 0
97 SubvolName      times SUBVOL_MAX db 0
99                 section .init
100 ldlinux_ent:
102 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
103 ; instead of 0000:7C00 and the like.  We don't want to add anything
104 ; more to the boot sector, so it is written to not assume a fixed
105 ; value in CS, but we don't want to deal with that anymore from now
106 ; on.
108                 jmp 0:.next     ; Normalize CS:IP
109 .next:          sti             ; In case of broken INT 13h BIOSes
112 ; Tell the user we got this far
114                 mov si,early_banner
115                 call writestr_early
118 ; Checksum data thus far
120                 mov si,ldlinux_sys
121                 mov cx,[bsBytesPerSec]
122                 shr cx,2
123                 mov edx,-LDLINUX_MAGIC
124 .checksum:
125                 lodsd
126                 add edx,eax
127                 loop .checksum
128                 mov [CheckSum],edx              ; Save intermediate result
129                 movzx ebx,si                    ; Start of the next sector
132 ; Tell the user if we're using EBIOS or CBIOS
134 print_bios:
135                 mov si,cbios_name
136                 cmp byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
137                 jne .cbios
138                 mov si,ebios_name
139                 mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
140 .cbios:
141                 mov [BIOSName],si
142                 call writestr_early
144                 section .earlybss
145                 alignb 2
146 %define HAVE_BIOSNAME 1
147 BIOSName        resw 1
149                 section .init
151 ; Now we read the rest of LDLINUX.SYS.
153 load_rest:
154                 push bx                         ; LSW of load address
156                 lea esi,[SectorPtrs]
157                 mov cx,[DataSectors]
158                 dec cx                          ; Minus this sector
160 .get_chunk:
161                 jcxz .done
162                 mov eax,[si]
163                 mov edx,[si+4]
164                 movzx ebp,word [si+8]
165                 sub cx,bp
166                 push ebx
167                 shr ebx,4                       ; Convert to a segment
168                 mov es,bx
169                 xor bx,bx
170                 call getlinsec
171                 pop ebx
172                 imul bp,[bsBytesPerSec]         ; Will be < 64K
173                 add ebx,ebp
174                 add si,10
175                 jmp .get_chunk
177 .done:
180 ; All loaded up, verify that we got what we needed.
181 ; Note: the checksum field is embedded in the checksum region, so
182 ; by the time we get to the end it should all cancel out.
184 verify_checksum:
185                 pop si                          ; LSW of load address
186                 movzx eax,word [bsBytesPerSec]
187                 shr ax,2
188                 mov ecx,[LDLDwords]             ; Total dwords
189                 sub ecx,eax                     ; ... minus one sector
190                 mov eax,[CheckSum]
191 .checksum:
192                 add eax,[si]
193                 add si,4
194                 jnz .nowrap
195                 ; Handle segment wrap
196                 mov dx,ds
197                 add dx,1000h
198                 mov ds,dx
199 .nowrap:
200                 dec ecx
201                 jnz .checksum
203                 mov ds,cx
205                 and eax,eax                     ; Should be zero
206                 jz all_read                     ; We're cool, go for it!
209 ; Uh-oh, something went bad...
211                 mov si,checksumerr_msg
212                 call writestr_early
213                 jmp kaboom
216 ; -----------------------------------------------------------------------------
217 ; Subroutines that have to be in the first sector
218 ; -----------------------------------------------------------------------------
223 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
224 ;            number in EAX into the buffer at ES:BX.  We try to optimize
225 ;            by loading up to a whole track at a time, but the user
226 ;            is responsible for not crossing a 64K boundary.
227 ;            (Yes, BP is weird for a count, but it was available...)
229 ;            On return, BX points to the first byte after the transferred
230 ;            block.
232 ;            This routine assumes CS == DS.
234                 global getlinsec
235 getlinsec:
236                 pushad
237                 add eax,[Hidden]                ; Add partition offset
238                 adc edx,[Hidden+4]
239 .jmp:           jmp strict short getlinsec_cbios
242 ; getlinsec_ebios:
244 ; getlinsec implementation for EBIOS (EDD)
246 getlinsec_ebios:
247 .loop:
248                 push bp                         ; Sectors left
249 .retry2:
250                 call maxtrans                   ; Enforce maximum transfer size
251                 movzx edi,bp                    ; Sectors we are about to read
252                 mov cx,retry_count
253 .retry:
255                 ; Form DAPA on stack
256                 push edx
257                 push eax
258                 push es
259                 push bx
260                 push di
261                 push word 16
262                 mov si,sp
263                 pushad
264                 mov ah,42h                      ; Extended Read
265                 push ds
266                 push ss
267                 pop ds
268                 call xint13
269                 pop ds
270                 popad
271                 lea sp,[si+16]                  ; Remove DAPA
272                 jc .error
273                 pop bp
274                 add eax,edi                     ; Advance sector pointer
275                 adc edx,0
276                 sub bp,di                       ; Sectors left
277                 imul di,[bsBytesPerSec]
278                 add bx,di                       ; Advance buffer pointer
279                 and bp,bp
280                 jnz .loop
282                 popad
283                 ret
285 .error:
286                 ; Some systems seem to get "stuck" in an error state when
287                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
288                 ; good, since some other systems get timeout failures
289                 ; waiting for the floppy disk to spin up.
291                 pushad                          ; Try resetting the device
292                 xor ax,ax
293                 call xint13
294                 popad
295                 loop .retry                     ; CX-- and jump if not zero
297                 ;shr word [MaxTransfer],1       ; Reduce the transfer size
298                 ;jnz .retry2
300                 ; Total failure.  Try falling back to CBIOS.
301                 mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
302                 ;mov byte [MaxTransfer],63      ; Max possibe CBIOS transfer
304                 pop bp
305                 ; ... fall through ...
308 ; getlinsec_cbios:
310 ; getlinsec implementation for legacy CBIOS
312 getlinsec_cbios:
313 .loop:
314                 push edx
315                 push eax
316                 push bp
317                 push bx
319                 movzx esi,word [bsSecPerTrack]
320                 movzx edi,word [bsHeads]
321                 ;
322                 ; Dividing by sectors to get (track,sector): we may have
323                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
324                 ;
325                 div esi
326                 xor cx,cx
327                 xchg cx,dx              ; CX <- sector index (0-based)
328                                         ; EDX <- 0
329                 ; eax = track #
330                 div edi                 ; Convert track to head/cyl
332                 cmp eax,1023            ; Outside the CHS range?
333                 ja kaboom
335                 ;
336                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
337                 ; BP = sectors to transfer, SI = bsSecPerTrack,
338                 ; ES:BX = data target
339                 ;
341                 call maxtrans                   ; Enforce maximum transfer size
343                 ; Must not cross track boundaries, so BP <= SI-CX
344                 sub si,cx
345                 cmp bp,si
346                 jna .bp_ok
347                 mov bp,si
348 .bp_ok:
350                 shl ah,6                ; Because IBM was STOOPID
351                                         ; and thought 8 bits were enough
352                                         ; then thought 10 bits were enough...
353                 inc cx                  ; Sector numbers are 1-based, sigh
354                 or cl,ah
355                 mov ch,al
356                 mov dh,dl
357                 xchg ax,bp              ; Sector to transfer count
358                 mov ah,02h              ; Read sectors
359                 mov bp,retry_count
360 .retry:
361                 pushad
362                 call xint13
363                 popad
364                 jc .error
365 .resume:
366                 movzx ecx,al            ; ECX <- sectors transferred
367                 imul ax,[bsBytesPerSec] ; Convert sectors in AL to bytes in AX
368                 pop bx
369                 add bx,ax
370                 pop bp
371                 pop eax
372                 pop edx
373                 add eax,ecx
374                 sub bp,cx
375                 jnz .loop
376                 popad
377                 ret
379 .error:
380                 dec bp
381                 jnz .retry
383                 xchg ax,bp              ; Sectors transferred <- 0
384                 shr word [MaxTransfer],1
385                 jnz .resume
386                 jmp kaboom
388 maxtrans:
389                 cmp bp,[MaxTransfer]
390                 jna .ok
391                 mov bp,[MaxTransfer]
392 .ok:            ret
396 ; writestr_early: write a null-terminated string to the console
397 ;           This assumes we're on page 0.  This is only used for early
398 ;           messages, so it should be OK.
400 writestr_early:
401                 pushad
402 .loop:          lodsb
403                 and al,al
404                 jz .return
405                 mov ah,0Eh              ; Write to screen as TTY
406                 mov bx,0007h            ; Attribute
407                 int 10h
408                 jmp short .loop
409 .return:        popad
410                 ret
413 ; Checksum error message
415 checksumerr_msg db ' Load error - ', 0  ; Boot failed appended
418 ; BIOS type string
420 cbios_name      db 'CHS', 0                     ; CHS/CBIOS
421 ebios_name      db 'EDD', 0                     ; EDD/EBIOS
424 ; Debug routine
426 %ifdef debug
427 safedumpregs:
428                 cmp word [Debug_Magic],0D00Dh
429                 jnz nc_return
430                 jmp dumpregs
431 %endif
433 rl_checkpt      equ $                           ; Must be <= 8000h
435 rl_checkpt_off  equ $-ldlinux_sys
436 %ifndef DEPEND
437  %if rl_checkpt_off > 512-10                    ; Need minimum one extent
438   %assign rl_checkpt_overflow rl_checkpt_off - (512-10)
439   %error Sector 1 overflow by rl_checkpt_overflow bytes
440  %endif
441 %endif
444 ; Extent pointers... each extent contains an 8-byte LBA and an 2-byte
445 ; sector count.  In most cases, we will only ever need a handful of
446 ; extents, but we have to assume a maximally fragmented system where each
447 ; extent contains only one sector.
449                 alignz 2
450 MaxInitDataSize equ 96 << 10
451 MaxLMA          equ LDLINUX_SYS+MaxInitDataSize
452 SectorPtrs      zb 10*(MaxInitDataSize >> MIN_SECTOR_SHIFT)
453 SectorPtrsEnd   equ $
455 ; ----------------------------------------------------------------------------
456 ;  End of code and data that have to be in the first sector
457 ; ----------------------------------------------------------------------------
459                 section .text16
460 all_read:
461                 ; We enter here with ES scrambled...
462                 xor ax,ax
463                 mov es,ax
465 ; Let the user (and programmer!) know we got this far.  This used to be
466 ; in Sector 1, but makes a lot more sense here.
468                 mov si,late_banner
469                 call writestr_early
471                 mov si,copyright_str
472                 call writestr_early
476 ; Insane hack to expand the DOS superblock to dwords
478 expand_super:
479                 xor eax,eax
480                 mov si,superblock
481                 mov di,SuperInfo
482                 mov cx,superinfo_size
483 .loop:
484                 lodsw
485                 dec si
486                 stosd                           ; Store expanded word
487                 xor ah,ah
488                 stosd                           ; Store expanded byte
489                 loop .loop
493 ; Common initialization code
495 %include "init.inc"
496                 
497                 pushad
498                 mov eax,ROOT_FS_OPS
499                 movzx dx,byte [DriveNumber]
500                 ; DH = 0: we are boot from disk not CDROM
501                 mov ecx,[Hidden]
502                 mov ebx,[Hidden+4]
503                 mov si,[bsHeads]
504                 mov di,[bsSecPerTrack]
505                 movzx ebp,word [MaxTransfer]
506                 pm_call fs_init
507                 popad
509                 section .bss16
510 SuperInfo       resq 16                 ; The first 16 bytes expanded 8 times
513 ; Banner information not needed in sector 1
515                 section .data16
516 syslinux_banner db CR, LF, MY_NAME, ' ', VERSION_STR
517 late_banner     db ' ', DATE_STR, 0
519                 section .text16