Home | History | Annotate | Download | only in BootSector
      1 #------------------------------------------------------------------------------
      2 #*
      3 #*   Copyright (c) 2006 - 2011, Intel Corporation. All rights reserved.<BR>
      4 #*   This program and the accompanying materials
      5 #*   are licensed and made available under the terms and conditions of the BSD License
      6 #*   which accompanies this distribution.  The full text of the license may be found at
      7 #*   http://opensource.org/licenses/bsd-license.php
      8 #*
      9 #*   THE PROGRAM IS DISTRIBUTED UNDER THE BSD LICENSE ON AN "AS IS" BASIS,
     10 #*   WITHOUT WARRANTIES OR REPRESENTATIONS OF ANY KIND, EITHER EXPRESS OR IMPLIED.
     11 #*
     12 #*    start.S
     13 #*
     14 #*   Abstract:
     15 #*
     16 #------------------------------------------------------------------------------
     17 
     18         .stack:
     19         .486p:
     20         .code16
     21 
     22 .equ                        FAT_DIRECTORY_ENTRY_SIZE, 0x020
     23 .equ                        FAT_DIRECTORY_ENTRY_SHIFT, 5
     24 .equ                        BLOCK_SIZE, 0x0200
     25 .equ                        BLOCK_MASK, 0x01ff
     26 .equ                        BLOCK_SHIFT, 9
     27 
     28        .org 0x0
     29 
     30 .global _start
     31 _start:
     32 
     33 Ia32Jump:
     34   jmp   BootSectorEntryPoint  # JMP inst    - 3 bytes
     35   nop
     36 
     37 OemId:              .ascii   "INTEL   "       # OemId               - 8 bytes
     38 
     39 SectorSize:         .word  0                  # Sector Size         - 16 bits
     40 SectorsPerCluster:  .byte  0                  # Sector Per Cluster  - 8 bits
     41 ReservedSectors:    .word  0                  # Reserved Sectors    - 16 bits
     42 NoFats:             .byte  0                  # Number of FATs      - 8 bits
     43 RootEntries:        .word  0                  # Root Entries        - 16 bits
     44 Sectors:            .word  0                  # Number of Sectors   - 16 bits
     45 Media:              .byte  0                  # Media               - 8 bits  - ignored
     46 SectorsPerFat:      .word  0                  # Sectors Per FAT     - 16 bits
     47 SectorsPerTrack:    .word  0                  # Sectors Per Track   - 16 bits - ignored
     48 Heads:              .word  0                  # Heads               - 16 bits - ignored
     49 HiddenSectors:      .long  0                  # Hidden Sectors      - 32 bits - ignored
     50 LargeSectors:       .long  0                  # Large Sectors       - 32 bits
     51 PhysicalDrive:      .byte  0                  # PhysicalDriveNumber - 8 bits  - ignored
     52 CurrentHead:        .byte  0                  # Current Head        - 8 bits
     53 Signature:          .byte  0                  # Signature           - 8 bits  - ignored
     54 VolId:              .ascii "    "             # Volume Serial Number- 4 bytes
     55 FatLabel:           .ascii "           "      # Label               - 11 bytes
     56 SystemId:           .ascii "FAT12   "         # SystemId            - 8 bytes
     57 
     58 BootSectorEntryPoint:
     59         #ASSUME ds:@code
     60         #ASSUME ss:@code
     61       # ds = 1000, es = 2000 + x (size of first cluster >> 4)
     62       # cx = Start Cluster of EfiLdr
     63       # dx = Start Cluster of Efivar.bin
     64 
     65 # Re use the BPB data stored in Boot Sector
     66         movw    $0x7c00, %bp
     67 
     68         pushw   %cx
     69 # Read Efivar.bin
     70 #       1000:dx    = DirectoryEntry of Efivar.bin -> BS.com has filled already
     71         movw    $0x1900, %ax
     72         movw    %ax, %es
     73         testw   %dx, %dx
     74         jnz     CheckVarStoreSize
     75 
     76         movb    $1, %al
     77 NoVarStore:
     78         pushw   %es
     79 # Set the 5th byte start @ 0:19000 to non-zero indicating we should init var store header in DxeIpl
     80         movb    %al, %es:(4)
     81         jmp     SaveVolumeId
     82 
     83 CheckVarStoreSize:
     84         movw    %dx, %di
     85         cmpl    $0x4000, %ds:2(%di)
     86         movb    $2, %al
     87         jne     NoVarStore
     88 
     89 LoadVarStore:
     90         movb    $0, %al
     91         movb    %al, %es:(4)
     92         movw    (%di), %cx
     93 #       ES:DI = 1500:0
     94         xorw    %di, %di
     95         pushw   %es
     96         movw    $0x1500, %ax
     97         movw    %ax, %es
     98         call    ReadFile
     99 SaveVolumeId:
    100         popw    %es
    101         movw    VolId(%bp), %ax
    102         movw    %ax, %es:(0)                    # Save Volume Id to 0:19000. we will find the correct volume according to this VolumeId
    103         movw    VolId+2(%bp), %ax
    104         movw    %ax, %es:(2)
    105 
    106 # Read Efildr
    107         popw    %cx
    108 #       cx    = Start Cluster of Efildr -> BS.com has filled already
    109 #       ES:DI = 2000:0, first cluster will be read again
    110         xorw    %di, %di                            # di = 0
    111         movw    $0x2000, %ax
    112         movw    %ax, %es
    113         call    ReadFile
    114         movw    %cs, %ax
    115         movw    %ax, %cs:JumpSegment
    116 
    117 JumpFarInstruction:
    118         .byte   0xea
    119 JumpOffset:
    120         .word   0x200
    121 JumpSegment:
    122         .word   0x2000
    123 
    124 
    125 
    126 # ****************************************************************************
    127 # ReadFile
    128 #
    129 # Arguments:
    130 #   CX    = Start Cluster of File
    131 #   ES:DI = Buffer to store file content read from disk
    132 #
    133 # Return:
    134 #   (ES << 4 + DI) = end of file content Buffer
    135 #
    136 # ****************************************************************************
    137 ReadFile:
    138 # si      = NumberOfClusters
    139 # cx      = ClusterNumber
    140 # dx      = CachedFatSectorNumber
    141 # ds:0000 = CacheFatSectorBuffer
    142 # es:di   = Buffer to load file
    143 # bx      = NextClusterNumber
    144         pusha
    145         movw    $1, %si                             # NumberOfClusters = 1
    146         pushw   %cx                                 # Push Start Cluster onto stack
    147         movw    $0xfff, %dx                         # CachedFatSectorNumber = 0xfff
    148 FatChainLoop:
    149         movw    %cx, %ax                            # ax = ClusterNumber
    150         andw    $0xff8, %ax                         # ax = ax & 0xff8
    151         cmpw    $0xff8, %ax                         # See if this is the last cluster
    152         je      FoundLastCluster                    # Jump if last cluster found
    153         movw    %cx, %ax                            # ax = ClusterNumber
    154         shlw    %ax                                 # ax = ClusterNumber * 2
    155         addw    %cx, %ax                            # ax = ClusterNumber * 2 + ClusterNumber = ClusterNumber * 3
    156         shrw    %ax                                 # FatOffset = ClusterNumber*3 / 2
    157         pushw   %si                                 # Save si
    158         movw    %ax, %si                            # si = FatOffset
    159         shrw    $BLOCK_SHIFT, %ax                   # ax = FatOffset >> BLOCK_SHIFT
    160         addw    ReservedSectors(%bp), %ax           # ax = FatSectorNumber = ReservedSectors + (FatOffset >> BLOCK_OFFSET)
    161         andw    $BLOCK_MASK,%si                     # si = FatOffset & BLOCK_MASK
    162         cmpw    %dx, %ax                            # Compare FatSectorNumber to CachedFatSectorNumber
    163         je      SkipFatRead
    164         movw    $2, %bx
    165         pushw   %es
    166         pushw   %ds
    167         popw    %es
    168         call    ReadBlocks                          # Read 2 blocks starting at AX storing at ES:DI
    169         popw    %es
    170         movw    %ax, %dx                            # CachedFatSectorNumber = FatSectorNumber
    171 SkipFatRead:
    172         movw    (%si), %bx                          # bx = NextClusterNumber
    173         movw    %cx, %ax                            # ax = ClusterNumber
    174         andw    $1, %ax                             # See if this is an odd cluster number
    175         je      EvenFatEntry
    176         shrw    $4, %bx                             # NextClusterNumber = NextClusterNumber >> 4
    177 EvenFatEntry:
    178         andw    $0xfff, %bx                         # Strip upper 4 bits of NextClusterNumber
    179         popw    %si                                 # Restore si
    180         decw    %bx                                 # bx = NextClusterNumber - 1
    181         cmpw    %cx, %bx                            # See if (NextClusterNumber-1)==ClusterNumber
    182         jne     ReadClusters
    183         incw    %bx                                 # bx = NextClusterNumber
    184         incw    %si                                 # NumberOfClusters++
    185         movw    %bx, %cx                            # ClusterNumber = NextClusterNumber
    186         jmp     FatChainLoop
    187 ReadClusters:
    188         incw    %bx
    189         popw    %ax                                 # ax = StartCluster
    190         pushw   %bx                                 # StartCluster = NextClusterNumber
    191         movw    %bx, %cx                            # ClusterNumber = NextClusterNumber
    192         subw    $2, %ax                             # ax = StartCluster - 2
    193         xorb    %bh, %bh
    194         movb    SectorsPerCluster(%bp), %bl         # bx = SectorsPerCluster
    195         mulw    %bx                                 # ax = (StartCluster - 2) * SectorsPerCluster
    196         addw    (%bp), %ax                          # ax = FirstClusterLBA + (StartCluster-2)*SectorsPerCluster
    197         pushw   %ax                                 # save start sector
    198         movw    %si, %ax                            # ax = NumberOfClusters
    199         mulw    %bx                                 # ax = NumberOfClusters * SectorsPerCluster
    200         movw    %ax, %bx                            # bx = Number of Sectors
    201         popw    %ax                                 # ax = Start Sector
    202         call    ReadBlocks
    203         movw    $1, %si                             # NumberOfClusters = 1
    204         jmp     FatChainLoop
    205 FoundLastCluster:
    206         popw    %cx
    207         popa
    208         ret
    209 
    210 
    211 # ****************************************************************************
    212 # ReadBlocks - Reads a set of blocks from a block device
    213 #
    214 # AX    = Start LBA
    215 # BX    = Number of Blocks to Read
    216 # ES:DI = Buffer to store sectors read from disk
    217 # ****************************************************************************
    218 
    219 # cx = Blocks
    220 # bx = NumberOfBlocks
    221 # si = StartLBA
    222 
    223 ReadBlocks:
    224         pusha
    225         addl    LBAOffsetForBootSector(%bp), %eax   # Add LBAOffsetForBootSector to Start LBA
    226         addl    HiddenSectors(%bp), %eax            # Add HiddenSectors to Start LBA
    227         movl    %eax, %esi                          # esi = Start LBA
    228         movw    %bx, %cx                            # cx = Number of blocks to read
    229 ReadCylinderLoop:
    230         movw    $0x7bfc, %bp                        # bp = 0x7bfc
    231         movl    %esi, %eax                          # eax = Start LBA
    232         xorl    %edx, %edx                          # edx = 0
    233         movzwl  (%bp), %ebx                         # bx = MaxSector
    234         divl    %ebx                                # ax = StartLBA / MaxSector
    235         incw    %dx                                 # dx = (StartLBA % MaxSector) + 1
    236 
    237         movw    (%bp), %bx                          # bx = MaxSector
    238         subw    %dx, %bx                            # bx = MaxSector - Sector
    239         incw    %bx                                 # bx = MaxSector - Sector + 1
    240         cmpw    %bx, %cx                            # Compare (Blocks) to (MaxSector - Sector + 1)
    241         jg      LimitTransfer
    242         movw    %cx, %bx                            # bx = Blocks
    243 LimitTransfer:
    244         pushw   %ax                                 # save ax
    245         movw    %es, %ax                            # ax = es
    246         shrw    $(BLOCK_SHIFT-4), %ax               # ax = Number of blocks into mem system
    247         andw    $0x7f, %ax                          # ax = Number of blocks into current seg
    248         addw    %bx, %ax                            # ax = End Block number of transfer
    249         cmpw    $0x80, %ax                          # See if it crosses a 64K boundry
    250         jle     NotCrossing64KBoundry               # Branch if not crossing 64K boundry
    251         subw    $0x80, %ax                          # ax = Number of blocks past 64K boundry
    252         subw    %ax, %bx                            # Decrease transfer size by block overage
    253 NotCrossing64KBoundry:
    254         popw    %ax                                 # restore ax
    255 
    256         pushw   %cx
    257         movb    %dl, %cl                            # cl = (StartLBA % MaxSector) + 1 = Sector
    258         xorw    %dx, %dx                            # dx = 0
    259         divw    2(%bp)                              # ax = ax / (MaxHead + 1) = Cylinder
    260                                                     # dx = ax % (MaxHead + 1) = Head
    261 
    262         pushw   %bx                                 # Save number of blocks to transfer
    263         movb    %dl, %dh                            # dh = Head
    264         movw    $0x7c00, %bp                        # bp = 0x7c00
    265         movb    PhysicalDrive(%bp), %dl             # dl = Drive Number
    266         movb    %al, %ch                            # ch = Cylinder
    267         movb    %bl, %al                            # al = Blocks
    268         movb    $2, %ah                             # ah = Function 2
    269         movw    %di, %bx                            # es:bx = Buffer address
    270         int     $0x13
    271         jc      DiskError
    272         popw    %bx
    273         popw    %cx
    274         movzwl  %bx, %ebx
    275         addl    %ebx, %esi                          # StartLBA = StartLBA + NumberOfBlocks
    276         subw    %bx, %cx                            # Blocks = Blocks - NumberOfBlocks
    277         movw    %es, %ax
    278         shlw    $(BLOCK_SHIFT-4), %bx
    279         addw    %bx, %ax
    280         movw    %ax, %es                            # es:di = es:di + NumberOfBlocks*BLOCK_SIZE
    281         cmpw    $0, %cx
    282         jne     ReadCylinderLoop
    283         popa
    284         ret
    285 
    286 DiskError:
    287         pushw %cs
    288         popw %ds
    289         leaw ErrorString, %si
    290         movw $7, %cx
    291         jmp  PrintStringAndHalt
    292 
    293 PrintStringAndHalt:
    294         movw $0xb800, %ax
    295         movw %ax, %es
    296         movw $160, %di
    297         rep
    298         movsw
    299 Halt:
    300         jmp   Halt
    301 
    302 ErrorString:
    303         .byte 'S', 0x0c, 'E', 0x0c, 'r', 0x0c, 'r', 0x0c, 'o', 0x0c, 'r', 0x0c, '!',0x0c
    304 
    305         .org     0x01fa
    306 LBAOffsetForBootSector:
    307         .long   0x0
    308 
    309         .org    0x01fe
    310         .word   0xaa55
    311 
    312 #******************************************************************************
    313 #******************************************************************************
    314 #******************************************************************************
    315 
    316 .equ                 DELAY_PORT, 0x0ed           # Port to use for 1uS delay
    317 .equ                 KBD_CONTROL_PORT, 0x060     # 8042 control port
    318 .equ                 KBD_STATUS_PORT, 0x064      # 8042 status port
    319 .equ                 WRITE_DATA_PORT_CMD, 0x0d1  # 8042 command to write the data port
    320 .equ                 ENABLE_A20_CMD, 0x0df       # 8042 command to enable A20
    321 
    322         .org     0x200
    323         jmp start
    324 Em64String:
    325         .byte 'E', 0x0c, 'm', 0x0c, '6', 0x0c, '4', 0x0c, 'T', 0x0c, ' ', 0x0c, 'U', 0x0c, 'n', 0x0c, 's', 0x0c, 'u', 0x0c, 'p', 0x0c, 'p', 0x0c, 'o', 0x0c, 'r', 0x0c, 't', 0x0c, 'e', 0x0c, 'd', 0x0c, '!', 0x0c
    326 
    327 start:
    328         movw %cs, %ax
    329         movw %ax, %ds
    330         movw %ax, %es
    331         movw %ax, %ss
    332         movw $MyStack, %sp
    333 
    334 #        mov ax,0b800h
    335 #        mov es,ax
    336 #        mov byte ptr es:[160],'a'
    337 #        mov ax,cs
    338 #        mov es,ax
    339 
    340         movl $0, %ebx
    341         leal MemoryMap, %edi
    342 MemMapLoop:
    343         movl $0xe820, %eax
    344         movl $20, %ecx
    345         movl $0x534d4150, %edx  # SMAP
    346         int $0x15
    347         jc  MemMapDone
    348         addl $20, %edi
    349         cmpl $0, %ebx
    350         je  MemMapDone
    351         jmp MemMapLoop
    352 MemMapDone:
    353         leal MemoryMap, %eax
    354         subl %eax, %edi                     # Get the address of the memory map
    355         movl %edi, MemoryMapSize            # Save the size of the memory map
    356 
    357         xorl    %ebx, %ebx
    358         movw    %cs, %bx                    # BX=segment
    359         shll    $4, %ebx                    # BX="linear" address of segment base
    360         leal    GDT_BASE(%ebx), %eax        # EAX=PHYSICAL address of gdt
    361         movl    %eax, (gdtr + 2)            # Put address of gdt into the gdtr
    362         leal    IDT_BASE(%ebx), %eax        # EAX=PHYSICAL address of idt
    363         movl    %eax, (idtr + 2)            # Put address of idt into the idtr
    364         leal    MemoryMapSize(%ebx), %edx   # Physical base address of the memory map
    365 
    366         addl $0x1000, %ebx                  # Source of EFI32
    367         movl %ebx, JUMP+2
    368         addl $0x1000, %ebx
    369         movl %ebx, %esi                     # Source of EFILDR32
    370 
    371 #        mov ax,0b800h
    372 #        mov es,ax
    373 #        mov byte ptr es:[162],'b'
    374 #        mov ax,cs
    375 #        mov es,ax
    376 
    377 #
    378 # Enable A20 Gate
    379 #
    380 
    381         movw $0x2401, %ax                   # Enable A20 Gate
    382         int $0x15
    383         jnc A20GateEnabled                  # Jump if it suceeded
    384 
    385 #
    386 # If INT 15 Function 2401 is not supported, then attempt to Enable A20 manually.
    387 #
    388 
    389         call    Empty8042InputBuffer        # Empty the Input Buffer on the 8042 controller
    390         jnz     Timeout8042                 # Jump if the 8042 timed out
    391         outw    %ax, $DELAY_PORT            # Delay 1 uS
    392         mov     $WRITE_DATA_PORT_CMD, %al   # 8042 cmd to write output port
    393         out     %al, $KBD_STATUS_PORT       # Send command to the 8042
    394         call    Empty8042InputBuffer        # Empty the Input Buffer on the 8042 controller
    395         jnz     Timeout8042                 # Jump if the 8042 timed out
    396         mov     $ENABLE_A20_CMD, %al        # gate address bit 20 on
    397         out     %al, $KBD_CONTROL_PORT      # Send command to thre 8042
    398         call    Empty8042InputBuffer        # Empty the Input Buffer on the 8042 controller
    399         movw    $25, %cx                    # Delay 25 uS for the command to complete on the 8042
    400 Delay25uS:
    401         outw    %ax, $DELAY_PORT            # Delay 1 uS
    402         loop    Delay25uS
    403 Timeout8042:
    404 
    405 
    406 A20GateEnabled:
    407         movw    $0x0008, %bx                # Flat data descriptor
    408 
    409 #
    410 # DISABLE INTERRUPTS - Entering Protected Mode
    411 #
    412 
    413         cli
    414 
    415 #        mov ax,0b800h
    416 #        mov es,ax
    417 #        mov byte ptr es:[164],'c'
    418 #        mov ax,cs
    419 #        mov es,ax
    420 
    421         .byte   0x66
    422         lgdt    gdtr
    423         .byte   0x66
    424         lidt    idtr
    425 
    426         movl    %cr0, %eax
    427         orb     $1, %al
    428         movl    %eax, %cr0
    429 JUMP:
    430 # jmp far 0010:00020000
    431         .byte 0x66
    432         .byte 0xea
    433         .long 0x00020000
    434         .word 0x0010
    435 
    436 Empty8042InputBuffer:
    437         movw $0, %cx
    438 Empty8042Loop:
    439         outw    %ax, $DELAY_PORT            # Delay 1us
    440         in      $KBD_STATUS_PORT, %al       # Read the 8042 Status Port
    441         andb    $0x2, %al                   # Check the Input Buffer Full Flag
    442         loopnz  Empty8042Loop               # Loop until the input buffer is empty or a timout of 65536 uS
    443         ret
    444 
    445 ##############################################################################
    446 # data
    447 ##############################################################################
    448 
    449         .p2align 1
    450 
    451         gdtr:    .long  GDT_END - GDT_BASE - 1  # GDT limit
    452         .long 0                                 # (GDT base gets set above)
    453 ##############################################################################
    454 #   global descriptor table (GDT)
    455 ##############################################################################
    456 
    457         .p2align 1
    458 
    459 GDT_BASE:
    460 # null descriptor
    461 .equ                NULL_SEL, .-GDT_BASE
    462         .word 0         # limit 15:0
    463         .word 0         # base 15:0
    464         .byte 0         # base 23:16
    465         .byte 0         # type
    466         .byte 0         # limit 19:16, flags
    467         .byte 0         # base 31:24
    468 
    469 # linear data segment descriptor
    470 .equ            LINEAR_SEL, .-GDT_BASE
    471         .word 0xFFFF    # limit 0xFFFFF
    472         .word 0         # base 0
    473         .byte 0
    474         .byte 0x92      # present, ring 0, data, expand-up, writable
    475         .byte 0xCF              # page-granular, 32-bit
    476         .byte 0
    477 
    478 # linear code segment descriptor
    479 .equ            LINEAR_CODE_SEL, .-GDT_BASE
    480         .word 0xFFFF    # limit 0xFFFFF
    481         .word 0         # base 0
    482         .byte 0
    483         .byte 0x9A      # present, ring 0, data, expand-up, writable
    484         .byte 0xCF              # page-granular, 32-bit
    485         .byte 0
    486 
    487 # system data segment descriptor
    488 .equ            SYS_DATA_SEL, .-GDT_BASE
    489         .word 0xFFFF    # limit 0xFFFFF
    490         .word 0         # base 0
    491         .byte 0
    492         .byte 0x92      # present, ring 0, data, expand-up, writable
    493         .byte 0xCF              # page-granular, 32-bit
    494         .byte 0
    495 
    496 # system code segment descriptor
    497 .equ            SYS_CODE_SEL, .-GDT_BASE
    498         .word 0xFFFF    # limit 0xFFFFF
    499         .word 0         # base 0
    500         .byte 0
    501         .byte 0x9A      # present, ring 0, data, expand-up, writable
    502         .byte 0xCF              # page-granular, 32-bit
    503         .byte 0
    504 
    505 # spare segment descriptor
    506 .equ        SPARE3_SEL, .-GDT_BASE
    507         .word 0         # limit 0xFFFFF
    508         .word 0         # base 0
    509         .byte 0
    510         .byte 0         # present, ring 0, data, expand-up, writable
    511         .byte 0         # page-granular, 32-bit
    512         .byte 0
    513 
    514 # spare segment descriptor
    515 .equ        SPARE4_SEL, .-GDT_BASE
    516         .word 0         # limit 0xFFFFF
    517         .word 0         # base 0
    518         .byte 0
    519         .byte 0         # present, ring 0, data, expand-up, writable
    520         .byte 0         # page-granular, 32-bit
    521         .byte 0
    522 
    523 # spare segment descriptor
    524 .equ        SPARE5_SEL, .-GDT_BASE
    525         .word 0         # limit 0xFFFFF
    526         .word 0         # base 0
    527         .byte 0
    528         .byte 0         # present, ring 0, data, expand-up, writable
    529         .byte 0         # page-granular, 32-bit
    530         .byte 0
    531 
    532 GDT_END:
    533 
    534         .p2align 1
    535 
    536 
    537 
    538 idtr:  .long  IDT_END - IDT_BASE - 1 # IDT limit
    539         .long 0                      # (IDT base gets set above)
    540 ##############################################################################
    541 #   interrupt descriptor table (IDT)
    542 #
    543 #   Note: The hardware IRQ's specified in this table are the normal PC/AT IRQ
    544 #       mappings.  This implementation only uses the system timer and all other
    545 #       IRQs will remain masked.  The descriptors for vectors 33+ are provided
    546 #       for convenience.
    547 ##############################################################################
    548 
    549 #idt_tag db "IDT",0
    550         .p2align 1
    551 
    552 IDT_BASE:
    553 # divide by zero (INT 0)
    554 .equ                DIV_ZERO_SEL, .-IDT_BASE
    555         .word 0            # offset 15:0
    556         .long SYS_CODE_SEL # selector 15:0
    557         .byte 0            # 0 for interrupt gate
    558         .byte 0x0e | 0x80  # type = 386 interrupt gate, present
    559         .word 0            # offset 31:16
    560 
    561 # debug exception (INT 1)
    562 .equ                DEBUG_EXCEPT_SEL, .-IDT_BASE
    563         .word 0            # offset 15:0
    564         .long SYS_CODE_SEL # selector 15:0
    565         .byte 0            # 0 for interrupt gate
    566         .byte 0x0e | 0x80  # type = 386 interrupt gate, present
    567         .word 0            # offset 31:16
    568 
    569 # NMI (INT 2)
    570 .equ                NMI_SEL, .-IDT_BASE
    571         .word 0            # offset 15:0
    572         .long SYS_CODE_SEL # selector 15:0
    573         .byte 0            # 0 for interrupt gate
    574         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    575         .word 0            # offset 31:16
    576 
    577 # soft breakpoint (INT 3)
    578 .equ                BREAKPOINT_SEL, .-IDT_BASE
    579         .word 0            # offset 15:0
    580         .long SYS_CODE_SEL # selector 15:0
    581         .byte 0            # 0 for interrupt gate
    582         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    583         .word 0            # offset 31:16
    584 
    585 # overflow (INT 4)
    586 .equ                OVERFLOW_SEL, .-IDT_BASE
    587         .word 0            # offset 15:0
    588         .long SYS_CODE_SEL # selector 15:0
    589         .byte 0            # 0 for interrupt gate
    590         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    591         .word 0            # offset 31:16
    592 
    593 # bounds check (INT 5)
    594 .equ                BOUNDS_CHECK_SEL, .-IDT_BASE
    595         .word 0            # offset 15:0
    596         .long SYS_CODE_SEL # selector 15:0
    597         .byte 0            # 0 for interrupt gate
    598         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    599         .word 0            # offset 31:16
    600 
    601 # invalid opcode (INT 6)
    602 .equ                INVALID_OPCODE_SEL, .-IDT_BASE
    603         .word 0            # offset 15:0
    604         .long SYS_CODE_SEL # selector 15:0
    605         .byte 0            # 0 for interrupt gate
    606         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    607         .word 0            # offset 31:16
    608 
    609 # device not available (INT 7)
    610 .equ                DEV_NOT_AVAIL_SEL, .-IDT_BASE
    611          .word 0            # offset 15:0
    612         .long SYS_CODE_SEL # selector 15:0
    613         .byte 0            # 0 for interrupt gate
    614         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    615         .word 0            # offset 31:16
    616 
    617 # double fault (INT 8)
    618 .equ                DOUBLE_FAULT_SEL, .-IDT_BASE
    619         .word 0            # offset 15:0
    620         .long SYS_CODE_SEL # selector 15:0
    621         .byte 0            # 0 for interrupt gate
    622         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    623         .word 0            # offset 31:16
    624 
    625 # Coprocessor segment overrun - reserved (INT 9)
    626 .equ                RSVD_INTR_SEL1, .-IDT_BASE
    627         .word 0            # offset 15:0
    628         .long SYS_CODE_SEL # selector 15:0
    629         .byte 0            # 0 for interrupt gate
    630         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    631         .word 0            # offset 31:16
    632 
    633 # invalid TSS (INT 0x0a)
    634 .equ                INVALID_TSS_SEL, .-IDT_BASE
    635         .word 0            # offset 15:0
    636         .long SYS_CODE_SEL # selector 15:0
    637         .byte 0            # 0 for interrupt gate
    638         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    639         .word 0            # offset 31:16
    640 
    641 # segment not present (INT 0x0b)
    642 .equ                SEG_NOT_PRESENT_SEL, .-IDT_BASE
    643         .word 0            # offset 15:0
    644         .long SYS_CODE_SEL # selector 15:0
    645         .byte 0            # 0 for interrupt gate
    646         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    647         .word 0            # offset 31:16
    648 
    649 # stack fault (INT 0x0c)
    650 .equ                STACK_FAULT_SEL, .-IDT_BASE
    651         .word 0            # offset 15:0
    652         .long SYS_CODE_SEL # selector 15:0
    653         .byte 0            # 0 for interrupt gate
    654         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    655         .word 0            # offset 31:16
    656 
    657 # general protection (INT 0x0d)
    658 .equ                GP_FAULT_SEL, .-IDT_BASE
    659         .word 0            # offset 15:0
    660         .long SYS_CODE_SEL # selector 15:0
    661         .byte 0            # 0 for interrupt gate
    662         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    663         .word 0            # offset 31:16
    664 
    665 # page fault (INT 0x0e)
    666 .equ                PAGE_FAULT_SEL, .-IDT_BASE
    667         .word 0            # offset 15:0
    668         .long SYS_CODE_SEL # selector 15:0
    669         .byte 0            # 0 for interrupt gate
    670         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    671         .word 0            # offset 31:16
    672 
    673 # Intel reserved - do not use (INT 0x0f)
    674 .equ                RSVD_INTR_SEL2, .-IDT_BASE
    675         .word 0            # offset 15:0
    676         .long SYS_CODE_SEL # selector 15:0
    677         .byte 0            # 0 for interrupt gate
    678         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    679         .word 0            # offset 31:16
    680 
    681 # floating point error (INT 0x10)
    682 .equ                FLT_POINT_ERR_SEL, .-IDT_BASE
    683         .word 0            # offset 15:0
    684         .long SYS_CODE_SEL # selector 15:0
    685         .byte 0            # 0 for interrupt gate
    686         .byte 0x0e |  0x80 # type = 386 interrupt gate, present
    687         .word 0            # offset 31:16
    688 
    689 # alignment check (INT 0x11)
    690 .equ                ALIGNMENT_CHECK_SEL, .-IDT_BASE
    691         .word 0            # offset 15:0
    692         .long SYS_CODE_SEL # selector 15:0
    693         .byte 0            # 0 for interrupt gate
    694         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    695         .word 0            # offset 31:16
    696 
    697 # machine check (INT 0x12)
    698 .equ                MACHINE_CHECK_SEL, .-IDT_BASE
    699         .word 0            # offset 15:0
    700         .long SYS_CODE_SEL # selector 15:0
    701         .byte 0            # 0 for interrupt gate
    702         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    703         .word 0            # offset 31:16
    704 
    705 # SIMD floating-point exception (INT 0x13)
    706 .equ                SIMD_EXCEPTION_SEL, .-IDT_BASE
    707         .word 0            # offset 15:0
    708         .long SYS_CODE_SEL # selector 15:0
    709         .byte 0            # 0 for interrupt gate
    710         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    711         .word 0            # offset 31:16
    712 
    713 # 85 unspecified descriptors, First 12 of them are reserved, the rest are avail
    714     .fill 85 * 8, 1, 0   # db (85 * 8) dup(0)
    715 
    716 # IRQ 0 (System timer) - (INT 0x68)
    717 .equ                IRQ0_SEL, .-IDT_BASE
    718         .word 0            # offset 15:0
    719         .long SYS_CODE_SEL # selector 15:0
    720         .byte 0            # 0 for interrupt gate
    721         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    722         .word 0            # offset 31:16
    723 
    724 # IRQ 1 (8042 Keyboard controller) - (INT 0x69)
    725 .equ                IRQ1_SEL, .-IDT_BASE
    726         .word 0            # offset 15:0
    727         .long SYS_CODE_SEL # selector 15:0
    728         .byte 0            # 0 for interrupt gate
    729         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    730         .word 0            # offset 31:16
    731 
    732 # Reserved - IRQ 2 redirect (IRQ 2) - DO NOT USE!!! - (INT 0x6a)
    733 .equ                IRQ2_SEL, .-IDT_BASE
    734         .word 0            # offset 15:0
    735         .long SYS_CODE_SEL # selector 15:0
    736         .byte 0            # 0 for interrupt gate
    737         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    738         .word 0            # offset 31:16
    739 
    740 # IRQ 3 (COM 2) - (INT 0x6b)
    741 .equ                IRQ3_SEL, .-IDT_BASE
    742         .word 0            # offset 15:0
    743         .long SYS_CODE_SEL # selector 15:0
    744         .byte 0            # 0 for interrupt gate
    745         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    746         .word 0            # offset 31:16
    747 
    748 # IRQ 4 (COM 1) - (INT 0x6c)
    749 .equ                IRQ4_SEL, .-IDT_BASE
    750         .word 0            # offset 15:0
    751         .long SYS_CODE_SEL # selector 15:0
    752         .byte 0            # 0 for interrupt gate
    753         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    754         .word 0            # offset 31:16
    755 
    756 # IRQ 5 (LPT 2) - (INT 0x6d)
    757 .equ                IRQ5_SEL, .-IDT_BASE
    758         .word 0            # offset 15:0
    759         .long SYS_CODE_SEL # selector 15:0
    760         .byte 0            # 0 for interrupt gate
    761         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    762         .word 0            # offset 31:16
    763 
    764 # IRQ 6 (Floppy controller) - (INT 0x6e)
    765 .equ                IRQ6_SEL, .-IDT_BASE
    766         .word 0            # offset 15:0
    767         .long SYS_CODE_SEL # selector 15:0
    768         .byte 0            # 0 for interrupt gate
    769         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    770         .word 0            # offset 31:16
    771 
    772 # IRQ 7 (LPT 1) - (INT 0x6f)
    773 .equ                IRQ7_SEL, .-IDT_BASE
    774         .word 0            # offset 15:0
    775         .long SYS_CODE_SEL # selector 15:0
    776         .byte 0            # 0 for interrupt gate
    777         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    778         .word 0            # offset 31:16
    779 
    780 # IRQ 8 (RTC Alarm) - (INT 0x70)
    781 .equ                IRQ8_SEL, .-IDT_BASE
    782         .word 0            # offset 15:0
    783         .long SYS_CODE_SEL # selector 15:0
    784         .byte 0            # 0 for interrupt gate
    785         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    786         .word 0            # offset 31:16
    787 
    788 # IRQ 9 - (INT 0x71)
    789 .equ                IRQ9_SEL, .-IDT_BASE
    790         .word 0            # offset 15:0
    791         .long SYS_CODE_SEL # selector 15:0
    792         .byte 0            # 0 for interrupt gate
    793         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    794         .word 0            # offset 31:16
    795 
    796 # IRQ 10 - (INT 0x72)
    797 .equ                 IRQ10_SEL, .-IDT_BASE
    798         .word 0            # offset 15:0
    799         .long SYS_CODE_SEL # selector 15:0
    800         .byte 0            # 0 for interrupt gate
    801         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    802         .word 0            # offset 31:16
    803 
    804 # IRQ 11 - (INT 0x73)
    805 .equ                 IRQ11_SEL, .-IDT_BASE
    806         .word 0            # offset 15:0
    807         .long SYS_CODE_SEL # selector 15:0
    808         .byte 0            # 0 for interrupt gate
    809         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    810         .word 0            # offset 31:16
    811 
    812 # IRQ 12 (PS/2 mouse) - (INT 0x74)
    813 .equ                 IRQ12_SEL, .-IDT_BASE
    814         .word 0            # offset 15:0
    815         .long SYS_CODE_SEL # selector 15:0
    816         .byte 0            # 0 for interrupt gate
    817         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    818         .word 0            # offset 31:16
    819 
    820 # IRQ 13 (Floating point error) - (INT 0x75)
    821 .equ                 IRQ13_SEL, .-IDT_BASE
    822         .word 0            # offset 15:0
    823         .long SYS_CODE_SEL # selector 15:0
    824         .byte 0            # 0 for interrupt gate
    825         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    826         .word 0            # offset 31:16
    827 
    828 # IRQ 14 (Secondary IDE) - (INT 0x76)
    829 .equ                 IRQ14_SEL, .-IDT_BASE
    830         .word 0            # offset 15:0
    831         .long SYS_CODE_SEL # selector 15:0
    832         .byte 0            # 0 for interrupt gate
    833         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    834         .word 0            # offset 31:16
    835 
    836 # IRQ 15 (Primary IDE) - (INT 0x77)
    837 .equ                 IRQ15_SEL, .-IDT_BASE
    838         .word 0            # offset 15:0
    839         .long SYS_CODE_SEL # selector 15:0
    840         .byte 0            # 0 for interrupt gate
    841         .byte 0x0e |  0x80 # (10001110)type = 386 interrupt gate, present
    842         .word 0            # offset 31:16
    843 
    844 IDT_END:
    845 
    846         .p2align 1
    847 
    848 MemoryMapSize:  .long 0
    849 MemoryMap:  .long 0,0,0,0,0,0,0,0
    850         .long 0,0,0,0,0,0,0,0
    851         .long 0,0,0,0,0,0,0,0
    852         .long 0,0,0,0,0,0,0,0
    853         .long 0,0,0,0,0,0,0,0
    854         .long 0,0,0,0,0,0,0,0
    855         .long 0,0,0,0,0,0,0,0
    856         .long 0,0,0,0,0,0,0,0
    857         .long 0,0,0,0,0,0,0,0
    858         .long 0,0,0,0,0,0,0,0
    859         .long 0,0,0,0,0,0,0,0
    860         .long 0,0,0,0,0,0,0,0
    861         .long 0,0,0,0,0,0,0,0
    862         .long 0,0,0,0,0,0,0,0
    863         .long 0,0,0,0,0,0,0,0
    864         .long 0,0,0,0,0,0,0,0
    865         .long 0,0,0,0,0,0,0,0
    866         .long 0,0,0,0,0,0,0,0
    867         .long 0,0,0,0,0,0,0,0
    868         .long 0,0,0,0,0,0,0,0
    869         .long 0,0,0,0,0,0,0,0
    870         .long 0,0,0,0,0,0,0,0
    871         .long 0,0,0,0,0,0,0,0
    872         .long 0,0,0,0,0,0,0,0
    873         .long 0,0,0,0,0,0,0,0
    874         .long 0,0,0,0,0,0,0,0
    875         .long 0,0,0,0,0,0,0,0
    876         .long 0,0,0,0,0,0,0,0
    877         .long 0,0,0,0,0,0,0,0
    878         .long 0,0,0,0,0,0,0,0
    879 
    880         .long 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
    881         .long 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
    882 
    883         .org 0x0fe0
    884 MyStack:
    885         # below is the pieces of the IVT that is used to redirect INT 68h - 6fh
    886         #    back to INT 08h - 0fh  when in real mode...  It is 'org'ed to a
    887         #    known low address (20f00) so it can be set up by PlMapIrqToVect in
    888         #    8259.c
    889 
    890         int $8
    891         iret
    892 
    893         int $9
    894         iret
    895 
    896         int $10
    897         iret
    898 
    899         int $11
    900         iret
    901 
    902         int $12
    903         iret
    904 
    905         int $13
    906         iret
    907 
    908         int $14
    909         iret
    910 
    911         int $15
    912         iret
    913 
    914 
    915         .org 0x0ffe
    916 BlockSignature:
    917         .word 0xaa55
    918 
    919 
    920