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