flat assembler
Message board for the users of flat assembler.

Index > OS Construction > Setting up PML4 table

Author
Thread Post new topic Reply to topic
AnonymousUser



Joined: 25 Jul 2014
Posts: 32
AnonymousUser 07 Aug 2014, 19:27
Hello all I have been working on a Bootloader and I am trying to enter Long mode from Protected mode and All I have left is to set up the PML4 table But I haven't been able to find any good references on how to do that here is a snippet of what I have done:
Code:
lidt [IDT]
         ;disable paging
        mov cr0, eax
        xor    eax, 1 << 31
        mov eax, cr0
        
        
        
        
        ; Enter long mode.
    mov eax, 10100000b                ; Set the PAE and PGE bit.
    mov cr4, eax
        
        ;Note: Will not work no table                        
        mov cr3, edx ; Point CR3 at the PML4.
               
        
        
        mov ecx, 0xC0000080               ; Read from the EFER MSR. 
    rdmsr    
 
    or eax, 0x00000100                ; Set the LME bit.
    wrmsr
 
    mov ebx, cr0                      ; Activate long mode -
    or ebx,0x80000001                 ; - by enabling paging and protection simultaneously.
    mov cr0, ebx        
        
        lgdt[GDT_64.Pointer]
        
        jmp 0x8:Long_Mode
        [BITS 64]
        
        
        Long_Mode:
    

_________________
Thanks in advance
Post 07 Aug 2014, 19:27
View user's profile Send private message Reply with quote
AnonymousUser



Joined: 25 Jul 2014
Posts: 32
AnonymousUser 07 Aug 2014, 23:43
I Just tried this:
Code:
[BITS 16]
org 0x2000

Start:

 jmp  main
;;;;;;;;;;;;;;;;;;
;                                ;
;                                ;
;    Constants   ;
;                                ;
;;;;;;;;;;;;;;;;;;
%DEFINE TEAL 0x03
%DEFINE RED 0x04
%DEFINE PURPLE 0x05
%DEFINE VIDEO_MEM 0xB8000
%DEFINE COLS    80                      ; width and height of screen
%DEFINE LINES   25


X_POS:  db 0
Y_POS:  db 0


;;;;;;;;;;;;;;;;;;
;    Enabling    ;
;    The A20     ;
;         line           ;
;;;;;;;;;;;;;;;;;;
EnableA20:

        IN AL, 0x92         ; A20, using fast A20 gate
    MOV CL, AL
    AND CL, 2
    JNZ .skip            ; if a20 bit seems set, don't touch it
    OR AL, 2
    OUT 0x92, AL
    .skip:

ret



        



main:           
;first stage of bootloader is loaded at the address 0x07c0:0
        ;second stage of bootloader is loaded at address 0x200:0x0
        
        
        cli
   xor ax, ax         ; All segments set to 0, flat memory model
   mov ds, ax
   mov es, ax
   mov gs, ax
   mov fs, ax
   mov ss, ax
   ;
   ; Set stack top SS:0xffff
   ;
   mov sp, 0x0FFFF
   ;


        mov [CDDriveNumber], dl
        
        SwitchToProtectedMode:
        
        lgdt [GDT_32];load the gdt
        call EnableA20
  
        
        mov eax, cr0
        or eax, 1
        mov cr0, eax
        
        
         ; Flush CS and set code selector
   ;
        jmp 0x8:Protected_Mode
        
        [BITS 32];Declare 32 bits
        
        Protected_Mode:
        
        
        
        ;set up segment registers
        XOR   AX, AX
        MOV   AX, 0x10 
        MOV   DS, AX
        MOV   ES, AX
        MOV   FS, AX
        MOV   GS, AX
        MOV   SS, AX
        MOV   ESP, 0x900000
        
        
        
        ;prints an A to the top of the screen
        
        call clear
        
        mov eax, cr0
        or eax, 1 << 31
        mov cr0, eax
        xor bx, bx
        
        mov bx, LOAD_SUCCESS
        call sPrint
        
        mov bx, Entered_PMODE
        call sPrint
        
        SwitchToLongMode:
        
        
        ;Disable paging
        
        
        
        ;lidt [IDT]
         
        ;lgdt[GDT_64.Pointer]
        
        xor eax, eax
        mov ebx, 0x100000
        .fill_table:
                mov ecx, ebx
                or ecx, 3
                mov [table_768+eax*4], ecx
                add ebx, 4096
                inc eax
                cmp eax, 1024
                je .end
                jmp .fill_table
 .end:
        
        
        
        
        
        mov al, 0xFF                                                            ; set out 0xFF to 0xA1 and 0x21 to disable all IRQs
        out 0xA1, al
        out 0x21, al

        ; Setup long mode.
        mov eax, cr0                                                            ; read from CR0
        and eax, 0x7FFFFFFF                                                     ; clear paging bit
        mov cr0, eax                                                            ; write to CR0
        
        mov eax, cr4                                                            ; read from CR4
        or eax, 0x000000A0                                                      ; set the PAE and PGE bit
        mov cr4, eax                                                            ; write to CR4

        mov eax, [table_768]                                    ; point eax to PML4 pointer location
        or eax, 0x0000000B                                                      ; enable write-through
        mov cr3, eax                                                            ; save PML4 pointer into CR3
        
        mov ecx, 0xC0000080                                                     ; read from the EFER MSR
        rdmsr                                                                           ; read MSR
        or eax, 0x00000101                                                      ; set the LME and SYSCALL/SYSRET bits
        wrmsr                                                                           ; write MSR

        lgdt [GDT_64.Pointer]                                                   ; load 64bit GDT pointer
        
        mov eax, cr0                                                            ; read from CR0
        or eax, 0x80000000                                                      ; set paging bit
        mov cr0, eax                                                            ; write to CR0
        
        
        jmp 0x8:Long_Mode
        [BITS 64]
        
        
        Long_Mode:
        
        xor bx, bx
        mov bx, Entered_LMODE
        call sPrint
        
        
        
        
        
        
        cli
        hlt
        [BITS 32]
        clear:
        
        pusha
        mov edi, VIDEO_MEM
        mov BYTE[edi], ' '
        mov BYTE[edi+1], 14
        rep stosw
        MOV BYTE[X_POS], 0x0
        MOV BYTE [Y_POS], 0x0
        popa
        ret
        
        sPrint:
        pusha
                jmp .start
                .Row:
                call NewLine
                MOV BYTE[EDI], ' '
                jmp .Next
                .start:
                MOV EDI, VIDEO_MEM
                xor ecx, ecx
                xor eax, eax
                mov     ecx, COLS*2             ; Mode 7 has 2 bytes per char, so its COLS*2 bytes per line
                mov     al, BYTE [Y_POS]        ; get y pos
                mul     ecx                     ; multiply y*COLS
                push    eax                     ; save eax--the multiplication
                 
                mov     al, byte [X_POS]        ; multiply _CurX by 2 because it is 2 bytes per char
                mov     cl, 2
                mul     cl
                pop     ecx                     ; pop y*COLS result
                add     eax, ecx
                
                
                add edi, eax
                mov al,BYTE[bx]
                
                cmp al, 0x0;check if end
                je .Done
                cmp al, 0xA;check if new line
                je .Row
                
                mov BYTE[edi],al 
                .Next:
                mov BYTE[edi+1], TEAL
                INC BX
                inc     BYTE[X_POS]             ; go to next character
                cmp     BYTE[X_POS], COLS               ; are we at the end of the line?
                je      .Row                    ; yep-go to next row
                
                
                jmp .start
        .Done:
        
        
        popa
        
        ret
        NewLine:
        inc BYTE[Y_POS]
        MOV BYTE[X_POS], -1
        
        ret
Entered_PMODE:  db "You have succcessfully entered Protected Mode Very Happy",0xA, 0
LOAD_SUCCESS:   db "Stage 2 Loaded Successfully",0xA, 0
CDDriveNumber:  db 0
Entered_LMODE:  db "You have successfully entered Long Mode Very Happy !!!!!!!!!!!",0xA,0


GDT_START:
;null descriptor
dd 0
dd 0
;data descriptor
dw 0xFFFF
dw 0
db 0
db 10011010b
db 11001111b
db 0
;code descriptor
dw 0xFFFF
dw 0
db 0
db 10010010b
db 11001111b
db 0
GDT_END:
align 4
GDT_32:
dw GDT_END - GDT_START - 1
dd GDT_START



GDT_64:
.Null:
    dq 0x0000000000000000             ; Null Descriptor - should be present.
 
.Code_64:
    dq 0x0020980000000000             ; 64-bit code descriptor. 
    dq 0x0000900000000000             ; 64-bit data descriptor. 
.Pointer:
    dw $ - GDT_64 - 1                    ; 16-bit Size (Limit) of GDT.
    dd GDT_64                            ; 32-bit Base Address of GDT. (CPU will zero extend to 64-bit)

        
        
        
ALIGN 4
IDT:
    .Length       dw 0
    .Base         dd 0

PML4_POINTER:;blank table
        dd 0                                                                            
PML4_POINTER_END:
table_768: dd 0


    

Still no luck Note: it does go into Protected mode correctly.

_________________
Thanks in advance
Post 07 Aug 2014, 23:43
View user's profile Send private message Reply with quote
BAiC



Joined: 22 Mar 2011
Posts: 272
Location: California
BAiC 08 Aug 2014, 00:42
Tomasz built an example that does this. it's in the examples section.
Post 08 Aug 2014, 00:42
View user's profile Send private message Visit poster's website Reply with quote
AnonymousUser



Joined: 25 Jul 2014
Posts: 32
AnonymousUser 08 Aug 2014, 00:47
I don't see it in the examples section all I see is the MIDI Input topic by Tomasz Could you give me a link???
Post 08 Aug 2014, 00:47
View user's profile Send private message Reply with quote
sinsi



Joined: 10 Aug 2007
Posts: 789
Location: Adelaide
sinsi 08 Aug 2014, 03:46
mov eax, [table_768] doesn't load the address of the table.
lea eax, [table_768] or mov eax, table_768 gets the address.
Post 08 Aug 2014, 03:46
View user's profile Send private message Reply with quote
AnonymousUser



Joined: 25 Jul 2014
Posts: 32
AnonymousUser 08 Aug 2014, 04:04
Just tried both of those still crashing looks like the address of the gdt is : 0x2217 right before it crashes
Post 08 Aug 2014, 04:04
View user's profile Send private message Reply with quote
BAiC



Joined: 22 Mar 2011
Posts: 272
Location: California
BAiC 08 Aug 2014, 05:11
Post 08 Aug 2014, 05:11
View user's profile Send private message Visit poster's website Reply with quote
AnonymousUser



Joined: 25 Jul 2014
Posts: 32
AnonymousUser 08 Aug 2014, 06:41
Ok I just tried the example like so:
Code:
main:            
;first stage of bootloader is loaded at the address 0x07c0:0 
        ;second stage of bootloader is loaded at address 0x200:0x0 
         
         
        cli 
   xor ax, ax         ; All segments set to 0, flat memory model 
   mov ds, ax 
   mov es, ax 
   mov gs, ax 
   mov fs, ax 
   mov ss, ax 
   ; 
   ; Set stack top SS:0xffff 
   ; 
   mov sp, 0x0FFFF 
   ; 


        mov [CDDriveNumber], dl 
         
        SwitchToProtectedMode: 
         
        lgdt [GDT_32];load the gdt 
        call EnableA20 
   
         
        mov eax, cr0 
        or eax, 1 
        mov cr0, eax 
         
         
         ; Flush CS and set code selector 
   ; 
        jmp 0x8:Protected_Mode 
         
        [BITS 32];Declare 32 bits 
         
        Protected_Mode: 
         
         
         
        mov     eax,0x10        ; load 4 GB data descriptor
                mov     ds,ax                   ; to all data segment registers
                mov     es,ax
                mov     fs,ax
                mov     gs,ax
                mov     ss,ax

                mov     eax,cr4
                or      eax,1 << 5
                mov     cr4,eax                 ; enable physical-address extensions

                mov     edi,70000h
                mov     ecx,4000h >> 2
                xor     eax,eax
                rep     stosd                   ; clear the page tables

                mov     dword [70000h],71000h + 111b ; first PDP table
                mov     dword [71000h],72000h + 111b ; first page directory
                mov     dword [72000h],73000h + 111b ; first page table

                mov     edi,73000h              ; address of first page table
                mov     eax,0 + 111b
                mov     ecx,256                 ; number of pages to map (1 MB)
        make_page_entries:
                stosd
                add     edi,4
                add     eax,1000h
                loop    make_page_entries

                mov     eax,70000h
                mov     cr3,eax                 ; load page-map level-4 base

                mov     ecx,0C0000080h          ; EFER MSR
                rdmsr
                or      eax,1 << 8              ; enable long mode
                wrmsr
                lgdt[GDT_64]
                mov     eax,cr0
                or      eax,1 << 31
                mov     cr0,eax                 ; enable paging

        jmp 0x08:Long_Mode 
        [BITS 64] 
         
         
        Long_Mode: 
         
        xor bx, bx 
        mov bx, Entered_LMODE 
        call sPrint 
         
         
         
         
         
         
        cli 
        hlt 
    

Still crashes I'll go and debug it now in bochs and see what I find.

_________________
Thanks in advance
Post 08 Aug 2014, 06:41
View user's profile Send private message Reply with quote
BAiC



Joined: 22 Mar 2011
Posts: 272
Location: California
BAiC 08 Aug 2014, 08:21
the example assembles fine. which means the error is in the code you included.

what's with the C shift operators (<<) ? FASM doesn't implement this syntax. use "shl" instead of "<<".

also; you're not including all of your code. so we can't test it.
Post 08 Aug 2014, 08:21
View user's profile Send private message Visit poster's website Reply with quote
AnonymousUser



Joined: 25 Jul 2014
Posts: 32
AnonymousUser 08 Aug 2014, 13:05
Here is the full code:
Stage1
Code:
[BITS   16]

[ORG  0x0]

start : jmp 0x7c0:main
;
; boot info block
;
times 8-($-$$) db 0
BootInfoPrimVolDescr   resd 1
BootInfoFileLoc           resd 1
BootInfoFileLength      resd  1
BootInfoChecksum       resd 1
BootInfoReserved        resd 40


;Colors for text
%DEFINE TEAL 0x03
%DEFINE RED 0x04
%DEFINE PURPLE 0x05
%define ISO_DIRECTORY_LEN 33      ; length of constant part of directory record
%define ISO_DIRECTORY_LBA_OFFSET 2

COL: db 0
ROW:  db 0
LOADSEG equ 0x200 ; ?
LOADOFFS equ 0 ; ?
jumptarget dw LOADOFFS, LOADSEG
;macro for print
%macro Print 2
pusha
        xor ax, ax
        xor dx, dx
        mov dh, BYTE[ROW];puts the row into the dh register
        mov dl, BYTE[COL]
        xor bx, bx
        mov bl, %2
        mov si, %1
        call cPrint
        mov BYTE[COL], dl
 ;saves the rows for the next time we need to print
popa
%endmacro

Print_ln:

pusha   
        mov dh, BYTE[ROW]          
    mov ah, 0x02            ;set cursor pos
    mov bh, 0x00            ;page 00
    inc dh                      ;row 00
    mov dl, 0x00            ;col. 00    
        int 0x10
        mov BYTE[ROW], dh
        mov BYTE[COL], 0
        popa


ret

itoa:;number is passed into ax
jmp .beggining
.negate:

neg ax
push ax

mov al, '-'
mov ah, 0xe 
int 0x10
pop ax
jmp .top
.beggining:
xor bx , bx
mov cx, 10;mov into cx 10
cmp ax, 0
jl .negate


.top:
        ;divide by 10 and push remainder onto stack 
        xor dx, dx;clear out remainder
        div cx ;divide ax by 10
        push dx;push the remainder onto the stack for later
        inc bx;count the number of digits
        test ax,ax;if ax = 0 then stop
jne .top

.loop:
        pop ax;restore the remainder
        add ax, '0';convert to ASCII
        mov ah, 0xe;print
        int 0x10
        dec bx;get ready for the next digit
        cmp bx, 0;if not zero then jump to .loop        
jne .loop
ret

cPrint:                   ; Routine: output string in SI to screen


 .top:
        ;Paramaters for Input 
    mov ah, 09h             ; Must be 9 to print color
    mov cx, 0x01                        ;x position
    lodsb                   ; Get character from string
    test al, al
    je .done                ; If char is zero, end of string
    int 0x10                 ; Otherwise, print it

    mov ah, 0x02                        ;set cursor position
    mov bh, 0x00                        ;page
    inc dl              ;column
    int 0x10                            ;changes the cursor position so the next char can be written at the new location
    jmp .top

 .done:
    ret

;clears the screen and sets the cursor position to the top left 
 clear:
    mov ah, 0x0F            ;get current video mode
    mov al, 0x00            ;reset register
    int 0x10                ;get video mode
    mov ah, 0x00            ;set video mode
    int 0x10                ;reset screen
    mov ah, 0x02            ;set cursor pos
    mov bh, 0x01            ;page 00
    mov dh, 0x00            ;row 00
    mov dl, 0x00            ;col. 00
    int 0x10            ;set pos
        mov BYTE[ROW], DH
        mov BYTE[COL],0
ret


Read_Sectors:  
        ;/* Read the sector into memory. */
       
                .ForLoop:
                        mov     ah,042h
                        xor     al,al
                        mov     si, DiskAddressPacket
                        mov     dl, [CDDriveNumber]
                        int     013h
        jnc    .Success         ; /* read error? */

        Print Read_Sector_Error_MSG, RED
                
                cli
                hlt

.Success:
                Print Progress_MSG , PURPLE
                inc WORD[DiskAddressPacket.SectorsToRead]
                
        loop    .ForLoop
                call Print_ln
ret
CHECK_DESC:
        Print CHECK_DESC_MSG, TEAL
        mov es, WORD[DiskAddressPacket.Segment]
        mov di, WORD[DiskAddressPacket.Offset]
        
        xor bx, bx
        .top:
                mov al, BYTE[ES:DI+BX]
                mov BYTE[VOLUME+BX], al
                
                inc bx
                cmp al, ' '
                je .Done
                jmp .top
        .Done:

        ;see if the Volume descriptor contains the Signature
        xor BX, BX; clear out bx
        add BX, 0x01;move into bx the offset
        xor cx, cx;clear out cx
        .toploop:
        xor ax, ax
        mov al, BYTE[VOLUME+BX] 
        cmp al, BYTE[CD_Signature+BX-1]
        je .FOUND_IT; Compare the letters Byte by Byte to see if they are the same
        jmp .Done2
        inc CX;increments if even one letter is wrong
        .FOUND_IT:
        Print Progress_MSG, PURPLE
        inc BX;Increments the offset
        
        jmp .toploop
        
        .Done2:
        cmp CX, 0;if signatures don't match then stop the system and print an error Message
        jne .FAIL
        call Print_ln
        
        Print FOUND_CD, TEAL
        jmp .Done3
        .FAIL:
        Print FILE_NOT_FOUND, RED
        cli
        hlt
        .Done3:
        call Print_ln
ret
READ_STAGE2:
        Print LOADING_STAGE2_MSG, TEAL
        call Print_ln
                
        mov di, [DiskAddressPacket.Offset]
        mov es, [DiskAddressPacket.Segment]

        
    xor BX, BX;clears out bx
        xor si, si ;clears out si
        xor cx, cx
        MOV CX, [ES:DI+32]
    .top:
                
                
                MOV AL,BYTE[ES:DI+BX] ;moves a byte of a possible start of a file entry
                cmp AL,BYTE[STAGE2];compares it with file I want
                je .Done;if it is then jump out of loop
                INC BX;get ready for next file entry
        jmp .top
        
        .Done:
        Print Found_Possible_FILE, TEAL;prints it found a possible file
        XOR SI, SI;Clear out for use
        ;=INC BX
        ;INC SI
        xor cx, cx;clear out for use as counter
        .top2:;compares strings to see if they are the same
                ;xor ax, ax;clears out acx
                
                ;prints out a letter to the screen
                MOV AL, BYTE[ES:DI+BX]
                MOV AH, 0xE
                INT 0x010
                ;;;;;;;;;;;;;;;;;;
                
                xor ax, ax
                MOV AL, BYTE [ES:DI+BX]
                cmp AL, BYTE[STAGE2+SI]
                
                je .Success
                call Print_ln
                jmp .top
                .Success:
                        
                        ;Print Progress_MSG, PURPLE;progress message
                                                
                        
                        INC BX;get ready for next character
                        INC SI;get ready for next character     
                        INC CX; increment counter 
        cmp CX, WORD[STAGE_2_LEN] 
        jne .top2
        ;call clear
        call Print_ln
        Print File_Found, TEAL;prints found file if found
        call Print_ln
        
        Print Reading_Sectors, TEAL;prints reading sector message
        ;call clear
        
        
        %define STAGE2_LEN 12            ; STAGE2.BIN;1
        %define ISO_DIRECTORY_LEN 33      ; length of constant part of directory record
        %define ISO_DIRECTORY_LBA_OFFSET 2  ; offset of LBA member of structure

   ;
   ; Set SEG:OFFSET to 0x2000 load address
   ;
   mov word [DiskAddressPacket.Offset], 0
   mov word [DiskAddressPacket.Segment], 0x200
   ;
   ; Adjust BX
   ;
   mov di, bx   ; save bx and get rid of it. Only want to use ES:DI
   xor bx, bx
   ;
   ; Adjust ES:DI to point to LBA / Extent member of directory structure
   ;
   sub di, STAGE2_LEN
   sub di, ISO_DIRECTORY_LEN
   add di, ISO_DIRECTORY_LBA_OFFSET
   ;
   ; Now [ES:DI] -> LBA / Extent of directory record in both endian formats; grab little endian format into EAX
   ;
   mov eax, [ES:DI]
   ;
   ; Now EAX = LBA to start loading from. Store it
   ;
   mov dword [DiskAddressPacket.End], EAX
   ;
   ; Should calculate this from extentSize field: sector count = (extentSize / sectorSize) + 1
   ;
   mov word [DiskAddressPacket.SectorsToRead], 4
        
        xor cx, cx;clears out cx
        mov cx, 0x01;puts in cx 0x04 for how many sectors to read
        call Read_Sectors;calls the read sectors
        Print READ_SUCCESS, TEAL;if it gets here that means it was successful
        ;jump to where the file is located and run it
        
        call Print_ln
        MOV AX, ES
        call itoa
        
        
        mov AL, ':'
        MOV AH, 0xE
        INT 0x010
        
        

        MOV AX, DI
        call itoa
        
        call Print_ln
        ;call clear
        mov dl, [CDDriveNumber]

        push    0x200
        push    0x000
        retf
         
        
        
        .FAIL:;it failed so print that the file wasn't found and halt the system
        ;call Print_ln
        Print FILE_NOT_FOUND, RED
        cli
        hlt
                 
ret
main:
        ;first stage of bootloader is loaded at the address 0x07c0:0x0
        ;second stage of bootloader is loaded at address 0x5000:0x0
        cli  
        mov ax, 0x07c0
    mov ds, ax
    mov es, ax
    mov fs, ax
    mov gs, ax
    ;Set up Stack
        xor ax, ax
    mov ss, ax
    mov sp, 0xFFFE
        sti
        
        mov     [CDDriveNumber],dl
        call clear


        Print W_MSG, TEAL;prints the loading message in colour
        Print DOTS, PURPLE
        call Print_ln
        call Print_ln
        
        Print BOOT_MSG, TEAL
        call Print_ln
        
        
        Print BootInfoPrimVolDescr_MSG, TEAL
        MOV AX, WORD[BootInfoPrimVolDescr]
        call itoa
        call Print_ln
        
        Print BootInfoFileLoc_MSG, TEAL
        MOV AX,  WORD[BootInfoFileLoc]
        call itoa
        call Print_ln
        
        Print BootInfoFileLength_MSG, TEAL
        MOV AX, WORD[BootInfoFileLength]
        call itoa
        call Print_ln
        
        Print BootInfoChecksum_MSG, TEAL
        MOV AX, WORD[BootInfoChecksum]
        call itoa
        call Print_ln
        
        Print BootInfoReserved_MSG, TEAL
        MOV AX, WORD[BootInfoReserved]
        call itoa
        call Print_ln
        
        call Print_ln


        
        

        ;First find the Signature of the CD 
        Print Reading_Sectors, TEAL
        LOAD_SIGNATURE:
        mov cx, 0x04
        call Read_Sectors
        
        Print READ_SUCCESS, TEAL
        call Print_ln
        ;load the Volume descriptor to the Volume variable
        call CHECK_DESC
        ;Now Load the Root Directory from the Volume Descriptor
        LOAD_ROOT:
                ;Print Reading_Sectors, TEAL
                mov es, WORD[DiskAddressPacket.Segment]
                mov di, WORD[DiskAddressPacket.Offset]
                
                XOR BX, BX
                MOV BX, 40 ;move in the offset
                VolumeLabelLoop: 

                        MOV CL,[ES:DI+BX]                   ; Grab a letter 
                        CMP CL,' '                          ; Is it a space? (Assumes end of string is space, may run out) 
                        JE .VolumeLabelDone                 ; Yes, we are done 

                        MOV [VOLUME+BX-40],CL 
                        INC BX 
                        JMP VolumeLabelLoop                 ; Need to compare BX to length of Volume Label on CD (32?) 

                        .VolumeLabelDone: 
                                Print Reading_Sectors, TEAL
                                MOV byte [VOLUME+BX-40],0      ; End the string 

                                MOV EAX,[ES:DI+158]                 ; LBA of root directory, where all things start. 
                                ;MOV [DiskAddressPacket.End],EAX     ; Load packet with new address on CD of the root directory 
                                MOV [DiskAddressPacket.End],EAX     ; Load packet with new address on CD of the root directory 
                                xor cx, cx
                                mov cx, 0x04
                                call Read_Sectors
                                                     
                                
                                Print READ_SUCCESS, TEAL;if the program gets here it means it was a success
                                call Print_ln
                                
LOAD_STAGE2:
                
        call READ_STAGE2
                
                
                .FAILURE:
                Print FILE_NOT_FOUND, RED
                cli
                hlt
                
                
                                        
CDDriveNumber:                          db              0x080
CD_Signature:                           db      "CD001"
CD_FILE_VER:                            db      0x01
CD_FileNameLength:                      db              0x0
CD_dir_curr_size:                       db              0x0
Reading_Sectors:                        db              "Reading sectors", 0
CHECK_DESC_MSG:                         db              "Checking for CD Signature",0
LOADING_STAGE2_MSG:                     db              "Loading Stage 2 of boot loader",0
STAGE_2_LEN:                            DW              0xC
File_Found:                                     db              "File for Stage 2 of the bootloader was found!!",0
LOADING_STAGE2_FAILED:          db      "Failed to load Stage 2 of the boot loader !!!!!",0
Found_Possible_FILE:            db              "Found Possible File: ",0
Colon:                                          db              ":",0
FILE_ENTRY:                                     db              0
JolietSig                               DB      25h, 2fh, 45h                               ; this is the value of the escape sequence for a Joliet CD 
BOOT_MSG:                                       DB              "Boot Info Table:", 0                           
DOTS:                                           db              ".....",0       
                                        ;Disk Address Packet                            
DiskAddressPacket:          db 0x010,0                                            
.SectorsToRead:             dw 1                              ; Number of sectors to read (read size of OS) 
.Offset:                    dw 0                              ; Offset :0000h
.Segment:                   dw 0x0200                         ; Segment 01000h
.End:                       dq 0x010                             ; Sector 16 or 10h on CD-ROM 

VOLUME:                                         DW 0
BootInfoPrimVolDescr_MSG:       db "Volume Descriptor: ", 0
BootInfoFileLoc_MSG         db "File Location:     ", 0  
BootInfoFileLength_MSG          db "File Length:       ", 0
BootInfoChecksum_MSG            db "Checksum:          ", 0
BootInfoReserved_MSG        db "Reserved:          ", 0                                 
W_MSG:                                          db "Loading Z-Boot", 0
STAGE2:                                         db "STAGE2.BIN;1"
Read_Sector_Error_MSG:          db "Error, failed to read sector",0
READ_SUCCESS:                           db "Sectors read correctly!",0
Progress_MSG:                           db ".",0
FILE_NOT_FOUND:                         db "Error, file not found!",0
FOUND_CD:                                       db "Found the CD Signature!", 0
times 2046 - ($ - $$)           db 0; padd out the rest of the file to 0









                                                        
                                                        
                                                        
                                                        
                                                        
                                                        
                                                        
    

Stage 2
Code:

[BITS 16] 
org 0x2000 

Start: 

 jmp  main 
;;;;;;;;;;;;;;;;;; 
;                                ; 
;                                ; 
;    Constants   ; 
;                                ; 
;;;;;;;;;;;;;;;;;; 
%DEFINE TEAL 0x03 
%DEFINE RED 0x04 
%DEFINE PURPLE 0x05 
%DEFINE VIDEO_MEM 0xB8000 
%DEFINE COLS    80                      ; width and height of screen 
%DEFINE LINES   25 
%DEFINE LONG_SELECTOR  3 << 3 

X_POS:  db 0 
Y_POS:  db 0 


;;;;;;;;;;;;;;;;;; 
;    Enabling    ; 
;    The A20     ; 
;         line           ; 
;;;;;;;;;;;;;;;;;; 
EnableA20: 

    IN AL, 0x92         ; A20, using fast A20 gate 
    MOV CL, AL 
    AND CL, 2 
    JNZ .skip            ; if a20 bit seems set, don't touch it 
    OR AL, 2 
    OUT 0x92, AL 
    .skip: 

ret 



         



main:            
;first stage of bootloader is loaded at the address 0x07c0:0 
        ;second stage of bootloader is loaded at address 0x200:0x0 
         
         
        cli 
   xor ax, ax         ; All segments set to 0, flat memory model 
   mov ds, ax 
   mov es, ax 
   mov gs, ax 
   mov fs, ax 
   mov ss, ax 
   ; 
   ; Set stack top SS:0xffff 
   ; 
   mov sp, 0x0FFFF 
   ; 


        mov [CDDriveNumber], dl 
         
        SwitchToProtectedMode: 
         
        lgdt [GDT_32];load the gdt 
        call EnableA20 
   
         
        mov eax, cr0 
        or eax, 1 
        mov cr0, eax 
         
         
         ; Flush CS and set code selector 
   ; 
        jmp 0x8:Protected_Mode 
         
        [BITS 32];Declare 32 bits 
         
        Protected_Mode: 
         
         
         
        mov     eax,0x10        ; load 4 GB data descriptor
                mov     ds,ax                   ; to all data segment registers
                mov     es,ax
                mov     fs,ax
                mov     gs,ax
                mov     ss,ax

                mov     eax,cr4
                or      eax,1 << 5
                mov     cr4,eax                 ; enable physical-address extensions

                mov     edi,70000h
                mov     ecx,4000h >> 2
                xor     eax,eax
                rep     stosd                   ; clear the page tables

                mov     dword [70000h],71000h + 111b ; first PDP table
                mov     dword [71000h],72000h + 111b ; first page directory
                mov     dword [72000h],73000h + 111b ; first page table

                mov     edi,73000h              ; address of first page table
                mov     eax,0 + 111b
                mov     ecx,256                 ; number of pages to map (1 MB)
        make_page_entries:
                stosd
                add     edi,4
                add     eax,1000h
                loop    make_page_entries

                mov     eax,70000h
                mov     cr3,eax                 ; load page-map level-4 base

                mov     ecx,0C0000080h          ; EFER MSR
                rdmsr
                or      eax,1 << 8              ; enable long mode
                wrmsr
                lgdt[GDT_64]
                mov     eax,cr0
                or      eax,1 << 31
                mov     cr0,eax                 ; enable paging

        jmp 0x08:Long_Mode 
        [BITS 64] 
         
         
        Long_Mode: 
         
        xor bx, bx 
        mov bx, Entered_LMODE 
        call sPrint 
         
         
         
         
         
         
        cli 
        hlt 
        [BITS 32] 
        clear: 
         
        pusha 
        mov edi, VIDEO_MEM 
        mov BYTE[edi], ' ' 
        mov BYTE[edi+1], TEAL
        rep stosw 
        MOV BYTE[X_POS], 0x0 
        MOV BYTE [Y_POS], 0x0 
        popa 
        ret 
         
        sPrint: 
        pusha 
                jmp .start 
                .Row: 
                call NewLine 
                MOV BYTE[EDI], ' ' 
                jmp .Next 
                .start: 
                MOV EDI, VIDEO_MEM 
                xor ecx, ecx 
                xor eax, eax 
                mov     ecx, COLS*2             ; Mode 7 has 2 bytes per char, so its COLS*2 bytes per line 
                mov     al, BYTE [Y_POS]        ; get y pos 
                mul     ecx                     ; multiply y*COLS 
                push    eax                     ; save eax--the multiplication 
                  
                mov     al, byte [X_POS]        ; multiply _CurX by 2 because it is 2 bytes per char 
                mov     cl, 2 
                mul     cl 
                pop     ecx                     ; pop y*COLS result 
                add     eax, ecx 
                 
                 
                add edi, eax 
                mov al,BYTE[bx] 
                 
                cmp al, 0x0;check if end 
                je .Done 
                cmp al, 0xA;check if new line 
                je .Row 
                 
                mov BYTE[edi],al  
                .Next: 
                mov BYTE[edi+1], PURPLE
                INC BX 
                inc     BYTE[X_POS]             ; go to next character 
                cmp     BYTE[X_POS], COLS               ; are we at the end of the line? 
                je      .Row                    ; yep-go to next row 
                 
                 
                jmp .start 
        .Done: 
         
         
        popa 
         
        ret 
        NewLine: 
        inc BYTE[Y_POS] 
        MOV BYTE[X_POS], -1 
         
        ret 
Entered_PMODE:  db "You have succcessfully entered Protected Mode Very Happy",0xA, 0 
LOAD_SUCCESS:   db "Stage 2 Loaded Successfully",0xA, 0 
CDDriveNumber:  db 0 
Entered_LMODE:  db "You have successfully entered Long Mode Very Happy !!!!!!!!!!!",0xA,0 


GDT_START: 
;null descriptor 
dd 0 
dd 0 
;data descriptor 
dw 0xFFFF 
dw 0 
db 0 
db 10011010b 
db 11001111b 
db 0 
;code descriptor 
dw 0xFFFF 
dw 0 
db 0 
db 10010010b 
db 11001111b 
db 0 
GDT_END: 
align 4 
GDT_32: 
dw GDT_END - GDT_START - 1 
dd GDT_START 



GDT_64: 
.Null: 
    dq 0x0000000000000000             ; Null Descriptor - should be present. 
  
.Code_64: 
    dq 0x0020980000000000             ; 64-bit code descriptor.  
    dq 0x0000900000000000             ; 64-bit data descriptor.  
.Pointer: 
    dw $ - GDT_64 - 1                    ; 16-bit Size (Limit) of GDT. 
    dd GDT_64                            ; 32-bit Base Address of GDT. (CPU will zero extend to 64-bit) 

         
         
         
ALIGN 4 
IDT: 
    .Length       dw 0 
    .Base         dd 0 

PML4_POINTER:;blank table 
        dd 0                                                                             
PML4_POINTER_END: 
table_768: dd 0 




    

for me shl doesen't work I have to use those operators instead They do the same thing I need to convert to fasm I am using nasm that's why I haven't been using complete code for me when I use the shl instruction it like shl ax, 2

_________________
Thanks in advance
Post 08 Aug 2014, 13:05
View user's profile Send private message Reply with quote
AnonymousUser



Joined: 25 Jul 2014
Posts: 32
AnonymousUser 08 Aug 2014, 13:36
The Problem seems to be happening when I enable paging here:
Code:
                mov     eax,cr0
                or      eax,1 shl 31
                mov     cr0,eax                 ; enable paging
    





the gdt seems to go back to address 0x0 for some reason and
Code:

cr0 = 0xe0000011 
cr2 = 0x0
cr3 = 0x0070000
cr4 = 0x0000020
EIP = 0x000020c1

    

That must mean something is wrong with my page table but I have no Idea what is I did it exactly as it was in the example

_________________
Thanks in advance
Post 08 Aug 2014, 13:36
View user's profile Send private message Reply with quote
AnonymousUser



Joined: 25 Jul 2014
Posts: 32
AnonymousUser 09 Aug 2014, 16:27
I figured out what it was The problem was that I was using the 32 bit functions in 64 bit and I forgot to use lgdt[GDT_64.Pointer] thanks for the help anyways guys
Post 09 Aug 2014, 16:27
View user's profile Send private message Reply with quote
smiddy



Joined: 31 Oct 2004
Posts: 557
smiddy 11 Aug 2014, 14:11
Smile
Post 11 Aug 2014, 14:11
View user's profile Send private message Reply with quote
Display posts from previous:
Post new topic Reply to topic

Jump to:  


< Last Thread | Next Thread >
Forum Rules:
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum
You cannot attach files in this forum
You can download files in this forum


Copyright © 1999-2024, Tomasz Grysztar. Also on GitHub, YouTube.

Website powered by rwasa.