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