Imported Upstream version 23.2
[rrq/maintain_lilo.git] / src / bootsect.S
1 !
2 !       bootsect.s
3 !       Copyright (C) 1991, 1992 Linus Torvalds
4 !
5 !       modified by Drew Eckhardt
6 !       modified by Bruce Evans (bde)
7 !       modified by John Coffman (2000, 2001)
8 !       modified by Joachim Wiedorn (2011)
9 !
10 !
11 ! bootsect.s is loaded at 0x7c00 by the bios-startup routines, and moves
12 ! itself out of the way to address 0x90000, and jumps there.
13 !
14 ! bde - should not jump blindly, there may be systems with only 512K low
15 ! memory.  Use int 0x12 to get the top of memory, etc.
16 !
17 ! It then loads 'setup' directly after itself (0x90200), and the system
18 ! at 0x10000, using BIOS interrupts. 
19 !
20 ! NOTE! currently system is at most (8*65536-4096) bytes long. This should 
21 ! be no problem, even in the future. I want to keep it simple. This 508 kB
22 ! kernel size should be enough, especially as this doesn't contain the
23 ! buffer cache as in minix (and especially now that the kernel is 
24 ! compressed :-)
25 !
26 ! The loader has been made as simple as possible, and continuous
27 ! read errors will result in a unbreakable loop. Reboot by hand. It
28 ! loads pretty fast by getting whole tracks at a time whenever possible.
29
30 ;#include <linux/config.h> /* for CONFIG_ROOT_RDONLY */
31 ;#include <asm/boot.h>
32
33 .text
34
35 SIZEBYTES = SIZEDISKB+511               ! round disk.b size for division
36 SETUPSECS = SIZEBYTES/512               ! size of disk.b in sectors
37 BOOTSEG   = 0x07C0                      ! original address of boot-sector
38 INITSEG   = 0x9000                      ! we move boot here - out of the way
39 SETUPSEG  = INITSEG+0x20                ! setup starts here
40 SYSSEG    = 0x1000                      ! system loaded at 0x10000 (65536).
41 MAX_SETUPSECS = 63                      ! same as  lilo.h   (for kernel >= 2.4.0)
42 STK_SIZE  = MAX_SETUPSECS*512+512       ! 0x4000
43
44 #ifndef SIZEKRNL
45 SYSSIZE   = 0x8000                      ! system size: number of 16-byte clicks
46                                         ! to be loaded
47 #else
48 SIZEKRNLP       = SIZEKRNL+15
49 SYSSIZE         = SIZEKRNLP/16
50 #endif
51 ASK_VGA   = 0xfffd
52
53 ! ROOT_DEV & SWAP_DEV are now written by "build".
54 ROOT_DEV = 0
55 SWAP_DEV = 0
56 #ifndef SVGA_MODE
57 #define SVGA_MODE ASK_VGA
58 #endif
59 #ifndef RAMDISK
60 #define RAMDISK 0
61 #endif 
62 #ifndef CONFIG_ROOT_RDONLY
63 #define CONFIG_ROOT_RDONLY 1
64 #endif
65
66 ! ld86 requires an entry symbol. This may as well be the usual one.
67 .globl  _main
68 _main:
69         mov     ax,#BOOTSEG
70         mov     ds,ax
71
72         int     0x12
73         sub     ax,#STK_SIZE/1024
74         shl     ax,#10-4
75         mov     bx,#INITSEG
76         cmp     ax,bx
77         jb      *+3
78         xchg    ax,bx
79
80         mov     es,ax
81         mov     cx,#256
82         sub     si,si
83         sub     di,di
84         cld
85         rep
86         movsw
87
88         mov     di,#STK_SIZE-12 ! 0x4000 is arbitrary value >= length of
89                                 ! bootsect + length of setup + room for stack
90                                 ! 12 is disk parm size
91
92 ! bde - changed 0xff00 to 0x4000 to use debugger at 0x6400 up (bde).  We
93 ! wouldn't have to worry about this if we checked the top of memory.  Also
94 ! my BIOS can be configured to put the wini drive tables in high memory
95 ! instead of in the vector table.  The old stack might have clobbered the
96 ! drive table.
97
98         mov     ds,ax
99         mov     ss,ax           ! put stack at INITSEG:0x4000-12.
100         mov     sp,di
101 ;       jmpi    go,INITSEG
102         push    es
103         push    #go
104         retf
105
106 ! ax and es already contain INITSEG
107
108 go:
109         add     ax,#0x20        ! seg offset to SETUPSEG
110         mov     setupseg,ax
111
112 /*
113  *      Many BIOS's default disk parameter tables will not 
114  *      recognize multi-sector reads beyond the maximum sector number
115  *      specified in the default diskette parameter tables - this may
116  *      mean 7 sectors in some cases.
117  *
118  *      Since single sector reads are slow and out of the question,
119  *      we must take care of this by creating new parameter tables
120  *      (for the first disk) in RAM.  We will set the maximum sector
121  *      count to 36 - the most we will encounter on an ED 2.88.  
122  *
123  *      High doesn't hurt.  Low does.
124  *
125  *      Segments are as follows: ds=es=ss=cs - INITSEG,
126  *              fs = 0, gs is unused.
127  */
128
129 ! cx contains 0 from rep movsw above
130
131         mov     bx,#0x78                ! fs:bx is parameter table address
132         push    ds
133         push    cx                      ! contains 0 from  rep movsw above
134         pop     ds
135         lds     si,(bx)                 ! ds:si is source
136
137         mov     cl,#6                   ! copy 12 bytes
138         cld
139         push    di
140
141         rep
142         movsw
143
144         pop     di
145         pop     ds
146
147         movb    4(di),*36               ! patch sector count
148
149 ;;;     seg fs
150         push    ds
151         push    #0
152         pop     ds
153         mov     (bx),di
154 ;;;     seg fs
155         mov     2(bx),es
156         pop     ds
157
158 ! load the setup-sectors directly after the bootblock.
159 ! Note that 'es' is already set up.
160 ! Also cx is 0 from rep movsw above.
161
162 load_setup:
163         xor     ah,ah                   ! reset FDC 
164         xor     dl,dl
165         int     0x13    
166
167         xor     dx, dx                  ! drive 0, head 0
168         mov     cl,#0x02                ! sector 2, track 0
169         mov     bx,#0x0200              ! address = 512, in INITSEG
170         mov     ah,#0x02                ! service 2, nr of sectors
171         mov     al,setup_sects          ! (assume all on head 0, track 0)
172         int     0x13                    ! read it
173         jnc     ok_load_setup           ! ok - continue
174
175         push    ax                      ! dump error code
176         call    print_nl
177         mov     bp, sp
178         call    print_hex
179         pop     ax      
180         
181         jmp     load_setup
182
183 ok_load_setup:
184
185 ! Get disk drive parameters, specifically nr of sectors/track
186
187 #if 0
188
189 ! bde - the Phoenix BIOS manual says function 0x08 only works for fixed
190 ! disks.  It doesn't work for one of my BIOS's (1987 Award).  It was
191 ! fatal not to check the error code.
192
193         xor     dl,dl
194         mov     ah,#0x08                ! AH=8 is get drive parameters
195         int     0x13
196         xor     ch,ch
197 #else
198
199 ! It seems that there is no BIOS call to get the number of sectors.  Guess
200 ! 36 sectors if sector 36 can be read, 18 sectors if sector 18 can be read,
201 ! 15 if sector 15 can be read.  Otherwise guess 9.
202
203         mov     si,#disksizes           ! table of sizes to try
204
205 probe_loop:
206         lodsb
207         cbw                             ! extend to word
208         mov     sectors, ax
209         cmp     si,#disksizes+4
210         jae     got_sectors             ! if all else fails, try 9
211         xchg    ax, cx                  ! cx = track and sector
212         xor     dx, dx                  ! drive 0, head 0
213         xor     bl, bl
214         mov     bh,setup_sects
215         inc     bh
216         shl     bh,#1                   ! address after setup (es = cs)
217         mov     ax,#0x0201              ! service 2, 1 sector
218         int     0x13
219         jc      probe_loop              ! try next value
220
221 #endif
222
223 got_sectors:
224
225
226 ! Print some inane message
227
228         mov     ah,#0x03                ! read cursor pos
229         xor     bh,bh
230         int     0x10
231         
232         mov     cx,#9
233         mov     bx,#0x0007              ! page 0, attribute 7 (normal)
234         mov     bp,#msg1
235         mov     ax,#0x1301              ! write string, move cursor
236         int     0x10
237
238 ! ok, we've written the message, now
239 ! we want to load the system (at 0x10000)
240
241 #if 0
242         mov     ax,#SYSSEG
243         mov     es,ax           ! segment of 0x010000
244 #else
245         push    #SYSSEG
246         pop     es
247 #endif
248 #ifdef SIZEKRNL
249         call    read_it
250 #endif
251         call    kill_motor
252         call    print_nl
253
254 ! After that we check which root-device to use. If the device is
255 ! defined (!= 0), nothing is done and the given device is used.
256 ! Otherwise, one of /dev/fd0H2880 (2,32) or /dev/PS0 (2,28) or /dev/at0 (2,8),
257 ! depending on the number of sectors we pretend to know we have.
258
259 #if 0
260 ;;      seg cs
261         mov     ax,root_dev
262         or      ax,ax
263         jne     root_defined
264 ;;      seg cs
265         mov     bx,sectors
266         mov     ax,#0x0208              ! /dev/ps0 - 1.2Mb
267         cmp     bx,#15
268         je      root_defined
269         mov     al,#0x1c                ! /dev/PS0 - 1.44Mb
270         cmp     bx,#18
271         je      root_defined
272         mov     al,#0x20                ! /dev/fd0H2880 - 2.88Mb
273         cmp     bx,#36
274         je      root_defined
275         mov     al,#0                   ! /dev/fd0 - autodetect
276 root_defined:
277 ;;      seg cs
278         mov     root_dev,ax
279 #endif
280
281 ! after that (everything loaded), we jump to
282 ! the setup-routine loaded directly after
283 ! the bootblock:
284
285         jmpi    0,SETUPSEG
286 setupseg        =       *-2
287
288 ! This routine loads the system at address 0x10000, making sure
289 ! no 64kB boundaries are crossed. We try to load it as fast as
290 ! possible, loading whole tracks whenever we can.
291 !
292 ! in:   es - starting address segment (normally 0x1000)
293 !
294 sread:  .word 0                 ! sectors read of current track
295 head:   .word 0                 ! current head
296 track:  .word 0                 ! current track
297
298 read_it:
299         mov     al,setup_sects
300         inc     al
301         mov     sread,al
302         mov ax,es
303         test ax,#0x0fff
304 die:    jne die                 ! es must be at 64kB boundary
305         xor bx,bx               ! bx is starting address within segment
306 rp_read:
307 #ifdef __BIG_KERNEL__
308 #define CALL_HIGHLOAD_KLUDGE .word 0x1eff,0x220 ! call far * bootsect_kludge
309                                 ! NOTE: as86 can't assemble this
310         CALL_HIGHLOAD_KLUDGE    ! this is within setup.S
311 #else
312         mov ax,es
313         sub ax,#SYSSEG
314 #endif
315         cmp ax,syssize          ! have we loaded all yet?
316         jbe ok1_read
317         ret
318 ok1_read:
319         mov ax,sectors
320         sub ax,sread
321         mov cx,ax
322         shl cx,#9
323         add cx,bx
324         jnc ok2_read
325         je ok2_read
326         xor ax,ax
327         sub ax,bx
328         shr ax,#9
329 ok2_read:
330         call read_track
331         mov cx,ax
332         add ax,sread
333         cmp ax,sectors
334         jne ok3_read
335         mov ax,#1
336         sub ax,head
337         jne ok4_read
338         inc track
339 ok4_read:
340         mov head,ax
341         xor ax,ax
342 ok3_read:
343         mov sread,ax
344         shl cx,#9
345         add bx,cx
346         jnc rp_read
347         mov ax,es
348         add ah,#0x10
349         mov es,ax
350         xor bx,bx
351         jmp rp_read
352
353 read_track:
354         pusha
355         pusha   
356         mov     ax, #0xe2e      ! loading... message 2e = .
357         mov     bx, #7
358         int     0x10
359         popa            
360
361         mov     dx,track
362         mov     cx,sread
363         inc     cx
364         mov     ch,dl
365         mov     dx,head
366         mov     dh,dl
367         and     dx,#0x0100
368         mov     ah,#2
369         
370         push    dx                              ! save for error dump
371         push    cx
372         push    bx
373         push    ax
374
375         int     0x13
376         jc      bad_rt
377         add     sp, #8
378         popa
379         ret
380
381 bad_rt: push    ax                              ! save error code
382         call    print_all                       ! ah = error, al = read
383         
384         
385         xor ah,ah
386         xor dl,dl
387         int 0x13
388         
389
390         add     sp, #10
391         popa    
392         jmp read_track
393
394 /*
395  *      print_all is for debugging purposes.  
396  *      It will print out all of the registers.  The assumption is that this is
397  *      called from a routine, with a stack frame like
398  *      dx 
399  *      cx
400  *      bx
401  *      ax
402  *      error
403  *      ret <- sp
404  *
405 */
406  
407 print_all:
408         mov     cx, #5          ! error code + 4 registers
409         mov     bp, sp  
410
411 print_loop:
412         push    cx              ! save count left
413         call    print_nl        ! nl for readability
414
415         cmp     cl, #5
416         jae     no_reg          ! see if register name is needed
417         
418         mov     ax, #0xe05 + 'A - 1
419         sub     al, cl
420         int     0x10
421
422         mov     al, #'X
423         int     0x10
424
425         mov     al, #':
426         int     0x10
427
428 no_reg:
429         add     bp, #2          ! next register
430         call    print_hex       ! print it
431         pop     cx
432         loop    print_loop
433         ret
434
435 print_nl:
436         mov     ax, #0xe0d      ! CR
437         int     0x10
438         mov     al, #0xa        ! LF
439         int     0x10
440         ret
441
442 /*
443  *      print_hex is for debugging purposes, and prints the word
444  *      pointed to by ss:bp in hexadecimal.
445 */
446
447 print_hex:
448         mov     cx, #4          ! 4 hex digits
449         mov     dx, (bp)        ! load word into dx
450 print_digit:
451         rol     dx, #4          ! rotate so that lowest 4 bits are used
452         mov     ax, #0xe0f      ! ah = request, al = mask for nybble
453         and     al, dl
454 #if 0
455         add     al, #0x90       ! convert al to ASCII hex (four instructions)
456         daa
457         adc     al, #0x40
458         daa
459 #else
460         daa                     ! shorter conversion routine
461         add     al,#0xF0
462         adc     al,#0x40        ! is now a hex char 0..9A..F
463 #endif
464         int     0x10
465         loop    print_digit
466         ret
467
468
469 /*
470  * This procedure turns off the floppy drive motor, so
471  * that we enter the kernel in a known state, and
472  * don't have to worry about it later.
473  */
474 kill_motor:
475         push    dx
476         mov     dx,#0x3f2
477         xor     al,al
478         out     dx,al           ; outb
479         pop     dx
480         ret
481
482 sectors:
483         .word 0
484
485 disksizes:
486         .byte 36,18,15,9
487
488 msg1:
489         .byte 13,10
490         .ascii "Loading"
491         .byte 0
492
493 .org 497
494 setup_sects:
495         .byte SETUPSECS
496 root_flags:
497         .word CONFIG_ROOT_RDONLY
498 syssize:
499         .word SYSSIZE
500 swap_dev:
501         .word SWAP_DEV
502 ram_size:
503         .word RAMDISK
504 vid_mode:
505         .word SVGA_MODE
506 root_dev:
507         .word ROOT_DEV
508 boot_flag:
509         .word 0xAA55