Expand PMF_FN_* macros.
[netbsd-mini2440.git] / sys / arch / i386 / stand / bootxx / pbr.S
blob44291969b33d2150d8620c1403e47513de2ca76b
1 /*      $NetBSD: pbr.S,v 1.16 2008/04/28 20:23:25 martin 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 (0x600).
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 0x600.
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:600 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.
100  */
102         .text
103         .code16
104 ENTRY(start)
105         /*
106          * The PC BIOS architecture defines a Boot Parameter Block (BPB) here.
107          * The actual format varies between different MS-DOS versions, but
108          * apparently some system BIOS insist on patching this area
109          * (especially on LS120 drives - which I thought had an MBR...).
110          * The initial jmp and nop are part of the standard and may be
111          * tested for by the system BIOS.
112          */
113         jmp     start0
114         nop
115         .ascii  "NetBSD60"              /* oemname (8 bytes) */
117         . = start + MBR_BPB_OFFSET      /* move to start of BPB */
118                                         /* (ensures oemname doesn't overflow) */
120         . = start + MBR_AFTERBPB        /* skip BPB */
121 start0:
122         xor     %ax, %ax                /* don't trust values of ds, es or ss */
123         mov     %ax, %ds
124         mov     %ax, %es
125         mov     %ax, %ss
126         mov     $0xfffc, %sp
128         /* A 'reset disk system' request is traditional here... */
129         push    %dx                     /* some BIOS zap %dl here :-( */
130         int     $0x13                   /* ah == 0 from code above */
131         pop     %dx
133         /* Read from start of disk */
134         movw    $0x0001, %cx            /* track zero sector 1 */
135         movb    %ch, %dh                /* dh = head = 0 */
136         call    chs_read
138 /* See if this is our code, if so we have already loaded the next stage */
140         xorl    %ebp, %ebp              /* pass sector 0 to next stage */
141         movl    (%bx), %eax             /* MBR code shouldn't even have ... */
142         cmpl    R(start), %eax          /* ... a jmp at the start. */
143         je      pbr_read_ok1
145 /* Now scan the MBR partition table for a netbsd partition */
146         
147         xorl    %ebx, %ebx              /* for base extended ptn chain */
148 scan_ptn_tbl:
149         xorl    %ecx, %ecx              /* for next extended ptn */
150         movw    $BOOTADDR + MBR_PART_OFFSET, %di
151 1:      movb    4(%di), %al             /* mbrp_type */
152         movl    8(%di), %ebp            /* mbrp_start == LBA sector */
153         addl    lba_sector, %ebp        /* add base of extended partition */
154 #ifdef BOOT_FROM_FAT
155         cmpb    $MBR_PTYPE_FAT12, %al
156         je      5f
157         cmpb    $MBR_PTYPE_FAT16S, %al
158         je      5f
159         cmpb    $MBR_PTYPE_FAT16B, %al
160         je      5f
161         cmpb    $MBR_PTYPE_FAT32, %al
162         je      5f
163         cmpb    $MBR_PTYPE_FAT32L, %al
164         je      5f
165         cmpb    $MBR_PTYPE_FAT16L, %al
166         je      5f
167 #else
168         cmpb    $MBR_PTYPE_NETBSD, %al
169 #endif
170         jne     10f
171 5:      testl   %esi, %esi              /* looking for a specific sector? */
172         je      boot
173         cmpl    %ebp, %esi              /* ptn we wanted? */
174         je      boot
175         /* check for extended partition */
176 10:     cmpb    $MBR_PTYPE_EXT, %al
177         je      15f
178         cmpb    $MBR_PTYPE_EXT_LBA, %al
179         je      15f
180         cmpb    $MBR_PTYPE_EXT_LNX, %al
181         jne     20f
182 15:     movl    8(%di), %ecx            /* sector of next ext. ptn */
183 20:     add     $0x10, %di
184         cmp     $BOOTADDR + MBR_MAGIC_OFFSET, %di
185         jne     1b
187         /* not in base partitions, check extended ones */
188         jecxz   no_netbsd_ptn
189         testl   %ebx, %ebx
190         jne     30f
191         xchgl   %ebx, %ecx              /* save base of ext ptn chain */
192 30:     addl    %ebx, %ecx              /* address this ptn */
193         movl    %ecx, lba_sector        /* sector to read */
194         call    read_lba
195         jmp     scan_ptn_tbl
197 no_netbsd_ptn:
198         /* Specific sector not found: try again looking for first NetBSD ptn */
199         testl   %esi, %esi
200         set_err(ERR_PTN)
201         jz      error
202         xorl    %esi, %esi
203         movl    %esi, lba_sector
204         jmp     start
207  * Sector below CHS limit
208  * Do a cylinder-head-sector read instead
209  * I believe the BIOS should do reads that cross track boundaries.
210  * (but the read should start at the beginning of a track...)
211  */
212 read_chs:
213         movb    1(%di), %dh                     /* head */
214         movw    2(%di), %cx                     /* ch=cyl, cl=sect */
215         call    chs_read
216 pbr_read_ok1:
217         jmp     pbr_read_ok
220  * Active partition pointed to by di.
222  * We can either do a CHS (Cylinder Head Sector) or an LBA (Logical
223  * Block Address) read.  Always doing the LBA one
224  * would be nice - unfortunately not all systems support it.
225  * Also some may contain a separate (eg SCSI) BIOS that doesn't
226  * support it even when the main BIOS does.
228  * The safest thing seems to be to find out whether the sector we
229  * want is inside the CHS sector count.  If it is we use CHS, if
230  * outside we use LBA.
232  * Actually we check that the CHS values reference the LBA sector,
233  * if not we assume that the LBA sector is above the limit, or that
234  * the geometry used (by fdisk) isn't correct.
235  */
236 boot:
237         movl    %ebp, lba_sector        /* to control block */
238         testl   %ebx, %ebx              /* was it an extended ptn? */
239         jnz     boot_lba                /* yes - boot with LBA reads */
241 /* get CHS values from BIOS */
242         push    %dx                             /* save drive number */
243         movb    $8, %ah
244         int     $0x13                           /* chs info */
247  * Validate geometry, if the CHS sector number doesn't match the LBA one
248  * we'll do an LBA read.
249  * calc: (cylinder * number_of_heads + head) * number_of_sectors + sector
250  * and compare against LBA sector number.
251  * Take a slight 'flier' and assume we can just check 16bits (very likely
252  * to be true because the number of sectors per track is 63).
253  */
254         movw    2(%di), %ax                     /* cylinder + sector */
255         push    %ax                             /* save for sector */
256         shr     $6, %al
257         xchgb   %al, %ah                        /* 10 bit cylinder number */
258         shr     $8, %dx                         /* last head */
259         inc     %dx                             /* number of heads */
260         mul     %dx
261         mov     1(%di), %dl                     /* head we want */
262         add     %dx, %ax
263         and     $0x3f, %cx                      /* number of sectors */
264         mul     %cx
265         pop     %dx                             /* recover sector we want */
266         and     $0x3f, %dx
267         add     %dx, %ax
268         dec     %ax
269         pop     %dx                             /* recover drive nmber */
271         cmp     %bp, %ax
272         je      read_chs
274 check_lba:
275 #ifdef NO_LBA_CHECK
276         jmp     boot_lba
277 #else
279  * Determine whether we have int13-extensions, by calling
280  * int 13, function 41. Check for the magic number returned,
281  * and the disk packet capability.
283  * This is actually relatively pointless:
284  * 1) we only use LBA reads if CHS ones would fail
285  * 2) the MBR code managed to read the same sectors
286  * 3) the BIOS will (ok should) reject the LBA read as a bad BIOS call
287  */
288         movw    $0x55aa, %bx
289         movb    $0x41, %ah
290         int     $0x13
291         jc      1f                              /* no int13 extensions */
292         cmpw    $0xaa55, %bx
293         jnz     1f
294         testb   $1, %cl
295         jnz     boot_lba
296 1:      set_err(ERR_NO_LBA)
297 #endif  /* NO_LBA_CHECK */
300  * Something went wrong,
301  * Output error code,
302  */
304 error:
305 #ifdef TERSE_ERROR
306         movb    %al, errcod
307         movw    $errtxt, %si
308         call    message
309 #else
310         push    %ax
311         movw    $errtxt, %si
312         call    message
313         pop     %si
314         call    message
315         movw    $newline, %si
316         call    message
317 #endif
318 1:      sti
319         hlt
320         jmp     1b
322 boot_lba:
323         call    read_lba
326  * Check magic number for valid stage 2 bootcode
327  * then jump into it.
328  */
329 pbr_read_ok:
330         cmpl    $X86_BOOT_MAGIC_1, bootxx_magic
331         set_err(ERR_NO_BOOTXX)
332         jnz     error
334         movl    %ebp, %esi                      /* %esi ptn base, %dl disk id */
335         jmp     $0, $bootxx                     /* our %cs may not be zero */
337 /* Read disk using int13-extension parameter block */
338 read_lba:
339         pusha
340         movw    $lba_info, %si                  /* ds:si is ctl block */
341         movb    $0x42, %ah
342 do_read:
343         int     $0x13
344         popa
346         set_err(ERR_READ)
347         jc      error
348         ret
350 /* Read using CHS */
352 chs_read:
353         movw    $BOOTADDR, %bx                  /* es:bx is buffer */
354         pusha
355         movw    $0x200 + BOOTXX_SECTORS, %ax    /* command 2, xx sectors */
356         jmp     do_read
358 _errtxt: .ascii "Error "                        /* runs into newline... */
359 _errcod: .byte  0                               /* ... if errcod set */
360 _newline:
361         .asciz  "\r\n"
363 #ifndef TERSE_ERROR
364 ERR_READ:       .asciz  "Disk read"
365 ERR_NO_BOOTXX:  .asciz  "Not a bootxx image"
366 ERR_PTN:        .asciz  "No NetBSD partition"
367 #ifndef NO_LBA_CHECK
368 ERR_NO_LBA:     .asciz  "Invalid CHS read"
369 #endif
370 #endif
373  * I hate #including source files, but pbr_magic below has to be at
374  * the correct absolute address.
375  * Clearly this could be done with a linker script.
376  */
378 #include <message.S>
379 #if 0
380 #include <dump_eax.S>
381 #endif
383 /* Control block for int-13 LBA read. */
384 _lba_info:
385         .word   0x10                            /* control block length */
386         .word   BOOTXX_SECTORS                  /* sector count */
387         .word   BOOTADDR                        /* offset in segment */
388         .word   0                               /* segment */
389 _lba_sector:
390         .long   0x0000                          /* sector # goes here... */
391         .long   0x0000
393 /* Drive Serial Number */
394         . = _C_LABEL(start) + MBR_DSN_OFFSET
395         .long   0
397 /* mbr_bootsel_magic (not used here) */
398         . = _C_LABEL(start) + MBR_BS_MAGIC_OFFSET
399         .word   0
402  * Provide empty MBR partition table.
403  * If this is installed as an MBR, the user can use fdisk(8) to create
404  * the correct partition table ...
405  */
406         . = _C_LABEL(start) + MBR_PART_OFFSET
407 _pbr_part0:
408         .byte   0, 0, 0, 0, 0, 0, 0, 0  
409         .long   0, 0
410 _pbr_part1:
411         .byte   0, 0, 0, 0, 0, 0, 0, 0  
412         .long   0, 0
413 _pbr_part2:
414         .byte   0, 0, 0, 0, 0, 0, 0, 0  
415         .long   0, 0
416 _pbr_part3:
417         .byte   0, 0, 0, 0, 0, 0, 0, 0  
418         .long   0, 0
421  * The magic comes last
422  */
423         . = _C_LABEL(start) + MBR_MAGIC_OFFSET
424 pbr_magic:
425         .word   MBR_MAGIC