Magellan Linux

Annotation of /trunk/mkinitrd-magellan/isolinux/ui.inc

Parent Directory Parent Directory | Revision Log Revision Log


Revision 1133 - (hide annotations) (download)
Thu Aug 19 09:50:43 2010 UTC (13 years, 8 months ago) by niro
File size: 16790 byte(s)
-updated to isolinux-3.86
1 niro 532 ;; -----------------------------------------------------------------------
2     ;;
3 niro 1133 ;; Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
4     ;; Copyright 2009-2010 Intel Corporation; author: H. Peter Anvin
5     ;;
6 niro 532 ;; 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     ; This file should be entered with the config file open (for getc)
16     ;
17 niro 1133 load_config_file:
18 niro 532 call parse_config ; Parse configuration file
19     no_config_file:
20 niro 1133
21     call adv_init
22 niro 532 ;
23 niro 1133 ; Check for an ADV boot-once entry
24     ;
25     mov dl,ADV_BOOTONCE
26     call adv_get
27     jcxz .no_bootonce
28    
29     .have_bootone:
30     ; We apparently have a boot-once set; clear it and
31     ; then execute the boot-once...
32    
33     ; Save the boot-once data; SI = data, CX = length
34     mov di,command_line
35     rep movsb
36     xor ax,ax
37     stosb
38    
39     ; Clear the boot-once data from the ADV
40     xor cx,cx ; Set to zero = delete
41     call adv_set
42     jc .err
43     call adv_write
44     .err: jmp load_kernel
45    
46     .no_bootonce:
47    
48     ;
49 niro 532 ; Check whether or not we are supposed to display the boot prompt.
50     ;
51     check_for_key:
52 niro 1133 test byte [KbdFlags],5Bh ; Shift Alt Caps Scroll
53     jnz enter_command
54 niro 532 cmp word [ForcePrompt],0 ; Force prompt?
55 niro 1133 jz auto_boot
56     cmp word [DefaultLevel],1 ; Active UI statement?
57     ja auto_boot
58 niro 532
59     enter_command:
60     cmp word [NoEscape],0 ; If NOESCAPE, no prompt,
61     jne auto_boot ; always run default cmd
62    
63     mov si,boot_prompt
64 niro 1133 call writestr
65 niro 532
66     mov byte [FuncFlag],0 ; <Ctrl-F> not pressed
67     mov di,command_line
68    
69     ;
70     ; get the very first character -- we can either time
71     ; out, or receive a character press at this time. Some dorky BIOSes stuff
72     ; a return in the buffer on bootup, so wipe the keyboard buffer first.
73     ;
74     clear_buffer: mov ah,11h ; Check for pending char
75     int 16h
76     jz get_char_time
77     mov ah,10h ; Get char
78     int 16h
79     jmp short clear_buffer
80    
81     ; For the first character, both KbdTimeout and
82     ; TotalTimeout apply; after that, only TotalTimeout.
83    
84     get_char_time:
85     mov eax,[TotalTimeout]
86     mov [ThisTotalTo],eax
87     mov eax,[KbdTimeout]
88     mov [ThisKbdTo],eax
89    
90     get_char:
91     call getchar_timeout
92     and dword [ThisKbdTo],0 ; For the next time...
93    
94     and al,al
95     jz func_key
96    
97     got_ascii: cmp al,7Fh ; <DEL> == <BS>
98     je backspace
99     cmp al,' ' ; ASCII?
100     jb not_ascii
101     ja enter_char
102     cmp di,command_line ; Space must not be first
103     je short get_char
104     enter_char: test byte [FuncFlag],1
105 niro 1133 jnz ctrl_f ; Keystroke after <Ctrl-F>
106     cmp di,max_cmd_len+command_line ; Check there's space
107 niro 532 jnb short get_char
108     stosb ; Save it
109     call writechr ; Echo to screen
110     jmp short get_char
111 niro 1133 not_ascii:
112 niro 532 cmp al,0Dh ; Enter
113     je command_done
114 niro 1133 cmp al,09h ; Tab
115     je display_labels
116 niro 532 cmp al,'F' & 1Fh ; <Ctrl-F>
117     je set_func_flag
118 niro 1133 %if IS_PXELINUX
119     cmp al,'N' & 1Fh ; <Ctrl-N>
120     je show_network_info
121     %endif
122 niro 532 cmp al,'U' & 1Fh ; <Ctrl-U>
123     je kill_command ; Kill input line
124     cmp al,'V' & 1Fh ; <Ctrl-V>
125     je print_version
126     cmp al,'X' & 1Fh ; <Ctrl-X>
127     je force_text_mode
128     cmp al,08h ; Backspace
129     jne get_char
130     backspace: cmp di,command_line ; Make sure there is anything
131     je get_char ; to erase
132     dec di ; Unstore one character
133     mov si,wipe_char ; and erase it from the screen
134 niro 1133 call writestr
135     get_char_2:
136     jmp short get_char
137 niro 532
138     kill_command:
139     call crlf
140     jmp enter_command
141    
142     force_text_mode:
143     call vgaclearmode
144     jmp enter_command
145    
146     set_func_flag:
147     mov byte [FuncFlag],1
148 niro 1133 jmp short get_char_2
149 niro 532
150 niro 1133 display_labels:
151     cmp word [NoComplete],0 ; Label completion enabled?
152     jne get_char_2
153     push di ; Save pointer
154     mov cx,di
155     sub cx,command_line
156     call crlf
157     mov esi,[HighMemSize] ; Start from top of memory
158     .scan:
159     cmp esi,[VKernelEnd]
160     jbe .not_vk
161    
162     push cx ; save command line size
163    
164     mov edi,VKernelBuf
165     call rllunpack
166     ; ESI updated on return
167    
168     sub di,cx ; Return to beginning of buf
169     pop cx ; restore command line size
170     push si ; save SI
171     cmp cx,0
172     jz .print
173     push di
174     push cx
175     mov si,command_line
176     es repe cmpsb
177     pop cx
178     pop di
179     jne .next
180     .print:
181     mov al,' '
182     call writechr
183    
184     mov si,di
185     call writestr
186     .next:
187     pop si ; restore SI
188     jmp .scan
189     .not_vk:
190     call crlf
191     jmp fk_wrcmd
192    
193     ctrl_f:
194 niro 532 xor ah,ah
195 niro 1133 mov [FuncFlag],ah
196     cmp al,'0'
197     jb get_char_2
198     je .zero ; <Ctrl-F>0 = F10
199     or al,20h ; Lower case
200     cmp al,'9'
201     jna .digit
202     cmp al,'a' ; F10-F12 = <Ctrl-F>A, B, C
203     jb get_char_2
204     cmp al,'c'
205     ja get_char_2
206     sub al,'a'-10
207     jmp show_help
208     .zero:
209     mov al,10
210     jmp show_help
211     .digit:
212     sub al,'1'
213     jmp show_help
214 niro 532
215     func_key:
216     ; AL = 0 if we get here
217     xchg al,ah
218 niro 1133 cmp al,44h ; F10
219     ja .f11_f12
220     sub al,3Bh ; F1
221     jb get_char_2
222     jmp show_help
223     .f11_f12:
224     cmp al,85h ; F11
225     jb get_char_2
226     cmp al,86h ; F12
227     ja get_char_2
228     sub al,85h-10
229    
230     show_help: ; AX = func key # (0 = F1, 9 = F10, 11 = F12)
231 niro 532 push di ; Save end-of-cmdline pointer
232     shl ax,FILENAME_MAX_LG2 ; Convert to pointer
233     add ax,FKeyName
234     xchg di,ax
235     cmp byte [di+NULLOFFSET],NULLFILE
236     je short fk_nofile ; Undefined F-key
237 niro 1133 call open
238 niro 532 jz short fk_nofile ; File not found
239     call crlf
240     call get_msg_file
241     jmp short fk_wrcmd
242    
243     print_version:
244     push di ; Command line write pointer
245     mov si,syslinux_banner
246 niro 1133 call writestr
247 niro 532 %ifdef HAVE_BIOSNAME
248     mov si,[BIOSName]
249 niro 1133 call writestr
250 niro 532 %endif
251     mov si,copyright_str
252 niro 1133 call writestr
253 niro 532
254     ; ... fall through ...
255    
256     ; Write the boot prompt and command line again and
257     ; wait for input. Note that this expects the cursor
258     ; to already have been CRLF'd, and that the old value
259     ; of DI (the command line write pointer) is on the stack.
260     fk_wrcmd:
261     mov si,boot_prompt
262 niro 1133 call writestr
263 niro 532 pop di ; Command line write pointer
264     push di
265     mov byte [di],0 ; Null-terminate command line
266     mov si,command_line
267 niro 1133 call writestr ; Write command line so far
268 niro 532 fk_nofile: pop di
269 niro 1133 jmp get_char
270 niro 532
271     ;
272 niro 1133 ; Show network info (in the form of the ipappend strings)
273     ;
274     %if IS_PXELINUX
275     show_network_info:
276     push di ; Command line write pointer
277     call crlf
278     mov si,IPAppends ; See comboot.doc
279     mov cx,numIPAppends
280     .loop:
281     lodsw
282     push si
283     mov si,ax
284     call writestr
285     call crlf
286     pop si
287     loop .loop
288     jmp fk_wrcmd
289     %endif
290    
291     ;
292 niro 532 ; Jump here to run the default command line
293     ;
294     auto_boot:
295 niro 1133 cmp word [DefaultLevel],0 ; No UI or DEFAULT?
296     jne .have_default
297     mov si,no_default_msg
298     call writestr
299     cmp word [NoEscape],0 ; NOESCAPE but no DEFAULT?
300     jne kaboom ; If so, we're stuck!
301     jmp enter_command
302    
303     .have_default:
304 niro 532 mov si,default_cmd
305     mov di,command_line
306     mov cx,(max_cmd_len+4) >> 2
307     rep movsd
308     jmp short load_kernel
309    
310 niro 1133 section .data
311     no_default_msg db 'No DEFAULT or UI configuration directive found!'
312     db CR, LF, 0
313    
314     section .text
315    
316 niro 532 ;
317     ; Jump here when the command line is completed
318     ;
319     command_done:
320     call crlf
321     cmp di,command_line ; Did we just hit return?
322     je auto_boot
323     xor al,al ; Store a final null
324     stosb
325    
326     load_kernel: ; Load the kernel now
327     ;
328     ; First we need to mangle the kernel name the way DOS would...
329     ;
330     mov si,command_line
331     mov di,KernelName
332     push si
333     call mangle_name
334     pop si
335     ;
336     ; Fast-forward to first option (we start over from the beginning, since
337     ; mangle_name doesn't necessarily return a consistent ending state.)
338     ;
339     clin_non_wsp: lodsb
340     cmp al,' '
341     ja clin_non_wsp
342     clin_is_wsp: and al,al
343     jz clin_opt_ptr
344     lodsb
345     cmp al,' '
346     jbe clin_is_wsp
347     clin_opt_ptr: dec si ; Point to first nonblank
348     mov [CmdOptPtr],si ; Save ptr to first option
349     ;
350     ; If "allowoptions 0", put a null character here in order to ignore any
351     ; user-specified options.
352     ;
353     mov ax,[AllowOptions]
354     and ax,ax
355     jnz clin_opt_ok
356     mov [si],al
357     clin_opt_ok:
358    
359     ;
360     ; Now check if it is a "virtual kernel"
361     ;
362     vk_check:
363 niro 1133 mov esi,[HighMemSize] ; Start from top of memory
364 niro 532 .scan:
365 niro 1133 cmp esi,[VKernelEnd]
366     jbe .not_vk
367 niro 532
368 niro 1133 mov edi,VKernelBuf
369 niro 532 call rllunpack
370 niro 1133 ; ESI updated on return
371 niro 532
372     sub di,cx ; Return to beginning of buf
373     push si
374 niro 1133 mov si,command_line
375     .loop:
376     lodsb
377     cmp al,' '
378     jbe .done
379     scasb
380     je .loop
381     .nomatch:
382 niro 532 pop si
383     jmp .scan
384 niro 1133 .done:
385     cmp byte [di],0 ; Must match end of string
386     jne .nomatch
387     pop si
388 niro 532
389     ;
390     ; We *are* using a "virtual kernel"
391     ;
392     .found:
393     push es
394     push word real_mode_seg
395     pop es
396     mov di,cmd_line_here
397     mov si,VKernelBuf+vk_append
398     mov cx,[VKernelBuf+vk_appendlen]
399     rep movsb
400     mov [CmdLinePtr],di ; Where to add rest of cmd
401     pop es
402     mov di,KernelName
403 niro 1133 push di
404 niro 532 mov si,VKernelBuf+vk_rname
405     mov cx,FILENAME_MAX ; We need ECX == CX later
406     rep movsb
407     pop di
408     %if IS_PXELINUX
409     mov al,[VKernelBuf+vk_ipappend]
410     mov [IPAppend],al
411     %endif
412     xor bx,bx ; Try only one version
413    
414 niro 1133 mov al,[VKernelBuf+vk_type]
415     mov [KernelType],al
416    
417     %if HAS_LOCALBOOT
418 niro 532 ; Is this a "localboot" pseudo-kernel?
419 niro 1133 cmp al,VK_LOCALBOOT ; al == KernelType
420     mov ax,[VKernelBuf+vk_rname] ; Possible localboot type
421     je local_boot
422 niro 532 %endif
423     jmp get_kernel
424    
425     .not_vk:
426     ;
427     ; Not a "virtual kernel" - check that's OK and construct the command line
428     ;
429     cmp word [AllowImplicit],byte 0
430     je bad_implicit
431     push es
432     push si
433     push di
434     mov di,real_mode_seg
435     mov es,di
436     mov si,AppendBuf
437     mov di,cmd_line_here
438     mov cx,[AppendLen]
439     rep movsb
440     mov [CmdLinePtr],di
441     pop di
442     pop si
443     pop es
444 niro 1133
445     mov [KernelType], cl ; CL == 0 here
446    
447 niro 532 ;
448     ; Find the kernel on disk
449     ;
450     get_kernel: mov byte [KernelName+FILENAME_MAX],0 ; Zero-terminate filename/extension
451     mov di,KernelName+4*IS_PXELINUX
452 niro 1133 cmp byte [di],' '
453     jbe bad_kernel ; Missing kernel name
454 niro 532 xor al,al
455     mov cx,FILENAME_MAX-5 ; Need 4 chars + null
456     repne scasb ; Scan for final null
457     jne .no_skip
458 niro 1133 dec di ; Point to final null
459 niro 532 .no_skip: mov [KernelExtPtr],di
460     mov bx,exten_table
461     .search_loop: push bx
462 niro 1133 mov di,KernelName ; Search on disk
463 niro 532 call searchdir
464     pop bx
465     jnz kernel_good
466     mov eax,[bx] ; Try a different extension
467     mov si,[KernelExtPtr]
468     mov [si],eax
469     mov byte [si+4],0
470     add bx,byte 4
471     cmp bx,exten_table_end
472     jna .search_loop ; allow == case (final case)
473     ; Fall into bad_kernel
474     ;
475     ; bad_kernel: Kernel image not found
476     ; bad_implicit: The user entered a nonvirtual kernel name, with "implicit 0"
477     ;
478     bad_implicit:
479     bad_kernel:
480     mov cx,[OnerrorLen]
481     and cx,cx
482     jnz on_error
483     .really:
484     mov si,KernelName
485     mov di,KernelCName
486     push di
487     call unmangle_name ; Get human form
488     mov si,err_notfound ; Complain about missing kernel
489 niro 1133 call writestr
490 niro 532 pop si ; KernelCName
491 niro 1133 call writestr
492 niro 532 mov si,crlf_msg
493     jmp abort_load ; Ask user for clue
494    
495     ;
496 niro 1133 ; on_error: bad kernel, but we have onerror set; CX = OnerrorLen
497 niro 532 ;
498     on_error:
499     mov si,Onerror
500     mov di,command_line
501     push si ; <A>
502     push di ; <B>
503     push cx ; <C>
504     push cx ; <D>
505     push di ; <E>
506     repe cmpsb
507     pop di ; <E> di == command_line
508     pop bx ; <D> bx == [OnerrorLen]
509     je bad_kernel.really ; Onerror matches command_line already
510     neg bx ; bx == -[OnerrorLen]
511     lea cx,[max_cmd_len+bx]
512     ; CX == max_cmd_len-[OnerrorLen]
513     mov di,command_line+max_cmd_len-1
514     mov byte [di+1],0 ; Enforce null-termination
515     lea si,[di+bx]
516     std
517     rep movsb ; Make space in command_line
518     cld
519     pop cx ; <C> cx == [OnerrorLen]
520     pop di ; <B> di == command_line
521     pop si ; <A> si == Onerror
522     rep movsb
523     jmp load_kernel
524    
525     ;
526     ; kernel_corrupt: Called if the kernel file does not seem healthy
527     ;
528     kernel_corrupt: mov si,err_notkernel
529     jmp abort_load
530    
531     ;
532     ; Get a key, observing ThisKbdTO and ThisTotalTO -- those are timeouts
533     ; which can be adjusted by the caller based on the corresponding
534     ; master variables; on return they're updated.
535     ;
536     ; This cheats. If we say "no timeout" we actually get a timeout of
537     ; 7.5 years.
538     ;
539     getchar_timeout:
540     call vgashowcursor
541 niro 1133 call reset_idle
542 niro 532
543     .loop:
544     push word [BIOS_timer]
545     call pollchar
546     jnz .got_char
547 niro 1133 call do_idle
548 niro 532 pop ax
549     cmp ax,[BIOS_timer] ; Has the timer advanced?
550     je .loop
551 niro 1133
552 niro 532 dec dword [ThisKbdTo]
553     jz .timeout
554     dec dword [ThisTotalTo]
555     jnz .loop
556    
557     .timeout:
558     ; Timeout!!!!
559     pop cx ; Discard return address
560     call vgahidecursor
561     mov si,Ontimeout ; Copy ontimeout command
562     mov di,command_line
563     mov cx,[OntimeoutLen] ; if we have one...
564     rep movsb
565     jmp command_done
566    
567     .got_char:
568     pop cx ; Discard
569     call getchar
570     call vgahidecursor
571     ret
572    
573     ;
574     ; This is it! We have a name (and location on the disk)... let's load
575     ; that sucker!! First we have to decide what kind of file this is; base
576     ; that decision on the file extension. The following extensions are
577     ; recognized; case insensitive:
578     ;
579 niro 1133 ; .com - COMBOOT image
580 niro 532 ; .cbt - COMBOOT image
581     ; .c32 - COM32 image
582     ; .bs - Boot sector
583     ; .0 - PXE bootstrap program (PXELINUX only)
584     ; .bin - Boot sector
585     ; .bss - Boot sector, but transfer over DOS superblock (SYSLINUX only)
586     ; .img - Floppy image (ISOLINUX only)
587     ;
588     ; Anything else is assumed to be a Linux kernel.
589     ;
590     section .bss
591     alignb 4
592     Kernel_EAX resd 1
593     Kernel_SI resw 1
594    
595     section .text
596     kernel_good_saved:
597     ; Alternate entry point for which the return from
598     ; searchdir is stored in memory. This is used for
599     ; COMBOOT function INT 22h, AX=0016h.
600     mov si,[Kernel_SI]
601     mov eax,[Kernel_EAX]
602    
603     kernel_good:
604 niro 1133 pushad
605     ;
606     ; Common initialization for all kernel types
607     ;
608     xor ax,ax
609     mov [InitRDPtr],ax
610     mov [QuietBoot],al
611     %if IS_PXELINUX
612     mov [KeepPXE],al
613     %endif
614    
615 niro 532 mov si,KernelName
616     mov di,KernelCName
617     call unmangle_name
618     sub di,KernelCName
619     mov [KernelCNameLen],di
620 niro 1133
621     ; Default memory limit, can be overridden by image loaders
622     mov eax,[HighMemRsvd]
623     mov [MyHighMemSize],eax
624    
625     popad
626    
627 niro 532 push di
628     push ax
629     mov di,KernelName+4*IS_PXELINUX
630     xor al,al
631     mov cx,FILENAME_MAX
632     repne scasb
633     jne .one_step
634     dec di
635     .one_step: mov ecx,[di-4] ; 4 bytes before end
636     pop ax
637     pop di
638    
639     ;
640 niro 1133 ; At this point, EAX contains the size of the kernel, SI contains
641     ; the file handle/cluster pointer, and ECX contains the extension (if any.)
642 niro 532 ;
643 niro 1133 movzx di,byte [KernelType]
644     add di,di
645     jmp [kerneltype_table+di]
646 niro 532
647 niro 1133 is_unknown_filetype:
648     or ecx,20202000h ; Force lower case (except dot)
649    
650 niro 532 cmp ecx,'.com'
651     je is_comboot_image
652     cmp ecx,'.cbt'
653     je is_comboot_image
654     cmp ecx,'.c32'
655     je is_com32_image
656     %if IS_ISOLINUX
657     cmp ecx,'.img'
658     je is_disk_image
659     %endif
660     cmp ecx,'.bss'
661     je is_bss_sector
662     cmp ecx,'.bin'
663     je is_bootsector
664     shr ecx,8
665     cmp ecx,'.bs'
666     je is_bootsector
667     shr ecx,8
668     cmp cx,'.0'
669     je is_bootsector
670 niro 1133
671 niro 532 ; Otherwise Linux kernel
672 niro 1133 jmp is_linux_kernel
673 niro 532
674 niro 1133 is_config_file:
675     pusha
676     mov si,KernelCName ; Save the config file name, for posterity
677     mov di,ConfigName
678     call strcpy
679     popa
680     call openfd
681     call reset_config
682     jmp load_config_file
683    
684     ; This is an image type we can't deal with
685     is_bad_image:
686     mov si,err_badimage
687     call writestr
688     jmp enter_command
689    
690     %if IS_SYSLINUX
691     ; ok
692     %else
693     is_bss_sector equ is_bad_image
694     %endif
695     %if IS_ISOLINUX
696     ; ok
697     %else
698     is_disk_image equ is_bad_image
699     %endif
700    
701     section .data
702     boot_prompt db 'boot: ', 0
703     wipe_char db BS, ' ', BS, 0
704     err_badimage db 'Invalid image type for this media type!', CR, LF, 0
705     err_notfound db 'Could not find kernel image: ',0
706     err_notkernel db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
707    
708    
709     alignz 2
710     kerneltype_table:
711     dw is_unknown_filetype ; VK_KERNEL
712     dw is_linux_kernel ; VK_LINUX
713     dw is_bootsector ; VK_BOOT
714     dw is_bss_sector ; VK_BSS
715     dw is_bootsector ; VK_PXE
716     dw is_disk_image ; VK_FDIMAGE
717     dw is_comboot_image ; VK_COMBOOT
718     dw is_com32_image ; VK_COM32
719     dw is_config_file ; VK_CONFIG
720    
721 niro 532 section .bss
722     alignb 4
723     ThisKbdTo resd 1 ; Temporary holder for KbdTimeout
724     ThisTotalTo resd 1 ; Temporary holder for TotalTimeout
725     KernelExtPtr resw 1 ; During search, final null pointer
726     CmdOptPtr resw 1 ; Pointer to first option on cmd line
727     KbdFlags resb 1 ; Check for keyboard escapes
728     FuncFlag resb 1 ; Escape sequences received from keyboard
729 niro 1133 KernelType resb 1 ; Kernel type, from vkernel, if known
730 niro 532
731     section .text
732 niro 1133 ;
733     ; Linux kernel loading code is common.
734     ;
735     %include "runkernel.inc"
736    
737     ;
738     ; COMBOOT-loading code
739     ;
740     %include "comboot.inc"
741     %include "com32.inc"
742     %include "cmdline.inc"
743    
744     ;
745     ; Boot sector loading code
746     ;
747     %include "bootsect.inc"
748    
749     ;
750     ; Abort loading code
751     ;
752     %include "abort.inc"
753    
754     ;
755     ; Hardware cleanup common code
756     ;
757     %include "cleanup.inc"