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