mirror of
https://github.com/ipxe/ipxe
synced 2025-12-13 07:20:47 +03:00
Initial revision
This commit is contained in:
614
src/arch/i386/prefix/bImageprefix.S
Normal file
614
src/arch/i386/prefix/bImageprefix.S
Normal file
@@ -0,0 +1,614 @@
|
||||
/*
|
||||
Copyright (C) 2000, Entity Cyber, Inc.
|
||||
|
||||
Authors: Gary Byers (gb@thinguin.org)
|
||||
Marty Connor (mdc@thinguin.org)
|
||||
Eric Biederman (ebiederman@lnxi.com)
|
||||
|
||||
This code also derives a lot from arch/i386/boot/setup.S in
|
||||
the linux kernel.
|
||||
|
||||
This software may be used and distributed according to the terms
|
||||
of the GNU Public License (GPL), incorporated herein by reference.
|
||||
|
||||
Description:
|
||||
|
||||
This is just a little bit of code and data that can get prepended
|
||||
to an Etherboot ROM image in order to allow LILO to load the
|
||||
result as if it were a Linux kernel image.
|
||||
|
||||
A real Linux kernel image consists of a one-sector boot loader
|
||||
(to load the image from a floppy disk), followed a few sectors
|
||||
of setup code, followed by the kernel code itself. There's
|
||||
a table in the first sector (starting at offset 497) that indicates
|
||||
how many sectors of setup code follow the first sector and which
|
||||
contains some other parameters that aren't interesting in this
|
||||
case.
|
||||
|
||||
When LILO loads the sectors that comprise a kernel image, it doesn't
|
||||
execute the code in the first sector (since that code would try to
|
||||
load the image from a floppy disk.) The code in the first sector
|
||||
below doesn't expect to get executed (and prints an error message
|
||||
if it ever -is- executed.) LILO's only interested in knowing the
|
||||
number of setup sectors advertised in the table (at offset 497 in
|
||||
the first sector.)
|
||||
|
||||
Etherboot doesn't require much in the way of setup code.
|
||||
Historically, the Linux kernel required at least 4 sectors of
|
||||
setup code. Current versions of LILO look at the byte at
|
||||
offset 497 in the first sector to indicate how many sectors
|
||||
of setup code are contained in the image.
|
||||
|
||||
The setup code that is present here does a lot of things
|
||||
exactly the way the linux kernel does them instead of in
|
||||
ways more typical of etherboot. Generally this is so
|
||||
the code can be strongly compatible with the linux kernel.
|
||||
In addition the general etherboot technique of enabling the a20
|
||||
after we switch into protected mode does not work if etherboot
|
||||
is being loaded at 1MB.
|
||||
*/
|
||||
|
||||
.equ CR0_PE,1
|
||||
|
||||
#ifdef GAS291
|
||||
#define DATA32 data32;
|
||||
#define ADDR32 addr32;
|
||||
#define LJMPI(x) ljmp x
|
||||
#else
|
||||
#define DATA32 data32
|
||||
#define ADDR32 addr32
|
||||
/* newer GAS295 require #define LJMPI(x) ljmp *x */
|
||||
#define LJMPI(x) ljmp x
|
||||
#endif
|
||||
|
||||
/* Simple and small GDT entries for booting only */
|
||||
#define GDT_ENTRY_BOOT_CS 2
|
||||
#define GDT_ENTRY_BOOT_DS (GDT_ENTRY_BOOT_CS + 1)
|
||||
#define __BOOT_CS (GDT_ENTRY_BOOT_CS * 8)
|
||||
#define __BOOT_DS (GDT_ENTRY_BOOT_DS * 8)
|
||||
|
||||
|
||||
#define SETUPSECS 4 /* Minimal nr of setup-sectors */
|
||||
#define PREFIXSIZE ((SETUPSECS+1)*512)
|
||||
#define PREFIXPGH (PREFIXSIZE / 16 )
|
||||
#define BOOTSEG 0x07C0 /* original address of boot-sector */
|
||||
#define INITSEG 0x9000 /* we move boot here - out of the way */
|
||||
#define SETUPSEG 0x9020 /* setup starts here */
|
||||
#define SYSSEG 0x1000 /* system loaded at 0x10000 (65536). */
|
||||
|
||||
#define DELTA_INITSEG (SETUPSEG - INITSEG) /* 0x0020 */
|
||||
|
||||
/* Signature words to ensure LILO loaded us right */
|
||||
#define SIG1 0xAA55
|
||||
#define SIG2 0x5A5A
|
||||
|
||||
.text
|
||||
.code16
|
||||
.arch i386
|
||||
.org 0
|
||||
.section ".prefix", "ax", @progbits
|
||||
.globl _prefix
|
||||
_prefix:
|
||||
|
||||
/*
|
||||
This is a minimal boot sector. If anyone tries to execute it (e.g., if
|
||||
a .lilo file is dd'ed to a floppy), print an error message.
|
||||
*/
|
||||
|
||||
bootsector:
|
||||
jmp $BOOTSEG, $go - _prefix /* reload cs:ip to match relocation addr */
|
||||
go:
|
||||
movw $0x2000, %di /* 0x2000 is arbitrary value >= length
|
||||
of bootsect + room for stack */
|
||||
|
||||
movw $BOOTSEG, %ax
|
||||
movw %ax,%ds
|
||||
movw %ax,%es
|
||||
|
||||
cli
|
||||
movw %ax, %ss /* put stack at BOOTSEG:0x2000. */
|
||||
movw %di,%sp
|
||||
sti
|
||||
|
||||
movw $why_end-why, %cx
|
||||
movw $why - _prefix, %si
|
||||
|
||||
movw $0x0007, %bx /* page 0, attribute 7 (normal) */
|
||||
movb $0x0e, %ah /* write char, tty mode */
|
||||
prloop:
|
||||
lodsb
|
||||
int $0x10
|
||||
loop prloop
|
||||
freeze: jmp freeze
|
||||
|
||||
why: .ascii "This image cannot be loaded from a floppy disk.\r\n"
|
||||
why_end:
|
||||
|
||||
|
||||
.org 497
|
||||
setup_sects:
|
||||
.byte SETUPSECS
|
||||
root_flags:
|
||||
.word 0
|
||||
syssize:
|
||||
.word _verbatim_size_pgh - PREFIXPGH
|
||||
swap_dev:
|
||||
.word 0
|
||||
ram_size:
|
||||
.word 0
|
||||
vid_mode:
|
||||
.word 0
|
||||
root_dev:
|
||||
.word 0
|
||||
boot_flag:
|
||||
.word 0xAA55
|
||||
|
||||
/*
|
||||
We're now at the beginning of the second sector of the image -
|
||||
where the setup code goes.
|
||||
|
||||
We don't need to do too much setup for Etherboot.
|
||||
|
||||
This code gets loaded at SETUPSEG:0. It wants to start
|
||||
executing the Etherboot image that's loaded at SYSSEG:0 and
|
||||
whose entry point is SYSSEG:0.
|
||||
*/
|
||||
setup_code:
|
||||
jmp trampoline
|
||||
# This is the setup header, and it must start at %cs:2 (old 0x9020:2)
|
||||
|
||||
.ascii "HdrS" # header signature
|
||||
.word 0x0203 # header version number (>= 0x0105)
|
||||
# or else old loadlin-1.5 will fail)
|
||||
realmode_swtch: .word 0, 0 # default_switch, SETUPSEG
|
||||
start_sys_seg: .word SYSSEG # low load segment (obsolete)
|
||||
.word kernel_version - setup_code
|
||||
# pointing to kernel version string
|
||||
# above section of header is compatible
|
||||
# with loadlin-1.5 (header v1.5). Don't
|
||||
# change it.
|
||||
|
||||
type_of_loader: .byte 0 # = 0, old one (LILO, Loadlin,
|
||||
# Bootlin, SYSLX, bootsect...)
|
||||
# See Documentation/i386/boot.txt for
|
||||
# assigned ids
|
||||
|
||||
# flags, unused bits must be zero (RFU) bit within loadflags
|
||||
loadflags:
|
||||
LOADED_HIGH = 1 # If set, the kernel is loaded high
|
||||
CAN_USE_HEAP = 0x80 # If set, the loader also has set
|
||||
# heap_end_ptr to tell how much
|
||||
# space behind setup.S can be used for
|
||||
# heap purposes.
|
||||
# Only the loader knows what is free
|
||||
.byte LOADED_HIGH
|
||||
|
||||
setup_move_size: .word 0x8000 # size to move, when setup is not
|
||||
# loaded at 0x90000. We will move setup
|
||||
# to 0x90000 then just before jumping
|
||||
# into the kernel. However, only the
|
||||
# loader knows how much data behind
|
||||
# us also needs to be loaded.
|
||||
|
||||
code32_start: # here loaders can put a different
|
||||
# start address for 32-bit code.
|
||||
.long 0x100000 # 0x100000 = default for big kernel
|
||||
|
||||
ramdisk_image: .long 0 # address of loaded ramdisk image
|
||||
# Here the loader puts the 32-bit
|
||||
# address where it loaded the image.
|
||||
# This only will be read by the kernel.
|
||||
|
||||
ramdisk_size: .long 0 # its size in bytes
|
||||
|
||||
bootsect_kludge:
|
||||
.long 0 # obsolete
|
||||
|
||||
heap_end_ptr: .word 0 # (Header version 0x0201 or later)
|
||||
# space from here (exclusive) down to
|
||||
# end of setup code can be used by setup
|
||||
# for local heap purposes.
|
||||
|
||||
pad1: .word 0
|
||||
cmd_line_ptr: .long 0 # (Header version 0x0202 or later)
|
||||
# If nonzero, a 32-bit pointer
|
||||
# to the kernel command line.
|
||||
# The command line should be
|
||||
# located between the start of
|
||||
# setup and the end of low
|
||||
# memory (0xa0000), or it may
|
||||
# get overwritten before it
|
||||
# gets read. If this field is
|
||||
# used, there is no longer
|
||||
# anything magical about the
|
||||
# 0x90000 segment; the setup
|
||||
# can be located anywhere in
|
||||
# low memory 0x10000 or higher.
|
||||
|
||||
ramdisk_max: .long 0 # (Header version 0x0203 or later)
|
||||
# The highest safe address for
|
||||
# the contents of an initrd
|
||||
|
||||
trampoline: call start_of_setup
|
||||
trampoline_end:
|
||||
.space 1024
|
||||
# End of setup header #####################################################
|
||||
|
||||
start_of_setup:
|
||||
# Set %ds = %cs, we know that SETUPSEG = %cs at this point
|
||||
movw %cs, %ax # aka SETUPSEG
|
||||
movw %ax, %ds
|
||||
# Check signature at end of setup
|
||||
cmpw $SIG1, (setup_sig1 - setup_code)
|
||||
jne bad_sig
|
||||
|
||||
cmpw $SIG2, (setup_sig2 - setup_code)
|
||||
jne bad_sig
|
||||
|
||||
jmp good_sig1
|
||||
|
||||
# Routine to print asciiz string at ds:si
|
||||
prtstr:
|
||||
lodsb
|
||||
andb %al, %al
|
||||
jz fin
|
||||
|
||||
call prtchr
|
||||
jmp prtstr
|
||||
|
||||
fin: ret
|
||||
|
||||
# Part of above routine, this one just prints ascii al
|
||||
prtchr: pushw %ax
|
||||
pushw %cx
|
||||
movw $7,%bx
|
||||
movw $0x01, %cx
|
||||
movb $0x0e, %ah
|
||||
int $0x10
|
||||
popw %cx
|
||||
popw %ax
|
||||
ret
|
||||
|
||||
no_sig_mess: .string "No setup signature found ..."
|
||||
|
||||
good_sig1:
|
||||
jmp good_sig
|
||||
|
||||
# We now have to find the rest of the setup code/data
|
||||
bad_sig:
|
||||
movw %cs, %ax # SETUPSEG
|
||||
subw $DELTA_INITSEG, %ax # INITSEG
|
||||
movw %ax, %ds
|
||||
xorb %bh, %bh
|
||||
movb (497), %bl # get setup sect from bootsect
|
||||
subw $4, %bx # LILO loads 4 sectors of setup
|
||||
shlw $8, %bx # convert to words (1sect=2^8 words)
|
||||
movw %bx, %cx
|
||||
shrw $3, %bx # convert to segment
|
||||
addw $SYSSEG, %bx
|
||||
movw %bx, %cs:(start_sys_seg - setup_code)
|
||||
# Move rest of setup code/data to here
|
||||
movw $2048, %di # four sectors loaded by LILO
|
||||
subw %si, %si
|
||||
pushw %cs
|
||||
popw %es
|
||||
movw $SYSSEG, %ax
|
||||
movw %ax, %ds
|
||||
rep
|
||||
movsw
|
||||
movw %cs, %ax # aka SETUPSEG
|
||||
movw %ax, %ds
|
||||
cmpw $SIG1, (setup_sig1 - setup_code)
|
||||
jne no_sig
|
||||
|
||||
cmpw $SIG2, (setup_sig2 - setup_code)
|
||||
jne no_sig
|
||||
|
||||
jmp good_sig
|
||||
|
||||
no_sig:
|
||||
lea (no_sig_mess - setup_code), %si
|
||||
call prtstr
|
||||
|
||||
no_sig_loop:
|
||||
hlt
|
||||
jmp no_sig_loop
|
||||
|
||||
good_sig:
|
||||
cmpw $0, %cs:(realmode_swtch - setup_code)
|
||||
jz rmodeswtch_normal
|
||||
|
||||
lcall *%cs:(realmode_swtch - setup_code)
|
||||
jmp rmodeswtch_end
|
||||
|
||||
rmodeswtch_normal:
|
||||
pushw %cs
|
||||
call default_switch
|
||||
|
||||
rmodeswtch_end:
|
||||
# we get the code32 start address and modify the below 'jmpi'
|
||||
# (loader may have changed it)
|
||||
movl %cs:(code32_start - setup_code), %eax
|
||||
movl %eax, %cs:(code32 - setup_code)
|
||||
|
||||
# then we load the segment descriptors
|
||||
movw %cs, %ax # aka SETUPSEG
|
||||
movw %ax, %ds
|
||||
|
||||
#
|
||||
# Enable A20. This is at the very best an annoying procedure.
|
||||
# A20 code ported from SYSLINUX 1.52-1.63 by H. Peter Anvin.
|
||||
#
|
||||
|
||||
A20_TEST_LOOPS = 32 # Iterations per wait
|
||||
A20_ENABLE_LOOPS = 255 # Total loops to try
|
||||
|
||||
a20_try_loop:
|
||||
|
||||
# First, see if we are on a system with no A20 gate.
|
||||
a20_none:
|
||||
call a20_test
|
||||
jnz a20_done
|
||||
|
||||
# Next, try the BIOS (INT 0x15, AX=0x2401)
|
||||
a20_bios:
|
||||
movw $0x2401, %ax
|
||||
pushfl # Be paranoid about flags
|
||||
int $0x15
|
||||
popfl
|
||||
|
||||
call a20_test
|
||||
jnz a20_done
|
||||
|
||||
# Try enabling A20 through the keyboard controller
|
||||
a20_kbc:
|
||||
call empty_8042
|
||||
|
||||
call a20_test # Just in case the BIOS worked
|
||||
jnz a20_done # but had a delayed reaction.
|
||||
|
||||
movb $0xD1, %al # command write
|
||||
outb %al, $0x64
|
||||
call empty_8042
|
||||
|
||||
movb $0xDF, %al # A20 on
|
||||
outb %al, $0x60
|
||||
call empty_8042
|
||||
|
||||
# Wait until a20 really *is* enabled; it can take a fair amount of
|
||||
# time on certain systems; Toshiba Tecras are known to have this
|
||||
# problem.
|
||||
a20_kbc_wait:
|
||||
xorw %cx, %cx
|
||||
a20_kbc_wait_loop:
|
||||
call a20_test
|
||||
jnz a20_done
|
||||
loop a20_kbc_wait_loop
|
||||
|
||||
# Final attempt: use "configuration port A"
|
||||
a20_fast:
|
||||
inb $0x92, %al # Configuration Port A
|
||||
orb $0x02, %al # "fast A20" version
|
||||
andb $0xFE, %al # don't accidentally reset
|
||||
outb %al, $0x92
|
||||
|
||||
# Wait for configuration port A to take effect
|
||||
a20_fast_wait:
|
||||
xorw %cx, %cx
|
||||
a20_fast_wait_loop:
|
||||
call a20_test
|
||||
jnz a20_done
|
||||
loop a20_fast_wait_loop
|
||||
|
||||
# A20 is still not responding. Try frobbing it again.
|
||||
#
|
||||
decb (a20_tries - setup_code)
|
||||
jnz a20_try_loop
|
||||
|
||||
movw $(a20_err_msg - setup_code), %si
|
||||
call prtstr
|
||||
|
||||
a20_die:
|
||||
hlt
|
||||
jmp a20_die
|
||||
|
||||
a20_tries:
|
||||
.byte A20_ENABLE_LOOPS
|
||||
|
||||
a20_err_msg:
|
||||
.ascii "linux: fatal error: A20 gate not responding!"
|
||||
.byte 13, 10, 0
|
||||
|
||||
# If we get here, all is good
|
||||
a20_done:
|
||||
# Leave the idt alone
|
||||
|
||||
# set up gdt
|
||||
xorl %eax, %eax # Compute gdt_base
|
||||
movw %ds, %ax # (Convert %ds:gdt to a linear ptr)
|
||||
shll $4, %eax
|
||||
addl $(bImage_gdt - setup_code), %eax
|
||||
movl %eax, (bImage_gdt_48+2 - setup_code)
|
||||
DATA32 lgdt %ds:(bImage_gdt_48 - setup_code) # load gdt with whatever is
|
||||
# appropriate
|
||||
|
||||
# Switch to protected mode
|
||||
movl %cr0, %eax
|
||||
orb $CR0_PE, %al
|
||||
movl %eax, %cr0
|
||||
|
||||
DATA32 ljmp %ds:(code32 - setup_code)
|
||||
code32:
|
||||
.long 0x100000
|
||||
.word __BOOT_CS, 0
|
||||
|
||||
# Here's a bunch of information about your current kernel..
|
||||
kernel_version: .ascii "Etherboot "
|
||||
.ascii VERSION
|
||||
.byte 0
|
||||
|
||||
# This is the default real mode switch routine.
|
||||
# to be called just before protected mode transition
|
||||
default_switch:
|
||||
cli # no interrupts allowed !
|
||||
movb $0x80, %al # disable NMI for bootup
|
||||
# sequence
|
||||
outb %al, $0x70
|
||||
lret
|
||||
|
||||
# This routine tests whether or not A20 is enabled. If so, it
|
||||
# exits with zf = 0.
|
||||
#
|
||||
# The memory address used, 0x200, is the int $0x80 vector, which
|
||||
# should be safe.
|
||||
|
||||
A20_TEST_ADDR = 4*0x80
|
||||
|
||||
a20_test:
|
||||
pushw %cx
|
||||
pushw %ax
|
||||
xorw %cx, %cx
|
||||
movw %cx, %fs # Low memory
|
||||
decw %cx
|
||||
movw %cx, %gs # High memory area
|
||||
movw $A20_TEST_LOOPS, %cx
|
||||
movw %fs:(A20_TEST_ADDR), %ax
|
||||
pushw %ax
|
||||
a20_test_wait:
|
||||
incw %ax
|
||||
movw %ax, %fs:(A20_TEST_ADDR)
|
||||
call delay # Serialize and make delay constant
|
||||
cmpw %gs:(A20_TEST_ADDR+0x10), %ax
|
||||
loope a20_test_wait
|
||||
|
||||
popw %fs:(A20_TEST_ADDR)
|
||||
popw %ax
|
||||
popw %cx
|
||||
ret
|
||||
|
||||
|
||||
# This routine checks that the keyboard command queue is empty
|
||||
# (after emptying the output buffers)
|
||||
#
|
||||
# Some machines have delusions that the keyboard buffer is always full
|
||||
# with no keyboard attached...
|
||||
#
|
||||
# If there is no keyboard controller, we will usually get 0xff
|
||||
# to all the reads. With each IO taking a microsecond and
|
||||
# a timeout of 100,000 iterations, this can take about half a
|
||||
# second ("delay" == outb to port 0x80). That should be ok,
|
||||
# and should also be plenty of time for a real keyboard controller
|
||||
# to empty.
|
||||
#
|
||||
|
||||
empty_8042:
|
||||
pushl %ecx
|
||||
movl $100000, %ecx
|
||||
|
||||
empty_8042_loop:
|
||||
decl %ecx
|
||||
jz empty_8042_end_loop
|
||||
|
||||
call delay
|
||||
|
||||
inb $0x64, %al # 8042 status port
|
||||
testb $1, %al # output buffer?
|
||||
jz no_output
|
||||
|
||||
call delay
|
||||
inb $0x60, %al # read it
|
||||
jmp empty_8042_loop
|
||||
|
||||
no_output:
|
||||
testb $2, %al # is input buffer full?
|
||||
jnz empty_8042_loop # yes - loop
|
||||
empty_8042_end_loop:
|
||||
popl %ecx
|
||||
|
||||
|
||||
# Delay is needed after doing I/O
|
||||
delay:
|
||||
outb %al,$0x80
|
||||
ret
|
||||
|
||||
# Descriptor tables
|
||||
#
|
||||
# NOTE: The intel manual says gdt should be sixteen bytes aligned for
|
||||
# efficiency reasons. However, there are machines which are known not
|
||||
# to boot with misaligned GDTs, so alter this at your peril! If you alter
|
||||
# GDT_ENTRY_BOOT_CS (in asm/segment.h) remember to leave at least two
|
||||
# empty GDT entries (one for NULL and one reserved).
|
||||
#
|
||||
# NOTE: On some CPUs, the GDT must be 8 byte aligned. This is
|
||||
# true for the Voyager Quad CPU card which will not boot without
|
||||
# This directive. 16 byte aligment is recommended by intel.
|
||||
#
|
||||
.balign 16
|
||||
bImage_gdt:
|
||||
.fill GDT_ENTRY_BOOT_CS,8,0
|
||||
|
||||
.word 0xFFFF # 4Gb - (0x100000*0x1000 = 4Gb)
|
||||
.word 0 # base address = 0
|
||||
.word 0x9A00 # code read/exec
|
||||
.word 0x00CF # granularity = 4096, 386
|
||||
# (+5th nibble of limit)
|
||||
|
||||
.word 0xFFFF # 4Gb - (0x100000*0x1000 = 4Gb)
|
||||
.word 0 # base address = 0
|
||||
.word 0x9200 # data read/write
|
||||
.word 0x00CF # granularity = 4096, 386
|
||||
# (+5th nibble of limit)
|
||||
bImage_gdt_end:
|
||||
.balign 4
|
||||
|
||||
.word 0 # alignment byte
|
||||
bImage_idt_48:
|
||||
.word 0 # idt limit = 0
|
||||
.long 0 # idt base = 0L
|
||||
|
||||
.word 0 # alignment byte
|
||||
bImage_gdt_48:
|
||||
.word bImage_gdt_end - bImage_gdt - 1 # gdt limit
|
||||
.long bImage_gdt_48 - setup_code # gdt base (filled in later)
|
||||
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
int $0x19 /* should try to boot machine */
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
|
||||
|
||||
.org (PREFIXSIZE - 4)
|
||||
# Setup signature -- must be last
|
||||
setup_sig1: .word SIG1
|
||||
setup_sig2: .word SIG2
|
||||
/* Etherboot expects to be contiguous in memory once loaded.
|
||||
* The linux bImage protocol does not do this, but since we
|
||||
* don't need any information that's left in the prefix, it
|
||||
* doesn't matter: we just have to ensure that we make it to _start
|
||||
*
|
||||
* protected_start will live at 0x100000 and it will be the
|
||||
* the first code called as we enter protected mode.
|
||||
*/
|
||||
.code32
|
||||
protected_start:
|
||||
/* Load segment registers */
|
||||
movw $__BOOT_DS, %ax
|
||||
movw %ax, %ss
|
||||
movw %ax, %ds
|
||||
movw %ax, %es
|
||||
movw %ax, %fs
|
||||
movw %ax, %gs
|
||||
|
||||
/* Use the internal etherboot stack */
|
||||
movl $(_prefix_stack_end - protected_start + 0x100000), %esp
|
||||
|
||||
pushl $0 /* No parameters to preserve for exit path */
|
||||
pushl $0 /* Use prefix exit path mechanism */
|
||||
|
||||
jmp _start
|
||||
/*
|
||||
That's about it.
|
||||
*/
|
||||
410
src/arch/i386/prefix/boot1a.s
Normal file
410
src/arch/i386/prefix/boot1a.s
Normal file
@@ -0,0 +1,410 @@
|
||||
# This code is no longer used in Etherboot. It is not maintained and
|
||||
# may not work.
|
||||
|
||||
|
||||
#
|
||||
# Copyright (c) 1998 Robert Nordier
|
||||
# All rights reserved.
|
||||
# Very small bootrom changes by Luigi Rizzo
|
||||
# <comment author="Luigi Rizzo">
|
||||
# I recently had the problem of downloading the etherboot code
|
||||
# from a hard disk partition instead of a floppy, and noticed that
|
||||
# floppyload.S does not do the job. With a bit of hacking to
|
||||
# the FreeBSD's boot1.s code, I managed to obtain a boot sector
|
||||
# which works both for floppies and hard disks -- basically you
|
||||
# do something like
|
||||
#
|
||||
# cat boot1a bin32/<yourcard>.lzrom > /dev/ad0s4
|
||||
#
|
||||
# (or whatever is the HD partition you are using, I am using slice
|
||||
# 4 on FreeBSD) and you are up and running.
|
||||
# Then with "fdisk" you have to mark your partition as having type "1"
|
||||
# (which is listed as DOS-- but basically it must be something matching
|
||||
# the variable PRT_BSD in the assembly source below).
|
||||
# </comment>
|
||||
#
|
||||
# Redistribution and use in source and binary forms are freely
|
||||
# permitted provided that the above copyright notice and this
|
||||
# paragraph and the following disclaimer are duplicated in all
|
||||
# such forms.
|
||||
#
|
||||
# This software is provided "AS IS" and without any express or
|
||||
# implied warranties, including, without limitation, the implied
|
||||
# warranties of merchantability and fitness for a particular
|
||||
# purpose.
|
||||
#
|
||||
# Makefile:
|
||||
#boot1a: boot1a.out
|
||||
# objcopy -S -O binary boot1a.out boot1a
|
||||
#
|
||||
#boot1a.out: boot1a.o
|
||||
# ld -nostdlib -static -N -e start -Ttext 0x7c00 -o boot1a.out boot1a.o
|
||||
#
|
||||
#boot1a.o: boot1a.s
|
||||
# as --defsym FLAGS=0x80 boot1a.s -o boot1a.o
|
||||
#
|
||||
#
|
||||
|
||||
# $FreeBSD: src/sys/boot/i386/boot2/boot1.s,v 1.10.2.2 2000/07/07 21:12:32 jhb Exp $
|
||||
|
||||
# Memory Locations
|
||||
.set MEM_REL,0x700 # Relocation address
|
||||
.set MEM_ARG,0x900 # Arguments
|
||||
.set MEM_ORG,0x7c00 # Origin
|
||||
.set MEM_BUF,0x8c00 # Load area
|
||||
.set MEM_BTX,0x9000 # BTX start
|
||||
.set MEM_JMP,0x9010 # BTX entry point
|
||||
.set MEM_USR,0xa000 # Client start
|
||||
.set BDA_BOOT,0x472 # Boot howto flag
|
||||
|
||||
# Partition Constants
|
||||
.set PRT_OFF,0x1be # Partition offset
|
||||
.set PRT_NUM,0x4 # Partitions
|
||||
.set PRT_BSD,0x1 # Partition type
|
||||
|
||||
# Flag Bits
|
||||
.set FL_PACKET,0x80 # Packet mode
|
||||
|
||||
# Misc. Constants
|
||||
.set SIZ_PAG,0x1000 # Page size
|
||||
.set SIZ_SEC,0x200 # Sector size
|
||||
|
||||
.globl start
|
||||
.globl xread
|
||||
.code16
|
||||
|
||||
start: jmp main # Start recognizably
|
||||
|
||||
.org 0x4,0x90
|
||||
#
|
||||
# Trampoline used by boot2 to call read to read data from the disk via
|
||||
# the BIOS. Call with:
|
||||
#
|
||||
# %cx:%ax - long - LBA to read in
|
||||
# %es:(%bx) - caddr_t - buffer to read data into
|
||||
# %dl - byte - drive to read from
|
||||
# %dh - byte - num sectors to read
|
||||
#
|
||||
|
||||
xread: push %ss # Address
|
||||
pop %ds # data
|
||||
#
|
||||
# Setup an EDD disk packet and pass it to read
|
||||
#
|
||||
xread.1: # Starting
|
||||
pushl $0x0 # absolute
|
||||
push %cx # block
|
||||
push %ax # number
|
||||
push %es # Address of
|
||||
push %bx # transfer buffer
|
||||
xor %ax,%ax # Number of
|
||||
movb %dh,%al # blocks to
|
||||
push %ax # transfer
|
||||
push $0x10 # Size of packet
|
||||
mov %sp,%bp # Packet pointer
|
||||
callw read # Read from disk
|
||||
lea 0x10(%bp),%sp # Clear stack
|
||||
lret # To far caller
|
||||
#
|
||||
# Load the rest of boot2 and BTX up, copy the parts to the right locations,
|
||||
# and start it all up.
|
||||
#
|
||||
|
||||
#
|
||||
# Setup the segment registers to flat addressing (segment 0) and setup the
|
||||
# stack to end just below the start of our code.
|
||||
#
|
||||
main: cld # String ops inc
|
||||
xor %cx,%cx # Zero
|
||||
mov %cx,%es # Address
|
||||
mov %cx,%ds # data
|
||||
mov %cx,%ss # Set up
|
||||
mov $start,%sp # stack
|
||||
#
|
||||
# Relocate ourself to MEM_REL. Since %cx == 0, the inc %ch sets
|
||||
# %cx == 0x100.
|
||||
#
|
||||
mov %sp,%si # Source
|
||||
mov $MEM_REL,%di # Destination
|
||||
incb %ch # Word count
|
||||
rep # Copy
|
||||
movsw # code
|
||||
#
|
||||
# If we are on a hard drive, then load the MBR and look for the first
|
||||
# FreeBSD slice. We use the fake partition entry below that points to
|
||||
# the MBR when we call nread. The first pass looks for the first active
|
||||
# FreeBSD slice. The second pass looks for the first non-active FreeBSD
|
||||
# slice if the first one fails.
|
||||
#
|
||||
mov $part4,%si # Partition
|
||||
cmpb $0x80,%dl # Hard drive?
|
||||
jb main.4 # No
|
||||
movb $0x1,%dh # Block count
|
||||
callw nread # Read MBR
|
||||
mov $0x1,%cx # Two passes
|
||||
main.1: mov $MEM_BUF+PRT_OFF,%si # Partition table
|
||||
movb $0x1,%dh # Partition
|
||||
main.2: cmpb $PRT_BSD,0x4(%si) # Our partition type?
|
||||
jne main.3 # No
|
||||
jcxz main.5 # If second pass
|
||||
testb $0x80,(%si) # Active?
|
||||
jnz main.5 # Yes
|
||||
main.3: add $0x10,%si # Next entry
|
||||
incb %dh # Partition
|
||||
cmpb $0x1+PRT_NUM,%dh # In table?
|
||||
jb main.2 # Yes
|
||||
dec %cx # Do two
|
||||
jcxz main.1 # passes
|
||||
#
|
||||
# If we get here, we didn't find any FreeBSD slices at all, so print an
|
||||
# error message and die.
|
||||
#
|
||||
booterror: mov $msg_part,%si # Message
|
||||
jmp error # Error
|
||||
#
|
||||
# Floppies use partition 0 of drive 0.
|
||||
#
|
||||
main.4: xor %dx,%dx # Partition:drive
|
||||
#
|
||||
# Ok, we have a slice and drive in %dx now, so use that to locate and load
|
||||
# boot2. %si references the start of the slice we are looking for, so go
|
||||
# ahead and load up the first 16 sectors (boot1 + boot2) from that. When
|
||||
# we read it in, we conveniently use 0x8c00 as our transfer buffer. Thus,
|
||||
# boot1 ends up at 0x8c00, and boot2 starts at 0x8c00 + 0x200 = 0x8e00.
|
||||
# The first part of boot2 is the disklabel, which is 0x200 bytes long.
|
||||
# The second part is BTX, which is thus loaded into 0x9000, which is where
|
||||
# it also runs from. The boot2.bin binary starts right after the end of
|
||||
# BTX, so we have to figure out where the start of it is and then move the
|
||||
# binary to 0xb000. Normally, BTX clients start at MEM_USR, or 0xa000, but
|
||||
# when we use btxld create boot2, we use an entry point of 0x1000. That
|
||||
# entry point is relative to MEM_USR; thus boot2.bin starts at 0xb000.
|
||||
#
|
||||
main.5: mov %dx,MEM_ARG # Save args
|
||||
movb $0x2,%dh # Sector count
|
||||
mov $0x7e00, %bx
|
||||
callw nreadbx # Read disk
|
||||
movb $0x40,%dh # Sector count
|
||||
movb %dh, %al
|
||||
callw puthex
|
||||
mov $0x7e00, %bx
|
||||
callw nreadbx # Read disk
|
||||
push %si
|
||||
mov $msg_r1,%si
|
||||
callw putstr
|
||||
pop %si
|
||||
lcall $0x800,$0 # enter the rom code
|
||||
int $0x19
|
||||
|
||||
msg_r1: .asciz " done\r\n"
|
||||
|
||||
.if 0
|
||||
mov $MEM_BTX,%bx # BTX
|
||||
mov 0xa(%bx),%si # Get BTX length and set
|
||||
add %bx,%si # %si to start of boot2.bin
|
||||
mov $MEM_USR+SIZ_PAG,%di # Client page 1
|
||||
mov $MEM_BTX+0xe*SIZ_SEC,%cx # Byte
|
||||
sub %si,%cx # count
|
||||
rep # Relocate
|
||||
movsb # client
|
||||
sub %di,%cx # Byte count
|
||||
xorb %al,%al # Zero assumed bss from
|
||||
rep # the end of boot2.bin
|
||||
stosb # up to 0x10000
|
||||
callw seta20 # Enable A20
|
||||
jmp start+MEM_JMP-MEM_ORG # Start BTX
|
||||
#
|
||||
# Enable A20 so we can access memory above 1 meg.
|
||||
#
|
||||
seta20: cli # Disable interrupts
|
||||
seta20.1: inb $0x64,%al # Get status
|
||||
testb $0x2,%al # Busy?
|
||||
jnz seta20.1 # Yes
|
||||
movb $0xd1,%al # Command: Write
|
||||
outb %al,$0x64 # output port
|
||||
seta20.2: inb $0x64,%al # Get status
|
||||
testb $0x2,%al # Busy?
|
||||
jnz seta20.2 # Yes
|
||||
movb $0xdf,%al # Enable
|
||||
outb %al,$0x60 # A20
|
||||
sti # Enable interrupts
|
||||
retw # To caller
|
||||
.endif
|
||||
#
|
||||
# Trampoline used to call read from within boot1.
|
||||
#
|
||||
nread: mov $MEM_BUF,%bx # Transfer buffer
|
||||
nreadbx: # same but address is in bx
|
||||
mov 0x8(%si),%ax # Get
|
||||
mov 0xa(%si),%cx # LBA
|
||||
push %bx
|
||||
push %ax
|
||||
callw putword
|
||||
pop %ax
|
||||
pop %bx
|
||||
push %cs # Read from
|
||||
callw xread.1 # disk
|
||||
jnc return # If success, return
|
||||
mov $msg_read,%si # Otherwise, set the error
|
||||
# message and fall through to
|
||||
# the error routine
|
||||
#
|
||||
# Print out the error message pointed to by %ds:(%si) followed
|
||||
# by a prompt, wait for a keypress, and then reboot the machine.
|
||||
#
|
||||
error: callw putstr # Display message
|
||||
mov $prompt,%si # Display
|
||||
callw putstr # prompt
|
||||
xorb %ah,%ah # BIOS: Get
|
||||
int $0x16 # keypress
|
||||
movw $0x1234, BDA_BOOT # Do a warm boot
|
||||
ljmp $0xffff,$0x0 # reboot the machine
|
||||
#
|
||||
# Display a null-terminated string using the BIOS output.
|
||||
#
|
||||
putstr.0: call putchar
|
||||
putstr: lodsb # Get char
|
||||
testb %al,%al # End of string?
|
||||
jne putstr.0 # No
|
||||
retw
|
||||
|
||||
putword: push %ax
|
||||
movb $'.', %al
|
||||
callw putchar
|
||||
movb %ah, %al
|
||||
callw puthex
|
||||
pop %ax
|
||||
puthex: push %ax
|
||||
shr $4, %al
|
||||
callw putdigit
|
||||
pop %ax
|
||||
putdigit:
|
||||
andb $0xf, %al
|
||||
addb $0x30, %al
|
||||
cmpb $0x39, %al
|
||||
jbe putchar
|
||||
addb $7, %al
|
||||
putchar: push %ax
|
||||
mov $0x7,%bx
|
||||
movb $0xe,%ah
|
||||
int $0x10
|
||||
pop %ax
|
||||
retw
|
||||
|
||||
#
|
||||
# Overused return code. ereturn is used to return an error from the
|
||||
# read function. Since we assume putstr succeeds, we (ab)use the
|
||||
# same code when we return from putstr.
|
||||
#
|
||||
ereturn: movb $0x1,%ah # Invalid
|
||||
stc # argument
|
||||
return: retw # To caller
|
||||
#
|
||||
# Reads sectors from the disk. If EDD is enabled, then check if it is
|
||||
# installed and use it if it is. If it is not installed or not enabled, then
|
||||
# fall back to using CHS. Since we use a LBA, if we are using CHS, we have to
|
||||
# fetch the drive parameters from the BIOS and divide it out ourselves.
|
||||
# Call with:
|
||||
#
|
||||
# %dl - byte - drive number
|
||||
# stack - 10 bytes - EDD Packet
|
||||
#
|
||||
read: push %dx # Save
|
||||
movb $0x8,%ah # BIOS: Get drive
|
||||
int $0x13 # parameters
|
||||
movb %dh,%ch # Max head number
|
||||
pop %dx # Restore
|
||||
jc return # If error
|
||||
andb $0x3f,%cl # Sectors per track
|
||||
jz ereturn # If zero
|
||||
cli # Disable interrupts
|
||||
mov 0x8(%bp),%eax # Get LBA
|
||||
push %dx # Save
|
||||
movzbl %cl,%ebx # Divide by
|
||||
xor %edx,%edx # sectors
|
||||
div %ebx # per track
|
||||
movb %ch,%bl # Max head number
|
||||
movb %dl,%ch # Sector number
|
||||
inc %bx # Divide by
|
||||
xorb %dl,%dl # number
|
||||
div %ebx # of heads
|
||||
movb %dl,%bh # Head number
|
||||
pop %dx # Restore
|
||||
cmpl $0x3ff,%eax # Cylinder number supportable?
|
||||
sti # Enable interrupts
|
||||
ja read.7 # No, try EDD
|
||||
xchgb %al,%ah # Set up cylinder
|
||||
rorb $0x2,%al # number
|
||||
orb %ch,%al # Merge
|
||||
inc %ax # sector
|
||||
xchg %ax,%cx # number
|
||||
movb %bh,%dh # Head number
|
||||
subb %ah,%al # Sectors this track
|
||||
mov 0x2(%bp),%ah # Blocks to read
|
||||
cmpb %ah,%al # To read
|
||||
jb read.2 # this
|
||||
movb %ah,%al # track
|
||||
read.2: mov $0x5,%di # Try count
|
||||
read.3: les 0x4(%bp),%bx # Transfer buffer
|
||||
push %ax # Save
|
||||
movb $0x2,%ah # BIOS: Read
|
||||
int $0x13 # from disk
|
||||
pop %bx # Restore
|
||||
jnc read.4 # If success
|
||||
dec %di # Retry?
|
||||
jz read.6 # No
|
||||
xorb %ah,%ah # BIOS: Reset
|
||||
int $0x13 # disk system
|
||||
xchg %bx,%ax # Block count
|
||||
jmp read.3 # Continue
|
||||
read.4: movzbw %bl,%ax # Sectors read
|
||||
add %ax,0x8(%bp) # Adjust
|
||||
jnc read.5 # LBA,
|
||||
incw 0xa(%bp) # transfer
|
||||
read.5: shlb %bl # buffer
|
||||
add %bl,0x5(%bp) # pointer,
|
||||
sub %al,0x2(%bp) # block count
|
||||
ja read # If not done
|
||||
read.6: retw # To caller
|
||||
read.7: testb $FL_PACKET,%cs:MEM_REL+flags-start # LBA support enabled?
|
||||
jz ereturn # No, so return an error
|
||||
mov $0x55aa,%bx # Magic
|
||||
push %dx # Save
|
||||
movb $0x41,%ah # BIOS: Check
|
||||
int $0x13 # extensions present
|
||||
pop %dx # Restore
|
||||
jc return # If error, return an error
|
||||
cmp $0xaa55,%bx # Magic?
|
||||
jne ereturn # No, so return an error
|
||||
testb $0x1,%cl # Packet interface?
|
||||
jz ereturn # No, so return an error
|
||||
mov %bp,%si # Disk packet
|
||||
movb $0x42,%ah # BIOS: Extended
|
||||
int $0x13 # read
|
||||
retw # To caller
|
||||
|
||||
# Messages
|
||||
|
||||
msg_read: .asciz "Rd"
|
||||
msg_part: .asciz "Boot"
|
||||
|
||||
prompt: .asciz " err\r\n"
|
||||
|
||||
flags: .byte FLAGS # Flags
|
||||
|
||||
.org PRT_OFF,0x90
|
||||
|
||||
# Partition table
|
||||
|
||||
.fill 0x30,0x1,0x0
|
||||
part4: .byte 0x80
|
||||
.byte 0x00 # start head
|
||||
.byte 0x01 # start sector (6 bits) + start cyl (2 bit)
|
||||
.byte 0x00 # start cyl (low 8 bits)
|
||||
.byte 0x1 # part.type
|
||||
.byte 0xff # end head
|
||||
.byte 0xff # end sect (6) + end_cyl(2)
|
||||
.byte 0xff # end cyl
|
||||
.byte 0x00, 0x00, 0x00, 0x00 # explicit start
|
||||
.byte 0x50, 0xc3, 0x00, 0x00 # 50000 sectors long, bleh
|
||||
|
||||
.word 0xaa55 # Magic number
|
||||
49
src/arch/i386/prefix/comprefix.S
Normal file
49
src/arch/i386/prefix/comprefix.S
Normal file
@@ -0,0 +1,49 @@
|
||||
/* We need a real mode stack that won't be stomped on by Etherboot
|
||||
which starts at 0x20000. Choose something that's sufficiently high,
|
||||
but not in DOC territory. Note that we couldn't do this in a real
|
||||
.com program since stack variables are in the same segment as the
|
||||
code and data, but this isn't really a .com program, it just looks
|
||||
like one to make DOS load it into memory. It still has the 64kB
|
||||
limitation of .com files though. */
|
||||
#define STACK_SEG 0x7000
|
||||
#define STACK_SIZE 0x4000
|
||||
|
||||
.text
|
||||
.code16
|
||||
.arch i386
|
||||
.section ".prefix", "ax", @progbits
|
||||
.globl _prefix
|
||||
|
||||
/* Cheat a little with the relocations: .COM files are loaded at 0x100 */
|
||||
_prefix:
|
||||
/* Set up temporary stack */
|
||||
movw $STACK_SEG, %ax
|
||||
movw %ax, %ss
|
||||
movw $STACK_SIZE, %sp
|
||||
|
||||
pushl $0 /* No parameters to preserve for exit path */
|
||||
pushw $0 /* Dummy return address - use prefix_exit */
|
||||
|
||||
/* Calculate segment address of image start */
|
||||
pushw %cs
|
||||
popw %ax
|
||||
addw $(0x100/16), %ax
|
||||
pushw %ax
|
||||
pushw $_start
|
||||
/* Calculated lcall to _start with %cs:0000 = image start */
|
||||
lret
|
||||
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
movw $0x4c00,%ax /* return to DOS */
|
||||
int $0x21 /* reach this on Quit */
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
|
||||
/* The body of etherboot is attached here at build time.
|
||||
* Force 16 byte alignment
|
||||
*/
|
||||
.align 16,0
|
||||
_body:
|
||||
96
src/arch/i386/prefix/elf_dprefix.S
Normal file
96
src/arch/i386/prefix/elf_dprefix.S
Normal file
@@ -0,0 +1,96 @@
|
||||
#include "elf.h"
|
||||
|
||||
.arch i386
|
||||
.section ".prefix", "a", @progbits
|
||||
|
||||
#define LOAD_ADDR 0x10000
|
||||
|
||||
/* ELF Header */
|
||||
.globl elf_header
|
||||
elf_header:
|
||||
e_ident: .byte 0x7f, 'E', 'L', 'F', 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0
|
||||
e_type: .short ET_DYN
|
||||
e_machine: .short EM_386
|
||||
e_version: .long 1
|
||||
e_entry: .long LOAD_ADDR + _start - elf_header
|
||||
e_phoff: .long elf_program_header - elf_header
|
||||
e_shoff: .long 0
|
||||
e_flags: .long 0
|
||||
e_ehsize: .short elf_header_end - elf_header
|
||||
e_phentsize: .short ELF32_PHDR_SIZE
|
||||
e_phnum: .short (elf_program_header_end - elf_program_header)/ELF32_PHDR_SIZE
|
||||
e_shentsize: .short 0
|
||||
e_shnum: .short 0
|
||||
e_shstrndx: .short 0
|
||||
elf_header_end:
|
||||
|
||||
elf_program_header:
|
||||
phdr1_p_type: .long PT_NOTE
|
||||
phdr1_p_offset: .long elf_note - elf_header
|
||||
phdr1_p_vaddr: .long elf_note
|
||||
phdr1_p_paddr: .long elf_note
|
||||
phdr1_p_filesz: .long elf_note_end - elf_note
|
||||
phdr1_p_memsz: .long elf_note_end - elf_note
|
||||
phdr1_p_flags: .long PF_R | PF_W | PF_X
|
||||
phdr1_p_align: .long 0
|
||||
|
||||
/* The decompressor */
|
||||
phdr2_p_type: .long PT_LOAD
|
||||
phdr2_p_offset: .long 0
|
||||
phdr2_p_vaddr: .long elf_header
|
||||
phdr2_p_paddr: .long LOAD_ADDR
|
||||
phdr2_p_filesz: .long _verbatim_size
|
||||
phdr2_p_memsz: .long _image_size
|
||||
phdr2_p_flags: .long PF_R | PF_W | PF_X
|
||||
phdr2_p_align: .long 16
|
||||
|
||||
elf_program_header_end:
|
||||
|
||||
.globl elf_note
|
||||
elf_note:
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_NAME
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.asciz "Etherboot"
|
||||
4:
|
||||
|
||||
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_VERSION
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.asciz VERSION
|
||||
4:
|
||||
|
||||
#if 0
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_CHECKSUM
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.word 0
|
||||
4:
|
||||
#endif
|
||||
.balign 4
|
||||
elf_note_end:
|
||||
|
||||
/* Dummy routines to satisfy the build */
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
96
src/arch/i386/prefix/elfprefix.S
Normal file
96
src/arch/i386/prefix/elfprefix.S
Normal file
@@ -0,0 +1,96 @@
|
||||
#include "elf.h"
|
||||
|
||||
.arch i386
|
||||
.section ".prefix", "a", @progbits
|
||||
|
||||
#define LOAD_ADDR 0x10000
|
||||
|
||||
/* ELF Header */
|
||||
.globl elf_header
|
||||
elf_header:
|
||||
e_ident: .byte 0x7f, 'E', 'L', 'F', 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0
|
||||
e_type: .short ET_EXEC
|
||||
e_machine: .short EM_386
|
||||
e_version: .long 1
|
||||
e_entry: .long LOAD_ADDR + _start - elf_header
|
||||
e_phoff: .long elf_program_header - elf_header
|
||||
e_shoff: .long 0
|
||||
e_flags: .long 0
|
||||
e_ehsize: .short elf_header_end - elf_header
|
||||
e_phentsize: .short ELF32_PHDR_SIZE
|
||||
e_phnum: .short (elf_program_header_end - elf_program_header)/ELF32_PHDR_SIZE
|
||||
e_shentsize: .short 0
|
||||
e_shnum: .short 0
|
||||
e_shstrndx: .short 0
|
||||
elf_header_end:
|
||||
|
||||
elf_program_header:
|
||||
phdr1_p_type: .long PT_NOTE
|
||||
phdr1_p_offset: .long elf_note - elf_header
|
||||
phdr1_p_vaddr: .long elf_note
|
||||
phdr1_p_paddr: .long elf_note
|
||||
phdr1_p_filesz: .long elf_note_end - elf_note
|
||||
phdr1_p_memsz: .long elf_note_end - elf_note
|
||||
phdr1_p_flags: .long PF_R | PF_W | PF_X
|
||||
phdr1_p_align: .long 0
|
||||
|
||||
/* The decompressor */
|
||||
phdr2_p_type: .long PT_LOAD
|
||||
phdr2_p_offset: .long 0
|
||||
phdr2_p_vaddr: .long elf_header
|
||||
phdr2_p_paddr: .long LOAD_ADDR
|
||||
phdr2_p_filesz: .long _verbatim_size
|
||||
phdr2_p_memsz: .long _image_size
|
||||
phdr2_p_flags: .long PF_R | PF_W | PF_X
|
||||
phdr2_p_align: .long 16
|
||||
|
||||
elf_program_header_end:
|
||||
|
||||
.globl elf_note
|
||||
elf_note:
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_NAME
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.asciz "Etherboot"
|
||||
4:
|
||||
|
||||
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_VERSION
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.asciz VERSION
|
||||
4:
|
||||
|
||||
#if 0
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_CHECKSUM
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.word 0
|
||||
4:
|
||||
#endif
|
||||
.balign 4
|
||||
elf_note_end:
|
||||
|
||||
/* Dummy routines to satisfy the build */
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
44
src/arch/i386/prefix/exeprefix.S
Executable file
44
src/arch/i386/prefix/exeprefix.S
Executable file
@@ -0,0 +1,44 @@
|
||||
/*
|
||||
Prefix for .exe images
|
||||
Doesn't work yet, even though it starts off the same as a .com
|
||||
image as shown by DOS debug.
|
||||
*/
|
||||
|
||||
.text
|
||||
.code16
|
||||
.arch i386
|
||||
.section ".prefix", "ax", @progbits
|
||||
.globl _prefix
|
||||
|
||||
_prefix:
|
||||
.byte 'M', 'Z'
|
||||
.short _exe_size_tail /* tail */
|
||||
.short _exe_size_pages /* pages */
|
||||
.short 0 /* relocations */
|
||||
.short 2 /* header paras */
|
||||
.short _exe_bss_size /* min */
|
||||
.short 0xFFFF /* max paras */
|
||||
.short _exe_ss_offset /* SS */
|
||||
.short _stack_size /* SP */
|
||||
.short 0 /* checksum */
|
||||
.short 0 /* IP */
|
||||
.short 0 /* CS */
|
||||
.short 0x1C /* reloc offset */
|
||||
.short 0 /* overlay number */
|
||||
.short 0 /* fill */
|
||||
.short 0 /* fill */
|
||||
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
movw $0x4c00,%ax /* return to DOS */
|
||||
int $0x21 /* reach this on Quit */
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
|
||||
/* The body of etherboot is attached here at build time.
|
||||
* Force 16 byte alignment
|
||||
*/
|
||||
.align 16,0
|
||||
_body:
|
||||
359
src/arch/i386/prefix/floppyprefix.S
Normal file
359
src/arch/i386/prefix/floppyprefix.S
Normal file
@@ -0,0 +1,359 @@
|
||||
/* NOTE: this boot sector contains instructions that need at least an 80186.
|
||||
* Yes, as86 has a bug somewhere in the valid instruction set checks.
|
||||
*
|
||||
* SYS_SIZE is the number of clicks (16 bytes) to be loaded.
|
||||
*/
|
||||
.equ SYSSIZE, 8192 # 8192 * 16 bytes = 128kB maximum size of .ROM file
|
||||
|
||||
/* floppyload.S Copyright (C) 1991, 1992 Linus Torvalds
|
||||
* modified by Drew Eckhardt
|
||||
* modified by Bruce Evans (bde)
|
||||
*
|
||||
* floppyprefix.S is loaded at 0x0000:0x7c00 by the bios-startup routines.
|
||||
*
|
||||
* It then loads the system at SYSSEG<<4, using BIOS interrupts.
|
||||
*
|
||||
* The loader has been made as simple as possible, and continuous read errors
|
||||
* will result in a unbreakable loop. Reboot by hand. It loads pretty fast by
|
||||
* getting whole tracks at a time whenever possible.
|
||||
*/
|
||||
|
||||
.equ BOOTSEG, 0x07C0 /* original address of boot-sector */
|
||||
|
||||
.equ SYSSEG, 0x1000 /* system loaded at SYSSEG<<4 */
|
||||
|
||||
.org 0
|
||||
.arch i386
|
||||
.text
|
||||
.section ".prefix", "ax", @progbits
|
||||
.code16
|
||||
|
||||
jmp $BOOTSEG, $go /* reload cs:ip to match relocation addr */
|
||||
go:
|
||||
movw $0x2000-12, %di /* 0x2000 is arbitrary value >= length */
|
||||
/* of bootsect + room for stack + 12 for */
|
||||
/* saved disk parm block */
|
||||
|
||||
movw $BOOTSEG, %ax
|
||||
movw %ax,%ds
|
||||
movw %ax,%es
|
||||
movw %ax,%ss /* put stack at BOOTSEG:0x4000-12. */
|
||||
movw %di,%sp
|
||||
|
||||
/* Many BIOS's default disk parameter tables will not recognize multi-sector
|
||||
* reads beyond the maximum sector number specified in the default diskette
|
||||
* parameter tables - this may mean 7 sectors in some cases.
|
||||
*
|
||||
* Since single sector reads are slow and out of the question, we must take care
|
||||
* of this by creating new parameter tables (for the first disk) in RAM. We
|
||||
* will set the maximum sector count to 36 - the most we will encounter on an
|
||||
* ED 2.88. High doesn't hurt. Low does.
|
||||
*
|
||||
* Segments are as follows: ds=es=ss=cs - BOOTSEG
|
||||
*/
|
||||
|
||||
xorw %cx,%cx
|
||||
movw %cx,%es /* access segment 0 */
|
||||
movw $0x78, %bx /* 0:bx is parameter table address */
|
||||
pushw %ds /* save ds */
|
||||
/* 0:bx is parameter table address */
|
||||
ldsw %es:(%bx),%si /* loads ds and si */
|
||||
|
||||
movw %ax,%es /* ax is BOOTSECT (loaded above) */
|
||||
movb $6, %cl /* copy 12 bytes */
|
||||
cld
|
||||
pushw %di /* keep a copy for later */
|
||||
rep
|
||||
movsw /* ds:si is source, es:di is dest */
|
||||
popw %di
|
||||
|
||||
movb $36,%es:4(%di)
|
||||
|
||||
movw %cx,%ds /* access segment 0 */
|
||||
xchgw %di,(%bx)
|
||||
movw %es,%si
|
||||
xchgw %si,2(%bx)
|
||||
popw %ds /* restore ds */
|
||||
movw %di, dpoff /* save old parameters */
|
||||
movw %si, dpseg /* to restore just before finishing */
|
||||
pushw %ds
|
||||
popw %es /* reload es */
|
||||
|
||||
/* Note that es is already set up. Also cx is 0 from rep movsw above. */
|
||||
|
||||
xorb %ah,%ah /* reset FDC */
|
||||
xorb %dl,%dl
|
||||
int $0x13
|
||||
|
||||
/* Get disk drive parameters, specifically number of sectors/track.
|
||||
*
|
||||
* It seems that there is no BIOS call to get the number of sectors. Guess
|
||||
* 36 sectors if sector 36 can be read, 18 sectors if sector 18 can be read,
|
||||
* 15 if sector 15 can be read. Otherwise guess 9.
|
||||
*/
|
||||
|
||||
movw $disksizes, %si /* table of sizes to try */
|
||||
|
||||
probe_loop:
|
||||
lodsb
|
||||
cbtw /* extend to word */
|
||||
movw %ax, sectors
|
||||
cmpw $disksizes+4, %si
|
||||
jae got_sectors /* if all else fails, try 9 */
|
||||
xchgw %cx,%ax /* cx = track and sector */
|
||||
xorw %dx,%dx /* drive 0, head 0 */
|
||||
movw $0x0200, %bx /* address after boot sector */
|
||||
/* (512 bytes from origin, es = cs) */
|
||||
movw $0x0201, %ax /* service 2, 1 sector */
|
||||
int $0x13
|
||||
jc probe_loop /* try next value */
|
||||
|
||||
got_sectors:
|
||||
movw $msg1end-msg1, %cx
|
||||
movw $msg1, %si
|
||||
call print_str
|
||||
|
||||
/* ok, we've written the Loading... message, now we want to load the system */
|
||||
|
||||
pushw %es /* = ds */
|
||||
movw $SYSSEG, %ax
|
||||
movw %ax,%es /* segment of SYSSEG<<4 */
|
||||
pushw %es
|
||||
call read_it
|
||||
|
||||
/* This turns off the floppy drive motor, so that we enter the kernel in a
|
||||
* known state, and don't have to worry about it later.
|
||||
*/
|
||||
movw $0x3f2, %dx
|
||||
xorb %al,%al
|
||||
outb %al,%dx
|
||||
|
||||
call print_nl
|
||||
pop %es /* = SYSSEG */
|
||||
pop %es /* balance push/pop es */
|
||||
sigok:
|
||||
|
||||
/* Restore original disk parameters */
|
||||
movw $0x78, %bx
|
||||
movw dpoff, %di
|
||||
movw dpseg, %si
|
||||
xorw %ax,%ax
|
||||
movw %ax,%ds
|
||||
movw %di,(%bx)
|
||||
movw %si,2(%bx)
|
||||
|
||||
/* after that (everything loaded), we call to the .ROM file loaded. */
|
||||
|
||||
pushl $0 /* No parameters to preserve for exit path */
|
||||
pushw $0 /* Use prefix exit path mechanism */
|
||||
ljmp $SYSSEG, $_start
|
||||
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
xchgw %bx, %bx
|
||||
int $0x19 /* should try to boot machine */
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
|
||||
/* This routine loads the system at address SYSSEG<<4, making sure no 64kB
|
||||
* boundaries are crossed. We try to load it as fast as possible, loading whole
|
||||
* tracks whenever we can.
|
||||
*
|
||||
* in: es - starting address segment (normally SYSSEG)
|
||||
*/
|
||||
read_it:
|
||||
movw $0,sread /* read whole image incl boot sector */
|
||||
movw %es,%ax
|
||||
testw $0x0fff, %ax
|
||||
die: jne die /* es must be at 64kB boundary */
|
||||
xorw %bx,%bx /* bx is starting address within segment */
|
||||
rp_read:
|
||||
movw %es,%ax
|
||||
movw %bx,%dx
|
||||
movb $4, %cl
|
||||
shrw %cl,%dx /* bx is always divisible by 16 */
|
||||
addw %dx,%ax
|
||||
cmpw $SYSSEG+SYSSIZE, %ax /* have we loaded all yet? */
|
||||
jb ok1_read
|
||||
ret
|
||||
ok1_read:
|
||||
movw sectors, %ax
|
||||
subw sread, %ax
|
||||
movw %ax,%cx
|
||||
shlw $9, %cx
|
||||
addw %bx,%cx
|
||||
jnc ok2_read
|
||||
je ok2_read
|
||||
xorw %ax,%ax
|
||||
subw %bx,%ax
|
||||
shrw $9, %ax
|
||||
ok2_read:
|
||||
call read_track
|
||||
movw %ax,%cx
|
||||
addw sread, %ax
|
||||
cmpw sectors, %ax
|
||||
jne ok3_read
|
||||
movw $1, %ax
|
||||
subw head, %ax
|
||||
jne ok4_read
|
||||
incw track
|
||||
ok4_read:
|
||||
movw %ax, head
|
||||
xorw %ax,%ax
|
||||
ok3_read:
|
||||
movw %ax, sread
|
||||
shlw $9, %cx
|
||||
addw %cx,%bx
|
||||
jnc rp_read
|
||||
movw %es,%ax
|
||||
addb $0x10, %ah
|
||||
movw %ax,%es
|
||||
xorw %bx,%bx
|
||||
jmp rp_read
|
||||
|
||||
read_track:
|
||||
pusha
|
||||
pushw %ax
|
||||
pushw %bx
|
||||
pushw %bp /* just in case the BIOS is buggy */
|
||||
movw $0x0e2e, %ax /* 0x2e = . */
|
||||
movw $0x0007, %bx
|
||||
int $0x10
|
||||
popw %bp
|
||||
popw %bx
|
||||
popw %ax
|
||||
|
||||
movw track, %dx
|
||||
movw sread, %cx
|
||||
incw %cx
|
||||
movb %dl,%ch
|
||||
movw head, %dx
|
||||
movb %dl,%dh
|
||||
andw $0x0100, %dx
|
||||
movb $2, %ah
|
||||
|
||||
pushw %dx /* save for error dump */
|
||||
pushw %cx
|
||||
pushw %bx
|
||||
pushw %ax
|
||||
|
||||
int $0x13
|
||||
jc bad_rt
|
||||
addw $8, %sp
|
||||
popa
|
||||
ret
|
||||
|
||||
bad_rt: pushw %ax /* save error code */
|
||||
call print_all /* ah = error, al = read */
|
||||
|
||||
xorb %ah,%ah
|
||||
xorb %dl,%dl
|
||||
int $0x13
|
||||
|
||||
addw $10, %sp
|
||||
popa
|
||||
jmp read_track
|
||||
|
||||
/* print_all is for debugging purposes. It will print out all of the registers.
|
||||
* The assumption is that this is called from a routine, with a stack frame like
|
||||
* dx
|
||||
* cx
|
||||
* bx
|
||||
* ax
|
||||
* error
|
||||
* ret <- sp
|
||||
*/
|
||||
|
||||
print_all:
|
||||
call print_nl /* nl for readability */
|
||||
movw $5, %cx /* error code + 4 registers */
|
||||
movw %sp,%bp
|
||||
|
||||
print_loop:
|
||||
pushw %cx /* save count left */
|
||||
|
||||
cmpb $5, %cl
|
||||
jae no_reg /* see if register name is needed */
|
||||
|
||||
movw $0x0007, %bx /* page 0, attribute 7 (normal) */
|
||||
movw $0xe05+0x41-1, %ax
|
||||
subb %cl,%al
|
||||
int $0x10
|
||||
|
||||
movb $0x58, %al /* 'X' */
|
||||
int $0x10
|
||||
|
||||
movb $0x3A, %al /* ':' */
|
||||
int $0x10
|
||||
|
||||
no_reg:
|
||||
addw $2, %bp /* next register */
|
||||
call print_hex /* print it */
|
||||
movb $0x20, %al /* print a space */
|
||||
int $0x10
|
||||
popw %cx
|
||||
loop print_loop
|
||||
call print_nl /* nl for readability */
|
||||
ret
|
||||
|
||||
print_str:
|
||||
movw $0x0007, %bx /* page 0, attribute 7 (normal) */
|
||||
movb $0x0e, %ah /* write char, tty mode */
|
||||
prloop:
|
||||
lodsb
|
||||
int $0x10
|
||||
loop prloop
|
||||
ret
|
||||
|
||||
print_nl:
|
||||
movw $0x0007, %bx /* page 0, attribute 7 (normal) */
|
||||
movw $0xe0d, %ax /* CR */
|
||||
int $0x10
|
||||
movb $0xa, %al /* LF */
|
||||
int $0x10
|
||||
ret
|
||||
|
||||
/* print_hex prints the word pointed to by ss:bp in hexadecimal. */
|
||||
|
||||
print_hex:
|
||||
movw (%bp),%dx /* load word into dx */
|
||||
movb $4, %cl
|
||||
movb $0x0e, %ah /* write char, tty mode */
|
||||
movw $0x0007, %bx /* page 0, attribute 7 (normal) */
|
||||
call print_digit
|
||||
call print_digit
|
||||
call print_digit
|
||||
/* fall through */
|
||||
print_digit:
|
||||
rol %cl,%dx /* rotate so that lowest 4 bits are used */
|
||||
movb $0x0f, %al /* mask for nybble */
|
||||
andb %dl,%al
|
||||
addb $0x90, %al /* convert al to ascii hex (four instructions) */
|
||||
daa
|
||||
adcb $0x40, %al
|
||||
daa
|
||||
int $0x10
|
||||
ret
|
||||
|
||||
sread: .word 0 /* sectors read of current track */
|
||||
head: .word 0 /* current head */
|
||||
track: .word 0 /* current track */
|
||||
|
||||
sectors:
|
||||
.word 0
|
||||
|
||||
dpseg: .word 0
|
||||
dpoff: .word 0
|
||||
|
||||
disksizes:
|
||||
.byte 36,18,15,9
|
||||
|
||||
msg1:
|
||||
.ascii "Loading ROM image"
|
||||
msg1end:
|
||||
|
||||
.org 510, 0
|
||||
.word 0xAA55
|
||||
|
||||
6
src/arch/i386/prefix/huf.lds
Normal file
6
src/arch/i386/prefix/huf.lds
Normal file
@@ -0,0 +1,6 @@
|
||||
OUTPUT_FORMAT("elf32-i386", "elf32-i386", "elf32-i386")
|
||||
OUTPUT_ARCH(i386)
|
||||
|
||||
SECTIONS {
|
||||
.huf : { *(*) }
|
||||
}
|
||||
6
src/arch/i386/prefix/img.lds
Normal file
6
src/arch/i386/prefix/img.lds
Normal file
@@ -0,0 +1,6 @@
|
||||
OUTPUT_FORMAT("elf32-i386", "elf32-i386", "elf32-i386")
|
||||
OUTPUT_ARCH(i386)
|
||||
|
||||
SECTIONS {
|
||||
.img : { *(*) }
|
||||
}
|
||||
144
src/arch/i386/prefix/liloprefix.S
Normal file
144
src/arch/i386/prefix/liloprefix.S
Normal file
@@ -0,0 +1,144 @@
|
||||
/*
|
||||
Copyright (C) 2000, Entity Cyber, Inc.
|
||||
|
||||
Authors: Gary Byers (gb@thinguin.org)
|
||||
Marty Connor (mdc@thinguin.org)
|
||||
|
||||
This software may be used and distributed according to the terms
|
||||
of the GNU Public License (GPL), incorporated herein by reference.
|
||||
|
||||
Description:
|
||||
|
||||
This is just a little bit of code and data that can get prepended
|
||||
to an Etherboot ROM image in order to allow LILO to load the
|
||||
result as if it were a Linux kernel image.
|
||||
|
||||
A real Linux kernel image consists of a one-sector boot loader
|
||||
(to load the image from a floppy disk), followed a few sectors
|
||||
of setup code, followed by the kernel code itself. There's
|
||||
a table in the first sector (starting at offset 497) that indicates
|
||||
how many sectors of setup code follow the first sector and which
|
||||
contains some other parameters that aren't interesting in this
|
||||
case.
|
||||
|
||||
When LILO loads the sectors that comprise a kernel image, it doesn't
|
||||
execute the code in the first sector (since that code would try to
|
||||
load the image from a floppy disk.) The code in the first sector
|
||||
below doesn't expect to get executed (and prints an error message
|
||||
if it ever -is- executed.) LILO's only interested in knowing the
|
||||
number of setup sectors advertised in the table (at offset 497 in
|
||||
the first sector.)
|
||||
|
||||
Etherboot doesn't require much in the way of setup code.
|
||||
Historically, the Linux kernel required at least 4 sectors of
|
||||
setup code. Current versions of LILO look at the byte at
|
||||
offset 497 in the first sector to indicate how many sectors
|
||||
of setup code are contained in the image.
|
||||
|
||||
*/
|
||||
|
||||
#define SETUPSECS 4 /* Minimal nr of setup-sectors */
|
||||
#define PREFIXSIZE ((SETUPSECS+1)*512)
|
||||
#define PREFIXPGH (PREFIXSIZE / 16 )
|
||||
#define BOOTSEG 0x07C0 /* original address of boot-sector */
|
||||
#define INITSEG 0x9000 /* we move boot here - out of the way */
|
||||
#define SETUPSEG 0x9020 /* setup starts here */
|
||||
#define SYSSEG 0x1000 /* system loaded at 0x10000 (65536). */
|
||||
|
||||
.text
|
||||
.code16
|
||||
.arch i386
|
||||
.org 0
|
||||
.section ".prefix", "ax", @progbits
|
||||
.globl _prefix
|
||||
_prefix:
|
||||
|
||||
/*
|
||||
This is a minimal boot sector. If anyone tries to execute it (e.g., if
|
||||
a .lilo file is dd'ed to a floppy), print an error message.
|
||||
*/
|
||||
|
||||
bootsector:
|
||||
jmp $BOOTSEG, $go - _prefix /* reload cs:ip to match relocation addr */
|
||||
go:
|
||||
movw $0x2000, %di /* 0x2000 is arbitrary value >= length
|
||||
of bootsect + room for stack */
|
||||
|
||||
movw $BOOTSEG, %ax
|
||||
movw %ax,%ds
|
||||
movw %ax,%es
|
||||
|
||||
cli
|
||||
movw %ax, %ss /* put stack at BOOTSEG:0x2000. */
|
||||
movw %di,%sp
|
||||
sti
|
||||
|
||||
movw $why_end-why, %cx
|
||||
movw $why - _prefix, %si
|
||||
|
||||
movw $0x0007, %bx /* page 0, attribute 7 (normal) */
|
||||
movb $0x0e, %ah /* write char, tty mode */
|
||||
prloop:
|
||||
lodsb
|
||||
int $0x10
|
||||
loop prloop
|
||||
freeze: jmp freeze
|
||||
|
||||
why: .ascii "This image cannot be loaded from a floppy disk.\r\n"
|
||||
why_end:
|
||||
|
||||
|
||||
.org 497
|
||||
setup_sects:
|
||||
.byte SETUPSECS
|
||||
root_flags:
|
||||
.word 0
|
||||
syssize:
|
||||
.word _verbatim_size_pgh - PREFIXPGH
|
||||
swap_dev:
|
||||
.word 0
|
||||
ram_size:
|
||||
.word 0
|
||||
vid_mode:
|
||||
.word 0
|
||||
root_dev:
|
||||
.word 0
|
||||
boot_flag:
|
||||
.word 0xAA55
|
||||
|
||||
/*
|
||||
We're now at the beginning of the second sector of the image -
|
||||
where the setup code goes.
|
||||
|
||||
We don't need to do too much setup for Etherboot.
|
||||
|
||||
This code gets loaded at SETUPSEG:0. It wants to start
|
||||
executing the Etherboot image that's loaded at SYSSEG:0 and
|
||||
whose entry point is SYSSEG:0.
|
||||
*/
|
||||
setup_code:
|
||||
pushl $0 /* No parameters to preserve for exit path */
|
||||
pushw $0 /* Use prefix exit path mechanism */
|
||||
/* Etherboot expects to be contiguous in memory once loaded.
|
||||
* LILO doesn't do this, but since we don't need any
|
||||
* information that's left in the prefix, it doesn't matter:
|
||||
* we just have to ensure that %cs:0000 is where the start of
|
||||
* the Etherboot image *would* be.
|
||||
*/
|
||||
ljmp $(SYSSEG-(PREFIXSIZE/16)), $_start
|
||||
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
int $0x19 /* should try to boot machine */
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
|
||||
.org (PREFIXSIZE-1)
|
||||
.byte 0
|
||||
prefix_end:
|
||||
/*
|
||||
That's about it.
|
||||
*/
|
||||
|
||||
163
src/arch/i386/prefix/lmelf_dprefix.S
Normal file
163
src/arch/i386/prefix/lmelf_dprefix.S
Normal file
@@ -0,0 +1,163 @@
|
||||
#include "elf.h"
|
||||
.arch sledgehammer
|
||||
.code32
|
||||
.equ FLAT_CODE_SEG,_pmcs-_gdt
|
||||
.equ FLAT_DATA_SEG,_pmds-_gdt
|
||||
.equ MSR_K6_EFER, 0xC0000080
|
||||
.equ EFER_LME, 0x00000100
|
||||
.equ X86_CR4_PAE, 0x00000020
|
||||
.equ CR0_PG, 0x80000000
|
||||
|
||||
.section ".prefix", "ax", @progbits
|
||||
|
||||
#define LOAD_ADDR 0x10000
|
||||
|
||||
/* ELF Header */
|
||||
.globl elf_header
|
||||
elf_header:
|
||||
e_ident: .byte 0x7f, 'E', 'L', 'F', 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0
|
||||
e_type: .short ET_DYN
|
||||
e_machine: .short EM_X86_64
|
||||
e_version: .long 1
|
||||
e_entry: .long LOAD_ADDR + elf_start - elf_header
|
||||
e_phoff: .long elf_program_header - elf_header
|
||||
e_shoff: .long 0
|
||||
e_flags: .long 0
|
||||
e_ehsize: .short elf_header_end - elf_header
|
||||
e_phentsize: .short ELF32_PHDR_SIZE
|
||||
e_phnum: .short (elf_program_header_end - elf_program_header)/ELF32_PHDR_SIZE
|
||||
e_shentsize: .short 0
|
||||
e_shnum: .short 0
|
||||
e_shstrndx: .short 0
|
||||
elf_header_end:
|
||||
|
||||
elf_program_header:
|
||||
phdr1_p_type: .long PT_NOTE
|
||||
phdr1_p_offset: .long elf_note - elf_header
|
||||
phdr1_p_vaddr: .long elf_note
|
||||
phdr1_p_paddr: .long elf_note
|
||||
phdr1_p_filesz: .long elf_note_end - elf_note
|
||||
phdr1_p_memsz: .long elf_note_end - elf_note
|
||||
phdr1_p_flags: .long PF_R | PF_W | PF_X
|
||||
phdr1_p_align: .long 0
|
||||
|
||||
/* The decompressor */
|
||||
phdr2_p_type: .long PT_LOAD
|
||||
phdr2_p_offset: .long 0
|
||||
phdr2_p_vaddr: .long elf_header
|
||||
phdr2_p_paddr: .long LOAD_ADDR
|
||||
phdr2_p_filesz: .long _verbatim_size
|
||||
phdr2_p_memsz: .long _image_size
|
||||
phdr2_p_flags: .long PF_R | PF_W | PF_X
|
||||
phdr2_p_align: .long 16
|
||||
|
||||
elf_program_header_end:
|
||||
|
||||
.globl elf_note
|
||||
elf_note:
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_NAME
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.asciz "Etherboot"
|
||||
4:
|
||||
|
||||
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_VERSION
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.asciz VERSION
|
||||
4:
|
||||
|
||||
#if 0
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_CHECKSUM
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.word 0
|
||||
4:
|
||||
#endif
|
||||
.balign 4
|
||||
elf_note_end:
|
||||
|
||||
elf_start:
|
||||
.code64
|
||||
/* Reload the gdt to something I know */
|
||||
leaq _gdt(%rip), %rax
|
||||
movq %rax, 0x02 + gdtptr(%rip)
|
||||
lgdt gdtptr(%rip)
|
||||
|
||||
/* Enter 32bit compatibility mode */
|
||||
leaq elf_start32(%rip), %rax
|
||||
movl %eax, 0x00 + elf_start32_addr(%rip)
|
||||
ljmp *elf_start32_addr(%rip)
|
||||
|
||||
elf_start32:
|
||||
.code32
|
||||
/* Reload the data segments */
|
||||
movl $FLAT_DATA_SEG, %eax
|
||||
movl %eax, %ds
|
||||
movl %eax, %es
|
||||
movl %eax, %ss
|
||||
|
||||
/* Disable paging */
|
||||
movl %cr0, %eax
|
||||
andl $~CR0_PG, %eax
|
||||
movl %eax, %cr0
|
||||
|
||||
/* Disable long mode */
|
||||
movl $MSR_K6_EFER, %ecx
|
||||
rdmsr
|
||||
andl $~EFER_LME, %eax
|
||||
wrmsr
|
||||
|
||||
/* Disable PAE */
|
||||
movl %cr4, %eax
|
||||
andl $~X86_CR4_PAE, %eax
|
||||
movl %eax, %cr4
|
||||
|
||||
/* Save the first argument */
|
||||
pushl %ebx
|
||||
jmp _start
|
||||
|
||||
gdtptr:
|
||||
.word _gdt_end - _gdt -1
|
||||
.long _gdt
|
||||
.long 0
|
||||
_gdt:
|
||||
elf_start32_addr:
|
||||
.long elf_start32
|
||||
.long FLAT_CODE_SEG
|
||||
_pmcs:
|
||||
/* 32 bit protected mode code segment, base 0 */
|
||||
.word 0xffff,0
|
||||
.byte 0,0x9f,0xcf,0
|
||||
|
||||
_pmds:
|
||||
/* 32 bit protected mode data segment, base 0 */
|
||||
.word 0xffff,0
|
||||
.byte 0,0x93,0xcf,0
|
||||
_gdt_end:
|
||||
|
||||
|
||||
/* Dummy routines to satisfy the build */
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
163
src/arch/i386/prefix/lmelf_prefix.S
Normal file
163
src/arch/i386/prefix/lmelf_prefix.S
Normal file
@@ -0,0 +1,163 @@
|
||||
#include "elf.h"
|
||||
.arch sledgehammer
|
||||
.code32
|
||||
.equ FLAT_CODE_SEG,_pmcs-_gdt
|
||||
.equ FLAT_DATA_SEG,_pmds-_gdt
|
||||
.equ MSR_K6_EFER, 0xC0000080
|
||||
.equ EFER_LME, 0x00000100
|
||||
.equ X86_CR4_PAE, 0x00000020
|
||||
.equ CR0_PG, 0x80000000
|
||||
|
||||
.section ".prefix", "ax", @progbits
|
||||
|
||||
#define LOAD_ADDR 0x10000
|
||||
|
||||
/* ELF Header */
|
||||
.globl elf_header
|
||||
elf_header:
|
||||
e_ident: .byte 0x7f, 'E', 'L', 'F', 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0
|
||||
e_type: .short ET_EXEC
|
||||
e_machine: .short EM_X86_64
|
||||
e_version: .long 1
|
||||
e_entry: .long LOAD_ADDR + elf_start - elf_header
|
||||
e_phoff: .long elf_program_header - elf_header
|
||||
e_shoff: .long 0
|
||||
e_flags: .long 0
|
||||
e_ehsize: .short elf_header_end - elf_header
|
||||
e_phentsize: .short ELF32_PHDR_SIZE
|
||||
e_phnum: .short (elf_program_header_end - elf_program_header)/ELF32_PHDR_SIZE
|
||||
e_shentsize: .short 0
|
||||
e_shnum: .short 0
|
||||
e_shstrndx: .short 0
|
||||
elf_header_end:
|
||||
|
||||
elf_program_header:
|
||||
phdr1_p_type: .long PT_NOTE
|
||||
phdr1_p_offset: .long elf_note - elf_header
|
||||
phdr1_p_vaddr: .long elf_note
|
||||
phdr1_p_paddr: .long elf_note
|
||||
phdr1_p_filesz: .long elf_note_end - elf_note
|
||||
phdr1_p_memsz: .long elf_note_end - elf_note
|
||||
phdr1_p_flags: .long PF_R | PF_W | PF_X
|
||||
phdr1_p_align: .long 0
|
||||
|
||||
/* The decompressor */
|
||||
phdr2_p_type: .long PT_LOAD
|
||||
phdr2_p_offset: .long 0
|
||||
phdr2_p_vaddr: .long elf_header
|
||||
phdr2_p_paddr: .long LOAD_ADDR
|
||||
phdr2_p_filesz: .long _verbatim_size
|
||||
phdr2_p_memsz: .long _image_size
|
||||
phdr2_p_flags: .long PF_R | PF_W | PF_X
|
||||
phdr2_p_align: .long 16
|
||||
|
||||
elf_program_header_end:
|
||||
|
||||
.globl elf_note
|
||||
elf_note:
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_NAME
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.asciz "Etherboot"
|
||||
4:
|
||||
|
||||
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_VERSION
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.asciz VERSION
|
||||
4:
|
||||
|
||||
#if 0
|
||||
.balign 4
|
||||
.int 2f - 1f
|
||||
.int 4f - 3f
|
||||
.int EIN_PROGRAM_CHECKSUM
|
||||
1: .asciz "ELFBoot"
|
||||
2:
|
||||
.balign 4
|
||||
3:
|
||||
.word 0
|
||||
4:
|
||||
#endif
|
||||
.balign 4
|
||||
elf_note_end:
|
||||
|
||||
elf_start:
|
||||
.code64
|
||||
/* Reload the gdt to something I know */
|
||||
leaq _gdt(%rip), %rax
|
||||
movq %rax, 0x02 + gdtptr(%rip)
|
||||
lgdt gdtptr(%rip)
|
||||
|
||||
/* Enter 32bit compatibility mode */
|
||||
leaq elf_start32(%rip), %rax
|
||||
movl %eax, 0x00 + elf_start32_addr(%rip)
|
||||
ljmp *elf_start32_addr(%rip)
|
||||
|
||||
elf_start32:
|
||||
.code32
|
||||
/* Reload the data segments */
|
||||
movl $FLAT_DATA_SEG, %eax
|
||||
movl %eax, %ds
|
||||
movl %eax, %es
|
||||
movl %eax, %ss
|
||||
|
||||
/* Disable paging */
|
||||
movl %cr0, %eax
|
||||
andl $~CR0_PG, %eax
|
||||
movl %eax, %cr0
|
||||
|
||||
/* Disable long mode */
|
||||
movl $MSR_K6_EFER, %ecx
|
||||
rdmsr
|
||||
andl $~EFER_LME, %eax
|
||||
wrmsr
|
||||
|
||||
/* Disable PAE */
|
||||
movl %cr4, %eax
|
||||
andl $~X86_CR4_PAE, %eax
|
||||
movl %eax, %cr4
|
||||
|
||||
/* Save the first argument */
|
||||
pushl %ebx
|
||||
jmp _start
|
||||
|
||||
gdtptr:
|
||||
.word _gdt_end - _gdt -1
|
||||
.long _gdt
|
||||
.long 0
|
||||
_gdt:
|
||||
elf_start32_addr:
|
||||
.long elf_start32
|
||||
.long FLAT_CODE_SEG
|
||||
_pmcs:
|
||||
/* 32 bit protected mode code segment, base 0 */
|
||||
.word 0xffff,0
|
||||
.byte 0,0x9f,0xcf,0
|
||||
|
||||
_pmds:
|
||||
/* 32 bit protected mode data segment, base 0 */
|
||||
.word 0xffff,0
|
||||
.byte 0,0x93,0xcf,0
|
||||
_gdt_end:
|
||||
|
||||
|
||||
/* Dummy routines to satisfy the build */
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
16
src/arch/i386/prefix/nullprefix.S
Normal file
16
src/arch/i386/prefix/nullprefix.S
Normal file
@@ -0,0 +1,16 @@
|
||||
.org 0
|
||||
.text
|
||||
.arch i386
|
||||
|
||||
.section ".prefix", "ax", @progbits
|
||||
.code16
|
||||
.globl _prefix
|
||||
_prefix:
|
||||
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
398
src/arch/i386/prefix/pxeprefix.S
Normal file
398
src/arch/i386/prefix/pxeprefix.S
Normal file
@@ -0,0 +1,398 @@
|
||||
/* Offsets of words containing ROM's CS and size (in 512 byte blocks)
|
||||
* from start of floppy boot block at 0x7c00
|
||||
* Offsets must match those in etherboot.h
|
||||
*/
|
||||
#define FLOPPY_SEGMENT 0x7c0
|
||||
|
||||
#define PXENV_UNDI_CLEANUP 0x02
|
||||
#define PXENV_UNDI_SHUTDOWN 0x05
|
||||
#define PXENV_STOP_UNDI 0x15
|
||||
#define PXENV_UNLOAD_STACK 0x70
|
||||
#define PXENV_STOP_BASE 0x76
|
||||
|
||||
#define PUSHA_SIZE 16
|
||||
#define PXE_STACK_MAGIC 0x57ac /* 'STac' */
|
||||
|
||||
.text
|
||||
.code16
|
||||
.arch i386
|
||||
.org 0
|
||||
.section ".prefix", "ax", @progbits
|
||||
.globl _prefix
|
||||
/*****************************************************************************
|
||||
* Entry point: set cs, ds, bp, print welcome message
|
||||
*****************************************************************************
|
||||
*/
|
||||
_prefix:
|
||||
jmp $FLOPPY_SEGMENT, $code_start-_prefix
|
||||
10: .asciz "PXE->EB "
|
||||
code_start:
|
||||
pusha /* Preserve all registers */
|
||||
push %ds
|
||||
movw %sp, %bp /* %bp must be preserved, hence do
|
||||
* this after the pusha */
|
||||
push $PXE_STACK_MAGIC /* PXE stack magic marker */
|
||||
|
||||
push %cs /* Set up data segment */
|
||||
pop %ds
|
||||
mov $0x40, %cx /* Set up %fs for access to 40:13 */
|
||||
mov %cx, %fs
|
||||
movw $10b-_prefix, %si /* Print welcome message */
|
||||
call print_message
|
||||
|
||||
/*****************************************************************************
|
||||
* Detect type of PXE available (!PXE, PXENV+ or none)
|
||||
*****************************************************************************
|
||||
*/
|
||||
detect_pxe:
|
||||
les 4+PUSHA_SIZE+2(%bp), %di /* !PXE structure */
|
||||
cmpl $0x45585021, %es:(%di) /* '!PXE' signature */
|
||||
je detected_pxe
|
||||
mov $0x5650, %ax
|
||||
int $0x1a
|
||||
cmp $0x564e, %ax
|
||||
jne detected_nothing
|
||||
cmpl $0x4e455850, %es:(%bx) /* 'PXEN' signature */
|
||||
jne detected_nothing
|
||||
cmpw $0x2b56, %es:4(%bx) /* 'V+' signature */
|
||||
je detected_pxenv
|
||||
|
||||
detected_nothing:
|
||||
movw $10f-_prefix, %si
|
||||
call print_message
|
||||
jmp finished_with_error
|
||||
10: .asciz "No PXE "
|
||||
|
||||
detected_pxenv: /* es:bx points to PXENV+ structure */
|
||||
push %es
|
||||
push %bx
|
||||
push %es:0x24(%bx) /* UNDI code segment */
|
||||
push %es:0x26(%bx) /* UNDI code size */
|
||||
push %es:0x20(%bx) /* UNDI data segment */
|
||||
push %es:0x22(%bx) /* UNDI data size */
|
||||
les %es:0x0a(%bx), %di /* Entry point to %es:%di */
|
||||
movw $10f-_prefix, %si
|
||||
jmp pxe_setup_done
|
||||
10: .asciz "PXENV+ "
|
||||
|
||||
detected_pxe: /* es:di points to !PXE structure */
|
||||
push %es
|
||||
push %di
|
||||
push %es:0x30(%di) /* UNDI code segment */
|
||||
push %es:0x36(%di) /* UNDI code size */
|
||||
push %es:0x28(%di) /* UNDI data segment */
|
||||
push %es:0x2e(%di) /* UNDI data size */
|
||||
les %es:0x10(%di), %di /* Entry point to %es:%di */
|
||||
movw $10f-_prefix, %si
|
||||
jmp pxe_setup_done
|
||||
10: .asciz "!PXE "
|
||||
|
||||
pxe_setup_done:
|
||||
mov %es, pxe_entry_segment - _prefix
|
||||
mov %di, pxe_entry_offset - _prefix
|
||||
pop %ax
|
||||
mov %ax, undi_data_size - _prefix
|
||||
pop %ax
|
||||
mov %ax, undi_data_segment - _prefix
|
||||
pop %ax
|
||||
mov %ax, undi_code_size - _prefix
|
||||
pop %ax
|
||||
mov %ax, undi_code_segment - _prefix
|
||||
call print_message
|
||||
pop %di
|
||||
pop %es /* Exit with %es:%di containing structure address */
|
||||
|
||||
/*****************************************************************************
|
||||
* Print information about located structure
|
||||
*****************************************************************************
|
||||
*/
|
||||
print_structure_information:
|
||||
call print_segoff /* %es:%di contains address of structure */
|
||||
les %ds:(pxe_entry_segoff - _prefix), %di
|
||||
call print_segoff
|
||||
les %ds:(undi_code_segoff - _prefix), %di
|
||||
call print_segoff
|
||||
les %ds:(undi_data_segoff - _prefix), %di
|
||||
call print_segoff
|
||||
|
||||
/*****************************************************************************
|
||||
* Unload PXE base code and UNDI driver
|
||||
*****************************************************************************
|
||||
*/
|
||||
#ifdef PXELOADER_KEEP_ALL
|
||||
xor %ax, %ax /* Force zero flag to show success */
|
||||
jmp do_not_free_base_mem /* Skip the unloading */
|
||||
#endif /* PXELOADER_KEEP_ALL */
|
||||
|
||||
unload_pxe:
|
||||
mov $PXENV_UNLOAD_STACK, %bx
|
||||
call pxe_call
|
||||
mov $PXENV_STOP_UNDI, %bx
|
||||
call pxe_call
|
||||
pushfw /* Ignore PXENV_UNDI_CLEANUP errors */
|
||||
mov $PXENV_UNDI_CLEANUP, %bx
|
||||
call pxe_call
|
||||
popfw
|
||||
/* On exit, zero flag is set iff all calls were successful */
|
||||
|
||||
/*****************************************************************************
|
||||
* Free base memory
|
||||
*****************************************************************************
|
||||
*/
|
||||
free_base_mem:
|
||||
jnz do_not_free_base_mem /* Using zero flag from unload_pxe */
|
||||
|
||||
mov undi_code_segment - _prefix, %bx
|
||||
mov undi_data_segment - _prefix, %cx
|
||||
mov undi_code_size - _prefix, %ax
|
||||
cmp %bx, %cx
|
||||
jb 1f
|
||||
mov %cx, %bx
|
||||
mov undi_data_size - _prefix, %ax
|
||||
1: add $0x0f, %ax /* Round up to next segment */
|
||||
shr $4, %ax
|
||||
add %bx, %ax /* Highest segment address into %ax */
|
||||
add $(1024 / 16 - 1), %ax /* Round up to next kb */
|
||||
shr $6, %ax /* New free basemem size in %ax */
|
||||
mov %fs:(0x13), %bx /* Old free base memory in %bx */
|
||||
mov %ax, %fs:(0x13) /* Store new free base memory size */
|
||||
|
||||
/* Note that zero_mem_loop will also zero out our stack, so make
|
||||
* sure the stack is empty at this point.
|
||||
*/
|
||||
mov %ax, %dx
|
||||
sub %bx, %dx /* numberof kb to zero in %dx */
|
||||
shl $6, %bx /* Segment address into %bx */
|
||||
zero_mem_loop:
|
||||
mov %bx, %es /* kB boundary into %es:00 */
|
||||
xor %ax, %ax
|
||||
xor %di, %di
|
||||
mov $0x400, %cx
|
||||
rep stosb /* fill kB with zeroes */
|
||||
add $(1024 / 16), %bx
|
||||
dec %dx
|
||||
jnz zero_mem_loop
|
||||
/* Will exit here with zero flag set, so no need to set it explicitly
|
||||
* in order to indicate success.
|
||||
*/
|
||||
|
||||
do_not_free_base_mem:
|
||||
pushf /* Save success (zero) flag status */
|
||||
mov %fs:(0x13), %ax /* Free base memory in %ax */
|
||||
call print_hex_word /* Print free base memory */
|
||||
popf /* Restore success (zero) flag */
|
||||
|
||||
/*****************************************************************************
|
||||
* Exit point
|
||||
* Jump to finished with the zero flag set to indicate success, or to
|
||||
* finished_with_error to always report an error
|
||||
*****************************************************************************
|
||||
*/
|
||||
finished:
|
||||
movw $10f-_prefix, %si
|
||||
jz 1f
|
||||
finished_with_error:
|
||||
movw $20f-_prefix, %si
|
||||
1:
|
||||
call print_message
|
||||
jmp 99f
|
||||
10: .asciz " ok\n"
|
||||
20: .asciz " err\n"
|
||||
|
||||
|
||||
/* We place a stack here. It doesn't get used until after all
|
||||
* the above code is finished, so we can happily write all
|
||||
* over it. Putting the stack here ensures that it doesn't
|
||||
* accidentally go over the 512 byte threshold, which would
|
||||
* cause problems when returning via start32's prefix
|
||||
* relocation mechanism.
|
||||
*/
|
||||
_estack:
|
||||
99:
|
||||
|
||||
/*****************************************************************************
|
||||
* Run Etherboot main code
|
||||
*****************************************************************************
|
||||
*/
|
||||
run_etherboot:
|
||||
/* Very temporarily switch stacks to one internal to the
|
||||
* prefix. Do this because the stack provided by the PXE ROM
|
||||
* could be absolutely anywhere, including in an area of
|
||||
* memory that the call to prelocate will vapourise...
|
||||
*/
|
||||
pushw %ss /* PXE stack pointer to ES:DI */
|
||||
popw %es
|
||||
movw %sp, %di
|
||||
pushw %ds /* Set up stack in "safe" area */
|
||||
popw %ss
|
||||
movw $_estack-_prefix, %sp
|
||||
pushw %es /* Record PXE stack pointer */
|
||||
pushw %di
|
||||
/* Relocate payload and stack to claimed base memory */
|
||||
pushw $4 /* Preserve old PXE stack pointer */
|
||||
call prelocate
|
||||
popw %ax /* Remove parameter */
|
||||
pushl $4 /* Preserve old PXE stack pointer */
|
||||
pushw $0 /* Indicate prefix exit mechanism */
|
||||
jmp _start /* Run Etherboot */
|
||||
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
pushw %cs /* Set %ds, %bp for access to text */
|
||||
popw %ds
|
||||
call 1f
|
||||
1: popw %bp
|
||||
popw %di /* Old PXE stack to %es:di */
|
||||
popw %es
|
||||
cmpw $PXE_STACK_MAGIC, %es:0(%di) /* See if PXE stack intact */
|
||||
jne exit_via_int18
|
||||
exit_via_pxe: /* Stack OK, return to PXE */
|
||||
push %es /* Restore PXE stack pointer */
|
||||
pop %ss
|
||||
mov %di, %sp
|
||||
pop %ax /* Discard PXE_STACK_MAGIC marker */
|
||||
leaw (10f-1b)(%bp), %si
|
||||
call print_exit_message
|
||||
pop %ds /* Restore PXE's DS */
|
||||
popa /* Restore PXE's other registers */
|
||||
movw $0, %ax /* Return PXENV_STATUS_SUCCESS */
|
||||
lret /* Return control to PXE ROM */
|
||||
10: .asciz "EB->PXE\r\n"
|
||||
exit_via_int18: /* Stack damaged, do int 18 */
|
||||
leaw (10f-1b)(%bp), %si
|
||||
call print_exit_message
|
||||
int $0x18
|
||||
10: .asciz "EB->BIOS\r\n"
|
||||
print_exit_message:
|
||||
movw $0x0007, %bx /* page 0, attribute 7 (normal) */
|
||||
movb $0x0e, %ah /* write char, tty mode */
|
||||
1: lodsb
|
||||
testb %al, %al
|
||||
je 2f
|
||||
int $0x10
|
||||
jmp 1b
|
||||
2: ret
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
|
||||
/*****************************************************************************
|
||||
* Subroutine: print character in %al (with LF -> LF,CR translation)
|
||||
*****************************************************************************
|
||||
*/
|
||||
print_character:
|
||||
movw $0x0007, %bx /* page 0, attribute 7 (normal) */
|
||||
movb $0x0e, %ah /* write char, tty mode */
|
||||
cmpb $0x0a, %al /* '\n'? */
|
||||
jne 1f
|
||||
int $0x10
|
||||
movb $0x0d, %al
|
||||
1: int $0x10
|
||||
ret
|
||||
|
||||
/*****************************************************************************
|
||||
* Subroutine: print a zero-terminated message starting at %si
|
||||
*****************************************************************************
|
||||
*/
|
||||
print_message:
|
||||
1: lodsb
|
||||
testb %al, %al
|
||||
je 2f
|
||||
call print_character
|
||||
jmp 1b
|
||||
2: ret
|
||||
|
||||
/*****************************************************************************
|
||||
* Subroutine: print hex word in %ax
|
||||
*****************************************************************************
|
||||
*/
|
||||
print_hex_word:
|
||||
mov $4, %cx
|
||||
1:
|
||||
push %ax
|
||||
shr $12, %ax
|
||||
/* Courtesy of Norbert Juffa <norbert.juffa@amd.com> */
|
||||
cmp $10, %al
|
||||
sbb $0x69, %al
|
||||
das
|
||||
call print_character
|
||||
pop %ax
|
||||
shl $4, %ax
|
||||
loop 1b
|
||||
ret
|
||||
|
||||
/*****************************************************************************
|
||||
* Subroutine: print segment:offset address in %es:%di
|
||||
*****************************************************************************
|
||||
*/
|
||||
print_segoff:
|
||||
push %di
|
||||
push %es
|
||||
pop %ax
|
||||
call print_hex_word
|
||||
movb $0x3a,%al /* ':' */
|
||||
call print_character
|
||||
pop %ax
|
||||
call print_hex_word
|
||||
mov $0x20, %al /* ' ' */
|
||||
call print_character
|
||||
ret
|
||||
|
||||
/*****************************************************************************
|
||||
* Make a PXE API call. Works with either !PXE or PXENV+ API.
|
||||
* Opcode in %bx. pxe_parameter_structure always used.
|
||||
* Returns status code (not exit code) in %bx and prints it.
|
||||
* ORs status code with overall status code in pxe_overall_status, returns
|
||||
* with zero flag set iff all PXE API calls have been successful.
|
||||
*****************************************************************************
|
||||
*/
|
||||
pxe_call:
|
||||
/* Set up registers for PXENV+ API. %bx already set up */
|
||||
push %ds
|
||||
pop %es
|
||||
mov $pxe_parameter_structure - _prefix, %di
|
||||
/* Set up stack for !PXE API */
|
||||
pushw %cs
|
||||
pushw %di
|
||||
pushw %bx
|
||||
/* Make the API call */
|
||||
lcall *(pxe_entry_segoff - _prefix)
|
||||
/* Reset the stack */
|
||||
add $6, %sp
|
||||
mov pxe_parameter_structure - _prefix, %ax
|
||||
push %ax
|
||||
call print_hex_word
|
||||
mov $0x20, %ax /* ' ' */
|
||||
call print_character
|
||||
pop %bx
|
||||
or %bx, pxe_overall_status - _prefix
|
||||
ret
|
||||
|
||||
/*****************************************************************************
|
||||
* PXE data structures
|
||||
*****************************************************************************
|
||||
*/
|
||||
|
||||
pxe_overall_status: .word 0
|
||||
|
||||
pxe_entry_segoff:
|
||||
pxe_entry_offset: .word 0
|
||||
pxe_entry_segment: .word 0
|
||||
|
||||
undi_code_segoff:
|
||||
undi_code_size: .word 0
|
||||
undi_code_segment: .word 0
|
||||
|
||||
undi_data_segoff:
|
||||
undi_data_size: .word 0
|
||||
undi_data_segment: .word 0
|
||||
|
||||
pxe_parameter_structure:
|
||||
.word 0
|
||||
.word 0,0,0,0,0
|
||||
|
||||
end_of_pxeloader:
|
||||
|
||||
.balign 16, 0
|
||||
payload:
|
||||
416
src/arch/i386/prefix/romprefix.S
Normal file
416
src/arch/i386/prefix/romprefix.S
Normal file
@@ -0,0 +1,416 @@
|
||||
/* At entry, the processor is in 16 bit real mode and the code is being
|
||||
* executed from an address it was not linked to. Code must be pic and
|
||||
* 32 bit sensitive until things are fixed up.
|
||||
*
|
||||
* Also be very careful as the stack is at the rear end of the interrupt
|
||||
* table so using a noticeable amount of stack space is a no-no.
|
||||
*/
|
||||
|
||||
/* Define DELAYED_INT when NO_DELAYED_INT is not defined.
|
||||
* This allows positive tests instead of tests that contain
|
||||
* double negatives, and become confusing.
|
||||
*/
|
||||
#ifndef NO_DELAYED_INT
|
||||
#define DELAYED_INT
|
||||
#endif
|
||||
|
||||
/* We need some unique magic ID, if we defer startup thru the INT18H or INT19H
|
||||
* handler. This way, we can check if we have already been installed.
|
||||
*/
|
||||
#ifndef MAGIC
|
||||
#define MAGIC 0xE44C
|
||||
#endif
|
||||
|
||||
/* Hook into INT18H or INT19H handler */
|
||||
#ifdef BOOT_INT18H
|
||||
#define BOOT_INT 0x18
|
||||
#else
|
||||
#define BOOT_INT 0x19
|
||||
#endif
|
||||
|
||||
#define BOOT_INT_VEC BOOT_INT*4
|
||||
#define SCRATCHVEC 0x300
|
||||
|
||||
/* Prefix exit codes. We store these on the stack so that we will
|
||||
* know how to return control to the BIOS when Etherboot exits.
|
||||
*/
|
||||
#define EXIT_VIA_LRET 0x0
|
||||
#define EXIT_VIA_INT_18 0x1
|
||||
#define EXIT_VIA_BOOT_INT 0x2
|
||||
|
||||
.text
|
||||
.code16
|
||||
.arch i386
|
||||
.org 0
|
||||
.section ".prefix", "ax", @progbits
|
||||
.globl _prefix
|
||||
_prefix:
|
||||
.word 0xAA55 /* BIOS extension signature */
|
||||
size: .byte 0 /* number of 512 byte blocks */
|
||||
/* = number of 256 word blocks */
|
||||
/* filled in by makerom program */
|
||||
jmp over /* skip over checksum */
|
||||
.byte 0 /* checksum */
|
||||
jmp legacyentry /* alternate entry point +6 */
|
||||
/* used by mknbi-rom */
|
||||
|
||||
#ifdef PCI_PNP_HEADER
|
||||
mfgstr:
|
||||
.asciz "Etherboot"
|
||||
|
||||
#ifdef PXE_EXPORT
|
||||
.org 0x16
|
||||
.word UNDIROMID - _prefix
|
||||
#endif /* PXE_EXPORT */
|
||||
|
||||
.org 0x18
|
||||
.word PCI - _prefix
|
||||
.word PnP - _prefix
|
||||
|
||||
PCI:
|
||||
.ascii "PCIR"
|
||||
.word 0x0000 /* vendor ID, filled in by makerom */
|
||||
.word 0x0000 /* device ID, filled in by makerom */
|
||||
.word 0x0000 /* pointer to vital product data */
|
||||
.word 0x0018 /* PCI data structure length */
|
||||
.byte 0x00 /* PCI data structure revision */
|
||||
.byte 0x02 /* Device Base Type code */
|
||||
.byte 0x00 /* Device Sub-Type code */
|
||||
.byte 0x00 /* Device Interface Type code */
|
||||
.word 0x0000 /* Image length same as offset 02h */
|
||||
.word 0x0001 /* revision level of code/data */
|
||||
.byte 0x00 /* code type */
|
||||
.byte 0x80 /* indicator (last PCI data structure) */
|
||||
.word 0x0000 /* reserved */
|
||||
|
||||
PnP:
|
||||
.ascii "$PnP"
|
||||
.byte 0x01 /* structure revision */
|
||||
.byte 0x02 /* length (in 16 byte increments) */
|
||||
.word 0x0000 /* offset of next header */
|
||||
.byte 0x00 /* Reserved */
|
||||
.byte 0x00 /* checksum filled by makerom */
|
||||
.long 0x00000000 /* Device identifier */
|
||||
.word mfgstr - _prefix
|
||||
.word 0x0 /* pointer to product name */
|
||||
/* filled by makerom */
|
||||
.byte 0x02 /* Device Base Type code */
|
||||
.byte 0x00 /* Device Sub-Type code */
|
||||
.byte 0x00 /* Device Interface Type code */
|
||||
.byte 0x14 /* device indicator */
|
||||
.word 0x0000 /* boot connection vector */
|
||||
.word 0x0000 /* disconnect vector */
|
||||
.word pnpentry - _prefix
|
||||
.word 0x0000 /* reserved */
|
||||
.word 0x0000 /* static resource information vector */
|
||||
#ifdef PXE_EXPORT
|
||||
UNDIROMID:
|
||||
.ascii "UNDI"
|
||||
.byte UNDIROMID_end - UNDIROMID /* length of structure */
|
||||
.byte 0 /* Checksum */
|
||||
.byte 0 /* Structure revision */
|
||||
.byte 0,1,2 /* PXE version 2.1.0 */
|
||||
.word UNDILoader - _prefix /* Offset to loader routine */
|
||||
.word UNDIStackSize /* Stack segment size */
|
||||
.word UNDIDataSize /* Data segment size */
|
||||
.word UNDICodeSize /* Code segment size */
|
||||
.ascii "PCIR"
|
||||
|
||||
/* The code segment contains our pxe_stack_t plus the PXE and
|
||||
* RM callback interfaces. We don't actually use a data
|
||||
* segment, but we put a nonzero value here to avoid confusing
|
||||
* things. 16k of stack space should be enough.
|
||||
*
|
||||
* When we claim our own memory, we fill out the data segment
|
||||
* with the address and size of the real-mode stack, so that
|
||||
* NBPs will free that area of memory for us. When the UNDI
|
||||
* loader is used to initialise us, we will never need a
|
||||
* real-mode stack because we will only ever be called via the
|
||||
* PXE API, hence our stack is already in base memory.
|
||||
*/
|
||||
.equ UNDICodeSize, _pxe_stack_size
|
||||
.equ UNDIDataSize, _real_mode_stack_size
|
||||
.equ UNDIStackSize, _real_mode_stack_size
|
||||
UNDIROMID_end:
|
||||
#endif /* PXE_EXPORT */
|
||||
|
||||
#endif /* PCI_PNP_HEADER */
|
||||
|
||||
/*
|
||||
* Explicitly specify DI is wrt ES to avoid problems with some BIOSes
|
||||
* Discovered by Eric Biederman
|
||||
* In addition, some BIOSes don't point DI to the string $PnP so
|
||||
* we need another #define to take care of that.
|
||||
*/
|
||||
over:
|
||||
#ifdef DEBUG_ROMPREFIX
|
||||
call print_bcv
|
||||
#endif
|
||||
/* Omit this test for ISA cards anyway */
|
||||
#ifdef PCI_PNP_HEADER
|
||||
/* Accept old name too for backward compatibility */
|
||||
#if !defined(BBS_BUT_NOT_PNP_COMPLIANT) && !defined(PNP_BUT_NOT_BBS_COMPLIANT)
|
||||
cmpw $'$'+'P'*256,%es:0(%di)
|
||||
jne notpnp
|
||||
cmpw $'n'+'P'*256,%es:2(%di)
|
||||
jne notpnp
|
||||
#endif /* BBS_BUT_NOT_PNP_COMPLIANT */
|
||||
movw $0x20,%ax
|
||||
lret
|
||||
#endif /* PCI_PNP_HEADER */
|
||||
notpnp:
|
||||
#ifdef DEBUG_ROMPREFIX
|
||||
call print_notpnp
|
||||
#endif
|
||||
#ifdef DELAYED_INT
|
||||
pushw %ax
|
||||
pushw %ds
|
||||
xorw %ax,%ax
|
||||
movw %ax,%ds /* access first 64kB segment */
|
||||
movw SCRATCHVEC+4, %ax /* check if already installed */
|
||||
cmpw $MAGIC, %ax /* check magic word */
|
||||
jz installed
|
||||
movw BOOT_INT_VEC, %ax /* hook into INT18H or INT19H */
|
||||
movw %ax, SCRATCHVEC
|
||||
movw BOOT_INT_VEC+2, %ax
|
||||
movw %ax, SCRATCHVEC+2
|
||||
movw $start_int - _prefix, %ax
|
||||
movw %ax, BOOT_INT_VEC
|
||||
movw %cs,%ax
|
||||
movw %ax, BOOT_INT_VEC+2
|
||||
movw $MAGIC, %ax /* set magic word */
|
||||
movw %ax, SCRATCHVEC+4
|
||||
#ifdef DEBUG_ROMPREFIX
|
||||
call print_installed
|
||||
#endif
|
||||
installed:
|
||||
popw %ds
|
||||
popw %ax
|
||||
movw $0x20,%ax
|
||||
lret
|
||||
|
||||
start_int: /* clobber magic id, so that we will */
|
||||
#ifdef DEBUG_ROMPREFIX
|
||||
call print_start_int
|
||||
#endif
|
||||
xorw %ax,%ax /* not inadvertendly end up in an */
|
||||
movw %ax,%ds /* endless loop */
|
||||
movw %ax, SCRATCHVEC+4
|
||||
movw SCRATCHVEC+2, %ax /* restore original INT19h handler */
|
||||
movw %ax, BOOT_INT_VEC+2
|
||||
movw SCRATCHVEC, %ax
|
||||
movw %ax, BOOT_INT_VEC
|
||||
pushl %eax /* padding */
|
||||
pushw $EXIT_VIA_BOOT_INT
|
||||
jmp invoke
|
||||
#endif /* DELAYED_INT */
|
||||
|
||||
|
||||
|
||||
|
||||
legacyentry:
|
||||
#ifdef DEBUG_ROMPREFIX
|
||||
call print_legacyentry
|
||||
#endif
|
||||
pushw $EXIT_VIA_LRET
|
||||
jmp invoke
|
||||
|
||||
|
||||
|
||||
#ifdef PCI_PNP_HEADER
|
||||
pnpentry:
|
||||
#ifdef DEBUG_ROMPREFIX
|
||||
call print_bev
|
||||
#endif
|
||||
pushl %eax /* padding */
|
||||
pushw $EXIT_VIA_INT_18
|
||||
jmp invoke
|
||||
#endif /* PCI_PNP_HEADER */
|
||||
|
||||
|
||||
invoke:
|
||||
/* Store ROM segment and size on stack */
|
||||
pushw %ax
|
||||
pushw %ds
|
||||
pushw %cs
|
||||
movzbw %cs:(size-_prefix), %ax
|
||||
shlw $9, %ax /* 512-byte blocks */
|
||||
pushw %ax
|
||||
/* Relocate to free base memory, switch stacks */
|
||||
pushw $12 /* Preserve exit code & far ret addr */
|
||||
call prelocate
|
||||
/* We are now running in RAM */
|
||||
popw %ax /* padding */
|
||||
movw %cs, %ax
|
||||
movw %ax, %ds
|
||||
popw %ds:(_prefix_rom+2) /* ROM size */
|
||||
popw %ds:(_prefix_rom+0) /* ROM segment */
|
||||
popw %ds /* Original %ds */
|
||||
popw %ax /* Original %ax */
|
||||
pushw %ax /* 4-byte alignment */
|
||||
pushl $8 /* Preserve exit code & far ret addr */
|
||||
pushw $0 /* Set null return address */
|
||||
jmp _start
|
||||
|
||||
|
||||
.section ".text16", "ax", @progbits
|
||||
.globl prefix_exit
|
||||
prefix_exit:
|
||||
popw %ax /* padding */
|
||||
popw %ax /* %ax = exit code */
|
||||
cmpw $EXIT_VIA_LRET, %ax
|
||||
jne 1f
|
||||
/* Exit via LRET */
|
||||
lret
|
||||
1: addw $4, %sp /* Strip padding */
|
||||
cmpw $EXIT_VIA_BOOT_INT, %ax
|
||||
jne 2f
|
||||
/* Exit via int BOOT_INT */
|
||||
int $BOOT_INT /* Try original vector */
|
||||
2: /* Exit via int $0x18 */
|
||||
int $0x18 /* As per BIOS Boot Spec, next dev */
|
||||
.globl prefix_exit_end
|
||||
prefix_exit_end:
|
||||
.previous
|
||||
|
||||
|
||||
|
||||
#ifdef PXE_EXPORT
|
||||
|
||||
#include "callbacks.h"
|
||||
#define PXENV_UNDI_LOADER 0x104d
|
||||
|
||||
.section ".prefix"
|
||||
UNDILoader:
|
||||
/* Loader API is different to the usual PXE API; there is no
|
||||
* opcode on the stack. We arrange the stack to look like a
|
||||
* normal PXE API call; this makes the Etherboot internals
|
||||
* cleaner and avoids adding an extra API type just for the
|
||||
* PXE loader.
|
||||
*/
|
||||
pushw %bx
|
||||
movw %sp, %ax /* Store original %ss:sp */
|
||||
pushw %ss
|
||||
pushw %ax
|
||||
pushl %eax /* Space for loader structure ptr */
|
||||
pushw %bp
|
||||
movw %sp, %bp
|
||||
movw 16(%bp), %ax /* Copy loader structure ptr */
|
||||
movw %ax, 2(%bp)
|
||||
movw 18(%bp), %ax
|
||||
movw %ax, 4(%bp)
|
||||
popw %bp
|
||||
pushw $PXENV_UNDI_LOADER /* PXE 'opcode' */
|
||||
pushl %eax /* dummy return address */
|
||||
/* Stack now looks like a normal PXE API call */
|
||||
/* Store ROM segment and size on stack */
|
||||
pushw %ax
|
||||
pushw %cs
|
||||
movzbw %cs:(size-_prefix), %ax
|
||||
shlw $9, %ax /* 512-byte blocks */
|
||||
pushw %ax
|
||||
/* Unpack Etherboot into temporarily claimed base memory */
|
||||
pushw $20 /* Dummy ret, PXE params, orig ss:sp */
|
||||
call prelocate
|
||||
popw %ax /* discard */
|
||||
popw %cs:(_prefix_rom+2) /* ROM size */
|
||||
popw %cs:(_prefix_rom+0) /* ROM segment */
|
||||
popw %ax /* Original %ax */
|
||||
/* Inhibit automatic deallocation of base memory */
|
||||
movl $0, %cs:_prefix_image_basemem
|
||||
/* Make PXE API call to Etherboot */
|
||||
pushl $0x201 /* PXE API version */
|
||||
/* Need to USE_INTERNAL_STACK, since we will call relocate() */
|
||||
pushl $(EB_OPCODE_PXE|EB_USE_INTERNAL_STACK) /* PXE API call type */
|
||||
call _entry
|
||||
addw $18, %sp /* discard */
|
||||
popw %bx /* Restore original %ss:sp */
|
||||
popw %ss
|
||||
movw %bx, %sp
|
||||
popw %bx
|
||||
call deprelocate
|
||||
lret $2 /* Skip our PXE 'opcode' */
|
||||
#endif /* PXE_EXPORT */
|
||||
|
||||
#ifdef DEBUG_ROMPREFIX
|
||||
.section ".prefix"
|
||||
|
||||
print_bcv:
|
||||
pushw %si
|
||||
movw $1f-_prefix, %si
|
||||
call print_message
|
||||
popw %si
|
||||
ret
|
||||
1: .asciz "ROM detected\r\n"
|
||||
|
||||
print_bev:
|
||||
pushw %si
|
||||
movw $1f-_prefix, %si
|
||||
call print_message
|
||||
popw %si
|
||||
ret
|
||||
1: .asciz "booting\r\n"
|
||||
|
||||
print_notpnp:
|
||||
pushw %si
|
||||
movw $1f-_prefix, %si
|
||||
call print_message
|
||||
popw %si
|
||||
ret
|
||||
1: .asciz ": Non-PnP BIOS detected!\r\n"
|
||||
|
||||
print_legacyentry:
|
||||
pushw %si
|
||||
movw $1f-_prefix, %si
|
||||
call print_message
|
||||
popw %si
|
||||
ret
|
||||
1: .asciz "ROM using legacy boot mechanism\r\n"
|
||||
|
||||
print_installed:
|
||||
pushw %si
|
||||
movw $1f-_prefix, %si
|
||||
call print_message
|
||||
popw %si
|
||||
ret
|
||||
1: .ascii "hooked boot via INT"
|
||||
#ifdef BOOT_INT18H
|
||||
.asciz "18\r\n"
|
||||
#else
|
||||
.asciz "19\r\n"
|
||||
#endif
|
||||
|
||||
print_start_int:
|
||||
pushw %si
|
||||
movw $1f-_prefix, %si
|
||||
call print_message
|
||||
popw %si
|
||||
ret
|
||||
1: .asciz "booting via hooked interrupt\r\n"
|
||||
|
||||
print_message:
|
||||
pushaw
|
||||
pushw %ds
|
||||
pushw %cs
|
||||
popw %ds
|
||||
pushw %si
|
||||
movw $1f-_prefix, %si
|
||||
call print_string
|
||||
popw %si
|
||||
call print_string
|
||||
popw %ds
|
||||
popaw
|
||||
ret
|
||||
1: .asciz "Etherboot "
|
||||
|
||||
print_string:
|
||||
1: lodsb
|
||||
testb %al,%al
|
||||
je 2f
|
||||
movw $0x0007, %bx /* page 0, attribute 7 (normal) */
|
||||
movb $0x0e, %ah /* write char, tty mode */
|
||||
int $0x10
|
||||
jmp 1b
|
||||
2: ret
|
||||
|
||||
#endif
|
||||
400
src/arch/i386/prefix/unhuf.S
Normal file
400
src/arch/i386/prefix/unhuf.S
Normal file
@@ -0,0 +1,400 @@
|
||||
/*****************************************************************************
|
||||
* NOTE: This code is no longer used in Etherboot. The obsolete
|
||||
* Makefile target .lzrom refers to it, but it is no longer being
|
||||
* maintained and may no longer work. Use .zrom instead (which uses
|
||||
* the unnrv2b decompressor).
|
||||
*****************************************************************************
|
||||
*/
|
||||
|
||||
/* At entry, the processor is in 16 bit real mode and the code is being
|
||||
* executed from an address it was not linked to. Code must be pic and
|
||||
* 32 bit sensitive until things are fixed up.
|
||||
*/
|
||||
|
||||
|
||||
/* LZHuf (LZSS) Decompressing boot loader for ROM images
|
||||
*
|
||||
* this code is based on the work of Haruyasu Yoshizaki and Haruhiko Okumura
|
||||
* who implemented the original compressor and decompressor in C code
|
||||
*
|
||||
* Converted to 32bit assembly 16 July 2002 Eric Biederman <ebiederman@lnxi.com>
|
||||
* Made PIC 10 Aug 2002 Eric Biederman <ebiederman@lnxi.com>
|
||||
*
|
||||
* Copyright 1997 by M. Gutschke <gutschk@math.uni-muenster.de>
|
||||
*
|
||||
* Compression pays off, as soon as the uncompressed image is bigger than
|
||||
* about 1.5kB. This assumes an average compressibility of about 60%.
|
||||
*/
|
||||
|
||||
|
||||
/* Do not change these values unless you really know what you are doing
|
||||
* the pre-computed lookup tables rely on the buffer size being 4kB or
|
||||
* smaller. The buffer size must be a power of two. The lookahead size has
|
||||
* to fit into 6 bits. If you change any of these numbers, you will also
|
||||
* have to adjust the compressor accordingly.
|
||||
*/
|
||||
#define BUFSZ 4096
|
||||
#define LOOKAHEAD 60
|
||||
#define THRESHOLD 2
|
||||
#define NCHAR (256+LOOKAHEAD-THRESHOLD)
|
||||
#define TABLESZ (NCHAR+NCHAR-1)
|
||||
#define ROOT (TABLESZ-1)
|
||||
|
||||
.text
|
||||
.arch i386
|
||||
.globl _start
|
||||
_start:
|
||||
cli
|
||||
|
||||
/* Save the initial register values */
|
||||
pushal
|
||||
|
||||
/*
|
||||
* See where I am running, and compute %ebp
|
||||
*/
|
||||
call 1f
|
||||
1: pop %ebp
|
||||
subl $1b, %ebp
|
||||
|
||||
/*
|
||||
* INIT -- initializes all data structures
|
||||
* ====
|
||||
*/
|
||||
|
||||
init:
|
||||
cld
|
||||
leal dcodrle(%ebp), %esi /* uncompress run length encoded */
|
||||
leal dcode(%ebp), %edi /* lookup table for codes */
|
||||
movb $6, %dl
|
||||
movb $0x20, %dh
|
||||
xorb %bh,%bh
|
||||
init0:
|
||||
lodsb
|
||||
movb %al,%bl
|
||||
init1:
|
||||
xorl %ecx, %ecx
|
||||
movb %dh,%cl
|
||||
movb %bh,%al
|
||||
rep
|
||||
stosb
|
||||
incb %bh
|
||||
decb %bl
|
||||
jnz init1
|
||||
shrb %dh
|
||||
decb %dl
|
||||
jnz init0
|
||||
movb $1, %bl /* uncompress run length encoded */
|
||||
movb $6, %bh /* lookup table for code lengths */
|
||||
init2:
|
||||
lodsb
|
||||
xorl %ecx, %ecx
|
||||
movb %al,%cl
|
||||
movb %bl,%al
|
||||
rep
|
||||
stosb
|
||||
incb %bl
|
||||
decb %bh
|
||||
jnz init2
|
||||
|
||||
movl $NCHAR, %ecx /* set all frequencies of leaf nodes */
|
||||
movw $1, %ax /* to one */
|
||||
rep
|
||||
stosw
|
||||
leal freq(%ebp), %esi
|
||||
movl $ROOT+1-NCHAR, %ecx
|
||||
init3:
|
||||
lodsw /* update frequencies of non-leaf nodes */
|
||||
movw %ax,%bx
|
||||
lodsw
|
||||
addw %bx,%ax
|
||||
stosw
|
||||
loop init3
|
||||
movw $0xFFFF, %ax
|
||||
stosw /* sentinel with infinite frequency */
|
||||
movl $NCHAR, %ecx
|
||||
movw $TABLESZ, %ax
|
||||
init4:
|
||||
stosw /* update son pointers for leaf nodes */
|
||||
incw %ax
|
||||
loop init4
|
||||
movl $ROOT+1-NCHAR, %ecx
|
||||
xorw %ax,%ax
|
||||
init5:
|
||||
stosw /* update son ptrs for non-leaf nodes */
|
||||
addw $2, %ax
|
||||
loop init5
|
||||
movl $ROOT+1-NCHAR, %ecx
|
||||
movw $NCHAR, %ax
|
||||
init6:
|
||||
stosw /* update parent ptrs for non-leaf nd. */
|
||||
stosw
|
||||
incw %ax
|
||||
loop init6
|
||||
movl $NCHAR, %ecx
|
||||
xorw %ax,%ax
|
||||
stosw /* root node has no parent */
|
||||
init7:
|
||||
stosw /* update parent ptrs for leaf nodes */
|
||||
incw %ax
|
||||
loop init7
|
||||
xorw %ax,%ax
|
||||
stosb /* clear getlen */
|
||||
stosw /* clear getbuf */
|
||||
movb $0x20, %al /* fill text buffer with spaces */
|
||||
leal spaces(%ebp), %edi
|
||||
movl $BUFSZ-LOOKAHEAD, %ecx
|
||||
rep
|
||||
|
||||
stosb
|
||||
/* fall thru */
|
||||
|
||||
/*
|
||||
* MAIN -- reads compressed codes and writes decompressed data
|
||||
* ====
|
||||
*/
|
||||
|
||||
leal _payload(%ebp), %esi /* get length of compressed data stream */
|
||||
leal uncompressed(%ebp), %edi
|
||||
|
||||
lodsl
|
||||
movl %eax, %ecx
|
||||
main1:
|
||||
pushl %ecx
|
||||
call dcdchr /* decode one code symbol */
|
||||
orb %ah,%ah /* test if 8bit character */
|
||||
jnz main2
|
||||
stosb /* store verbatim */
|
||||
popl %ecx
|
||||
loop main1 /* proceed with next compressed code */
|
||||
jmp done /* until end of input is detected */
|
||||
main2:
|
||||
pushl %eax
|
||||
call dcdpos /* compute position in output buffer */
|
||||
movl %esi, %eax
|
||||
subl %edi, %ebx
|
||||
notl %ebx
|
||||
movl %ebx, %esi /* si := di - dcdpos() - 1 */
|
||||
popl %ecx
|
||||
subl $255-THRESHOLD, %ecx /* compute length of code sequence */
|
||||
movl %ecx, %edx
|
||||
rep
|
||||
movsb
|
||||
movl %eax,%esi
|
||||
popl %ecx
|
||||
subl %edx, %ecx /* check end of input condition */
|
||||
jnz main1 /* proceed with next compressed code */
|
||||
done:
|
||||
/* Start Etherboot */
|
||||
popal
|
||||
jmp uncompressed
|
||||
/*
|
||||
* GETBIT -- gets one bit pointed to by DS:ESI
|
||||
* ======
|
||||
*
|
||||
* changes: AX,CX,DL
|
||||
*/
|
||||
|
||||
getbit:
|
||||
movb $8, %cl
|
||||
movb getlen(%ebp), %dl /* compute number of bits required */
|
||||
subb %dl,%cl /* to fill read buffer */
|
||||
jae getbit1
|
||||
movw getbuf(%ebp), %ax /* there is still enough read ahead data */
|
||||
jmp getbit2
|
||||
getbit1:
|
||||
lodsb /* get next byte from input stream */
|
||||
xorb %ah,%ah
|
||||
shlw %cl,%ax /* shift, so that it will fit into */
|
||||
movw getbuf(%ebp), %cx /* read ahead buffer */
|
||||
orw %cx,%ax
|
||||
addb $8, %dl /* update number of bits in buffer */
|
||||
getbit2:
|
||||
movw %ax,%cx
|
||||
shlw %cx /* extract one bit from buffer */
|
||||
movw %cx, getbuf(%ebp)
|
||||
decb %dl
|
||||
movb %dl, getlen(%ebp) /* and update number of bits */
|
||||
shlw %ax /* return in carry flag */
|
||||
ret
|
||||
|
||||
|
||||
/*
|
||||
* DCDPOS -- decodes position in textbuffer as pointed to by DS:SI, result in BX
|
||||
* ======
|
||||
*
|
||||
* changes: AX,EBX,ECX,DX
|
||||
*/
|
||||
|
||||
dcdpos:
|
||||
movl $0x0800, %ebx
|
||||
dcdpos1:
|
||||
shlb %bl /* read one byte */
|
||||
call getbit
|
||||
jnc dcdpos2
|
||||
incb %bl
|
||||
dcdpos2:
|
||||
decb %bh
|
||||
jnz dcdpos1
|
||||
movb %bl,%dh /* read length of code from table */
|
||||
xorb %bh,%bh
|
||||
xorl %ecx, %ecx
|
||||
movb dlen(%ebx, %ebp),%cl
|
||||
movb dcode(%ebx, %ebp),%bl /* get top six bits from table */
|
||||
shll $6, %ebx
|
||||
dcdpos3:
|
||||
pushl %ecx /* read the rest from the input stream */
|
||||
shlb %dh
|
||||
call getbit
|
||||
jnc dcdpos4
|
||||
incb %dh
|
||||
dcdpos4:
|
||||
popl %ecx
|
||||
loop dcdpos3
|
||||
andb $0x3f, %dh /* combine upper and lower half of code */
|
||||
orb %dh,%bl
|
||||
ret
|
||||
|
||||
/*
|
||||
* DCDCHR -- decodes one compressed character pointed to by DS:SI
|
||||
* ======
|
||||
*
|
||||
* changes: AX,BX,CX,DX
|
||||
*/
|
||||
|
||||
dcdchr:
|
||||
movl $ROOT, %ebx /* start at root entry */
|
||||
shll %ebx
|
||||
movzwl son(%ebx, %ebp),%ebx
|
||||
dcdchr1:
|
||||
call getbit /* get a single bit */
|
||||
jnc dcdchr2
|
||||
incl %ebx /* travel left or right */
|
||||
dcdchr2:
|
||||
shll %ebx
|
||||
movzwl son(%ebx, %ebp), %ebx
|
||||
cmpl $TABLESZ, %ebx /* until we come to a leaf node */
|
||||
jb dcdchr1
|
||||
movl %ebx, %eax
|
||||
subl $TABLESZ, %eax
|
||||
/* fall thru */
|
||||
|
||||
/*
|
||||
* UPDATE -- updates huffman tree after incrementing frequency for code in BX
|
||||
* ======
|
||||
*
|
||||
* changes: BX,CX,DX
|
||||
*/
|
||||
|
||||
update:
|
||||
/* we do not check whether the frequency count has overrun.
|
||||
* this will cause problems for large files, but be should be fine
|
||||
* as long as the compressed size does not exceed 32kB and we
|
||||
* cannot do more than this anyways, because we load into the
|
||||
* upper 32kB of conventional memory
|
||||
*/
|
||||
pushl %esi
|
||||
pushl %eax
|
||||
shll %ebx
|
||||
movzwl parent(%ebx, %ebp),%ebx
|
||||
update1:
|
||||
shll %ebx
|
||||
movzwl freq(%ebx, %ebp), %edx
|
||||
incl %edx /* increment frequency count by one */
|
||||
movw %dx, freq(%ebx, %ebp)
|
||||
leal 2+freq(%ebx, %ebp), %esi
|
||||
lodsw /* check if nodes need reordering */
|
||||
cmpw %ax, %dx
|
||||
jbe update5
|
||||
update2:
|
||||
lodsw
|
||||
cmpw %dx, %ax
|
||||
jb update2
|
||||
movzwl -4(%esi), %ecx
|
||||
movw %cx, freq(%ebx, %ebp) /* swap frequency of entries */
|
||||
movw %dx, -4(%esi)
|
||||
|
||||
movl %esi, %eax /* compute index of new entry */
|
||||
subl $freq+4, %eax
|
||||
subl %ebp, %eax
|
||||
|
||||
movl %eax, %edx
|
||||
shrl %eax
|
||||
movzwl son(%ebx, %ebp), %ecx /* get son of old entry */
|
||||
movl %ecx, %esi
|
||||
addl %esi, %esi
|
||||
movw %ax, parent(%esi, %ebp) /* and update the ptr to new parent */
|
||||
cmpl $TABLESZ, %ecx
|
||||
jae update3 /* do this for both branches */
|
||||
movw %ax, parent+2(%esi, %ebp) /* if not a leaf node */
|
||||
update3:
|
||||
movl %edx, %esi
|
||||
movzwl son(%esi, %ebp), %edx /* get son of new entry */
|
||||
movw %cx, son(%esi, %ebp) /* update its contents */
|
||||
movl %edx, %esi
|
||||
addl %esi, %esi
|
||||
movl %ebx, %ecx
|
||||
shrl %ecx
|
||||
movw %cx, parent(%esi, %ebp) /* and update the ptr to new paren */
|
||||
cmpl $TABLESZ, %edx
|
||||
jae update4 /* do this for both branches */
|
||||
movw %cx, parent+2(%esi, %ebp) /* if not a leaf node */
|
||||
update4:
|
||||
movw %dx, son(%ebx, %ebp) /* update son of old entry */
|
||||
movl %eax, %ebx /* continue with new entry */
|
||||
shll %ebx
|
||||
update5:
|
||||
movzwl parent(%ebx, %ebp), %ebx /* continue with parent */
|
||||
orl %ebx, %ebx
|
||||
jnz update1 /* until we found the root entry */
|
||||
popl %eax
|
||||
popl %esi
|
||||
ret
|
||||
|
||||
/*
|
||||
* constant data. this part of the program resides in ROM and cannot be
|
||||
* changed
|
||||
*
|
||||
* run length encoded tables will be uncompressed into the bss segment
|
||||
* take care with any symbols here for .com files to add 0x100 to address
|
||||
*/
|
||||
|
||||
dcodrle: .byte 0x01,0x03,0x08,0x0C,0x18,0x10
|
||||
dlenrle: .byte 0x20,0x30,0x40,0x30,0x30,0x10
|
||||
|
||||
/*
|
||||
* variable data segment (bss)
|
||||
* this segment will always be found at 0x90000 (i.e. at RELOC - SCRATCH)
|
||||
*
|
||||
* do not change the order or the sizes of any of the following tables
|
||||
* the initialization code makes assumptions on the exact layout of the
|
||||
* data structures...
|
||||
*/
|
||||
|
||||
.bss
|
||||
/* lookup table for index into buffer of recently output characters */
|
||||
dcode: .skip 256
|
||||
|
||||
/* lookup table for length of code sequence from buffer of recent characters */
|
||||
dlen: .skip 256
|
||||
|
||||
/* table with frequency counts for all codes */
|
||||
freq: .skip 2*(TABLESZ+1)
|
||||
|
||||
/* pointer to child nodes */
|
||||
son: .skip 2*(TABLESZ)
|
||||
|
||||
/* the first part of this table contains all the codes (0..TABLESZ-1) */
|
||||
/* the second part contains all leaf nodes (TABLESZ..) */
|
||||
parent: .skip 2*(TABLESZ+NCHAR)
|
||||
|
||||
/* temporary storage for extracting bits from compressed data stream */
|
||||
getlen: .skip 1
|
||||
getbuf: .skip 1
|
||||
|
||||
/* the initial buffer has to be filled with spaces */
|
||||
.balign 4
|
||||
spaces:
|
||||
.skip BUFSZ - LOOKAHEAD
|
||||
/* uncompressed data will be written here */
|
||||
uncompressed:
|
||||
|
||||
33
src/arch/i386/prefix/unhuf.lds
Normal file
33
src/arch/i386/prefix/unhuf.lds
Normal file
@@ -0,0 +1,33 @@
|
||||
OUTPUT_FORMAT("elf32-i386", "elf32-i386", "elf32-i386")
|
||||
OUTPUT_ARCH(i386)
|
||||
|
||||
SECTIONS
|
||||
{
|
||||
. = 0;
|
||||
.text : {
|
||||
_text = .;
|
||||
*(.head)
|
||||
*(.text)
|
||||
} = 0x9090
|
||||
.rodata : {
|
||||
*(.rodata)
|
||||
}
|
||||
_etext = . ;
|
||||
.data : {
|
||||
*(.data)
|
||||
/* Force 4 byte alignment */
|
||||
. = ALIGN(4);
|
||||
_payload = . ;
|
||||
*(.huf)
|
||||
_epayload = . ;
|
||||
}
|
||||
_edata = . ;
|
||||
_data_size = _edata - _start;
|
||||
/* Etherboot needs to be 16 byte aligned */
|
||||
. = ALIGN(16);
|
||||
.bss : {
|
||||
*(.bss)
|
||||
}
|
||||
_end = . ;
|
||||
_image_size = _end - _start;
|
||||
}
|
||||
129
src/arch/i386/prefix/unnrv2b.S
Normal file
129
src/arch/i386/prefix/unnrv2b.S
Normal file
@@ -0,0 +1,129 @@
|
||||
/*
|
||||
* Copyright (C) 1996-2002 Markus Franz Xaver Johannes Oberhumer
|
||||
*
|
||||
* This file 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; either version 2 of
|
||||
* the License, or (at your option) any later version.
|
||||
*
|
||||
* Originally this code was part of ucl the data compression library
|
||||
* for upx the ``Ultimate Packer of eXecutables''.
|
||||
*
|
||||
* - Converted to gas assembly, and refitted to work with etherboot.
|
||||
* Eric Biederman 20 Aug 2002
|
||||
*
|
||||
* - Structure modified to be a subroutine call rather than an
|
||||
* executable prefix.
|
||||
* Michael Brown 30 Mar 2004
|
||||
*/
|
||||
|
||||
|
||||
.text
|
||||
.arch i386
|
||||
.section ".prefix", "ax", @progbits
|
||||
.code32
|
||||
|
||||
.globl decompress
|
||||
decompress:
|
||||
/* Save the initial register values */
|
||||
pushal
|
||||
|
||||
/*
|
||||
* See where I am running, and compute %ebp
|
||||
* %ebp holds delta between physical and virtual addresses.
|
||||
*/
|
||||
call 1f
|
||||
1: popl %ebp
|
||||
subl $1b, %ebp
|
||||
|
||||
/* "compressed" and "decompress_to" defined by linker script */
|
||||
/* move compressed image up to temporary area before decompressing */
|
||||
std
|
||||
movl $_compressed_size, %ecx
|
||||
leal _compressed+4-1(%ebp, %ecx), %esi
|
||||
leal _compressed_copy-1(%ebp, %ecx), %edi
|
||||
rep movsb
|
||||
/* Setup to run the decompressor */
|
||||
cld
|
||||
leal _compressed_copy(%ebp), %esi
|
||||
leal decompress_to(%ebp), %edi
|
||||
movl $-1, %ebp /* last_m_off = -1 */
|
||||
jmp dcl1_n2b
|
||||
|
||||
/* ------------- DECOMPRESSION -------------
|
||||
|
||||
Input:
|
||||
%esi - source
|
||||
%edi - dest
|
||||
%ebp - -1
|
||||
cld
|
||||
|
||||
Output:
|
||||
%eax - 0
|
||||
%ecx - 0
|
||||
*/
|
||||
|
||||
.macro getbit bits
|
||||
.if \bits == 1
|
||||
addl %ebx, %ebx
|
||||
jnz 1f
|
||||
.endif
|
||||
movl (%esi), %ebx
|
||||
subl $-4, %esi /* sets carry flag */
|
||||
adcl %ebx, %ebx
|
||||
1:
|
||||
.endm
|
||||
|
||||
decompr_literals_n2b:
|
||||
movsb
|
||||
|
||||
decompr_loop_n2b:
|
||||
addl %ebx, %ebx
|
||||
jnz dcl2_n2b
|
||||
dcl1_n2b:
|
||||
getbit 32
|
||||
dcl2_n2b:
|
||||
jc decompr_literals_n2b
|
||||
xorl %eax, %eax
|
||||
incl %eax /* m_off = 1 */
|
||||
loop1_n2b:
|
||||
getbit 1
|
||||
adcl %eax, %eax /* m_off = m_off*2 + getbit() */
|
||||
getbit 1
|
||||
jnc loop1_n2b /* while(!getbit()) */
|
||||
xorl %ecx, %ecx
|
||||
subl $3, %eax
|
||||
jb decompr_ebpeax_n2b /* if (m_off == 2) goto decompr_ebpeax_n2b ? */
|
||||
shll $8, %eax
|
||||
movb (%esi), %al /* m_off = (m_off - 3)*256 + src[ilen++] */
|
||||
incl %esi
|
||||
xorl $-1, %eax
|
||||
jz decompr_end_n2b /* if (m_off == 0xffffffff) goto decomp_end_n2b */
|
||||
movl %eax, %ebp /* last_m_off = m_off ?*/
|
||||
decompr_ebpeax_n2b:
|
||||
getbit 1
|
||||
adcl %ecx, %ecx /* m_len = getbit() */
|
||||
getbit 1
|
||||
adcl %ecx, %ecx /* m_len = m_len*2 + getbit()) */
|
||||
jnz decompr_got_mlen_n2b /* if (m_len == 0) goto decompr_got_mlen_n2b */
|
||||
incl %ecx /* m_len++ */
|
||||
loop2_n2b:
|
||||
getbit 1
|
||||
adcl %ecx, %ecx /* m_len = m_len*2 + getbit() */
|
||||
getbit 1
|
||||
jnc loop2_n2b /* while(!getbit()) */
|
||||
incl %ecx
|
||||
incl %ecx /* m_len += 2 */
|
||||
decompr_got_mlen_n2b:
|
||||
cmpl $-0xd00, %ebp
|
||||
adcl $1, %ecx /* m_len = m_len + 1 + (last_m_off > 0xd00) */
|
||||
pushl %esi
|
||||
leal (%edi,%ebp), %esi /* m_pos = dst + olen + -m_off */
|
||||
rep
|
||||
movsb /* dst[olen++] = *m_pos++ while(m_len > 0) */
|
||||
popl %esi
|
||||
jmp decompr_loop_n2b
|
||||
decompr_end_n2b:
|
||||
/* Restore the initial register values */
|
||||
popal
|
||||
ret
|
||||
Reference in New Issue
Block a user