Fix some errors in man/lilo.8
[rrq/maintain_lilo.git] / src / mbr.S
1 ;  mbr.S -- Master Boot Record to boot first partition marked active
2 ;
3 ; Copyright 2002-2004 John Coffman.
4 ; All rights reserved.
5 ;
6 ; Licensed under the terms contained in the file 'COPYING' in the 
7 ; source directory.
8 ;
9
10 /* set to 1 for debugging output */
11 #define DEBUG 0
12
13 #define SEARCH 1                /* turn on search for device code */
14 #define CYL1023 0               /* 1==compare to 1023 / 0==fn8 cyl #    */
15 #define PASS_PARAMS 1           /* 1==pass lilo parameters */
16 #define BYPASS18 0              /* bypass int 18h exit */
17
18 #ifdef MBX
19 # define EXT_PART 1             /* search extended partitions, too */
20 /*# define VIDEO_ENABLE         / we just have no space for this */
21 # define VIDEO_ENABLE           /* we now do have space for this */
22 #else
23 # define EXT_PART 0             /* search primary partition only */
24 # define VIDEO_ENABLE
25 #endif
26
27 DELAY   = 12                    /* tenths of a second */
28
29 #if DEBUG
30 STEP    = 1                     /* delay is in seconds if DEBUG */
31 # ifdef VIDEO_ENABLE
32 /*#  undef VIDEO_ENABLE*/
33 # endif
34 #else
35 STEP    = 10                    /* delay is in deciseconds if not DEBUG */
36 #endif
37
38 #define LILO_ASM
39 #include "lilo.h"
40
41
42         .text
43
44         .globl  _main
45
46         .org    PARTS_LOAD
47
48 zero:
49 _main:  cli                     ! NT 4 blows up if this is missing
50         jmp     start
51
52 #if EXT_PART
53 stage:  .byte   STAGE_MBR2      ! search extended partitions, too
54 #else
55 stage:  .byte   STAGE_MBR       ! search primary parition only
56 #endif
57
58         .org    PARTS_LOAD+6
59 sig:    .ascii  "LILO"          ! signature
60 vers:   .word   VERSION
61
62 ! the disk I/O packet   DS:SI uses it
63 packet: .word   16              ! size of packet
64         .word   1               ! count of sectors to transfer
65 addr:   .word   BOOTSEG*16      ! address offset to transfer to
66         .word   0               ! address segment to transfer to
67 daddr:  .long   0               ! low order disk address
68         .long   0               ! high order disk address
69 ! end of packet
70
71
72         
73 #if DEBUG
74 #if !SEARCH
75 dout:   push    ax              ! save low half
76         shr     eax,#16
77         call    wout            ! put out high word
78         pop     ax
79 wout:   push    ax
80         xchg    ah,al           ! put out AH first
81         call    bout
82         pop     ax              ! restore AL
83 #endif
84 bout:   push    ax              ! convert & output hex byte in AL
85         shr     al,#4           ! high nibble
86         call    nout
87         pop     ax              ! low nibble
88 nout:   and     al,#0x0F        ! write the nibble in low half of AL
89         daa                     ! convert to upper case hex character
90         add     al,#0xF0        ! **
91         adc     al,#0x40        ! **
92 cout:   push    bx              ! write character to the console
93         mov     ah,#0x0E        ! video BIOS function 14
94         mov     bh,#0
95         int     0x10            ! video interrupt
96         pop     bx
97         ret
98 #endif
99
100 say:    pop     si              ! get CS:SI pointer to character string
101 say1:   lodsb                   ! but DS==CS, so this works
102         or      al,al           ! NUL terminated?
103         jz      say9
104 #if DEBUG
105         call    cout
106 #else
107         mov     ah,#0x0E        ! in-line character write routine
108         mov     bx,#07          ! write to page 0
109         int     0x10            ! video interrupt
110 #endif
111         jmp     say1
112 say9:
113 #if DEBUG
114         jmp     si              ! return from "say:"
115 #endif
116 stop:
117 #if DEBUG
118         hlt                     ! wait for interrupt
119         jmp     stop            ! loop back after interrupt
120 #else
121 #if BYPASS18
122         xor     eax,eax         ! EXPERIMENTAL code
123         mov     [daddr],eax     ! zero the disk address
124         inc     dx              ! try the next device code
125         call    disk_read       ! read sector 0
126         jmpi    (addr)
127 #else
128         mov     cx,#DELAY*16/STEP  ! delay DELAY/10 seconds, DX doesn't matter
129
130         mov     ah,#0x86
131         int     0x15            ! delay call
132
133         int     0x18            ! exit to BIOS
134
135 #endif  /* BYPASS18 */
136 #endif  /* DEBUG */
137
138 start:
139         xor     ax,ax                   ! all addressing from 0000:0000
140         mov     ss,ax                   ! set up the stack
141         mov     sp,#BOOTSEG*16          ! #0x7C00
142         sti                             ! enable interrupts
143 #if PASS_PARAMS
144         mov     cx,sp
145         push    es
146         push    bx
147         push    si
148         push    dx
149         mov     si,cx
150 #else
151         mov     si,sp                   ! from here 0000:7C000
152 #endif
153         cld                             ! clear direction flag (UP)
154         mov     ds,ax                   ! DS=0
155         mov     es,ax                   ! ES=0
156         mov     di,#PARTS_LOAD          ! move to here 0000:0600
157         mov     cx,#SECTOR_SIZE/2       ! one sector worth
158         rep
159           movsw                         ! move words
160         jmpi    go,0                    ! intersegment jump 0:go
161 go:
162 #ifdef VIDEO_ENABLE
163         pusha                   ! certain video cards trash DX
164 #if 0
165         mov     al,[0x449]              ! get video mode
166         cbw
167 #else
168         mov     ax,#0x1200      ! enable video (VGA)
169         mov     bl,#0x36        ! (probably a nop on EGA or MDA)
170 #endif
171         int     0x10            ! 
172
173         popa                    ! DX must be protected from rogue video cards
174 #endif
175
176 #if SEARCH
177         mov     edi,[serial_no]         ! serial number to look for
178         or      edi,edi
179         jz      use_boot
180
181         mov     ah,#8           ! get number of hard drives
182         mov     dl,#0x80
183         int     0x13
184         movzx   cx,dl
185
186         xchg    ax,dx           ! save device code in AX
187         mov     dx,#0x80        ! device 80
188
189 vagain:
190         call    disk_read       
191
192         cmp     edi,[BOOTSEG*16+PART_TABLE_OFFSET-6]
193         je      vol_found
194         inc     dx              ! try next device
195         loop    vagain
196
197         xchg    ax,dx           ! try what we were passed
198
199 vol_found:
200 use_boot:
201
202 #endif
203
204 #if DEBUG
205         call    say                     ! debugging dump of DL
206         .ascii  "DL="
207         .byte   0
208         mov     ax,dx
209         call    bout                    ! write the byte in AL
210 #if !SEARCH
211         mov     al,#0x20
212         call    cout
213         mov     eax,[serial_no]         ! serial number to look for
214         call    dout
215 #endif
216         call    say
217         .byte   13,10,0
218 #endif  
219         mov     si,#p_table             ! scan the partition table 
220 #if EXT_PART
221         xor     edi,edi                 ! BASE = 0
222 #endif
223         mov     cx,#4                   ! 4 entries
224 find_active:
225 #if EXT_PART
226         call    is_ext                  ! test for extended
227 #endif
228         test    byte ptr (si),#0x80     ! test hi-bit
229         mov     bp,si                   ! save possible ptr
230         js      one_found               ! found Active if sign bit set
231         add     si,#16                  ! move to next entry
232         loop    find_active             ! & loop back
233
234 #if EXT_PART
235 /* no primary partition was marked active */
236         xchg    edi,ebp                 ! EBP = base, EDI = second
237         xor     edi,edi
238
239 /* extended partitions exist, search them */
240 ext_search:
241         add     edi,ebp                 ! second += base
242         mov     [daddr],edi
243         call    disk_read
244         mov     si,#BOOTSEG*16+PART_TABLE_OFFSET        ! pt[0]
245         test    byte ptr (si),#0x80     ! test hi-bit
246         js      boot_si                 ! one to boot if set
247         add     si,#16                  ! pt[1]
248         call    is_ext                  ! will set EDI
249         jz      ext_search
250 #endif
251
252         call    say                     ! comment & quit
253 #if DEBUG
254         .ascii  "nPa"
255 #else
256         .ascii  "No partition active"
257 #endif
258         .byte   13,10,0
259 #if DEBUG
260 stop1:  br      stop
261 #endif
262
263
264 #if !EXT_PART
265 find_more:                              ! check for more that one partition
266 #if EXT_PART
267         call    is_ext                  ! continue check for extended part.
268 #endif
269         test    byte ptr (si),#0x80     ! with active bit set
270         jns     one_found
271         call    say                     ! oops, a second partition is active
272 #if DEBUG
273         .ascii  "iPT"
274 #else
275         .ascii  "Invalid PT"
276 #endif
277         .byte   13,10,0                 ! comment & quit
278 #if DEBUG
279         jmp     stop1
280 #endif
281
282 one_found:                              ! one partition is active
283         add     si,#16                  ! go on & test others
284         loop    find_more               ! continue the loop
285
286 ; BP points at the only active partition
287
288         mov     si,bp           ; now SI points at active partition
289 #else
290 one_found:
291 #endif  /* !EXT_PART */
292
293 boot_si:
294         mov     eax,(si+8)      ; get partition start
295 #if EXT_PART
296         add     [daddr],eax     ; set disk address
297 #else
298         mov     [daddr],eax     ; set disk address
299 #endif
300         call    disk_read       ; read sector
301
302 boot_it:
303 ;;;     seg     es                      ! DS==ES, so don't need prefix
304         cmp     word ptr [BOOTSEG*16+BOOT_SIG_OFFSET],#0xAA55   ! look for boot signature
305         jne     no_boot                 ! not bootable if no sig.
306
307 #ifdef LCF_COHERENT
308         mov     (si),dl         ; move into partition table
309 #endif
310         xor     ax,ax           ; signal no disk error
311 #if DEBUG
312         pusha
313         call    say
314         .ascii  "B:"
315         .byte   13,10,0
316
317         mov     cx,#DELAY*16/STEP/2  ! delay DELAY/10 seconds, DX doesn't matter
318
319         mov     ah,#0x86
320         int     0x15            ! delay call
321         popa
322 #endif
323 #if PASS_PARAMS
324         pop     ax              ! check for possible params
325         cmp     al,#0xFE        !
326         jne     no_params
327         mov     ah,dl
328         pop     si
329         pop     bx
330         pop     es
331         xchg    ax,dx
332 no_params:
333 #endif
334         jmpi    (addr)
335
336
337 no_boot: call   say
338 #if DEBUG
339         .ascii  "nBs"
340 #else
341 #if EXT_PART
342 ;;;     .ascii  "No 0xAA55 in partition"
343         .ascii  "No boot sig. in partition"
344 #else
345         .ascii  "No boot signature in partition"
346 #endif
347 #endif
348         .byte   13,10,0
349 #if DEBUG
350         jmp     stop1
351 #endif
352
353 ! packet read routine
354 disk_read:
355         pusha
356         mov     bp,#12          ! retry count
357
358 disk_retry:
359         mov     si,#packet
360         mov     bx,#0x55AA      ;magic number
361         mov     ah,#0x41
362         int     0x13
363         jc      disk_convert
364         cmp     bx,#0xAA55      ;changed?
365         jne     disk_convert
366         test    cl,#EDD_PACKET  ;EDD packet calls supported
367         jz      disk_convert
368
369         mov     ah,#0x42
370         jmp     disk_int13
371
372
373 disk_convert:
374         push    dx
375         mov     ah,#8           ! get geometry
376         int     0x13
377         jc      disk_error12
378
379 #if !CYL1023
380         push    cx
381         shr     cl,#6           ;;;;
382         xchg    cl,ch      ;CX is max cylinder number
383         mov     di,cx      ;DI saves it
384         pop     cx
385 #endif
386         shr     dx,#8
387         xchg    ax,dx           ;AX <- DX
388         inc     ax              ;AX is number of heads (256 allowed)
389
390         and     cx,#0x003f      ;CX is number of sectors
391         mul     cx              ; kills DX also
392         xchg    ax,bx           ;save in BX
393
394         mov     ax,[daddr]      ;low part of address
395         mov     dx,[daddr+2]    ;hi part of address
396         
397         cmp     dx,bx
398         jae     disk_error2     ;prevent division error
399         div     bx              ;AX is cyl, DX is head/sect
400 #if CYL1023
401         cmp     ax,#1023
402 #else
403         cmp     ax,di
404 #endif
405         ja      disk_error2     ;cyl is too big
406
407         shl     ah,#6           ; save hi 2 bits
408         xchg    al,ah
409         xchg    ax,dx
410         div     cl              ;AH = sec-1, AL = head
411         or      dl,ah      ;form Cyl/Sec
412         mov     cx,dx
413         inc     cx              ; sector is 1 based
414
415         pop     dx              ! restore device code
416         mov     dh,al           ! set head#
417         mov     ax,#0x201       ;read, count of 1
418
419 disk_int13:
420         les     bx,[addr-packet](si)    ! for both reads
421         int     0x13
422         jc      disk_error1
423 disk_ret:
424         popa
425         ret
426
427
428 disk_error2:
429         mov     ah,#0x40        ; signal seek error
430 disk_error12:
431         pop     dx
432 disk_error1:
433         dec     bp
434         jz      disk_error0
435
436 ;;      mov     ah,#0x0D        ! reset fixed disk controller
437         xor     ah,ah
438         int     0x13
439         jmp     disk_retry
440
441 disk_error0:
442 disk_error:
443 #if DEBUG
444         xchg    al,ah           ; error code to AL
445         call    bout
446         call    say
447         .ascii  "=dRe"
448 #else
449         call    say             ; something is wrong with the disk read
450         .ascii  "Disk read error"
451 #endif
452         .byte   13,10,0
453 #if DEBUG
454         br      stop
455 #endif
456
457
458
459 #if EXT_PART
460 /* return ZF=1 if SI -> extended partition and set EDI */
461 is_ext:
462         mov     al,(si+4)               ; get partition type
463         cmp     al,#PART_DOS_EXTD
464         jz      is_extd
465         cmp     al,#PART_WIN_EXTD_LBA
466         jz      is_extd
467         cmp     al,#PART_LINUX_EXTD
468         jnz     is_extr
469 is_extd:
470         mov     edi,(si+8)              ; get start to edi
471 is_extr:
472         ret
473 #endif
474
475 theend1:        /* better be at or below 07B6 */
476
477         .org    PARTS_LOAD+MAX_BOOT_SIZE
478         .word   0
479 serial_no:      .blkb   4       ! volume serial number
480         .blkb   2
481
482 !!!     .org    0x1be           ! spot for the partition table
483 p_table:
484         .blkb   16              ! the partition table is filled in
485         .blkb   16              ! when this Master Boot Record is installed
486         .blkb   16              ! just leave space
487         .blkb   16              ! here
488 #if defined MBX
489         .org    *-2
490         .long   MBX             ! boot block signature check
491 #elif defined MBR
492         .org    *-2
493         .long   MBR             ! boot block signature check
494 #else
495         .word   0xAA55          ! boot block signature goes here
496 #endif
497
498 theend: ! must be 0000:0800