Magellan Linux

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1133 - (hide annotations) (download)
Thu Aug 19 09:50:43 2010 UTC (13 years, 8 months ago) by niro
File size: 17162 byte(s)
-updated to isolinux-3.86
1 niro 532 ;; -----------------------------------------------------------------------
2     ;;
3 niro 1133 ;; Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
4     ;; Copyright 2009-2010 Intel Corporation; author: H. Peter Anvin
5     ;;
6 niro 532 ;; 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 niro 1133 ;;
17 niro 532 ;; Common code for running a Linux kernel
18     ;;
19    
20     ;
21     ; Hook macros, that may or may not be defined
22     ;
23     %ifndef HAVE_UNLOAD_PREP
24     %macro UNLOAD_PREP 0
25     %endmacro
26     %endif
27    
28     ;
29     ; A Linux kernel consists of three parts: boot sector, setup code, and
30     ; kernel code. The boot sector is never executed when using an external
31     ; booting utility, but it contains some status bytes that are necessary.
32     ;
33 niro 1133 ; First check that our kernel is at least 1K, or else it isn't long
34     ; enough to have the appropriate headers.
35 niro 532 ;
36     ; We used to require the kernel to be 64K or larger, but it has gotten
37     ; popular to use the Linux kernel format for other things, which may
38     ; not be so large.
39     ;
40 niro 1133 ; Additionally, we used to have a test for 8 MB or smaller. Equally
41     ; obsolete.
42     ;
43 niro 532 is_linux_kernel:
44 niro 1133 push si ; <A> file pointer
45    
46 niro 532 ;
47     ; Now start transferring the kernel
48     ;
49     push word real_mode_seg
50     pop es
51    
52     ;
53     ; Start by loading the bootsector/setup code, to see if we need to
54     ; do something funky. It should fit in the first 32K (loading 64K won't
55     ; work since we might have funny stuff up near the end of memory).
56     ;
57     call abort_check ; Check for abort key
58 niro 1133 mov cx,8000h >> SECTOR_SHIFT ; Half a moby (32K)
59 niro 532 xor bx,bx
60 niro 1133 pop si ; <A> file pointer
61 niro 532 call getfssec
62 niro 1133 cmp cx,1024
63     jb kernel_corrupt
64 niro 532 cmp word [es:bs_bootsign],0AA55h
65     jne kernel_corrupt ; Boot sec signature missing
66    
67     ;
68 niro 1133 ; Save the file pointer for later...
69 niro 532 ;
70 niro 1133 push si ; <A> file pointer
71    
72 niro 532 ;
73     ; Construct the command line (append options have already been copied)
74     ;
75     construct_cmdline:
76     mov di,[CmdLinePtr]
77 niro 1133 mov si,boot_image ; BOOT_IMAGE=
78 niro 532 mov cx,boot_image_len
79     rep movsb
80 niro 1133 mov si,KernelCName ; Unmangled kernel name
81 niro 532 mov cx,[KernelCNameLen]
82     rep movsb
83     mov al,' ' ; Space
84     stosb
85    
86 niro 1133 call do_ip_append ; Handle IPAppend
87 niro 532
88     mov si,[CmdOptPtr] ; Options from user input
89     call strcpy
90    
91     ;
92     ; Scan through the command line for anything that looks like we might be
93     ; interested in. The original version of this code automatically assumed
94     ; the first option was BOOT_IMAGE=, but that is no longer certain.
95     ;
96 niro 1133 parse_cmdline:
97     mov di,cmd_line_here
98     .skipspace: mov al,[es:di]
99     inc di
100     .skipspace_loaded:
101 niro 532 and al,al
102     jz cmdline_end
103     cmp al,' '
104 niro 1133 jbe .skipspace
105     dec di
106    
107     ; ES:DI now points to the beginning of an option
108     mov si,options_list
109     .next_opt:
110     movzx cx,byte [si]
111     jcxz .skip_opt
112     push di
113     inc si
114 niro 532 repe cmpsb
115 niro 1133 jne .no_match
116 niro 532
117 niro 1133 ; This either needs to have been an option with parameter,
118     ; or be followed by EOL/whitespace
119     mov ax,[es:di-1] ; AL = last chr; AH = following
120     cmp al,'='
121     je .is_match
122     cmp ah,' '
123     ja .no_match
124     .is_match:
125     pop ax ; Drop option pointer on stack
126     call [si]
127     .skip_opt:
128     mov al,[es:di]
129     inc di
130 niro 532 cmp al,' '
131 niro 1133 ja .skip_opt
132     jmp .skipspace_loaded
133     .no_match:
134     pop di
135     add si,cx ; Skip remaining bytes
136     inc si ; Skip function pointer
137     inc si
138     jmp .next_opt
139    
140     opt_vga:
141     mov ax,[es:di-1]
142     mov bx,-1
143     cmp ax,'=n' ; vga=normal
144     je .vc0
145 niro 532 dec bx ; bx <- -2
146 niro 1133 cmp ax,'=e' ; vga=ext
147     je .vc0
148     dec bx ; bx <- -3
149     cmp ax,'=a' ; vga=ask
150     je .vc0
151     mov bx,0x0f04 ; bx <- 0x0f04 (current mode)
152     cmp ax,'=c' ; vga=current
153     je .vc0
154     call parseint_esdi ; vga=<number>
155     jc .skip ; Not an integer
156     .vc0: mov [es:bs_vidmode],bx ; Set video mode
157     .skip:
158     ret
159    
160     opt_mem:
161     call parseint_esdi
162     jc .skip
163 niro 532 %if HIGHMEM_SLOP != 0
164     sub ebx,HIGHMEM_SLOP
165     %endif
166 niro 1133 mov [MyHighMemSize],ebx
167     .skip:
168     ret
169    
170     opt_quiet:
171     mov byte [QuietBoot],QUIET_FLAG
172     ret
173    
174     %if IS_PXELINUX
175     opt_keeppxe:
176     or byte [KeepPXE],1 ; KeepPXE set by command line
177     ret
178     %endif
179    
180     opt_initrd:
181     mov ax,di
182     cmp byte [es:di],' '
183     ja .have_initrd
184     xor ax,ax
185     .have_initrd:
186     mov [InitRDPtr],ax
187     ret
188    
189     ;
190     ; After command line parsing...
191     ;
192 niro 532 cmdline_end:
193 niro 1133 sub di,cmd_line_here
194     mov [CmdLineLen],di ; Length including final null
195    
196 niro 532 ;
197     ; Now check if we have a large kernel, which needs to be loaded high
198     ;
199 niro 1133 prepare_header:
200 niro 532 mov dword [RamdiskMax], HIGHMEM_MAX ; Default initrd limit
201     cmp dword [es:su_header],HEADER_ID ; New setup code ID
202 niro 1133 jne old_kernel ; Old kernel, load low
203     mov ax,[es:su_version]
204     mov [KernelVersion],ax
205     cmp ax,0200h ; Setup code version 2.0
206     jb old_kernel ; Old kernel, load low
207     cmp ax,0201h ; Version 2.01+?
208 niro 532 jb new_kernel ; If 2.00, skip this step
209 niro 1133 ; Set up the heap (assuming loading high for now)
210     mov word [es:su_heapend],linux_stack-512
211 niro 532 or byte [es:su_loadflags],80h ; Let the kernel know we care
212 niro 1133 cmp ax,0203h ; Version 2.03+?
213 niro 532 jb new_kernel ; Not 2.03+
214     mov eax,[es:su_ramdisk_max]
215     mov [RamdiskMax],eax ; Set the ramdisk limit
216    
217     ;
218     ; We definitely have a new-style kernel. Let the kernel know who we are,
219     ; and that we are clueful
220     ;
221     new_kernel:
222     mov byte [es:su_loader],my_id ; Show some ID
223     xor eax,eax
224     mov [es:su_ramdisklen],eax ; No initrd loaded yet
225    
226     ;
227     ; About to load the kernel. This is a modern kernel, so use the boot flags
228     ; we were provided.
229     ;
230     mov al,[es:su_loadflags]
231 niro 1133 or al,[QuietBoot] ; Set QUIET_FLAG if needed
232     mov [es:su_loadflags],al
233 niro 532 mov [LoadFlags],al
234 niro 1133
235     any_kernel:
236     mov si,loading_msg
237     call writestr_qchk
238     mov si,KernelCName ; Print kernel name part of
239     call writestr_qchk ; "Loading" message
240    
241 niro 532 ;
242     ; Load the kernel. We always load it at 100000h even if we're supposed to
243     ; load it "low"; for a "low" load we copy it down to low memory right before
244     ; jumping to it.
245     ;
246     read_kernel:
247 niro 1133 movzx ax,byte [es:bs_setupsecs] ; Setup sectors
248     and ax,ax
249     jnz .sects_ok
250     mov al,4 ; 0 = 4 setup sectors
251     .sects_ok:
252     inc ax ; Including the boot sector
253     mov [SetupSecs],ax
254 niro 532
255 niro 1133 call dot_pause
256    
257 niro 532 ;
258     ; Move the stuff beyond the setup code to high memory at 100000h
259     ;
260     movzx esi,word [SetupSecs] ; Setup sectors
261     shl si,9 ; Convert to bytes
262     mov ecx,8000h ; 32K
263     sub ecx,esi ; Number of bytes to copy
264     add esi,(real_mode_seg << 4) ; Pointer to source
265     mov edi,100000h ; Copy to address 100000h
266    
267     call bcopy ; Transfer to high memory
268    
269 niro 1133 pop si ; <A> File pointer
270     and si,si ; EOF already?
271     jz high_load_done
272    
273 niro 532 ; On exit EDI -> where to load the rest
274    
275 niro 1133 mov bx,dot_pause
276     or eax,-1 ; Load the whole file
277     mov dx,3 ; Pad to dword
278     call load_high
279 niro 532
280     high_load_done:
281     mov [KernelEnd],edi
282     mov ax,real_mode_seg ; Set to real mode seg
283     mov es,ax
284    
285     mov si,dot_msg
286 niro 1133 call writestr_qchk
287 niro 532
288     ;
289 niro 1133 ; Some older kernels (1.2 era) would have more than 4 setup sectors, but
290     ; would not rely on the boot protocol to manage that. These kernels fail
291     ; if they see protected-mode kernel data after the setup sectors, so
292     ; clear that memory.
293     ;
294     push di
295     mov di,[SetupSecs]
296     shl di,9
297     xor eax,eax
298     mov cx,cmd_line_here
299     sub cx,di
300     shr cx,2
301     rep stosd
302     pop di
303    
304     ;
305 niro 532 ; Now see if we have an initial RAMdisk; if so, do requisite computation
306     ; We know we have a new kernel; the old_kernel code already will have objected
307     ; if we tried to load initrd using an old kernel
308     ;
309     load_initrd:
310 niro 1133 ; Cap the ramdisk memory range if appropriate
311     mov eax,[RamdiskMax]
312     cmp eax,[MyHighMemSize]
313     ja .ok
314     mov [MyHighMemSize],eax
315     .ok:
316     xor eax,eax
317     cmp [InitRDPtr],ax
318     jz .noinitrd
319 niro 532 call parse_load_initrd
320 niro 1133 .noinitrd:
321    
322 niro 532 ;
323     ; Abandon hope, ye that enter here! We do no longer permit aborts.
324     ;
325 niro 1133 call abort_check ; Last chance!!
326 niro 532
327     mov si,ready_msg
328 niro 1133 call writestr_qchk
329 niro 532
330     UNLOAD_PREP ; Module-specific hook
331    
332     ;
333     ; Now, if we were supposed to load "low", copy the kernel down to 10000h
334     ; and the real mode stuff to 90000h. We assume that all bzImage kernels are
335     ; capable of starting their setup from a different address.
336     ;
337     mov ax,real_mode_seg
338 niro 1133 mov es,ax
339 niro 532 mov fs,ax
340    
341     ;
342 niro 1133 ; If the default root device is set to FLOPPY (0000h), change to
343     ; /dev/fd0 (0200h)
344     ;
345     cmp word [es:bs_rootdev],byte 0
346     jne root_not_floppy
347     mov word [es:bs_rootdev],0200h
348     root_not_floppy:
349    
350     ;
351     ; Copy command line. Unfortunately, the old kernel boot protocol requires
352 niro 532 ; the command line to exist in the 9xxxxh range even if the rest of the
353     ; setup doesn't.
354     ;
355 niro 1133 setup_command_line:
356     mov dx,[KernelVersion]
357 niro 532 test byte [LoadFlags],LOAD_HIGH
358 niro 1133 jz .need_high_cmdline
359     cmp dx,0202h ; Support new cmdline protocol?
360     jb .need_high_cmdline
361 niro 532 ; New cmdline protocol
362     ; Store 32-bit (flat) pointer to command line
363 niro 1133 ; This is the "high" location, since we have bzImage
364     mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4)+cmd_line_here
365     mov word [HeapEnd],linux_stack
366     mov word [fs:su_heapend],linux_stack-512
367     jmp .setup_done
368 niro 532
369 niro 1133 .need_high_cmdline:
370 niro 532 ;
371 niro 1133 ; Copy command line down to fit in high conventional memory
372     ; -- this happens if we have a zImage kernel or the protocol
373     ; is less than 2.02.
374 niro 532 ;
375     mov si,cmd_line_here
376 niro 1133 mov di,old_cmd_line_here
377 niro 532 mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic
378     mov [fs:kern_cmd_offset],di ; Store pointer
379 niro 1133 mov word [HeapEnd],old_linux_stack
380     mov ax,255 ; Max cmdline limit
381     cmp dx,0201h
382     jb .adjusted
383     ; Protocol 2.01+
384     mov word [fs:su_heapend],old_linux_stack-512
385     jbe .adjusted
386     ; Protocol 2.02+
387     ; Note that the only reason we would end up here is
388     ; because we have a zImage, so we anticipate the move
389     ; to 90000h already...
390     mov dword [fs:su_cmd_line_ptr],0x90000+old_cmd_line_here
391     mov ax,old_max_cmd_len ; 2.02+ allow a higher limit
392     .adjusted:
393 niro 532
394     mov cx,[CmdLineLen]
395 niro 1133 cmp cx,ax
396 niro 532 jna .len_ok
397 niro 1133 mov cx,ax ; Truncate the command line
398 niro 532 .len_ok:
399     fs rep movsb
400 niro 1133 stosb ; Final null, note AL=0 already
401     mov [CmdLineEnd],di
402     cmp dx,0200h
403     jb .nomovesize
404     mov [es:su_movesize],di ; Tell the kernel what to move
405     .nomovesize:
406     .setup_done:
407 niro 532
408 niro 1133 ;
409     ; Time to start setting up move descriptors
410     ;
411     setup_move:
412     mov di,trackbuf
413     xor cx,cx ; Number of descriptors
414    
415     mov bx,es ; real_mode_seg
416     mov fs,bx
417     push ds ; We need DS == ES == CS here
418 niro 532 pop es
419    
420     test byte [LoadFlags],LOAD_HIGH
421 niro 1133 jnz .loading_high
422 niro 532
423 niro 1133 ; Loading low: move real_mode stuff to 90000h, then move the kernel down
424     mov eax,90000h
425     stosd
426     mov eax,real_mode_seg << 4
427     stosd
428     movzx eax,word [CmdLineEnd]
429     stosd
430     inc cx
431 niro 532
432 niro 1133 mov eax,10000h ; Target address of low kernel
433     stosd
434     mov eax,100000h ; Where currently loaded
435     stosd
436     neg eax
437     add eax,[KernelEnd]
438     stosd
439     inc cx
440 niro 532
441 niro 1133 mov bx,9000h ; Revised real mode segment
442 niro 532
443 niro 1133 .loading_high:
444 niro 532
445 niro 1133 cmp word [InitRDPtr],0 ; Did we have an initrd?
446     je .no_initrd
447    
448     mov eax,[fs:su_ramdiskat]
449     stosd
450     mov eax,[InitRDStart]
451     stosd
452     mov eax,[fs:su_ramdisklen]
453     stosd
454     inc cx
455    
456     .no_initrd:
457     push dword run_linux_kernel
458     push cx ; Length of descriptor list
459    
460     ; BX points to the final real mode segment, and will be loaded
461     ; into DS.
462    
463     test byte [QuietBoot],QUIET_FLAG
464     jz replace_bootstrap
465     jmp replace_bootstrap_noclearmode
466    
467     run_linux_kernel:
468 niro 532 ;
469     ; Set up segment registers and the Linux real-mode stack
470 niro 1133 ; Note: ds == the real mode segment
471 niro 532 ;
472     cli
473 niro 1133 mov ax,ds
474     mov ss,ax
475     mov sp,strict word linux_stack
476     ; Point HeapEnd to the immediate of the instruction above
477     HeapEnd equ $-2 ; Self-modifying code! Fun!
478     mov es,ax
479     mov fs,ax
480     mov gs,ax
481    
482 niro 532 ;
483     ; We're done... now RUN THAT KERNEL!!!!
484     ; Setup segment == real mode segment + 020h; we need to jump to offset
485     ; zero in the real mode segment.
486     ;
487 niro 1133 add ax,020h
488     push ax
489 niro 532 push word 0h
490     retf
491    
492     ;
493     ; Load an older kernel. Older kernels always have 4 setup sectors, can't have
494     ; initrd, and are always loaded low.
495     ;
496     old_kernel:
497 niro 1133 xor ax,ax
498     cmp word [InitRDPtr],ax ; Old kernel can't have initrd
499     je .load
500 niro 532 mov si,err_oldkernel
501     jmp abort_load
502 niro 1133 .load:
503     mov byte [LoadFlags],al ; Always low
504     mov word [KernelVersion],ax ; Version 0.00
505     jmp any_kernel
506 niro 532
507     ;
508     ; parse_load_initrd
509     ;
510 niro 1133 ; Parse an initrd= option and load the initrds. This sets
511     ; InitRDStart and InitRDEnd with dword padding between; we then
512     ; do a global memory shuffle to move it to the end of memory.
513 niro 532 ;
514 niro 1133 ; On entry, EDI points to where to start loading.
515     ;
516 niro 532 parse_load_initrd:
517     push es
518     push ds
519     mov ax,real_mode_seg
520     mov ds,ax
521     push cs
522     pop es ; DS == real_mode_seg, ES == CS
523    
524 niro 1133 mov [cs:InitRDStart],edi
525     mov [cs:InitRDEnd],edi
526    
527 niro 532 mov si,[cs:InitRDPtr]
528 niro 1133
529     .get_chunk:
530     ; DS:SI points to the start of a name
531    
532     mov bx,si
533 niro 532 .find_end:
534     lodsb
535 niro 1133 cmp al,','
536     je .got_end
537 niro 532 cmp al,' '
538 niro 1133 jbe .got_end
539     jmp .find_end
540 niro 532
541 niro 1133 .got_end:
542     push ax ; Terminating character
543     push si ; Next filename (if any)
544     mov byte [si-1],0 ; Zero-terminate
545     mov si,bx ; Current filename
546 niro 532
547 niro 1133 push di
548 niro 532 mov di,InitRD ; Target buffer for mangled name
549     call mangle_name
550 niro 1133 pop di
551 niro 532 call loadinitrd
552 niro 1133
553 niro 532 pop si
554     pop ax
555 niro 1133 mov [si-1],al ; Restore ending byte
556 niro 532
557 niro 1133 cmp al,','
558     je .get_chunk
559 niro 532
560 niro 1133 ; Compute the initrd target location
561     ; Note: we round to a page boundary twice here. The first
562     ; time it is to make sure we don't use any fractional page
563     ; which may be valid RAM but which will be ignored by the
564     ; kernel (and therefore is inaccessible.) The second time
565     ; it is to make sure we start out on page boundary.
566     mov edx,[cs:InitRDEnd]
567     sub edx,[cs:InitRDStart]
568     mov [su_ramdisklen],edx
569     mov eax,[cs:MyHighMemSize]
570     and ax,0F000h ; Round to a page boundary
571     sub eax,edx
572     and ax,0F000h ; Round to a page boundary
573     mov [su_ramdiskat],eax
574    
575 niro 532 pop ds
576     pop es
577     ret
578    
579     ;
580     ; Load RAM disk into high memory
581     ;
582     ; Input: InitRD - set to the mangled name of the initrd
583 niro 1133 ; EDI - location to load
584     ; Output: EDI - location for next initrd
585     ; InitRDEnd - updated
586 niro 532 ;
587     loadinitrd:
588     push ds
589     push es
590     mov ax,cs ; CS == DS == ES
591     mov ds,ax
592     mov es,ax
593 niro 1133 push edi
594 niro 532 mov si,InitRD
595     mov di,InitRDCName
596     call unmangle_name ; Create human-readable name
597     sub di,InitRDCName
598     mov [InitRDCNameLen],di
599     mov di,InitRD
600     call searchdir ; Look for it in directory
601 niro 1133 pop edi
602 niro 532 jz .notthere
603    
604     push si
605     mov si,crlfloading_msg ; Write "Loading "
606 niro 1133 call writestr_qchk
607 niro 532 mov si,InitRDCName ; Write ramdisk name
608 niro 1133 call writestr_qchk
609 niro 532 mov si,dotdot_msg ; Write dots
610 niro 1133 call writestr_qchk
611 niro 532 pop si
612    
613 niro 1133 .li_skip_echo:
614     mov dx,3
615     mov bx,dot_pause
616     call load_high
617     mov [InitRDEnd],ebx
618 niro 532
619     pop es
620     pop ds
621 niro 1133 ret
622 niro 532
623     .notthere:
624     mov si,err_noinitrd
625 niro 1133 call writestr
626 niro 532 mov si,InitRDCName
627 niro 1133 call writestr
628 niro 532 mov si,crlf_msg
629     jmp abort_load
630    
631 niro 1133 ;
632     ; writestr_qchk: writestr, except allows output to be suppressed
633     ; assumes CS == DS
634     ;
635     writestr_qchk:
636     test byte [QuietBoot],QUIET_FLAG
637     jz writestr
638     ret
639 niro 532
640 niro 1133 section .data
641     crlfloading_msg db CR, LF
642     loading_msg db 'Loading ', 0
643     dotdot_msg db '.'
644     dot_msg db '.', 0
645     ready_msg db 'ready.', CR, LF, 0
646     err_oldkernel db 'Cannot load a ramdisk with an old kernel image.'
647     db CR, LF, 0
648     err_noinitrd db CR, LF, 'Could not find ramdisk image: ', 0
649 niro 532
650     boot_image db 'BOOT_IMAGE='
651     boot_image_len equ $-boot_image
652    
653 niro 1133 ;
654     ; Command line options we'd like to take a look at
655     ;
656     %macro cmd_opt 2
657     %strlen cmd_opt_len %1
658     db cmd_opt_len
659     db %1
660     dw %2
661     %endmacro
662     options_list:
663     cmd_opt "vga=", opt_vga
664     cmd_opt "mem=", opt_mem
665     cmd_opt "quiet", opt_quiet
666     str_initrd equ $+1 ; Pointer to "initrd=" in memory
667     cmd_opt "initrd=", opt_initrd
668     %if IS_PXELINUX
669     cmd_opt "keeppxe", opt_keeppxe
670     %endif
671     db 0
672    
673 niro 532 section .bss
674     alignb 4
675 niro 1133 MyHighMemSize resd 1 ; Possibly adjusted highmem size
676 niro 532 RamdiskMax resd 1 ; Highest address for ramdisk
677     KernelSize resd 1 ; Size of kernel in bytes
678     KernelSects resd 1 ; Size of kernel in sectors
679     KernelEnd resd 1 ; Ending address of the kernel image
680 niro 1133 InitRDStart resd 1 ; Start of initrd (pre-relocation)
681     InitRDEnd resd 1 ; End of initrd (pre-relocation)
682 niro 532 CmdLineLen resw 1 ; Length of command line including null
683 niro 1133 CmdLineEnd resw 1 ; End of the command line in real_mode_seg
684     SetupSecs resw 1 ; Number of setup sectors (+bootsect)
685     KernelVersion resw 1 ; Kernel protocol version
686     ;
687     ; These are derived from the command-line parser
688     ;
689 niro 532 InitRDPtr resw 1 ; Pointer to initrd= option in command line
690     LoadFlags resb 1 ; Loadflags from kernel
691 niro 1133 QuietBoot resb 1 ; Set if a quiet boot is requested