Adding debian version 3.70~pre8+dfsg-1.
[syslinux-debian/hramrach.git] / gpxe / src / arch / i386 / prefix / bImageprefix.S
blob30020f73118846bd19a92ed5ab202c70881f927d
1 /*
2         Copyright (C) 2000, Entity Cyber, Inc.
4         Authors: Gary Byers (gb@thinguin.org)
5                  Marty Connor (mdc@thinguin.org)
6                  Eric Biederman (ebiederman@lnxi.com)
8         This code also derives a lot from arch/i386/boot/setup.S in
9         the linux kernel.
11         This software may be used and distributed according to the terms
12         of the GNU Public License (GPL), incorporated herein by reference.
14         Description:    
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.
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.
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.)
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.
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.
51         .equ    CR0_PE,1
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
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)
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). */
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
85         .text
86         .code16
87         .arch i386
88         .org    0
89         .section ".prefix", "ax", @progbits
90 _prefix:
92 /* 
93         This is a minimal boot sector.  If anyone tries to execute it (e.g., if
94         a .lkrn file is dd'ed to a floppy), print an error message. 
97 bootsector: 
98         jmp     $BOOTSEG, $go - _prefix /* reload cs:ip to match relocation addr */
99 go: 
100         movw    $0x2000, %di            /*  0x2000 is arbitrary value >= length
101                                             of bootsect + room for stack */
103         movw    $BOOTSEG, %ax
104         movw    %ax,%ds
105         movw    %ax,%es
107         cli
108         movw    %ax, %ss                /* put stack at BOOTSEG:0x2000. */
109         movw    %di,%sp
110         sti
112         movw    $why_end-why, %cx
113         movw    $why - _prefix, %si
115         movw    $0x0007, %bx            /* page 0, attribute 7 (normal) */
116         movb    $0x0e, %ah              /* write char, tty mode */
117 prloop: 
118         lodsb
119         int     $0x10
120         loop    prloop
121 freeze: jmp     freeze
123 why:    .ascii  "This image cannot be loaded from a floppy disk.\r\n"
124 why_end: 
127         .org    497
128 setup_sects: 
129         .byte   SETUPSECS
130 root_flags: 
131         .word   0
132 syssize: 
133         .word   _verbatim_size_pgh - PREFIXPGH
134 swap_dev: 
135         .word   0
136 ram_size: 
137         .word   0
138 vid_mode: 
139         .word   0
140 root_dev: 
141         .word   0
142 boot_flag: 
143         .word   0xAA55
146         We're now at the beginning of the second sector of the image -
147         where the setup code goes.
149         We don't need to do too much setup for Etherboot.
151         This code gets loaded at SETUPSEG:0.  It wants to start
152         executing the Etherboot image that's loaded at SYSSEG:0 and
153         whose entry point is SYSSEG:0.
155 setup_code:
156         jmp     trampoline
157 # This is the setup header, and it must start at %cs:2 (old 0x9020:2)
159                 .ascii  "HdrS"          # header signature
160                 .word   0x0203          # header version number (>= 0x0105)
161                                         # or else old loadlin-1.5 will fail)
162 realmode_swtch: .word   0, 0            # default_switch, SETUPSEG
163 start_sys_seg:  .word   SYSSEG          # low load segment (obsolete)
164                 .word   kernel_version - setup_code
165                                         # pointing to kernel version string
166                                         # above section of header is compatible
167                                         # with loadlin-1.5 (header v1.5). Don't
168                                         # change it.
170 type_of_loader: .byte   0               # = 0, old one (LILO, Loadlin,
171                                         #      Bootlin, SYSLX, bootsect...)
172                                         # See Documentation/i386/boot.txt for
173                                         # assigned ids
174         
175 # flags, unused bits must be zero (RFU) bit within loadflags
176 loadflags:
177 LOADED_HIGH     = 1                     # If set, the kernel is loaded high
178 CAN_USE_HEAP    = 0x80                  # If set, the loader also has set
179                                         # heap_end_ptr to tell how much
180                                         # space behind setup.S can be used for
181                                         # heap purposes.
182                                         # Only the loader knows what is free
183                 .byte   LOADED_HIGH
185 setup_move_size: .word  0x8000          # size to move, when setup is not
186                                         # loaded at 0x90000. We will move setup 
187                                         # to 0x90000 then just before jumping
188                                         # into the kernel. However, only the
189                                         # loader knows how much data behind
190                                         # us also needs to be loaded.
192 code32_start:                           # here loaders can put a different
193                                         # start address for 32-bit code.
194                 .long   0x100000        # 0x100000 = default for big kernel
196 ramdisk_image:  .long   0               # address of loaded ramdisk image
197                                         # Here the loader puts the 32-bit
198                                         # address where it loaded the image.
199                                         # This only will be read by the kernel.
201 ramdisk_size:   .long   0               # its size in bytes
203 bootsect_kludge:
204                 .long   0               # obsolete
206 heap_end_ptr:   .word   0               # (Header version 0x0201 or later)
207                                         # space from here (exclusive) down to
208                                         # end of setup code can be used by setup
209                                         # for local heap purposes.
211 pad1:           .word   0
212 cmd_line_ptr:   .long 0                 # (Header version 0x0202 or later)
213                                         # If nonzero, a 32-bit pointer
214                                         # to the kernel command line.
215                                         # The command line should be
216                                         # located between the start of
217                                         # setup and the end of low
218                                         # memory (0xa0000), or it may
219                                         # get overwritten before it
220                                         # gets read.  If this field is
221                                         # used, there is no longer
222                                         # anything magical about the
223                                         # 0x90000 segment; the setup
224                                         # can be located anywhere in
225                                         # low memory 0x10000 or higher.
227 ramdisk_max:    .long 0                 # (Header version 0x0203 or later)
228                                         # The highest safe address for
229                                         # the contents of an initrd
231 trampoline:     call    start_of_setup
232 trampoline_end:
233                 .space  1024
234 # End of setup header #####################################################
236 start_of_setup:
237 # Set %ds = %cs, we know that SETUPSEG = %cs at this point
238         movw    %cs, %ax                # aka SETUPSEG
239         movw    %ax, %ds
240 # Check signature at end of setup
241         cmpw    $SIG1, (setup_sig1 - setup_code)
242         jne     bad_sig
244         cmpw    $SIG2, (setup_sig2 - setup_code)
245         jne     bad_sig
247         jmp     good_sig1
249 # Routine to print asciiz string at ds:si
250 prtstr:
251         lodsb
252         andb    %al, %al
253         jz      fin
255         call    prtchr
256         jmp     prtstr
258 fin:    ret
260 # Part of above routine, this one just prints ascii al
261 prtchr: pushw   %ax
262         pushw   %cx
263         movw    $7,%bx
264         movw    $0x01, %cx
265         movb    $0x0e, %ah
266         int     $0x10
267         popw    %cx
268         popw    %ax
269         ret
271 no_sig_mess: .string    "No setup signature found ..."
273 good_sig1:
274         jmp     good_sig
276 # We now have to find the rest of the setup code/data
277 bad_sig:
278         movw    %cs, %ax                        # SETUPSEG
279         subw    $DELTA_INITSEG, %ax             # INITSEG
280         movw    %ax, %ds
281         xorb    %bh, %bh
282         movb    (497), %bl                      # get setup sect from bootsect
283         subw    $4, %bx                         # LILO loads 4 sectors of setup
284         shlw    $8, %bx                         # convert to words (1sect=2^8 words)
285         movw    %bx, %cx
286         shrw    $3, %bx                         # convert to segment
287         addw    $SYSSEG, %bx
288         movw    %bx, %cs:(start_sys_seg - setup_code)
289 # Move rest of setup code/data to here
290         movw    $2048, %di                      # four sectors loaded by LILO
291         subw    %si, %si
292         pushw   %cs
293         popw    %es
294         movw    $SYSSEG, %ax
295         movw    %ax, %ds
296         rep
297         movsw
298         movw    %cs, %ax                        # aka SETUPSEG
299         movw    %ax, %ds
300         cmpw    $SIG1, (setup_sig1 - setup_code)
301         jne     no_sig
303         cmpw    $SIG2, (setup_sig2 - setup_code)
304         jne     no_sig
306         jmp     good_sig
308 no_sig:
309         lea     (no_sig_mess - setup_code), %si
310         call    prtstr
312 no_sig_loop:
313         hlt
314         jmp     no_sig_loop
316 good_sig:
317         cmpw    $0, %cs:(realmode_swtch - setup_code)
318         jz      rmodeswtch_normal
320         lcall   *%cs:(realmode_swtch - setup_code)
321         jmp     rmodeswtch_end
323 rmodeswtch_normal:
324         pushw   %cs
325         call    default_switch
327 rmodeswtch_end:
328 # we get the code32 start address and modify the below 'jmpi'
329 # (loader may have changed it)
330         movl    %cs:(code32_start - setup_code), %eax
331         movl    %eax, %cs:(code32 - setup_code)
333 # then we load the segment descriptors
334         movw    %cs, %ax                        # aka SETUPSEG
335         movw    %ax, %ds
338 # Enable A20.  This is at the very best an annoying procedure.
339 # A20 code ported from SYSLINUX 1.52-1.63 by H. Peter Anvin.
342 A20_TEST_LOOPS          =  32           # Iterations per wait
343 A20_ENABLE_LOOPS        = 255           # Total loops to try            
345 a20_try_loop:
347         # First, see if we are on a system with no A20 gate.
348 a20_none:
349         call    a20_test
350         jnz     a20_done
352         # Next, try the BIOS (INT 0x15, AX=0x2401)
353 a20_bios:
354         movw    $0x2401, %ax
355         pushfl                                  # Be paranoid about flags
356         int     $0x15
357         popfl
359         call    a20_test
360         jnz     a20_done
362         # Try enabling A20 through the keyboard controller
363 a20_kbc:
364         call    empty_8042
366         call    a20_test                        # Just in case the BIOS worked
367         jnz     a20_done                        # but had a delayed reaction.
369         movb    $0xD1, %al                      # command write
370         outb    %al, $0x64
371         call    empty_8042
373         movb    $0xDF, %al                      # A20 on
374         outb    %al, $0x60
375         call    empty_8042
377         # Wait until a20 really *is* enabled; it can take a fair amount of
378         # time on certain systems; Toshiba Tecras are known to have this
379         # problem.
380 a20_kbc_wait:
381         xorw    %cx, %cx
382 a20_kbc_wait_loop:
383         call    a20_test
384         jnz     a20_done
385         loop    a20_kbc_wait_loop
387         # Final attempt: use "configuration port A"
388 a20_fast:
389         inb     $0x92, %al                      # Configuration Port A
390         orb     $0x02, %al                      # "fast A20" version
391         andb    $0xFE, %al                      # don't accidentally reset
392         outb    %al, $0x92
394         # Wait for configuration port A to take effect
395 a20_fast_wait:
396         xorw    %cx, %cx
397 a20_fast_wait_loop:
398         call    a20_test
399         jnz     a20_done
400         loop    a20_fast_wait_loop
402         # A20 is still not responding.  Try frobbing it again.
403         # 
404         decb    (a20_tries - setup_code)
405         jnz     a20_try_loop
406         
407         movw    $(a20_err_msg - setup_code), %si
408         call    prtstr
410 a20_die:
411         hlt
412         jmp     a20_die
414 a20_tries:
415         .byte   A20_ENABLE_LOOPS
417 a20_err_msg:
418         .ascii  "linux: fatal error: A20 gate not responding!"
419         .byte   13, 10, 0
421         # If we get here, all is good
422 a20_done:
423         # Leave the idt alone
424         
425         # set up gdt 
426         xorl    %eax, %eax                              # Compute gdt_base
427         movw    %ds, %ax                                # (Convert %ds:gdt to a linear ptr)
428         shll    $4, %eax
429         addl    $(bImage_gdt - setup_code), %eax
430         movl    %eax, (bImage_gdt_48+2 - setup_code)
431         DATA32 lgdt %ds:(bImage_gdt_48 - setup_code)    # load gdt with whatever is
432                                                         # appropriate
434         # Switch to protected mode
435         movl    %cr0, %eax
436         orb     $CR0_PE, %al
437         movl    %eax, %cr0
439         DATA32 ljmp *%ds:(code32 - setup_code)
440 code32:
441         .long   0x100000
442         .word   __BOOT_CS, 0
443         
444 # Here's a bunch of information about your current kernel..
445 kernel_version: .ascii  "Etherboot "
446                 .ascii  VERSION
447                 .byte   0
449 # This is the default real mode switch routine.
450 # to be called just before protected mode transition
451 default_switch:
452         cli                                     # no interrupts allowed !
453         movb    $0x80, %al                      # disable NMI for bootup
454                                                 # sequence
455         outb    %al, $0x70
456         lret
458 # This routine tests whether or not A20 is enabled.  If so, it
459 # exits with zf = 0.
461 # The memory address used, 0x200, is the int $0x80 vector, which
462 # should be safe.
464 A20_TEST_ADDR = 4*0x80
466 a20_test:
467         pushw   %cx
468         pushw   %ax
469         xorw    %cx, %cx
470         movw    %cx, %fs                        # Low memory
471         decw    %cx
472         movw    %cx, %gs                        # High memory area
473         movw    $A20_TEST_LOOPS, %cx
474         movw    %fs:(A20_TEST_ADDR), %ax
475         pushw   %ax
476 a20_test_wait:
477         incw    %ax
478         movw    %ax, %fs:(A20_TEST_ADDR)
479         call    delay                           # Serialize and make delay constant
480         cmpw    %gs:(A20_TEST_ADDR+0x10), %ax
481         loope   a20_test_wait
483         popw    %fs:(A20_TEST_ADDR)
484         popw    %ax
485         popw    %cx
486         ret     
489 # This routine checks that the keyboard command queue is empty
490 # (after emptying the output buffers)
492 # Some machines have delusions that the keyboard buffer is always full
493 # with no keyboard attached...
495 # If there is no keyboard controller, we will usually get 0xff
496 # to all the reads.  With each IO taking a microsecond and
497 # a timeout of 100,000 iterations, this can take about half a
498 # second ("delay" == outb to port 0x80). That should be ok,
499 # and should also be plenty of time for a real keyboard controller
500 # to empty.
503 empty_8042:
504         pushl   %ecx
505         movl    $100000, %ecx
507 empty_8042_loop:
508         decl    %ecx
509         jz      empty_8042_end_loop
511         call    delay
513         inb     $0x64, %al                      # 8042 status port
514         testb   $1, %al                         # output buffer?
515         jz      no_output
517         call    delay
518         inb     $0x60, %al                      # read it
519         jmp     empty_8042_loop
521 no_output:
522         testb   $2, %al                         # is input buffer full?
523         jnz     empty_8042_loop                 # yes - loop
524 empty_8042_end_loop:
525         popl    %ecx
527                 
528 # Delay is needed after doing I/O
529 delay:
530         outb    %al,$0x80
531         ret
533 # Descriptor tables
535 # NOTE: The intel manual says gdt should be sixteen bytes aligned for
536 # efficiency reasons.  However, there are machines which are known not
537 # to boot with misaligned GDTs, so alter this at your peril!  If you alter
538 # GDT_ENTRY_BOOT_CS (in asm/segment.h) remember to leave at least two
539 # empty GDT entries (one for NULL and one reserved).
541 # NOTE: On some CPUs, the GDT must be 8 byte aligned.  This is
542 # true for the Voyager Quad CPU card which will not boot without
543 # This directive.  16 byte aligment is recommended by intel.
545         .balign 16
546 bImage_gdt:
547         .fill GDT_ENTRY_BOOT_CS,8,0
549         .word   0xFFFF                          # 4Gb - (0x100000*0x1000 = 4Gb)
550         .word   0                               # base address = 0
551         .word   0x9A00                          # code read/exec
552         .word   0x00CF                          # granularity = 4096, 386
553                                                 #  (+5th nibble of limit)
555         .word   0xFFFF                          # 4Gb - (0x100000*0x1000 = 4Gb)
556         .word   0                               # base address = 0
557         .word   0x9200                          # data read/write
558         .word   0x00CF                          # granularity = 4096, 386
559                                                 #  (+5th nibble of limit)
560 bImage_gdt_end:
561         .balign 4
562         
563         .word   0                               # alignment byte
564 bImage_idt_48:
565         .word   0                               # idt limit = 0
566         .long   0                               # idt base = 0L
568         .word   0                               # alignment byte
569 bImage_gdt_48:
570         .word   bImage_gdt_end - bImage_gdt - 1 # gdt limit
571         .long   bImage_gdt_48 - setup_code      # gdt base (filled in later)
573         .section ".text16", "ax", @progbits
574 prefix_exit:
575         int     $0x19           /* should try to boot machine */
576 prefix_exit_end:
577         .previous
578         
579         
580         .org (PREFIXSIZE - 4)
581 # Setup signature -- must be last
582 setup_sig1:     .word   SIG1
583 setup_sig2:     .word   SIG2
584         /* Etherboot expects to be contiguous in memory once loaded.
585          * The linux bImage protocol does not do this, but since we
586          * don't need any information that's left in the prefix, it
587          * doesn't matter: we just have to ensure that we make it to _start
588          *
589          * protected_start will live at 0x100000 and it will be the
590          * the first code called as we enter protected mode.
591          */
592         .code32
593 protected_start:
594         /* Load segment registers */
595         movw    $__BOOT_DS, %ax
596         movw    %ax, %ss
597         movw    %ax, %ds
598         movw    %ax, %es
599         movw    %ax, %fs
600         movw    %ax, %gs
602         /* Use the internal etherboot stack */
603         movl    $(_prefix_stack_end - protected_start + 0x100000), %esp
605         pushl   $0              /* No parameters to preserve for exit path */
606         pushl   $0              /* Use prefix exit path mechanism */
607         
608         jmp     _start
610         That's about it.