Releasing debian version 4.04+dfsg-9.
[syslinux-debian/hramrach.git] / core / diskstart.inc
blob02505a6b05b3cb301ad564deb2c751d63ef3c083
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 early_banner    db CR, LF, MY_NAME, ' ', VERSION_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 ; Pointer to the Syslinux banner
81 BannerPtr       dw syslinux_banner - LDLINUX_SYS
84 ; Base directory name and subvolume, if applicable.
86 %define HAVE_CURRENTDIRNAME
87                 global CurrentDirName, SubvolName
88 CurrentDirName  times CURRENTDIR_MAX db 0
89 SubvolName      times SUBVOL_MAX db 0
91                 section .init
92 ldlinux_ent:
94 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
95 ; instead of 0000:7C00 and the like.  We don't want to add anything
96 ; more to the boot sector, so it is written to not assume a fixed
97 ; value in CS, but we don't want to deal with that anymore from now
98 ; on.
100                 jmp 0:.next     ; Normalize CS:IP
101 .next:          sti             ; In case of broken INT 13h BIOSes
104 ; Tell the user we got this far
106                 mov si,early_banner
107                 call writestr_early
110 ; Checksum data thus far
112                 mov si,ldlinux_sys
113                 mov cx,SECTOR_SIZE >> 2
114                 mov edx,-LDLINUX_MAGIC
115 .checksum:
116                 lodsd
117                 add edx,eax
118                 loop .checksum
119                 mov [CheckSum],edx              ; Save intermediate result
122 ; Tell the user if we're using EBIOS or CBIOS
124 print_bios:
125                 mov si,cbios_name
126                 cmp byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
127                 jne .cbios
128                 mov si,ebios_name
129                 mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
130 .cbios:
131                 mov [BIOSName],si
132                 call writestr_early
134                 section .earlybss
135 %define HAVE_BIOSNAME 1
136 BIOSName        resw 1
138                 section .init
140 ; Now we read the rest of LDLINUX.SYS.
142 load_rest:
143                 lea esi,[SectorPtrs]
144                 mov ebx,TEXT_START+2*SECTOR_SIZE ; Where we start loading
145                 mov cx,[DataSectors]
146                 dec cx                          ; Minus this sector
148 .get_chunk:
149                 jcxz .done
150                 mov eax,[si]
151                 mov edx,[si+4]
152                 movzx ebp,word [si+8]
153                 sub cx,bp
154                 push ebx
155                 shr ebx,4                       ; Convert to a segment
156                 mov es,bx
157                 xor bx,bx
158                 call getlinsec
159                 pop ebx
160                 shl ebp,SECTOR_SHIFT
161                 add ebx,ebp
162                 add si,10
163                 jmp .get_chunk
165 .done:
168 ; All loaded up, verify that we got what we needed.
169 ; Note: the checksum field is embedded in the checksum region, so
170 ; by the time we get to the end it should all cancel out.
172 verify_checksum:
173                 mov si,ldlinux_sys + SECTOR_SIZE
174                 mov ecx,[LDLDwords]
175                 sub ecx,SECTOR_SIZE >> 2
176                 mov eax,[CheckSum]
177 .checksum:
178                 add eax,[si]
179                 add si,4
180                 jnz .nowrap
181                 ; Handle segment wrap
182                 mov dx,ds
183                 add dx,1000h
184                 mov ds,dx
185 .nowrap:
186                 dec ecx
187                 jnz .checksum
189                 mov ds,cx
191                 and eax,eax                     ; Should be zero
192                 jz all_read                     ; We're cool, go for it!
195 ; Uh-oh, something went bad...
197                 mov si,checksumerr_msg
198                 call writestr_early
199                 jmp kaboom
202 ; -----------------------------------------------------------------------------
203 ; Subroutines that have to be in the first sector
204 ; -----------------------------------------------------------------------------
209 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
210 ;            number in EAX into the buffer at ES:BX.  We try to optimize
211 ;            by loading up to a whole track at a time, but the user
212 ;            is responsible for not crossing a 64K boundary.
213 ;            (Yes, BP is weird for a count, but it was available...)
215 ;            On return, BX points to the first byte after the transferred
216 ;            block.
218 ;            This routine assumes CS == DS.
220                 global getlinsec
221 getlinsec:
222                 pushad
223                 add eax,[Hidden]                ; Add partition offset
224                 adc edx,[Hidden+4]
225 .jmp:           jmp strict short getlinsec_cbios
228 ; getlinsec_ebios:
230 ; getlinsec implementation for EBIOS (EDD)
232 getlinsec_ebios:
233 .loop:
234                 push bp                         ; Sectors left
235 .retry2:
236                 call maxtrans                   ; Enforce maximum transfer size
237                 movzx edi,bp                    ; Sectors we are about to read
238                 mov cx,retry_count
239 .retry:
241                 ; Form DAPA on stack
242                 push edx
243                 push eax
244                 push es
245                 push bx
246                 push di
247                 push word 16
248                 mov si,sp
249                 pushad
250                 mov ah,42h                      ; Extended Read
251                 push ds
252                 push ss
253                 pop ds
254                 call xint13
255                 pop ds
256                 popad
257                 lea sp,[si+16]                  ; Remove DAPA
258                 jc .error
259                 pop bp
260                 add eax,edi                     ; Advance sector pointer
261                 adc edx,0
262                 sub bp,di                       ; Sectors left
263                 shl di,SECTOR_SHIFT             ; 512-byte sectors
264                 add bx,di                       ; Advance buffer pointer
265                 and bp,bp
266                 jnz .loop
268                 popad
269                 ret
271 .error:
272                 ; Some systems seem to get "stuck" in an error state when
273                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
274                 ; good, since some other systems get timeout failures
275                 ; waiting for the floppy disk to spin up.
277                 pushad                          ; Try resetting the device
278                 xor ax,ax
279                 call xint13
280                 popad
281                 loop .retry                     ; CX-- and jump if not zero
283                 ;shr word [MaxTransfer],1       ; Reduce the transfer size
284                 ;jnz .retry2
286                 ; Total failure.  Try falling back to CBIOS.
287                 mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
288                 ;mov byte [MaxTransfer],63      ; Max possibe CBIOS transfer
290                 pop bp
291                 ; ... fall through ...
294 ; getlinsec_cbios:
296 ; getlinsec implementation for legacy CBIOS
298 getlinsec_cbios:
299 .loop:
300                 push edx
301                 push eax
302                 push bp
303                 push bx
305                 movzx esi,word [bsSecPerTrack]
306                 movzx edi,word [bsHeads]
307                 ;
308                 ; Dividing by sectors to get (track,sector): we may have
309                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
310                 ;
311                 div esi
312                 xor cx,cx
313                 xchg cx,dx              ; CX <- sector index (0-based)
314                                         ; EDX <- 0
315                 ; eax = track #
316                 div edi                 ; Convert track to head/cyl
318                 cmp eax,1023            ; Outside the CHS range?
319                 ja kaboom
321                 ;
322                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
323                 ; BP = sectors to transfer, SI = bsSecPerTrack,
324                 ; ES:BX = data target
325                 ;
327                 call maxtrans                   ; Enforce maximum transfer size
329                 ; Must not cross track boundaries, so BP <= SI-CX
330                 sub si,cx
331                 cmp bp,si
332                 jna .bp_ok
333                 mov bp,si
334 .bp_ok:
336                 shl ah,6                ; Because IBM was STOOPID
337                                         ; and thought 8 bits were enough
338                                         ; then thought 10 bits were enough...
339                 inc cx                  ; Sector numbers are 1-based, sigh
340                 or cl,ah
341                 mov ch,al
342                 mov dh,dl
343                 xchg ax,bp              ; Sector to transfer count
344                 mov ah,02h              ; Read sectors
345                 mov bp,retry_count
346 .retry:
347                 pushad
348                 call xint13
349                 popad
350                 jc .error
351 .resume:
352                 movzx ecx,al            ; ECX <- sectors transferred
353                 shl ax,SECTOR_SHIFT     ; Convert sectors in AL to bytes in AX
354                 pop bx
355                 add bx,ax
356                 pop bp
357                 pop eax
358                 pop edx
359                 add eax,ecx
360                 sub bp,cx
361                 jnz .loop
362                 popad
363                 ret
365 .error:
366                 dec bp
367                 jnz .retry
369                 xchg ax,bp              ; Sectors transferred <- 0
370                 shr word [MaxTransfer],1
371                 jnz .resume
372                 jmp kaboom
374 maxtrans:
375                 cmp bp,[MaxTransfer]
376                 jna .ok
377                 mov bp,[MaxTransfer]
378 .ok:            ret
382 ; writestr_early: write a null-terminated string to the console
383 ;           This assumes we're on page 0.  This is only used for early
384 ;           messages, so it should be OK.
386 writestr_early:
387                 pushad
388 .loop:          lodsb
389                 and al,al
390                 jz .return
391                 mov ah,0Eh              ; Write to screen as TTY
392                 mov bx,0007h            ; Attribute
393                 int 10h
394                 jmp short .loop
395 .return:        popad
396                 ret
399 ; Checksum error message
401 checksumerr_msg db ' Load error - ', 0  ; Boot failed appended
404 ; BIOS type string
406 cbios_name      db 'CHS', 0                     ; CHS/CBIOS
407 ebios_name      db 'EDD', 0                     ; EDD/EBIOS
410 ; Debug routine
412 %ifdef debug
413 safedumpregs:
414                 cmp word [Debug_Magic],0D00Dh
415                 jnz nc_return
416                 jmp dumpregs
417 %endif
419 rl_checkpt      equ $                           ; Must be <= 8000h
421 rl_checkpt_off  equ ($-$$)
422 %ifndef DEPEND
423  %if rl_checkpt_off > 3F6h                      ; Need one extent
424   %assign rl_checkpt_overflow rl_checkpt_off - 3F6h
425   %error Sector 1 overflow by rl_checkpt_overflow bytes
426  %endif
427 %endif
430 ; Extent pointers... each extent contains an 8-byte LBA and an 2-byte
431 ; sector count.  In most cases, we will only ever need a handful of
432 ; extents, but we have to assume a maximally fragmented system where each
433 ; extent contains only one sector.
435                 alignz 2
436 MaxInitDataSize equ 96 << 10
437 MaxLMA          equ TEXT_START+SECTOR_SIZE+MaxInitDataSize
438 SectorPtrs      zb 10*(MaxInitDataSize >> SECTOR_SHIFT)
439 SectorPtrsEnd   equ $
441 ; ----------------------------------------------------------------------------
442 ;  End of code and data that have to be in the first sector
443 ; ----------------------------------------------------------------------------
445                 section .text16
446 all_read:
447                 ; We enter here with ES scrambled...
448                 xor ax,ax
449                 mov es,ax
451 ; Let the user (and programmer!) know we got this far.  This used to be
452 ; in Sector 1, but makes a lot more sense here.
454                 mov si,late_banner
455                 call writestr_early
457                 mov si,copyright_str
458                 call writestr_early
462 ; Insane hack to expand the DOS superblock to dwords
464 expand_super:
465                 xor eax,eax
466                 mov si,superblock
467                 mov di,SuperInfo
468                 mov cx,superinfo_size
469 .loop:
470                 lodsw
471                 dec si
472                 stosd                           ; Store expanded word
473                 xor ah,ah
474                 stosd                           ; Store expanded byte
475                 loop .loop
479 ; Common initialization code
481 %include "init.inc"
482                 
483                 pushad
484                 mov eax,ROOT_FS_OPS
485                 movzx dx,byte [DriveNumber]
486                 ; DH = 0: we are boot from disk not CDROM
487                 mov ecx,[Hidden]
488                 mov ebx,[Hidden+4]
489                 mov si,[bsHeads]
490                 mov di,[bsSecPerTrack]
491                 movzx ebp,word [MaxTransfer]
492                 pm_call fs_init
493                 popad
495                 section .bss16
496 SuperInfo       resq 16                 ; The first 16 bytes expanded 8 times
499 ; Banner information not needed in sector 1
501                 section .data16
502 syslinux_banner db CR, LF, MY_NAME, ' ', VERSION_STR
503 late_banner     db ' ', DATE_STR, 0
505                 section .text16