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