installer: fix 0 used as NULL
[syslinux/sherbszt.git] / core / diskstart.inc
blob875b40938543287ce06dcae23404300380c08a9d
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:data hidden, SubvolName:data hidden
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                 global BIOSName
146                 alignb 2
147 %define HAVE_BIOSNAME 1
148 BIOSName        resw 1
150                 section .init
152 ; Now we read the rest of LDLINUX.SYS.
154 load_rest:
155                 push bx                         ; LSW of load address
157                 lea esi,[SectorPtrs]
158                 mov cx,[DataSectors]
159                 dec cx                          ; Minus this sector
161 .get_chunk:
162                 jcxz .done
163                 mov eax,[si]
164                 mov edx,[si+4]
165                 movzx ebp,word [si+8]
166                 sub cx,bp
167                 push ebx
168                 shr ebx,4                       ; Convert to a segment
169                 mov es,bx
170                 xor bx,bx
171                 call getlinsec
172                 pop ebx
173                 imul bp,[bsBytesPerSec]         ; Will be < 64K
174                 add ebx,ebp
175                 add si,10
176                 jmp .get_chunk
178 .done:
181 ; All loaded up, verify that we got what we needed.
182 ; Note: the checksum field is embedded in the checksum region, so
183 ; by the time we get to the end it should all cancel out.
185 verify_checksum:
186                 pop si                          ; LSW of load address
187                 movzx eax,word [bsBytesPerSec]
188                 shr ax,2
189                 mov ecx,[LDLDwords]             ; Total dwords
190                 sub ecx,eax                     ; ... minus one sector
191                 mov eax,[CheckSum]
192 .checksum:
193                 add eax,[si]
194                 add si,4
195                 jnz .nowrap
196                 ; Handle segment wrap
197                 mov dx,ds
198                 add dx,1000h
199                 mov ds,dx
200 .nowrap:
201                 dec ecx
202                 jnz .checksum
204                 mov ds,cx
206                 and eax,eax                     ; Should be zero
207                 jz all_read                     ; We're cool, go for it!
210 ; Uh-oh, something went bad...
212                 mov si,checksumerr_msg
213                 call writestr_early
214                 jmp kaboom
217 ; -----------------------------------------------------------------------------
218 ; Subroutines that have to be in the first sector
219 ; -----------------------------------------------------------------------------
224 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
225 ;            number in EAX into the buffer at ES:BX.  We try to optimize
226 ;            by loading up to a whole track at a time, but the user
227 ;            is responsible for not crossing a 64K boundary.
228 ;            (Yes, BP is weird for a count, but it was available...)
230 ;            On return, BX points to the first byte after the transferred
231 ;            block.
233 ;            This routine assumes CS == DS.
235                 global getlinsec:function hidden
236 getlinsec:
237                 pushad
238                 add eax,[Hidden]                ; Add partition offset
239                 adc edx,[Hidden+4]
240 .jmp:           jmp strict short getlinsec_cbios
243 ; getlinsec_ebios:
245 ; getlinsec implementation for EBIOS (EDD)
247 getlinsec_ebios:
248 .loop:
249                 push bp                         ; Sectors left
250 .retry2:
251                 call maxtrans                   ; Enforce maximum transfer size
252                 movzx edi,bp                    ; Sectors we are about to read
253                 mov cx,retry_count
254 .retry:
256                 ; Form DAPA on stack
257                 push edx
258                 push eax
259                 push es
260                 push bx
261                 push di
262                 push word 16
263                 mov si,sp
264                 pushad
265                 mov ah,42h                      ; Extended Read
266                 push ds
267                 push ss
268                 pop ds
269                 call xint13
270                 pop ds
271                 popad
272                 lea sp,[si+16]                  ; Remove DAPA
273                 jc .error
274                 pop bp
275                 add eax,edi                     ; Advance sector pointer
276                 adc edx,0
277                 sub bp,di                       ; Sectors left
278                 imul di,[bsBytesPerSec]
279                 add bx,di                       ; Advance buffer pointer
280                 and bp,bp
281                 jnz .loop
283                 popad
284                 ret
286 .error:
287                 ; Some systems seem to get "stuck" in an error state when
288                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
289                 ; good, since some other systems get timeout failures
290                 ; waiting for the floppy disk to spin up.
292                 pushad                          ; Try resetting the device
293                 xor ax,ax
294                 call xint13
295                 popad
296                 loop .retry                     ; CX-- and jump if not zero
298                 ;shr word [MaxTransfer],1       ; Reduce the transfer size
299                 ;jnz .retry2
301                 ; Total failure.  Try falling back to CBIOS.
302                 mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
303                 ;mov byte [MaxTransfer],63      ; Max possibe CBIOS transfer
305                 pop bp
306                 ; ... fall through ...
309 ; getlinsec_cbios:
311 ; getlinsec implementation for legacy CBIOS
313 getlinsec_cbios:
314 .loop:
315                 push edx
316                 push eax
317                 push bp
318                 push bx
320                 movzx esi,word [bsSecPerTrack]
321                 movzx edi,word [bsHeads]
322                 ;
323                 ; Dividing by sectors to get (track,sector): we may have
324                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
325                 ;
326                 div esi
327                 xor cx,cx
328                 xchg cx,dx              ; CX <- sector index (0-based)
329                                         ; EDX <- 0
330                 ; eax = track #
331                 div edi                 ; Convert track to head/cyl
333                 cmp eax,1023            ; Outside the CHS range?
334                 ja kaboom
336                 ;
337                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
338                 ; BP = sectors to transfer, SI = bsSecPerTrack,
339                 ; ES:BX = data target
340                 ;
342                 call maxtrans                   ; Enforce maximum transfer size
344                 ; Must not cross track boundaries, so BP <= SI-CX
345                 sub si,cx
346                 cmp bp,si
347                 jna .bp_ok
348                 mov bp,si
349 .bp_ok:
351                 shl ah,6                ; Because IBM was STOOPID
352                                         ; and thought 8 bits were enough
353                                         ; then thought 10 bits were enough...
354                 inc cx                  ; Sector numbers are 1-based, sigh
355                 or cl,ah
356                 mov ch,al
357                 mov dh,dl
358                 xchg ax,bp              ; Sector to transfer count
359                 mov ah,02h              ; Read sectors
360                 mov bp,retry_count
361 .retry:
362                 pushad
363                 call xint13
364                 popad
365                 jc .error
366 .resume:
367                 movzx ecx,al            ; ECX <- sectors transferred
368                 imul ax,[bsBytesPerSec] ; Convert sectors in AL to bytes in AX
369                 pop bx
370                 add bx,ax
371                 pop bp
372                 pop eax
373                 pop edx
374                 add eax,ecx
375                 sub bp,cx
376                 jnz .loop
377                 popad
378                 ret
380 .error:
381                 dec bp
382                 jnz .retry
384                 xchg ax,bp              ; Sectors transferred <- 0
385                 shr word [MaxTransfer],1
386                 jnz .resume
387                 jmp kaboom
389 maxtrans:
390                 cmp bp,[MaxTransfer]
391                 jna .ok
392                 mov bp,[MaxTransfer]
393 .ok:            ret
397 ; writestr_early: write a null-terminated string to the console
398 ;           This assumes we're on page 0.  This is only used for early
399 ;           messages, so it should be OK.
401 writestr_early:
402                 pushad
403 .loop:          lodsb
404                 and al,al
405                 jz .return
406                 mov ah,0Eh              ; Write to screen as TTY
407                 mov bx,0007h            ; Attribute
408                 int 10h
409                 jmp short .loop
410 .return:        popad
411                 ret
414 ; Checksum error message
416 checksumerr_msg db ' Load error - ', 0  ; Boot failed appended
419 ; BIOS type string
421 cbios_name      db 'CHS', 0                     ; CHS/CBIOS
422 ebios_name      db 'EDD', 0                     ; EDD/EBIOS
425 ; Debug routine
427 %ifdef debug
428 safedumpregs:
429                 cmp word [Debug_Magic],0D00Dh
430                 jnz nc_return
431                 jmp dumpregs
432 %endif
434 rl_checkpt      equ $                           ; Must be <= 8000h
436 rl_checkpt_off  equ $-ldlinux_sys
437 %ifndef DEPEND
438  %if rl_checkpt_off > 512-10                    ; Need minimum one extent
439   %assign rl_checkpt_overflow rl_checkpt_off - (512-10)
440   %error Sector 1 overflow by rl_checkpt_overflow bytes
441  %endif
442 %endif
445 ; Extent pointers... each extent contains an 8-byte LBA and an 2-byte
446 ; sector count.  In most cases, we will only ever need a handful of
447 ; extents, but we have to assume a maximally fragmented system where each
448 ; extent contains only one sector.
450                 alignz 2
451 MaxInitDataSize equ 96 << 10
452 MaxLMA          equ LDLINUX_SYS+MaxInitDataSize
453 SectorPtrs      zb 10*(MaxInitDataSize >> MIN_SECTOR_SHIFT)
454 SectorPtrsEnd   equ $
456 ; ----------------------------------------------------------------------------
457 ;  End of code and data that have to be in the first sector
458 ; ----------------------------------------------------------------------------
460                 section .text16
461 all_read:
462                 ; We enter here with ES scrambled...
463                 xor ax,ax
464                 mov es,ax
466 ; Let the user (and programmer!) know we got this far.  This used to be
467 ; in Sector 1, but makes a lot more sense here.
469                 mov si,late_banner
470                 call writestr_early
472                 mov si,copyright_str
473                 call writestr_early
477 ; Insane hack to expand the DOS superblock to dwords
479 expand_super:
480                 xor eax,eax
481                 mov si,superblock
482                 mov di,SuperInfo
483                 mov cx,superinfo_size
484 .loop:
485                 lodsw
486                 dec si
487                 stosd                           ; Store expanded word
488                 xor ah,ah
489                 stosd                           ; Store expanded byte
490                 loop .loop
494 ; Common initialization code
496 %include "init.inc"
497                 
498                 pushad
499                 mov eax,ROOT_FS_OPS
500                 movzx dx,byte [DriveNumber]
501                 ; DH = 0: we are boot from disk not CDROM
502                 mov ecx,[Hidden]
503                 mov ebx,[Hidden+4]
504                 mov si,[bsHeads]
505                 mov di,[bsSecPerTrack]
506                 movzx ebp,word [MaxTransfer]
507                 pm_call pm_fs_init
508                 pm_call load_env32
509                 popad
511                 section .bss16
512 SuperInfo       resq 16                 ; The first 16 bytes expanded 8 times
515 ; Banner information not needed in sector 1
517                 section .data16
518                 global syslinux_banner
519 syslinux_banner db CR, LF, MY_NAME, ' ', VERSION_STR
520 late_banner     db ' ', DATE_STR, 0
522                 section .text16