patch-2.3.21 linux/arch/i386/boot/setup.S
Next file: linux/arch/i386/boot/tools/build.c
Previous file: linux/arch/i386/boot/compressed/Makefile
Back to the patch index
Back to the overall index
- Lines: 1516
- Date:
Mon Oct 11 14:06:10 1999
- Orig file:
v2.3.20/linux/arch/i386/boot/setup.S
- Orig date:
Sat Oct 9 11:47:50 1999
diff -u --recursive --new-file v2.3.20/linux/arch/i386/boot/setup.S linux/arch/i386/boot/setup.S
@@ -1,35 +1,38 @@
-!
-! setup.S Copyright (C) 1991, 1992 Linus Torvalds
-!
-! setup.s is responsible for getting the system data from the BIOS,
-! and putting them into the appropriate places in system memory.
-! both setup.s and system has been loaded by the bootblock.
-!
-! This code asks the bios for memory/disk/other parameters, and
-! puts them in a "safe" place: 0x90000-0x901FF, ie where the
-! boot-block used to be. It is then up to the protected mode
-! system to read them from there before the area is overwritten
-! for buffer-blocks.
-!
-! Move PS/2 aux init code to psaux.c
-! (troyer@saifr00.cfsat.Honeywell.COM) 03Oct92
-!
-! some changes and additional features by Christoph Niemann,
-! March 1993/June 1994 (Christoph.Niemann@linux.org)
-!
-! add APM BIOS checking by Stephen Rothwell, May 1994
-! (Stephen.Rothwell@canb.auug.org.au)
-!
-! High load stuff, initrd support and position independency
-! by Hans Lermen & Werner Almesberger, February 1996
-! <lermen@elserv.ffm.fgan.de>, <almesber@lrc.epfl.ch>
-!
-! Video handling moved to video.S by Martin Mares, March 1996
-! <mj@k332.feld.cvut.cz>
-!
-! Extended memory detection scheme retwiddled by orc@pell.chi.il.us (david
-! parsons) to avoid loadlin confusion, July 1997
-!
+/*
+ * setup.S Copyright (C) 1991, 1992 Linus Torvalds
+ *
+ * setup.s is responsible for getting the system data from the BIOS,
+ * and putting them into the appropriate places in system memory.
+ * both setup.s and system has been loaded by the bootblock.
+ *
+ * This code asks the bios for memory/disk/other parameters, and
+ * puts them in a "safe" place: 0x90000-0x901FF, ie where the
+ * boot-block used to be. It is then up to the protected mode
+ * system to read them from there before the area is overwritten
+ * for buffer-blocks.
+ *
+ * Move PS/2 aux init code to psaux.c
+ * (troyer@saifr00.cfsat.Honeywell.COM) 03Oct92
+ *
+ * some changes and additional features by Christoph Niemann,
+ * March 1993/June 1994 (Christoph.Niemann@linux.org)
+ *
+ * add APM BIOS checking by Stephen Rothwell, May 1994
+ * (Stephen.Rothwell@canb.auug.org.au)
+ *
+ * High load stuff, initrd support and position independency
+ * by Hans Lermen & Werner Almesberger, February 1996
+ * <lermen@elserv.ffm.fgan.de>, <almesber@lrc.epfl.ch>
+ *
+ * Video handling moved to video.S by Martin Mares, March 1996
+ * <mj@k332.feld.cvut.cz>
+ *
+ * Extended memory detection scheme retwiddled by orc@pell.chi.il.us (david
+ * parsons) to avoid loadlin confusion, July 1997
+ *
+ * Transcribed from Intel (as86) -> AT&T (gas) by Chris Noe, May 1999.
+ * <stiker@northlink.com>
+ */
#define __ASSEMBLY__
#include <linux/config.h>
@@ -39,17 +42,20 @@
#include <asm/boot.h>
#include <asm/e820.h>
-! Signature words to ensure LILO loaded us right
+/* Signature words to ensure LILO loaded us right */
#define SIG1 0xAA55
#define SIG2 0x5A5A
-INITSEG = DEF_INITSEG ! 0x9000, we move boot here - out of the way
-SYSSEG = DEF_SYSSEG ! 0x1000, system loaded at 0x10000 (65536).
-SETUPSEG = DEF_SETUPSEG ! 0x9020, this is the current segment
- ! ... and the former contents of CS
-DELTA_INITSEG = SETUPSEG - INITSEG ! 0x0020
+INITSEG = DEF_INITSEG # 0x9000, we move boot here, out of the way
+SYSSEG = DEF_SYSSEG # 0x1000, system loaded at 0x10000 (65536).
+SETUPSEG = DEF_SETUPSEG # 0x9020, this is the current segment
+ # ... and the former contents of CS
+DELTA_INITSEG = SETUPSEG - INITSEG # 0x0020
+
+.code16
.globl begtext, begdata, begbss, endtext, enddata, endbss
+
.text
begtext:
.data
@@ -58,631 +64,617 @@
begbss:
.text
-entry start
start:
jmp trampoline
-! ------------------------ start of header --------------------------------
-!
-! SETUP-header, must start at CS:2 (old 0x9020:2)
-!
- .ascii "HdrS" ! Signature for SETUP-header
- .word 0x0201 ! Version number of header format
- ! (must be >= 0x0105
- ! else old loadlin-1.5 will fail)
-realmode_swtch: .word 0,0 ! default_switch,SETUPSEG
+
+# This is the setup header, and it must start at %cs:2 (old 0x9020:2)
+
+ .ascii "HdrS" # header signature
+ .word 0x0201 # 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
- .word kernel_version ! pointing to kernel version string
- ! note: above part of header is compatible with loadlin-1.5 (header v1.5),
- ! must not change it
-
-type_of_loader: .byte 0 ! = 0, old one (LILO, Loadlin,
- ! Bootlin, SYSLX, bootsect...)
- ! else it is set by the loader:
- ! 0xTV: T=0 for LILO
- ! T=1 for Loadlin
- ! T=2 for bootsect-loader
- ! T=3 for SYSLX
- ! T=4 for ETHERBOOT
- ! V = version
-loadflags: ! flags, unused bits must be zero (RFU)
-LOADED_HIGH = 1 ! bit within loadflags,
- ! if set, then 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!
+ .word kernel_version # 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...)
+ # else it is set by the loader:
+ # 0xTV: T=0 for LILO
+ # T=1 for Loadlin
+ # T=2 for bootsect-loader
+ # T=3 for SYSLX
+ # T=4 for ETHERBOOT
+ # V = version
+
+# 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
#ifndef __BIG_KERNEL__
- .byte 0x00
+ .byte 0
#else
.byte LOADED_HIGH
#endif
-setup_move_size: .word 0x8000 ! size to move, when we (setup) are not
- ! loaded at 0x90000. We will move ourselves
- ! to 0x90000 then just before jumping into
- ! the kernel. However, only the loader
- ! know how much of data behind us also needs
- ! to be loaded.
-code32_start: ! here loaders can put a different
- ! start address for 32-bit code.
+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.
#ifndef __BIG_KERNEL__
- .long 0x1000 ! 0x1000 = default for zImage
+ .long 0x1000 # 0x1000 = default for zImage
#else
- .long 0x100000 ! 0x100000 = default for big kernel
+ .long 0x100000 # 0x100000 = default for big kernel
#endif
-ramdisk_image: .long 0 ! address of loaded ramdisk image
- ! Here the loader (or kernel generator) puts
- ! the 32-bit address were it loaded the image.
- ! This only will be interpreted by the kernel.
-ramdisk_size: .long 0 ! its size in bytes
+
+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
+
+.global bootsect_kludge # so that we can see it in bootsect.S
bootsect_kludge:
- .word bootsect_helper,SETUPSEG
-heap_end_ptr: .word modelist+1024 ! space from here (exclusive) down to
- ! end of setup code can be used by setup
- ! for local heap purposes.
+ .word bootsect_helper, SETUPSEG
+
+heap_end_ptr: .word modelist+1024 # space from here (exclusive) down to
+ # end of setup code can be used by setup
+ # for local heap purposes.
trampoline: call start_of_setup
.space 1024
-! ------------------------ end of header ----------------------------------
+# End of setup header #####################################################
start_of_setup:
-! Bootlin depends on this being done early
- mov ax,#0x01500
- mov dl,#0x81
- int 0x13
+# Bootlin depends on this being done early
+ movw $0x01500, %ax
+ movb $0x81, %dl
+ int $0x13
#ifdef SAFE_RESET_DISK_CONTROLLER
-! Reset the disk controller.
- mov ax,#0x0000
- mov dl,#0x80
- int 0x13
+# Reset the disk controller.
+ movw $0x0000, %ax
+ movb $0x80, $dl
+ int $0x13
#endif
-! set DS=CS, we know that SETUPSEG == CS at this point
- mov ax,cs ! aka #SETUPSEG
- mov ds,ax
-
-! Check signature at end of setup
- cmp setup_sig1,#SIG1
+# 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
jne bad_sig
- cmp setup_sig2,#SIG2
+
+ cmpw $SIG2, setup_sig2
jne bad_sig
- jmp good_sig1
-! Routine to print ASCIIz string at DS:SI
+ jmp good_sig1
-prtstr: lodsb
- and al,al
+# Routine to print asciiz string at ds:si
+prtstr:
+ lodsb
+ andb %al, %al
jz fin
+
call prtchr
jmp prtstr
-fin: ret
-! Space printing
-
-prtsp2: call prtspc ! Print double space
-prtspc: mov al,#0x20 ! Print single space (fall-thru!)
-
-! Part of above routine, this one just prints ASCII al
+fin: ret
-prtchr: push ax
- push cx
- xor bh,bh
- mov cx,#0x01
- mov ah,#0x0e
- int 0x10
- pop cx
- pop ax
+# Space printing
+prtsp2: call prtspc # Print double space
+prtspc: movb $0x20, %al # Print single space (note: fall-thru)
+
+# Part of above routine, this one just prints ascii al
+prtchr: pushw %ax
+ pushw %cx
+ xorb %bh, %bh
+ movw $0x01, %cx
+ movb $0x0e, %ah
+ int $0x10
+ popw %cx
+ popw %ax
ret
-beep: mov al,#0x07
+beep: movb $0x07, %al
jmp prtchr
-no_sig_mess: .ascii "No setup signature found ..."
- db 0x00
+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
+# We now have to find the rest of the setup code/data
bad_sig:
- mov ax,cs ! aka #SETUPSEG
- sub ax,#DELTA_INITSEG ! aka #INITSEG
- mov ds,ax
- xor bh,bh
- mov bl,[497] ! get setup sects from boot sector
- sub bx,#4 ! LILO loads 4 sectors of setup
- shl bx,#7 ! convert to dwords (1sect=2^7 dwords)
- mov cx,bx
- shr bx,#2 ! convert to segment
- add bx,#SYSSEG
- seg cs
- mov start_sys_seg,bx
-
-! Move rest of setup code/data to here
- mov di,#2048 ! four sectors loaded by LILO
- sub si,si
- mov ax,cs ! aka #SETUPSEG
- mov es,ax
- mov ax,#SYSSEG
- mov ds,ax
+ 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 $7, %bx # convert to dwords (1sect=2^7 dwords)
+ movw %bx, %cx
+ shrw $2, %bx # convert to segment
+ addw $SYSSEG, %bx
+ movw %bx, %cs:start_sys_seg
+# Move rest of setup code/data to here
+ movw $2048, %di # four sectors loaded by LILO
+ subw %si, %si
+ movw %cs, %ax # aka SETUPSEG
+ movw %ax, %es
+ movw $SYSSEG, %ax
+ movw %ax, %ds
rep
- movsd
-
- mov ax,cs ! aka #SETUPSEG
- mov ds,ax
- cmp setup_sig1,#SIG1
+ movsl
+ movw %cs, %ax # aka SETUPSEG
+ movw %ax, %ds
+ cmpw $SIG1, setup_sig1
jne no_sig
- cmp setup_sig2,#SIG2
+
+ cmpw $SIG2, setup_sig2
jne no_sig
+
jmp good_sig
no_sig:
- lea si,no_sig_mess
+ lea no_sig_mess, %si
call prtstr
+
no_sig_loop:
jmp no_sig_loop
good_sig:
- mov ax,cs ! aka #SETUPSEG
- sub ax,#DELTA_INITSEG ! aka #INITSEG
- mov ds,ax
-
-! check if an old loader tries to load a big-kernel
- seg cs
- test byte ptr loadflags,#LOADED_HIGH ! Have we a big kernel?
- jz loader_ok ! NO, no danger even for old loaders
- ! YES, we have a big-kernel
- seg cs
- cmp byte ptr type_of_loader,#0 ! Have we one of the new loaders?
- jnz loader_ok ! YES, OK
- ! NO, we have an old loader, must give up
- push cs
- pop ds
- lea si,loader_panic_mess
+ movw %cs, %ax # aka SETUPSEG
+ subw $DELTA_INITSEG, %ax # aka INITSEG
+ movw %ax, %ds
+# Check if an old loader tries to load a big-kernel
+ testb $LOADED_HIGH, %cs:loadflags # Do we have a big kernel?
+ jz loader_ok # No, no danger for old loaders.
+
+ cmpb $0, %cs:type_of_loader # Do we have a loader that
+ # can deal with us?
+ jnz loader_ok # Yes, continue.
+
+ pushw %cs # No, we have an old loader,
+ popw %ds # die.
+ lea loader_panic_mess, %si
call prtstr
+
jmp no_sig_loop
-loader_panic_mess:
- .ascii "Wrong loader: giving up."
- db 0
+
+loader_panic_mess: .string "Wrong loader, giving up..."
loader_ok:
-! Get memory size (extended mem, kB)
+# Get memory size (extended mem, kB)
- xor eax, eax
- mov dword ptr [0x1e0], eax
+ xorl %eax, %eax
+ movl %eax, (0x1e0)
#ifndef STANDARD_MEMORY_BIOS_CALL
-
- mov byte ptr [E820NR], al
-
-! Try three different memory detection schemes. First, try
-! e820h, which lets us assemble a memory map, then try e801h,
-! which returns a 32-bit memory size, and finally 88h, which
-! returns 0-64m
-
-! method E820H:
-! the memory map from hell. e820h returns memory classified into
-! a whole bunch of different types, and allows memory holes and
-! everything. We scan through this memory map and build a list
-! of the first 32 memory areas, which we return at [E820MAP].
-!
+ movb %al, (E820NR)
+# Try three different memory detection schemes. First, try
+# e820h, which lets us assemble a memory map, then try e801h,
+# which returns a 32-bit memory size, and finally 88h, which
+# returns 0-64m
+
+# method E820H:
+# the memory map from hell. e820h returns memory classified into
+# a whole bunch of different types, and allows memory holes and
+# everything. We scan through this memory map and build a list
+# of the first 32 memory areas, which we return at [E820MAP].
+#
meme820:
- mov edx, #0x534d4150 ! ascii `SMAP'
- xor ebx, ebx ! continuation counter
-
- mov di, #E820MAP ! point into the whitelist
- ! so we can have the bios
- ! directly write into it.
+ movl $0x534d4150, %edx # ascii `SMAP'
+ xorl %ebx, %ebx # continuation counter
+ movw $E820MAP, %di # point into the whitelist
+ # so we can have the bios
+ # directly write into it.
jmpe820:
- mov eax, #0x0000e820 ! e820, upper word zeroed
- mov ecx, #20 ! size of the e820rec
-
- push ds ! data record.
- pop es
- int 0x15 ! make the call
- jc bail820 ! fall to e801 if it fails
-
- cmp eax, #0x534d4150 ! check the return is `SMAP'
- jne bail820 ! fall to e801 if it fails
-
-! cmp dword ptr [16+di], #1 ! is this usable memory?
-! jne again820
-
- ! If this is usable memory, we save it by simply advancing di by
- ! sizeof(e820rec).
- !
+ movl $0x0000e820, %eax # e820, upper word zeroed
+ movl $20, %ecx # size of the e820rec
+ pushw %ds # data record.
+ popw %es
+ int $0x15 # make the call
+ jc bail820 # fall to e801 if it fails
+
+ cmpl $0x534d4150, %eax # check the return is `SMAP'
+ jne bail820 # fall to e801 if it fails
+
+# cmpl $1, 16(%di) # is this usable memory?
+# jne again820
+
+ # If this is usable memory, we save it by simply advancing %di by
+ # sizeof(e820rec).
+ #
good820:
- mov al, byte ptr [E820NR] ! up to 32 good entries, that is
- cmp al, #E820MAX
+ movb (E820NR), %al # up to 32 entries
+ cmpb $E820MAX, %al
jnl bail820
- inc byte ptr [E820NR]
- mov ax, di
- add ax, #20
- mov di, ax
+ incb (E820NR)
+ movw %di, %ax
+ addw $20, %ax
+ movw %ax, %di
again820:
- cmp ebx, #0 ! check to see if ebx is
- jne jmpe820 ! set to EOF
-
+ cmpl $0, %ebx # check to see if
+ jne jmpe820 # %ebx is set to EOF
bail820:
-! method E801H:
-! memory size is in 1k chunksizes, to avoid confusing loadlin.
-! we store the 0xe801 memory size in a completely different place,
-! because it will most likely be longer than 16 bits.
-! (use 1e0 because that's what Larry Augustine uses in his
-! alternative new memory detection scheme, and it's sensible
-! to write everything into the same place.)
+# method E801H:
+# memory size is in 1k chunksizes, to avoid confusing loadlin.
+# we store the 0xe801 memory size in a completely different place,
+# because it will most likely be longer than 16 bits.
+# (use 1e0 because that's what Larry Augustine uses in his
+# alternative new memory detection scheme, and it's sensible
+# to write everything into the same place.)
meme801:
-
- mov ax,#0xe801
- int 0x15
+ movw $0xe801, %ax
+ int $0x15
jc mem88
- and edx, #0xffff ! clear sign extend
- shl edx, 6 ! and go from 64k to 1k chunks
- mov [0x1e0],edx ! store extended memory size
+ andl $0xffff, %edx # clear sign extend
+ shll $6, %edx # and go from 64k to 1k chunks
+ movl %edx, (0x1e0) # store extended memory size
+ andl $0xffff, %ecx # clear sign extend
+ addl %ecx, (0x1e0) # and add lower memory into
+ # total size.
- and ecx, #0xffff ! clear sign extend
- add [0x1e0],ecx ! and add lower memory into total size.
-
-! Ye Olde Traditional Methode. Returns the memory size (up to 16mb or
-! 64mb, depending on the bios) in ax.
+# Ye Olde Traditional Methode. Returns the memory size (up to 16mb or
+# 64mb, depending on the bios) in ax.
mem88:
#endif
- mov ah,#0x88
- int 0x15
- mov [2],ax
-
-! Set the keyboard repeat rate to the max
-
- mov ax,#0x0305
- xor bx,bx ! clear bx
- int 0x16
-
-! Check for video adapter and its parameters and allow the
-! user to browse video modes.
-
- call video ! NOTE: we need DS pointing to boot sector
-
-! Get hd0 data
-
- xor ax,ax ! clear ax
- mov ds,ax
- lds si,[4*0x41]
- mov ax,cs ! aka #SETUPSEG
- sub ax,#DELTA_INITSEG ! aka #INITSEG
- push ax
- mov es,ax
- mov di,#0x0080
- mov cx,#0x10
- push cx
+ movb $0x88, %ah
+ int $0x15
+ movw %ax, (2)
+
+# Set the keyboard repeat rate to the max
+ movw $0x0305, %ax
+ xorw %bx, %bx
+ int $0x16
+
+# Check for video adapter and its parameters and allow the
+# user to browse video modes.
+ call video # NOTE: we need %ds pointing
+ # to bootsector
+
+# Get hd0 data...
+ xorw %ax, %ax
+ movw %ax, %ds
+ ldsw (4 * 0x41), %si
+ movw %cs, %ax # aka SETUPSEG
+ subw $DELTA_INITSEG, %ax # aka INITSEG
+ pushw %ax
+ movw %ax, %es
+ movw $0x0080, %di
+ movw $0x10, %cx
+ pushw %cx
cld
rep
- movsb
-
-! Get hd1 data
-
- xor ax,ax ! clear ax
- mov ds,ax
- lds si,[4*0x46]
- pop cx
- pop es
- mov di,#0x0090
+ movsb
+# Get hd1 data...
+ xorw %ax, %ax
+ movw %ax, %ds
+ ldsw (4 * 0x46), %si
+ popw %cx
+ popw %es
+ movw $0x0090, %di
rep
movsb
-
-! Check that there IS a hd1 :-)
-
- mov ax,#0x01500
- mov dl,#0x81
- int 0x13
+# Check that there IS a hd1 :-)
+ movw $0x01500, %ax
+ movb $0x81, %dl
+ int $0x13
jc no_disk1
- cmp ah,#3
+
+ cmpb $3, %ah
je is_disk1
+
no_disk1:
- mov ax,cs ! aka #SETUPSEG
- sub ax,#DELTA_INITSEG ! aka #INITSEG
- mov es,ax
- mov di,#0x0090
- mov cx,#0x10
- xor ax,ax ! clear ax
+ movw %cs, %ax # aka SETUPSEG
+ subw $DELTA_INITSEG, %ax # aka INITSEG
+ movw %ax, %es
+ movw $0x0090, %di
+ movw $0x10, %cx
+ xorw %ax, %ax
cld
rep
stosb
is_disk1:
-
-! check for Micro Channel (MCA) bus
- mov ax,cs ! aka #SETUPSEG
- sub ax,#DELTA_INITSEG ! aka #INITSEG
- mov ds,ax
- mov ds,ax
- xor ax,ax
- mov [0xa0], ax ! set table length to 0
- mov ah, #0xc0
+# check for Micro Channel (MCA) bus
+ movw %cs, %ax # aka SETUPSEG
+ subw $DELTA_INITSEG, %ax # aka INITSEG
+ movw %ax, %ds
+ xorw %ax, %ax
+ movw %ax, 0xa0 # set table length to 0
+ movb $0xc0, %ah
stc
- int 0x15 ! puts feature table at es:bx
- jc no_mca
- push ds
- mov ax,es
- mov ds,ax
- mov ax,cs ! aka #SETUPSEG
- sub ax, #DELTA_INITSEG ! aka #INITSEG
- mov es,ax
- mov si,bx
- mov di,#0xa0
- mov cx,(si)
- add cx,#2 ! table length is a short
- cmp cx,#0x10
- jc sysdesc_ok
- mov cx,#0x10 ! we keep only first 16 bytes
+ int $0x15 # moves feature table to es:bx
+ jc no_mca
+
+ pushw %ds
+ movw %es, %ax
+ movw %ax, %ds
+ movw %cs, %ax # aka SETUPSEG
+ subw $DELTA_INITSEG, %ax # aka INITSEG
+ movw %ax, %es
+ movw %bx, %si
+ movw $0xa0, %di
+ movw (%si), %cx
+ addw $2, %cx # table length is a short
+ cmpw $0x10, %cx
+ jc sysdesc_ok
+
+ movw $0x10, %cx # we keep only first 16 bytes
sysdesc_ok:
rep
movsb
- pop ds
-
+ popw %ds
no_mca:
-
-! Check for PS/2 pointing device
-
- mov ax,cs ! aka #SETUPSEG
- sub ax,#DELTA_INITSEG ! aka #INITSEG
- mov ds,ax
- mov [0x1ff],#0 ! default is no pointing device
- int 0x11 ! int 0x11: equipment determination
- test al,#0x04 ! check if pointing device installed
+# Check for PS/2 pointing device
+ movw %cs, %ax # aka SETUPSEG
+ subw $DELTA_INITSEG, %ax # aka INITSEG
+ movw %ax, %ds
+ movw $0, (0x1ff) # default is no pointing device
+ int $0x11 # int 0x11: equipment list
+ testb $0x04, %al # check if mouse installed
jz no_psmouse
- mov [0x1ff],#0xaa ! device present
+
+ movw $0xAA, (0x1ff) # device present
no_psmouse:
#ifdef CONFIG_APM
-! check for APM BIOS
- ! NOTE: DS is pointing to the boot sector
- !
- mov [64],#0 ! version == 0 means no APM BIOS
-
- mov ax,#0x05300 ! APM BIOS installation check
- xor bx,bx
- int 0x15
- jc done_apm_bios ! error -> no APM BIOS
-
- cmp bx,#0x0504d ! check for "PM" signature
- jne done_apm_bios ! no signature -> no APM BIOS
-
- and cx,#0x02 ! Is 32 bit supported?
- je done_apm_bios ! no ...
-
- mov ax,#0x05304 ! Disconnect first just in case
- xor bx,bx
- int 0x15 ! ignore return code
-
- mov ax,#0x05303 ! 32 bit connect
- xor ebx,ebx
- int 0x15
- jc no_32_apm_bios ! error
-
- mov [66],ax ! BIOS code segment
- mov [68],ebx ! BIOS entry point offset
- mov [72],cx ! BIOS 16 bit code segment
- mov [74],dx ! BIOS data segment
- mov [78],esi ! BIOS code segment length
- mov [82],di ! BIOS data segment length
-!
-! Redo the installation check as the 32 bit connect
-! modifies the flags returned on some BIOSs
-!
- mov ax,#0x05300 ! APM BIOS installation check
- xor bx,bx
- int 0x15
- jc apm_disconnect ! error -> should not happen, tidy up
+# Then check for an APM BIOS...
+ # %ds points to the bootsector
+ movw $0, 0x40 # version = 0 means no APM BIOS
+ movw $0x05300, %ax # APM BIOS installation check
+ xorw %bx, %bx
+ int $0x15
+ jc done_apm_bios # Nope, no APM BIOS
+
+ cmpw $0x0504d, %bx # Check for "PM" signature
+ jne done_apm_bios # No signature, no APM BIOS
+
+ andw $0x02, %cx # Is 32 bit supported?
+ je done_apm_bios # No 32-bit, no (good) APM BIOS
+
+ movw $0x05304, %ax # Disconnect first just in case
+ xorw %bx, %bx
+ int $0x15 # ignore return code
+ movw $0x05303, %ax # 32 bit connect
+ xorw %ebx, %ebx
+ int $0x15
+ jc no_32_apm_bios # Ack, error.
+
+ movw %ax, (66) # BIOS code segment
+ movl %ebx, (68) # BIOS entry point offset
+ movw %cx, (72) # BIOS 16 bit code segment
+ movw %dx, (74) # BIOS data segment
+ movl %esi, (78) # BIOS code segment length
+ movw %di, (82) # BIOS data segment length
+# Redo the installation check as the 32 bit connect
+# modifies the flags returned on some BIOSs
+ movw $0x05300, %ax # APM BIOS installation check
+ xorw %bx, %bx
+ int $0x15
+ jc apm_disconnect # error -> shouldn't happen
- cmp bx,#0x0504d ! check for "PM" signature
- jne apm_disconnect ! no signature -> should not happen, tidy up
+ cmpw $0x0504d, %bx # check for "PM" signature
+ jne apm_disconnect # no sig -> shouldn't happen
- mov [64],ax ! record the APM BIOS version
- mov [76],cx ! and flags
+ movw %ax, (64) # record the APM BIOS version
+ movw %cx, (76) # and flags
jmp done_apm_bios
-apm_disconnect:
- mov ax,#0x05304 ! Disconnect
- xor bx,bx
- int 0x15 ! ignore return code
+apm_disconnect: # Tidy up
+ movw $0x05304, %ax # Disconnect
+ xorw %bx, %bx
+ int $0x15 # ignore return code
+
jmp done_apm_bios
no_32_apm_bios:
- and [76], #0xfffd ! remove 32 bit support bit
-
+ andw $0xfffd, (76) # remove 32 bit support bit
done_apm_bios:
#endif
-! Now we want to move to protected mode ...
-
- seg cs
- cmp realmode_swtch,#0
+# Now we want to move to protected mode ...
+ cmpw $0, %cs:realmode_swtch
jz rmodeswtch_normal
- seg cs
- callf far * realmode_swtch
+
+ call *%cs:realmode_swtch
+
jmp rmodeswtch_end
+
rmodeswtch_normal:
- push cs
+ pushw %cs
call default_switch
-rmodeswtch_end:
-! we get the code32 start address and modify the below 'jmpi'
-! (loader may have changed it)
- seg cs
- mov eax,code32_start
- seg cs
- mov code32,eax
-
-! Now we move the system to its rightful place
-! ...but we check, if we have a big-kernel.
-! in this case we *must* not move it ...
- seg cs
- test byte ptr loadflags,#LOADED_HIGH
- jz do_move0 ! we have a normal low loaded zImage
- ! we have a high loaded big kernel
- jmp end_move ! ... and we skip moving
+rmodeswtch_end:
+# we get the code32 start address and modify the below 'jmpi'
+# (loader may have changed it)
+ movl %cs:code32_start, %eax
+ movl %eax, %cs:code32
+
+# Now we move the system to its rightful place ... but we check if we have a
+# big-kernel. In that case we *must* not move it ...
+ testb $LOADED_HIGH, %cs:loadflags
+ jz do_move0 # .. then we have a normal low
+ # loaded zImage
+ # .. or else we have a high
+ # loaded bzImage
+ jmp end_move # ... and we skip moving
do_move0:
- mov ax,#0x100 ! start of destination segment
- mov bp,cs ! aka #SETUPSEG
- sub bp,#DELTA_INITSEG ! aka #INITSEG
- seg cs
- mov bx,start_sys_seg ! start of source segment
- cld ! 'direction'=0, movs moves forward
+ movw $0x100, %ax # start of destination segment
+ movw %cs, %bp # aka SETUPSEG
+ subw $DELTA_INITSEG, %bp # aka INITSEG
+ movw %cs:start_sys_seg, %bx # start of source segment
+ cld
do_move:
- mov es,ax ! destination segment
- inc ah ! instead of add ax,#0x100
- mov ds,bx ! source segment
- add bx,#0x100
- sub di,di
- sub si,si
- mov cx,#0x400
+ movw %ax, %es # destination segment
+ incb %ah # instead of add ax,#0x100
+ movw %bx, %ds # source segment
+ addw $0x100, %bx
+ subw %di, %di
+ subw %si, %si
+ movw $0x400, %cx
rep
- movsd
- cmp bx,bp ! we assume start_sys_seg > 0x200,
- ! so we will perhaps read one page more then
- ! needed, but never overwrite INITSEG because
- ! destination is minimum one page below source
+ movsl
+ cmpw %bp, %bx # assume start_sys_seg > 0x200,
+ # so we will perhaps read one
+ # page more than needed, but
+ # never overwrite INITSEG
+ # because destination is a
+ # minimum one page below source
jb do_move
-! then we load the segment descriptors
-
end_move:
- mov ax,cs ! aka #SETUPSEG ! right, forgot this at first. didn't work :-)
- mov ds,ax
-
-! If we have our code not at 0x90000, we need to move it there now.
-! We also then need to move the parameters behind it (command line)
-! Because we would overwrite the code on the current IP, we move
-! it in two steps, jumping high after the first one.
- mov ax,cs
- cmp ax,#SETUPSEG
+# then we load the segment descriptors
+ movw %cs, %ax # aka SETUPSEG
+ movw %ax, %ds
+
+# If we have our code not at 0x90000, we need to move it there now.
+# We also then need to move the params behind it (commandline)
+# Because we would overwrite the code on the current IP, we move
+# it in two steps, jumping high after the first one.
+ movw %cs, %ax
+ cmpw $SETUPSEG, %ax
je end_move_self
- cli ! make sure we really have interrupts disabled !
- ! because after this the stack should not be used
- sub ax,#DELTA_INITSEG ! aka #INITSEG
- mov dx,ss
- cmp dx,ax
+
+ cli # make sure we really have
+ # interrupts disabled !
+ # because after this the stack
+ # should not be used
+ subw $DELTA_INITSEG, %ax # aka INITSEG
+ movw %ss, %dx
+ cmpw %ax, %dx
jb move_self_1
- add dx,#INITSEG
- sub dx,ax ! this will be SS after the move
+
+ addw $INITSEG, %dx
+ subw %ax, %dx # this will go into %ss after
+ # the move
move_self_1:
- mov ds,ax
- mov ax,#INITSEG ! real INITSEG
- mov es,ax
- seg cs
- mov cx,setup_move_size
- std ! we have to move up, so we use direction down
- ! because the areas may overlap
- mov di,cx
- dec di
- mov si,di
- sub cx,#move_self_here+0x200
+ movw %ax, %ds
+ movw $INITSEG, %ax # real INITSEG
+ movw %ax, %es
+ movw %cs:setup_move_size, %cx
+ std # we have to move up, so we use
+ # direction down because the
+ # areas may overlap
+ movw %cx, %di
+ decw %di
+ movw %di, %si
+ subw $move_self_here+0x200, %cx
rep
movsb
- jmpi move_self_here,SETUPSEG ! jump to our final place
+ ljmp $SETUPSEG, $move_self_here
+
move_self_here:
- mov cx,#move_self_here+0x200
+ movw $move_self_here+0x200, %cx
rep
movsb
- mov ax,#SETUPSEG
- mov ds,ax
- mov ss,dx
- ! now we are at the right place
-end_move_self:
-
- lidt idt_48 ! load idt with 0,0
- lgdt gdt_48 ! load gdt with whatever appropriate
-
-! that was painless, now we enable A20
+ movw $SETUPSEG, %ax
+ movw %ax, %ds
+ movw %dx, %ss
+end_move_self: # now we are at the right place
+ lidt idt_48 # load idt with 0,0
+ lgdt gdt_48 # load gdt with whatever is
+ # appropriate
+# that was painless, now we enable a20
call empty_8042
- mov al,#0xD1 ! command write
- out #0x64,al
+
+ movb $0xD1, %al # command write
+ outb %al, $0x64
call empty_8042
- mov al,#0xDF ! A20 on
- out #0x60,al
+
+ 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. The memory location used here is the int 0x1f vector,
-! which should be safe to use; any *unused* memory location < 0xfff0
-! should work here.
-
-#define TEST_ADDR 0x7c
-
- push ds
- xor ax,ax ! segment 0x0000
- mov ds,ax
- dec ax ! segment 0xffff (HMA)
- mov gs,ax
- mov bx,[TEST_ADDR] ! we want to restore the value later
+# 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. The memory location used here (0x200) is the int 0x80
+# vector, which should be safe to use.
+ push %ds
+ push %es
+ xorw %ax, %ax # segment 0x0000
+ movw %ax, %fs
+ decw %ax # segment 0xffff (HMA)
+ movw %ax, %gs
a20_wait:
- inc ax
- mov [TEST_ADDR],ax
- seg gs
- cmp ax,[TEST_ADDR+0x10]
- je a20_wait ! loop until no longer aliased
- mov [TEST_ADDR],bx ! restore original value
- pop ds
-
-! make sure any possible coprocessor is properly reset..
-
- xor ax,ax
- out #0xf0,al
- call delay
- out #0xf1,al
+ incw %ax # unused memory location <0xfff0
+ movw %ax, %fs:(0x200) # we use the "int 0x80" vector
+ cmpw %gs:(0x210), %ax # and its corresponding HMA addr
+ je a20_wait # loop until no longer aliased
+
+# make sure any possible coprocessor is properly reset..
+ xorw %ax, %ax
+ outb %al, $0xf0
call delay
-! well, that went ok, I hope. Now we mask all interrupts - the rest
-! is done in init_IRQ().
+ outb %al, $0xf1
+ call delay
- mov al,#0xFF ! mask off all interrupts for now
- out #0xA1,al
+# well, that went ok, I hope. Now we mask all interrupts - the rest
+# is done in init_IRQ().
+ movb $0xFF, %al # mask all interrupts for now
+ outb %al, $0xA1
call delay
- mov al,#0xFB ! mask all irq's but irq2 which
- out #0x21,al ! is cascaded
+
+ movb $0xFB, %al # mask all irq's but irq2 which
+ outb %al, $0x21 # is cascaded
-! Well, that certainly wasn't fun :-(. Hopefully it works, and we don't
-! need no steenking BIOS anyway (except for the initial loading :-).
-! The BIOS routine wants lots of unnecessary data, and it's less
-! "interesting" anyway. This is how REAL programmers do it.
-!
-! Well, now's the time to actually move into protected mode. To make
-! things as simple as possible, we do no register set-up or anything,
-! we let the GNU-compiled 32-bit programs do that. We just jump to
-! absolute address 0x1000 (or the loader supplied one),
-! in 32-bit protected mode.
-!
-! Note that the short jump isn't strictly needed, although there are
-! reasons why it might be a good idea. It won't hurt in any case.
-!
- mov ax,#1 ! protected mode (PE) bit
- lmsw ax ! This is it!
+# Well, that certainly wasn't fun :-(. Hopefully it works, and we don't
+# need no steenking BIOS anyway (except for the initial loading :-).
+# The BIOS-routine wants lots of unnecessary data, and it's less
+# "interesting" anyway. This is how REAL programmers do it.
+#
+# Well, now's the time to actually move into protected mode. To make
+# things as simple as possible, we do no register set-up or anything,
+# we let the gnu-compiled 32-bit programs do that. We just jump to
+# absolute address 0x1000 (or the loader supplied one),
+# in 32-bit protected mode.
+#
+# Note that the short jump isn't strictly needed, although there are
+# reasons why it might be a good idea. It won't hurt in any case.
+ movw $1, %ax # protected mode (PE) bit
+ lmsw %ax # This is it!
jmp flush_instr
-flush_instr:
- xor bx,bx ! Flag to indicate a boot
-! NOTE: For high loaded big kernels we need a
-! jmpi 0x100000,__KERNEL_CS
-!
-! but we yet haven't reloaded the CS register, so the default size
-! of the target offset still is 16 bit.
-! However, using an operant prefix (0x66), the CPU will properly
-! take our 48 bit far pointer. (INTeL 80386 Programmer's Reference
-! Manual, Mixing 16-bit and 32-bit code, page 16-6)
- db 0x66,0xea ! prefix + jmpi-opcode
-code32: dd 0x1000 ! will be set to 0x100000 for big kernels
- dw __KERNEL_CS
+flush_instr:
+ xorw %bx, %bx # Flag to indicate a boot
+# NOTE: For high loaded big kernels we need a
+# jmpi 0x100000,__KERNEL_CS
+#
+# but we yet haven't reloaded the CS register, so the default size
+# of the target offset still is 16 bit.
+# However, using an operant prefix (0x66), the CPU will properly
+# take our 48 bit far pointer. (INTeL 80386 Programmer's Reference
+# Manual, Mixing 16-bit and 32-bit code, page 16-6)
+
+ .byte 0x66, 0xea # prefix + jmpi-opcode
+code32: .long 0x1000 # will be set to 0x100000
+ # for big kernels
+ .word __KERNEL_CS
+# Here's a bunch of information about your current kernel..
kernel_version: .ascii UTS_RELEASE
.ascii " ("
.ascii LINUX_COMPILE_BY
@@ -690,191 +682,184 @@
.ascii LINUX_COMPILE_HOST
.ascii ") "
.ascii UTS_VERSION
- db 0
-
-! This is the default real mode switch routine.
-! to be called just before protected mode transition
+ .byte 0
+# This is the default real mode switch routine.
+# to be called just before protected mode transition
default_switch:
- cli ! no interrupts allowed !
- mov al,#0x80 ! disable NMI for the bootup sequence
- out #0x70,al
- retf
-
-! This routine only gets called, if we get loaded by the simple
-! bootsect loader _and_ have a bzImage to load.
-! Because there is no place left in the 512 bytes of the boot sector,
-! we must emigrate to code space here.
-!
+ cli # no interrupts allowed !
+ movb $0x80, %al # disable NMI for bootup
+ # sequence
+ outb %al, $0x70
+ lret
+
+# This routine only gets called, if we get loaded by the simple
+# bootsect loader _and_ have a bzImage to load.
+# Because there is no place left in the 512 bytes of the boot sector,
+# we must emigrate to code space here.
bootsect_helper:
- seg cs
- cmp word ptr bootsect_es,#0
+ cmpw $0, %cs:bootsect_es
jnz bootsect_second
- seg cs
- mov byte ptr type_of_loader,#0x20
- mov ax,es
- shr ax,#4
- seg cs
- mov byte ptr bootsect_src_base+2,ah
- mov ax,es
- seg cs
- mov bootsect_es,ax
- sub ax,#SYSSEG
- retf ! nothing else to do for now
+
+ movb $0x20, %cs:type_of_loader
+ movw %es, %ax
+ shrw $4, %ax
+ movb %ah, %cs:bootsect_src_base+2
+ movw %es, %ax
+ movw %ax, %cs:bootsect_es
+ subw $SYSSEG, %ax
+ lret # nothing else to do for now
+
bootsect_second:
- push cx
- push si
- push bx
- test bx,bx ! 64K full ?
+ pushw %cx
+ pushw %si
+ pushw %bx
+ testw %bx, %bx # 64K full?
jne bootsect_ex
- mov cx,#0x8000 ! full 64K move, INT15 moves words
- push cs
- pop es
- mov si,#bootsect_gdt
- mov ax,#0x8700
- int 0x15
- jc bootsect_panic ! this, if INT15 fails
- seg cs
- mov es,bootsect_es ! we reset es to always point to 0x10000
- seg cs
- inc byte ptr bootsect_dst_base+2
+
+ movw $0x8000, %cx # full 64K, INT15 moves words
+ pushw %cs
+ popw %es
+ movw $bootsect_gdt, %si
+ movw $0x8700, %ax
+ int $0x15
+ jc bootsect_panic # this, if INT15 fails
+
+ movw %cs:bootsect_es, %es # we reset %es to always point
+ incb %cs:bootsect_dst_base+2 # to 0x10000
bootsect_ex:
- seg cs
- mov ah, byte ptr bootsect_dst_base+2
- shl ah,4 ! we now have the number of moved frames in ax
- xor al,al
- pop bx
- pop si
- pop cx
- retf
+ movb %cs:bootsect_dst_base+2, %ah
+ shlb $4, %ah # we now have the number of
+ # moved frames in %ax
+ xorb %al, %al
+ popw %bx
+ popw %si
+ popw %cx
+ lret
bootsect_gdt:
- .word 0,0,0,0
- .word 0,0,0,0
+ .word 0, 0, 0, 0
+ .word 0, 0, 0, 0
+
bootsect_src:
.word 0xffff
+
bootsect_src_base:
- .byte 0,0,1 ! base = 0x010000
- .byte 0x93 ! typbyte
- .word 0 ! limit16,base24 =0
+ .byte 0x00, 0x00, 0x01 # base = 0x010000
+ .byte 0x93 # typbyte
+ .word 0 # limit16,base24 =0
+
bootsect_dst:
.word 0xffff
+
bootsect_dst_base:
- .byte 0,0,0x10 ! base = 0x100000
- .byte 0x93 ! typbyte
- .word 0 ! limit16,base24 =0
- .word 0,0,0,0 ! BIOS CS
- .word 0,0,0,0 ! BIOS DS
+ .byte 0x00, 0x00, 0x10 # base = 0x100000
+ .byte 0x93 # typbyte
+ .word 0 # limit16,base24 =0
+ .word 0, 0, 0, 0 # BIOS CS
+ .word 0, 0, 0, 0 # BIOS DS
+
bootsect_es:
.word 0
bootsect_panic:
- push cs
- pop ds
+ pushw %cs
+ popw %ds
cld
- lea si,bootsect_panic_mess
+ leaw bootsect_panic_mess, %si
call prtstr
+
bootsect_panic_loop:
jmp bootsect_panic_loop
+
bootsect_panic_mess:
- .ascii "INT15 refuses to access high memory. Giving up."
- db 0
+ .string "INT15 refuses to access high mem, giving up."
-! 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...
+# 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...
empty_8042:
- push ecx
- mov ecx,#0xFFFFFF
+ pushl %ecx
+ movl $0xFFFFFF, %ecx
empty_8042_loop:
- dec ecx
- jz empty_8042_end_loop
+ decl %ecx
+ jz empty_8042_end_loop
call delay
- in al,#0x64 ! 8042 status port
- test al,#1 ! output buffer?
+
+ inb $0x64, %al # 8042 status port
+ testb $1, %al # output buffer?
jz no_output
+
call delay
- in al,#0x60 ! read it
+ inb $0x60, %al # read it
jmp empty_8042_loop
+
no_output:
- test al,#2 ! is input buffer full?
- jnz empty_8042_loop ! yes - loop
+ testb $2, %al # is input buffer full?
+ jnz empty_8042_loop # yes - loop
empty_8042_end_loop:
- pop ecx
+ popl %ecx
ret
-!
-! Read the CMOS clock. Return the seconds in al
-!
+# Read the cmos clock. Return the seconds in al
gettime:
- push cx
- mov ah,#0x02
- int 0x1a
- mov al,dh ! dh contains the seconds
- and al,#0x0f
- mov ah,dh
- mov cl,#0x04
- shr ah,cl
+ pushw %cx
+ movb $0x02, %ah
+ int $0x1a
+ movb %dh, %al # %dh contains the seconds
+ andb $0x0f, %al
+ movb %dh, %ah
+ movb $0x04, %cl
+ shrb %cl, %ah
aad
- pop cx
+ popw %cx
ret
-!
-! Delay is needed after doing I/O
-!
+# Delay is needed after doing I/O
delay:
- .word 0x00eb ! jmp $+2
+ jmp .+2 # jmp $+2
ret
-!
-! Descriptor tables
-!
-
+# Descriptor tables
gdt:
- .word 0,0,0,0 ! dummy
-
- .word 0,0,0,0 ! unused
-
- .word 0xFFFF ! 4Gb - (0x100000*0x1000 = 4Gb)
- .word 0x0000 ! base address=0
- .word 0x9A00 ! code read/exec
- .word 0x00CF ! granularity=4096, 386 (+5th nibble of limit)
-
- .word 0xFFFF ! 4Gb - (0x100000*0x1000 = 4Gb)
- .word 0x0000 ! base address=0
- .word 0x9200 ! data read/write
- .word 0x00CF ! granularity=4096, 386 (+5th nibble of limit)
+ .word 0, 0, 0, 0 # dummy
+ .word 0, 0, 0, 0 # unused
+ .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)
idt_48:
- .word 0 ! idt limit=0
- .word 0,0 ! idt base=0L
-
+ .word 0 # idt limit = 0
+ .word 0, 0 # idt base = 0L
gdt_48:
- .word 0x800 ! gdt limit=2048, 256 GDT entries
- .word 512+gdt,0x9 ! gdt base = 0X9xxxx
+ .word 0x8000 # gdt limit=2048,
+ # 256 GDT entries
-!
-! Include video setup & detection code
-!
+ .word 512+gdt, 0x9 # gdt base = 0X9xxxx
-#include "video.S"
+# Include video setup & detection code
-!
-! Setup signature -- must be last
-!
+#include "video.S"
+# Setup signature -- must be last
setup_sig1: .word SIG1
setup_sig2: .word SIG2
-!
-! After this point, there is some free space which is used by the video mode
-! handling code to store the temporary mode table (not used by the kernel).
-!
+# After this point, there is some free space which is used by the video mode
+# handling code to store the temporary mode table (not used by the kernel).
modelist:
FUNET's LINUX-ADM group, linux-adm@nic.funet.fi
TCL-scripts by Sam Shen (who was at: slshen@lbl.gov)