Magellan Linux

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

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 1132 by niro, Sat Sep 1 22:45:15 2007 UTC revision 1133 by niro, Thu Aug 19 09:50:43 2010 UTC
# Line 1  Line 1 
 ;; $Id: runkernel.inc,v 1.1 2007-09-01 22:44:05 niro Exp $  
1  ;; -----------------------------------------------------------------------  ;; -----------------------------------------------------------------------
2  ;;    ;;
3  ;;   Copyright 1994-2005 H. Peter Anvin - All Rights Reserved  ;;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
4    ;;   Copyright 2009-2010 Intel Corporation; author: H. Peter Anvin
5  ;;  ;;
6  ;;   This program is free software; you can redistribute it and/or modify  ;;   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  ;;   it under the terms of the GNU General Public License as published by
# Line 13  Line 13 
13    
14  ;;  ;;
15  ;; runkernel.inc  ;; runkernel.inc
16  ;;  ;;
17  ;; Common code for running a Linux kernel  ;; Common code for running a Linux kernel
18  ;;  ;;
19    
20  ;  ;
21  ; Hook macros, that may or may not be defined  ; Hook macros, that may or may not be defined
22  ;  ;
 %ifndef HAVE_SPECIAL_APPEND  
 %macro SPECIAL_APPEND 0  
 %endmacro  
 %endif  
   
23  %ifndef HAVE_UNLOAD_PREP  %ifndef HAVE_UNLOAD_PREP
24  %macro UNLOAD_PREP 0  %macro UNLOAD_PREP 0
25  %endmacro  %endmacro
# Line 35  Line 30 
30  ; kernel code. The boot sector is never executed when using an external  ; kernel code. The boot sector is never executed when using an external
31  ; booting utility, but it contains some status bytes that are necessary.  ; booting utility, but it contains some status bytes that are necessary.
32  ;  ;
33  ; First check that our kernel is at least 1K and less than 8M (if it is  ; First check that our kernel is at least 1K, or else it isn't long
34  ; more than 8M, we need to change the logic for loading it anyway...)  ; enough to have the appropriate headers.
35  ;  ;
36  ; We used to require the kernel to be 64K or larger, but it has gotten  ; 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  ; popular to use the Linux kernel format for other things, which may
38  ; not be so large.  ; not be so large.
39  ;  ;
40    ; Additionally, we used to have a test for 8 MB or smaller.  Equally
41    ; obsolete.
42    ;
43  is_linux_kernel:  is_linux_kernel:
44                  cmp dx,80h ; 8 megs   push si ; <A> file pointer
45   ja kernel_corrupt  
  and dx,dx  
  jnz kernel_sane  
  cmp ax,1024 ; Bootsect + 1 setup sect  
  jb kernel_corrupt  
 kernel_sane: push ax  
  push dx  
  push si  
  mov si,loading_msg  
                 call cwritestr  
46  ;  ;
47  ; Now start transferring the kernel  ; Now start transferring the kernel
48  ;  ;
49   push word real_mode_seg   push word real_mode_seg
50   pop es   pop es
51    
  movzx eax,ax ; Fix this by using a 32-bit  
  shl edx,16 ; register for the kernel size  
  or eax,edx  
  mov [KernelSize],eax  
  add eax,SECTOR_SIZE-1  
  shr eax,SECTOR_SHIFT  
                 mov [KernelSects],eax ; Total sectors in kernel  
   
 ;  
 ; Now, if we transfer these straight, we'll hit 64K boundaries. Hence we  
 ; have to see if we're loading more than 64K, and if so, load it step by  
 ; step.  
 ;  
   
52  ;  ;
53  ; Start by loading the bootsector/setup code, to see if we need to  ; 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  ; 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).  ; work since we might have funny stuff up near the end of memory).
 ; If we have larger than 32K clusters, yes, we're hosed.  
56  ;  ;
57   call abort_check ; Check for abort key   call abort_check ; Check for abort key
58   mov ecx,8000h >> SECTOR_SHIFT ; Half a moby (32K)   mov cx,8000h >> SECTOR_SHIFT ; Half a moby (32K)
  cmp ecx,[KernelSects]  
  jna .normalkernel  
  mov ecx,[KernelSects]  
 .normalkernel:  
  sub [KernelSects],ecx  
59   xor bx,bx   xor bx,bx
60                  pop si                          ; Cluster pointer on stack                  pop si                          ; <A> file pointer
61   call getfssec   call getfssec
62     cmp cx,1024
63     jb kernel_corrupt
64                  cmp word [es:bs_bootsign],0AA55h                  cmp word [es:bs_bootsign],0AA55h
65   jne kernel_corrupt ; Boot sec signature missing   jne kernel_corrupt ; Boot sec signature missing
66    
67  ;  ;
68  ; Save the cluster pointer for later...  ; Save the file pointer for later...
69  ;  ;
70   push si   push si ; <A> file pointer
71  ;  
 ; Get the BIOS' idea of what the size of high memory is.  
 ;  
  call highmemsize  
72  ;  ;
73  ; Construct the command line (append options have already been copied)  ; Construct the command line (append options have already been copied)
74  ;  ;
75  construct_cmdline:  construct_cmdline:
76   mov di,[CmdLinePtr]   mov di,[CmdLinePtr]
77                  mov si,boot_image         ; BOOT_IMAGE=                  mov si,boot_image ; BOOT_IMAGE=
78                  mov cx,boot_image_len                  mov cx,boot_image_len
79                  rep movsb                  rep movsb
80                  mov si,KernelCName       ; Unmangled kernel name                  mov si,KernelCName ; Unmangled kernel name
81                  mov cx,[KernelCNameLen]                  mov cx,[KernelCNameLen]
82                  rep movsb                  rep movsb
83                  mov al,' '                      ; Space                  mov al,' '                      ; Space
84                  stosb                  stosb
85    
86   SPECIAL_APPEND ; Module-specific hook   call do_ip_append ; Handle IPAppend
87    
88                  mov si,[CmdOptPtr]              ; Options from user input                  mov si,[CmdOptPtr]              ; Options from user input
89   call strcpy   call strcpy
# Line 125  construct_cmdline: Line 93  construct_cmdline:
93  ; interested in.  The original version of this code automatically assumed  ; interested in.  The original version of this code automatically assumed
94  ; the first option was BOOT_IMAGE=, but that is no longer certain.  ; the first option was BOOT_IMAGE=, but that is no longer certain.
95  ;  ;
96   mov si,cmd_line_here  parse_cmdline:
97   xor ax,ax   mov di,cmd_line_here
98                  mov [InitRDPtr],ax ; No initrd= option (yet)  .skipspace: mov al,[es:di]
99                  push es ; Set DS <- real_mode_seg   inc di
100                  pop ds  .skipspace_loaded:
 get_next_opt:   lodsb  
101   and al,al   and al,al
102   jz cmdline_end   jz cmdline_end
103   cmp al,' '   cmp al,' '
104   jbe get_next_opt   jbe .skipspace
105   dec si   dec di
106                  mov eax,[si]  
107                  cmp eax,'vga='   ; ES:DI now points to the beginning of an option
108   je is_vga_cmd   mov si,options_list
109                  cmp eax,'mem='  .next_opt:
110   je is_mem_cmd   movzx cx,byte [si]
111  %if IS_PXELINUX   jcxz .skip_opt
112   cmp eax,'keep' ; Is it "keeppxe"?   push di
113   jne .notkeep   inc si
  cmp dword [si+3],'ppxe'  
  jne .notkeep  
  cmp byte [si+7],' ' ; Must be whitespace or EOS  
  ja .notkeep  
  or byte [cs:KeepPXE],1  
 .notkeep:  
 %endif  
                 push es                         ; Save ES -> real_mode_seg  
                 push cs  
                 pop es                          ; Set ES <- normal DS  
                 mov di,initrd_cmd  
  mov cx,initrd_cmd_len  
114   repe cmpsb   repe cmpsb
115                  jne .not_initrd   jne .no_match
116    
117     ; 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   cmp al,' '   cmp al,' '
131   jbe .noramdisk   ja .skip_opt
132   mov [cs:InitRDPtr],si   jmp .skipspace_loaded
133   jmp .not_initrd  .no_match:
134  .noramdisk:   pop di
135   xor ax,ax   add si,cx ; Skip remaining bytes
136   mov [cs:InitRDPtr],ax   inc si ; Skip function pointer
137  .not_initrd: pop es                          ; Restore ES -> real_mode_seg   inc si
138  skip_this_opt:  lodsb                           ; Load from command line   jmp .next_opt
139                  cmp al,' '  
140                  ja skip_this_opt  opt_vga:
141                  dec si   mov ax,[es:di-1]
142                  jmp short get_next_opt   mov bx,-1
143  is_vga_cmd:   cmp ax,'=n' ; vga=normal
144                  add si,4   je .vc0
                 mov eax,[si-1]  
                 mov bx,-1  
                 cmp eax,'=nor' ; vga=normal  
                 je vc0  
145   dec bx ; bx <- -2   dec bx ; bx <- -2
146                  cmp eax,'=ext' ; vga=ext   cmp ax,'=e' ; vga=ext
147                  je vc0   je .vc0
148                  dec bx ; bx <- -3   dec bx ; bx <- -3
149                  cmp eax,'=ask' ; vga=ask   cmp ax,'=a' ; vga=ask
150                  je vc0   je .vc0
151                  call parseint                   ; vga=<number>   mov bx,0x0f04 ; bx <- 0x0f04 (current mode)
152   jc skip_this_opt ; Not an integer   cmp ax,'=c' ; vga=current
153  vc0: mov [bs_vidmode],bx ; Set video mode   je .vc0
154   jmp short skip_this_opt   call parseint_esdi ; vga=<number>
155  is_mem_cmd:   jc .skip ; Not an integer
156                  add si,4  .vc0: mov [es:bs_vidmode],bx ; Set video mode
157                  call parseint  .skip:
158   jc skip_this_opt ; Not an integer   ret
159    
160    opt_mem:
161     call parseint_esdi
162     jc .skip
163  %if HIGHMEM_SLOP != 0  %if HIGHMEM_SLOP != 0
164   sub ebx,HIGHMEM_SLOP   sub ebx,HIGHMEM_SLOP
165  %endif  %endif
166   mov [cs:HighMemSize],ebx   mov [MyHighMemSize],ebx
167   jmp short skip_this_opt  .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  cmdline_end:  cmdline_end:
193                  push cs                         ; Restore standard DS   sub di,cmd_line_here
194                  pop ds   mov [CmdLineLen],di ; Length including final null
195   sub si,cmd_line_here  
  mov [CmdLineLen],si ; Length including final null  
196  ;  ;
197  ; Now check if we have a large kernel, which needs to be loaded high  ; Now check if we have a large kernel, which needs to be loaded high
198  ;  ;
199    prepare_header:
200   mov dword [RamdiskMax], HIGHMEM_MAX ; Default initrd limit   mov dword [RamdiskMax], HIGHMEM_MAX ; Default initrd limit
201   cmp dword [es:su_header],HEADER_ID ; New setup code ID   cmp dword [es:su_header],HEADER_ID ; New setup code ID
202   jne old_kernel ; Old kernel, load low   jne old_kernel ; Old kernel, load low
203   cmp word [es:su_version],0200h ; Setup code version 2.0   mov ax,[es:su_version]
204   jb old_kernel ; Old kernel, load low   mov [KernelVersion],ax
205                  cmp word [es:su_version],0201h ; Version 2.01+?   cmp ax,0200h ; Setup code version 2.0
206     jb old_kernel ; Old kernel, load low
207     cmp ax,0201h ; Version 2.01+?
208                  jb new_kernel                   ; If 2.00, skip this step                  jb new_kernel                   ; If 2.00, skip this step
209                  mov word [es:su_heapend],linux_stack ; Set up the heap   ; Set up the heap (assuming loading high for now)
210                    mov word [es:su_heapend],linux_stack-512
211                  or byte [es:su_loadflags],80h ; Let the kernel know we care                  or byte [es:su_loadflags],80h ; Let the kernel know we care
212   cmp word [es:su_version],0203h ; Version 2.03+?   cmp ax,0203h ; Version 2.03+?
213   jb new_kernel ; Not 2.03+   jb new_kernel ; Not 2.03+
214   mov eax,[es:su_ramdisk_max]   mov eax,[es:su_ramdisk_max]
215   mov [RamdiskMax],eax ; Set the ramdisk limit   mov [RamdiskMax],eax ; Set the ramdisk limit
# Line 225  cmdline_end: Line 220  cmdline_end:
220  ;  ;
221  new_kernel:  new_kernel:
222   mov byte [es:su_loader],my_id ; Show some ID   mov byte [es:su_loader],my_id ; Show some ID
  movzx ax,byte [es:bs_setupsecs] ; Variable # of setup sectors  
  mov [SetupSecs],ax  
223   xor eax,eax   xor eax,eax
224   mov [es:su_ramdisklen],eax ; No initrd loaded yet   mov [es:su_ramdisklen],eax ; No initrd loaded yet
225    
# Line 235  new_kernel: Line 228  new_kernel:
228  ; we were provided.  ; we were provided.
229  ;  ;
230                  mov al,[es:su_loadflags]                  mov al,[es:su_loadflags]
231     or al,[QuietBoot] ; Set QUIET_FLAG if needed
232     mov [es:su_loadflags],al
233   mov [LoadFlags],al   mov [LoadFlags],al
234    
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  ;  ;
242  ; Load the kernel.  We always load it at 100000h even if we're supposed to  ; 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  ; load it "low"; for a "low" load we copy it down to low memory right before
244  ; jumping to it.  ; jumping to it.
245  ;  ;
246  read_kernel:  read_kernel:
247                  mov si,KernelCName ; Print kernel name part of   movzx ax,byte [es:bs_setupsecs] ; Setup sectors
248                  call cwritestr                  ; "Loading" message   and ax,ax
249                  mov si,dotdot_msg ; Print dots   jnz .sects_ok
250                  call cwritestr   mov al,4 ; 0 = 4 setup sectors
251    .sects_ok:
252                  mov eax,[HighMemSize]   inc ax ; Including the boot sector
253   sub eax,100000h ; Load address   mov [SetupSecs],ax
254   cmp eax,[KernelSize]  
255   jb no_high_mem ; Not enough high memory   call dot_pause
256    
257  ;  ;
258  ; Move the stuff beyond the setup code to high memory at 100000h  ; Move the stuff beyond the setup code to high memory at 100000h
259  ;  ;
260   movzx esi,word [SetupSecs] ; Setup sectors   movzx esi,word [SetupSecs] ; Setup sectors
  inc si ; plus 1 boot sector  
261                  shl si,9 ; Convert to bytes                  shl si,9 ; Convert to bytes
262                  mov ecx,8000h ; 32K                  mov ecx,8000h ; 32K
263   sub ecx,esi ; Number of bytes to copy   sub ecx,esi ; Number of bytes to copy
  push ecx  
264   add esi,(real_mode_seg << 4) ; Pointer to source   add esi,(real_mode_seg << 4) ; Pointer to source
265                  mov edi,100000h                 ; Copy to address 100000h                  mov edi,100000h                 ; Copy to address 100000h
266    
267                  call bcopy ; Transfer to high memory                  call bcopy ; Transfer to high memory
268    
269   ; On exit EDI -> where to load the rest   pop si ; <A> File pointer
270     and si,si ; EOF already?
271     jz high_load_done
272    
273                  mov si,dot_msg ; Progress report   ; On exit EDI -> where to load the rest
                 call cwritestr  
                 call abort_check  
   
  pop ecx ; Number of bytes in the initial portion  
  pop si ; Restore file handle/cluster pointer  
  mov eax,[KernelSize]  
  sub eax,8000h ; Amount of kernel not yet loaded  
  jbe high_load_done ; Zero left (tiny kernel)  
274    
275   xor dx,dx ; No padding needed   mov bx,dot_pause
276   call load_high ; Copy the file   or eax,-1 ; Load the whole file
277     mov dx,3 ; Pad to dword
278     call load_high
279    
280  high_load_done:  high_load_done:
281   mov [KernelEnd],edi   mov [KernelEnd],edi
# Line 286  high_load_done: Line 283  high_load_done:
283                  mov es,ax                  mov es,ax
284    
285                  mov si,dot_msg                  mov si,dot_msg
286                  call cwritestr                  call writestr_qchk
287    
288    ;
289    ; 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  ; Now see if we have an initial RAMdisk; if so, do requisite computation  ; Now see if we have an initial RAMdisk; if so, do requisite computation
# Line 294  high_load_done: Line 307  high_load_done:
307  ; if we tried to load initrd using an old kernel  ; if we tried to load initrd using an old kernel
308  ;  ;
309  load_initrd:  load_initrd:
310                  cmp word [InitRDPtr],0   ; Cap the ramdisk memory range if appropriate
311                  jz nk_noinitrd   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   call parse_load_initrd   call parse_load_initrd
320  nk_noinitrd:  .noinitrd:
321    
322  ;  ;
323  ; Abandon hope, ye that enter here!  We do no longer permit aborts.  ; Abandon hope, ye that enter here!  We do no longer permit aborts.
324  ;  ;
325                  call abort_check         ; Last chance!!                  call abort_check ; Last chance!!
326    
327   mov si,ready_msg   mov si,ready_msg
328   call cwritestr   call writestr_qchk
   
  call vgaclearmode ; We can't trust ourselves after this  
329    
330   UNLOAD_PREP ; Module-specific hook   UNLOAD_PREP ; Module-specific hook
331    
# Line 316  nk_noinitrd: Line 335  nk_noinitrd:
335  ; capable of starting their setup from a different address.  ; capable of starting their setup from a different address.
336  ;  ;
337   mov ax,real_mode_seg   mov ax,real_mode_seg
338     mov es,ax
339   mov fs,ax   mov fs,ax
340    
341  ;  ;
342  ; Copy command line.  Unfortunately, the kernel boot protocol requires  ; 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  ; the command line to exist in the 9xxxxh range even if the rest of the  ; the command line to exist in the 9xxxxh range even if the rest of the
353  ; setup doesn't.  ; setup doesn't.
354  ;  ;
355   cli ; In case of hooked interrupts  setup_command_line:
356     mov dx,[KernelVersion]
357   test byte [LoadFlags],LOAD_HIGH   test byte [LoadFlags],LOAD_HIGH
358   jz need_high_cmdline   jz .need_high_cmdline
359   cmp word [fs:su_version],0202h ; Support new cmdline protocol?   cmp dx,0202h ; Support new cmdline protocol?
360   jb need_high_cmdline   jb .need_high_cmdline
361   ; New cmdline protocol   ; New cmdline protocol
362   ; Store 32-bit (flat) pointer to command line   ; Store 32-bit (flat) pointer to command line
363   mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4) + cmd_line_here   ; This is the "high" location, since we have bzImage
364   jmp short in_proper_place   mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4)+cmd_line_here
365     mov word [HeapEnd],linux_stack
366  need_high_cmdline:   mov word [fs:su_heapend],linux_stack-512
367  ;   jmp .setup_done
368  ; Copy command line up to 90000h  
369    .need_high_cmdline:
370    ;
371    ; 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  ;  ;
  mov ax,9000h ; Note AL <- 0  
  mov es,ax  
375   mov si,cmd_line_here   mov si,cmd_line_here
376   mov di,si   mov di,old_cmd_line_here
377   mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic   mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic
378   mov [fs:kern_cmd_offset],di ; Store pointer   mov [fs:kern_cmd_offset],di ; Store pointer
379     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    
394   mov cx,[CmdLineLen]   mov cx,[CmdLineLen]
395   cmp cx,255   cmp cx,ax
396   jna .len_ok   jna .len_ok
397   mov cx,255 ; Protocol < 0x202 has 255 as hard limit   mov cx,ax ; Truncate the command line
398  .len_ok:  .len_ok:
399   fs rep movsb   fs rep movsb
400   stosb ; Final null, note AL == 0 already   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    
408    ;
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   push fs   mov bx,es ; real_mode_seg
416     mov fs,bx
417     push ds ; We need DS == ES == CS here
418   pop es   pop es
419    
420   test byte [LoadFlags],LOAD_HIGH   test byte [LoadFlags],LOAD_HIGH
421   jnz in_proper_place ; If high load, we're done   jnz .loading_high
   
 ;  
 ; Loading low; we can't assume it's safe to run in place.  
 ;  
 ; Copy real_mode stuff up to 90000h  
 ;  
  mov ax,9000h  
  mov es,ax  
  mov cx,[SetupSecs]  
  inc cx ; Setup + boot sector  
  shl cx,7 ; Sectors -> dwords  
  xor si,si  
  xor di,di  
  fs rep movsd ; Copy setup + boot sector  
 ;  
 ; Some kernels in the 1.2 ballpark but pre-bzImage have more than 4  
 ; setup sectors, but the boot protocol had not yet been defined.  They  
 ; rely on a signature to figure out if they need to copy stuff from  
 ; the "protected mode" kernel area.  Unfortunately, we used that area  
 ; as a transfer buffer, so it's going to find the signature there.  
 ; Hence, zero the low 32K beyond the setup area.  
 ;  
  mov di,[SetupSecs]  
  inc di ; Setup + boot sector  
  mov cx,32768/512 ; Sectors/32K  
  sub cx,di ; Remaining sectors  
  shl di,9 ; Sectors -> bytes  
  shl cx,7 ; Sectors -> dwords  
  xor eax,eax  
  rep stosd ; Clear region  
 ;  
 ; Copy the kernel down to the "low" location  
 ;  
  mov ecx,[KernelSize]  
  mov esi,100000h  
  mov edi,10000h  
  call bcopy  
422    
423  ;  ; Loading low: move real_mode stuff to 90000h, then move the kernel down
424  ; Now everything is where it needs to be...   mov eax,90000h
425  ;   stosd
426  ; When we get here, es points to the final segment, either   mov eax,real_mode_seg << 4
427  ; 9000h or real_mode_seg   stosd
428  ;   movzx eax,word [CmdLineEnd]
429  in_proper_place:   stosd
430     inc cx
431    
432     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    
441     mov bx,9000h ; Revised real mode segment
442    
443    .loading_high:
444    
445     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:
 ; If the default root device is set to FLOPPY (0000h), change to  
 ; /dev/fd0 (0200h)  
 ;  
  cmp word [es:bs_rootdev],byte 0  
  jne root_not_floppy  
  mov word [es:bs_rootdev],0200h  
 root_not_floppy:  
   
 ;  
 ; Copy the disk table to high memory, then re-initialize the floppy  
 ; controller  
 ;  
 %if IS_SYSLINUX || IS_MDSLINUX  
  lgs si,[cs:fdctab]  
  mov di,linux_fdctab  
  mov cx,6 ; 12 bytes  
  gs rep movsw  
  mov [cs:fdctab],word linux_fdctab ; Save new floppy tab pos  
  mov [cs:fdctab+2],es  
 %endif  
 ;  
 ; Linux wants the floppy motor shut off before starting the kernel,  
 ; at least bootsect.S seems to imply so.  
 ;  
 kill_motor:  
  xor ax,ax  
  xor dx,dx  
  int 13h  
   
 ;  
 ; If we're debugging, wait for a keypress so we can read any debug messages  
 ;  
 %ifdef debug  
                 xor ax,ax  
                 int 16h  
 %endif  
468  ;  ;
469  ; Set up segment registers and the Linux real-mode stack  ; Set up segment registers and the Linux real-mode stack
470  ; Note: es == the real mode segment  ; Note: ds == the real mode segment
471  ;  ;
472   cli   cli
473   mov bx,es   mov ax,ds
474   mov ds,bx   mov ss,ax
475   mov fs,bx   mov sp,strict word linux_stack
476   mov gs,bx   ; Point HeapEnd to the immediate of the instruction above
477   mov ss,bx  HeapEnd equ $-2 ; Self-modifying code!  Fun!
478   mov sp,linux_stack   mov es,ax
479     mov fs,ax
480     mov gs,ax
481    
482  ;  ;
483  ; We're done... now RUN THAT KERNEL!!!!  ; We're done... now RUN THAT KERNEL!!!!
484  ; Setup segment == real mode segment + 020h; we need to jump to offset  ; Setup segment == real mode segment + 020h; we need to jump to offset
485  ; zero in the real mode segment.  ; zero in the real mode segment.
486  ;  ;
487   add bx,020h   add ax,020h
488   push bx   push ax
489   push word 0h   push word 0h
490   retf   retf
491    
# Line 466  kill_motor: Line 494  kill_motor:
494  ; initrd, and are always loaded low.  ; initrd, and are always loaded low.
495  ;  ;
496  old_kernel:  old_kernel:
497                 cmp word [InitRDPtr],0 ; Old kernel can't have initrd   xor ax,ax
498                  je load_old_kernel   cmp word [InitRDPtr],ax ; Old kernel can't have initrd
499                    je .load
500                  mov si,err_oldkernel                  mov si,err_oldkernel
501                  jmp abort_load                  jmp abort_load
502  load_old_kernel:  .load:
503   mov word [SetupSecs],4 ; Always 4 setup sectors   mov byte [LoadFlags],al ; Always low
504   mov byte [LoadFlags],0 ; Always low   mov word [KernelVersion],ax ; Version 0.00
505   jmp read_kernel   jmp any_kernel
506    
507  ;  ;
508  ; parse_load_initrd  ; parse_load_initrd
509  ;  ;
510  ; Parse an initrd= option and load the initrds.  Note that we load  ; Parse an initrd= option and load the initrds.  This sets
511  ; from the high end of memory first, so we parse this option from  ; InitRDStart and InitRDEnd with dword padding between; we then
512  ; left to right.  ; do a global memory shuffle to move it to the end of memory.
513    ;
514    ; On entry, EDI points to where to start loading.
515  ;  ;
516  parse_load_initrd:  parse_load_initrd:
517   push es   push es
# Line 490  parse_load_initrd: Line 521  parse_load_initrd:
521   push cs   push cs
522   pop es ; DS == real_mode_seg, ES == CS   pop es ; DS == real_mode_seg, ES == CS
523    
524     mov [cs:InitRDStart],edi
525     mov [cs:InitRDEnd],edi
526    
527   mov si,[cs:InitRDPtr]   mov si,[cs:InitRDPtr]
 .find_end:  
  lodsb  
  cmp al,' '  
  ja .find_end  
  ; Now SI points to one character beyond the  
  ; byte that ended this option.  
528    
529  .get_chunk:  .get_chunk:
530   dec si   ; DS:SI points to the start of a name
531    
532   ; DS:SI points to a termination byte   mov bx,si
533    .find_end:
534     lodsb
535     cmp al,','
536     je .got_end
537     cmp al,' '
538     jbe .got_end
539     jmp .find_end
540    
541   xor ax,ax  .got_end:
542   xchg al,[si] ; Zero-terminate   push ax ; Terminating character
543   push si ; Save ending byte address   push si ; Next filename (if any)
544   push ax ; Save ending byte   mov byte [si-1],0 ; Zero-terminate
545     mov si,bx ; Current filename
 .find_start:  
  dec si  
  cmp si,[cs:InitRDPtr]  
  je .got_start  
  cmp byte [si],','  
  jne .find_start  
546    
547   ; It's a comma byte   push di
  inc si  
   
 .got_start:  
  push si  
548   mov di,InitRD ; Target buffer for mangled name   mov di,InitRD ; Target buffer for mangled name
549   call mangle_name   call mangle_name
550     pop di
551   call loadinitrd   call loadinitrd
  pop si  
552    
553     pop si
554   pop ax   pop ax
555   pop di   mov [si-1],al ; Restore ending byte
556   mov [di],al ; Restore ending byte  
557     cmp al,','
558     je .get_chunk
559    
560   cmp si,[cs:InitRDPtr]   ; Compute the initrd target location
561   ja .get_chunk   ; 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   pop ds   pop ds
576   pop es   pop es
# Line 540  parse_load_initrd: Line 580  parse_load_initrd:
580  ; Load RAM disk into high memory  ; Load RAM disk into high memory
581  ;  ;
582  ; Input: InitRD - set to the mangled name of the initrd  ; Input: InitRD - set to the mangled name of the initrd
583    ; EDI - location to load
584    ; Output: EDI - location for next initrd
585    ; InitRDEnd - updated
586  ;  ;
587  loadinitrd:  loadinitrd:
588   push ds   push ds
# Line 547  loadinitrd: Line 590  loadinitrd:
590   mov ax,cs ; CS == DS == ES   mov ax,cs ; CS == DS == ES
591   mov ds,ax   mov ds,ax
592   mov es,ax   mov es,ax
593     push edi
594                  mov si,InitRD                  mov si,InitRD
595                  mov di,InitRDCName                  mov di,InitRDCName
596                  call unmangle_name              ; Create human-readable name                  call unmangle_name              ; Create human-readable name
# Line 554  loadinitrd: Line 598  loadinitrd:
598                  mov [InitRDCNameLen],di                  mov [InitRDCNameLen],di
599                  mov di,InitRD                  mov di,InitRD
600                  call searchdir                  ; Look for it in directory                  call searchdir                  ; Look for it in directory
601     pop edi
602   jz .notthere   jz .notthere
603    
  mov cx,dx  
  shl ecx,16  
  mov cx,ax ; ECX <- ram disk length  
   
  mov ax,real_mode_seg  
  mov es,ax  
   
  push ecx ; Bytes to load  
  cmp dword [es:su_ramdisklen],0  
  je .nopadding ; Don't pad the last initrd  
  add ecx,4095  
  and cx,0F000h  
 .nopadding:  
  add [es:su_ramdisklen],ecx  
  mov edx,[HighMemSize] ; End of memory  
  dec edx  
  mov eax,[RamdiskMax] ; Highest address allowed by kernel  
  cmp edx,eax  
  jna .memsize_ok  
  mov edx,eax ; Adjust to fit inside limit  
 .memsize_ok:  
  inc edx  
                 and dx,0F000h ; Round down to 4K boundary  
  sub edx,ecx ; Subtract size of ramdisk  
                 and dx,0F000h ; Round down to 4K boundary  
  cmp edx,[KernelEnd] ; Are we hitting the kernel image?  
  jb no_high_mem  
   
                 mov [es:su_ramdiskat],edx ; Load address  
  mov [RamdiskMax],edx ; Next initrd loaded here  
   
                 mov edi,edx ; initrd load address  
604   push si   push si
605   mov si,crlfloading_msg ; Write "Loading "   mov si,crlfloading_msg ; Write "Loading "
606   call cwritestr   call writestr_qchk
607                  mov si,InitRDCName ; Write ramdisk name                  mov si,InitRDCName ; Write ramdisk name
608                  call cwritestr                  call writestr_qchk
609                  mov si,dotdot_msg ; Write dots                  mov si,dotdot_msg ; Write dots
610                  call cwritestr                  call writestr_qchk
611   pop si   pop si
612    
613   pop eax ; Bytes to load  .li_skip_echo:
614   mov dx,0FFFh ; Pad to page   mov dx,3
615   call load_high ; Load the file   mov bx,dot_pause
616     call load_high
617     mov [InitRDEnd],ebx
618    
619   pop es   pop es
620   pop ds   pop ds
621   jmp crlf ; Print carriage return and return   ret
622    
623  .notthere:  .notthere:
624                  mov si,err_noinitrd                  mov si,err_noinitrd
625                  call cwritestr                  call writestr
626                  mov si,InitRDCName                  mov si,InitRDCName
627                  call cwritestr                  call writestr
628                  mov si,crlf_msg                  mov si,crlf_msg
629                  jmp abort_load                  jmp abort_load
630    
631  no_high_mem:     ; Error routine  ;
632   mov si,err_nohighmem  ; writestr_qchk: writestr, except allows output to be suppressed
633                  jmp abort_load  ; assumes CS == DS
634    ;
635                  ret  writestr_qchk:
636     test byte [QuietBoot],QUIET_FLAG
637     jz writestr
638     ret
639    
640   section .data   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    
650  boot_image      db 'BOOT_IMAGE='  boot_image      db 'BOOT_IMAGE='
651  boot_image_len  equ $-boot_image  boot_image_len  equ $-boot_image
652    
653    ;
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   section .bss   section .bss
674   alignb 4   alignb 4
675    MyHighMemSize resd 1 ; Possibly adjusted highmem size
676  RamdiskMax resd 1 ; Highest address for ramdisk  RamdiskMax resd 1 ; Highest address for ramdisk
677  KernelSize resd 1 ; Size of kernel in bytes  KernelSize resd 1 ; Size of kernel in bytes
678  KernelSects resd 1 ; Size of kernel in sectors  KernelSects resd 1 ; Size of kernel in sectors
679  KernelEnd resd 1 ; Ending address of the kernel image  KernelEnd resd 1 ; Ending address of the kernel image
680    InitRDStart resd 1 ; Start of initrd (pre-relocation)
681    InitRDEnd resd 1 ; End of initrd (pre-relocation)
682  CmdLineLen resw 1 ; Length of command line including null  CmdLineLen resw 1 ; Length of command line including null
683  SetupSecs resw 1 ; Number of setup sectors  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  InitRDPtr resw 1 ; Pointer to initrd= option in command line  InitRDPtr resw 1 ; Pointer to initrd= option in command line
690  LoadFlags resb 1 ; Loadflags from kernel  LoadFlags resb 1 ; Loadflags from kernel
691    QuietBoot resb 1 ; Set if a quiet boot is requested

Legend:
Removed from v.1132  
changed lines
  Added in v.1133