More fixes to the extlinux installer; change back to writable types
[profile/ivi/syslinux.git] / runkernel.inc
1 ;; $Id$
2 ;; -----------------------------------------------------------------------
3 ;;   
4 ;;   Copyright 1994-2002 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.
11 ;;
12 ;; -----------------------------------------------------------------------
13
14 ;;
15 ;; runkernel.inc
16 ;; 
17 ;; Common code for running a Linux kernel
18 ;;
19
20 ;
21 ; Hook macros, that may or may not be defined
22 ;
23 %ifndef HAVE_SPECIAL_APPEND
24 %macro SPECIAL_APPEND 0
25 %endmacro
26 %endif
27
28 %ifndef HAVE_UNLOAD_PREP
29 %macro UNLOAD_PREP 0
30 %endmacro
31 %endif
32
33 ;
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.
37 ;
38 ; First check that our kernel is at least 1K and less than 8M (if it is
39 ; more than 8M, we need to change the logic for loading it anyway...)
40 ;
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.
44 ;
45 is_linux_kernel:
46                 cmp dx,80h                      ; 8 megs
47                 ja kernel_corrupt
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
57 ;
58 ; Now start transferring the kernel
59 ;
60                 push word real_mode_seg
61                 pop es
62
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
70
71 ;
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.
75 ;
76
77 ;
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.
82 ;
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
95
96 ;
97 ; Save the cluster pointer for later...
98 ;
99                 push si
100 ;
101 ; Get the BIOS' idea of what the size of high memory is.
102 ;
103                 call highmemsize
104 ;
105 ; Construct the command line (append options have already been copied)
106 ;
107 construct_cmdline:
108                 mov di,[CmdLinePtr]
109                 mov si,boot_image               ; BOOT_IMAGE=
110                 mov cx,boot_image_len
111                 rep movsb
112                 mov si,KernelCName              ; Unmangled kernel name
113                 mov cx,[KernelCNameLen]
114                 rep movsb
115                 mov al,' '                      ; Space
116                 stosb
117
118                 SPECIAL_APPEND                  ; Module-specific hook
119
120                 mov si,[CmdOptPtr]              ; Options from user input
121                 call strcpy
122
123 ;
124 ; Scan through the command line for anything that looks like we might be
125 ; interested in.  The original version of this code automatically assumed
126 ; the first option was BOOT_IMAGE=, but that is no longer certain.
127 ;
128                 mov si,cmd_line_here
129                 mov byte [initrd_flag],0
130                 push es                         ; Set DS <- real_mode_seg
131                 pop ds
132 get_next_opt:   lodsb
133                 and al,al
134                 jz cmdline_end
135                 cmp al,' '
136                 jbe get_next_opt
137                 dec si
138                 mov eax,[si]
139                 cmp eax,'vga='
140                 je is_vga_cmd
141                 cmp eax,'mem='
142                 je is_mem_cmd
143 %if IS_PXELINUX
144                 cmp eax,'keep'                  ; Is it "keeppxe"?
145                 jne .notkeep
146                 cmp dword [si+3],'ppxe'
147                 jne .notkeep
148                 cmp byte [si+7],' '             ; Must be whitespace or EOS
149                 ja .notkeep
150                 or byte [cs:KeepPXE],1
151 .notkeep:
152 %endif
153                 push es                         ; Save ES -> real_mode_seg
154                 push cs
155                 pop es                          ; Set ES <- normal DS
156                 mov di,initrd_cmd
157                 mov cx,initrd_cmd_len
158                 repe cmpsb
159                 jne not_initrd
160
161                 mov di,InitRD
162                 push si                         ; mangle_dir mangles si
163                 call mangle_name                ; Mangle ramdisk name
164                 pop si
165                 cmp byte [es:InitRD],NULLFILE   ; Null filename?
166                 seta byte [es:initrd_flag]      ; Set flag if not
167 not_initrd:     pop es                          ; Restore ES -> real_mode_seg
168 skip_this_opt:  lodsb                           ; Load from command line
169                 cmp al,' '
170                 ja skip_this_opt
171                 dec si
172                 jmp short get_next_opt
173 is_vga_cmd:
174                 add si,4
175                 mov eax,[si-1]
176                 mov bx,-1
177                 cmp eax,'=nor'                  ; vga=normal
178                 je vc0
179                 dec bx                          ; bx <- -2
180                 cmp eax,'=ext'                  ; vga=ext
181                 je vc0
182                 dec bx                          ; bx <- -3
183                 cmp eax,'=ask'                  ; vga=ask
184                 je vc0
185                 call parseint                   ; vga=<number>
186                 jc skip_this_opt                ; Not an integer
187 vc0:            mov [bs_vidmode],bx             ; Set video mode
188                 jmp short skip_this_opt
189 is_mem_cmd:
190                 add si,4
191                 call parseint
192                 jc skip_this_opt                ; Not an integer
193 %if HIGHMEM_SLOP != 0
194                 sub ebx,HIGHMEM_SLOP
195 %endif
196                 mov [cs:HighMemSize],ebx
197                 jmp short skip_this_opt
198 cmdline_end:
199                 push cs                         ; Restore standard DS
200                 pop ds
201                 sub si,cmd_line_here
202                 mov [CmdLineLen],si             ; Length including final null
203 ;
204 ; Now check if we have a large kernel, which needs to be loaded high
205 ;
206                 mov dword [RamdiskMax], HIGHMEM_MAX     ; Default initrd limit
207                 cmp dword [es:su_header],HEADER_ID      ; New setup code ID
208                 jne old_kernel          ; Old kernel, load low
209                 cmp word [es:su_version],0200h  ; Setup code version 2.0
210                 jb old_kernel           ; Old kernel, load low
211                 cmp word [es:su_version],0201h  ; Version 2.01+?
212                 jb new_kernel                   ; If 2.00, skip this step
213                 mov word [es:su_heapend],linux_stack    ; Set up the heap
214                 or byte [es:su_loadflags],80h   ; Let the kernel know we care
215                 cmp word [es:su_version],0203h  ; Version 2.03+?
216                 jb new_kernel                   ; Not 2.03+
217                 mov eax,[es:su_ramdisk_max]
218                 mov [RamdiskMax],eax            ; Set the ramdisk limit
219
220 ;
221 ; We definitely have a new-style kernel.  Let the kernel know who we are,
222 ; and that we are clueful
223 ;
224 new_kernel:
225                 mov byte [es:su_loader],my_id   ; Show some ID
226                 movzx ax,byte [es:bs_setupsecs] ; Variable # of setup sectors
227                 mov [SetupSecs],ax
228 ;
229 ; About to load the kernel.  This is a modern kernel, so use the boot flags
230 ; we were provided.
231 ;
232                 mov al,[es:su_loadflags]
233                 mov [LoadFlags],al
234 ;
235 ; Load the kernel.  We always load it at 100000h even if we're supposed to
236 ; load it "low"; for a "low" load we copy it down to low memory right before
237 ; jumping to it.
238 ;
239 read_kernel:
240                 mov si,KernelCName              ; Print kernel name part of
241                 call cwritestr                  ; "Loading" message
242                 mov si,dotdot_msg               ; Print dots
243                 call cwritestr
244
245                 mov eax,[HighMemSize]
246                 sub eax,100000h                 ; Load address
247                 cmp eax,[KernelSize]
248                 jb no_high_mem          ; Not enough high memory
249 ;
250 ; Move the stuff beyond the setup code to high memory at 100000h
251 ;
252                 movzx esi,word [SetupSecs]      ; Setup sectors
253                 inc si                          ; plus 1 boot sector
254                 shl si,9                        ; Convert to bytes
255                 mov ecx,8000h                   ; 32K
256                 sub ecx,esi                     ; Number of bytes to copy
257                 push ecx
258                 add esi,(real_mode_seg << 4)    ; Pointer to source
259                 mov edi,100000h                 ; Copy to address 100000h
260
261                 call bcopy                      ; Transfer to high memory
262
263                 ; On exit EDI -> where to load the rest
264
265                 mov si,dot_msg                  ; Progress report
266                 call cwritestr
267                 call abort_check
268
269                 pop ecx                         ; Number of bytes in the initial portion
270                 pop si                          ; Restore file handle/cluster pointer
271                 mov eax,[KernelSize]
272                 sub eax,8000h                   ; Amount of kernel not yet loaded
273                 jbe high_load_done              ; Zero left (tiny kernel)
274
275                 call load_high                  ; Copy the file
276
277 high_load_done:
278                 mov ax,real_mode_seg            ; Set to real mode seg
279                 mov es,ax
280
281                 mov si,dot_msg
282                 call cwritestr
283
284 ;
285 ; Now see if we have an initial RAMdisk; if so, do requisite computation
286 ; We know we have a new kernel; the old_kernel code already will have objected
287 ; if we tried to load initrd using an old kernel
288 ;
289 load_initrd:
290                 test byte [initrd_flag],1
291                 jz nk_noinitrd
292                 push es                         ; ES->real_mode_seg
293                 push ds
294                 pop es                          ; We need ES==DS
295                 mov si,InitRD
296                 mov di,InitRDCName
297                 call unmangle_name              ; Create human-readable name
298                 sub di,InitRDCName
299                 mov [InitRDCNameLen],di
300                 mov di,InitRD
301                 call searchdir                  ; Look for it in directory
302                 pop es
303                 jz initrd_notthere
304                 mov [es:su_ramdisklen1],ax      ; Ram disk length
305                 mov [es:su_ramdisklen2],dx
306                 mov edx,[HighMemSize]           ; End of memory
307                 dec edx
308                 mov eax,[RamdiskMax]            ; Highest address allowed by kernel
309                 cmp edx,eax
310                 jna memsize_ok
311                 mov edx,eax                     ; Adjust to fit inside limit
312 memsize_ok:
313                 inc edx
314                 xor dx,dx                       ; Round down to 64K boundary
315                 sub edx,[es:su_ramdisklen]      ; Subtract size of ramdisk
316                 xor dx,dx                       ; Round down to 64K boundary
317                 mov [es:su_ramdiskat],edx       ; Load address
318                 call loadinitrd                 ; Load initial ramdisk
319                 jmp short initrd_end
320
321 initrd_notthere:
322                 mov si,err_noinitrd
323                 call cwritestr
324                 mov si,InitRDCName
325                 call cwritestr
326                 mov si,crlf_msg
327                 jmp abort_load
328
329 no_high_mem:    mov si,err_nohighmem            ; Error routine
330                 jmp abort_load
331
332 initrd_end:
333 nk_noinitrd:
334 ;
335 ; Abandon hope, ye that enter here!  We do no longer permit aborts.
336 ;
337                 call abort_check                ; Last chance!!
338
339                 mov si,ready_msg
340                 call cwritestr
341
342                 call vgaclearmode               ; We can't trust ourselves after this
343
344                 UNLOAD_PREP                     ; Module-specific hook
345
346 ;
347 ; Now, if we were supposed to load "low", copy the kernel down to 10000h
348 ; and the real mode stuff to 90000h.  We assume that all bzImage kernels are
349 ; capable of starting their setup from a different address.
350 ;
351                 mov ax,real_mode_seg
352                 mov fs,ax
353
354 ;
355 ; Copy command line.  Unfortunately, the kernel boot protocol requires
356 ; the command line to exist in the 9xxxxh range even if the rest of the
357 ; setup doesn't.
358 ;
359                 cli                             ; In case of hooked interrupts
360                 test byte [LoadFlags],LOAD_HIGH
361                 jz need_high_cmdline
362                 cmp word [fs:su_version],0202h  ; Support new cmdline protocol?
363                 jb need_high_cmdline
364                 ; New cmdline protocol
365                 ; Store 32-bit (flat) pointer to command line
366                 mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4) + cmd_line_here
367                 jmp short in_proper_place
368
369 need_high_cmdline:
370 ;
371 ; Copy command line up to 90000h
372 ;
373                 mov ax,9000h
374                 mov es,ax
375                 mov si,cmd_line_here
376                 mov di,si
377                 mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic
378                 mov [fs:kern_cmd_offset],di     ; Store pointer
379
380                 mov cx,[CmdLineLen]
381                 add cx,byte 3
382                 shr cx,2                        ; Convert to dwords
383                 fs rep movsd
384
385                 push fs
386                 pop es
387
388                 test byte [LoadFlags],LOAD_HIGH
389                 jnz in_proper_place             ; If high load, we're done
390
391 ;
392 ; Loading low; we can't assume it's safe to run in place.
393 ;
394 ; Copy real_mode stuff up to 90000h
395 ;
396                 mov ax,9000h
397                 mov es,ax
398                 mov cx,[SetupSecs]
399                 inc cx                          ; Setup + boot sector
400                 shl cx,7                        ; Sectors -> dwords
401                 xor si,si
402                 xor di,di
403                 fs rep movsd                    ; Copy setup + boot sector
404 ;
405 ; Some kernels in the 1.2 ballpark but pre-bzImage have more than 4
406 ; setup sectors, but the boot protocol had not yet been defined.  They
407 ; rely on a signature to figure out if they need to copy stuff from
408 ; the "protected mode" kernel area.  Unfortunately, we used that area
409 ; as a transfer buffer, so it's going to find the signature there.
410 ; Hence, zero the low 32K beyond the setup area.
411 ;
412                 mov di,[SetupSecs]
413                 inc di                          ; Setup + boot sector
414                 mov cx,32768/512                ; Sectors/32K
415                 sub cx,di                       ; Remaining sectors
416                 shl di,9                        ; Sectors -> bytes
417                 shl cx,7                        ; Sectors -> dwords
418                 xor eax,eax
419                 rep stosd                       ; Clear region
420 ;
421 ; Copy the kernel down to the "low" location
422 ;
423                 mov ecx,[KernelSize]
424                 mov esi,100000h
425                 mov edi,10000h
426                 call bcopy
427
428 ;
429 ; Now everything is where it needs to be...
430 ;
431 ; When we get here, es points to the final segment, either
432 ; 9000h or real_mode_seg
433 ;
434 in_proper_place:
435
436 ;
437 ; If the default root device is set to FLOPPY (0000h), change to
438 ; /dev/fd0 (0200h)
439 ;
440                 cmp word [es:bs_rootdev],byte 0
441                 jne root_not_floppy
442                 mov word [es:bs_rootdev],0200h
443 root_not_floppy:
444
445 ;
446 ; Copy the disk table to high memory, then re-initialize the floppy
447 ; controller
448 ;
449 %if IS_SYSLINUX || IS_MDSLINUX
450                 lgs si,[cs:fdctab]
451                 mov di,linux_fdctab
452                 mov cx,6                        ; 12 bytes
453                 gs rep movsw
454                 mov [cs:fdctab],word linux_fdctab ; Save new floppy tab pos
455                 mov [cs:fdctab+2],es
456 %endif
457 ;
458 ; Linux wants the floppy motor shut off before starting the kernel,
459 ; at least bootsect.S seems to imply so.
460 ;
461 kill_motor:
462                 xor ax,ax
463                 xor dx,dx
464                 int 13h
465
466 ;
467 ; If we're debugging, wait for a keypress so we can read any debug messages
468 ;
469 %ifdef debug
470                 xor ax,ax
471                 int 16h
472 %endif
473 ;
474 ; Set up segment registers and the Linux real-mode stack
475 ; Note: es == the real mode segment
476 ;
477                 cli
478                 mov bx,es
479                 mov ds,bx
480                 mov fs,bx
481                 mov gs,bx
482                 mov ss,bx
483                 mov sp,linux_stack
484 ;
485 ; We're done... now RUN THAT KERNEL!!!!
486 ; Setup segment == real mode segment + 020h; we need to jump to offset
487 ; zero in the real mode segment.
488 ;
489                 add bx,020h
490                 push bx
491                 push word 0h
492                 retf
493
494 ;
495 ; Load an older kernel.  Older kernels always have 4 setup sectors, can't have
496 ; initrd, and are always loaded low.
497 ;
498 old_kernel:
499                 test byte [initrd_flag],1       ; Old kernel can't have initrd
500                 jz load_old_kernel
501                 mov si,err_oldkernel
502                 jmp abort_load
503 load_old_kernel:
504                 mov word [SetupSecs],4          ; Always 4 setup sectors
505                 mov byte [LoadFlags],0          ; Always low
506                 jmp read_kernel
507
508 ;
509 ; Load RAM disk into high memory
510 ;
511 ; Need to be set:
512 ;       su_ramdiskat    - Where in memory to load
513 ;       su_ramdisklen   - Size of file
514 ;       SI              - initrd filehandle/cluster pointer
515 ;
516                 section .text
517 loadinitrd:
518                 push es                         ; Save ES on entry
519                 mov ax,real_mode_seg
520                 mov es,ax
521                 mov edi,[es:su_ramdiskat]       ; initrd load address
522                 push si
523                 mov si,crlfloading_msg          ; Write "Loading "
524                 call cwritestr
525                 mov si,InitRDCName              ; Write ramdisk name
526                 call cwritestr
527                 mov si,dotdot_msg               ; Write dots
528                 call cwritestr
529                 pop si
530
531                 mov eax,[es:su_ramdisklen]
532                 call load_high                  ; Load the file
533
534                 call crlf
535                 pop es                          ; Restore original ES
536                 ret
537
538                 section .data
539 boot_image      db 'BOOT_IMAGE='
540 boot_image_len  equ $-boot_image
541
542                 section .bss
543                 alignb 4
544 RamdiskMax      resd 1                  ; Highest address for ramdisk
545 KernelSize      resd 1                  ; Size of kernel in bytes
546 KernelSects     resd 1                  ; Size of kernel in sectors
547 CmdLineLen      resw 1                  ; Length of command line including null
548 SetupSecs       resw 1                  ; Number of setup sectors
549 LoadFlags       resb 1                  ; Loadflags from kernel