sprofalyze fixes
[minix.git] / sys / arch / i386 / stand / bootxx / pbr.S
blobd93983b297746656b3789e9836da992977fa86a3
1 /*      $NetBSD: pbr.S,v 1.20 2011/08/17 00:07:38 jakllsch Exp $        */
3 /*-
4  * Copyright (c) 2003,2004 The NetBSD Foundation, Inc.
5  * All rights reserved.
6  *
7  * This code is derived from software contributed to The NetBSD Foundation
8  * by David Laight.
9  *
10  * Redistribution and use in source and binary forms, with or without
11  * modification, are permitted provided that the following conditions
12  * are met:
13  * 1. Redistributions of source code must retain the above copyright
14  *    notice, this list of conditions and the following disclaimer.
15  * 2. Redistributions in binary form must reproduce the above copyright
16  *    notice, this list of conditions and the following disclaimer in the
17  *    documentation and/or other materials provided with the distribution.
18  *
19  * THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
20  * ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
21  * TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
22  * PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE FOUNDATION OR CONTRIBUTORS
23  * BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
24  * CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
25  * SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
26  * INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
27  * CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
28  * ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
29  * POSSIBILITY OF SUCH DAMAGE.
30  */
33  * i386 partition boot code
34  *
35  * This code resides in sector zero of the netbsd partition, or sector
36  * zero of an unpartitioned disk (eg a floppy).
37  * Sector 1 is assumed to contain the netbsd disklabel.
38  * Sectors 2 until the end of the track contain the next phase of bootstrap.
39  * Which know how to read the interactive 'boot' program from filestore.
40  * The job of this code is to read in the phase 1 bootstrap.
41  *
42  * Makefile supplies:
43  * PRIMARY_LOAD_ADDRESS:        Address we load code to (0x1000).
44  * BOOTXX_SECTORS:              Number of sectors we load (15).
45  * X86_BOOT_MAGIC_1:            A random magic number.
46  *
47  * Although this code is executing at 0x7c00, it is linked to address 0x1000.
48  * All data references MUST be fixed up using R().
49  */
51 #include <machine/asm.h>
52 #include <sys/bootblock.h>
54 #define OURADDR         0x7c00          /* our address */
55 #define BOOTADDR        PRIMARY_LOAD_ADDRESS
57 #define R(a) (a - BOOTADDR + OURADDR)
59 #define lba_info R(_lba_info)
60 #define lba_sector R(_lba_sector)
61 #define errtxt R(_errtxt)
62 #define errcod R(_errcod)
63 #define newline R(_newline)
65 #define TABENTRYSIZE    (MBR_BS_PARTNAMESIZE + 1)
66 #define NAMETABSIZE     (4 * TABENTRYSIZE)
68 #ifdef BOOT_FROM_FAT
69 #define MBR_AFTERBPB    90              /* BPB size in FAT32 partition BR */
70 #else
71 #define MBR_AFTERBPB    62              /* BPB size in floppy master BR */
72 #endif
74 #ifdef TERSE_ERROR
76  * Error codes. Done this way to save space.
77  */
78 #define ERR_READ        '2'             /* Read error */
79 #define ERR_NO_BOOTXX   'B'             /* No bootxx_xfs in 3rd sector */
80 #define ERR_PTN         'P'             /* partition not defined */
81 #define ERR_NO_LBA      'L'             /* sector above chs limit */
83 #define set_err(err)    movb    $err, %al
85 #else
86 #define set_err(err)    mov     $R(err), %ax
87 #endif
90  * This code is loaded to addresss 0:7c00 by either the system BIOS
91  * (for a floppy) or the mbr boot code.  Since the boot program will
92  * be loaded to address 1000:0, we don't need to relocate ourselves
93  * and can load the subsequent blocks (that load boot) to an address
94  * of our choosing. 0:1000 is a not unreasonable choice.
95  *
96  * On entry the BIOS drive number is in %dl and %esi may contain the
97  * sector we were loaded from (if we were loaded by NetBSD mbr code).
98  * In any case we have to re-read sector zero of the disk and hunt
99  * through the BIOS partition table for the NetBSD partition.
101  * Or, we may have been loaded by a GPT hybrid MBR, handoff state is
102  * specified in T13 EDD-4 annex A.
103  */
105         .text
106         .code16
107 ENTRY(start)
108         /*
109          * The PC BIOS architecture defines a Boot Parameter Block (BPB) here.
110          * The actual format varies between different MS-DOS versions, but
111          * apparently some system BIOS insist on patching this area
112          * (especially on LS120 drives - which I thought had an MBR...).
113          * The initial jmp and nop are part of the standard and may be
114          * tested for by the system BIOS.
115          */
116         jmp     start0
117         nop
118         .ascii  "NetBSD60"              /* oemname (8 bytes) */
120         . = start + MBR_BPB_OFFSET      /* move to start of BPB */
121                                         /* (ensures oemname doesn't overflow) */
123         . = start + MBR_AFTERBPB        /* skip BPB */
124 start0:
125         xor     %cx, %cx                /* don't trust values of ds, es or ss */
126         mov     %cx, %ss
127         mov     %cx, %sp
128         mov     %cx, %es
129 #ifndef BOOT_FROM_FAT
130         cmpl    $0x54504721, %eax       /* did a GPT hybrid MBR start us? */
131         je      boot_gpt
132 #endif
133         mov     %cx, %ds
134         xor     %ax, %ax
136         /* A 'reset disk system' request is traditional here... */
137         push    %dx                     /* some BIOS zap %dl here :-( */
138         int     $0x13                   /* ah == 0 from code above */
139         pop     %dx
141         /* Read from start of disk */
142         incw    %cx                     /* track zero sector 1 */
143         movb    %ch, %dh                /* dh = head = 0 */
144         call    chs_read
146 /* See if this is our code, if so we have already loaded the next stage */
148         xorl    %ebp, %ebp              /* pass sector 0 to next stage */
149         movl    (%bx), %eax             /* MBR code shouldn't even have ... */
150         cmpl    R(start), %eax          /* ... a jmp at the start. */
151         je      pbr_read_ok1
153 /* Now scan the MBR partition table for a netbsd partition */
154         
155         xorl    %ebx, %ebx              /* for base extended ptn chain */
156 scan_ptn_tbl:
157         xorl    %ecx, %ecx              /* for next extended ptn */
158         movw    $BOOTADDR + MBR_PART_OFFSET, %di
159 1:      movb    4(%di), %al             /* mbrp_type */
160         movl    8(%di), %ebp            /* mbrp_start == LBA sector */
161         addl    lba_sector, %ebp        /* add base of extended partition */
162 #ifdef BOOT_FROM_FAT
163         cmpb    $MBR_PTYPE_FAT12, %al
164         je      5f
165         cmpb    $MBR_PTYPE_FAT16S, %al
166         je      5f
167         cmpb    $MBR_PTYPE_FAT16B, %al
168         je      5f
169         cmpb    $MBR_PTYPE_FAT32, %al
170         je      5f
171         cmpb    $MBR_PTYPE_FAT32L, %al
172         je      5f
173         cmpb    $MBR_PTYPE_FAT16L, %al
174         je      5f
175 #elif BOOT_FROM_MINIXFS3
176         cmpb    $MBR_PTYPE_MINIX_14B, %al
177         je      5f
178 #else
179         cmpb    $MBR_PTYPE_NETBSD, %al
180 #endif
181         jne     10f
182 5:      testl   %esi, %esi              /* looking for a specific sector? */
183         je      boot
184         cmpl    %ebp, %esi              /* ptn we wanted? */
185         je      boot
186         /* check for extended partition */
187 10:     cmpb    $MBR_PTYPE_EXT, %al
188         je      15f
189         cmpb    $MBR_PTYPE_EXT_LBA, %al
190         je      15f
191         cmpb    $MBR_PTYPE_EXT_LNX, %al
192         jne     20f
193 15:     movl    8(%di), %ecx            /* sector of next ext. ptn */
194 20:     add     $0x10, %di
195         cmp     $BOOTADDR + MBR_MAGIC_OFFSET, %di
196         jne     1b
198         /* not in base partitions, check extended ones */
199         jecxz   no_netbsd_ptn
200         testl   %ebx, %ebx
201         jne     30f
202         xchgl   %ebx, %ecx              /* save base of ext ptn chain */
203 30:     addl    %ebx, %ecx              /* address this ptn */
204         movl    %ecx, lba_sector        /* sector to read */
205         call    read_lba
206         jmp     scan_ptn_tbl
208 no_netbsd_ptn:
209         /* Specific sector not found: try again looking for first NetBSD ptn */
210         testl   %esi, %esi
211         set_err(ERR_PTN)
212         jz      error
213         xorl    %esi, %esi
214         movl    %esi, lba_sector
215         jmp     start
218  * Sector below CHS limit
219  * Do a cylinder-head-sector read instead
220  * I believe the BIOS should do reads that cross track boundaries.
221  * (but the read should start at the beginning of a track...)
222  */
223 read_chs:
224         movb    1(%di), %dh                     /* head */
225         movw    2(%di), %cx                     /* ch=cyl, cl=sect */
226         call    chs_read
227 pbr_read_ok1:
228         jmp     pbr_read_ok
231  * Active partition pointed to by di.
233  * We can either do a CHS (Cylinder Head Sector) or an LBA (Logical
234  * Block Address) read.  Always doing the LBA one
235  * would be nice - unfortunately not all systems support it.
236  * Also some may contain a separate (eg SCSI) BIOS that doesn't
237  * support it even when the main BIOS does.
239  * The safest thing seems to be to find out whether the sector we
240  * want is inside the CHS sector count.  If it is we use CHS, if
241  * outside we use LBA.
243  * Actually we check that the CHS values reference the LBA sector,
244  * if not we assume that the LBA sector is above the limit, or that
245  * the geometry used (by fdisk) isn't correct.
246  */
247 boot:
248         movl    %ebp, lba_sector        /* to control block */
249         testl   %ebx, %ebx              /* was it an extended ptn? */
250         jnz     boot_lba                /* yes - boot with LBA reads */
252 /* get CHS values from BIOS */
253         push    %dx                             /* save drive number */
254         movb    $8, %ah
255         int     $0x13                           /* chs info */
258  * Validate geometry, if the CHS sector number doesn't match the LBA one
259  * we'll do an LBA read.
260  * calc: (cylinder * number_of_heads + head) * number_of_sectors + sector
261  * and compare against LBA sector number.
262  * Take a slight 'flier' and assume we can just check 16bits (very likely
263  * to be true because the number of sectors per track is 63).
264  */
265         movw    2(%di), %ax                     /* cylinder + sector */
266         push    %ax                             /* save for sector */
267         shr     $6, %al
268         xchgb   %al, %ah                        /* 10 bit cylinder number */
269         shr     $8, %dx                         /* last head */
270         inc     %dx                             /* number of heads */
271         mul     %dx
272         mov     1(%di), %dl                     /* head we want */
273         add     %dx, %ax
274         and     $0x3f, %cx                      /* number of sectors */
275         mul     %cx
276         pop     %dx                             /* recover sector we want */
277         and     $0x3f, %dx
278         add     %dx, %ax
279         dec     %ax
280         pop     %dx                             /* recover drive nmber */
282         cmp     %bp, %ax
283         je      read_chs
285 check_lba:
286 #ifdef NO_LBA_CHECK
287         jmp     boot_lba
288 #else
290  * Determine whether we have int13-extensions, by calling
291  * int 13, function 41. Check for the magic number returned,
292  * and the disk packet capability.
294  * This is actually relatively pointless:
295  * 1) we only use LBA reads if CHS ones would fail
296  * 2) the MBR code managed to read the same sectors
297  * 3) the BIOS will (ok should) reject the LBA read as a bad BIOS call
298  */
299         movw    $0x55aa, %bx
300         movb    $0x41, %ah
301         int     $0x13
302         jc      1f                              /* no int13 extensions */
303         cmpw    $0xaa55, %bx
304         jnz     1f
305         testb   $1, %cl
306         jnz     boot_lba
307 1:      set_err(ERR_NO_LBA)
308 #endif  /* NO_LBA_CHECK */
311  * Something went wrong,
312  * Output error code,
313  */
315 error:
316 #ifdef TERSE_ERROR
317         movb    %al, errcod
318         movw    $errtxt, %si
319         call    message
320 #else
321         push    %ax
322         movw    $errtxt, %si
323         call    message
324         pop     %si
325         call    message
326         movw    $newline, %si
327         call    message
328 #endif
329 1:      sti
330         hlt
331         jmp     1b
333 boot_lba:
334         call    read_lba
337  * Check magic number for valid stage 2 bootcode
338  * then jump into it.
339  */
340 pbr_read_ok:
341         cmpl    $X86_BOOT_MAGIC_1, bootxx_magic
342         set_err(ERR_NO_BOOTXX)
343         jnz     error
345         movl    %ebp, %esi                      /* %esi ptn base, %dl disk id */
346         movl    lba_sector + 4, %edi            /* %edi ptn base high */
347         jmp     $0, $bootxx                     /* our %cs may not be zero */
349 /* Read disk using int13-extension parameter block */
350 read_lba:
351         pusha
352         movw    $lba_info, %si                  /* ds:si is ctl block */
353         movb    $0x42, %ah
354 do_read:
355         int     $0x13
356         popa
358         set_err(ERR_READ)
359         jc      error
360         ret
362 /* Read using CHS */
364 chs_read:
365         movw    $BOOTADDR, %bx                  /* es:bx is buffer */
366         pusha
367         movw    $0x200 + BOOTXX_SECTORS, %ax    /* command 2, xx sectors */
368         jmp     do_read
370 #ifndef BOOT_FROM_FAT
371 boot_gpt:
372         movl    (20+32+0)(%si), %ebp
373         movl    (20+32+4)(%si), %edi
374         movw    %cx, %ds
375         movl    %ebp, lba_sector + 0
376         movl    %edi, lba_sector + 4
377         movl    %ebp, %esi
378         jmp     boot_lba
379 #endif
381 _errtxt: .ascii "Error "                        /* runs into newline... */
382 _errcod: .byte  0                               /* ... if errcod set */
383 _newline:
384         .asciz  "\r\n"
386 #ifndef TERSE_ERROR
387 ERR_READ:       .asciz  "read"
388 ERR_NO_BOOTXX:  .asciz  "no magic"
389 ERR_PTN:        .asciz  "no slice"
390 #ifndef NO_LBA_CHECK
391 ERR_NO_LBA:     .asciz  "need LBA"
392 #endif
393 #endif
396  * I hate #including source files, but pbr_magic below has to be at
397  * the correct absolute address.
398  * Clearly this could be done with a linker script.
399  */
401 #include <message.S>
402 #if 0
403 #include <dump_eax.S>
404 #endif
406 /* Control block for int-13 LBA read. */
407 _lba_info:
408         .word   0x10                            /* control block length */
409         .word   BOOTXX_SECTORS                  /* sector count */
410         .word   BOOTADDR                        /* offset in segment */
411         .word   0                               /* segment */
412 _lba_sector:
413         .quad   0                               /* sector # goes here... */
415 /* Drive Serial Number */
416         . = _C_LABEL(start) + MBR_DSN_OFFSET
417         .long   0
419 /* mbr_bootsel_magic (not used here) */
420         . = _C_LABEL(start) + MBR_BS_MAGIC_OFFSET
421         .word   0
424  * Provide empty MBR partition table.
425  * If this is installed as an MBR, the user can use fdisk(8) to create
426  * the correct partition table ...
427  */
428         . = _C_LABEL(start) + MBR_PART_OFFSET
429 _pbr_part0:
430         .byte   0, 0, 0, 0, 0, 0, 0, 0  
431         .long   0, 0
432 _pbr_part1:
433         .byte   0, 0, 0, 0, 0, 0, 0, 0  
434         .long   0, 0
435 _pbr_part2:
436         .byte   0, 0, 0, 0, 0, 0, 0, 0  
437         .long   0, 0
438 _pbr_part3:
439         .byte   0, 0, 0, 0, 0, 0, 0, 0  
440         .long   0, 0
443  * The magic comes last
444  */
445         . = _C_LABEL(start) + MBR_MAGIC_OFFSET
446 pbr_magic:
447         .word   MBR_MAGIC