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