Add DMUA flag (by Niels Thykier)
[rrq/maintain_lilo.git] / src / first.S
1 #if 0
2 ;  first.S  -  LILO first stage boot loader with LBA32 support */
3 Copyright 1992-1998 Werner Almesberger.
4 Copyright 1999-2005 John Coffman.
5 All rights reserved.
6
7 Licensed under the terms contained in the file 'COPYING' in the 
8 source directory.
9
10 #endif
11 #define LILO_ASM
12 #include "lilo.h"
13 get common.s            /* as86 "include" will bypass the CPP */
14
15 #define DEBUG 0
16
17 #if VERSION_MINOR>=50
18 # define DEBUG_NEW
19
20 # undef VIDEO_ENABLE
21 # define VIDEO_ENABLE 3
22
23 # define VALIDATE !DEBUG        /* adds 0Dh bytes */
24 # define SECOND_CHECK !DEBUG    /* adds  5h bytes */
25 # define CYL1023 DEBUG          /* subs  8h bytes */
26 # define GEOMETRIC !DEBUG       /* adds  1h byte  */
27
28 # if DEBUG
29 #  define DEBUG_LARGE
30 # endif
31 #else
32
33 # define VALIDATE 1             /* adds 0Dh bytes */
34 # define SECOND_CHECK 1         /* adds  5h bytes */
35 # define CYL1023 0              /* subs  8h bytes */
36 # define GEOMETRIC 1            /* adds  1h byte  */
37 #endif
38
39
40 !  VIDEO_ENABLE for those systems that disable the video on boot
41 !       = 0             first stage does not enable video
42 !       = 1             use get vid mode/set vid mode to enable
43 !       = 2             use VGA enable call to enable video
44 !                       (cannot use, as code gets too big)
45 !       = 3             use direct mode set (mode 3, CGA, EGA, VGA)
46 !       = 7             use direct mode set (mode 7, MDA)
47 !
48 #ifndef VIDEO_ENABLE
49 # if VALIDATE==0
50 #  define VIDEO_ENABLE 2
51 # else
52 #  define VIDEO_ENABLE 2
53 # endif
54 #endif
55
56 ! do not change the following -- it must correspond to the code in bsect.c
57 #define RELOCATABLE -1
58
59
60         .text
61
62         .globl  _main
63
64         .org    0
65
66 zero:
67 _main:  cli                     ! NT 4 blows up if this is missing
68         jmp     start
69
70 stage:  .byte   STAGE_FIRST
71         .org    4
72 reloc:
73 #if RELOCATABLE
74         .word   theend-zero     ! size of the code & params
75 #else
76         .word   0               ! no size indication
77 #endif
78         .org    6
79
80 ! Boot device parameters. They are set by the installer.
81
82 sig:    .ascii  "LILO"
83 vers:   .word   VERSION
84 mapstamp: .long 0               ! map timestamp
85
86 length  =  *-sig                ! for the stage 1 vs stage 2 comparison
87
88 raid:   .long   0               ! raid sector offset
89 tstamp: .long   0               ! timestamp
90 map_serial_no:  .long   0       ! volume S/N containing map file
91 prompt: .word   0               ! indicates whether to always enter prompt
92                                 ! contains many other flags, too
93
94 d_dev:  .byte   0x80            ! map file device code
95 d_flag: .byte   0               ! disk addressing flags
96 d_addr: .long   0               ! disk addr of second stage index sector
97
98
99 edd_packet      =  0
100 ;;;     .word   16              ! size of packet
101 ;;;     .word   1               ! count of bytes to read
102
103 edd_addr        =  4
104 ;;;     .word   map2            ! where to read
105 ;;;     .word   *-*             ! segment where to read
106
107 edd_d_addr      =  8
108 ;;;     .long   1               ! low address or CX,DX (geometric)
109                                 ! start at sector 1 for search in geo mode
110
111 ;;;     .long   0               ! hi address
112
113 #if 0
114 !  These locations are referenced as EX_OFF 
115 !                                       (they used to be at CODE_START_1)
116 ext_si: .word   0               ! external interface
117 ext_es: .word   0               ! these locations are referenced in second.S
118 ext_bx: .word   0               ! do not disturb the ordering
119 ext_dl: .byte   0               ! second.S will check this magic number
120 ext_dh: .byte   0               ! not referenced, but must align stack
121 ext_stack:
122 #endif
123         
124 /***************************************************/
125 !       The following instruction MUST be
126 !       first instruction after the CLI/JMP short
127 !       at the start of the file; otherwise
128 !       the boot sector relocation fails.
129 !
130 start:
131         mov     ax,#BOOTSEG     ! use DS,ES,SS = 0x07C0
132 /***************************************************/
133
134         mov     ss,ax
135         mov     sp,#SETUP_STACKSIZE     ! set the stack for First Stage
136         sti                     ! now it is safe
137
138         push    dx              ! set ext_dl (and ext_dh, which is not used)
139         push    bx              ! WATCH the order of pushes
140         push    es              ! set ext_es
141         push    si              ! set ext_si
142
143 #ifdef DEBUG_NEW
144         push    ds
145         push    es      ! just not enough space with debug turned on
146 #endif
147
148 #define JRC_DS_EQ_SS
149
150         cld                     ! do not forget to do this !!!
151         mov     ds,ax           ! address data area
152         xor     bp,bp           ! shorted addressing
153
154 #if VIDEO_ENABLE
155 ! a BIOS has been found where the video interrupt (0x10) trashes DX
156 !   so, we had better be very paranoid about DX
157 !
158 # if VIDEO_ENABLE==2
159         pusha                   ! protect DX
160 # endif
161 # if VIDEO_ENABLE > 2
162         mov     ax,#VIDEO_ENABLE        ! set video mode 3 or 7
163 # elif VIDEO_ENABLE==1
164         mov     ah,#15          ! get video mode
165         int     0x10
166         cbw
167 # else  /* VIDEO_ENABLE==2 */
168         mov     ax,#0x1200      ! enable video (VGA)
169         mov     bl,#0x36        ! (probably a nop on EGA or MDA)
170 # endif
171         int     0x10            ! video call
172 # if VIDEO_ENABLE==2
173         popa                    ! restore DX
174 # endif
175 #endif
176
177 #if (VIDEO_ENABLE&1) == 0
178         mov     al,#0x0d        ! gimme a CR ...
179         call    display
180 ; the suspect call for trashing DX on one BIOS:
181         mov     al,#0x0a        ! ... an LF ...
182         call    display
183 #endif
184
185 #if defined(DEBUG_NEW)
186         mov     ah,dl
187         call    bout            ! code in AH
188 #endif
189         mov     al,#0x4c        ! ... an 'L' ...
190         call    display
191
192 lagain:
193         pusha                   ! preserve all the registers for restart
194
195         push    ds
196         pop     es              ! use buffer at end of boot sector
197
198         cmp     dl,#EX_DL_MAG   ! possible boot command line (chain.S)
199         jne     boot_in_dl
200         mov     dl,dh           ! code passed in DH instead
201 boot_in_dl:
202
203         mov     bx,#map2        ! buffer for volume search
204         mov     dh,[d_dev](bp)  ! map device to DH
205
206 #if VALIDATE
207         mov     ax,dx           ! copy device code to AL
208         and     ah,#0x80        ! AH = 00 or 80
209         xor     al,ah           ! hi-bits must be the same
210         js      use_installed
211         cmp     al,#MAX_BIOS_DEVICES    ! limit the device code
212         jae     use_installed   ! jump if DL is not valid
213 #endif
214
215 ! map is on boot device for RAID1, and if so marked; viz.,
216
217         test    byte ptr [prompt](bp),#FLAG_MAP_ON_BOOT
218         jnz     use_boot        ! as passed in from BIOS or MBR loader
219
220 use_installed:
221         mov     dl,dh           ! device code to DL
222         mov     esi,[map_serial_no](bp) ! to search for
223         or      esi,esi
224         jz      done_search
225
226         push    dx              ! save flags
227
228         mov     ah,#8           ! get number of hard disks
229         mov     dl,#0x80
230         push    bx              ! paranoia
231         int     0x13
232         pop     bx
233         jc      error
234
235         movzx   cx,dl           ! extend to word in CX
236
237 #if GEOMETRIC
238         mov     dx,#0x80-1      ! device 80, flags=0
239 #else
240         mov     dx,#LBA32_FLAG*256+0x80-1       ! device 80, flags=LBA32
241 #endif
242
243 vagain:
244         inc     dx
245         xor     eax,eax
246 #if GEOMETRIC
247         inc     ax              ! geometric addressing
248 #endif
249         call    disk_read       ! read 
250
251         cmp     esi,[PART_TABLE_OFFSET-6](bx)
252         je      vol_found
253         loop    vagain
254
255         pop     dx              ! restore specified BIOS code
256                                 ! AX and DX are identical at this point
257
258 vol_found:
259                 ! uses value in DX, stack may have extra value
260
261 done_search:    
262 use_boot:
263         push    bx              ! save map2 for later
264
265         mov     dh,[d_flag](bp) ! get device flags to DH
266         mov     si,#d_addr
267         call    pread           ! increments BX
268
269         mov     ah,#0x99        ! possible error code
270         cmp     dword (bx-4),#EX_MAG_HL ! "LILO"
271         jne     error
272
273         pop     si              ! point at #map2
274
275 #if 1
276         push    #SETUP_STACKSIZE/16 + BOOTSEG + SECTOR_SIZE/16*2
277         pop     es
278 #else
279         mov     ax,ds           ! get segment
280         add     ax,#SETUP_STACKSIZE/16    !   + SECTOR_SIZE/16*2
281         mov     es,ax
282 #endif
283         xor     bx,bx
284
285 sload:
286         call    pread           ! read using map at DS:SI
287         jnz     sload           ! into memory at ES:BX (auto increment)
288
289 ! Verify second stage loader signature
290         
291         mov     si,#sig         ! pointer to signature area
292         mov     di,si
293         mov     cx,#length      ! number of bytes to compare
294         mov     ah,#0x9A        ! possible error code
295         repe
296           cmpsb                 ! check Signature 1 & 2
297         jne     error   ! check Signature 2
298
299 #if SECOND_CHECK
300 /* it would be nice to re-incorporate this check */
301         mov     al,#STAGE_SECOND        ! do not touch AH (error code)
302         scasb
303         jne     error
304 #endif
305
306 ! Start the second stage loader     DS=location of Params
307
308         push    es              ! segment of second stage
309         push    bp              ! BP==0
310
311         mov     al,#0x49        ! display an 'I'
312         call    display
313
314         retf                    ! Jump to ES:BP
315
316
317
318
319 disk_error2:
320         mov     ah,#0x40        ; signal seek error
321
322 ! no return from error
323 error:
324
325 #ifndef LCF_NO1STDIAG
326         mov     al,#32          ! display a space
327         call    display0
328
329         call    bout
330 #endif
331
332 #ifndef DEBUG_LARGE
333         dec     byte [zero](bp)         !  CLI == 0xFA == 250
334         jz      zzz
335
336 #ifndef DEBUG_NEW
337         mov     sp,#SETUP_STACKSIZE-4*2-8*2     ! set the stack for First Stage
338 #else
339         mov     sp,#SETUP_STACKSIZE-4*2-2*2-8*2 ! set the stack for First Stage
340 #endif
341         popa                            ! restore registers for restart
342         jmp     near lagain             ! redo from start
343 #endif
344
345
346 zzz:
347 #ifndef DEBUG_NEW
348         hlt
349 #endif
350         jmp     zzz             ! spin; wait for Ctrl-Alt-Del
351
352
353
354
355 ! packet read routine
356
357 disk_read:
358 #ifndef JRC_DS_EQ_SS
359         push    ds
360 #endif
361         pusha
362
363 #ifndef JRC_DS_EQ_SS
364         push    ss
365         pop     ds
366 #endif
367
368         push    bp              ! BP==0
369         push    bp              ! BP==0
370
371         push    eax             ! low order disk address
372 #ifdef DEBUG_LARGE
373         xchg    ax,dx
374         call    wout
375         xchg    ax,dx
376         call    dout            ! print out disk address
377 #endif
378         push    es              ! memory segment ES
379         push    bx              ! memory offset BX
380         push    #1              ! sector count
381         push    #16             ! size of packet = 16 bytes
382         mov     si,sp           ! address of packet  DS:SI
383
384         push    bx
385
386         test    dh,#LINEAR_FLAG|LBA32_FLAG
387         jz      disk_geometric
388         
389         test    dh,#LBA32_FLAG
390         jz      disk_convert    ; it must be LINEAR
391
392         mov     bx,#0x55AA      ;magic number
393         mov     ah,#0x41
394         int     0x13
395         jc      disk_convert
396         cmp     bx,#0xAA55      ;changed?
397         jne     disk_convert
398         test    cl,#EDD_PACKET  ;EDD packet calls supported
399         jnz     disk_edd
400
401 disk_convert:
402         push    dx
403         push    es              ! protect on floppies
404         mov     ah,#8           ! get geometry
405         int     0x13
406         pop     es
407 disk_error3:                    ! transfer through on CF=1
408         jc      error           ! disk_error12
409
410 #if !CYL1023
411         push    cx
412         shr     cl,#6           ;;;;
413         xchg    cl,ch      ;CX is max cylinder number
414         mov     di,cx      ;DI saves it
415         pop     cx
416 #endif
417         shr     dx,#8
418         xchg    ax,dx           ;AX <- DX
419         inc     ax              ;AX is number of heads (256 allowed)
420
421 ; compensate for Davide BIOS bug
422         dec     cx              ; 1..63 -> 0..62;  0->63
423         and     cx,#0x003f      ;CX is number of sectors
424         inc     cx              ; allow Sectors==0 to mean 64
425
426         mul     cx              ; kills DX also
427         xchg    ax,bx           ;save in BX
428
429         mov     ax,[edd_d_addr](si)     ;low part of address
430         mov     dx,[edd_d_addr+2](si)   ;hi part of address
431
432         cmp     dx,bx
433         jae     disk_error2     ;prevent division error
434
435         div     bx              ;AX is cyl, DX is head/sect
436 #if CYL1023
437         cmp     ax,#1023
438 #else
439         cmp     ax,di
440 #endif
441         ja      disk_error2     ;cyl is too big
442
443         shl     ah,#6           ; save hi 2 bits
444         xchg    al,ah
445         xchg    ax,dx
446         div     cl              ;AH = sec-1, AL = head
447         or      dl,ah      ;form Cyl/Sec
448         mov     cx,dx
449         inc     cx              ; sector is 1 based
450
451         pop     dx              ! restore device code
452         mov     dh,al           ! set head#
453         jmp     disk_read2
454
455
456
457 disk_edd:
458         mov     ah,#0x42
459 disk_int13:
460         pop     bx
461
462         mov     bp,#5
463 disk_retry:
464         pusha
465         int     0x13
466 #if 0
467         stc
468         mov     ah,#0x9C
469 #endif
470         jnc     disk_okay
471
472         dec     bp              ! does not alter CF, already 0
473         jz      disk_error3     ! go to "jc" with CF=1 & ZF=1
474
475         xor     ax,ax           ! reset the disk controller
476         int     0x13
477         popa                    ! reset AX,BX,CX,DX,SI
478         dec     bp              ! fix up BP count
479         jmp     disk_retry
480
481
482 disk_geometric:
483         push    eax
484         pop     cx
485         pop     ax
486         mov     dh,ah
487
488 disk_read2:
489         mov     ax,#0x201       ;read, count of 1
490         jmp     disk_int13
491
492
493 disk_okay:
494 ; the pusha block is implicitly removed below
495 ;;;     mov     (si+2*16-1),ah  ! set error code
496 ;   the error code is never checked
497         lea     sp,(si+16)      ! do not touch carry; 
498         popa
499 #ifndef JRC_DS_EQ_SS
500         pop     ds
501 #endif
502         ret
503
504
505
506 ! Pointer Read -- read using pointer in DS:SI
507
508 pread:
509         lodsd                   ! get address
510         or      eax,eax
511         jz      done
512         add     eax,[raid](bp)  ! reloc is 0 on non-raid
513         call    disk_read       
514
515         add     bh,#SECTOR_SIZE/256     ! next sector
516 done:
517         ret
518
519
520
521
522 #if !defined(LCF_NO1STDIAG) || defined(DEBUG_NEW)
523 bout:   rol     ax,#4           ! bring hi-nibble to position
524         call    nout
525         rol     ax,#4           ! bring lo-nibble to position
526 nout:   and     al,#0x0F        ! display one nibble
527         daa                     ! shorter conversion routine
528         add     al,#0xF0
529         adc     al,#0x40        ! is now a hex char 0..9A..F
530 #endif
531 ; display - write byte in AL to console
532 ;       preserves all register contents
533
534 display0:
535 #ifndef LCF_NOVGA
536 display:
537 #endif
538         pusha           ! make sure no register is changed
539         mov     bx,#7           !  BH=0, BL=07
540         mov     ah,#14
541         int     0x10
542         popa            ! restore all the registers
543 #ifdef LCF_NOVGA
544 display:
545 #endif
546         ret
547
548 #ifdef DEBUG_LARGE
549
550 dout:   pushad
551         ror     eax,#16
552         call    wout
553         ror     eax,#16
554         call    wout
555         mov     al,#0x20        ! space
556         call    display
557         popad
558         ret
559
560 wout:   push    ax
561         call    bout    ! put out AH
562         pop     ax
563         push    ax
564         xchg    al,ah
565         call    bout    ! put out AL (now in AH)
566         pop     ax
567         ret
568 #endif
569
570 theend:
571
572 !
573 !   If 'first' loads as the MBR, then there must be space for the partition
574 !   table.  If 'first' loads as the boot record of some partition, then
575 !   the space reserved below is not used.  But we must reserve the area
576 !   as a hedge against the first case.
577 !
578 !
579         .org    MAX_BOOT_SIZE   !
580         .word   0,0,0,0         ! space for NT, DRDOS, and LiLO volume S/N
581
582 !       .org    0x1be           ! spot for the partition table
583 p_table:
584         .blkb   16
585         .blkb   16
586         .blkb   16
587         .blkb   16
588 #ifdef FIRST
589         .org    *-2
590         .long   FIRST           ! boot block check
591 #else
592         .word   0xAA55          ! boot block signature
593 #endif
594
595 ! Better be exactly 0x200
596
597 map2    equ     *               ! addressed as ES:[map2]