Magellan Linux

Annotation of /trunk/mkinitrd-magellan/isolinux/runkernel.inc

Parent Directory Parent Directory | Revision Log Revision Log


Revision 532 - (hide annotations) (download)
Sat Sep 1 22:45:15 2007 UTC (16 years, 8 months ago) by niro
File size: 17189 byte(s)
-import if magellan mkinitrd; it is a fork of redhats mkinitrd-5.0.8 with all magellan patches and features; deprecates magellan-src/mkinitrd

1 niro 532 ;; $Id: runkernel.inc,v 1.1 2007-09-01 22:44:05 niro Exp $
2     ;; -----------------------------------------------------------------------
3     ;;
4     ;; Copyright 1994-2005 H. Peter Anvin - All Rights Reserved
5     ;;
6     ;; This program is free software; you can redistribute it and/or modify
7     ;; it under the terms of the GNU General Public License as published by
8     ;; the Free Software Foundation, Inc., 53 Temple Place Ste 330,
9     ;; Boston MA 02111-1307, USA; either version 2 of the License, or
10     ;; (at your option) any later version; incorporated herein by reference.
11     ;;
12     ;; -----------------------------------------------------------------------
13    
14     ;;
15     ;; runkernel.inc
16     ;;
17     ;; Common code for running a Linux kernel
18     ;;
19    
20     ;
21     ; Hook macros, that may or may not be defined
22     ;
23     %ifndef HAVE_SPECIAL_APPEND
24     %macro SPECIAL_APPEND 0
25     %endmacro
26     %endif
27    
28     %ifndef HAVE_UNLOAD_PREP
29     %macro UNLOAD_PREP 0
30     %endmacro
31     %endif
32    
33     ;
34     ; A Linux kernel consists of three parts: boot sector, setup code, and
35     ; kernel code. The boot sector is never executed when using an external
36     ; booting utility, but it contains some status bytes that are necessary.
37     ;
38     ; First check that our kernel is at least 1K and less than 8M (if it is
39     ; more than 8M, we need to change the logic for loading it anyway...)
40     ;
41     ; We used to require the kernel to be 64K or larger, but it has gotten
42     ; popular to use the Linux kernel format for other things, which may
43     ; not be so large.
44     ;
45     is_linux_kernel:
46     cmp dx,80h ; 8 megs
47     ja kernel_corrupt
48     and dx,dx
49     jnz kernel_sane
50     cmp ax,1024 ; Bootsect + 1 setup sect
51     jb kernel_corrupt
52     kernel_sane: push ax
53     push dx
54     push si
55     mov si,loading_msg
56     call cwritestr
57     ;
58     ; Now start transferring the kernel
59     ;
60     push word real_mode_seg
61     pop es
62    
63     movzx eax,ax ; Fix this by using a 32-bit
64     shl edx,16 ; register for the kernel size
65     or eax,edx
66     mov [KernelSize],eax
67     add eax,SECTOR_SIZE-1
68     shr eax,SECTOR_SHIFT
69     mov [KernelSects],eax ; Total sectors in kernel
70    
71     ;
72     ; Now, if we transfer these straight, we'll hit 64K boundaries. Hence we
73     ; have to see if we're loading more than 64K, and if so, load it step by
74     ; step.
75     ;
76    
77     ;
78     ; Start by loading the bootsector/setup code, to see if we need to
79     ; do something funky. It should fit in the first 32K (loading 64K won't
80     ; work since we might have funny stuff up near the end of memory).
81     ; If we have larger than 32K clusters, yes, we're hosed.
82     ;
83     call abort_check ; Check for abort key
84     mov ecx,8000h >> SECTOR_SHIFT ; Half a moby (32K)
85     cmp ecx,[KernelSects]
86     jna .normalkernel
87     mov ecx,[KernelSects]
88     .normalkernel:
89     sub [KernelSects],ecx
90     xor bx,bx
91     pop si ; Cluster pointer on stack
92     call getfssec
93     cmp word [es:bs_bootsign],0AA55h
94     jne kernel_corrupt ; Boot sec signature missing
95    
96     ;
97     ; Save the cluster pointer for later...
98     ;
99     push si
100     ;
101     ; Get the BIOS' idea of what the size of high memory is.
102     ;
103     call highmemsize
104     ;
105     ; Construct the command line (append options have already been copied)
106     ;
107     construct_cmdline:
108     mov di,[CmdLinePtr]
109     mov si,boot_image ; BOOT_IMAGE=
110     mov cx,boot_image_len
111     rep movsb
112     mov si,KernelCName ; Unmangled kernel name
113     mov cx,[KernelCNameLen]
114     rep movsb
115     mov al,' ' ; Space
116     stosb
117    
118     SPECIAL_APPEND ; Module-specific hook
119    
120     mov si,[CmdOptPtr] ; Options from user input
121     call strcpy
122    
123     ;
124     ; Scan through the command line for anything that looks like we might be
125     ; interested in. The original version of this code automatically assumed
126     ; the first option was BOOT_IMAGE=, but that is no longer certain.
127     ;
128     mov si,cmd_line_here
129     xor ax,ax
130     mov [InitRDPtr],ax ; No initrd= option (yet)
131     push es ; Set DS <- real_mode_seg
132     pop ds
133     get_next_opt: lodsb
134     and al,al
135     jz cmdline_end
136     cmp al,' '
137     jbe get_next_opt
138     dec si
139     mov eax,[si]
140     cmp eax,'vga='
141     je is_vga_cmd
142     cmp eax,'mem='
143     je is_mem_cmd
144     %if IS_PXELINUX
145     cmp eax,'keep' ; Is it "keeppxe"?
146     jne .notkeep
147     cmp dword [si+3],'ppxe'
148     jne .notkeep
149     cmp byte [si+7],' ' ; Must be whitespace or EOS
150     ja .notkeep
151     or byte [cs:KeepPXE],1
152     .notkeep:
153     %endif
154     push es ; Save ES -> real_mode_seg
155     push cs
156     pop es ; Set ES <- normal DS
157     mov di,initrd_cmd
158     mov cx,initrd_cmd_len
159     repe cmpsb
160     jne .not_initrd
161    
162     cmp al,' '
163     jbe .noramdisk
164     mov [cs:InitRDPtr],si
165     jmp .not_initrd
166     .noramdisk:
167     xor ax,ax
168     mov [cs:InitRDPtr],ax
169     .not_initrd: pop es ; Restore ES -> real_mode_seg
170     skip_this_opt: lodsb ; Load from command line
171     cmp al,' '
172     ja skip_this_opt
173     dec si
174     jmp short get_next_opt
175     is_vga_cmd:
176     add si,4
177     mov eax,[si-1]
178     mov bx,-1
179     cmp eax,'=nor' ; vga=normal
180     je vc0
181     dec bx ; bx <- -2
182     cmp eax,'=ext' ; vga=ext
183     je vc0
184     dec bx ; bx <- -3
185     cmp eax,'=ask' ; vga=ask
186     je vc0
187     call parseint ; vga=<number>
188     jc skip_this_opt ; Not an integer
189     vc0: mov [bs_vidmode],bx ; Set video mode
190     jmp short skip_this_opt
191     is_mem_cmd:
192     add si,4
193     call parseint
194     jc skip_this_opt ; Not an integer
195     %if HIGHMEM_SLOP != 0
196     sub ebx,HIGHMEM_SLOP
197     %endif
198     mov [cs:HighMemSize],ebx
199     jmp short skip_this_opt
200     cmdline_end:
201     push cs ; Restore standard DS
202     pop ds
203     sub si,cmd_line_here
204     mov [CmdLineLen],si ; Length including final null
205     ;
206     ; Now check if we have a large kernel, which needs to be loaded high
207     ;
208     mov dword [RamdiskMax], HIGHMEM_MAX ; Default initrd limit
209     cmp dword [es:su_header],HEADER_ID ; New setup code ID
210     jne old_kernel ; Old kernel, load low
211     cmp word [es:su_version],0200h ; Setup code version 2.0
212     jb old_kernel ; Old kernel, load low
213     cmp word [es:su_version],0201h ; Version 2.01+?
214     jb new_kernel ; If 2.00, skip this step
215     mov word [es:su_heapend],linux_stack ; Set up the heap
216     or byte [es:su_loadflags],80h ; Let the kernel know we care
217     cmp word [es:su_version],0203h ; Version 2.03+?
218     jb new_kernel ; Not 2.03+
219     mov eax,[es:su_ramdisk_max]
220     mov [RamdiskMax],eax ; Set the ramdisk limit
221    
222     ;
223     ; We definitely have a new-style kernel. Let the kernel know who we are,
224     ; and that we are clueful
225     ;
226     new_kernel:
227     mov byte [es:su_loader],my_id ; Show some ID
228     movzx ax,byte [es:bs_setupsecs] ; Variable # of setup sectors
229     mov [SetupSecs],ax
230     xor eax,eax
231     mov [es:su_ramdisklen],eax ; No initrd loaded yet
232    
233     ;
234     ; About to load the kernel. This is a modern kernel, so use the boot flags
235     ; we were provided.
236     ;
237     mov al,[es:su_loadflags]
238     mov [LoadFlags],al
239     ;
240     ; Load the kernel. We always load it at 100000h even if we're supposed to
241     ; load it "low"; for a "low" load we copy it down to low memory right before
242     ; jumping to it.
243     ;
244     read_kernel:
245     mov si,KernelCName ; Print kernel name part of
246     call cwritestr ; "Loading" message
247     mov si,dotdot_msg ; Print dots
248     call cwritestr
249    
250     mov eax,[HighMemSize]
251     sub eax,100000h ; Load address
252     cmp eax,[KernelSize]
253     jb no_high_mem ; Not enough high memory
254     ;
255     ; Move the stuff beyond the setup code to high memory at 100000h
256     ;
257     movzx esi,word [SetupSecs] ; Setup sectors
258     inc si ; plus 1 boot sector
259     shl si,9 ; Convert to bytes
260     mov ecx,8000h ; 32K
261     sub ecx,esi ; Number of bytes to copy
262     push ecx
263     add esi,(real_mode_seg << 4) ; Pointer to source
264     mov edi,100000h ; Copy to address 100000h
265    
266     call bcopy ; Transfer to high memory
267    
268     ; On exit EDI -> where to load the rest
269    
270     mov si,dot_msg ; Progress report
271     call cwritestr
272     call abort_check
273    
274     pop ecx ; Number of bytes in the initial portion
275     pop si ; Restore file handle/cluster pointer
276     mov eax,[KernelSize]
277     sub eax,8000h ; Amount of kernel not yet loaded
278     jbe high_load_done ; Zero left (tiny kernel)
279    
280     xor dx,dx ; No padding needed
281     call load_high ; Copy the file
282    
283     high_load_done:
284     mov [KernelEnd],edi
285     mov ax,real_mode_seg ; Set to real mode seg
286     mov es,ax
287    
288     mov si,dot_msg
289     call cwritestr
290    
291     ;
292     ; Now see if we have an initial RAMdisk; if so, do requisite computation
293     ; We know we have a new kernel; the old_kernel code already will have objected
294     ; if we tried to load initrd using an old kernel
295     ;
296     load_initrd:
297     cmp word [InitRDPtr],0
298     jz nk_noinitrd
299     call parse_load_initrd
300     nk_noinitrd:
301     ;
302     ; Abandon hope, ye that enter here! We do no longer permit aborts.
303     ;
304     call abort_check ; Last chance!!
305    
306     mov si,ready_msg
307     call cwritestr
308    
309     call vgaclearmode ; We can't trust ourselves after this
310    
311     UNLOAD_PREP ; Module-specific hook
312    
313     ;
314     ; Now, if we were supposed to load "low", copy the kernel down to 10000h
315     ; and the real mode stuff to 90000h. We assume that all bzImage kernels are
316     ; capable of starting their setup from a different address.
317     ;
318     mov ax,real_mode_seg
319     mov fs,ax
320    
321     ;
322     ; Copy command line. Unfortunately, the kernel boot protocol requires
323     ; the command line to exist in the 9xxxxh range even if the rest of the
324     ; setup doesn't.
325     ;
326     cli ; In case of hooked interrupts
327     test byte [LoadFlags],LOAD_HIGH
328     jz need_high_cmdline
329     cmp word [fs:su_version],0202h ; Support new cmdline protocol?
330     jb need_high_cmdline
331     ; New cmdline protocol
332     ; Store 32-bit (flat) pointer to command line
333     mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4) + cmd_line_here
334     jmp short in_proper_place
335    
336     need_high_cmdline:
337     ;
338     ; Copy command line up to 90000h
339     ;
340     mov ax,9000h ; Note AL <- 0
341     mov es,ax
342     mov si,cmd_line_here
343     mov di,si
344     mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic
345     mov [fs:kern_cmd_offset],di ; Store pointer
346    
347     mov cx,[CmdLineLen]
348     cmp cx,255
349     jna .len_ok
350     mov cx,255 ; Protocol < 0x202 has 255 as hard limit
351     .len_ok:
352     fs rep movsb
353     stosb ; Final null, note AL == 0 already
354    
355     push fs
356     pop es
357    
358     test byte [LoadFlags],LOAD_HIGH
359     jnz in_proper_place ; If high load, we're done
360    
361     ;
362     ; Loading low; we can't assume it's safe to run in place.
363     ;
364     ; Copy real_mode stuff up to 90000h
365     ;
366     mov ax,9000h
367     mov es,ax
368     mov cx,[SetupSecs]
369     inc cx ; Setup + boot sector
370     shl cx,7 ; Sectors -> dwords
371     xor si,si
372     xor di,di
373     fs rep movsd ; Copy setup + boot sector
374     ;
375     ; Some kernels in the 1.2 ballpark but pre-bzImage have more than 4
376     ; setup sectors, but the boot protocol had not yet been defined. They
377     ; rely on a signature to figure out if they need to copy stuff from
378     ; the "protected mode" kernel area. Unfortunately, we used that area
379     ; as a transfer buffer, so it's going to find the signature there.
380     ; Hence, zero the low 32K beyond the setup area.
381     ;
382     mov di,[SetupSecs]
383     inc di ; Setup + boot sector
384     mov cx,32768/512 ; Sectors/32K
385     sub cx,di ; Remaining sectors
386     shl di,9 ; Sectors -> bytes
387     shl cx,7 ; Sectors -> dwords
388     xor eax,eax
389     rep stosd ; Clear region
390     ;
391     ; Copy the kernel down to the "low" location
392     ;
393     mov ecx,[KernelSize]
394     mov esi,100000h
395     mov edi,10000h
396     call bcopy
397    
398     ;
399     ; Now everything is where it needs to be...
400     ;
401     ; When we get here, es points to the final segment, either
402     ; 9000h or real_mode_seg
403     ;
404     in_proper_place:
405    
406     ;
407     ; If the default root device is set to FLOPPY (0000h), change to
408     ; /dev/fd0 (0200h)
409     ;
410     cmp word [es:bs_rootdev],byte 0
411     jne root_not_floppy
412     mov word [es:bs_rootdev],0200h
413     root_not_floppy:
414    
415     ;
416     ; Copy the disk table to high memory, then re-initialize the floppy
417     ; controller
418     ;
419     %if IS_SYSLINUX || IS_MDSLINUX
420     lgs si,[cs:fdctab]
421     mov di,linux_fdctab
422     mov cx,6 ; 12 bytes
423     gs rep movsw
424     mov [cs:fdctab],word linux_fdctab ; Save new floppy tab pos
425     mov [cs:fdctab+2],es
426     %endif
427     ;
428     ; Linux wants the floppy motor shut off before starting the kernel,
429     ; at least bootsect.S seems to imply so.
430     ;
431     kill_motor:
432     xor ax,ax
433     xor dx,dx
434     int 13h
435    
436     ;
437     ; If we're debugging, wait for a keypress so we can read any debug messages
438     ;
439     %ifdef debug
440     xor ax,ax
441     int 16h
442     %endif
443     ;
444     ; Set up segment registers and the Linux real-mode stack
445     ; Note: es == the real mode segment
446     ;
447     cli
448     mov bx,es
449     mov ds,bx
450     mov fs,bx
451     mov gs,bx
452     mov ss,bx
453     mov sp,linux_stack
454     ;
455     ; We're done... now RUN THAT KERNEL!!!!
456     ; Setup segment == real mode segment + 020h; we need to jump to offset
457     ; zero in the real mode segment.
458     ;
459     add bx,020h
460     push bx
461     push word 0h
462     retf
463    
464     ;
465     ; Load an older kernel. Older kernels always have 4 setup sectors, can't have
466     ; initrd, and are always loaded low.
467     ;
468     old_kernel:
469     cmp word [InitRDPtr],0 ; Old kernel can't have initrd
470     je load_old_kernel
471     mov si,err_oldkernel
472     jmp abort_load
473     load_old_kernel:
474     mov word [SetupSecs],4 ; Always 4 setup sectors
475     mov byte [LoadFlags],0 ; Always low
476     jmp read_kernel
477    
478     ;
479     ; parse_load_initrd
480     ;
481     ; Parse an initrd= option and load the initrds. Note that we load
482     ; from the high end of memory first, so we parse this option from
483     ; left to right.
484     ;
485     parse_load_initrd:
486     push es
487     push ds
488     mov ax,real_mode_seg
489     mov ds,ax
490     push cs
491     pop es ; DS == real_mode_seg, ES == CS
492    
493     mov si,[cs:InitRDPtr]
494     .find_end:
495     lodsb
496     cmp al,' '
497     ja .find_end
498     ; Now SI points to one character beyond the
499     ; byte that ended this option.
500    
501     .get_chunk:
502     dec si
503    
504     ; DS:SI points to a termination byte
505    
506     xor ax,ax
507     xchg al,[si] ; Zero-terminate
508     push si ; Save ending byte address
509     push ax ; Save ending byte
510    
511     .find_start:
512     dec si
513     cmp si,[cs:InitRDPtr]
514     je .got_start
515     cmp byte [si],','
516     jne .find_start
517    
518     ; It's a comma byte
519     inc si
520    
521     .got_start:
522     push si
523     mov di,InitRD ; Target buffer for mangled name
524     call mangle_name
525     call loadinitrd
526     pop si
527    
528     pop ax
529     pop di
530     mov [di],al ; Restore ending byte
531    
532     cmp si,[cs:InitRDPtr]
533     ja .get_chunk
534    
535     pop ds
536     pop es
537     ret
538    
539     ;
540     ; Load RAM disk into high memory
541     ;
542     ; Input: InitRD - set to the mangled name of the initrd
543     ;
544     loadinitrd:
545     push ds
546     push es
547     mov ax,cs ; CS == DS == ES
548     mov ds,ax
549     mov es,ax
550     mov si,InitRD
551     mov di,InitRDCName
552     call unmangle_name ; Create human-readable name
553     sub di,InitRDCName
554     mov [InitRDCNameLen],di
555     mov di,InitRD
556     call searchdir ; Look for it in directory
557     jz .notthere
558    
559     mov cx,dx
560     shl ecx,16
561     mov cx,ax ; ECX <- ram disk length
562    
563     mov ax,real_mode_seg
564     mov es,ax
565    
566     push ecx ; Bytes to load
567     cmp dword [es:su_ramdisklen],0
568     je .nopadding ; Don't pad the last initrd
569     add ecx,4095
570     and cx,0F000h
571     .nopadding:
572     add [es:su_ramdisklen],ecx
573     mov edx,[HighMemSize] ; End of memory
574     dec edx
575     mov eax,[RamdiskMax] ; Highest address allowed by kernel
576     cmp edx,eax
577     jna .memsize_ok
578     mov edx,eax ; Adjust to fit inside limit
579     .memsize_ok:
580     inc edx
581     and dx,0F000h ; Round down to 4K boundary
582     sub edx,ecx ; Subtract size of ramdisk
583     and dx,0F000h ; Round down to 4K boundary
584     cmp edx,[KernelEnd] ; Are we hitting the kernel image?
585     jb no_high_mem
586    
587     mov [es:su_ramdiskat],edx ; Load address
588     mov [RamdiskMax],edx ; Next initrd loaded here
589    
590     mov edi,edx ; initrd load address
591     push si
592     mov si,crlfloading_msg ; Write "Loading "
593     call cwritestr
594     mov si,InitRDCName ; Write ramdisk name
595     call cwritestr
596     mov si,dotdot_msg ; Write dots
597     call cwritestr
598     pop si
599    
600     pop eax ; Bytes to load
601     mov dx,0FFFh ; Pad to page
602     call load_high ; Load the file
603    
604     pop es
605     pop ds
606     jmp crlf ; Print carriage return and return
607    
608     .notthere:
609     mov si,err_noinitrd
610     call cwritestr
611     mov si,InitRDCName
612     call cwritestr
613     mov si,crlf_msg
614     jmp abort_load
615    
616     no_high_mem: ; Error routine
617     mov si,err_nohighmem
618     jmp abort_load
619    
620     ret
621    
622     section .data
623     boot_image db 'BOOT_IMAGE='
624     boot_image_len equ $-boot_image
625    
626     section .bss
627     alignb 4
628     RamdiskMax resd 1 ; Highest address for ramdisk
629     KernelSize resd 1 ; Size of kernel in bytes
630     KernelSects resd 1 ; Size of kernel in sectors
631     KernelEnd resd 1 ; Ending address of the kernel image
632     CmdLineLen resw 1 ; Length of command line including null
633     SetupSecs resw 1 ; Number of setup sectors
634     InitRDPtr resw 1 ; Pointer to initrd= option in command line
635     LoadFlags resb 1 ; Loadflags from kernel