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