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