VirtualBox

source: vbox/trunk/src/VBox/Devices/PC/Etherboot-src/arch/i386/prefix/bImageprefix.S@ 16444

Last change on this file since 16444 was 1, checked in by vboxsync, 55 years ago

import

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 15.2 KB
Line 
1/*
2 Copyright (C) 2000, Entity Cyber, Inc.
3
4 Authors: Gary Byers ([email protected])
5 Marty Connor ([email protected])
6 Eric Biederman ([email protected])
7
8 This code also derives a lot from arch/i386/boot/setup.S in
9 the linux kernel.
10
11 This software may be used and distributed according to the terms
12 of the GNU Public License (GPL), incorporated herein by reference.
13
14 Description:
15
16 This is just a little bit of code and data that can get prepended
17 to an Etherboot ROM image in order to allow LILO to load the
18 result as if it were a Linux kernel image.
19
20 A real Linux kernel image consists of a one-sector boot loader
21 (to load the image from a floppy disk), followed a few sectors
22 of setup code, followed by the kernel code itself. There's
23 a table in the first sector (starting at offset 497) that indicates
24 how many sectors of setup code follow the first sector and which
25 contains some other parameters that aren't interesting in this
26 case.
27
28 When LILO loads the sectors that comprise a kernel image, it doesn't
29 execute the code in the first sector (since that code would try to
30 load the image from a floppy disk.) The code in the first sector
31 below doesn't expect to get executed (and prints an error message
32 if it ever -is- executed.) LILO's only interested in knowing the
33 number of setup sectors advertised in the table (at offset 497 in
34 the first sector.)
35
36 Etherboot doesn't require much in the way of setup code.
37 Historically, the Linux kernel required at least 4 sectors of
38 setup code. Current versions of LILO look at the byte at
39 offset 497 in the first sector to indicate how many sectors
40 of setup code are contained in the image.
41
42 The setup code that is present here does a lot of things
43 exactly the way the linux kernel does them instead of in
44 ways more typical of etherboot. Generally this is so
45 the code can be strongly compatible with the linux kernel.
46 In addition the general etherboot technique of enabling the a20
47 after we switch into protected mode does not work if etherboot
48 is being loaded at 1MB.
49*/
50
51 .equ CR0_PE,1
52
53#ifdef GAS291
54#define DATA32 data32;
55#define ADDR32 addr32;
56#define LJMPI(x) ljmp x
57#else
58#define DATA32 data32
59#define ADDR32 addr32
60/* newer GAS295 require #define LJMPI(x) ljmp *x */
61#define LJMPI(x) ljmp x
62#endif
63
64/* Simple and small GDT entries for booting only */
65#define GDT_ENTRY_BOOT_CS 2
66#define GDT_ENTRY_BOOT_DS (GDT_ENTRY_BOOT_CS + 1)
67#define __BOOT_CS (GDT_ENTRY_BOOT_CS * 8)
68#define __BOOT_DS (GDT_ENTRY_BOOT_DS * 8)
69
70
71#define SETUPSECS 4 /* Minimal nr of setup-sectors */
72#define PREFIXSIZE ((SETUPSECS+1)*512)
73#define PREFIXPGH (PREFIXSIZE / 16 )
74#define BOOTSEG 0x07C0 /* original address of boot-sector */
75#define INITSEG 0x9000 /* we move boot here - out of the way */
76#define SETUPSEG 0x9020 /* setup starts here */
77#define SYSSEG 0x1000 /* system loaded at 0x10000 (65536). */
78
79#define DELTA_INITSEG (SETUPSEG - INITSEG) /* 0x0020 */
80
81/* Signature words to ensure LILO loaded us right */
82#define SIG1 0xAA55
83#define SIG2 0x5A5A
84
85 .text
86 .code16
87 .arch i386
88 .org 0
89 .section ".prefix", "ax", @progbits
90 .globl _prefix
91_prefix:
92
93/*
94 This is a minimal boot sector. If anyone tries to execute it (e.g., if
95 a .lilo file is dd'ed to a floppy), print an error message.
96*/
97
98bootsector:
99 jmp $BOOTSEG, $go - _prefix /* reload cs:ip to match relocation addr */
100go:
101 movw $0x2000, %di /* 0x2000 is arbitrary value >= length
102 of bootsect + room for stack */
103
104 movw $BOOTSEG, %ax
105 movw %ax,%ds
106 movw %ax,%es
107
108 cli
109 movw %ax, %ss /* put stack at BOOTSEG:0x2000. */
110 movw %di,%sp
111 sti
112
113 movw $why_end-why, %cx
114 movw $why - _prefix, %si
115
116 movw $0x0007, %bx /* page 0, attribute 7 (normal) */
117 movb $0x0e, %ah /* write char, tty mode */
118prloop:
119 lodsb
120 int $0x10
121 loop prloop
122freeze: jmp freeze
123
124why: .ascii "This image cannot be loaded from a floppy disk.\r\n"
125why_end:
126
127
128 .org 497
129setup_sects:
130 .byte SETUPSECS
131root_flags:
132 .word 0
133syssize:
134 .word _verbatim_size_pgh - PREFIXPGH
135swap_dev:
136 .word 0
137ram_size:
138 .word 0
139vid_mode:
140 .word 0
141root_dev:
142 .word 0
143boot_flag:
144 .word 0xAA55
145
146/*
147 We're now at the beginning of the second sector of the image -
148 where the setup code goes.
149
150 We don't need to do too much setup for Etherboot.
151
152 This code gets loaded at SETUPSEG:0. It wants to start
153 executing the Etherboot image that's loaded at SYSSEG:0 and
154 whose entry point is SYSSEG:0.
155*/
156setup_code:
157 jmp trampoline
158# This is the setup header, and it must start at %cs:2 (old 0x9020:2)
159
160 .ascii "HdrS" # header signature
161 .word 0x0203 # header version number (>= 0x0105)
162 # or else old loadlin-1.5 will fail)
163realmode_swtch: .word 0, 0 # default_switch, SETUPSEG
164start_sys_seg: .word SYSSEG # low load segment (obsolete)
165 .word kernel_version - setup_code
166 # pointing to kernel version string
167 # above section of header is compatible
168 # with loadlin-1.5 (header v1.5). Don't
169 # change it.
170
171type_of_loader: .byte 0 # = 0, old one (LILO, Loadlin,
172 # Bootlin, SYSLX, bootsect...)
173 # See Documentation/i386/boot.txt for
174 # assigned ids
175
176# flags, unused bits must be zero (RFU) bit within loadflags
177loadflags:
178LOADED_HIGH = 1 # If set, the kernel is loaded high
179CAN_USE_HEAP = 0x80 # If set, the loader also has set
180 # heap_end_ptr to tell how much
181 # space behind setup.S can be used for
182 # heap purposes.
183 # Only the loader knows what is free
184 .byte LOADED_HIGH
185
186setup_move_size: .word 0x8000 # size to move, when setup is not
187 # loaded at 0x90000. We will move setup
188 # to 0x90000 then just before jumping
189 # into the kernel. However, only the
190 # loader knows how much data behind
191 # us also needs to be loaded.
192
193code32_start: # here loaders can put a different
194 # start address for 32-bit code.
195 .long 0x100000 # 0x100000 = default for big kernel
196
197ramdisk_image: .long 0 # address of loaded ramdisk image
198 # Here the loader puts the 32-bit
199 # address where it loaded the image.
200 # This only will be read by the kernel.
201
202ramdisk_size: .long 0 # its size in bytes
203
204bootsect_kludge:
205 .long 0 # obsolete
206
207heap_end_ptr: .word 0 # (Header version 0x0201 or later)
208 # space from here (exclusive) down to
209 # end of setup code can be used by setup
210 # for local heap purposes.
211
212pad1: .word 0
213cmd_line_ptr: .long 0 # (Header version 0x0202 or later)
214 # If nonzero, a 32-bit pointer
215 # to the kernel command line.
216 # The command line should be
217 # located between the start of
218 # setup and the end of low
219 # memory (0xa0000), or it may
220 # get overwritten before it
221 # gets read. If this field is
222 # used, there is no longer
223 # anything magical about the
224 # 0x90000 segment; the setup
225 # can be located anywhere in
226 # low memory 0x10000 or higher.
227
228ramdisk_max: .long 0 # (Header version 0x0203 or later)
229 # The highest safe address for
230 # the contents of an initrd
231
232trampoline: call start_of_setup
233trampoline_end:
234 .space 1024
235# End of setup header #####################################################
236
237start_of_setup:
238# Set %ds = %cs, we know that SETUPSEG = %cs at this point
239 movw %cs, %ax # aka SETUPSEG
240 movw %ax, %ds
241# Check signature at end of setup
242 cmpw $SIG1, (setup_sig1 - setup_code)
243 jne bad_sig
244
245 cmpw $SIG2, (setup_sig2 - setup_code)
246 jne bad_sig
247
248 jmp good_sig1
249
250# Routine to print asciiz string at ds:si
251prtstr:
252 lodsb
253 andb %al, %al
254 jz fin
255
256 call prtchr
257 jmp prtstr
258
259fin: ret
260
261# Part of above routine, this one just prints ascii al
262prtchr: pushw %ax
263 pushw %cx
264 movw $7,%bx
265 movw $0x01, %cx
266 movb $0x0e, %ah
267 int $0x10
268 popw %cx
269 popw %ax
270 ret
271
272no_sig_mess: .string "No setup signature found ..."
273
274good_sig1:
275 jmp good_sig
276
277# We now have to find the rest of the setup code/data
278bad_sig:
279 movw %cs, %ax # SETUPSEG
280 subw $DELTA_INITSEG, %ax # INITSEG
281 movw %ax, %ds
282 xorb %bh, %bh
283 movb (497), %bl # get setup sect from bootsect
284 subw $4, %bx # LILO loads 4 sectors of setup
285 shlw $8, %bx # convert to words (1sect=2^8 words)
286 movw %bx, %cx
287 shrw $3, %bx # convert to segment
288 addw $SYSSEG, %bx
289 movw %bx, %cs:(start_sys_seg - setup_code)
290# Move rest of setup code/data to here
291 movw $2048, %di # four sectors loaded by LILO
292 subw %si, %si
293 pushw %cs
294 popw %es
295 movw $SYSSEG, %ax
296 movw %ax, %ds
297 rep
298 movsw
299 movw %cs, %ax # aka SETUPSEG
300 movw %ax, %ds
301 cmpw $SIG1, (setup_sig1 - setup_code)
302 jne no_sig
303
304 cmpw $SIG2, (setup_sig2 - setup_code)
305 jne no_sig
306
307 jmp good_sig
308
309no_sig:
310 lea (no_sig_mess - setup_code), %si
311 call prtstr
312
313no_sig_loop:
314 hlt
315 jmp no_sig_loop
316
317good_sig:
318 cmpw $0, %cs:(realmode_swtch - setup_code)
319 jz rmodeswtch_normal
320
321 lcall *%cs:(realmode_swtch - setup_code)
322 jmp rmodeswtch_end
323
324rmodeswtch_normal:
325 pushw %cs
326 call default_switch
327
328rmodeswtch_end:
329# we get the code32 start address and modify the below 'jmpi'
330# (loader may have changed it)
331 movl %cs:(code32_start - setup_code), %eax
332 movl %eax, %cs:(code32 - setup_code)
333
334# then we load the segment descriptors
335 movw %cs, %ax # aka SETUPSEG
336 movw %ax, %ds
337
338#
339# Enable A20. This is at the very best an annoying procedure.
340# A20 code ported from SYSLINUX 1.52-1.63 by H. Peter Anvin.
341#
342
343A20_TEST_LOOPS = 32 # Iterations per wait
344A20_ENABLE_LOOPS = 255 # Total loops to try
345
346a20_try_loop:
347
348 # First, see if we are on a system with no A20 gate.
349a20_none:
350 call a20_test
351 jnz a20_done
352
353 # Next, try the BIOS (INT 0x15, AX=0x2401)
354a20_bios:
355 movw $0x2401, %ax
356 pushfl # Be paranoid about flags
357 int $0x15
358 popfl
359
360 call a20_test
361 jnz a20_done
362
363 # Try enabling A20 through the keyboard controller
364a20_kbc:
365 call empty_8042
366
367 call a20_test # Just in case the BIOS worked
368 jnz a20_done # but had a delayed reaction.
369
370 movb $0xD1, %al # command write
371 outb %al, $0x64
372 call empty_8042
373
374 movb $0xDF, %al # A20 on
375 outb %al, $0x60
376 call empty_8042
377
378 # Wait until a20 really *is* enabled; it can take a fair amount of
379 # time on certain systems; Toshiba Tecras are known to have this
380 # problem.
381a20_kbc_wait:
382 xorw %cx, %cx
383a20_kbc_wait_loop:
384 call a20_test
385 jnz a20_done
386 loop a20_kbc_wait_loop
387
388 # Final attempt: use "configuration port A"
389a20_fast:
390 inb $0x92, %al # Configuration Port A
391 orb $0x02, %al # "fast A20" version
392 andb $0xFE, %al # don't accidentally reset
393 outb %al, $0x92
394
395 # Wait for configuration port A to take effect
396a20_fast_wait:
397 xorw %cx, %cx
398a20_fast_wait_loop:
399 call a20_test
400 jnz a20_done
401 loop a20_fast_wait_loop
402
403 # A20 is still not responding. Try frobbing it again.
404 #
405 decb (a20_tries - setup_code)
406 jnz a20_try_loop
407
408 movw $(a20_err_msg - setup_code), %si
409 call prtstr
410
411a20_die:
412 hlt
413 jmp a20_die
414
415a20_tries:
416 .byte A20_ENABLE_LOOPS
417
418a20_err_msg:
419 .ascii "linux: fatal error: A20 gate not responding!"
420 .byte 13, 10, 0
421
422 # If we get here, all is good
423a20_done:
424 # Leave the idt alone
425
426 # set up gdt
427 xorl %eax, %eax # Compute gdt_base
428 movw %ds, %ax # (Convert %ds:gdt to a linear ptr)
429 shll $4, %eax
430 addl $(bImage_gdt - setup_code), %eax
431 movl %eax, (bImage_gdt_48+2 - setup_code)
432 DATA32 lgdt %ds:(bImage_gdt_48 - setup_code) # load gdt with whatever is
433 # appropriate
434
435 # Switch to protected mode
436 movl %cr0, %eax
437 orb $CR0_PE, %al
438 movl %eax, %cr0
439
440 DATA32 ljmp %ds:(code32 - setup_code)
441code32:
442 .long 0x100000
443 .word __BOOT_CS, 0
444
445# Here's a bunch of information about your current kernel..
446kernel_version: .ascii "Etherboot "
447 .ascii VERSION
448 .byte 0
449
450# This is the default real mode switch routine.
451# to be called just before protected mode transition
452default_switch:
453 cli # no interrupts allowed !
454 movb $0x80, %al # disable NMI for bootup
455 # sequence
456 outb %al, $0x70
457 lret
458
459# This routine tests whether or not A20 is enabled. If so, it
460# exits with zf = 0.
461#
462# The memory address used, 0x200, is the int $0x80 vector, which
463# should be safe.
464
465A20_TEST_ADDR = 4*0x80
466
467a20_test:
468 pushw %cx
469 pushw %ax
470 xorw %cx, %cx
471 movw %cx, %fs # Low memory
472 decw %cx
473 movw %cx, %gs # High memory area
474 movw $A20_TEST_LOOPS, %cx
475 movw %fs:(A20_TEST_ADDR), %ax
476 pushw %ax
477a20_test_wait:
478 incw %ax
479 movw %ax, %fs:(A20_TEST_ADDR)
480 call delay # Serialize and make delay constant
481 cmpw %gs:(A20_TEST_ADDR+0x10), %ax
482 loope a20_test_wait
483
484 popw %fs:(A20_TEST_ADDR)
485 popw %ax
486 popw %cx
487 ret
488
489
490# This routine checks that the keyboard command queue is empty
491# (after emptying the output buffers)
492#
493# Some machines have delusions that the keyboard buffer is always full
494# with no keyboard attached...
495#
496# If there is no keyboard controller, we will usually get 0xff
497# to all the reads. With each IO taking a microsecond and
498# a timeout of 100,000 iterations, this can take about half a
499# second ("delay" == outb to port 0x80). That should be ok,
500# and should also be plenty of time for a real keyboard controller
501# to empty.
502#
503
504empty_8042:
505 pushl %ecx
506 movl $100000, %ecx
507
508empty_8042_loop:
509 decl %ecx
510 jz empty_8042_end_loop
511
512 call delay
513
514 inb $0x64, %al # 8042 status port
515 testb $1, %al # output buffer?
516 jz no_output
517
518 call delay
519 inb $0x60, %al # read it
520 jmp empty_8042_loop
521
522no_output:
523 testb $2, %al # is input buffer full?
524 jnz empty_8042_loop # yes - loop
525empty_8042_end_loop:
526 popl %ecx
527
528
529# Delay is needed after doing I/O
530delay:
531 outb %al,$0x80
532 ret
533
534# Descriptor tables
535#
536# NOTE: The intel manual says gdt should be sixteen bytes aligned for
537# efficiency reasons. However, there are machines which are known not
538# to boot with misaligned GDTs, so alter this at your peril! If you alter
539# GDT_ENTRY_BOOT_CS (in asm/segment.h) remember to leave at least two
540# empty GDT entries (one for NULL and one reserved).
541#
542# NOTE: On some CPUs, the GDT must be 8 byte aligned. This is
543# true for the Voyager Quad CPU card which will not boot without
544# This directive. 16 byte aligment is recommended by intel.
545#
546 .balign 16
547bImage_gdt:
548 .fill GDT_ENTRY_BOOT_CS,8,0
549
550 .word 0xFFFF # 4Gb - (0x100000*0x1000 = 4Gb)
551 .word 0 # base address = 0
552 .word 0x9A00 # code read/exec
553 .word 0x00CF # granularity = 4096, 386
554 # (+5th nibble of limit)
555
556 .word 0xFFFF # 4Gb - (0x100000*0x1000 = 4Gb)
557 .word 0 # base address = 0
558 .word 0x9200 # data read/write
559 .word 0x00CF # granularity = 4096, 386
560 # (+5th nibble of limit)
561bImage_gdt_end:
562 .balign 4
563
564 .word 0 # alignment byte
565bImage_idt_48:
566 .word 0 # idt limit = 0
567 .long 0 # idt base = 0L
568
569 .word 0 # alignment byte
570bImage_gdt_48:
571 .word bImage_gdt_end - bImage_gdt - 1 # gdt limit
572 .long bImage_gdt_48 - setup_code # gdt base (filled in later)
573
574 .section ".text16", "ax", @progbits
575 .globl prefix_exit
576prefix_exit:
577 int $0x19 /* should try to boot machine */
578 .globl prefix_exit_end
579prefix_exit_end:
580 .previous
581
582
583 .org (PREFIXSIZE - 4)
584# Setup signature -- must be last
585setup_sig1: .word SIG1
586setup_sig2: .word SIG2
587 /* Etherboot expects to be contiguous in memory once loaded.
588 * The linux bImage protocol does not do this, but since we
589 * don't need any information that's left in the prefix, it
590 * doesn't matter: we just have to ensure that we make it to _start
591 *
592 * protected_start will live at 0x100000 and it will be the
593 * the first code called as we enter protected mode.
594 */
595 .code32
596protected_start:
597 /* Load segment registers */
598 movw $__BOOT_DS, %ax
599 movw %ax, %ss
600 movw %ax, %ds
601 movw %ax, %es
602 movw %ax, %fs
603 movw %ax, %gs
604
605 /* Use the internal etherboot stack */
606 movl $(_prefix_stack_end - protected_start + 0x100000), %esp
607
608 pushl $0 /* No parameters to preserve for exit path */
609 pushl $0 /* Use prefix exit path mechanism */
610
611 jmp _start
612/*
613 That's about it.
614*/
Note: See TracBrowser for help on using the repository browser.

© 2024 Oracle Support Privacy / Do Not Sell My Info Terms of Use Trademark Policy Automated Access Etiquette