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