Extended X86 BootLoader

ShiftLeft 0 Tallied Votes 316 Views Share

This is a special purpose boot loader for a system I've called Proto-Sys. Eventually it is going to become a 64 bit application that will encompass all the resources to hook into drivers, benchmark code and optomize algorithms.

Synopsis:

* Preserve registers as they were passed by BIOS
* Create a 64K stack frame just below BDA
* Reserve 192 bytes for scratch area at top of frame pointed to by SS:BP
* Load remainder of the lowest density disk (7 sectors)
* Move that 4K image lower in memory. In this case 6A:0
* Build an E820 memory map starting @ 50:0
* Test and turn on A20 using fast A20 gate

Fundementally, I just like experimenting with algorithms as a hobby, so you may see some unorthodox methodolgy, but generally this code does reinforce the concept of segmented memory in real or 16 bit. In the next stage, I'll be going into protected mode and that is where all the details of the machines state will be displayed. If any of you have legacy hardward, post 80286, I would appreciate you testing this code on your systems.

Even if you don't have real hardware, it would be interesting too as I use BOCHS 2.6.5

BDA  equ  0x0040     ; BDA segment
                   MEM  equ  0x0013     ; Offset to memsize.
          CURRENT_PAGE  equ  0x0062

                VIDEO   equ     16
                  SCP   equ      2      ; Set cursor position
                  GCP   equ      3      ; Get cursor position
                  CAP   equ      5      ; Get Active page
                  SPU   equ      6
                  WCA   equ      9
                  TTY   equ     14
                  
                ReBoot  equ     25
       SYSTEM_SERVICE   equ     21

               DISK_IO  equ     19
              D_STATUS  equ      1
                D_READ  equ      2
               D_WRITE  equ      3
               D_PARAM  equ      8
                GET_DP  equ     52
              EXT_READ  equ     66

        KEYBOARD        equ     25
         GETCHAR        equ      3
        TELETYPE        equ     14
        
        BLACK           equ     0
        BLUE            equ     1
        GREEN           equ     2
        CYAN            equ     3
        RED             equ     4
        MAGENTA         equ     5
        BROWN           equ     6
        LGREY           equ     7
        DGREY           equ     8
        LBLUE           equ     9
        LGREEN          equ     10
        LCYAN           equ     11
        LRED            equ     12
        LMAGENTA        equ     13
        YELLOW          equ     14
        WHITE           equ     15
        
        FLASHING        equ     128

   BOOT_SEG     equ     0x7c0
    EXT_IMG     equ     0x06a           ; Base address of extended boot image

 BOOT_DRIVE     equ     BP - 10         ; 00 or 01 FDD, 80 or 8? for HDD\SD\USB


; Strictly for curiosities sake, preserve general purpose and segment registers so thier state
; as passed by BIOS can be displayed later.

        pusha                           ; AX CX DX BX SP BP SI DI

        push    cs
        push    ds
        push    es
        push    ss
        push    fs                      ; Stack now has 14 word values, 16 assuming the
        push    gs                      ; the first two is a far pointer back into BIOS.

    ; Do a far jump to compensate for quirky BIOS and so value for CS:IP is known.

        jmp     BOOT_SEG:Begin

; NOTE:  I won't document these two procedurs as they live for a very short period of time
; as they are overwritten by E820 map. Subsequent sources will have more elaborate versions
; of these.

; --------------------------------------------------------------------------------------------

  ShowS:
        mov     ah, TTY                 ; Teletype output

    @@: lodsb
        or      al, al                  ; Terminating character yet?
        jz      @F

        int     VIDEO
        jmp     @B

    @@: ret

; --------------------------------------------------------------------------------------------

  I2A:  std                             ; Reverse direction
        push    es
        push    cs
        pop     es

    @@: push    ax
        and     al, 15
        or      al, '0'
        cmp     al, '9'
        jbe     $ + 4

        add     al, 7

        stosb
        pop     ax
        shr     ax, 4
        jnz     @B

        pop     es
        cld
        ret

        align   8
; ============================================================================================
; Conventional address space 0:0000 > F:FFFF needs to be initialized peculiar
; to my OS's requirements.

  Begin:

    ; Determine number of 4k blocks up to EBDA.

        mov     ax, BDA                 ; AX = 40H
        mov     ds, ax                  ; DS points to BIOS Data Area
        mov     ax, [MEM]               ; Get # of 4k blocks from 40:13
        shl     ax, 6                   ; Convert to segment value, AX *= 64

    ; Create a 64k block of data for scratch and stack and initialize it to -1's. This is
    ; to facilitate stack probbing in the event of memory leaks in stack space.

        sub     ah, 16                  ; Bumpto beginning of this 64k block
        mov     es, ax                  ; Essentially AX -= 0x1000
        or      eax, -1                 ; Fill pattern for 64k block
        mov     cx, 0x4000              ; Number of dwords to be written
        xor     di, di
        rep     stosd                   ; Fill buffer

    ; C0 (192) bytes of this buffer is going to be a scatch area pointed to by SS:BP.
    ; The 16 word values on stack are going to be moved to new TOS

        sub     di, 192 + 32            ; ES:DI now points to new TOS
        push    ss
        pop     ds
        mov     si, sp                  ; DS:SI points to values previously save
        mov     cl, 16
        rep     movsw                   ; Move values saved in preamble

    ; New BP and SP to be established.

        mov     bp, di                  ; DI points to scratch area @ FF40
        mov     ax, es

    ; New stack pointer can be set and we want to make sure an interrupt doesn't happen
    ; at the same time.

        cli
        mov     sp, di
        sub     sp, 32
        mov     ss, ax
        sti                             ; New stack established.

    ; Give user a little indication of what is going on.

        push    cs
        pop     ds                      ; DS:SI points to prompts
        mov     si, Prompt
        call    ShowS

    ; Load remainder of track at 7E00 assuming it is a 360k low density disk with only 8
    ; sectors / track. In effect this gives us a 4K boot loader.

        mov     ax, cs
        add     al, 32
        mov     es, ax
        xor     bx, bx                  ; ES:BX points to buffer @ 7E0:0000
        mov     dl, [BOOT_DRIVE]        ; Drive designator passed by BIOS
        mov     cx, 2                   ; CH = 0 (Head #), CL start @ second sector
        mov     ax, D_READ * 256 + 7    ; AH = Read and AL for next 7 sectors
        int     DISK_IO
        or      ah, ah                  ; Test if there was an error
        jz      @F

    ; Show that load failed with error #.

        mov     si, Error               ; Error String
        mov     di, si
        add     di, 16                  ; Point to last digit of error number
        shr     ax, 8                   ; Shift error number into LSB
        call    I2A                     ; Convert to ASCII Hex
        call    ShowS

    ; If we get an error here, it's probably because media is defective so just changing disk
    ; and re-setting is the easiest as this has a very slim chance of happening.

        hlt
        jmp     $ - 1                   ; Spin indefinately

    ; Not particularly useful information, but does give user some indication what's going on

    @@: mov     di, si
        add     di, 4
        mov     ax, es
        call    I2A
        call    ShowS

    ; Now we are going to move this all out of the way into lower memory starting @ 50:0

        xor     si, si                  ; DS:SI points to beginning of this code
        mov     ax, EXT_IMG
        mov     es, ax
        mov     di, si                  ; ES:DI points to buffer in low memory
        mov     cx, 2 * 512             ; Total size of this code block
        rep     movsd                   ; Move 1024 dwords = 4,096 or 8 512 byte sectors

        jmp     EXT_IMG:@F              ; Branch to this code at its new location

  Prompt        db     13, 10, 'Proto_Sys extended load ', 0, '@ 000:0', 0
   Error        db     'Failed Error = 00', 0

; As it will persist for a little while, E820 map will live just above BDA @ 0x50:0

        MAP_BASE        equ     0x50    ; Base segment of E820 map

      ENTRY_SIZE        equ     BP + 0
        A20_LINE        equ     ENTRY_SIZE

           COUNT        equ     BP + 1  ; # of map entries and thier actual size @ BP (word)
     MAX_ENTRIES        equ     BP + 2  ; Maximum number of etnries
       E820_PNTR        equ     MAX_ENTRIES

    ; Initialize a reasonable sized buffer to null. This is to eliminate extraneous data from
    ; each 20 byte entry that are going to be aligned on 32 byte boundaries.

    @@: mov     cx, cs
        add     cx, @F / 16
        mov     ax, MAP_BASE
        sub     cx, ax
        mov     [MAX_ENTRIES], cl       ; Maximum number of entries
        shl     cx, 2
        mov     es, ax
        mov     ds, ax                  ; Segment pointers must be the same
        xor     eax, eax
        mov     di, ax
        push    di

        align   16

    @@: rep     stosd                   ; 0500H to 2300 fill with nulls (more than enough)

    ; Initialize register to values required by int 0x15 (Big memory services).

        pop     di                      ; ES:DI points to base of E820 map
        mov     ebx, eax                ; Continuation value initially null.
        mov     edx, 'PAMS'             ; Map signature
        mov     ecx, eax
        mov     [ENTRY_SIZE], ax        ; # of entries and length of each to null
        jmp     @F                      ; BP + 1 = Length of each entry

    ; This local subroutine essentially save 20 bytes of code. Every bit counts when
    ; restricted to 512.

  GetMData:
        push    edx                     ; Preserve signature
        mov     cl, 24                  ; Some BIOS may have extended lengths
        mov     eax, 0xE820
        inc     byte [di + 20]
        int     SYSTEM_SERVICE
        pop     edx                     ; Restore signature
        ret

    ; This is only called once as there is a set of specific errors associated with first
    ; invocation.

    @@: call    GetMData                ; Initial call to function
    
        jc      .Done                   ; If CF on first pass, no map
        cmp     eax, edx
        jne     .Done                   ; If string "SMAP" was not returned, error
        test    ebx, ebx
        jz      .Done                   ; EBX = 0 if end of map and at this point no entries

    ; Top of loop, keep calling function until EBX returns null or an error occurs

    .NextEntry:
        jcxz    .Skip                   ; Function error
        mov     [ENTRY_SIZE], cl
        cmp     cl, 20
        jbe     @F
        test    byte [di + 20], 1
        je      .Skip
        
    @@: mov     eax, [di+8]
        or      eax, [di+12]            ; Ignore entries with null lengths
        jz      .Skip
        
        inc     byte [COUNT]          ; Bump entry count
        add     di, 32                  ; Point to next entry
        mov     ax, [COUNT]
        sub     ah, al
        jc      .Done

    .Skip:
        test    ebx, ebx
        jz      .Done                   ; ZF = 1, then list is complete
        call    GetMData                ; Read another entry
        jnc     .NextEntry              ; CF = 0, continue

   .Done:
        xor     eax, eax
        mov     ax, es
        shl     ax, 4
        mov     [E820_PNTR], eax

; We could just simply turn the gate on, but I would like to know which BIOS already have
; gate on and which don't.

  Check_A20:
        mov     byte [A20_LINE], GREEN  ; A20 was already on
        mov     cx, 0x8000              ; Try turning A20 on 32,768 times

    ; This sets up pointers for what is known as the wrap around method. In this case
    ; DS:SI (0x7c5) will point to "GetMData" and ES:DI (1007c5) if gate is on

        mov     si, cs
        shl     si, 4
        add     si, GetMData
        mov     di, si
        add     di, 16
        xor     ax, ax
        mov     ds, ax
        dec     ax
        mov     es, ax

    ; Take value at memory location, negate it and write it back. If it's not the same
    ; then gate is on

    @@: push    di
        push    si      
        lodsw
        neg     ax
        stosw
        cmp     [si-2], ax
        pop     si
        pop     di
        jnz     .On

    ; This fast A20 gate mentod works on my test system, Phoenix TrustedCore Desktop SP2
    ; for ThinkCenter.

        mov     byte [A20_LINE], YELLOW ; A20 turned off with fast method
        in      al, 0x92
        or      al, 2
        out     0x92, al
        dec     cx
        jnz     @b
        
        mov     byte [A20_LINE], RED  ; Indication that A20 failed

  .On:

; These remaining 63 bytes in this sector are going to be reserved for alternate methods of
; turning A20 on if this fast gate mentod didn't work.

        times (508 - $) db      144

        jmp     @F                      ; Bounce over boot signature
        dw      0xAA55                  ; Boot signature

; Beginning of sector 2 of boot image

    @@: