VESA library: add support for reading lss16 images
[profile/ivi/syslinux.git] / runkernel.inc
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.
10 ;;
11 ;; -----------------------------------------------------------------------
12
13 ;;
14 ;; runkernel.inc
15 ;;
16 ;; Common code for running a Linux kernel
17 ;;
18
19 ;
20 ; Hook macros, that may or may not be defined
21 ;
22 %ifndef HAVE_SPECIAL_APPEND
23 %macro SPECIAL_APPEND 0
24 %endmacro
25 %endif
26
27 %ifndef HAVE_UNLOAD_PREP
28 %macro UNLOAD_PREP 0
29 %endmacro
30 %endif
31
32 ;
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.
36 ;
37 ; First check that our kernel is at least 1K, or else it isn't long
38 ; enough to have the appropriate headers.
39 ;
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.
43 ;
44 ; Additionally, we used to have a test for 8 MB or smaller.  Equally
45 ; obsolete.
46 ;
47 is_linux_kernel:
48                 push si                         ; <A> file pointer
49                 mov si,loading_msg
50                 call cwritestr
51                 mov si,KernelCName              ; Print kernel name part of
52                 call cwritestr                  ; "Loading" message
53
54
55 ;
56 ; Now start transferring the kernel
57 ;
58                 push word real_mode_seg
59                 pop es
60
61 ;
62 ; Start by loading the bootsector/setup code, to see if we need to
63 ; do something funky.  It should fit in the first 32K (loading 64K won't
64 ; work since we might have funny stuff up near the end of memory).
65 ;
66                 call dot_pause                  ; Check for abort key
67                 mov cx,8000h >> SECTOR_SHIFT    ; Half a moby (32K)
68                 xor bx,bx
69                 pop si                          ; <A> file pointer
70                 call getfssec
71                 cmp cx,1024
72                 jb kernel_corrupt
73                 cmp word [es:bs_bootsign],0AA55h
74                 jne kernel_corrupt              ; Boot sec signature missing
75
76 ;
77 ; Save the file pointer for later...
78 ;
79                 push si                         ; <A> file pointer
80
81 ;
82 ; Construct the command line (append options have already been copied)
83 ;
84 construct_cmdline:
85                 mov di,[CmdLinePtr]
86                 mov si,boot_image               ; BOOT_IMAGE=
87                 mov cx,boot_image_len
88                 rep movsb
89                 mov si,KernelCName              ; Unmangled kernel name
90                 mov cx,[KernelCNameLen]
91                 rep movsb
92                 mov al,' '                      ; Space
93                 stosb
94
95                 SPECIAL_APPEND                  ; Module-specific hook
96
97                 mov si,[CmdOptPtr]              ; Options from user input
98                 call strcpy
99
100 ;
101 ; Scan through the command line for anything that looks like we might be
102 ; interested in.  The original version of this code automatically assumed
103 ; the first option was BOOT_IMAGE=, but that is no longer certain.
104 ;
105                 mov si,cmd_line_here
106                 xor ax,ax
107                 mov [InitRDPtr],ax              ; No initrd= option (yet)
108                 push es                         ; Set DS <- real_mode_seg
109                 pop ds
110 get_next_opt:   lodsb
111                 and al,al
112                 jz cmdline_end
113                 cmp al,' '
114                 jbe get_next_opt
115                 dec si
116                 mov eax,[si]
117                 cmp eax,'vga='
118                 je is_vga_cmd
119                 cmp eax,'mem='
120                 je is_mem_cmd
121 %if IS_PXELINUX
122                 cmp eax,'keep'                  ; Is it "keeppxe"?
123                 jne .notkeep
124                 cmp dword [si+3],'ppxe'
125                 jne .notkeep
126                 cmp byte [si+7],' '             ; Must be whitespace or EOS
127                 ja .notkeep
128                 or byte [cs:KeepPXE],1
129 .notkeep:
130 %endif
131                 push es                         ; <B> ES -> real_mode_seg
132                 push cs
133                 pop es                          ; Set ES <- normal DS
134                 mov di,initrd_cmd
135                 mov cx,initrd_cmd_len
136                 repe cmpsb
137                 jne .not_initrd
138
139                 cmp al,' '
140                 jbe .noramdisk
141                 mov [cs:InitRDPtr],si
142                 jmp .not_initrd
143 .noramdisk:
144                 xor ax,ax
145                 mov [cs:InitRDPtr],ax
146 .not_initrd:    pop es                          ; <B> ES -> real_mode_seg
147 skip_this_opt:  lodsb                           ; Load from command line
148                 cmp al,' '
149                 ja skip_this_opt
150                 dec si
151                 jmp short get_next_opt
152 is_vga_cmd:
153                 add si,4
154                 mov eax,[si-1]
155                 mov bx,-1
156                 cmp eax,'=nor'                  ; vga=normal
157                 je vc0
158                 dec bx                          ; bx <- -2
159                 cmp eax,'=ext'                  ; vga=ext
160                 je vc0
161                 dec bx                          ; bx <- -3
162                 cmp eax,'=ask'                  ; vga=ask
163                 je vc0
164                 call parseint                   ; vga=<number>
165                 jc skip_this_opt                ; Not an integer
166 vc0:            mov [bs_vidmode],bx             ; Set video mode
167                 jmp short skip_this_opt
168 is_mem_cmd:
169                 add si,4
170                 call parseint
171                 jc skip_this_opt                ; Not an integer
172 %if HIGHMEM_SLOP != 0
173                 sub ebx,HIGHMEM_SLOP
174 %endif
175                 mov [cs:MyHighMemSize],ebx
176                 jmp short skip_this_opt
177 cmdline_end:
178                 push cs                         ; Restore standard DS
179                 pop ds
180                 sub si,cmd_line_here
181                 mov [CmdLineLen],si             ; Length including final null
182 ;
183 ; Now check if we have a large kernel, which needs to be loaded high
184 ;
185 prepare_header:
186                 mov dword [RamdiskMax], HIGHMEM_MAX     ; Default initrd limit
187                 cmp dword [es:su_header],HEADER_ID      ; New setup code ID
188                 jne old_kernel                  ; Old kernel, load low
189                 mov ax,[es:su_version]
190                 mov [KernelVersion],ax
191                 cmp ax,0200h                    ; Setup code version 2.0
192                 jb old_kernel                   ; Old kernel, load low
193                 cmp ax,0201h                    ; Version 2.01+?
194                 jb new_kernel                   ; If 2.00, skip this step
195                 ; Set up the heap (assuming loading high for now)
196                 mov word [es:su_heapend],linux_stack-512
197                 or byte [es:su_loadflags],80h   ; Let the kernel know we care
198                 cmp ax,0203h                    ; Version 2.03+?
199                 jb new_kernel                   ; Not 2.03+
200                 mov eax,[es:su_ramdisk_max]
201                 mov [RamdiskMax],eax            ; Set the ramdisk limit
202
203 ;
204 ; We definitely have a new-style kernel.  Let the kernel know who we are,
205 ; and that we are clueful
206 ;
207 new_kernel:
208                 mov byte [es:su_loader],my_id   ; Show some ID
209                 xor eax,eax
210                 mov [es:su_ramdisklen],eax      ; No initrd loaded yet
211
212 ;
213 ; About to load the kernel.  This is a modern kernel, so use the boot flags
214 ; we were provided.
215 ;
216                 mov al,[es:su_loadflags]
217                 mov [LoadFlags],al
218
219                 ; Cap the ramdisk memory range if appropriate
220                 mov eax,[RamdiskMax]
221                 cmp eax,[MyHighMemSize]
222                 ja .ok
223                 mov [MyHighMemSize],eax
224 .ok:
225
226 any_kernel:
227
228 ;
229 ; Load the kernel.  We always load it at 100000h even if we're supposed to
230 ; load it "low"; for a "low" load we copy it down to low memory right before
231 ; jumping to it.
232 ;
233 read_kernel:
234                 movzx ax,byte [es:bs_setupsecs] ; Setup sectors
235                 and ax,ax
236                 jnz .sects_ok
237                 mov al,4                        ; 0 = 4 setup sectors
238 .sects_ok:
239                 inc ax                          ; Including the boot sector
240                 mov [SetupSecs],ax
241
242                 call dot_pause
243
244 ;
245 ; Move the stuff beyond the setup code to high memory at 100000h
246 ;
247                 movzx esi,word [SetupSecs]      ; Setup sectors
248                 shl si,9                        ; Convert to bytes
249                 mov ecx,8000h                   ; 32K
250                 sub ecx,esi                     ; Number of bytes to copy
251                 add esi,(real_mode_seg << 4)    ; Pointer to source
252                 mov edi,100000h                 ; Copy to address 100000h
253
254                 call bcopy                      ; Transfer to high memory
255
256                 pop si                          ; <A> File pointer
257                 and si,si                       ; EOF already?
258                 jz high_load_done
259
260                 ; On exit EDI -> where to load the rest
261
262                 mov bx,dot_pause
263                 or eax,-1                       ; Load the whole file
264                 mov dx,3                        ; Pad to dword
265                 call load_high
266
267 high_load_done:
268                 mov [KernelEnd],edi
269                 mov ax,real_mode_seg            ; Set to real mode seg
270                 mov es,ax
271
272                 mov si,dot_msg
273                 call cwritestr
274 ;
275 ; Some older kernels (1.2 era) would have more than 4 setup sectors, but
276 ; would not rely on the boot protocol to manage that.  These kernels fail
277 ; if they see protected-mode kernel data after the setup sectors, so
278 ; clear that memory.
279 ;
280                 mov di,[SetupSecs]
281                 shl di,9
282                 xor eax,eax
283                 mov cx,cmd_line_here
284                 sub cx,di
285                 shr cx,2
286                 rep stosd
287
288 ;
289 ; Now see if we have an initial RAMdisk; if so, do requisite computation
290 ; We know we have a new kernel; the old_kernel code already will have objected
291 ; if we tried to load initrd using an old kernel
292 ;
293 load_initrd:
294                 xor eax,eax
295                 cmp [InitRDPtr],ax
296                 jz .noinitrd
297                 call parse_load_initrd
298 .noinitrd:
299
300 ;
301 ; Abandon hope, ye that enter here!  We do no longer permit aborts.
302 ;
303                 call abort_check                ; Last chance!!
304
305                 mov si,ready_msg
306                 call cwritestr
307
308                 UNLOAD_PREP                     ; Module-specific hook
309
310 ;
311 ; Now, if we were supposed to load "low", copy the kernel down to 10000h
312 ; and the real mode stuff to 90000h.  We assume that all bzImage kernels are
313 ; capable of starting their setup from a different address.
314 ;
315                 mov ax,real_mode_seg
316                 mov es,ax
317                 mov fs,ax
318
319 ;
320 ; If the default root device is set to FLOPPY (0000h), change to
321 ; /dev/fd0 (0200h)
322 ;
323                 cmp word [es:bs_rootdev],byte 0
324                 jne root_not_floppy
325                 mov word [es:bs_rootdev],0200h
326 root_not_floppy:
327
328 ;
329 ; Copy command line.  Unfortunately, the old kernel boot protocol requires
330 ; the command line to exist in the 9xxxxh range even if the rest of the
331 ; setup doesn't.
332 ;
333 setup_command_line:
334                 mov dx,[KernelVersion]
335                 test byte [LoadFlags],LOAD_HIGH
336                 jz .need_high_cmdline
337                 cmp dx,0202h                    ; Support new cmdline protocol?
338                 jb .need_high_cmdline
339                 ; New cmdline protocol
340                 ; Store 32-bit (flat) pointer to command line
341                 ; This is the "high" location, since we have bzImage
342                 mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4)+cmd_line_here
343                 mov word [HeapEnd],linux_stack
344                 mov word [fs:su_heapend],linux_stack-512
345                 jmp .setup_done
346
347 .need_high_cmdline:
348 ;
349 ; Copy command line down to fit in high conventional memory
350 ; -- this happens if we have a zImage kernel or the protocol
351 ; is less than 2.02.
352 ;
353                 mov si,cmd_line_here
354                 mov di,old_cmd_line_here
355                 mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic
356                 mov [fs:kern_cmd_offset],di     ; Store pointer
357                 mov word [HeapEnd],old_linux_stack
358                 mov ax,255                      ; Max cmdline limit
359                 cmp dx,0201h
360                 jb .adjusted
361                 ; Protocol 2.01+
362                 mov word [fs:su_heapend],old_linux_stack-512
363                 jbe .adjusted
364                 ; Protocol 2.02+
365                 ; Note that the only reason we would end up here is
366                 ; because we have a zImage, so we anticipate the move
367                 ; to 90000h already...
368                 mov dword [fs:su_cmd_line_ptr],0x90000+old_cmd_line_here
369                 mov ax,old_max_cmd_len          ; 2.02+ allow a higher limit
370 .adjusted:
371
372                 mov cx,[CmdLineLen]
373                 cmp cx,ax
374                 jna .len_ok
375                 mov cx,ax                       ; Truncate the command line
376 .len_ok:
377                 fs rep movsb
378                 stosb                           ; Final null, note AL=0 already
379                 mov [CmdLineEnd],di
380                 cmp dx,0200h
381                 jb .nomovesize
382                 mov [es:su_movesize],di         ; Tell the kernel what to move
383 .nomovesize:
384 .setup_done:
385
386 ;
387 ; Time to start setting up move descriptors
388 ;
389 setup_move:
390                 mov di,trackbuf
391                 xor cx,cx                       ; Number of descriptors
392
393                 mov bx,es                       ; real_mode_seg
394                 mov fs,bx
395                 push ds                         ; We need DS == ES == CS here
396                 pop es
397
398                 test byte [LoadFlags],LOAD_HIGH
399                 jnz .loading_high
400
401 ; Loading low: move real_mode stuff to 90000h, then move the kernel down
402                 mov eax,90000h
403                 stosd
404                 mov eax,real_mode_seg << 4
405                 stosd
406                 movzx eax,word [CmdLineEnd]
407                 stosd
408                 inc cx
409
410                 mov eax,10000h                  ; Target address of low kernel
411                 stosd
412                 mov eax,100000h                 ; Where currently loaded
413                 stosd
414                 neg eax
415                 add eax,[KernelEnd]
416                 stosd
417                 inc cx
418
419                 mov bx,9000h                    ; Revised real mode segment
420
421 .loading_high:
422
423                 cmp word [InitRDPtr],0          ; Did we have an initrd?
424                 je .no_initrd
425
426                 mov eax,[fs:su_ramdiskat]
427                 stosd
428                 mov eax,[InitRDStart]
429                 stosd
430                 mov eax,[fs:su_ramdisklen]
431                 stosd
432                 inc cx
433
434 .no_initrd:
435                 push cx                         ; Length of descriptor list
436                 push word trackbuf
437
438 %ifdef DEBUG_TRACERS
439                 pushad
440                 mov si,trackbuf
441 .foo:
442                 lodsd
443                 call writehex8
444                 mov al,'.'
445                 call writechr
446                 lodsd
447                 call writehex8
448                 mov al,'.'
449                 call writechr
450                 lodsd
451                 call writehex8
452                 call crlf
453                 loop .foo
454                 popad
455 %endif
456
457                 mov dword [EntryPoint],run_linux_kernel
458                 ; BX points to the final real mode segment, and will be loaded
459                 ; into DS.
460                 jmp replace_bootstrap
461
462
463 run_linux_kernel:
464 ;
465 ; Set up segment registers and the Linux real-mode stack
466 ; Note: ds == the real mode segment
467 ;
468                 cli
469                 mov ax,ds
470                 mov ss,ax
471                 mov sp,strict word linux_stack
472                 ; Point HeapEnd to the immediate of the instruction above
473 HeapEnd         equ $-2                 ; Self-modifying code!  Fun!
474                 mov es,ax
475                 mov fs,ax
476                 mov gs,ax
477
478 ;
479 ; We're done... now RUN THAT KERNEL!!!!
480 ; Setup segment == real mode segment + 020h; we need to jump to offset
481 ; zero in the real mode segment.
482 ;
483                 add ax,020h
484                 push ax
485                 push word 0h
486                 retf
487
488 ;
489 ; Load an older kernel.  Older kernels always have 4 setup sectors, can't have
490 ; initrd, and are always loaded low.
491 ;
492 old_kernel:
493                 xor ax,ax
494                 cmp word [InitRDPtr],ax         ; Old kernel can't have initrd
495                 je .load
496                 mov si,err_oldkernel
497                 jmp abort_load
498 .load:
499                 mov byte [LoadFlags],al         ; Always low
500                 mov word [KernelVersion],ax     ; Version 0.00
501                 jmp any_kernel
502
503 ;
504 ; parse_load_initrd
505 ;
506 ; Parse an initrd= option and load the initrds.  This sets
507 ; InitRDStart and InitRDEnd with dword padding between; we then
508 ; do a global memory shuffle to move it to the end of memory.
509 ;
510 ; On entry, EDI points to where to start loading.
511 ;
512 parse_load_initrd:
513                 push es
514                 push ds
515                 mov ax,real_mode_seg
516                 mov ds,ax
517                 push cs
518                 pop es                  ; DS == real_mode_seg, ES == CS
519
520                 mov [cs:InitRDStart],edi
521                 mov [cs:InitRDEnd],edi
522
523                 mov si,[cs:InitRDPtr]
524
525 .get_chunk:
526                 ; DS:SI points to the start of a name
527
528                 mov bx,si
529 .find_end:
530                 lodsb
531                 cmp al,','
532                 je .got_end
533                 cmp al,' '
534                 jbe .got_end
535                 jmp .find_end
536
537 .got_end:
538                 push ax                 ; Terminating character
539                 push si                 ; Next filename (if any)
540                 mov byte [si-1],0       ; Zero-terminate
541                 mov si,bx               ; Current filename
542
543                 push di
544                 mov di,InitRD           ; Target buffer for mangled name
545                 call mangle_name
546                 pop di
547                 call loadinitrd
548
549                 pop si
550                 pop ax
551                 mov [si-1],al           ; Restore ending byte
552
553                 cmp al,','
554                 je .get_chunk
555
556                 ; Compute the initrd target location
557                 mov edx,[cs:InitRDEnd]
558                 sub edx,[cs:InitRDStart]
559                 mov [su_ramdisklen],edx
560                 mov eax,[cs:MyHighMemSize]
561                 sub eax,edx
562                 and ax,0F000h           ; Round to a page boundary
563                 mov [su_ramdiskat],eax
564
565                 pop ds
566                 pop es
567                 ret
568
569 ;
570 ; Load RAM disk into high memory
571 ;
572 ; Input:        InitRD          - set to the mangled name of the initrd
573 ;               EDI             - location to load
574 ; Output:       EDI             - location for next initrd
575 ;               InitRDEnd       - updated
576 ;
577 loadinitrd:
578                 push ds
579                 push es
580                 mov ax,cs                       ; CS == DS == ES
581                 mov ds,ax
582                 mov es,ax
583                 push edi
584                 mov si,InitRD
585                 mov di,InitRDCName
586                 call unmangle_name              ; Create human-readable name
587                 sub di,InitRDCName
588                 mov [InitRDCNameLen],di
589                 mov di,InitRD
590                 call searchdir                  ; Look for it in directory
591                 pop edi
592                 jz .notthere
593
594                 push si
595                 mov si,crlfloading_msg          ; Write "Loading "
596                 call cwritestr
597                 mov si,InitRDCName              ; Write ramdisk name
598                 call cwritestr
599                 mov si,dotdot_msg               ; Write dots
600                 call cwritestr
601                 pop si
602
603                 mov dx,3
604                 mov bx,dot_pause
605                 call load_high
606                 mov [InitRDEnd],ebx
607
608                 pop es
609                 pop ds
610                 ret
611
612 .notthere:
613                 mov si,err_noinitrd
614                 call cwritestr
615                 mov si,InitRDCName
616                 call cwritestr
617                 mov si,crlf_msg
618                 jmp abort_load
619
620 no_high_mem:                                    ; Error routine
621                 mov si,err_nohighmem
622                 jmp abort_load
623
624                 ret
625
626                 section .data
627 crlfloading_msg db CR, LF
628 loading_msg     db 'Loading ', 0
629 dotdot_msg      db '.'
630 dot_msg         db '.', 0
631 ready_msg       db 'ready.', CR, LF, 0
632 err_oldkernel   db 'Cannot load a ramdisk with an old kernel image.'
633                 db CR, LF, 0
634 err_noinitrd    db CR, LF, 'Could not find ramdisk image: ', 0
635
636 boot_image      db 'BOOT_IMAGE='
637 boot_image_len  equ $-boot_image
638
639                 section .bss
640                 alignb 4
641 MyHighMemSize   resd 1                  ; Possibly adjusted highmem size
642 RamdiskMax      resd 1                  ; Highest address for ramdisk
643 KernelSize      resd 1                  ; Size of kernel in bytes
644 KernelSects     resd 1                  ; Size of kernel in sectors
645 KernelEnd       resd 1                  ; Ending address of the kernel image
646 InitRDStart     resd 1                  ; Start of initrd (pre-relocation)
647 InitRDEnd       resd 1                  ; End of initrd (pre-relocation)
648 CmdLineLen      resw 1                  ; Length of command line including null
649 CmdLineEnd      resw 1                  ; End of the command line in real_mode_seg
650 SetupSecs       resw 1                  ; Number of setup sectors (+bootsect)
651 InitRDPtr       resw 1                  ; Pointer to initrd= option in command line
652 KernelVersion   resw 1                  ; Kernel protocol version
653 LoadFlags       resb 1                  ; Loadflags from kernel