summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorhpa <hpa>2002-04-27 23:41:49 +0000
committerhpa <hpa>2002-04-27 23:41:49 +0000
commit7fb748081728cf625444cd7f37c96ae4435e06a6 (patch)
treee6a4fa02937168ed23b31f517743ee05611565ac
parentac0f6669a22e4805d4e2ecb4a9df5ca43c109af3 (diff)
downloadsyslinux-7fb748081728cf625444cd7f37c96ae4435e06a6.tar.gz
More factoring of common code
-rw-r--r--bcopy32.inc414
-rw-r--r--comboot.inc116
-rw-r--r--isolinux.asm1075
-rw-r--r--ldlinux.asm1083
-rw-r--r--loadhigh.inc98
-rw-r--r--pxelinux.asm1079
-rw-r--r--runkernel.inc614
7 files changed, 1278 insertions, 3201 deletions
diff --git a/bcopy32.inc b/bcopy32.inc
new file mode 100644
index 00000000..daa061e9
--- /dev/null
+++ b/bcopy32.inc
@@ -0,0 +1,414 @@
+;; $Id$
+;; -----------------------------------------------------------------------
+;;
+;; Copyright 1994-2002 H. Peter Anvin - All Rights Reserved
+;;
+;; This program is free software; you can redistribute it and/or modify
+;; it under the terms of the GNU General Public License as published by
+;; the Free Software Foundation, Inc., 53 Temple Place Ste 330,
+;; Bostom MA 02111-1307, USA; either version 2 of the License, or
+;; (at your option) any later version; incorporated herein by reference.
+;;
+;; -----------------------------------------------------------------------
+
+;;
+;; bcopy32.inc
+;;
+;; 32-bit bcopy routine for real mode
+;;
+
+;
+; 32-bit bcopy routine for real mode
+;
+; We enter protected mode, set up a flat 32-bit environment, run rep movsd
+; and then exit. IMPORTANT: This code assumes cs == 0.
+;
+; This code is probably excessively anal-retentive in its handling of
+; segments, but this stuff is painful enough as it is without having to rely
+; on everything happening "as it ought to."
+;
+; IMPORTANT: This code must be capable of operating when copied to the
+; trackbuf area (1000h). The routine bcopy_over_self handles this mode
+; of operation, including any necessary adjustments.
+;
+ align 4
+__bcopy_start:
+
+bcopy_gdt: dw bcopy_gdt_size-1 ; Null descriptor - contains GDT
+.adj1: dd bcopy_gdt ; pointer for LGDT instruction
+ dw 0
+ dd 0000ffffh ; Code segment, use16, readable,
+ dd 00009b00h ; present, dpl 0, cover 64K
+ dd 0000ffffh ; Data segment, use16, read/write,
+ dd 008f9300h ; present, dpl 0, cover all 4G
+ dd 0000ffffh ; Data segment, use16, read/write,
+ dd 00009300h ; present, dpl 0, cover 64K
+bcopy_gdt_size: equ $-bcopy_gdt
+
+bcopy: push eax
+ pushf ; Saves, among others, the IF flag
+ push gs
+ push fs
+ push ds
+ push es
+ mov [cs:SavedSSSP],sp
+ mov ax,ss
+ mov [cs:SavedSSSP+2],ax
+
+ cli
+ call enable_a20
+
+.adj2: o32 lgdt [cs:bcopy_gdt]
+ mov eax,cr0
+ or al,1
+ mov cr0,eax ; Enter protected mode
+ jmp 08h:.in_pm
+
+.in_pm: mov ax,10h ; Data segment selector
+ mov es,ax
+ mov ds,ax
+
+ mov al,18h ; "Real-mode-like" data segment
+ mov ss,ax
+ mov fs,ax
+ mov gs,ax
+
+ a32 rep movsd ; Do our business
+
+ mov es,ax ; Set to "real-mode-like"
+ mov ds,ax
+
+ mov eax,cr0
+ and al,~1
+ mov cr0,eax ; Disable protected mode
+.adj3: jmp 0:.in_rm
+
+.in_rm: ; Back in real mode
+ lss sp,[cs:SavedSSSP]
+ pop es
+ pop ds
+ pop fs
+ pop gs
+ call disable_a20
+
+ popf ; Re-enables interrupts
+ pop eax
+ ret
+
+;
+; Routines to enable and disable (yuck) A20. These routines are gathered
+; from tips from a couple of sources, including the Linux kernel and
+; http://www.x86.org/. The need for the delay to be as large as given here
+; is indicated by Donnie Barnes of RedHat, the problematic system being an
+; IBM ThinkPad 760EL.
+;
+; We typically toggle A20 twice for every 64K transferred.
+;
+%define io_delay call _io_delay
+%define IO_DELAY_PORT 80h ; Invalid port (we hope!)
+%define disable_wait 32 ; How long to wait for a disable
+
+%define A20_DUNNO 0 ; A20 type unknown
+%define A20_NONE 1 ; A20 always on?
+%define A20_BIOS 2 ; A20 BIOS enable
+%define A20_KBC 3 ; A20 through KBC
+%define A20_FAST 4 ; A20 through port 92h
+
+ align 2
+A20List dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
+A20DList dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
+a20_adjust_cnt equ ($-A20List)/2
+A20Type dw A20_DUNNO ; A20 type unknown
+
+slow_out: out dx, al ; Fall through
+
+_io_delay: out IO_DELAY_PORT,al
+ out IO_DELAY_PORT,al
+ ret
+
+enable_a20:
+ pushad
+ mov byte [cs:A20Tries],255 ; Times to try to make this work
+
+try_enable_a20:
+;
+; Flush the caches
+;
+; call try_wbinvd
+
+;
+; If the A20 type is known, jump straight to type
+;
+ mov bp,[cs:A20Type]
+ add bp,bp ; Convert to word offset
+.adj4: jmp word [cs:bp+A20List]
+
+;
+; First, see if we are on a system with no A20 gate
+;
+a20_dunno:
+a20_none:
+ mov byte [cs:A20Type], A20_NONE
+ call a20_test
+ jnz a20_done
+
+;
+; Next, try the BIOS (INT 15h AX=2401h)
+;
+a20_bios:
+ mov byte [cs:A20Type], A20_BIOS
+ mov ax,2401h
+ pushf ; Some BIOSes muck with IF
+ int 15h
+ popf
+
+ call a20_test
+ jnz a20_done
+
+;
+; Enable the keyboard controller A20 gate
+;
+a20_kbc:
+ mov dl, 1 ; Allow early exit
+ call empty_8042
+ jnz a20_done ; A20 live, no need to use KBC
+
+ mov byte [cs:A20Type], A20_KBC ; Starting KBC command sequence
+
+ mov al,0D1h ; Command write
+ out 064h, al
+ call empty_8042_uncond
+
+ mov al,0DFh ; A20 on
+ out 060h, al
+ call empty_8042_uncond
+
+ ; Verify that A20 actually is enabled. Do that by
+ ; observing a word in low memory and the same word in
+ ; the HMA until they are no longer coherent. Note that
+ ; we don't do the same check in the disable case, because
+ ; we don't want to *require* A20 masking (SYSLINUX should
+ ; work fine without it, if the BIOS does.)
+.kbc_wait: push cx
+ xor cx,cx
+.kbc_wait_loop:
+ call a20_test
+ jnz a20_done_pop
+ loop .kbc_wait_loop
+
+ pop cx
+;
+; Running out of options here. Final attempt: enable the "fast A20 gate"
+;
+a20_fast:
+ mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
+ in al, 092h
+ or al,02h
+ and al,~01h ; Don't accidentally reset the machine!
+ out 092h, al
+
+.fast_wait: push cx
+ xor cx,cx
+.fast_wait_loop:
+ call a20_test
+ jnz a20_done_pop
+ loop .fast_wait_loop
+
+ pop cx
+
+;
+; Oh bugger. A20 is not responding. Try frobbing it again; eventually give up
+; and report failure to the user.
+;
+
+
+ dec byte [cs:A20Tries]
+ jnz try_enable_a20
+
+ mov si, err_a20
+ jmp abort_load
+;
+; A20 unmasked, proceed...
+;
+a20_done_pop: pop cx
+a20_done: popad
+ ret
+
+;
+; This routine tests if A20 is enabled (ZF = 0). This routine
+; must not destroy any register contents.
+;
+a20_test:
+ push es
+ push cx
+ push ax
+ mov cx,0FFFFh ; HMA = segment 0FFFFh
+ mov es,cx
+ mov cx,32 ; Loop count
+ mov ax,[cs:A20Test]
+.a20_wait: inc ax
+ mov [cs:A20Test],ax
+ io_delay ; Serialize, and fix delay
+ cmp ax,[es:A20Test+10h]
+ loopz .a20_wait
+.a20_done: pop ax
+ pop cx
+ pop es
+ ret
+
+disable_a20:
+ pushad
+;
+; Flush the caches
+;
+; call try_wbinvd
+
+ mov bp,[cs:A20Type]
+ add bp,bp ; Convert to word offset
+.adj5: jmp word [cs:bp+A20DList]
+
+a20d_bios:
+ mov ax,2400h
+ pushf ; Some BIOSes muck with IF
+ int 15h
+ popf
+ jmp short a20d_snooze
+
+;
+; Disable the "fast A20 gate"
+;
+a20d_fast:
+ in al, 092h
+ and al,~03h
+ out 092h, al
+ jmp short a20d_snooze
+
+;
+; Disable the keyboard controller A20 gate
+;
+a20d_kbc:
+ call empty_8042_uncond
+ mov al,0D1h
+ out 064h, al ; Command write
+ call empty_8042_uncond
+ mov al,0DDh ; A20 off
+ out 060h, al
+ call empty_8042_uncond
+ ; Wait a bit for it to take effect
+a20d_snooze:
+ push cx
+ mov cx, disable_wait
+.delayloop: call a20_test
+ jz .disabled
+ loop .delayloop
+.disabled: pop cx
+a20d_dunno:
+a20d_none:
+ popad
+ ret
+
+;
+; Routine to empty the 8042 KBC controller. If dl != 0
+; then we will test A20 in the loop and exit if A20 is
+; suddenly enabled.
+;
+empty_8042_uncond:
+ xor dl,dl
+empty_8042:
+ call a20_test
+ jz .a20_on
+ and dl,dl
+ jnz .done
+.a20_on: io_delay
+ in al, 064h ; Status port
+ test al,1
+ jz .no_output
+ io_delay
+ in al, 060h ; Read input
+ jmp short empty_8042
+.no_output:
+ test al,2
+ jnz empty_8042
+ io_delay
+.done: ret
+
+;
+; WBINVD instruction; gets auto-eliminated on 386 CPUs
+;
+try_wbinvd:
+ wbinvd
+ ret
+
+;
+; bcopy_over_self:
+;
+; This routine is used to copy large blocks of code on top of
+; conventional memory (to 0:7c00). We therefore have to move
+; necessary code into the trackbuf area before doing the copy,
+; and do adjustments to anything except BSS area references.
+;
+; After performing the copy, this routine resets the stack and
+; jumps to 0:7c00.
+;
+; Inputs:
+; ESI, EDI, ECX - same as bcopy
+; EDX - edx on invocation
+; EAX - esi on invocation
+;
+%define ADJUST (__bcopy_start - trackbuf)
+
+ align 2
+adjlist dw bcopy_gdt.adj1 - ADJUST
+ dw bcopy.adj2 + 5 - ADJUST
+ dw bcopy.adj3 + 1 - ADJUST
+ dw try_enable_a20.adj4 + 3 - ADJUST
+ dw disable_a20.adj5 + 3 - ADJUST
+adjlist_cnt equ ($-adjlist)/2
+
+bcopy_over_self:
+ cli
+ cld
+ xor bx,bx
+ mov ds,bx
+ mov es,bx
+ mov ss,bx
+ mov sp,7c00h
+
+ push eax
+ push edx
+ push esi
+ push edi
+ push ecx
+
+ mov si,__bcopy_start
+ mov di,trackbuf
+ mov cx,(__bcopy_end - __bcopy_start + 3) >> 2
+ rep movsd
+
+ mov si,A20List - ADJUST
+ mov cx,a20_adjust_cnt
+.adjust1:
+ sub word [si], ADJUST
+ inc si
+ inc si
+ loop .adjust1
+
+ mov si, adjlist
+ mov cx, adjlist_cnt
+.adjust2:
+ lodsw
+ xchg di,ax
+ sub word [di], ADJUST
+ loop .adjust2
+
+ jmp .next-ADJUST
+.next:
+ pop ecx
+ pop edi
+ pop esi
+ call bcopy
+
+ pop edx
+ pop esi
+ jmp 0:7c00h
+__bcopy_end:
diff --git a/comboot.inc b/comboot.inc
new file mode 100644
index 00000000..db199145
--- /dev/null
+++ b/comboot.inc
@@ -0,0 +1,116 @@
+;; $Id$
+;; -----------------------------------------------------------------------
+;;
+;; Copyright 1994-2002 H. Peter Anvin - All Rights Reserved
+;;
+;; This program is free software; you can redistribute it and/or modify
+;; it under the terms of the GNU General Public License as published by
+;; the Free Software Foundation, Inc., 53 Temple Place Ste 330,
+;; Bostom MA 02111-1307, USA; either version 2 of the License, or
+;; (at your option) any later version; incorporated herein by reference.
+;;
+;; -----------------------------------------------------------------------
+
+;;
+;; comboot.inc
+;;
+;; Common code for running a COMBOOT image
+;;
+
+;
+; Load a COMBOOT image. A COMBOOT image is basically a DOS .COM file,
+; except that it may, of course, not contain any DOS system calls. We
+; do, however, allow the execution of INT 20h to return to SYSLINUX.
+;
+is_comboot_image:
+ and dx,dx
+ jnz near comboot_too_large
+ cmp ax,0ff00h ; Max size in bytes
+ jae comboot_too_large
+
+ ;
+ ; Set up the DOS vectors in the IVT (INT 20h-3fh)
+ ;
+ mov dword [4*0x20],comboot_return ; INT 20h vector
+ mov eax,comboot_bogus
+ mov di,4*0x21
+ mov cx,31 ; All remaining DOS vectors
+ rep stosd
+
+ mov cx,comboot_seg
+ mov es,cx
+
+ mov bx,100h ; Load at <seg>:0100h
+
+ mov cx,[ClustPerMoby] ; Absolute maximum # of clusters
+ call getfssec
+
+ xor di,di
+ mov cx,64 ; 256 bytes (size of PSP)
+ xor eax,eax ; Clear PSP
+ rep stosd
+
+ mov word [es:0], 020CDh ; INT 20h instruction
+ ; First non-free paragraph
+ mov word [es:02h], comboot_seg+1000h
+
+ ; Copy the command line from high memory
+ mov cx,125 ; Max cmdline len (minus space and CR)
+ mov si,[CmdOptPtr]
+ mov di,081h ; Offset in PSP for command line
+ mov al,' ' ; DOS command lines begin with a space
+ stosb
+
+comboot_cmd_cp: lodsb
+ and al,al
+ jz comboot_end_cmd
+ stosb
+ loop comboot_cmd_cp
+comboot_end_cmd: mov al,0Dh ; CR after last character
+ stosb
+ mov al,126 ; Include space but not CR
+ sub al,cl
+ mov [es:80h], al ; Store command line length
+
+ mov [SavedSSSP],sp
+ mov ax,ss ; Save away SS:SP
+ mov [SavedSSSP+2],ax
+
+ call vgaclearmode ; Reset video
+
+ mov ax,es
+ mov ds,ax
+ mov ss,ax
+ xor sp,sp
+ push word 0 ; Return to address 0 -> exit
+
+ jmp comboot_seg:100h ; Run it
+
+; Looks like a COMBOOT image but too large
+comboot_too_large:
+ mov si,err_comlarge
+ call cwritestr
+cb_enter: jmp enter_command
+
+; Proper return vector
+comboot_return: cli ; Don't trust anyone
+ lss sp,[cs:SavedSSSP]
+ mov ds,ax
+ mov es,ax
+ sti
+ cld
+ jmp short cb_enter
+
+; Attempted to execute DOS system call
+comboot_bogus: cli ; Don't trust anyone
+ lss sp,[cs:SavedSSSP]
+ mov ds,ax
+ mov es,ax
+ sti
+ cld
+ mov si,KernelCName
+ call cwritestr
+ mov si,err_notdos
+ call cwritestr
+ jmp short cb_enter
+
diff --git a/isolinux.asm b/isolinux.asm
index 48f8d25a..f560e117 100644
--- a/isolinux.asm
+++ b/isolinux.asm
@@ -33,8 +33,9 @@ my_id equ isolinux_id
max_cmd_len equ 255 ; Must be odd; 255 is the kernel limit
FILENAME_MAX_LG2 equ 8 ; log2(Max filename size Including final null)
FILENAME_MAX equ (1 << FILENAME_MAX_LG2)
+NULLFILE equ 0 ; Zero byte == null file name
HIGHMEM_MAX equ 037FFFFFFh ; DEFAULT highest address for an initrd
-HIGHMEM_SLOP equ 128*1024 ; Avoid this much memory near the top
+%assign HIGHMEM_SLOP 128*1024 ; Avoid this much memory near the top
DEFAULT_BAUD equ 9600 ; Default baud rate for serial port
BAUD_DIVISOR equ 115200 ; Serial port parameter
MAX_OPEN_LG2 equ 6 ; log2(Max number of open files)
@@ -153,9 +154,9 @@ HiLoadAddr resd 1 ; Address pointer for high load loop
HighMemSize resd 1 ; End of memory pointer (bytes)
RamdiskMax resd 1 ; Highest address for a ramdisk
KernelSize resd 1 ; Size of kernel (bytes)
+SavedSSSP resd 1 ; Our SS:SP while running a COMBOOT image
RootDir resb dir_t_size ; Root directory
CurDir resb dir_t_size ; Current directory
-SavedSSSP resd 1 ; Our SS:SP while running a COMBOOT image
KernelClust resd 1 ; Kernel size in clusters
InitStack resd 1 ; Initial stack pointer (SS:SP)
FirstSecSum resd 1 ; Checksum of bytes 64-2048
@@ -1238,655 +1239,16 @@ kernel_good:
cmp ecx,'.bs'
je near is_bootsector
; Otherwise Linux kernel
-;
-; A Linux kernel consists of three parts: boot sector, setup code, and
-; kernel code. The boot sector is never executed when using an external
-; booting utility, but it contains some status bytes that are necessary.
-;
-; First check that our kernel is at least 1K and less than 8M (if it is
-; more than 8M, we need to change the logic for loading it anyway...)
-;
-; We used to require the kernel to be 64K or larger, but it has gotten
-; popular to use the Linux kernel format for other things, which may
-; not be so large.
-;
-is_linux_kernel:
- cmp dx,80h ; 8 megs
- ja kernel_corrupt
- and dx,dx
- jnz kernel_sane
- cmp ax,1024 ; Bootsect + 1 setup sect
- jb near kernel_corrupt
-kernel_sane: push ax
- push dx
- push si
- mov si,loading_msg
- call cwritestr
-;
-; Now start transferring the kernel
-;
- push word real_mode_seg
- pop es
-
- movzx eax,ax ; Fix this by using a 32-bit
- shl edx,16 ; register for the kernel size
- or eax,edx
- mov [KernelSize],eax
- xor edx,edx
- div dword [ClustSize] ; # of clusters total
- ; Round up...
- add edx,byte -1 ; Sets CF if EDX >= 1
- adc eax,byte 0 ; Add 1 to EAX if CF set
- mov [KernelClust],eax
-
-;
-; Now, if we transfer these straight, we'll hit 64K boundaries. Hence we
-; have to see if we're loading more than 64K, and if so, load it step by
-; step.
-;
-
-;
-; Start by loading the bootsector/setup code, to see if we need to
-; do something funky. It should fit in the first 32K (loading 64K won't
-; work since we might have funny stuff up near the end of memory).
-; If we have larger than 32K clusters, yes, we're hosed.
-;
- call abort_check ; Check for abort key
- mov ecx,[ClustPerMoby]
- shr ecx,1 ; Half a moby
- cmp ecx,[KernelClust]
- jna .normalkernel
- mov ecx,[KernelClust]
-.normalkernel:
- sub [KernelClust],ecx
- xor bx,bx
- pop si ; Cluster pointer on stack
- call getfssec
- cmp word [es:bs_bootsign],0AA55h
- jne near kernel_corrupt ; Boot sec signature missing
-;
-; Get the BIOS' idea of what the size of high memory is.
-;
- push si ; Save our cluster pointer!
-;
-; First, try INT 15:E820 (get BIOS memory map)
-;
-get_e820:
- push es
- xor ebx,ebx ; Start with first record
- mov es,bx ; Need ES = DS = 0 for now
- jmp short .do_e820 ; Skip "at end" check first time!
-.int_loop: and ebx,ebx ; If we're back at beginning...
- jz no_e820 ; ... bail; nothing found
-.do_e820: mov eax,0000E820h
- mov edx,534D4150h ; "SMAP" backwards
- mov ecx,20
- mov di,E820Buf
- int 15h
- jc no_e820
- cmp eax,534D4150h
- jne no_e820
-;
-; Look for a memory block starting at <= 1 MB and continuing upward
-;
- cmp dword [E820Buf+4], byte 0
- ja .int_loop ; Start >= 4 GB?
- mov edx, (1 << 20)
- sub edx, [E820Buf]
- jb .int_loop ; Start >= 1 MB?
- mov eax, 0FFFFFFFFh
- cmp dword [E820Buf+12], byte 0
- ja .huge ; Size >= 4 GB
- mov eax, [E820Buf+8]
-.huge: sub eax, edx ; Adjust size to start at 1 MB
- jbe .int_loop ; Completely below 1 MB?
-
- ; Now EAX contains the size of memory 1 MB...up
- cmp dword [E820Buf+16], byte 1
- jne near err_nohighmem ; High memory isn't usable memory!!!!
-
- ; We're good!
- pop es
- jmp short got_highmem_add1mb ; Still need to add low 1 MB
-
-;
-; INT 15:E820 failed. Try INT 15:E801.
-;
-no_e820: pop es
-
- mov ax,0e801h ; Query high memory (semi-recent)
- int 15h
- jc no_e801
- cmp ax,3c00h
- ja no_e801 ; > 3C00h something's wrong with this call
- jb e801_hole ; If memory hole we can only use low part
-
- mov ax,bx
- shl eax,16 ; 64K chunks
- add eax,(16 << 20) ; Add first 16M
- jmp short got_highmem
-
-;
-; INT 15:E801 failed. Try INT 15:88.
-;
-no_e801:
- mov ah,88h ; Query high memory (oldest)
- int 15h
- cmp ax,14*1024 ; Don't trust memory >15M
- jna e801_hole
- mov ax,14*1024
-e801_hole:
- and eax,0ffffh
- shl eax,10 ; Convert from kilobytes
-got_highmem_add1mb:
- add eax,(1 << 20) ; First megabyte
-got_highmem:
- sub eax,HIGHMEM_SLOP
- mov [HighMemSize],eax
-
-;
-; Construct the command line (append options have already been copied)
-;
-construct_cmdline:
- mov di,[CmdLinePtr]
- mov si,boot_image ; BOOT_IMAGE=
- mov cx,boot_image_len
- rep movsb
- mov si,KernelCName ; Unmangled kernel name
- mov cx,[KernelCNameLen]
- rep movsb
- mov al,' ' ; Space
- stosb
-
-.noipappend:
- mov si,[CmdOptPtr] ; Options from user input
- mov cx,(kern_cmd_len+3) >> 2
- rep movsd
-;
-; Scan through the command line for anything that looks like we might be
-; interested in. The original version of this code automatically assumed
-; the first option was BOOT_IMAGE=, but that is no longer certain.
-;
- mov si,cmd_line_here
- mov byte [initrd_flag],0
- push es ; Set DS <- real_mode_seg
- pop ds
-get_next_opt: lodsb
- and al,al
- jz near cmdline_end
- cmp al,' '
- jbe get_next_opt
- dec si
- mov eax,[si]
- cmp eax,'vga='
- je is_vga_cmd
- cmp eax,'mem='
- je is_mem_cmd
- push es ; Save ES -> real_mode_seg
- push cs
- pop es ; Set ES <- normal DS
- mov di,initrd_cmd
- mov cx,initrd_cmd_len
- repe cmpsb
- jne not_initrd
- mov di,InitRD
- push si ; mangle_dir mangles si
- call mangle_name ; Mangle ramdisk name
- pop si
- cmp byte [es:InitRD],0 ; Null filename?
- seta byte [es:initrd_flag] ; Set flag if not
-not_initrd: pop es ; Restore ES -> real_mode_seg
-skip_this_opt: lodsb ; Load from command line
- cmp al,' '
- ja skip_this_opt
- dec si
- jmp short get_next_opt
-is_vga_cmd:
- add si,byte 4
- mov eax,[si]
- mov bx,-1
- cmp eax, 'norm' ; vga=normal
- je vc0
- and eax,0ffffffh ; 3 bytes
- mov bx,-2
- cmp eax, 'ext' ; vga=ext
- je vc0
- mov bx,-3
- cmp eax, 'ask' ; vga=ask
- je vc0
- call parseint ; vga=<number>
- jc skip_this_opt ; Not an integer
-vc0: mov [bs_vidmode],bx ; Set video mode
- jmp short skip_this_opt
-is_mem_cmd:
- add si,byte 4
- call parseint
- jc skip_this_opt ; Not an integer
- sub ebx,HIGHMEM_SLOP
- mov [cs:HighMemSize],ebx
- jmp short skip_this_opt
-cmdline_end:
- push cs ; Restore standard DS
- pop ds
- sub si,cmd_line_here
- mov [CmdLineLen],si ; Length including final null
-;
-; Now check if we have a large kernel, which needs to be loaded high
-;
- mov dword [RamdiskMax], HIGHMEM_MAX ; Default initrd limit
- cmp dword [es:su_header],HEADER_ID ; New setup code ID
- jne near old_kernel ; Old kernel, load low
- cmp word [es:su_version],0200h ; Setup code version 2.0
- jb near old_kernel ; Old kernel, load low
- cmp word [es:su_version],0201h ; Version 2.01+?
- jb new_kernel ; If 2.00, skip this step
- mov word [es:su_heapend],linux_stack ; Set up the heap
- or byte [es:su_loadflags],80h ; Let the kernel know we care
- cmp word [es:su_version],0203h ; Version 2.03+?
- jb new_kernel ; Not 2.03+
- mov eax,[es:su_ramdisk_max]
- mov [RamdiskMax],eax ; Set the ramdisk limit
-
-;
-; We definitely have a new-style kernel. Let the kernel know who we are,
-; and that we are clueful
-;
-new_kernel:
- mov byte [es:su_loader],my_id ; Show some ID
- movzx ax,byte [es:bs_setupsecs] ; Variable # of setup sectors
- mov [SetupSecs],ax
-;
-; About to load the kernel. This is a modern kernel, so use the boot flags
-; we were provided.
-;
- mov al,[es:su_loadflags]
- mov [LoadFlags],al
-;
-; Load the kernel. We always load it at 100000h even if we're supposed to
-; load it "low"; for a "low" load we copy it down to low memory right before
-; jumping to it.
-;
-read_kernel:
- mov si,KernelCName ; Print kernel name part of
- call cwritestr ; "Loading" message
- mov si,dotdot_msg ; Print dots
- call cwritestr
-
- mov eax,[HighMemSize]
- sub eax,100000h ; Load address
- cmp eax,[KernelSize]
- jb near no_high_mem ; Not enough high memory
-;
-; Move the stuff beyond the setup code to high memory at 100000h
-;
- movzx esi,word [SetupSecs] ; Setup sectors
- inc esi ; plus 1 boot sector
- shl esi,9 ; Convert to bytes
- mov ecx,8000h ; 32K
- sub ecx,esi ; Number of bytes to copy
- push ecx
- shr ecx,2 ; Convert to dwords
- add esi,(real_mode_seg << 4) ; Pointer to source
- mov edi,100000h ; Copy to address 100000h
- call bcopy ; Transfer to high memory
-
- ; On exit EDI -> where to load the rest
-
- mov si,dot_msg ; Progress report
- call cwritestr
- call abort_check
-
- pop ecx ; Number of bytes in the initial portion
- pop si ; Restore file handle/cluster pointer
- mov eax,[KernelSize]
- sub eax,ecx ; Amount of kernel left over
- jbe high_load_done ; Zero left (tiny kernel)
-
- call load_high ; Copy the file
-
-high_load_done:
- mov ax,real_mode_seg ; Set to real mode seg
- mov es,ax
-
- mov si,dot_msg
- call cwritestr
-
-;
-; Now see if we have an initial RAMdisk; if so, do requisite computation
-; We know we have a new kernel; the old_kernel code already will have objected
-; if we tried to load initrd using an old kernel
-;
-load_initrd:
- test byte [initrd_flag],1
- jz near nk_noinitrd
- push es ; ES->real_mode_seg
- push ds
- pop es ; We need ES==DS
- mov si,InitRD
- mov di,InitRDCName
- call unmangle_name ; Create human-readable name
- sub di,InitRDCName
- mov [InitRDCNameLen],di
- mov di,InitRD
- call searchdir ; Look for it in directory
- pop es
- jz initrd_notthere
- mov [es:su_ramdisklen1],ax ; Ram disk length
- mov [es:su_ramdisklen2],dx
- mov edx,[HighMemSize] ; End of memory
- dec edx
- mov eax,[RamdiskMax] ; Highest address allowed by kernel
- cmp edx,eax
- jna memsize_ok
- mov edx,eax ; Adjust to fit inside limit
-memsize_ok:
- inc edx
- xor dx,dx ; Round down to 64K boundary
- sub edx,[es:su_ramdisklen] ; Subtract size of ramdisk
- xor dx,dx ; Round down to 64K boundary
- mov [es:su_ramdiskat],edx ; Load address
- call loadinitrd ; Load initial ramdisk
- jmp short initrd_end
-
-initrd_notthere:
- mov si,err_noinitrd
- call cwritestr
- mov si,InitRDCName
- call cwritestr
- mov si,crlf_msg
- jmp abort_load
-
-no_high_mem: mov si,err_nohighmem ; Error routine
- jmp abort_load
-
-initrd_end:
-nk_noinitrd:
-;
-; Abandon hope, ye that enter here! We do no longer permit aborts.
-;
- call abort_check ; Last chance!!
-
- mov si,ready_msg
- call cwritestr
-
- call vgaclearmode ; We can't trust ourselves after this
-
- cli
- xor ax,ax
- mov ss,ax
- mov sp,7C00h ; Set up a more normal stack
-
-;
-; Now, if we were supposed to load "low", copy the kernel down to 10000h
-; and the real mode stuff to 90000h. We assume that all bzImage kernels are
-; capable of starting their setup from a different address.
-;
- mov ax,real_mode_seg
- mov fs,ax
-
-;
-; Copy command line. Unfortunately, the kernel boot protocol requires
-; the command line to exist in the 9xxxxh range even if the rest of the
-; setup doesn't.
-;
- cli ; In case of hooked interrupts
- test byte [LoadFlags],LOAD_HIGH
- jz need_high_cmdline
- cmp word [fs:su_version],0202h ; Support new cmdline protocol?
- jb need_high_cmdline
- ; New cmdline protocol
- ; Store 32-bit (flat) pointer to command line
- mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4) + cmd_line_here
- jmp short in_proper_place
-
-need_high_cmdline:
-;
-; Copy command line up to 90000h
-;
- mov ax,9000h
- mov es,ax
- mov si,cmd_line_here
- mov di,si
- mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic
- mov [fs:kern_cmd_offset],di ; Store pointer
-
- mov cx,[CmdLineLen]
- add cx,byte 3
- shr cx,2 ; Convert to dwords
- fs rep movsd
-
- push fs
- pop es
-
- test byte [LoadFlags],LOAD_HIGH
- jnz in_proper_place ; If high load, we're done
;
-; Loading low; we can't assume it's safe to run in place.
-;
-; Copy real_mode stuff up to 90000h
-;
- mov ax,9000h
- mov es,ax
- mov cx,[SetupSecs]
- inc cx ; Setup + boot sector
- shl cx,7 ; Sectors -> dwords
- xor si,si
- xor di,di
- fs rep movsd ; Copy setup + boot sector
-;
-; Some kernels in the 1.2 ballpark but pre-bzImage have more than 4
-; setup sectors, but the boot protocol had not yet been defined. They
-; rely on a signature to figure out if they need to copy stuff from
-; the "protected mode" kernel area. Unfortunately, we used that area
-; as a transfer buffer, so it's going to find the signature there.
-; Hence, zero the low 32K beyond the setup area.
-;
- mov di,[SetupSecs]
- inc di ; Setup + boot sector
- mov cx,32768/512 ; Sectors/32K
- sub cx,di ; Remaining sectors
- shl di,9 ; Sectors -> bytes
- shl cx,7 ; Sectors -> dwords
- xor eax,eax
- rep stosd ; Clear region
-;
-; Copy the kernel down to the "low" location
-;
- mov ecx,[KernelSize]
- add ecx,3 ; Round upwards
- shr ecx,2 ; Bytes -> dwords
- mov esi,100000h
- mov edi,10000h
- call bcopy
-
-;
-; Now everything is where it needs to be...
-;
-; When we get here, es points to the final segment, either
-; 9000h or real_mode_seg
-;
-in_proper_place:
-
-;
-; If the default root device is set to FLOPPY (0000h), change to
-; /dev/fd0 (0200h)
-;
- cmp word [es:bs_rootdev],byte 0
- jne root_not_floppy
- mov word [es:bs_rootdev],0200h
-root_not_floppy:
-;
-; Copy the disk table to high memory, then re-initialize the floppy
-; controller
-;
-; This needs to be moved before the copy
-;
-%if 0
- push ds
- push bx
- lds si,[fdctab]
- mov di,linux_fdctab
- mov cx,3 ; 12 bytes
- push di
- rep movsd
- pop di
- mov [fdctab1],di ; Save new floppy tab pos
- mov [fdctab2],es
- xor ax,ax
- xor dx,dx
- int 13h
- pop bx
- pop ds
-%endif
-;
-; Linux wants the floppy motor shut off before starting the kernel,
-; at least bootsect.S seems to imply so
-;
-kill_motor:
- mov dx,03F2h
- xor al,al
- call slow_out
-;
-; If we're debugging, wait for a keypress so we can read any debug messages
-;
-%ifdef debug
- xor ax,ax
- int 16h
-%endif
-;
-; Set up segment registers and the Linux real-mode stack
-; Note: es == the real mode segment
-;
- cli
- mov bx,es
- mov ds,bx
- mov fs,bx
- mov gs,bx
- mov ss,bx
- mov sp,linux_stack
-;
-; We're done... now RUN THAT KERNEL!!!!
-; Setup segment == real mode segment + 020h; we need to jump to offset
-; zero in the real mode segment.
+; Linux kernel loading code is common.
;
- add bx,020h
- push bx
- push word 0h
- retf
+%include "runkernel.inc"
;
-; Load an older kernel. Older kernels always have 4 setup sectors, can't have
-; initrd, and are always loaded low.
+; COMBOOT-loading code
;
-old_kernel:
- test byte [initrd_flag],1 ; Old kernel can't have initrd
- jz load_old_kernel
- mov si,err_oldkernel
- jmp abort_load
-load_old_kernel:
- mov word [SetupSecs],4 ; Always 4 setup sectors
- mov byte [LoadFlags],0 ; Always low
- jmp read_kernel
-
-;
-; Load a COMBOOT image. A COMBOOT image is basically a DOS .COM file,
-; except that it may, of course, not contain any DOS system calls. We
-; do, however, allow the execution of INT 20h to return to SYSLINUX.
-;
-is_comboot_image:
- and dx,dx
- jnz near comboot_too_large
- cmp ax,0ff00h ; Max size in bytes
- jae comboot_too_large
-
- ;
- ; Set up the DOS vectors in the IVT (INT 20h-3fh)
- ;
- mov dword [4*0x20],comboot_return ; INT 20h vector
- mov eax,comboot_bogus
- mov di,4*0x21
- mov cx,31 ; All remaining DOS vectors
- rep stosd
-
- mov cx,comboot_seg
- mov es,cx
-
- mov bx,100h ; Load at <seg>:0100h
-
- mov cx,[ClustPerMoby] ; Absolute maximum # of clusters
- call getfssec
-
- xor di,di
- mov cx,64 ; 256 bytes (size of PSP)
- xor eax,eax ; Clear PSP
- rep stosd
-
- mov word [es:0], 020CDh ; INT 20h instruction
- ; First non-free paragraph
- mov word [es:02h], comboot_seg+1000h
-
- ; Copy the command line from high memory
- mov cx,125 ; Max cmdline len (minus space and CR)
- mov si,[CmdOptPtr]
- mov di,081h ; Offset in PSP for command line
- mov al,' ' ; DOS command lines begin with a space
- stosb
-
-comboot_cmd_cp: lodsb
- and al,al
- jz comboot_end_cmd
- stosb
- loop comboot_cmd_cp
-comboot_end_cmd: mov al,0Dh ; CR after last character
- stosb
- mov al,126 ; Include space but not CR
- sub al,cl
- mov [es:80h], al ; Store command line length
-
- mov [SavedSSSP],sp
- mov ax,ss ; Save away SS:SP
- mov [SavedSSSP+2],ax
-
- call vgaclearmode ; Reset video
-
- mov ax,es
- mov ds,ax
- mov ss,ax
- xor sp,sp
- push word 0 ; Return to address 0 -> exit
-
- jmp comboot_seg:100h ; Run it
-
-; Looks like a COMBOOT image but too large
-comboot_too_large:
- mov si,err_comlarge
- call cwritestr
-cb_enter: jmp enter_command
-
-; Proper return vector
-comboot_return: cli ; Don't trust anyone
- xor ax,ax
- mov ds,ax
- mov es,ax
- lss sp,[SavedSSSP]
- sti
- cld
- jmp short cb_enter
-
-; Attempted to execute DOS system call
-comboot_bogus: cli ; Don't trust anyone
- xor ax,ax
- mov ds,ax
- mov es,ax
- lss sp,[SavedSSSP]
- sti
- cld
- mov si,KernelCName
- call cwritestr
- mov si,err_notdos
- call cwritestr
- jmp short cb_enter
+%include "comboot.inc"
;
; Load a boot sector
@@ -2068,424 +1430,6 @@ local_boot:
jmp kaboom ; If we returned, oh boy...
;
-; 32-bit bcopy routine for real mode
-;
-; We enter protected mode, set up a flat 32-bit environment, run rep movsd
-; and then exit. IMPORTANT: This code assumes cs == 0.
-;
-; This code is probably excessively anal-retentive in its handling of
-; segments, but this stuff is painful enough as it is without having to rely
-; on everything happening "as it ought to."
-;
- align 4
-bcopy_gdt: dw bcopy_gdt_size-1 ; Null descriptor - contains GDT
- dd bcopy_gdt ; pointer for LGDT instruction
- dw 0
- dd 0000ffffh ; Code segment, use16, readable,
- dd 00009b00h ; present, dpl 0, cover 64K
- dd 0000ffffh ; Data segment, use16, read/write,
- dd 008f9300h ; present, dpl 0, cover all 4G
- dd 0000ffffh ; Data segment, use16, read/write,
- dd 00009300h ; present, dpl 0, cover 64K
-bcopy_gdt_size: equ $-bcopy_gdt
-
-bcopy: push eax
- pushf ; Saves, among others, the IF flag
- push gs
- push fs
- push ds
- push es
- mov [cs:SavedSSSP],sp
- mov ax,ss
- mov [cs:SavedSSSP+2],ax
-
- cli
- call enable_a20
-
- o32 lgdt [cs:bcopy_gdt]
- mov eax,cr0
- or al,1
- mov cr0,eax ; Enter protected mode
- jmp 08h:.in_pm
-
-.in_pm: mov ax,10h ; Data segment selector
- mov es,ax
- mov ds,ax
-
- mov al,18h ; "Real-mode-like" data segment
- mov ss,ax
- mov fs,ax
- mov gs,ax
-
- a32 rep movsd ; Do our business
-
- mov es,ax ; Set to "real-mode-like"
- mov ds,ax
-
- mov eax,cr0
- and al,~1
- mov cr0,eax ; Disable protected mode
- jmp 0:.in_rm
-
-.in_rm: ; Back in real mode
- lss sp,[cs:SavedSSSP]
- pop es
- pop ds
- pop fs
- pop gs
- call disable_a20
-
- popf ; Re-enables interrupts
- pop eax
- ret
-
-;
-; Routines to enable and disable (yuck) A20. These routines are gathered
-; from tips from a couple of sources, including the Linux kernel and
-; http://www.x86.org/. The need for the delay to be as large as given here
-; is indicated by Donnie Barnes of RedHat, the problematic system being an
-; IBM ThinkPad 760EL.
-;
-; We typically toggle A20 twice for every 64K transferred.
-;
-%define io_delay call _io_delay
-%define IO_DELAY_PORT 80h ; Invalid port (we hope!)
-%define disable_wait 32 ; How long to wait for a disable
-
-%define A20_DUNNO 0 ; A20 type unknown
-%define A20_NONE 1 ; A20 always on?
-%define A20_BIOS 2 ; A20 BIOS enable
-%define A20_KBC 3 ; A20 through KBC
-%define A20_FAST 4 ; A20 through port 92h
-
-slow_out: out dx, al ; Fall through
-
-_io_delay: out IO_DELAY_PORT,al
- out IO_DELAY_PORT,al
- ret
-
-enable_a20:
- pushad
- mov byte [cs:A20Tries],255 ; Times to try to make this work
-
-try_enable_a20:
-;
-; Flush the caches
-;
-; call try_wbinvd
-
-;
-; If the A20 type is known, jump straight to type
-;
- mov bp,[cs:A20Type]
- add bp,bp ; Convert to word offset
- jmp word [cs:bp+A20List]
-
-;
-; First, see if we are on a system with no A20 gate
-;
-a20_dunno:
-a20_none:
- mov byte [cs:A20Type], A20_NONE
- call a20_test
- jnz a20_done
-
-;
-; Next, try the BIOS (INT 15h AX=2401h)
-;
-a20_bios:
- mov byte [cs:A20Type], A20_BIOS
- mov ax,2401h
- pushf ; Some BIOSes muck with IF
- int 15h
- popf
-
- call a20_test
- jnz a20_done
-
-;
-; Enable the keyboard controller A20 gate
-;
-a20_kbc:
- mov dl, 1 ; Allow early exit
- call empty_8042
- jnz a20_done ; A20 live, no need to use KBC
-
- mov byte [cs:A20Type], A20_KBC ; Starting KBC command sequence
-
- mov al,0D1h ; Command write
- out 064h, al
- call empty_8042_uncond
-
- mov al,0DFh ; A20 on
- out 060h, al
- call empty_8042_uncond
-
- ; Verify that A20 actually is enabled. Do that by
- ; observing a word in low memory and the same word in
- ; the HMA until they are no longer coherent. Note that
- ; we don't do the same check in the disable case, because
- ; we don't want to *require* A20 masking (SYSLINUX should
- ; work fine without it, if the BIOS does.)
-.kbc_wait: push cx
- xor cx,cx
-.kbc_wait_loop:
- call a20_test
- jnz a20_done_pop
- loop .kbc_wait_loop
-
- pop cx
-;
-; Running out of options here. Final attempt: enable the "fast A20 gate"
-;
-a20_fast:
- mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
- in al, 092h
- or al,02h
- and al,~01h ; Don't accidentally reset the machine!
- out 092h, al
-
-.fast_wait: push cx
- xor cx,cx
-.fast_wait_loop:
- call a20_test
- jnz a20_done_pop
- loop .fast_wait_loop
-
- pop cx
-
-;
-; Oh bugger. A20 is not responding. Try frobbing it again; eventually give up
-; and report failure to the user.
-;
-
-
- dec byte [cs:A20Tries]
- jnz try_enable_a20
-
- mov si, err_a20
- jmp abort_load
-;
-; A20 unmasked, proceed...
-;
-a20_done_pop: pop cx
-a20_done: popad
- ret
-
-;
-; This routine tests if A20 is enabled (ZF = 0). This routine
-; must not destroy any register contents.
-;
-a20_test:
- push es
- push cx
- push ax
- mov cx,0FFFFh ; HMA = segment 0FFFFh
- mov es,cx
- mov cx,32 ; Loop count
- mov ax,[cs:A20Test]
-.a20_wait: inc ax
- mov [cs:A20Test],ax
- io_delay ; Serialize, and fix delay
- cmp ax,[es:A20Test+10h]
- loopz .a20_wait
-.a20_done: pop ax
- pop cx
- pop es
- ret
-
-disable_a20:
- pushad
-;
-; Flush the caches
-;
-; call try_wbinvd
-
- mov bp,[cs:A20Type]
- add bp,bp ; Convert to word offset
- jmp word [cs:bp+A20DList]
-
-a20d_bios:
- mov ax,2400h
- pushf ; Some BIOSes muck with IF
- int 15h
- popf
- jmp short a20d_snooze
-
-;
-; Disable the "fast A20 gate"
-;
-a20d_fast:
- in al, 092h
- and al,~03h
- out 092h, al
- jmp short a20d_snooze
-
-;
-; Disable the keyboard controller A20 gate
-;
-a20d_kbc:
- call empty_8042_uncond
- mov al,0D1h
- out 064h, al ; Command write
- call empty_8042_uncond
- mov al,0DDh ; A20 off
- out 060h, al
- call empty_8042_uncond
- ; Wait a bit for it to take effect
-a20d_snooze:
- push cx
- mov cx, disable_wait
-.delayloop: call a20_test
- jz .disabled
- loop .delayloop
-.disabled: pop cx
-a20d_dunno:
-a20d_none:
- popad
- ret
-
-;
-; Routine to empty the 8042 KBC controller. If dl != 0
-; then we will test A20 in the loop and exit if A20 is
-; suddenly enabled.
-;
-empty_8042_uncond:
- xor dl,dl
-empty_8042:
- call a20_test
- jz .a20_on
- and dl,dl
- jnz .done
-.a20_on: io_delay
- in al, 064h ; Status port
- test al,1
- jz .no_output
- io_delay
- in al, 060h ; Read input
- jmp short empty_8042
-.no_output:
- test al,2
- jnz empty_8042
- io_delay
-.done: ret
-
-;
-; WBINVD instruction; gets auto-eliminated on 386 CPUs
-;
-try_wbinvd:
- wbinvd
- ret
-
-;
-; Load RAM disk into high memory
-;
-; Need to be set:
-; su_ramdiskat - Where in memory to load
-; su_ramdisklen - Size of file
-; SI - initrd filehandle/cluster pointer
-;
-loadinitrd:
- push es ; Save ES on entry
- mov ax,real_mode_seg
- mov es,ax
- mov edi,[es:su_ramdiskat] ; initrd load address
- push si
- mov si,crlfloading_msg ; Write "Loading "
- call cwritestr
- mov si,InitRDCName ; Write ramdisk name
- call cwritestr
- mov si,dotdot_msg ; Write dots
- call cwritestr
- pop si
-
- mov eax,[es:su_ramdisklen]
- call load_high ; Load the file
-
- call crlf
- pop es ; Restore original ES
- ret
-
-;
-; load_high: loads (the remainder of) a file into high memory.
-; This routine prints dots for each 64K transferred, and
-; calls abort_check periodically.
-;
-; The xfer_buf_seg is used as a bounce buffer.
-;
-; The input address (EDI) should be dword aligned, and the final
-; dword written is padded with zeroes if necessary.
-;
-; Inputs: SI = file handle/cluster pointer
-; EDI = target address in high memory
-; EAX = size of remaining file in bytes
-;
-; Outputs: SI = file handle/cluster pointer
-; EDI = first untouched address (not including padding)
-;
-load_high:
- push es
-
- mov bx,xfer_buf_seg
- mov es,bx
-
-.read_loop:
- and si,si ; If SI == 0 then we have end of file
- jz .eof
- push si
- mov si,dot_msg
- call cwritestr
- pop si
- call abort_check
-
- push eax ; <A> Total bytes to transfer
- cmp eax,(1 << 16) ; Max 64K in one transfer
- jna .size_ok
- mov eax,(1 << 16)
-.size_ok:
- xor edx,edx
- push eax ; <B> Bytes transferred this chunk
- movzx ecx,word [ClustSize]
- div ecx ; Convert to clusters
- ; Round up...
- add edx,byte -1 ; Sets CF if EDX >= 1
- adc eax,byte 0 ; Add 1 to EAX if CF set
-
- ; Now (e)ax contains the number of clusters to get
- push edi ; <C> Target buffer
- mov cx,ax
- xor bx,bx ; ES:0
- call getfssec ; Load the data into xfer_buf_seg
- pop edi ; <C> Target buffer
- pop ecx ; <B> Byte count this round
- push ecx ; <B> Byte count this round
- push edi ; <C> Target buffer
-.fix_slop:
- test cl,3
- jz .noslop
- ; The last dword fractional - pad with zeroes
- ; Zero-padding is critical for multi-file initramfs.
- mov byte [es:ecx],0
- inc ecx
- jmp short .fix_slop
-.noslop:
- shr ecx,2 ; Convert to dwords
- push esi ; <D> File handle/cluster pointer
- mov esi,(xfer_buf_seg << 4) ; Source address
- call bcopy ; Copy to high memory
- pop esi ; <D> File handle/cluster pointer
- pop edi ; <C> Target buffer
- pop ecx ; <B> Byte count this round
- pop eax ; <A> Total bytes to transfer
- add edi,ecx
- sub eax,ecx
- jnz .read_loop ; More to read...
-
-.eof:
- pop es
- ret
-
-;
; abort_check: let the user abort with <ESC> or <Ctrl-C>
;
abort_check:
@@ -2924,6 +1868,8 @@ getfssec:
%include "conio.inc" ; Console I/O
%include "parseconfig.inc" ; High-level config file handling
%include "parsecmd.inc" ; Low-level config file handling
+%include "bcopy32.inc" ; 32-bit bcopy
+%include "loadhigh.inc" ; Load a file into high memory
%include "font.inc" ; VGA font stuff
%include "graphics.inc" ; VGA graphics
@@ -3080,9 +2026,6 @@ ForcePrompt dw 0 ; Force prompt
AllowImplicit dw 1 ; Allow implicit kernels
SerialPort dw 0 ; Serial port base (or 0 for no serial port)
NextSocket dw 49152 ; Counter for allocating socket numbers
-A20List dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
-A20DList dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
-A20Type dw A20_DUNNO ; A20 type unknown
VGAFontSize dw 16 ; Defaults to 16 byte font
UserFont db 0 ; Using a user-specified font
ScrollAttribute db 07h ; White on black (for text mode)
diff --git a/ldlinux.asm b/ldlinux.asm
index cd22f429..af4243ad 100644
--- a/ldlinux.asm
+++ b/ldlinux.asm
@@ -40,8 +40,10 @@ my_id equ syslinux_id
max_cmd_len equ 255 ; Must be odd; 255 is the kernel limit
FILENAME_MAX_LG2 equ 4 ; log2(Max filename size Including final null)
FILENAME_MAX equ 11 ; Max mangled filename size
+NULLFILE equ ' ' ; First char space == null filename
retry_count equ 6 ; How patient are we with the disk?
HIGHMEM_MAX equ 037FFFFFFh ; DEFAULT highest address for an initrd
+%assign HIGHMEM_SLOP 0 ; Avoid this much memory near the top
DEFAULT_BAUD equ 9600 ; Default baud rate for serial port
BAUD_DIVISOR equ 115200 ; Serial port parameter
;
@@ -133,6 +135,7 @@ HiLoadAddr resd 1 ; Address pointer for high load loop
HighMemSize resd 1 ; End of memory pointer (bytes)
RamdiskMax resd 1 ; Highest address for a ramdisk
KernelSize resd 1 ; Size of kernel (bytes)
+SavedSSSP resd 1 ; Our SS:SP while running a COMBOOT image
KernelName resb 12 ; Mangled name for kernel
; (note the spare byte after!)
RootDir equ $ ; Location of root directory
@@ -166,7 +169,6 @@ KernelCNameLen resw 1 ; Length of unmangled kernel name
InitRDCNameLen resw 1 ; Length of unmangled initrd name
NextCharJump resw 1 ; Routine to interpret next print char
SetupSecs resw 1 ; Number of setup sectors
-SavedSP resw 1 ; Our SP while running a COMBOOT image
A20Test resw 1 ; Counter for testing status of A20
CmdLineLen resw 1 ; Length of command line including null
GraphXSize resw 1 ; Width of splash screen file
@@ -1369,667 +1371,16 @@ kernel_good:
cmp ecx,'BSS'
je near is_bss_sector
; Otherwise Linux kernel
-;
-; A Linux kernel consists of three parts: boot sector, setup code, and
-; kernel code. The boot sector is never executed when using an external
-; booting utility, but it contains some status bytes that are necessary.
-; The boot sector and setup code together form exactly 5 sectors that
-; should be loaded at 9000:0. The subsequent code should be loaded
-; at 1000:0. For simplicity, we load the whole thing at 0F60:0, and
-; copy the latter stuff afterwards.
-;
-; NOTE: In the previous code I have avoided making any assumptions regarding
-; the size of a sector, in case this concept ever gets extended to other
-; media like CD-ROM (not that a CD-ROM would be bloody likely to use a FAT
-; filesystem, of course). However, a "sector" when it comes to Linux booting
-; stuff means 512 bytes *no matter what*, so here I am using that piece
-; of knowledge.
-;
-; First check that our kernel is at least 1K and less than 8M (if it is
-; more than 8M, we need to change the logic for loading it anyway...)
-;
-; We used to require the kernel to be 64K or larger, but it has gotten
-; popular to use the Linux kernel format for other things, which may
-; not be so large.
-;
-is_linux_kernel:
- cmp dx,80h ; 8 megs
- ja kernel_corrupt
- and dx,dx
- jnz kernel_sane
- cmp ax,1024 ; Bootsect + 1 setup sect
- jb kernel_corrupt
-kernel_sane: push ax
- push dx
- push si
- mov si,loading_msg
- call cwritestr
-;
-; Now start transferring the kernel
-;
- push word real_mode_seg
- pop es
-
- push ax
- push dx
- div word [ClustSize] ; # of clusters total
- and dx,dx ; Round up
- setnz dl
- movzx dx,dl
- add ax,dx
- mov [KernelClust],ax
- pop dx
- pop ax
- mov [KernelSize],ax
- mov [KernelSize+2],dx
-;
-; Now, if we transfer these straight, we'll hit 64K boundaries. Hence we
-; have to see if we're loading more than 64K, and if so, load it step by
-; step.
-;
- mov dx,1 ; 10000h
- xor ax,ax
- div word [ClustSize]
- mov [ClustPerMoby],ax ; Clusters/64K
-;
-; Start by loading the bootsector/setup code, to see if we need to
-; do something funky. It should fit in the first 32K (loading 64K won't
-; work since we might have funny stuff up near the end of memory).
-; If we have larger than 32K clusters, yes, we're hosed.
-;
- call abort_check ; Check for abort key
- mov cx,[ClustPerMoby]
- shr cx,1 ; Half a moby
- cmp cx,[KernelClust]
- jna .normalkernel
- mov cx,[KernelClust]
-.normalkernel:
- sub [KernelClust],cx
- xor bx,bx
- pop si ; Cluster pointer on stack
- call getfssec
- cmp word [es:bs_bootsign],0AA55h
- jne near kernel_corrupt ; Boot sec signature missing
-;
-; Get the BIOS' idea of what the size of high memory is.
-;
- push si ; Save our cluster pointer!
-;
-; First, try INT 15:E820 (get BIOS memory map)
-;
-get_e820:
- push es
- xor ebx,ebx ; Start with first record
- mov es,bx ; Need ES = DS = 0 for now
- jmp short .do_e820 ; Skip "at end" check first time!
-.int_loop: and ebx,ebx ; If we're back at beginning...
- jz no_e820 ; ... bail; nothing found
-.do_e820: mov eax,0000E820h
- mov edx,534D4150h ; "SMAP" backwards
- mov ecx,20
- mov di,E820Buf
- int 15h
- jc no_e820
- cmp eax,534D4150h
- jne no_e820
-;
-; Look for a memory block starting at <= 1 MB and continuing upward
-;
- cmp dword [E820Buf+4], byte 0
- ja .int_loop ; Start >= 4 GB?
- mov edx, (1 << 20)
- sub edx, [E820Buf]
- jb .int_loop ; Start >= 1 MB?
- mov eax, 0FFFFFFFFh
- cmp dword [E820Buf+12], byte 0
- ja .huge ; Size >= 4 GB
- mov eax, [E820Buf+8]
-.huge: sub eax, edx ; Adjust size to start at 1 MB
- jbe .int_loop ; Completely below 1 MB?
-
- ; Now EAX contains the size of memory 1 MB...up
- cmp dword [E820Buf+16], byte 1
- jne near err_nohighmem ; High memory isn't usable memory!!!!
-
- ; We're good!
- pop es
- jmp short got_highmem_add1mb ; Still need to add low 1 MB
-
-;
-; INT 15:E820 failed. Try INT 15:E801.
-;
-no_e820: pop es
-
- mov ax,0e801h ; Query high memory (semi-recent)
- int 15h
- jc no_e801
- cmp ax,3c00h
- ja no_e801 ; > 3C00h something's wrong with this call
- jb e801_hole ; If memory hole we can only use low part
-
- mov ax,bx
- shl eax,16 ; 64K chunks
- add eax,(16 << 20) ; Add first 16M
- jmp short got_highmem
-
-;
-; INT 15:E801 failed. Try INT 15:88.
-;
-no_e801:
- mov ah,88h ; Query high memory (oldest)
- int 15h
- cmp ax,14*1024 ; Don't trust memory >15M
- jna e801_hole
- mov ax,14*1024
-e801_hole:
- and eax,0ffffh
- shl eax,10 ; Convert from kilobytes
-got_highmem_add1mb:
- add eax,(1 << 20) ; First megabyte
-got_highmem:
- mov [HighMemSize],eax
-
-;
-; Construct the command line (append options have already been copied)
-;
- mov di,[CmdLinePtr]
- mov si,boot_image ; BOOT_IMAGE=
- mov cx,boot_image_len
- rep movsb
- mov si,KernelCName ; Unmangled kernel name
- mov cx,[KernelCNameLen]
- rep movsb
- mov al,' ' ; Space
- stosb
- mov si,[CmdOptPtr] ; Options from user input
- mov cx,(kern_cmd_len+3) >> 2
- rep movsd
-;
-%ifdef debug
- push ds ; DEBUG DEBUG DEBUG
- push es
- pop ds
- mov si,cmd_line_here
- call cwritestr
- pop ds
- call crlf
-%endif
-;
-; Scan through the command line for anything that looks like we might be
-; interested in. The original version of this code automatically assumed
-; the first option was BOOT_IMAGE=, but that is no longer certain.
-;
- mov si,cmd_line_here
- mov byte [initrd_flag],0
- push es ; Set DS <- real_mode_seg
- pop ds
-get_next_opt: lodsb
- and al,al
- jz near cmdline_end
- cmp al,' '
- jbe get_next_opt
- dec si
- mov eax,[si]
- cmp eax,'vga='
- je is_vga_cmd
- cmp eax,'mem='
- je is_mem_cmd
- push es ; Save ES -> real_mode_seg
- push cs
- pop es ; Set ES <- normal DS
- mov di,initrd_cmd
- mov cx,initrd_cmd_len
- repe cmpsb
- jne not_initrd
- mov di,InitRD
- push si ; mangle_dir mangles si
- call mangle_name ; Mangle ramdisk name
- pop si
- cmp byte [es:InitRD],' ' ; Null filename?
- seta byte [es:initrd_flag] ; Set flag if not
-not_initrd: pop es ; Restore ES -> real_mode_seg
-skip_this_opt: lodsb ; Load from command line
- cmp al,' '
- ja skip_this_opt
- dec si
- jmp short get_next_opt
-is_vga_cmd:
- add si,byte 4
- mov eax,[si]
- mov bx,-1
- cmp eax, 'norm' ; vga=normal
- je vc0
- and eax,0ffffffh ; 3 bytes
- mov bx,-2
- cmp eax, 'ext' ; vga=ext
- je vc0
- mov bx,-3
- cmp eax, 'ask' ; vga=ask
- je vc0
- call parseint ; vga=<number>
- jc skip_this_opt ; Not an integer
-vc0: mov [bs_vidmode],bx ; Set video mode
- jmp short skip_this_opt
-is_mem_cmd:
- add si,byte 4
- call parseint
- jc skip_this_opt ; Not an integer
- mov [cs:HighMemSize],ebx
- jmp short skip_this_opt
-cmdline_end:
- push cs ; Restore standard DS
- pop ds
- sub si,cmd_line_here
- mov [CmdLineLen],si ; Length including final null
-;
-; Now check if we have a large kernel, which needs to be loaded high
-;
- mov dword [RamdiskMax], HIGHMEM_MAX ; Default initrd limit
- cmp dword [es:su_header],HEADER_ID ; New setup code ID
- jne near old_kernel ; Old kernel, load low
- cmp word [es:su_version],0200h ; Setup code version 2.0
- jb near old_kernel ; Old kernel, load low
- cmp word [es:su_version],0201h ; Version 2.01+?
- jb new_kernel ; If 2.00, skip this step
- mov word [es:su_heapend],linux_stack ; Set up the heap
- or byte [es:su_loadflags],80h ; Let the kernel know we care
- cmp word [es:su_version],0203h ; Version 2.03+?
- jb new_kernel ; Not 2.03+
- mov eax,[es:su_ramdisk_max]
- mov [RamdiskMax],eax ; Set the ramdisk limit
-
-;
-; We definitely have a new-style kernel. Let the kernel know who we are,
-; and that we are clueful
-;
-new_kernel:
- mov byte [es:su_loader],my_id ; Show some ID
- movzx ax,byte [es:bs_setupsecs] ; Variable # of setup sectors
- mov [SetupSecs],ax
-;
-; About to load the kernel. This is a modern kernel, so use the boot flags
-; we were provided.
-;
- mov al,[es:su_loadflags]
- mov [LoadFlags],al
-;
-; Load the kernel. We always load it at 100000h even if we're supposed to
-; load it "low"; for a "low" load we copy it down to low memory right before
-; jumping to it.
-;
-read_kernel:
- mov si,KernelCName ; Print kernel name part of
- call cwritestr ; "Loading" message
- mov si,dotdot_msg ; Print dots
- call cwritestr
-
- mov eax,[HighMemSize]
- sub eax,100000h ; Load address
- cmp eax,[KernelSize]
- jb near no_high_mem ; Not enough high memory
-;
-; Move the stuff beyond the setup code to high memory at 100000h
-;
- movzx esi,word [SetupSecs] ; Setup sectors
- inc esi ; plus 1 boot sector
- shl esi,9 ; Convert to bytes
- mov ecx,8000h ; 32K
- sub ecx,esi ; Number of bytes to copy
- push ecx
- shr ecx,2 ; Convert to dwords
- add esi,(real_mode_seg << 4) ; Pointer to source
- mov edi,100000h ; Copy to address 100000h
- call bcopy ; Transfer to high memory
-
- ; On exit EDI -> where to load the rest
-
- mov si,dot_msg ; Progress report
- call cwritestr
- call abort_check
-
- pop ecx ; Number of bytes in the initial portion
- pop si ; Restore file handle/cluster pointer
- mov eax,[KernelSize]
- sub eax,ecx ; Amount of kernel left over
- jbe high_load_done ; Zero left (tiny kernel)
-
- call load_high ; Copy the file
-
-high_load_done:
- mov ax,real_mode_seg ; Set to real mode seg
- mov es,ax
-
- mov si,dot_msg
- call cwritestr
-
-;
-; Now see if we have an initial RAMdisk; if so, do requisite computation
-; We know we have a new kernel; the old_kernel code already will have objected
-; if we tried to load initrd using an old kernel
-;
-load_initrd:
- test byte [initrd_flag],1
- jz near nk_noinitrd
- push es ; ES->real_mode_seg
- push ds
- pop es ; We need ES==DS
- mov si,InitRD
- mov di,InitRDCName
- call unmangle_name ; Create human-readable name
- sub di,InitRDCName
- mov [InitRDCNameLen],di
- mov di,InitRD
- call searchdir ; Look for it in directory
- pop es
- jz initrd_notthere
- mov [es:su_ramdisklen1],ax ; Ram disk length
- mov [es:su_ramdisklen2],dx
- mov edx,[HighMemSize] ; End of memory
- dec edx
- mov eax,[RamdiskMax] ; Highest address allowed by kernel
- cmp edx,eax
- jna memsize_ok
- mov edx,eax ; Adjust to fit inside limit
-memsize_ok:
- inc edx
- xor dx,dx ; Round down to 64K boundary
- sub edx,[es:su_ramdisklen] ; Subtract size of ramdisk
- xor dx,dx ; Round down to 64K boundary
- mov [es:su_ramdiskat],edx ; Load address
- call loadinitrd ; Load initial ramdisk
- jmp short initrd_end
-
-initrd_notthere:
- mov si,err_noinitrd
- call cwritestr
- mov si,InitRDCName
- call cwritestr
- mov si,crlf_msg
- jmp abort_load
-
-no_high_mem: mov si,err_nohighmem ; Error routine
- jmp abort_load
-
-initrd_end:
-nk_noinitrd:
-;
-; Abandon hope, ye that enter here! We do no longer permit aborts.
-;
- call abort_check ; Last chance!!
-
- mov si,ready_msg
- call cwritestr
-
- call vgaclearmode ; We can't trust ourselves after this
-;
-; Now, if we were supposed to load "low", copy the kernel down to 10000h
-; and the real mode stuff to 90000h. We assume that all bzImage kernels are
-; capable of starting their setup from a different address.
-;
- mov ax,real_mode_seg
- mov fs,ax
-
-;
-; Copy command line. Unfortunately, the kernel boot protocol requires
-; the command line to exist in the 9xxxxh range even if the rest of the
-; setup doesn't.
-;
- cli ; In case of hooked interrupts
- test byte [LoadFlags],LOAD_HIGH
- jz need_high_cmdline
- cmp word [fs:su_version],0202h ; Support new cmdline protocol?
- jb need_high_cmdline
- ; New cmdline protocol
- ; Store 32-bit (flat) pointer to command line
- mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4) + cmd_line_here
- jmp short in_proper_place
-need_high_cmdline:
;
-; Copy command line up to 90000h
+; Linux kernel loading code is common.
;
- mov ax,9000h
- mov es,ax
- mov si,cmd_line_here
- mov di,si
- mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic
- mov [fs:kern_cmd_offset],di ; Store pointer
-
- mov cx,[CmdLineLen]
- add cx,byte 3
- shr cx,2 ; Convert to dwords
- fs rep movsd
-
- push fs
- pop es
-
- test byte [LoadFlags],LOAD_HIGH
- jnz in_proper_place ; If high load, we're done
+%include "runkernel.inc"
;
-; Loading low; we can't assume it's safe to run in place.
-;
-; Copy real_mode stuff up to 90000h
-;
- mov ax,9000h
- mov es,ax
- mov cx,[SetupSecs]
- inc cx ; Setup + boot sector
- shl cx,7 ; Sectors -> dwords
- xor si,si
- xor di,di
- fs rep movsd ; Copy setup + boot sector
-;
-; Some kernels in the 1.2 ballpark but pre-bzImage have more than 4
-; setup sectors, but the boot protocol had not yet been defined. They
-; rely on a signature to figure out if they need to copy stuff from
-; the "protected mode" kernel area. Unfortunately, we used that area
-; as a transfer buffer, so it's going to find the signature there.
-; Hence, zero the low 32K beyond the setup area.
-;
- mov di,[SetupSecs]
- inc di ; Setup + boot sector
- mov cx,32768/512 ; Sectors/32K
- sub cx,di ; Remaining sectors
- shl di,9 ; Sectors -> bytes
- shl cx,7 ; Sectors -> dwords
- xor eax,eax
- rep stosd ; Clear region
+; COMBOOT-loading code
;
-; Copy the kernel down to the "low" location
-;
- mov ecx,[KernelSize]
- add ecx,3 ; Round upwards
- shr ecx,2 ; Bytes -> dwords
- mov esi,100000h
- mov edi,10000h
- call bcopy
-
-;
-; Now everything is where it needs to be...
-;
-; When we get here, es points to the final segment, either
-; 9000h or real_mode_seg
-;
-in_proper_place:
-
-;
-; If the default root device is set to FLOPPY (0000h), change to
-; /dev/fd0 (0200h)
-;
- cmp word [es:bs_rootdev],byte 0
- jne root_not_floppy
- mov word [es:bs_rootdev],0200h
-root_not_floppy:
-;
-; Copy the disk table to high memory, then re-initialize the floppy
-; controller
-;
-; This needs to be moved before the copy
-;
-%if 0
- push ds
- push bx
- lds si,[fdctab]
- mov di,linux_fdctab
- mov cx,3 ; 12 bytes
- push di
- rep movsd
- pop di
- mov [fdctab1],di ; Save new floppy tab pos
- mov [fdctab2],es
- xor ax,ax
- xor dx,dx
- int 13h
- pop bx
- pop ds
-%endif
-;
-; Linux wants the floppy motor shut off before starting the kernel,
-; at least bootsect.S seems to imply so
-;
-kill_motor:
- mov dx,03F2h
- xor al,al
- call slow_out
-;
-; If we're debugging, wait for a keypress so we can read any debug messages
-;
-%ifdef debug
- xor ax,ax
- int 16h
-%endif
-;
-; Set up segment registers and the Linux real-mode stack
-; Note: es == the real mode segment
-;
- cli
- mov bx,es
- mov ds,bx
- mov fs,bx
- mov gs,bx
- mov ss,bx
- mov sp,linux_stack
-;
-; We're done... now RUN THAT KERNEL!!!!
-; Setup segment == real mode segment + 020h; we need to jump to offset
-; zero in the real mode segment.
-;
- add bx,020h
- push bx
- push word 0h
- retf
-
-;
-; Load an older kernel. Older kernels always have 4 setup sectors, can't have
-; initrd, and are always loaded low.
-;
-old_kernel:
- test byte [initrd_flag],1 ; Old kernel can't have initrd
- jz load_old_kernel
- mov si,err_oldkernel
- jmp abort_load
-load_old_kernel:
- mov word [SetupSecs],4 ; Always 4 setup sectors
- mov byte [LoadFlags],0 ; Always low
- jmp read_kernel
-
-;
-; Load a COMBOOT image. A COMBOOT image is basically a DOS .COM file,
-; except that it may, of course, not contain any DOS system calls. We
-; do, however, allow the execution of INT 20h to return to SYSLINUX.
-;
-is_comboot_image:
- and dx,dx
- jnz comboot_too_large
- cmp ax,0ff00h ; Max size in bytes
- jae comboot_too_large
-
- ;
- ; Set up the DOS vectors in the IVT (INT 20h-3fh)
- ;
- mov dword [4*0x20],comboot_return ; INT 20h vector
- mov eax,comboot_bogus
- mov di,4*0x21
- mov cx,31 ; All remaining DOS vectors
- rep stosd
-
- mov cx,comboot_seg
- mov es,cx
-
- mov bx,100h ; Load at <seg>:0100h
-
- mov cx,[ClustPerMoby] ; Absolute maximum # of clusters
- call getfssec
-
- xor di,di
- mov cx,64 ; 256 bytes (size of PSP)
- xor eax,eax ; Clear PSP
- rep stosd
-
- mov word [es:0], 020CDh ; INT 20h instruction
- ; First non-free paragraph
- mov word [es:02h], comboot_seg+1000h
-
- ; Copy the command line from high memory
- mov cx,125 ; Max cmdline len (minus space and CR)
- mov si,[CmdOptPtr]
- mov di,081h ; Offset in PSP for command line
- mov al,' ' ; DOS command lines begin with a space
- stosb
-
-comboot_cmd_cp: lodsb
- and al,al
- jz comboot_end_cmd
- stosb
- loop comboot_cmd_cp
-comboot_end_cmd: mov al,0Dh ; CR after last character
- stosb
- mov al,126 ; Include space but not CR
- sub al,cl
- mov [es:80h], al ; Store command line length
-
- call vgaclearmode ; Reset video
-
- mov ax,es
- mov ds,ax
- mov ss,ax
- xor sp,sp
- push word 0 ; Return to address 0 -> exit
-
- jmp comboot_seg:100h ; Run it
-
-; Looks like a COMBOOT image but too large
-comboot_too_large:
- mov si,err_comlarge
- call cwritestr
-cb_enter: jmp enter_command
-
-; Proper return vector
-comboot_return: cli ; Don't trust anyone
- xor ax,ax
- mov ss,ax
- mov sp,[ss:SavedSP]
- mov ds,ax
- mov es,ax
- sti
- cld
- jmp short cb_enter
-
-; Attempted to execute DOS system call
-comboot_bogus: cli ; Don't trust anyone
- xor ax,ax
- mov ss,ax
- mov sp,[ss:SavedSP]
- mov ds,ax
- mov es,ax
- sti
- cld
- mov si,KernelCName
- call cwritestr
- mov si,err_notdos
- call cwritestr
- jmp short cb_enter
+%include "comboot.inc"
;
; Load a boot sector
@@ -2093,421 +1444,6 @@ bad_bootsec:
jmp enter_command
;
-; 32-bit bcopy routine for real mode
-;
-; We enter protected mode, set up a flat 32-bit environment, run rep movsd
-; and then exit. IMPORTANT: This code assumes cs == ss == 0.
-;
-; This code is probably excessively anal-retentive in its handling of
-; segments, but this stuff is painful enough as it is without having to rely
-; on everything happening "as it ought to."
-;
- align 4
-bcopy_gdt: dw bcopy_gdt_size-1 ; Null descriptor - contains GDT
- dd bcopy_gdt ; pointer for LGDT instruction
- dw 0
- dd 0000ffffh ; Code segment, use16, readable,
- dd 00009b00h ; present, dpl 0, cover 64K
- dd 0000ffffh ; Data segment, use16, read/write,
- dd 008f9300h ; present, dpl 0, cover all 4G
- dd 0000ffffh ; Data segment, use16, read/write,
- dd 00009300h ; present, dpl 0, cover 64K
-bcopy_gdt_size: equ $-bcopy_gdt
-
-bcopy: push eax
- pushf ; Saves, among others, the IF flag
- push gs
- push fs
- push ds
- push es
-
- cli
- call enable_a20
-
- o32 lgdt [cs:bcopy_gdt]
- mov eax,cr0
- or al,1
- mov cr0,eax ; Enter protected mode
- jmp 08h:.in_pm
-
-.in_pm: mov ax,10h ; Data segment selector
- mov es,ax
- mov ds,ax
-
- mov al,18h ; "Real-mode-like" data segment
- mov ss,ax
- mov fs,ax
- mov gs,ax
-
- a32 rep movsd ; Do our business
-
- mov es,ax ; Set to "real-mode-like"
- mov ds,ax
-
- mov eax,cr0
- and al,~1
- mov cr0,eax ; Disable protected mode
- jmp 0:.in_rm
-
-.in_rm: xor ax,ax ; Back in real mode
- mov ss,ax
- pop es
- pop ds
- pop fs
- pop gs
- call disable_a20
-
- popf ; Re-enables interrupts
- pop eax
- ret
-
-;
-; Routines to enable and disable (yuck) A20. These routines are gathered
-; from tips from a couple of sources, including the Linux kernel and
-; http://www.x86.org/. The need for the delay to be as large as given here
-; is indicated by Donnie Barnes of RedHat, the problematic system being an
-; IBM ThinkPad 760EL.
-;
-; We typically toggle A20 twice for every 64K transferred.
-;
-%define io_delay call _io_delay
-%define IO_DELAY_PORT 80h ; Invalid port (we hope!)
-%define disable_wait 32 ; How long to wait for a disable
-
-%define A20_DUNNO 0 ; A20 type unknown
-%define A20_NONE 1 ; A20 always on?
-%define A20_BIOS 2 ; A20 BIOS enable
-%define A20_KBC 3 ; A20 through KBC
-%define A20_FAST 4 ; A20 through port 92h
-
-slow_out: out dx, al ; Fall through
-
-_io_delay: out IO_DELAY_PORT,al
- out IO_DELAY_PORT,al
- ret
-
-enable_a20:
- pushad
- mov byte [cs:A20Tries],255 ; Times to try to make this work
-
-try_enable_a20:
-;
-; Flush the caches
-;
-; call try_wbinvd
-
-;
-; If the A20 type is known, jump straight to type
-;
- mov bp,[cs:A20Type]
- add bp,bp ; Convert to word offset
- jmp word [cs:bp+A20List]
-
-;
-; First, see if we are on a system with no A20 gate
-;
-a20_dunno:
-a20_none:
- mov byte [cs:A20Type], A20_NONE
- call a20_test
- jnz a20_done
-
-;
-; Next, try the BIOS (INT 15h AX=2401h)
-;
-a20_bios:
- mov byte [cs:A20Type], A20_BIOS
- mov ax,2401h
- pushf ; Some BIOSes muck with IF
- int 15h
- popf
-
- call a20_test
- jnz a20_done
-
-;
-; Enable the keyboard controller A20 gate
-;
-a20_kbc:
- mov dl, 1 ; Allow early exit
- call empty_8042
- jnz a20_done ; A20 live, no need to use KBC
-
- mov byte [cs:A20Type], A20_KBC ; Starting KBC command sequence
-
- mov al,0D1h ; Command write
- out 064h, al
- call empty_8042_uncond
-
- mov al,0DFh ; A20 on
- out 060h, al
- call empty_8042_uncond
-
- ; Verify that A20 actually is enabled. Do that by
- ; observing a word in low memory and the same word in
- ; the HMA until they are no longer coherent. Note that
- ; we don't do the same check in the disable case, because
- ; we don't want to *require* A20 masking (SYSLINUX should
- ; work fine without it, if the BIOS does.)
-.kbc_wait: push cx
- xor cx,cx
-.kbc_wait_loop:
- call a20_test
- jnz a20_done_pop
- loop .kbc_wait_loop
-
- pop cx
-;
-; Running out of options here. Final attempt: enable the "fast A20 gate"
-;
-a20_fast:
- mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
- in al, 092h
- or al,02h
- and al,~01h ; Don't accidentally reset the machine!
- out 092h, al
-
-.fast_wait: push cx
- xor cx,cx
-.fast_wait_loop:
- call a20_test
- jnz a20_done_pop
- loop .fast_wait_loop
-
- pop cx
-
-;
-; Oh bugger. A20 is not responding. Try frobbing it again; eventually give up
-; and report failure to the user.
-;
-
-
- dec byte [cs:A20Tries]
- jnz try_enable_a20
-
- mov si, err_a20
- jmp abort_load
-;
-; A20 unmasked, proceed...
-;
-a20_done_pop: pop cx
-a20_done: popad
- ret
-
-;
-; This routine tests if A20 is enabled (ZF = 0). This routine
-; must not destroy any register contents.
-;
-a20_test:
- push es
- push cx
- push ax
- mov cx,0FFFFh ; HMA = segment 0FFFFh
- mov es,cx
- mov cx,32 ; Loop count
- mov ax,[cs:A20Test]
-.a20_wait: inc ax
- mov [cs:A20Test],ax
- io_delay ; Serialize, and fix delay
- cmp ax,[es:A20Test+10h]
- loopz .a20_wait
-.a20_done: pop ax
- pop cx
- pop es
- ret
-
-disable_a20:
- pushad
-;
-; Flush the caches
-;
-; call try_wbinvd
-
- mov bp,[cs:A20Type]
- add bp,bp ; Convert to word offset
- jmp word [cs:bp+A20DList]
-
-a20d_bios:
- mov ax,2400h
- pushf ; Some BIOSes muck with IF
- int 15h
- popf
- jmp short a20d_snooze
-
-;
-; Disable the "fast A20 gate"
-;
-a20d_fast:
- in al, 092h
- and al,~03h
- out 092h, al
- jmp short a20d_snooze
-
-;
-; Disable the keyboard controller A20 gate
-;
-a20d_kbc:
- call empty_8042_uncond
- mov al,0D1h
- out 064h, al ; Command write
- call empty_8042_uncond
- mov al,0DDh ; A20 off
- out 060h, al
- call empty_8042_uncond
- ; Wait a bit for it to take effect
-a20d_snooze:
- push cx
- mov cx, disable_wait
-.delayloop: call a20_test
- jz .disabled
- loop .delayloop
-.disabled: pop cx
-a20d_dunno:
-a20d_none:
- popad
- ret
-
-;
-; Routine to empty the 8042 KBC controller. If dl != 0
-; then we will test A20 in the loop and exit if A20 is
-; suddenly enabled.
-;
-empty_8042_uncond:
- xor dl,dl
-empty_8042:
- call a20_test
- jz .a20_on
- and dl,dl
- jnz .done
-.a20_on: io_delay
- in al, 064h ; Status port
- test al,1
- jz .no_output
- io_delay
- in al, 060h ; Read input
- jmp short empty_8042
-.no_output:
- test al,2
- jnz empty_8042
- io_delay
-.done: ret
-
-;
-; WBINVD instruction; gets auto-eliminated on 386 CPUs
-;
-try_wbinvd:
- wbinvd
- ret
-
-;
-; Load RAM disk into high memory
-;
-; Need to be set:
-; su_ramdiskat - Where in memory to load
-; su_ramdisklen - Size of file
-; SI - initrd filehandle/cluster pointer
-;
-loadinitrd:
- push es ; Save ES on entry
- mov ax,real_mode_seg
- mov es,ax
- mov edi,[es:su_ramdiskat] ; initrd load address
- push si
- mov si,crlfloading_msg ; Write "Loading "
- call cwritestr
- mov si,InitRDCName ; Write ramdisk name
- call cwritestr
- mov si,dotdot_msg ; Write dots
- call cwritestr
- pop si
-
- mov eax,[es:su_ramdisklen]
- call load_high ; Load the file
-
- call crlf
- pop es ; Restore original ES
- ret
-
-;
-; load_high: loads (the remainder of) a file into high memory.
-; This routine prints dots for each 64K transferred, and
-; calls abort_check periodically.
-;
-; The xfer_buf_seg is used as a bounce buffer.
-;
-; The input address (EDI) should be dword aligned, and the final
-; dword written is padded with zeroes if necessary.
-;
-; Inputs: SI = file handle/cluster pointer
-; EDI = target address in high memory
-; EAX = size of remaining file in bytes
-;
-; Outputs: SI = file handle/cluster pointer
-; EDI = first untouched address (not including padding)
-;
-load_high:
- push es
-
- mov bx,xfer_buf_seg
- mov es,bx
-
-.read_loop:
- and si,si ; If SI == 0 then we have end of file
- jz .eof
- push si
- mov si,dot_msg
- call cwritestr
- pop si
- call abort_check
-
- push eax ; <A> Total bytes to transfer
- cmp eax,(1 << 16) ; Max 64K in one transfer
- jna .size_ok
- mov eax,(1 << 16)
-.size_ok:
- xor edx,edx
- push eax ; <B> Bytes transferred this chunk
- movzx ecx,word [ClustSize]
- div ecx ; Convert to clusters
- ; Round up...
- add edx,byte -1 ; Sets CF if EDX >= 1
- adc eax,byte 0 ; Add 1 to EAX if CF set
-
- ; Now (e)ax contains the number of clusters to get
- push edi ; <C> Target buffer
- mov cx,ax
- xor bx,bx ; ES:0
- call getfssec ; Load the data into xfer_buf_seg
- pop edi ; <C> Target buffer
- pop ecx ; <B> Byte count this round
- push ecx ; <B> Byte count this round
- push edi ; <C> Target buffer
-.fix_slop:
- test cl,3
- jz .noslop
- ; The last dword fractional - pad with zeroes
- ; Zero-padding is critical for multi-file initramfs.
- mov byte [es:ecx],0
- inc ecx
- jmp short .fix_slop
-.noslop:
- shr ecx,2 ; Convert to dwords
- push esi ; <D> File handle/cluster pointer
- mov esi,(xfer_buf_seg << 4) ; Source address
- call bcopy ; Copy to high memory
- pop esi ; <D> File handle/cluster pointer
- pop edi ; <C> Target buffer
- pop ecx ; <B> Byte count this round
- pop eax ; <A> Total bytes to transfer
- add edi,ecx
- sub eax,ecx
- jnz .read_loop ; More to read...
-
-.eof:
- pop es
- ret
-
-;
; abort_check: let the user abort with <ESC> or <Ctrl-C>
;
abort_check:
@@ -2783,6 +1719,8 @@ lc_ret: ret
%include "writestr.inc" ; String output
%include "parseconfig.inc" ; High-level config file handling
%include "parsecmd.inc" ; Low-level config file handling
+%include "bcopy32.inc" ; 32-bit bcopy
+%include "loadhigh.inc" ; Load a file into high memory
%include "font.inc" ; VGA font stuff
%include "graphics.inc" ; VGA graphics
@@ -2919,9 +1857,6 @@ VKernelCtr dw 0 ; Number of registered vkernels
ForcePrompt dw 0 ; Force prompt
AllowImplicit dw 1 ; Allow implicit kernels
SerialPort dw 0 ; Serial port base (or 0 for no serial port)
-A20List dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
-A20DList dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
-A20Type dw A20_DUNNO ; A20 type unknown
VGAFontSize dw 16 ; Defaults to 16 byte font
UserFont db 0 ; Using a user-specified font
ScrollAttribute db 07h ; White on black (for text mode)
diff --git a/loadhigh.inc b/loadhigh.inc
new file mode 100644
index 00000000..c952ae87
--- /dev/null
+++ b/loadhigh.inc
@@ -0,0 +1,98 @@
+;; $Id$
+;; -----------------------------------------------------------------------
+;;
+;; Copyright 1994-2002 H. Peter Anvin - All Rights Reserved
+;;
+;; This program is free software; you can redistribute it and/or modify
+;; it under the terms of the GNU General Public License as published by
+;; the Free Software Foundation, Inc., 53 Temple Place Ste 330,
+;; Bostom MA 02111-1307, USA; either version 2 of the License, or
+;; (at your option) any later version; incorporated herein by reference.
+;;
+;; -----------------------------------------------------------------------
+
+;;
+;; loadhigh.inc
+;;
+;; Load a file into high memory
+;;
+
+;
+; load_high: loads (the remainder of) a file into high memory.
+; This routine prints dots for each 64K transferred, and
+; calls abort_check periodically.
+;
+; The xfer_buf_seg is used as a bounce buffer.
+;
+; The input address (EDI) should be dword aligned, and the final
+; dword written is padded with zeroes if necessary.
+;
+; Inputs: SI = file handle/cluster pointer
+; EDI = target address in high memory
+; EAX = size of remaining file in bytes
+;
+; Outputs: SI = file handle/cluster pointer
+; EDI = first untouched address (not including padding)
+;
+load_high:
+ push es
+
+ mov bx,xfer_buf_seg
+ mov es,bx
+
+.read_loop:
+ and si,si ; If SI == 0 then we have end of file
+ jz .eof
+ push si
+ mov si,dot_msg
+ call cwritestr
+ pop si
+ call abort_check
+
+ push eax ; <A> Total bytes to transfer
+ cmp eax,(1 << 16) ; Max 64K in one transfer
+ jna .size_ok
+ mov eax,(1 << 16)
+.size_ok:
+ xor edx,edx
+ push eax ; <B> Bytes transferred this chunk
+ movzx ecx,word [ClustSize]
+ div ecx ; Convert to clusters
+ ; Round up...
+ add edx,byte -1 ; Sets CF if EDX >= 1
+ adc eax,byte 0 ; Add 1 to EAX if CF set
+
+ ; Now (e)ax contains the number of clusters to get
+ push edi ; <C> Target buffer
+ mov cx,ax
+ xor bx,bx ; ES:0
+ call getfssec ; Load the data into xfer_buf_seg
+ pop edi ; <C> Target buffer
+ pop ecx ; <B> Byte count this round
+ push ecx ; <B> Byte count this round
+ push edi ; <C> Target buffer
+.fix_slop:
+ test cl,3
+ jz .noslop
+ ; The last dword fractional - pad with zeroes
+ ; Zero-padding is critical for multi-file initramfs.
+ mov byte [es:ecx],0
+ inc ecx
+ jmp short .fix_slop
+.noslop:
+ shr ecx,2 ; Convert to dwords
+ push esi ; <D> File handle/cluster pointer
+ mov esi,(xfer_buf_seg << 4) ; Source address
+ call bcopy ; Copy to high memory
+ pop esi ; <D> File handle/cluster pointer
+ pop edi ; <C> Target buffer
+ pop ecx ; <B> Byte count this round
+ pop eax ; <A> Total bytes to transfer
+ add edi,ecx
+ sub eax,ecx
+ jnz .read_loop ; More to read...
+
+.eof:
+ pop es
+ ret
+
diff --git a/pxelinux.asm b/pxelinux.asm
index 36278652..8c83faca 100644
--- a/pxelinux.asm
+++ b/pxelinux.asm
@@ -33,9 +33,10 @@ my_id equ pxelinux_id
max_cmd_len equ 255 ; Must be odd; 255 is the kernel limit
FILENAME_MAX_LG2 equ 6 ; log2(Max filename size Including final null)
FILENAME_MAX equ (1 << FILENAME_MAX_LG2)
+NULLFILE equ 0 ; Zero byte == null file name
REBOOT_TIME equ 5*60 ; If failure, time until full reset
HIGHMEM_MAX equ 037FFFFFFh ; DEFAULT highest address for an initrd
-HIGHMEM_SLOP equ 128*1024 ; Avoid this much memory near the top
+%assign HIGHMEM_SLOP 128*1024 ; Avoid this much memory near the top
DEFAULT_BAUD equ 9600 ; Default baud rate for serial port
BAUD_DIVISOR equ 115200 ; Serial port parameter
MAX_SOCKETS_LG2 equ 6 ; log2(Max number of open sockets)
@@ -195,9 +196,9 @@ HiLoadAddr resd 1 ; Address pointer for high load loop
HighMemSize resd 1 ; End of memory pointer (bytes)
RamdiskMax resd 1 ; Highest address for a ramdisk
KernelSize resd 1 ; Size of kernel (bytes)
+SavedSSSP resd 1 ; Our SS:SP while running a COMBOOT image
Stack resd 1 ; Pointer to reset stack
PXEEntry resd 1 ; !PXE API entry point
-SavedSSSP resd 1 ; Our SS:SP while running a COMBOOT image
RebootTime resd 1 ; Reboot timeout, if set by option
KernelClust resd 1 ; Kernel size in clusters
FBytes equ $ ; Used by open/getc
@@ -1150,165 +1151,13 @@ kernel_good:
je near is_bootsector
; Otherwise Linux kernel
;
-; A Linux kernel consists of three parts: boot sector, setup code, and
-; kernel code. The boot sector is never executed when using an external
-; booting utility, but it contains some status bytes that are necessary.
-;
-; First check that our kernel is at least 1K and less than 8M (if it is
-; more than 8M, we need to change the logic for loading it anyway...)
-;
-; We used to require the kernel to be 64K or larger, but it has gotten
-; popular to use the Linux kernel format for other things, which may
-; not be so large.
-;
-is_linux_kernel:
- cmp dx,80h ; 8 megs
- ja kernel_corrupt
- and dx,dx
- jnz kernel_sane
- cmp ax,1024 ; Bootsect + 1 setup sect
- jb kernel_corrupt
-kernel_sane: push ax
- push dx
- push si
- mov si,loading_msg
- call cwritestr
-;
-; Now start transferring the kernel
-;
- push word real_mode_seg
- pop es
-
- movzx eax,ax ; Fix this by using a 32-bit
- shl edx,16 ; register for the kernel size
- or eax,edx
- mov [KernelSize],eax
- xor edx,edx
- div dword [ClustSize] ; # of clusters total
- ; Round up...
- add edx,byte -1 ; Sets CF if EDX >= 1
- adc eax,byte 0 ; Add 1 to EAX if CF set
- mov [KernelClust],eax
-
-;
-; Now, if we transfer these straight, we'll hit 64K boundaries. Hence we
-; have to see if we're loading more than 64K, and if so, load it step by
-; step.
+; Linux kernel loading code is common. However, we need to define
+; a couple of helper macros...
;
-;
-; Start by loading the bootsector/setup code, to see if we need to
-; do something funky. It should fit in the first 32K (loading 64K won't
-; work since we might have funny stuff up near the end of memory).
-; If we have larger than 32K clusters, yes, we're hosed.
-;
- call abort_check ; Check for abort key
- mov ecx,[ClustPerMoby]
- shr ecx,1 ; Half a moby
- cmp ecx,[KernelClust]
- jna .normalkernel
- mov ecx,[KernelClust]
-.normalkernel:
- sub [KernelClust],ecx
- xor bx,bx
- pop si ; Cluster pointer on stack
- call getfssec
- cmp word [es:bs_bootsign],0AA55h
- jne near kernel_corrupt ; Boot sec signature missing
-;
-; Get the BIOS' idea of what the size of high memory is.
-;
- push si ; Save our cluster pointer!
-;
-; First, try INT 15:E820 (get BIOS memory map)
-;
-get_e820:
- push es
- xor ebx,ebx ; Start with first record
- mov es,bx ; Need ES = DS = 0 for now
- jmp short .do_e820 ; Skip "at end" check first time!
-.int_loop: and ebx,ebx ; If we're back at beginning...
- jz no_e820 ; ... bail; nothing found
-.do_e820: mov eax,0000E820h
- mov edx,534D4150h ; "SMAP" backwards
- mov ecx,20
- mov di,E820Buf
- int 15h
- jc no_e820
- cmp eax,534D4150h
- jne no_e820
-;
-; Look for a memory block starting at <= 1 MB and continuing upward
-;
- cmp dword [E820Buf+4], byte 0
- ja .int_loop ; Start >= 4 GB?
- mov edx, (1 << 20)
- sub edx, [E820Buf]
- jb .int_loop ; Start >= 1 MB?
- mov eax, 0FFFFFFFFh
- cmp dword [E820Buf+12], byte 0
- ja .huge ; Size >= 4 GB
- mov eax, [E820Buf+8]
-.huge: sub eax, edx ; Adjust size to start at 1 MB
- jbe .int_loop ; Completely below 1 MB?
-
- ; Now EAX contains the size of memory 1 MB...up
- cmp dword [E820Buf+16], byte 1
- jne near err_nohighmem ; High memory isn't usable memory!!!!
-
- ; We're good!
- pop es
- jmp short got_highmem_add1mb ; Still need to add low 1 MB
-
-;
-; INT 15:E820 failed. Try INT 15:E801.
-;
-no_e820: pop es
-
- mov ax,0e801h ; Query high memory (semi-recent)
- int 15h
- jc no_e801
- cmp ax,3c00h
- ja no_e801 ; > 3C00h something's wrong with this call
- jb e801_hole ; If memory hole we can only use low part
-
- mov ax,bx
- shl eax,16 ; 64K chunks
- add eax,(16 << 20) ; Add first 16M
- jmp short got_highmem
-
-;
-; INT 15:E801 failed. Try INT 15:88.
-;
-no_e801:
- mov ah,88h ; Query high memory (oldest)
- int 15h
- cmp ax,14*1024 ; Don't trust memory >15M
- jna e801_hole
- mov ax,14*1024
-e801_hole:
- and eax,0ffffh
- shl eax,10 ; Convert from kilobytes
-got_highmem_add1mb:
- add eax,(1 << 20) ; First megabyte
-got_highmem:
- sub eax,HIGHMEM_SLOP
- mov [HighMemSize],eax
-
-;
-; Construct the command line (append options have already been copied)
-;
-construct_cmdline:
- mov di,[CmdLinePtr]
- mov si,boot_image ; BOOT_IMAGE=
- mov cx,boot_image_len
- rep movsb
- mov si,KernelCName ; Unmangled kernel name
- mov cx,[KernelCNameLen]
- rep movsb
- mov al,' ' ; Space
- stosb
-
+; Handle "ipappend" option
+%define HAVE_SPECIAL_APPEND
+%macro SPECIAL_APPEND 0
mov al,[IPAppend] ; ip=
and al,al
jz .noipappend
@@ -1318,497 +1167,24 @@ construct_cmdline:
mov al,' '
stosb
.noipappend:
- mov si,[CmdOptPtr] ; Options from user input
- mov cx,(kern_cmd_len+3) >> 2
- rep movsd
-;
-; Scan through the command line for anything that looks like we might be
-; interested in. The original version of this code automatically assumed
-; the first option was BOOT_IMAGE=, but that is no longer certain.
-;
- mov si,cmd_line_here
- mov byte [initrd_flag],0
- push es ; Set DS <- real_mode_seg
- pop ds
-get_next_opt: lodsb
- and al,al
- jz near cmdline_end
- cmp al,' '
- jbe get_next_opt
- dec si
- mov eax,[si]
- cmp eax,'vga='
- je is_vga_cmd
- cmp eax,'mem='
- je is_mem_cmd
- push es ; Save ES -> real_mode_seg
- push cs
- pop es ; Set ES <- normal DS
- mov di,initrd_cmd
- mov cx,initrd_cmd_len
- repe cmpsb
- jne not_initrd
- mov di,InitRD
- push si ; mangle_dir mangles si
- call mangle_name ; Mangle ramdisk name
- pop si
- cmp byte [es:InitRD],0 ; Null filename?
- seta byte [es:initrd_flag] ; Set flag if not
-not_initrd: pop es ; Restore ES -> real_mode_seg
-skip_this_opt: lodsb ; Load from command line
- cmp al,' '
- ja skip_this_opt
- dec si
- jmp short get_next_opt
-is_vga_cmd:
- add si,byte 4
- mov eax,[si]
- mov bx,-1
- cmp eax, 'norm' ; vga=normal
- je vc0
- and eax,0ffffffh ; 3 bytes
- mov bx,-2
- cmp eax, 'ext' ; vga=ext
- je vc0
- mov bx,-3
- cmp eax, 'ask' ; vga=ask
- je vc0
- call parseint ; vga=<number>
- jc skip_this_opt ; Not an integer
-vc0: mov [bs_vidmode],bx ; Set video mode
- jmp short skip_this_opt
-is_mem_cmd:
- add si,byte 4
- call parseint
- jc skip_this_opt ; Not an integer
- sub ebx,HIGHMEM_SLOP
- mov [cs:HighMemSize],ebx
- jmp short skip_this_opt
-cmdline_end:
- push cs ; Restore standard DS
- pop ds
- sub si,cmd_line_here
- mov [CmdLineLen],si ; Length including final null
-;
-; Now check if we have a large kernel, which needs to be loaded high
-;
- mov dword [RamdiskMax], HIGHMEM_MAX ; Default initrd limit
- cmp dword [es:su_header],HEADER_ID ; New setup code ID
- jne near old_kernel ; Old kernel, load low
- cmp word [es:su_version],0200h ; Setup code version 2.0
- jb near old_kernel ; Old kernel, load low
- cmp word [es:su_version],0201h ; Version 2.01+?
- jb new_kernel ; If 2.00, skip this step
- mov word [es:su_heapend],linux_stack ; Set up the heap
- or byte [es:su_loadflags],80h ; Let the kernel know we care
- cmp word [es:su_version],0203h ; Version 2.03+?
- jb new_kernel ; Not 2.03+
- mov eax,[es:su_ramdisk_max]
- mov [RamdiskMax],eax ; Set the ramdisk limit
-
-;
-; We definitely have a new-style kernel. Let the kernel know who we are,
-; and that we are clueful
-;
-new_kernel:
- mov byte [es:su_loader],my_id ; Show some ID
- movzx ax,byte [es:bs_setupsecs] ; Variable # of setup sectors
- mov [SetupSecs],ax
-;
-; About to load the kernel. This is a modern kernel, so use the boot flags
-; we were provided.
-;
- mov al,[es:su_loadflags]
- mov [LoadFlags],al
-;
-; Load the kernel. We always load it at 100000h even if we're supposed to
-; load it "low"; for a "low" load we copy it down to low memory right before
-; jumping to it.
-;
-read_kernel:
- mov si,KernelCName ; Print kernel name part of
- call cwritestr ; "Loading" message
- mov si,dotdot_msg ; Print dots
- call cwritestr
-
- mov eax,[HighMemSize]
- sub eax,100000h ; Load address
- cmp eax,[KernelSize]
- jb near no_high_mem ; Not enough high memory
-;
-; Move the stuff beyond the setup code to high memory at 100000h
-;
- movzx esi,word [SetupSecs] ; Setup sectors
- inc esi ; plus 1 boot sector
- shl esi,9 ; Convert to bytes
- mov ecx,8000h ; 32K
- sub ecx,esi ; Number of bytes to copy
- push ecx
- shr ecx,2 ; Convert to dwords
- add esi,(real_mode_seg << 4) ; Pointer to source
- mov edi,100000h ; Copy to address 100000h
- call bcopy ; Transfer to high memory
-
- ; On exit EDI -> where to load the rest
-
- mov si,dot_msg ; Progress report
- call cwritestr
- call abort_check
-
- pop ecx ; Number of bytes in the initial portion
- pop si ; Restore file handle/cluster pointer
- mov eax,[KernelSize]
- sub eax,ecx ; Amount of kernel left over
- jbe high_load_done ; Zero left (tiny kernel)
-
- call load_high ; Copy the file
-
-high_load_done:
- mov ax,real_mode_seg ; Set to real mode seg
- mov es,ax
-
- mov si,dot_msg
- call cwritestr
-
-;
-; Now see if we have an initial RAMdisk; if so, do requisite computation
-; We know we have a new kernel; the old_kernel code already will have objected
-; if we tried to load initrd using an old kernel
-;
-load_initrd:
- test byte [initrd_flag],1
- jz near nk_noinitrd
- push es ; ES->real_mode_seg
- push ds
- pop es ; We need ES==DS
- mov si,InitRD
- mov di,InitRDCName
- call unmangle_name ; Create human-readable name
- sub di,InitRDCName
- mov [InitRDCNameLen],di
- mov di,InitRD
- call searchdir ; Look for it in directory
- pop es
- jz initrd_notthere
- mov [es:su_ramdisklen1],ax ; Ram disk length
- mov [es:su_ramdisklen2],dx
- mov edx,[HighMemSize] ; End of memory
- dec edx
- mov eax,[RamdiskMax] ; Highest address allowed by kernel
- cmp edx,eax
- jna memsize_ok
- mov edx,eax ; Adjust to fit inside limit
-memsize_ok:
- inc edx
- xor dx,dx ; Round down to 64K boundary
- sub edx,[es:su_ramdisklen] ; Subtract size of ramdisk
- xor dx,dx ; Round down to 64K boundary
- mov [es:su_ramdiskat],edx ; Load address
- call loadinitrd ; Load initial ramdisk
- jmp short initrd_end
-
-initrd_notthere:
- mov si,err_noinitrd
- call cwritestr
- mov si,InitRDCName
- call cwritestr
- mov si,crlf_msg
- jmp abort_load
-
-no_high_mem: mov si,err_nohighmem ; Error routine
- jmp abort_load
-
-initrd_end:
-nk_noinitrd:
-;
-; Abandon hope, ye that enter here! We do no longer permit aborts.
-;
- call abort_check ; Last chance!!
-
- mov si,ready_msg
- call cwritestr
+%endmacro
- call vgaclearmode ; We can't trust ourselves after this
-;
; Unload PXE stack
-;
+%define HAVE_UNLOAD_PREP
+%macro UNLOAD_PREP 0
call unload_pxe
cli
xor ax,ax
mov ss,ax
- mov sp,7C00h ; Set up a more normal stack
-
-;
-; Now, if we were supposed to load "low", copy the kernel down to 10000h
-; and the real mode stuff to 90000h. We assume that all bzImage kernels are
-; capable of starting their setup from a different address.
-;
- mov ax,real_mode_seg
- mov fs,ax
+ mov sp,7C00h ; Set up a conventional stack
+%endmacro
-;
-; Copy command line. Unfortunately, the kernel boot protocol requires
-; the command line to exist in the 9xxxxh range even if the rest of the
-; setup doesn't.
-;
- cli ; In case of hooked interrupts
- test byte [LoadFlags],LOAD_HIGH
- jz need_high_cmdline
- cmp word [fs:su_version],0202h ; Support new cmdline protocol?
- jb need_high_cmdline
- ; New cmdline protocol
- ; Store 32-bit (flat) pointer to command line
- mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4) + cmd_line_here
- jmp short in_proper_place
+%include "runkernel.inc"
-need_high_cmdline:
;
-; Copy command line up to 90000h
+; COMBOOT-loading code
;
- mov ax,9000h
- mov es,ax
- mov si,cmd_line_here
- mov di,si
- mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic
- mov [fs:kern_cmd_offset],di ; Store pointer
-
- mov cx,[CmdLineLen]
- add cx,byte 3
- shr cx,2 ; Convert to dwords
- fs rep movsd
-
- push fs
- pop es
-
- test byte [LoadFlags],LOAD_HIGH
- jnz in_proper_place ; If high load, we're done
-
-;
-; Loading low; we can't assume it's safe to run in place.
-;
-; Copy real_mode stuff up to 90000h
-;
- mov ax,9000h
- mov es,ax
- mov cx,[SetupSecs]
- inc cx ; Setup + boot sector
- shl cx,7 ; Sectors -> dwords
- xor si,si
- xor di,di
- fs rep movsd ; Copy setup + boot sector
-;
-; Some kernels in the 1.2 ballpark but pre-bzImage have more than 4
-; setup sectors, but the boot protocol had not yet been defined. They
-; rely on a signature to figure out if they need to copy stuff from
-; the "protected mode" kernel area. Unfortunately, we used that area
-; as a transfer buffer, so it's going to find the signature there.
-; Hence, zero the low 32K beyond the setup area.
-;
- mov di,[SetupSecs]
- inc di ; Setup + boot sector
- mov cx,32768/512 ; Sectors/32K
- sub cx,di ; Remaining sectors
- shl di,9 ; Sectors -> bytes
- shl cx,7 ; Sectors -> dwords
- xor eax,eax
- rep stosd ; Clear region
-;
-; Copy the kernel down to the "low" location
-;
- mov ecx,[KernelSize]
- add ecx,3 ; Round upwards
- shr ecx,2 ; Bytes -> dwords
- mov esi,100000h
- mov edi,10000h
- call bcopy
-
-;
-; Now everything is where it needs to be...
-;
-; When we get here, es points to the final segment, either
-; 9000h or real_mode_seg
-;
-in_proper_place:
-
-;
-; If the default root device is set to FLOPPY (0000h), change to
-; /dev/fd0 (0200h)
-;
- cmp word [es:bs_rootdev],byte 0
- jne root_not_floppy
- mov word [es:bs_rootdev],0200h
-root_not_floppy:
-;
-; Copy the disk table to high memory, then re-initialize the floppy
-; controller
-;
-; This needs to be moved before the copy
-;
-%if 0
- push ds
- push bx
- lds si,[fdctab]
- mov di,linux_fdctab
- mov cx,3 ; 12 bytes
- push di
- rep movsd
- pop di
- mov [fdctab1],di ; Save new floppy tab pos
- mov [fdctab2],es
- xor ax,ax
- xor dx,dx
- int 13h
- pop bx
- pop ds
-%endif
-;
-; Linux wants the floppy motor shut off before starting the kernel,
-; at least bootsect.S seems to imply so
-;
-kill_motor:
- mov dx,03F2h
- xor al,al
- call slow_out
-;
-; If we're debugging, wait for a keypress so we can read any debug messages
-;
-%ifdef debug
- xor ax,ax
- int 16h
-%endif
-;
-; Set up segment registers and the Linux real-mode stack
-; Note: es == the real mode segment
-;
- cli
- mov bx,es
- mov ds,bx
- mov fs,bx
- mov gs,bx
- mov ss,bx
- mov sp,linux_stack
-;
-; We're done... now RUN THAT KERNEL!!!!
-; Setup segment == real mode segment + 020h; we need to jump to offset
-; zero in the real mode segment.
-;
- add bx,020h
- push bx
- push word 0h
- retf
-
-;
-; Load an older kernel. Older kernels always have 4 setup sectors, can't have
-; initrd, and are always loaded low.
-;
-old_kernel:
- test byte [initrd_flag],1 ; Old kernel can't have initrd
- jz load_old_kernel
- mov si,err_oldkernel
- jmp abort_load
-load_old_kernel:
- mov word [SetupSecs],4 ; Always 4 setup sectors
- mov byte [LoadFlags],0 ; Always low
- jmp read_kernel
-
-;
-; Load a COMBOOT image. A COMBOOT image is basically a DOS .COM file,
-; except that it may, of course, not contain any DOS system calls. We
-; do, however, allow the execution of INT 20h to return to SYSLINUX.
-;
-is_comboot_image:
- and dx,dx
- jnz near comboot_too_large
- cmp ax,0ff00h ; Max size in bytes
- jae comboot_too_large
-
- ;
- ; Set up the DOS vectors in the IVT (INT 20h-3fh)
- ;
- mov dword [4*0x20],comboot_return ; INT 20h vector
- mov eax,comboot_bogus
- mov di,4*0x21
- mov cx,31 ; All remaining DOS vectors
- rep stosd
-
- mov cx,comboot_seg
- mov es,cx
-
- mov bx,100h ; Load at <seg>:0100h
-
- mov cx,[ClustPerMoby] ; Absolute maximum # of clusters
- call getfssec
-
- xor di,di
- mov cx,64 ; 256 bytes (size of PSP)
- xor eax,eax ; Clear PSP
- rep stosd
-
- mov word [es:0], 020CDh ; INT 20h instruction
- ; First non-free paragraph
- mov word [es:02h], comboot_seg+1000h
-
- ; Copy the command line from high memory
- mov cx,125 ; Max cmdline len (minus space and CR)
- mov si,[CmdOptPtr]
- mov di,081h ; Offset in PSP for command line
- mov al,' ' ; DOS command lines begin with a space
- stosb
-
-comboot_cmd_cp: lodsb
- and al,al
- jz comboot_end_cmd
- stosb
- loop comboot_cmd_cp
-comboot_end_cmd: mov al,0Dh ; CR after last character
- stosb
- mov al,126 ; Include space but not CR
- sub al,cl
- mov [es:80h], al ; Store command line length
-
- mov [SavedSSSP],sp
- mov ax,ss ; Save away SS:SP
- mov [SavedSSSP+2],ax
-
- call vgaclearmode ; Reset video
-
- mov ax,es
- mov ds,ax
- mov ss,ax
- xor sp,sp
- push word 0 ; Return to address 0 -> exit
-
- jmp comboot_seg:100h ; Run it
-
-; Looks like a COMBOOT image but too large
-comboot_too_large:
- mov si,err_comlarge
- call cwritestr
-cb_enter: jmp enter_command
-
-; Proper return vector
-comboot_return: cli ; Don't trust anyone
- xor ax,ax
- mov ds,ax
- mov es,ax
- lss sp,[SavedSSSP]
- sti
- cld
- jmp short cb_enter
-
-; Attempted to execute DOS system call
-comboot_bogus: cli ; Don't trust anyone
- xor ax,ax
- mov ds,ax
- mov es,ax
- lss sp,[SavedSSSP]
- sti
- cld
- mov si,KernelCName
- call cwritestr
- mov si,err_notdos
- call cwritestr
- jmp short cb_enter
+%include "comboot.inc"
;
; Load a boot sector
@@ -1840,424 +1216,6 @@ local_boot:
retf ; Return to PXE
;
-; 32-bit bcopy routine for real mode
-;
-; We enter protected mode, set up a flat 32-bit environment, run rep movsd
-; and then exit. IMPORTANT: This code assumes cs == 0.
-;
-; This code is probably excessively anal-retentive in its handling of
-; segments, but this stuff is painful enough as it is without having to rely
-; on everything happening "as it ought to."
-;
- align 4
-bcopy_gdt: dw bcopy_gdt_size-1 ; Null descriptor - contains GDT
- dd bcopy_gdt ; pointer for LGDT instruction
- dw 0
- dd 0000ffffh ; Code segment, use16, readable,
- dd 00009b00h ; present, dpl 0, cover 64K
- dd 0000ffffh ; Data segment, use16, read/write,
- dd 008f9300h ; present, dpl 0, cover all 4G
- dd 0000ffffh ; Data segment, use16, read/write,
- dd 00009300h ; present, dpl 0, cover 64K
-bcopy_gdt_size: equ $-bcopy_gdt
-
-bcopy: push eax
- pushf ; Saves, among others, the IF flag
- push gs
- push fs
- push ds
- push es
- mov [cs:SavedSSSP],sp
- mov ax,ss
- mov [cs:SavedSSSP+2],ax
-
- cli
- call enable_a20
-
- o32 lgdt [cs:bcopy_gdt]
- mov eax,cr0
- or al,1
- mov cr0,eax ; Enter protected mode
- jmp 08h:.in_pm
-
-.in_pm: mov ax,10h ; Data segment selector
- mov es,ax
- mov ds,ax
-
- mov al,18h ; "Real-mode-like" data segment
- mov ss,ax
- mov fs,ax
- mov gs,ax
-
- a32 rep movsd ; Do our business
-
- mov es,ax ; Set to "real-mode-like"
- mov ds,ax
-
- mov eax,cr0
- and al,~1
- mov cr0,eax ; Disable protected mode
- jmp 0:.in_rm
-
-.in_rm: ; Back in real mode
- lss sp,[cs:SavedSSSP]
- pop es
- pop ds
- pop fs
- pop gs
- call disable_a20
-
- popf ; Re-enables interrupts
- pop eax
- ret
-
-;
-; Routines to enable and disable (yuck) A20. These routines are gathered
-; from tips from a couple of sources, including the Linux kernel and
-; http://www.x86.org/. The need for the delay to be as large as given here
-; is indicated by Donnie Barnes of RedHat, the problematic system being an
-; IBM ThinkPad 760EL.
-;
-; We typically toggle A20 twice for every 64K transferred.
-;
-%define io_delay call _io_delay
-%define IO_DELAY_PORT 80h ; Invalid port (we hope!)
-%define disable_wait 32 ; How long to wait for a disable
-
-%define A20_DUNNO 0 ; A20 type unknown
-%define A20_NONE 1 ; A20 always on?
-%define A20_BIOS 2 ; A20 BIOS enable
-%define A20_KBC 3 ; A20 through KBC
-%define A20_FAST 4 ; A20 through port 92h
-
-slow_out: out dx, al ; Fall through
-
-_io_delay: out IO_DELAY_PORT,al
- out IO_DELAY_PORT,al
- ret
-
-enable_a20:
- pushad
- mov byte [cs:A20Tries],255 ; Times to try to make this work
-
-try_enable_a20:
-;
-; Flush the caches
-;
-; call try_wbinvd
-
-;
-; If the A20 type is known, jump straight to type
-;
- mov bp,[cs:A20Type]
- add bp,bp ; Convert to word offset
- jmp word [cs:bp+A20List]
-
-;
-; First, see if we are on a system with no A20 gate
-;
-a20_dunno:
-a20_none:
- mov byte [cs:A20Type], A20_NONE
- call a20_test
- jnz a20_done
-
-;
-; Next, try the BIOS (INT 15h AX=2401h)
-;
-a20_bios:
- mov byte [cs:A20Type], A20_BIOS
- mov ax,2401h
- pushf ; Some BIOSes muck with IF
- int 15h
- popf
-
- call a20_test
- jnz a20_done
-
-;
-; Enable the keyboard controller A20 gate
-;
-a20_kbc:
- mov dl, 1 ; Allow early exit
- call empty_8042
- jnz a20_done ; A20 live, no need to use KBC
-
- mov byte [cs:A20Type], A20_KBC ; Starting KBC command sequence
-
- mov al,0D1h ; Command write
- out 064h, al
- call empty_8042_uncond
-
- mov al,0DFh ; A20 on
- out 060h, al
- call empty_8042_uncond
-
- ; Verify that A20 actually is enabled. Do that by
- ; observing a word in low memory and the same word in
- ; the HMA until they are no longer coherent. Note that
- ; we don't do the same check in the disable case, because
- ; we don't want to *require* A20 masking (SYSLINUX should
- ; work fine without it, if the BIOS does.)
-.kbc_wait: push cx
- xor cx,cx
-.kbc_wait_loop:
- call a20_test
- jnz a20_done_pop
- loop .kbc_wait_loop
-
- pop cx
-;
-; Running out of options here. Final attempt: enable the "fast A20 gate"
-;
-a20_fast:
- mov byte [cs:A20Type], A20_FAST ; Haven't used the KBC yet
- in al, 092h
- or al,02h
- and al,~01h ; Don't accidentally reset the machine!
- out 092h, al
-
-.fast_wait: push cx
- xor cx,cx
-.fast_wait_loop:
- call a20_test
- jnz a20_done_pop
- loop .fast_wait_loop
-
- pop cx
-
-;
-; Oh bugger. A20 is not responding. Try frobbing it again; eventually give up
-; and report failure to the user.
-;
-
-
- dec byte [cs:A20Tries]
- jnz try_enable_a20
-
- mov si, err_a20
- jmp abort_load
-;
-; A20 unmasked, proceed...
-;
-a20_done_pop: pop cx
-a20_done: popad
- ret
-
-;
-; This routine tests if A20 is enabled (ZF = 0). This routine
-; must not destroy any register contents.
-;
-a20_test:
- push es
- push cx
- push ax
- mov cx,0FFFFh ; HMA = segment 0FFFFh
- mov es,cx
- mov cx,32 ; Loop count
- mov ax,[cs:A20Test]
-.a20_wait: inc ax
- mov [cs:A20Test],ax
- io_delay ; Serialize, and fix delay
- cmp ax,[es:A20Test+10h]
- loopz .a20_wait
-.a20_done: pop ax
- pop cx
- pop es
- ret
-
-disable_a20:
- pushad
-;
-; Flush the caches
-;
-; call try_wbinvd
-
- mov bp,[cs:A20Type]
- add bp,bp ; Convert to word offset
- jmp word [cs:bp+A20DList]
-
-a20d_bios:
- mov ax,2400h
- pushf ; Some BIOSes muck with IF
- int 15h
- popf
- jmp short a20d_snooze
-
-;
-; Disable the "fast A20 gate"
-;
-a20d_fast:
- in al, 092h
- and al,~03h
- out 092h, al
- jmp short a20d_snooze
-
-;
-; Disable the keyboard controller A20 gate
-;
-a20d_kbc:
- call empty_8042_uncond
- mov al,0D1h
- out 064h, al ; Command write
- call empty_8042_uncond
- mov al,0DDh ; A20 off
- out 060h, al
- call empty_8042_uncond
- ; Wait a bit for it to take effect
-a20d_snooze:
- push cx
- mov cx, disable_wait
-.delayloop: call a20_test
- jz .disabled
- loop .delayloop
-.disabled: pop cx
-a20d_dunno:
-a20d_none:
- popad
- ret
-
-;
-; Routine to empty the 8042 KBC controller. If dl != 0
-; then we will test A20 in the loop and exit if A20 is
-; suddenly enabled.
-;
-empty_8042_uncond:
- xor dl,dl
-empty_8042:
- call a20_test
- jz .a20_on
- and dl,dl
- jnz .done
-.a20_on: io_delay
- in al, 064h ; Status port
- test al,1
- jz .no_output
- io_delay
- in al, 060h ; Read input
- jmp short empty_8042
-.no_output:
- test al,2
- jnz empty_8042
- io_delay
-.done: ret
-
-;
-; WBINVD instruction; gets auto-eliminated on 386 CPUs
-;
-try_wbinvd:
- wbinvd
- ret
-
-;
-; Load RAM disk into high memory
-;
-; Need to be set:
-; su_ramdiskat - Where in memory to load
-; su_ramdisklen - Size of file
-; SI - initrd filehandle/cluster pointer
-;
-loadinitrd:
- push es ; Save ES on entry
- mov ax,real_mode_seg
- mov es,ax
- mov edi,[es:su_ramdiskat] ; initrd load address
- push si
- mov si,crlfloading_msg ; Write "Loading "
- call cwritestr
- mov si,InitRDCName ; Write ramdisk name
- call cwritestr
- mov si,dotdot_msg ; Write dots
- call cwritestr
- pop si
-
- mov eax,[es:su_ramdisklen]
- call load_high ; Load the file
-
- call crlf
- pop es ; Restore original ES
- ret
-
-;
-; load_high: loads (the remainder of) a file into high memory.
-; This routine prints dots for each 64K transferred, and
-; calls abort_check periodically.
-;
-; The xfer_buf_seg is used as a bounce buffer.
-;
-; The input address (EDI) should be dword aligned, and the final
-; dword written is padded with zeroes if necessary.
-;
-; Inputs: SI = file handle/cluster pointer
-; EDI = target address in high memory
-; EAX = size of remaining file in bytes
-;
-; Outputs: SI = file handle/cluster pointer
-; EDI = first untouched address (not including padding)
-;
-load_high:
- push es
-
- mov bx,xfer_buf_seg
- mov es,bx
-
-.read_loop:
- and si,si ; If SI == 0 then we have end of file
- jz .eof
- push si
- mov si,dot_msg
- call cwritestr
- pop si
- call abort_check
-
- push eax ; <A> Total bytes to transfer
- cmp eax,(1 << 16) ; Max 64K in one transfer
- jna .size_ok
- mov eax,(1 << 16)
-.size_ok:
- xor edx,edx
- push eax ; <B> Bytes transferred this chunk
- movzx ecx,word [ClustSize]
- div ecx ; Convert to clusters
- ; Round up...
- add edx,byte -1 ; Sets CF if EDX >= 1
- adc eax,byte 0 ; Add 1 to EAX if CF set
-
- ; Now (e)ax contains the number of clusters to get
- push edi ; <C> Target buffer
- mov cx,ax
- xor bx,bx ; ES:0
- call getfssec ; Load the data into xfer_buf_seg
- pop edi ; <C> Target buffer
- pop ecx ; <B> Byte count this round
- push ecx ; <B> Byte count this round
- push edi ; <C> Target buffer
-.fix_slop:
- test cl,3
- jz .noslop
- ; The last dword fractional - pad with zeroes
- ; Zero-padding is critical for multi-file initramfs.
- mov byte [es:ecx],0
- inc ecx
- jmp short .fix_slop
-.noslop:
- shr ecx,2 ; Convert to dwords
- push esi ; <D> File handle/cluster pointer
- mov esi,(xfer_buf_seg << 4) ; Source address
- call bcopy ; Copy to high memory
- pop esi ; <D> File handle/cluster pointer
- pop edi ; <C> Target buffer
- pop ecx ; <B> Byte count this round
- pop eax ; <A> Total bytes to transfer
- add edi,ecx
- sub eax,ecx
- jnz .read_loop ; More to read...
-
-.eof:
- pop es
- ret
-
-;
; abort_check: let the user abort with <ESC> or <Ctrl-C>
;
abort_check:
@@ -3324,6 +2282,8 @@ writestr equ cwritestr
%include "writehex.inc" ; Hexadecimal output
%include "parseconfig.inc" ; High-level config file handling
%include "parsecmd.inc" ; Low-level config file handling
+%include "bcopy32.inc" ; 32-bit bcopy
+%include "loadhigh.inc" ; Load a file into high memory
%include "font.inc" ; VGA font stuff
%include "graphics.inc" ; VGA graphics
@@ -3538,9 +2498,6 @@ ForcePrompt dw 0 ; Force prompt
AllowImplicit dw 1 ; Allow implicit kernels
SerialPort dw 0 ; Serial port base (or 0 for no serial port)
NextSocket dw 49152 ; Counter for allocating socket numbers
-A20List dw a20_dunno, a20_none, a20_bios, a20_kbc, a20_fast
-A20DList dw a20d_dunno, a20d_none, a20d_bios, a20d_kbc, a20d_fast
-A20Type dw A20_DUNNO ; A20 type unknown
VGAFontSize dw 16 ; Defaults to 16 byte font
UserFont db 0 ; Using a user-specified font
ScrollAttribute db 07h ; White on black (for text mode)
diff --git a/runkernel.inc b/runkernel.inc
new file mode 100644
index 00000000..cc1dfb1e
--- /dev/null
+++ b/runkernel.inc
@@ -0,0 +1,614 @@
+;; $Id$
+;; -----------------------------------------------------------------------
+;;
+;; Copyright 1994-2002 H. Peter Anvin - All Rights Reserved
+;;
+;; This program is free software; you can redistribute it and/or modify
+;; it under the terms of the GNU General Public License as published by
+;; the Free Software Foundation, Inc., 53 Temple Place Ste 330,
+;; Bostom MA 02111-1307, USA; either version 2 of the License, or
+;; (at your option) any later version; incorporated herein by reference.
+;;
+;; -----------------------------------------------------------------------
+
+;;
+;; runkernel.inc
+;;
+;; Common code for running a Linux kernel
+;;
+
+;
+; Hook macros, that may or may not be defined
+;
+%ifndef HAVE_SPECIAL_APPEND
+%macro SPECIAL_APPEND 0
+%endmacro
+%endif
+
+%ifndef HAVE_UNLOAD_PREP
+%macro UNLOAD_PREP 0
+%endmacro
+%endif
+
+;
+; A Linux kernel consists of three parts: boot sector, setup code, and
+; kernel code. The boot sector is never executed when using an external
+; booting utility, but it contains some status bytes that are necessary.
+;
+; First check that our kernel is at least 1K and less than 8M (if it is
+; more than 8M, we need to change the logic for loading it anyway...)
+;
+; We used to require the kernel to be 64K or larger, but it has gotten
+; popular to use the Linux kernel format for other things, which may
+; not be so large.
+;
+is_linux_kernel:
+ cmp dx,80h ; 8 megs
+ ja kernel_corrupt
+ and dx,dx
+ jnz kernel_sane
+ cmp ax,1024 ; Bootsect + 1 setup sect
+ jb near kernel_corrupt
+kernel_sane: push ax
+ push dx
+ push si
+ mov si,loading_msg
+ call cwritestr
+;
+; Now start transferring the kernel
+;
+ push word real_mode_seg
+ pop es
+
+ movzx eax,ax ; Fix this by using a 32-bit
+ shl edx,16 ; register for the kernel size
+ or eax,edx
+ mov [KernelSize],eax
+ xor edx,edx
+ div dword [ClustSize] ; # of clusters total
+ ; Round up...
+ add edx,byte -1 ; Sets CF if EDX >= 1
+ adc eax,byte 0 ; Add 1 to EAX if CF set
+ mov [KernelClust],eax
+
+;
+; Now, if we transfer these straight, we'll hit 64K boundaries. Hence we
+; have to see if we're loading more than 64K, and if so, load it step by
+; step.
+;
+
+;
+; Start by loading the bootsector/setup code, to see if we need to
+; do something funky. It should fit in the first 32K (loading 64K won't
+; work since we might have funny stuff up near the end of memory).
+; If we have larger than 32K clusters, yes, we're hosed.
+;
+ call abort_check ; Check for abort key
+ mov ecx,[ClustPerMoby]
+ shr ecx,1 ; Half a moby
+ cmp ecx,[KernelClust]
+ jna .normalkernel
+ mov ecx,[KernelClust]
+.normalkernel:
+ sub [KernelClust],ecx
+ xor bx,bx
+ pop si ; Cluster pointer on stack
+ call getfssec
+ cmp word [es:bs_bootsign],0AA55h
+ jne near kernel_corrupt ; Boot sec signature missing
+;
+; Get the BIOS' idea of what the size of high memory is.
+;
+ push si ; Save our cluster pointer!
+;
+; First, try INT 15:E820 (get BIOS memory map)
+;
+get_e820:
+ push es
+ xor ebx,ebx ; Start with first record
+ mov es,bx ; Need ES = DS = 0 for now
+ jmp short .do_e820 ; Skip "at end" check first time!
+.int_loop: and ebx,ebx ; If we're back at beginning...
+ jz no_e820 ; ... bail; nothing found
+.do_e820: mov eax,0000E820h
+ mov edx,534D4150h ; "SMAP" backwards
+ mov ecx,20
+ mov di,E820Buf
+ int 15h
+ jc no_e820
+ cmp eax,534D4150h
+ jne no_e820
+;
+; Look for a memory block starting at <= 1 MB and continuing upward
+;
+ cmp dword [E820Buf+4], byte 0
+ ja .int_loop ; Start >= 4 GB?
+ mov edx, (1 << 20)
+ sub edx, [E820Buf]
+ jb .int_loop ; Start >= 1 MB?
+ mov eax, 0FFFFFFFFh
+ cmp dword [E820Buf+12], byte 0
+ ja .huge ; Size >= 4 GB
+ mov eax, [E820Buf+8]
+.huge: sub eax, edx ; Adjust size to start at 1 MB
+ jbe .int_loop ; Completely below 1 MB?
+
+ ; Now EAX contains the size of memory 1 MB...up
+ cmp dword [E820Buf+16], byte 1
+ jne near err_nohighmem ; High memory isn't usable memory!!!!
+
+ ; We're good!
+ pop es
+ jmp short got_highmem_add1mb ; Still need to add low 1 MB
+
+;
+; INT 15:E820 failed. Try INT 15:E801.
+;
+no_e820: pop es
+
+ mov ax,0e801h ; Query high memory (semi-recent)
+ int 15h
+ jc no_e801
+ cmp ax,3c00h
+ ja no_e801 ; > 3C00h something's wrong with this call
+ jb e801_hole ; If memory hole we can only use low part
+
+ mov ax,bx
+ shl eax,16 ; 64K chunks
+ add eax,(16 << 20) ; Add first 16M
+ jmp short got_highmem
+
+;
+; INT 15:E801 failed. Try INT 15:88.
+;
+no_e801:
+ mov ah,88h ; Query high memory (oldest)
+ int 15h
+ cmp ax,14*1024 ; Don't trust memory >15M
+ jna e801_hole
+ mov ax,14*1024
+e801_hole:
+ and eax,0ffffh
+ shl eax,10 ; Convert from kilobytes
+got_highmem_add1mb:
+ add eax,(1 << 20) ; First megabyte
+got_highmem:
+%if HIGHMEM_SLOP != 0
+ sub eax,HIGHMEM_SLOP
+%endif
+ mov [HighMemSize],eax
+
+;
+; Construct the command line (append options have already been copied)
+;
+construct_cmdline:
+ mov di,[CmdLinePtr]
+ mov si,boot_image ; BOOT_IMAGE=
+ mov cx,boot_image_len
+ rep movsb
+ mov si,KernelCName ; Unmangled kernel name
+ mov cx,[KernelCNameLen]
+ rep movsb
+ mov al,' ' ; Space
+ stosb
+
+ SPECIAL_APPEND ; Module-specific hook
+
+ mov si,[CmdOptPtr] ; Options from user input
+ mov cx,(kern_cmd_len+3) >> 2
+ rep movsd
+
+;
+; Scan through the command line for anything that looks like we might be
+; interested in. The original version of this code automatically assumed
+; the first option was BOOT_IMAGE=, but that is no longer certain.
+;
+ mov si,cmd_line_here
+ mov byte [initrd_flag],0
+ push es ; Set DS <- real_mode_seg
+ pop ds
+get_next_opt: lodsb
+ and al,al
+ jz near cmdline_end
+ cmp al,' '
+ jbe get_next_opt
+ dec si
+ mov eax,[si]
+ cmp eax,'vga='
+ je is_vga_cmd
+ cmp eax,'mem='
+ je is_mem_cmd
+ push es ; Save ES -> real_mode_seg
+ push cs
+ pop es ; Set ES <- normal DS
+ mov di,initrd_cmd
+ mov cx,initrd_cmd_len
+ repe cmpsb
+ jne not_initrd
+ mov di,InitRD
+ push si ; mangle_dir mangles si
+ call mangle_name ; Mangle ramdisk name
+ pop si
+ cmp byte [es:InitRD],NULLFILE ; Null filename?
+ seta byte [es:initrd_flag] ; Set flag if not
+not_initrd: pop es ; Restore ES -> real_mode_seg
+skip_this_opt: lodsb ; Load from command line
+ cmp al,' '
+ ja skip_this_opt
+ dec si
+ jmp short get_next_opt
+is_vga_cmd:
+ add si,byte 4
+ mov eax,[si]
+ mov bx,-1
+ cmp eax, 'norm' ; vga=normal
+ je vc0
+ and eax,0ffffffh ; 3 bytes
+ mov bx,-2
+ cmp eax, 'ext' ; vga=ext
+ je vc0
+ mov bx,-3
+ cmp eax, 'ask' ; vga=ask
+ je vc0
+ call parseint ; vga=<number>
+ jc skip_this_opt ; Not an integer
+vc0: mov [bs_vidmode],bx ; Set video mode
+ jmp short skip_this_opt
+is_mem_cmd:
+ add si,byte 4
+ call parseint
+ jc skip_this_opt ; Not an integer
+%if HIGHMEM_SLOP != 0
+ sub ebx,HIGHMEM_SLOP
+%endif
+ mov [cs:HighMemSize],ebx
+ jmp short skip_this_opt
+cmdline_end:
+ push cs ; Restore standard DS
+ pop ds
+ sub si,cmd_line_here
+ mov [CmdLineLen],si ; Length including final null
+;
+; Now check if we have a large kernel, which needs to be loaded high
+;
+ mov dword [RamdiskMax], HIGHMEM_MAX ; Default initrd limit
+ cmp dword [es:su_header],HEADER_ID ; New setup code ID
+ jne near old_kernel ; Old kernel, load low
+ cmp word [es:su_version],0200h ; Setup code version 2.0
+ jb near old_kernel ; Old kernel, load low
+ cmp word [es:su_version],0201h ; Version 2.01+?
+ jb new_kernel ; If 2.00, skip this step
+ mov word [es:su_heapend],linux_stack ; Set up the heap
+ or byte [es:su_loadflags],80h ; Let the kernel know we care
+ cmp word [es:su_version],0203h ; Version 2.03+?
+ jb new_kernel ; Not 2.03+
+ mov eax,[es:su_ramdisk_max]
+ mov [RamdiskMax],eax ; Set the ramdisk limit
+
+;
+; We definitely have a new-style kernel. Let the kernel know who we are,
+; and that we are clueful
+;
+new_kernel:
+ mov byte [es:su_loader],my_id ; Show some ID
+ movzx ax,byte [es:bs_setupsecs] ; Variable # of setup sectors
+ mov [SetupSecs],ax
+;
+; About to load the kernel. This is a modern kernel, so use the boot flags
+; we were provided.
+;
+ mov al,[es:su_loadflags]
+ mov [LoadFlags],al
+;
+; Load the kernel. We always load it at 100000h even if we're supposed to
+; load it "low"; for a "low" load we copy it down to low memory right before
+; jumping to it.
+;
+read_kernel:
+ mov si,KernelCName ; Print kernel name part of
+ call cwritestr ; "Loading" message
+ mov si,dotdot_msg ; Print dots
+ call cwritestr
+
+ mov eax,[HighMemSize]
+ sub eax,100000h ; Load address
+ cmp eax,[KernelSize]
+ jb near no_high_mem ; Not enough high memory
+;
+; Move the stuff beyond the setup code to high memory at 100000h
+;
+ movzx esi,word [SetupSecs] ; Setup sectors
+ inc esi ; plus 1 boot sector
+ shl esi,9 ; Convert to bytes
+ mov ecx,8000h ; 32K
+ sub ecx,esi ; Number of bytes to copy
+ push ecx
+ shr ecx,2 ; Convert to dwords
+ add esi,(real_mode_seg << 4) ; Pointer to source
+ mov edi,100000h ; Copy to address 100000h
+ call bcopy ; Transfer to high memory
+
+ ; On exit EDI -> where to load the rest
+
+ mov si,dot_msg ; Progress report
+ call cwritestr
+ call abort_check
+
+ pop ecx ; Number of bytes in the initial portion
+ pop si ; Restore file handle/cluster pointer
+ mov eax,[KernelSize]
+ sub eax,ecx ; Amount of kernel left over
+ jbe high_load_done ; Zero left (tiny kernel)
+
+ call load_high ; Copy the file
+
+high_load_done:
+ mov ax,real_mode_seg ; Set to real mode seg
+ mov es,ax
+
+ mov si,dot_msg
+ call cwritestr
+
+;
+; Now see if we have an initial RAMdisk; if so, do requisite computation
+; We know we have a new kernel; the old_kernel code already will have objected
+; if we tried to load initrd using an old kernel
+;
+load_initrd:
+ test byte [initrd_flag],1
+ jz near nk_noinitrd
+ push es ; ES->real_mode_seg
+ push ds
+ pop es ; We need ES==DS
+ mov si,InitRD
+ mov di,InitRDCName
+ call unmangle_name ; Create human-readable name
+ sub di,InitRDCName
+ mov [InitRDCNameLen],di
+ mov di,InitRD
+ call searchdir ; Look for it in directory
+ pop es
+ jz initrd_notthere
+ mov [es:su_ramdisklen1],ax ; Ram disk length
+ mov [es:su_ramdisklen2],dx
+ mov edx,[HighMemSize] ; End of memory
+ dec edx
+ mov eax,[RamdiskMax] ; Highest address allowed by kernel
+ cmp edx,eax
+ jna memsize_ok
+ mov edx,eax ; Adjust to fit inside limit
+memsize_ok:
+ inc edx
+ xor dx,dx ; Round down to 64K boundary
+ sub edx,[es:su_ramdisklen] ; Subtract size of ramdisk
+ xor dx,dx ; Round down to 64K boundary
+ mov [es:su_ramdiskat],edx ; Load address
+ call loadinitrd ; Load initial ramdisk
+ jmp short initrd_end
+
+initrd_notthere:
+ mov si,err_noinitrd
+ call cwritestr
+ mov si,InitRDCName
+ call cwritestr
+ mov si,crlf_msg
+ jmp abort_load
+
+no_high_mem: mov si,err_nohighmem ; Error routine
+ jmp abort_load
+
+initrd_end:
+nk_noinitrd:
+;
+; Abandon hope, ye that enter here! We do no longer permit aborts.
+;
+ call abort_check ; Last chance!!
+
+ mov si,ready_msg
+ call cwritestr
+
+ call vgaclearmode ; We can't trust ourselves after this
+
+ UNLOAD_PREP ; Module-specific hook
+
+;
+; Now, if we were supposed to load "low", copy the kernel down to 10000h
+; and the real mode stuff to 90000h. We assume that all bzImage kernels are
+; capable of starting their setup from a different address.
+;
+ mov ax,real_mode_seg
+ mov fs,ax
+
+;
+; Copy command line. Unfortunately, the kernel boot protocol requires
+; the command line to exist in the 9xxxxh range even if the rest of the
+; setup doesn't.
+;
+ cli ; In case of hooked interrupts
+ test byte [LoadFlags],LOAD_HIGH
+ jz need_high_cmdline
+ cmp word [fs:su_version],0202h ; Support new cmdline protocol?
+ jb need_high_cmdline
+ ; New cmdline protocol
+ ; Store 32-bit (flat) pointer to command line
+ mov dword [fs:su_cmd_line_ptr],(real_mode_seg << 4) + cmd_line_here
+ jmp short in_proper_place
+
+need_high_cmdline:
+;
+; Copy command line up to 90000h
+;
+ mov ax,9000h
+ mov es,ax
+ mov si,cmd_line_here
+ mov di,si
+ mov [fs:kern_cmd_magic],word CMD_MAGIC ; Store magic
+ mov [fs:kern_cmd_offset],di ; Store pointer
+
+ mov cx,[CmdLineLen]
+ add cx,byte 3
+ shr cx,2 ; Convert to dwords
+ fs rep movsd
+
+ push fs
+ pop es
+
+ test byte [LoadFlags],LOAD_HIGH
+ jnz in_proper_place ; If high load, we're done
+
+;
+; Loading low; we can't assume it's safe to run in place.
+;
+; Copy real_mode stuff up to 90000h
+;
+ mov ax,9000h
+ mov es,ax
+ mov cx,[SetupSecs]
+ inc cx ; Setup + boot sector
+ shl cx,7 ; Sectors -> dwords
+ xor si,si
+ xor di,di
+ fs rep movsd ; Copy setup + boot sector
+;
+; Some kernels in the 1.2 ballpark but pre-bzImage have more than 4
+; setup sectors, but the boot protocol had not yet been defined. They
+; rely on a signature to figure out if they need to copy stuff from
+; the "protected mode" kernel area. Unfortunately, we used that area
+; as a transfer buffer, so it's going to find the signature there.
+; Hence, zero the low 32K beyond the setup area.
+;
+ mov di,[SetupSecs]
+ inc di ; Setup + boot sector
+ mov cx,32768/512 ; Sectors/32K
+ sub cx,di ; Remaining sectors
+ shl di,9 ; Sectors -> bytes
+ shl cx,7 ; Sectors -> dwords
+ xor eax,eax
+ rep stosd ; Clear region
+;
+; Copy the kernel down to the "low" location
+;
+ mov ecx,[KernelSize]
+ add ecx,3 ; Round upwards
+ shr ecx,2 ; Bytes -> dwords
+ mov esi,100000h
+ mov edi,10000h
+ call bcopy
+
+;
+; Now everything is where it needs to be...
+;
+; When we get here, es points to the final segment, either
+; 9000h or real_mode_seg
+;
+in_proper_place:
+
+;
+; If the default root device is set to FLOPPY (0000h), change to
+; /dev/fd0 (0200h)
+;
+ cmp word [es:bs_rootdev],byte 0
+ jne root_not_floppy
+ mov word [es:bs_rootdev],0200h
+root_not_floppy:
+;
+; Copy the disk table to high memory, then re-initialize the floppy
+; controller
+;
+; This needs to be moved before the copy
+;
+%if 0
+ push ds
+ push bx
+ lds si,[fdctab]
+ mov di,linux_fdctab
+ mov cx,3 ; 12 bytes
+ push di
+ rep movsd
+ pop di
+ mov [fdctab1],di ; Save new floppy tab pos
+ mov [fdctab2],es
+ xor ax,ax
+ xor dx,dx
+ int 13h
+ pop bx
+ pop ds
+%endif
+;
+; Linux wants the floppy motor shut off before starting the kernel,
+; at least bootsect.S seems to imply so
+;
+kill_motor:
+ mov dx,03F2h
+ xor al,al
+ call slow_out
+;
+; If we're debugging, wait for a keypress so we can read any debug messages
+;
+%ifdef debug
+ xor ax,ax
+ int 16h
+%endif
+;
+; Set up segment registers and the Linux real-mode stack
+; Note: es == the real mode segment
+;
+ cli
+ mov bx,es
+ mov ds,bx
+ mov fs,bx
+ mov gs,bx
+ mov ss,bx
+ mov sp,linux_stack
+;
+; We're done... now RUN THAT KERNEL!!!!
+; Setup segment == real mode segment + 020h; we need to jump to offset
+; zero in the real mode segment.
+;
+ add bx,020h
+ push bx
+ push word 0h
+ retf
+
+;
+; Load an older kernel. Older kernels always have 4 setup sectors, can't have
+; initrd, and are always loaded low.
+;
+old_kernel:
+ test byte [initrd_flag],1 ; Old kernel can't have initrd
+ jz load_old_kernel
+ mov si,err_oldkernel
+ jmp abort_load
+load_old_kernel:
+ mov word [SetupSecs],4 ; Always 4 setup sectors
+ mov byte [LoadFlags],0 ; Always low
+ jmp read_kernel
+
+;
+; Load RAM disk into high memory
+;
+; Need to be set:
+; su_ramdiskat - Where in memory to load
+; su_ramdisklen - Size of file
+; SI - initrd filehandle/cluster pointer
+;
+loadinitrd:
+ push es ; Save ES on entry
+ mov ax,real_mode_seg
+ mov es,ax
+ mov edi,[es:su_ramdiskat] ; initrd load address
+ push si
+ mov si,crlfloading_msg ; Write "Loading "
+ call cwritestr
+ mov si,InitRDCName ; Write ramdisk name
+ call cwritestr
+ mov si,dotdot_msg ; Write dots
+ call cwritestr
+ pop si
+
+ mov eax,[es:su_ramdisklen]
+ call load_high ; Load the file
+
+ call crlf
+ pop es ; Restore original ES
+ ret