core, bios: Move __syslinux_shuffler_size to assembly
[syslinux/sherbszt.git] / core / diskboot.inc
blobce75b8c9f745d727d44d9d2ea0a20598af45be44
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 ; diskboot.inc
17 ; Common boot sector code for harddisk-based Syslinux derivatives.
19 ; Requires macros z[bwd], labels ldlinux_ent, ldlinux_magic, ldlinux_sys
20 ; and constants BS_MAGIC_VER, LDLINUX_MAGIC, retry_count, Sect1Ptr[01]_VAL,
21 ; STACK_TOP
24                 section .init
26 ; Some of the things that have to be saved very early are saved
27 ; "close" to the initial stack pointer offset, in order to
28 ; reduce the code size...
31                 global StackBuf, PartInfo, Hidden, OrigESDI, DriveNumber
32 StackBuf        equ STACK_TOP-44-92     ; Start the stack here (grow down - 4K)
33 PartInfo        equ StackBuf
34 .mbr            equ PartInfo
35 .gptlen         equ PartInfo+16
36 .gpt            equ PartInfo+20
37 FloppyTable     equ PartInfo+76
38 ; Total size of PartInfo + FloppyTable == 76+16 = 92 bytes
39 Hidden          equ StackBuf-24         ; Partition offset (qword)
40 OrigFDCTabPtr   equ StackBuf-16         ; Original FDC table
41 OrigDSSI        equ StackBuf-12         ; DS:SI -> partinfo
42 OrigESDI        equ StackBuf-8          ; ES:DI -> $PnP structure
43 DriveNumber     equ StackBuf-4          ; Drive number
44 StackHome       equ Hidden              ; The start of the canonical stack
47 ; Primary entry point.  Tempting as though it may be, we can't put the
48 ; initial "cli" here; the jmp opcode in the first byte is part of the
49 ; "magic number" (using the term very loosely) for the DOS superblock.
51 bootsec         equ $
52 _start:         jmp short start         ; 2 bytes
53                 nop                     ; 1 byte
55 ; "Superblock" follows -- it's in the boot sector, so it's already
56 ; loaded and ready for us
58 bsOemName       db MY_NAME              ; The SYS command sets this, so...
59                 zb 8-($-bsOemName)
62 ; These are the fields we actually care about.  We end up expanding them
63 ; all to dword size early in the code, so generate labels for both
64 ; the expanded and unexpanded versions.
66 %macro          superb 1
67 bx %+ %1        equ SuperInfo+($-superblock)*8+4
68 bs %+ %1        equ $
69                 zb 1
70 %endmacro
71 %macro          superw 1
72 bx %+ %1        equ SuperInfo+($-superblock)*8
73 bs %+ %1        equ $
74                 zw 1
75 %endmacro
76 %macro          superd 1
77 bx %+ %1        equ $                   ; no expansion for dwords
78 bs %+ %1        equ $
79                 zd 1
80 %endmacro
81 superblock      equ $
82                 superw BytesPerSec
83                 superb SecPerClust
84                 superw ResSectors
85                 superb FATs
86                 superw RootDirEnts
87                 superw Sectors
88                 superb Media
89                 superw FATsecs
90                 superw SecPerTrack
91                 superw Heads
92 superinfo_size  equ ($-superblock)-1    ; How much to expand
93                 superd Hidden
94                 superd HugeSectors
95                 ;
96                 ; This is as far as FAT12/16 and FAT32 are consistent
97                 ;
98                 ; FAT12/16 need 26 more bytes,
99                 ; FAT32 need 54 more bytes
100                 ;
101 superblock_len_fat16    equ $-superblock+26
102 superblock_len_fat32    equ $-superblock+54
103                 zb 54                   ; Maximum needed size
104 superblock_max  equ $-superblock
106 SecPerClust     equ bxSecPerClust
109 ; Note we don't check the constraints above now; we did that at install
110 ; time (we hope!)
112 start:
113                 cli                     ; No interrupts yet, please
114                 cld                     ; Copy upwards
116 ; Set up the stack
118                 xor cx,cx
119                 mov ss,cx
120                 mov sp,StackBuf-2       ; Just below BSS (-2 for alignment)
121                 push dx                 ; Save drive number (in DL)
122                 push es                 ; Save initial ES:DI -> $PnP pointer
123                 push di
124                 push ds                 ; Save original DS:SI -> partinfo
125                 push si
126                 mov es,cx
129 ; DS:SI may contain a partition table entry and possibly a GPT entry.
130 ; Preserve it for us.  This saves 56 bytes of the GPT entry, which is
131 ; currently the maximum we care about.  Total is 76 bytes.
133                 mov cl,(16+4+56)/2      ; Save partition info
134                 mov di,PartInfo
135                 rep movsw               ; This puts CX back to zero
137                 mov ds,cx               ; Now we can initialize DS...
140 ; Now sautee the BIOS floppy info block to that it will support decent-
141 ; size transfers; the floppy block is 11 bytes and is stored in the
142 ; INT 1Eh vector (brilliant waste of resources, eh?)
144 ; Of course, if BIOSes had been properly programmed, we wouldn't have
145 ; had to waste precious space with this code.
147                 mov bx,fdctab
148                 lfs si,[bx]             ; FS:SI -> original fdctab
149                 push fs                 ; Save on stack in case we need to bail
150                 push si
152                 ; Save the old fdctab even if hard disk so the stack layout
153                 ; is the same.  The instructions above do not change the flags
154                 and dl,dl               ; If floppy disk (00-7F), assume no
155                                         ; partition table
156                 js harddisk
158 floppy:
159                 xor ax,ax
160                 mov cl,6                ; 12 bytes (CX == 0)
161                 ; es:di -> FloppyTable already
162                 ; This should be safe to do now, interrupts are off...
163                 mov [bx],di             ; FloppyTable
164                 mov [bx+2],ax           ; Segment 0
165                 fs rep movsw            ; Faster to move words
166                 mov cl,[bsSecPerTrack]  ; Patch the sector count
167                 mov [di-12+4],cl
169                 push ax                 ; Partition offset == 0
170                 push ax
171                 push ax
172                 push ax
174                 int 13h                 ; Some BIOSes need this
175                         ; Using xint13 costs +1B
176                 jmp short not_harddisk
178 ; The drive number and possibly partition information was passed to us
179 ; by the BIOS or previous boot loader (MBR).  Current "best practice" is to
180 ; trust that rather than what the superblock contains.
182 ; Note: di points to beyond the end of PartInfo
183 ; Note: false negatives might slip through the handover area's sanity checks,
184 ;       if the region is very close (less than a paragraph) to
185 ;       PartInfo ; no false positives are possible though
187 harddisk:
188                 mov dx,[di-76-10]       ; Original DS
189                 mov si,[di-76-12]       ; Original SI
190                 shr si,4
191                 add dx,si
192                 cmp dx,4fh              ; DS:SI < 50h:0 (BDA or IVT) ?
193                 jbe .no_partition
194                 cmp dx,(PartInfo-75)>>4 ; DS:SI in overwritten memory?
195                 jae .no_partition
196                 test byte [di-76],7Fh   ; Sanity check: "active flag" should
197                 jnz .no_partition       ; be 00 or 80
198                 cmp [di-76+4],cl        ; Sanity check: partition type != 0
199                 je .no_partition
200                 cmp eax,'!GPT'          ; !GPT signature?
201                 jne .mbr
202                 cmp byte [di-76+4],0EDh ; Synthetic GPT partition entry?
203                 jne .mbr
204 .gpt:                                   ; GPT-style partition info
205                 push dword [di-76+20+36]
206                 push dword [di-76+20+32]
207                 jmp .gotoffs
208 .mbr:                                   ; MBR-style partition info
209                 push cx                 ; Upper half partition offset == 0
210                 push cx
211                 push dword [di-76+8]    ; Partition offset (dword)
212                 jmp .gotoffs
213 .no_partition:
215 ; No partition table given... assume that the Hidden field in the boot sector
216 ; tells the truth (in particular, is zero if this is an unpartitioned disk.)
218                 push cx
219                 push cx
220                 push dword [bsHidden]
221 .gotoffs:
223 ; Get disk drive parameters (don't trust the superblock.)  Don't do this for
224 ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
225 ; what the *drive* supports, not about the *media*.  Fortunately floppy disks
226 ; tend to have a fixed, well-defined geometry which is stored in the superblock.
228                 ; DL == drive # still
229                 mov ah,08h
230                 call xint13
231                 jc no_driveparm
232                 and ah,ah
233                 jnz no_driveparm
234                 shr dx,8
235                 inc dx                  ; Contains # of heads - 1
236                 mov [bsHeads],dx
237                 and cx,3fh
238                 mov [bsSecPerTrack],cx
239 no_driveparm:
240 not_harddisk:
242 ; Ready to enable interrupts, captain
244                 sti
247 ; Do we have EBIOS (EDD)?
249 eddcheck:
250                 mov bx,55AAh
251                 mov ah,41h              ; EDD existence query
252                 call xint13
253                 jc .noedd
254                 cmp bx,0AA55h
255                 jne .noedd
256                 test cl,1               ; Extended disk access functionality set
257                 jz .noedd
258                 ;
259                 ; We have EDD support...
260                 ;
261                 mov byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
262 .noedd:
265 ; Load the first sector of LDLINUX.SYS; this used to be all proper
266 ; with parsing the superblock and root directory; it doesn't fit
267 ; together with EBIOS support, unfortunately.
269 Sect1Load:
270                 mov eax,strict dword Sect1Ptr0_VAL      ; 0xdeadbeef
271 Sect1Ptr0       equ $-4
272                 mov edx,strict dword Sect1Ptr1_VAL      ; 0xfeedface
273 Sect1Ptr1       equ $-4
274                 mov bx,ldlinux_sys      ; Where to load it
275                 call getonesec
277                 ; Some modicum of integrity checking
278                 cmp dword [ldlinux_magic+4],LDLINUX_MAGIC^HEXDATE
279                 jne kaboom
281                 ; Go for it!
282                 jmp ldlinux_ent
285 ; getonesec: load a single disk linear sector EDX:EAX into the buffer
286 ;            at ES:BX.
288 ;            This routine assumes CS == DS == SS, and trashes most registers.
290 ; Stylistic note: use "xchg" instead of "mov" when the source is a register
291 ; that is dead from that point; this saves space.  However, please keep
292 ; the order to dst,src to keep things sane.
294 getonesec:
295                 add eax,[Hidden]                ; Add partition offset
296                 adc edx,[Hidden+4]
297                 mov cx,retry_count
298 .jmp:           jmp strict short getonesec_cbios
301 ; getonesec_ebios:
303 ; getonesec implementation for EBIOS (EDD)
305 getonesec_ebios:
306 .retry:
307                 ; Form DAPA on stack
308                 push edx
309                 push eax
310                 push es
311                 push bx
312                 push word 1
313                 push word 16
314                 mov si,sp
315                 pushad
316                 mov ah,42h                      ; Extended Read
317                 call xint13
318                 popad
319                 lea sp,[si+16]                  ; Remove DAPA
320                 jc .error
321                 ret
323 .error:
324                 ; Some systems seem to get "stuck" in an error state when
325                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
326                 ; good, since some other systems get timeout failures
327                 ; waiting for the floppy disk to spin up.
329                 pushad                          ; Try resetting the device
330                 xor ax,ax
331                 call xint13
332                 popad
333                 loop .retry                     ; CX-- and jump if not zero
335                 ; Total failure.  Try falling back to CBIOS.
336                 mov byte [getonesec.jmp+1],(getonesec_cbios-(getonesec.jmp+2))
339 ; getonesec_cbios:
341 ; getlinsec implementation for legacy CBIOS
343 getonesec_cbios:
344 .retry:
345                 pushad
347                 movzx esi,word [bsSecPerTrack]
348                 movzx edi,word [bsHeads]
349                 ;
350                 ; Dividing by sectors to get (track,sector): we may have
351                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
352                 ;
353                 div esi
354                 xor cx,cx
355                 xchg cx,dx              ; CX <- sector index (0-based)
356                                         ; EDX <- 0
357                 ; eax = track #
358                 div edi                 ; Convert track to head/cyl
360                 cmp eax,1023            ; Outside the CHS range?
361                 ja kaboom
363                 ;
364                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
365                 ; SI = bsSecPerTrack, ES:BX = data target
366                 ;
367                 shl ah,6                ; Because IBM was STOOPID
368                                         ; and thought 8 bits were enough
369                                         ; then thought 10 bits were enough...
370                 inc cx                  ; Sector numbers are 1-based, sigh
371                 or cl,ah
372                 mov ch,al
373                 mov dh,dl
374                 mov ax,0201h            ; Read one sector
375                 call xint13
376                 popad
377                 jc .error
378                 ret
380 .error:
381                 loop .retry
382                 ; Fall through to disk_error
385 ; kaboom: write a message and bail out.
387 %ifdef BINFMT
388                 global kaboom
389 %else
390                 global kaboom:function hidden
391 %endif
392 disk_error:
393 kaboom:
394                 xor si,si
395                 mov ss,si
396                 mov sp,OrigFDCTabPtr    ; Reset stack
397                 mov ds,si               ; Reset data segment
398                 pop dword [fdctab]      ; Restore FDC table
399 .patch:                                 ; When we have full code, intercept here
400                 mov si,bailmsg
401 .loop:          lodsb
402                 and al,al
403                 jz .done
404                 mov ah,0Eh              ; Write to screen as TTY
405                 mov bx,0007h            ; Attribute
406                 int 10h
407                 jmp short .loop
409 .done:
410                 xor ax,ax
411 .again:         int 16h                 ; Wait for keypress
412                                         ; NB: replaced by int 18h if
413                                         ; chosen at install time..
414                 int 19h                 ; And try once more to boot...
415 .norge:         hlt                     ; If int 19h returned; this is the end
416                 jmp short .norge
419 ; INT 13h wrapper function
421 xint13:
422                 mov dl,[DriveNumber]
423                 push es         ; ES destroyed by INT 13h AH 08h
424                 int 13h
425                 pop es
426                 ret
429 ; Error message on failure
431 bailmsg:        db 'Boot error', 0Dh, 0Ah, 0
433                 ; This fails if the boot sector overflowsg
434                 zb 1F8h-($-$$)
436 bs_magic        dd LDLINUX_MAGIC
437 bs_link         dw (Sect1Load - bootsec) | BS_MAGIC_VER
438 bootsignature   dw 0xAA55
441 ; ===========================================================================
442 ;  End of boot sector
443 ; ===========================================================================