Palacios Public Git Repository

To checkout Palacios execute

  git clone http://v3vee.org/palacios/palacios.web/palacios.git
This will give you the master branch. You probably want the devel branch or one of the release branches. To switch to the devel branch, simply execute
  cd palacios
  git checkout --track -b devel origin/devel
The other branches are similar.


Merge branch 'devel'
[palacios.git] / kitten / arch / x86_64 / boot / setup.S
1 /*
2  *      setup.S         Copyright (C) 1991, 1992 Linus Torvalds
3  *
4  * setup.s is responsible for getting the system data from the BIOS,
5  * and putting them into the appropriate places in system memory.
6  * both setup.s and system has been loaded by the bootblock.
7  *
8  * This code asks the bios for memory/disk/other parameters, and
9  * puts them in a "safe" place: 0x90000-0x901FF, ie where the
10  * boot-block used to be. It is then up to the protected mode
11  * system to read them from there before the area is overwritten
12  * for buffer-blocks.
13  *
14  * Move PS/2 aux init code to psaux.c
15  * (troyer@saifr00.cfsat.Honeywell.COM) 03Oct92
16  *
17  * some changes and additional features by Christoph Niemann,
18  * March 1993/June 1994 (Christoph.Niemann@linux.org)
19  *
20  * add APM BIOS checking by Stephen Rothwell, May 1994
21  * (sfr@canb.auug.org.au)
22  *
23  * High load stuff, initrd support and position independency
24  * by Hans Lermen & Werner Almesberger, February 1996
25  * <lermen@elserv.ffm.fgan.de>, <almesber@lrc.epfl.ch>
26  *
27  * Video handling moved to video.S by Martin Mares, March 1996
28  * <mj@k332.feld.cvut.cz>
29  *
30  * Extended memory detection scheme retwiddled by orc@pell.chi.il.us (david
31  * parsons) to avoid loadlin confusion, July 1997
32  *
33  * Transcribed from Intel (as86) -> AT&T (gas) by Chris Noe, May 1999.
34  * <stiker@northlink.com>
35  *
36  * Fix to work around buggy BIOSes which don't use carry bit correctly
37  * and/or report extended memory in CX/DX for e801h memory size detection 
38  * call.  As a result the kernel got wrong figures.  The int15/e801h docs
39  * from Ralf Brown interrupt list seem to indicate AX/BX should be used
40  * anyway.  So to avoid breaking many machines (presumably there was a reason
41  * to orginally use CX/DX instead of AX/BX), we do a kludge to see
42  * if CX/DX have been changed in the e801 call and if so use AX/BX .
43  * Michael Miller, April 2001 <michaelm@mjmm.org>
44  *
45  * Added long mode checking and SSE force. March 2003, Andi Kleen.              
46  */
47
48 #include <arch/segment.h>
49 #include <lwk/version.h>
50 #include <lwk/compile.h>
51 #include <lwk/init.h>
52 #include <arch/boot.h>
53 #include <arch/e820.h>
54 #include <arch/page.h>
55
56 /* Signature words to ensure LILO loaded us right */
57 #define SIG1    0xAA55
58 #define SIG2    0x5A5A
59
60 INITSEG  = DEF_INITSEG          # 0x9000, we move boot here, out of the way
61 SYSSEG   = DEF_SYSSEG           # 0x1000, system loaded at 0x10000 (65536).
62 SETUPSEG = DEF_SETUPSEG         # 0x9020, this is the current segment
63                                 # ... and the former contents of CS
64
65 DELTA_INITSEG = SETUPSEG - INITSEG      # 0x0020
66
67 .code16
68 .globl begtext, begdata, begbss, endtext, enddata, endbss
69
70 .text
71 begtext:
72 .data
73 begdata:
74 .bss
75 begbss:
76 .text
77
78 start:
79         jmp     trampoline
80
81 # This is the setup header, and it must start at %cs:2 (old 0x9020:2)
82
83                 .ascii  "HdrS"          # header signature
84                 .word   0x0206          # header version number (>= 0x0105)
85                                         # or else old loadlin-1.5 will fail)
86 realmode_swtch: .word   0, 0            # default_switch, SETUPSEG
87 start_sys_seg:  .word   SYSSEG
88                 .word   kernel_version  # pointing to kernel version string
89                                         # above section of header is compatible
90                                         # with loadlin-1.5 (header v1.5). Don't
91                                         # change it.
92
93 type_of_loader: .byte   0               # = 0, old one (LILO, Loadlin,
94                                         #      Bootlin, SYSLX, bootsect...)
95                                         # See Documentation/i386/boot.txt for
96                                         # assigned ids
97         
98 # flags, unused bits must be zero (RFU) bit within loadflags
99 loadflags:
100 LOADED_HIGH     = 1                     # If set, the kernel is loaded high
101 CAN_USE_HEAP    = 0x80                  # If set, the loader also has set
102                                         # heap_end_ptr to tell how much
103                                         # space behind setup.S can be used for
104                                         # heap purposes.
105                                         # Only the loader knows what is free
106 #ifndef __BIG_KERNEL__
107                 .byte   0
108 #else
109                 .byte   LOADED_HIGH
110 #endif
111
112 setup_move_size: .word  0x8000          # size to move, when setup is not
113                                         # loaded at 0x90000. We will move setup 
114                                         # to 0x90000 then just before jumping
115                                         # into the kernel. However, only the
116                                         # loader knows how much data behind
117                                         # us also needs to be loaded.
118
119 code32_start:                           # here loaders can put a different
120                                         # start address for 32-bit code.
121 #ifndef __BIG_KERNEL__
122                 .long   0x1000          #   0x1000 = default for zImage
123 #else
124                 .long   0x100000        # 0x100000 = default for big kernel
125 #endif
126
127 ramdisk_image:  .long   0               # address of loaded ramdisk image
128                                         # Here the loader puts the 32-bit
129                                         # address where it loaded the image.
130                                         # This only will be read by the kernel.
131
132 ramdisk_size:   .long   0               # its size in bytes
133
134 bootsect_kludge:
135                 .long   0               # obsolete
136
137 heap_end_ptr:   .word   modelist+1024   # (Header version 0x0201 or later)
138                                         # space from here (exclusive) down to
139                                         # end of setup code can be used by setup
140                                         # for local heap purposes.
141
142 pad1:           .word   0
143 cmd_line_ptr:   .long 0                 # (Header version 0x0202 or later)
144                                         # If nonzero, a 32-bit pointer
145                                         # to the kernel command line.
146                                         # The command line should be
147                                         # located between the start of
148                                         # setup and the end of low
149                                         # memory (0xa0000), or it may
150                                         # get overwritten before it
151                                         # gets read.  If this field is
152                                         # used, there is no longer
153                                         # anything magical about the
154                                         # 0x90000 segment; the setup
155                                         # can be located anywhere in
156                                         # low memory 0x10000 or higher.
157
158 ramdisk_max:    .long 0xffffffff
159 kernel_alignment:  .long 0x200000       # physical addr alignment required for
160                                         # protected mode relocatable kernel
161 #ifdef CONFIG_RELOCATABLE
162 relocatable_kernel:    .byte 1
163 #else
164 relocatable_kernel:    .byte 0
165 #endif
166 pad2:                  .byte 0
167 pad3:                  .word 0
168
169 cmdline_size:   .long   COMMAND_LINE_SIZE-1     #length of the command line,
170                                                 #added with boot protocol
171                                                 #version 2.06
172
173 trampoline:     call    start_of_setup
174                 .align 16
175                                         # The offset at this point is 0x240
176                 .space  (0xeff-0x240+1) # E820 & EDD space (ending at 0xeff)
177 # End of setup header #####################################################
178
179 start_of_setup:
180 # Bootlin depends on this being done early
181         movw    $0x01500, %ax
182         movb    $0x81, %dl
183         int     $0x13
184
185 #ifdef SAFE_RESET_DISK_CONTROLLER
186 # Reset the disk controller.
187         movw    $0x0000, %ax
188         movb    $0x80, %dl
189         int     $0x13
190 #endif
191
192 # Set %ds = %cs, we know that SETUPSEG = %cs at this point
193         movw    %cs, %ax                # aka SETUPSEG
194         movw    %ax, %ds
195 # Check signature at end of setup
196         cmpw    $SIG1, setup_sig1
197         jne     bad_sig
198
199         cmpw    $SIG2, setup_sig2
200         jne     bad_sig
201
202         jmp     good_sig1
203
204 # Routine to print asciiz string at ds:si
205 prtstr:
206         lodsb
207         andb    %al, %al
208         jz      fin
209
210         call    prtchr
211         jmp     prtstr
212
213 fin:    ret
214
215 # Space printing
216 prtsp2: call    prtspc          # Print double space
217 prtspc: movb    $0x20, %al      # Print single space (note: fall-thru)
218
219 prtchr: 
220         pushw   %ax
221         pushw   %cx
222         movw    $0007,%bx
223         movw    $0x01, %cx
224         movb    $0x0e, %ah
225         int     $0x10
226         popw    %cx
227         popw    %ax
228         ret
229
230 beep:   movb    $0x07, %al
231         jmp     prtchr
232         
233 no_sig_mess: .string    "No setup signature found ..."
234
235 good_sig1:
236         jmp     good_sig
237
238 # We now have to find the rest of the setup code/data
239 bad_sig:
240         movw    %cs, %ax                        # SETUPSEG
241         subw    $DELTA_INITSEG, %ax             # INITSEG
242         movw    %ax, %ds
243         xorb    %bh, %bh
244         movb    (497), %bl                      # get setup sect from bootsect
245         subw    $4, %bx                         # LILO loads 4 sectors of setup
246         shlw    $8, %bx                         # convert to words (1sect=2^8 words)
247         movw    %bx, %cx
248         shrw    $3, %bx                         # convert to segment
249         addw    $SYSSEG, %bx
250         movw    %bx, %cs:start_sys_seg
251 # Move rest of setup code/data to here
252         movw    $2048, %di                      # four sectors loaded by LILO
253         subw    %si, %si
254         movw    %cs, %ax                        # aka SETUPSEG
255         movw    %ax, %es
256         movw    $SYSSEG, %ax
257         movw    %ax, %ds
258         rep
259         movsw
260         movw    %cs, %ax                        # aka SETUPSEG
261         movw    %ax, %ds
262         cmpw    $SIG1, setup_sig1
263         jne     no_sig
264
265         cmpw    $SIG2, setup_sig2
266         jne     no_sig
267
268         jmp     good_sig
269
270 no_sig:
271         lea     no_sig_mess, %si
272         call    prtstr
273
274 no_sig_loop:
275         jmp     no_sig_loop
276
277 good_sig:
278         movw    %cs, %ax                        # aka SETUPSEG
279         subw    $DELTA_INITSEG, %ax             # aka INITSEG
280         movw    %ax, %ds
281 # Check if an old loader tries to load a big-kernel
282         testb   $LOADED_HIGH, %cs:loadflags     # Do we have a big kernel?
283         jz      loader_ok                       # No, no danger for old loaders.
284
285         cmpb    $0, %cs:type_of_loader          # Do we have a loader that
286                                                 # can deal with us?
287         jnz     loader_ok                       # Yes, continue.
288
289         pushw   %cs                             # No, we have an old loader,
290         popw    %ds                             # die. 
291         lea     loader_panic_mess, %si
292         call    prtstr
293
294         jmp     no_sig_loop
295
296 loader_panic_mess: .string "Wrong loader, giving up..."
297
298 loader_ok:
299         /* check for long mode. */
300         /* we have to do this before the VESA setup, otherwise the user
301            can't see the error message. */
302         
303         pushw   %ds
304         movw    %cs,%ax
305         movw    %ax,%ds
306         
307         call verify_cpu
308         testl %eax,%eax
309         jz sse_ok
310
311 no_longmode:
312         call    beep
313         lea     long_mode_panic,%si
314         call    prtstr
315 no_longmode_loop:               
316         jmp     no_longmode_loop
317 long_mode_panic:
318         .string "BOOT FAILURE: This system does not support x86_64 long mode."
319         .byte 0
320
321 #include "../kernel/verify_cpu.S"
322 sse_ok:
323         popw    %ds
324         
325 # tell BIOS we want to go to long mode
326         movl  $0xec00,%eax      # declare target operating mode
327         movl  $2,%ebx           # long mode
328         int $0x15                       
329         
330 # Get memory size (extended mem, kB)
331
332         xorl    %eax, %eax
333         movl    %eax, (0x1e0)
334 #ifndef STANDARD_MEMORY_BIOS_CALL
335         movb    %al, (E820NR)
336 # Try three different memory detection schemes.  First, try
337 # e820h, which lets us assemble a memory map, then try e801h,
338 # which returns a 32-bit memory size, and finally 88h, which
339 # returns 0-64m
340
341 # method E820H:
342 # the memory map from hell.  e820h returns memory classified into
343 # a whole bunch of different types, and allows memory holes and
344 # everything.  We scan through this memory map and build a list
345 # of the first 32 memory areas, which we return at [E820MAP].
346 # This is documented at http://www.acpi.info/, in the ACPI 2.0 specification.
347
348 #define SMAP  0x534d4150
349
350 meme820:
351         xorl    %ebx, %ebx                      # continuation counter
352         movw    $E820MAP, %di                   # point into the whitelist
353                                                 # so we can have the bios
354                                                 # directly write into it.
355
356 jmpe820:
357         movl    $0x0000e820, %eax               # e820, upper word zeroed
358         movl    $SMAP, %edx                     # ascii 'SMAP'
359         movl    $20, %ecx                       # size of the e820rec
360         pushw   %ds                             # data record.
361         popw    %es
362         int     $0x15                           # make the call
363         jc      bail820                         # fall to e801 if it fails
364
365         cmpl    $SMAP, %eax                     # check the return is `SMAP'
366         jne     bail820                         # fall to e801 if it fails
367
368 #       cmpl    $1, 16(%di)                     # is this usable memory?
369 #       jne     again820
370
371         # If this is usable memory, we save it by simply advancing %di by
372         # sizeof(e820rec).
373         #
374 good820:
375         movb    (E820NR), %al                   # up to 128 entries
376         cmpb    $E820MAX, %al
377         jae     bail820
378
379         incb    (E820NR)
380         movw    %di, %ax
381         addw    $20, %ax
382         movw    %ax, %di
383 again820:
384         cmpl    $0, %ebx                        # check to see if
385         jne     jmpe820                         # %ebx is set to EOF
386 bail820:
387
388
389 # method E801H:
390 # memory size is in 1k chunksizes, to avoid confusing loadlin.
391 # we store the 0xe801 memory size in a completely different place,
392 # because it will most likely be longer than 16 bits.
393 # (use 1e0 because that's what Larry Augustine uses in his
394 # alternative new memory detection scheme, and it's sensible
395 # to write everything into the same place.)
396
397 meme801:
398         stc                                     # fix to work around buggy
399         xorw    %cx,%cx                         # BIOSes which don't clear/set
400         xorw    %dx,%dx                         # carry on pass/error of
401                                                 # e801h memory size call
402                                                 # or merely pass cx,dx though
403                                                 # without changing them.
404         movw    $0xe801, %ax
405         int     $0x15
406         jc      mem88
407
408         cmpw    $0x0, %cx                       # Kludge to handle BIOSes
409         jne     e801usecxdx                     # which report their extended
410         cmpw    $0x0, %dx                       # memory in AX/BX rather than
411         jne     e801usecxdx                     # CX/DX.  The spec I have read
412         movw    %ax, %cx                        # seems to indicate AX/BX 
413         movw    %bx, %dx                        # are more reasonable anyway...
414
415 e801usecxdx:
416         andl    $0xffff, %edx                   # clear sign extend
417         shll    $6, %edx                        # and go from 64k to 1k chunks
418         movl    %edx, (0x1e0)                   # store extended memory size
419         andl    $0xffff, %ecx                   # clear sign extend
420         addl    %ecx, (0x1e0)                   # and add lower memory into
421                                                 # total size.
422
423 # Ye Olde Traditional Methode.  Returns the memory size (up to 16mb or
424 # 64mb, depending on the bios) in ax.
425 mem88:
426
427 #endif
428         movb    $0x88, %ah
429         int     $0x15
430         movw    %ax, (2)
431
432 # Set the keyboard repeat rate to the max
433         movw    $0x0305, %ax
434         xorw    %bx, %bx
435         int     $0x16
436
437 # Check for video adapter and its parameters and allow the
438 # user to browse video modes.
439         call    video                           # NOTE: we need %ds pointing
440                                                 # to bootsector
441
442 # Get hd0 data...
443         xorw    %ax, %ax
444         movw    %ax, %ds
445         ldsw    (4 * 0x41), %si
446         movw    %cs, %ax                        # aka SETUPSEG
447         subw    $DELTA_INITSEG, %ax             # aka INITSEG
448         pushw   %ax
449         movw    %ax, %es
450         movw    $0x0080, %di
451         movw    $0x10, %cx
452         pushw   %cx
453         cld
454         rep
455         movsb
456 # Get hd1 data...
457         xorw    %ax, %ax
458         movw    %ax, %ds
459         ldsw    (4 * 0x46), %si
460         popw    %cx
461         popw    %es
462         movw    $0x0090, %di
463         rep
464         movsb
465 # Check that there IS a hd1 :-)
466         movw    $0x01500, %ax
467         movb    $0x81, %dl
468         int     $0x13
469         jc      no_disk1
470         
471         cmpb    $3, %ah
472         je      is_disk1
473
474 no_disk1:
475         movw    %cs, %ax                        # aka SETUPSEG
476         subw    $DELTA_INITSEG, %ax             # aka INITSEG
477         movw    %ax, %es
478         movw    $0x0090, %di
479         movw    $0x10, %cx
480         xorw    %ax, %ax
481         cld
482         rep
483         stosb
484 is_disk1:
485
486 # Check for PS/2 pointing device
487         movw    %cs, %ax                        # aka SETUPSEG
488         subw    $DELTA_INITSEG, %ax             # aka INITSEG
489         movw    %ax, %ds
490         movb    $0, (0x1ff)                     # default is no pointing device
491         int     $0x11                           # int 0x11: equipment list
492         testb   $0x04, %al                      # check if mouse installed
493         jz      no_psmouse
494
495         movb    $0xAA, (0x1ff)                  # device present
496 no_psmouse:
497
498 # Now we want to move to protected mode ...
499         cmpw    $0, %cs:realmode_swtch
500         jz      rmodeswtch_normal
501
502         lcall   *%cs:realmode_swtch
503
504         jmp     rmodeswtch_end
505
506 rmodeswtch_normal:
507         pushw   %cs
508         call    default_switch
509
510 rmodeswtch_end:
511 # we get the code32 start address and modify the below 'jmpi'
512 # (loader may have changed it)
513         movl    %cs:code32_start, %eax
514         movl    %eax, %cs:code32
515
516 # Now we move the system to its rightful place ... but we check if we have a
517 # big-kernel. In that case we *must* not move it ...
518         testb   $LOADED_HIGH, %cs:loadflags
519         jz      do_move0                        # .. then we have a normal low
520                                                 # loaded zImage
521                                                 # .. or else we have a high
522                                                 # loaded bzImage
523         jmp     end_move                        # ... and we skip moving
524
525 do_move0:
526         movw    $0x100, %ax                     # start of destination segment
527         movw    %cs, %bp                        # aka SETUPSEG
528         subw    $DELTA_INITSEG, %bp             # aka INITSEG
529         movw    %cs:start_sys_seg, %bx          # start of source segment
530         cld
531 do_move:
532         movw    %ax, %es                        # destination segment
533         incb    %ah                             # instead of add ax,#0x100
534         movw    %bx, %ds                        # source segment
535         addw    $0x100, %bx
536         subw    %di, %di
537         subw    %si, %si
538         movw    $0x800, %cx
539         rep
540         movsw
541         cmpw    %bp, %bx                        # assume start_sys_seg > 0x200,
542                                                 # so we will perhaps read one
543                                                 # page more than needed, but
544                                                 # never overwrite INITSEG
545                                                 # because destination is a
546                                                 # minimum one page below source
547         jb      do_move
548
549 end_move:
550 # then we load the segment descriptors
551         movw    %cs, %ax                        # aka SETUPSEG
552         movw    %ax, %ds
553                 
554 # Check whether we need to be downward compatible with version <=201
555         cmpl    $0, cmd_line_ptr
556         jne     end_move_self           # loader uses version >=202 features
557         cmpb    $0x20, type_of_loader
558         je      end_move_self           # bootsect loader, we know of it
559
560 # Boot loader doesnt support boot protocol version 2.02.
561 # If we have our code not at 0x90000, we need to move it there now.
562 # We also then need to move the params behind it (commandline)
563 # Because we would overwrite the code on the current IP, we move
564 # it in two steps, jumping high after the first one.
565         movw    %cs, %ax
566         cmpw    $SETUPSEG, %ax
567         je      end_move_self
568
569         cli                                     # make sure we really have
570                                                 # interrupts disabled !
571                                                 # because after this the stack
572                                                 # should not be used
573         subw    $DELTA_INITSEG, %ax             # aka INITSEG
574         movw    %ss, %dx
575         cmpw    %ax, %dx
576         jb      move_self_1
577
578         addw    $INITSEG, %dx
579         subw    %ax, %dx                        # this will go into %ss after
580                                                 # the move
581 move_self_1:
582         movw    %ax, %ds
583         movw    $INITSEG, %ax                   # real INITSEG
584         movw    %ax, %es
585         movw    %cs:setup_move_size, %cx
586         std                                     # we have to move up, so we use
587                                                 # direction down because the
588                                                 # areas may overlap
589         movw    %cx, %di
590         decw    %di
591         movw    %di, %si
592         subw    $move_self_here+0x200, %cx
593         rep
594         movsb
595         ljmp    $SETUPSEG, $move_self_here
596
597 move_self_here:
598         movw    $move_self_here+0x200, %cx
599         rep
600         movsb
601         movw    $SETUPSEG, %ax
602         movw    %ax, %ds
603         movw    %dx, %ss
604 end_move_self:                                  # now we are at the right place
605         lidt    idt_48                          # load idt with 0,0
606         xorl    %eax, %eax                      # Compute gdt_base
607         movw    %ds, %ax                        # (Convert %ds:gdt to a linear ptr)
608         shll    $4, %eax
609         addl    $gdt, %eax
610         movl    %eax, (gdt_48+2)
611         lgdt    gdt_48                          # load gdt with whatever is
612                                                 # appropriate
613
614 # that was painless, now we enable a20
615         call    empty_8042
616
617         movb    $0xD1, %al                      # command write
618         outb    %al, $0x64
619         call    empty_8042
620
621         movb    $0xDF, %al                      # A20 on
622         outb    %al, $0x60
623         call    empty_8042
624
625 #
626 #       You must preserve the other bits here. Otherwise embarrasing things
627 #       like laptops powering off on boot happen. Corrected version by Kira
628 #       Brown from Linux 2.2
629 #
630         inb     $0x92, %al                      # 
631         orb     $02, %al                        # "fast A20" version
632         outb    %al, $0x92                      # some chips have only this
633
634 # wait until a20 really *is* enabled; it can take a fair amount of
635 # time on certain systems; Toshiba Tecras are known to have this
636 # problem.  The memory location used here (0x200) is the int 0x80
637 # vector, which should be safe to use.
638
639         xorw    %ax, %ax                        # segment 0x0000
640         movw    %ax, %fs
641         decw    %ax                             # segment 0xffff (HMA)
642         movw    %ax, %gs
643 a20_wait:
644         incw    %ax                             # unused memory location <0xfff0
645         movw    %ax, %fs:(0x200)                # we use the "int 0x80" vector
646         cmpw    %gs:(0x210), %ax                # and its corresponding HMA addr
647         je      a20_wait                        # loop until no longer aliased
648
649 # make sure any possible coprocessor is properly reset..
650         xorw    %ax, %ax
651         outb    %al, $0xf0
652         call    delay
653
654         outb    %al, $0xf1
655         call    delay
656
657 # well, that went ok, I hope. Now we mask all interrupts - the rest
658 # is done in init_IRQ().
659         movb    $0xFF, %al                      # mask all interrupts for now
660         outb    %al, $0xA1
661         call    delay
662         
663         movb    $0xFB, %al                      # mask all irq's but irq2 which
664         outb    %al, $0x21                      # is cascaded
665
666 # Well, that certainly wasn't fun :-(. Hopefully it works, and we don't
667 # need no steenking BIOS anyway (except for the initial loading :-).
668 # The BIOS-routine wants lots of unnecessary data, and it's less
669 # "interesting" anyway. This is how REAL programmers do it.
670 #
671 # Well, now's the time to actually move into protected mode. To make
672 # things as simple as possible, we do no register set-up or anything,
673 # we let the gnu-compiled 32-bit programs do that. We just jump to
674 # absolute address 0x1000 (or the loader supplied one),
675 # in 32-bit protected mode.
676 #
677 # Note that the short jump isn't strictly needed, although there are
678 # reasons why it might be a good idea. It won't hurt in any case.
679         movw    $1, %ax                         # protected mode (PE) bit
680         lmsw    %ax                             # This is it!
681         jmp     flush_instr
682
683 flush_instr:
684         xorw    %bx, %bx                        # Flag to indicate a boot
685         xorl    %esi, %esi                      # Pointer to real-mode code
686         movw    %cs, %si
687         subw    $DELTA_INITSEG, %si
688         shll    $4, %esi                        # Convert to 32-bit pointer
689 # NOTE: For high loaded big kernels we need a
690 #       jmpi    0x100000,__KERNEL_CS
691 #
692 #       but we yet haven't reloaded the CS register, so the default size 
693 #       of the target offset still is 16 bit.
694 #       However, using an operand prefix (0x66), the CPU will properly
695 #       take our 48 bit far pointer. (INTeL 80386 Programmer's Reference
696 #       Manual, Mixing 16-bit and 32-bit code, page 16-6)
697
698         .byte 0x66, 0xea                        # prefix + jmpi-opcode
699 code32: .long   0x1000                          # will be set to 0x100000
700                                                 # for big kernels
701         .word   __KERNEL_CS
702
703 # Here's a bunch of information about your current kernel..
704 kernel_version: .ascii  UTS_RELEASE
705                 .ascii  " ("
706                 .ascii  LWK_COMPILE_BY
707                 .ascii  "@"
708                 .ascii  LWK_COMPILE_HOST
709                 .ascii  ") "
710                 .ascii  UTS_VERSION
711                 .byte   0
712
713 # This is the default real mode switch routine.
714 # to be called just before protected mode transition
715 default_switch:
716         cli                                     # no interrupts allowed !
717         movb    $0x80, %al                      # disable NMI for bootup
718                                                 # sequence
719         outb    %al, $0x70
720         lret
721
722
723 # This routine checks that the keyboard command queue is empty
724 # (after emptying the output buffers)
725 #
726 # Some machines have delusions that the keyboard buffer is always full
727 # with no keyboard attached...
728 #
729 # If there is no keyboard controller, we will usually get 0xff
730 # to all the reads.  With each IO taking a microsecond and
731 # a timeout of 100,000 iterations, this can take about half a
732 # second ("delay" == outb to port 0x80). That should be ok,
733 # and should also be plenty of time for a real keyboard controller
734 # to empty.
735 #
736
737 empty_8042:
738         pushl   %ecx
739         movl    $100000, %ecx
740
741 empty_8042_loop:
742         decl    %ecx
743         jz      empty_8042_end_loop
744
745         call    delay
746
747         inb     $0x64, %al                      # 8042 status port
748         testb   $1, %al                         # output buffer?
749         jz      no_output
750
751         call    delay
752         inb     $0x60, %al                      # read it
753         jmp     empty_8042_loop
754
755 no_output:
756         testb   $2, %al                         # is input buffer full?
757         jnz     empty_8042_loop                 # yes - loop
758 empty_8042_end_loop:
759         popl    %ecx
760         ret
761
762 # Read the cmos clock. Return the seconds in al
763 gettime:
764         pushw   %cx
765         movb    $0x02, %ah
766         int     $0x1a
767         movb    %dh, %al                        # %dh contains the seconds
768         andb    $0x0f, %al
769         movb    %dh, %ah
770         movb    $0x04, %cl
771         shrb    %cl, %ah
772         aad
773         popw    %cx
774         ret
775
776 # Delay is needed after doing I/O
777 delay:
778         outb    %al,$0x80
779         ret
780
781 # Descriptor tables
782 gdt:
783         .word   0, 0, 0, 0                      # dummy
784
785         .word   0, 0, 0, 0                      # unused
786
787         .word   0xFFFF                          # 4Gb - (0x100000*0x1000 = 4Gb)
788         .word   0                               # base address = 0
789         .word   0x9A00                          # code read/exec
790         .word   0x00CF                          # granularity = 4096, 386
791                                                 #  (+5th nibble of limit)
792
793         .word   0xFFFF                          # 4Gb - (0x100000*0x1000 = 4Gb)
794         .word   0                               # base address = 0
795         .word   0x9200                          # data read/write
796         .word   0x00CF                          # granularity = 4096, 386
797                                                 #  (+5th nibble of limit)
798 gdt_end:
799 idt_48:
800         .word   0                               # idt limit = 0
801         .word   0, 0                            # idt base = 0L
802 gdt_48:
803         .word   gdt_end-gdt-1                   # gdt limit
804         .word   0, 0                            # gdt base (filled in later)
805
806 # Include video setup & detection code
807
808 #include "video.S"
809
810 # Setup signature -- must be last
811 setup_sig1:     .word   SIG1
812 setup_sig2:     .word   SIG2
813
814 # After this point, there is some free space which is used by the video mode
815 # handling code to store the temporary mode table (not used by the kernel).
816
817 modelist:
818
819 .text
820 endtext:
821 .data
822 enddata:
823 .bss
824 endbss: