VirtualBox

忽略:
時間撮記:
2016-3-7 下午11:15:22 (9 年 以前)
作者:
vboxsync
訊息:

bs3kit: Updates thowards v8086.

位置:
trunk/src/VBox/ValidationKit/bootsectors/bs3kit
檔案:
修改 21 筆資料

圖例:

未更動
新增
刪除
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-SwitchTo16Bit.asm

    r59934 r59949  
    4343        mov     ax, seg g_bBs3CurrentMode
    4444        mov     ds, ax
    45         mov     al, [g_bBs3CurrentMode]
     45        mov     al, [BS3_DATA16_WRT(g_bBs3CurrentMode)]
    4646        and     al, BS3_MODE_CODE_MASK
    4747        cmp     al, BS3_MODE_CODE_V86
     
    9999
    100100        ; Update globals.
    101         and     byte [g_bBs3CurrentMode], ~BS3_MODE_CODE_MASK
    102         or      byte [g_bBs3CurrentMode], BS3_MODE_CODE_16
     101        and     byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], ~BS3_MODE_CODE_MASK
     102        or      byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], BS3_MODE_CODE_16
    103103
    104104        popfd
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-SwitchTo16BitV86.asm

    r59941 r59949  
    4343        ; Construct basic v8086 return frame.
    4444        BS3_ONLY_16BIT_STMT movzx   esp, sp
    45         push    dword 0                         ; +0x20: GS
    46         push    dword 0                         ; +0x1c: FS
    47         push    dword BS3_SEL_DATA16            ; +0x18: ES
    48         push    dword BS3_SEL_DATA16            ; +0x14: DS
    49         push    dword 0                         ; +0x10: SS - later
    50         push    dword 0                         ; +0x0c: return ESP, later.
     45        push    dword 0                                 ; +0x20: GS
     46        push    dword 0                                 ; +0x1c: FS
     47        push    dword BS3_SEL_DATA16                    ; +0x18: ES
     48        push    dword BS3_SEL_DATA16                    ; +0x14: DS
     49        push    dword 0                                 ; +0x10: SS - later
     50        push    dword 0                                 ; +0x0c: return ESP, later.
    5151        pushfd
    52         or      dword [esp], X86_EFL_VM         ; +0x08: Set the VM flag in EFLAGS.
    53         push    dword BS3_SEL_TEXT16            ; +0x04
     52        or      dword [esp], X86_EFL_VM | X86_EFL_IOPL  ; +0x08: Set IOPL=3 and the VM flag (EFLAGS).
     53        push    dword BS3_SEL_TEXT16                    ; +0x04
    5454        push    word 0
    5555 %if TMPL_BITS == 16
    56         push    word [esp + 2 + 8 * 4 + 2]      ; +0x00
     56        push    word [esp + 2 + 8 * 4 + 2]              ; +0x00
    5757 %else
    58         push    word [esp + 2 + 8 * 4]          ; +0x00
     58        push    word [esp + 2 + 8 * 4]                  ; +0x00
    5959 %endif
    6060        ; Save registers and stuff.
     
    6969        mov     ax, seg g_bBs3CurrentMode
    7070        mov     ds, ax
    71         mov     al, [g_bBs3CurrentMode]
     71        mov     al, [BS3_DATA16_WRT(g_bBs3CurrentMode)]
    7272        and     al, BS3_MODE_CODE_MASK
    7373        cmp     al, BS3_MODE_CODE_V86
     
    9191        jz      .is_ring0
    9292        call    Bs3SwitchToRing0
     93 %if TMPL_BITS == 16
     94        mov     ax, seg g_bBs3CurrentMode
     95        mov     ds, ax                  ; parnoia
     96 %endif
    9397.is_ring0:
    9498
    9599        ; Update globals.
    96         and     byte [g_bBs3CurrentMode], ~BS3_MODE_CODE_MASK
    97         or      byte [g_bBs3CurrentMode], BS3_MODE_CODE_16
     100        and     byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], ~BS3_MODE_CODE_MASK
     101        or      byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], BS3_MODE_CODE_V86
    98102
    99103 %if TMPL_BITS != 16
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-SwitchTo32Bit.asm

    r59941 r59949  
    6161        mov     ax, seg g_bBs3CurrentMode
    6262        mov     ds, ax
    63         mov     al, [g_bBs3CurrentMode]
     63        mov     al, [BS3_DATA16_WRT(g_bBs3CurrentMode)]
    6464        and     al, BS3_MODE_CODE_MASK
    6565        cmp     al, BS3_MODE_CODE_V86
     
    128128
    129129        ; Update globals.
    130         and     byte [g_bBs3CurrentMode], ~BS3_MODE_CODE_MASK
    131         or      byte [g_bBs3CurrentMode], BS3_MODE_CODE_32
     130        and     byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], ~BS3_MODE_CODE_MASK
     131        or      byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], BS3_MODE_CODE_32
    132132
    133133 %if TMPL_BITS == 16
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-SwitchTo64Bit.asm

    r59934 r59949  
    5858        ; Check that this is LM16
    5959        mov     ax, seg g_bBs3CurrentMode
    60         cmp     byte [g_bBs3CurrentMode], BS3_MODE_LM16
     60        cmp     byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], BS3_MODE_LM16
    6161        je      .ok_lm16
    6262        int3
     
    9090
    9191        ; Update globals.
    92         and     byte [BS3_WRT_RIP(g_bBs3CurrentMode)], ~BS3_MODE_CODE_MASK
    93         or      byte [BS3_WRT_RIP(g_bBs3CurrentMode)], BS3_MODE_CODE_64
     92        and     byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], ~BS3_MODE_CODE_MASK
     93        or      byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], BS3_MODE_CODE_64
    9494
    9595 %if TMPL_BITS == 16
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-SwitchToRing0.asm

    r59287 r59949  
    55
    66;
    7 ; Copyright (C) 2007-2015 Oracle Corporation
     7; Copyright (C) 2007-2016 Oracle Corporation
    88;
    99; This file is part of VirtualBox Open Source Edition (OSE), as
     
    2727%include "bs3kit-template-header.mac"
    2828
     29
     30%if TMPL_BITS == 16
     31BS3_EXTERN_DATA16 g_bBs3CurrentMode
     32%endif
     33TMPL_BEGIN_TEXT
     34
     35
    2936;;
    3037; @cproto   BS3_DECL(void) Bs3SwitchToRing0(void);
     
    3340;
    3441BS3_PROC_BEGIN_CMN Bs3SwitchToRing0
    35         push    sAX
     42        push    xAX
    3643
    3744%if TMPL_BITS == 16
    38         smsw    ax
    39         test    ax, X86_CR0_PE
    40         jz      .return                 ; real mode.
     45        ; Check the current mode.
     46        push    ds
     47        mov     ax, seg g_bBs3CurrentMode
     48        mov     ds, ax
     49        mov     al, [BS3_DATA16_WRT(g_bBs3CurrentMode)]
     50        pop     ds
     51
     52        ; If real mode: Nothing to do, it's considered ring-0 here.
     53        cmp     al, BS3_MODE_RM
     54        je      .return
     55
     56        ; If V8086 mode: Have to make the system call (v8086 mode is ring-3).
     57        and     al, BS3_MODE_CODE_MASK
     58        cmp     al, BS3_MODE_CODE_V86
     59        je      .just_do_it
    4160%endif
     61
     62        ; In protected mode: Check the CPL we're currently at skip syscall if ring-0 already.
    4263        mov     ax, cs
    4364        test    ax, 3
    4465        jz      .return
    4566
    46         mov     eax, BS3_SYSCALL_TO_RING0
     67.just_do_it:
     68        mov     xAX, BS3_SYSCALL_TO_RING0
    4769        int     BS3_TRAP_SYSCALL
    4870
    4971.return:
    50         pop     sAX
     72        pop     xAX
    5173        ret
    5274BS3_PROC_END_CMN   Bs3SwitchToRing0
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-SwitchToRing1.asm

    r59287 r59949  
    55
    66;
    7 ; Copyright (C) 2007-2015 Oracle Corporation
     7; Copyright (C) 2007-2016 Oracle Corporation
    88;
    99; This file is part of VirtualBox Open Source Edition (OSE), as
     
    2727%include "bs3kit-template-header.mac"
    2828
     29
     30%if TMPL_BITS == 16
     31BS3_EXTERN_DATA16 g_bBs3CurrentMode
     32%endif
     33TMPL_BEGIN_TEXT
     34
     35
    2936;;
    3037; @cproto   BS3_DECL(void) Bs3SwitchToRing1(void);
     
    3340;
    3441BS3_PROC_BEGIN_CMN Bs3SwitchToRing1
    35         push    sAX
     42        push    xAX
    3643
     44%if TMPL_BITS == 16
     45        ; Check the current mode.
     46        push    ds
     47        mov     ax, seg g_bBs3CurrentMode
     48        mov     ds, ax
     49        mov     al, [BS3_DATA16_WRT(g_bBs3CurrentMode)]
     50        pop     ds
     51
     52        ; If real mode: assert, shouldn't call this function in real mode!
     53        cmp     al, BS3_MODE_RM
     54        jne     .not_real_mode
     55        int3
     56        jmp     .return
     57.not_real_mode:
     58
     59        ; If V8086 mode: Have to make the system call (v8086 mode is kind of like ring-3).
     60        and     al, BS3_MODE_CODE_MASK
     61        cmp     al, BS3_MODE_CODE_V86
     62        je      .just_do_it
     63%endif
     64
     65        ; In protected mode: Check the CPL we're currently at skip syscall if ring-1 already.
    3766        mov     ax, cs
    3867        and     ax, 3
     
    4069        je      .return
    4170
    42         mov     eax, BS3_SYSCALL_TO_RING1
     71.just_do_it:
     72        mov     xAX, BS3_SYSCALL_TO_RING1
    4373        int     BS3_TRAP_SYSCALL
    4474
    4575.return:
    46         pop     sAX
     76        pop     xAX
    4777        ret
    4878BS3_PROC_END_CMN   Bs3SwitchToRing1
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-SwitchToRing2.asm

    r59287 r59949  
    55
    66;
    7 ; Copyright (C) 2007-2015 Oracle Corporation
     7; Copyright (C) 2007-2016 Oracle Corporation
    88;
    99; This file is part of VirtualBox Open Source Edition (OSE), as
     
    2727%include "bs3kit-template-header.mac"
    2828
     29
     30%if TMPL_BITS == 16
     31BS3_EXTERN_DATA16 g_bBs3CurrentMode
     32%endif
     33TMPL_BEGIN_TEXT
     34
     35
    2936;;
    3037; @cproto   BS3_DECL(void) Bs3SwitchToRing2(void);
     
    3340;
    3441BS3_PROC_BEGIN_CMN Bs3SwitchToRing2
    35         push    sAX
     42        push    xAX
    3643
     44%if TMPL_BITS == 16
     45        ; Check the current mode.
     46        push    ds
     47        mov     ax, seg g_bBs3CurrentMode
     48        mov     ds, ax
     49        mov     al, [BS3_DATA16_WRT(g_bBs3CurrentMode)]
     50        pop     ds
     51
     52        ; If real mode: assert, shouldn't call this function in real mode!
     53        cmp     al, BS3_MODE_RM
     54        jne     .not_real_mode
     55        int3
     56        jmp     .return
     57.not_real_mode:
     58
     59        ; If V8086 mode: Have to make the system call (v8086 mode is kind of like ring-3).
     60        and     al, BS3_MODE_CODE_MASK
     61        cmp     al, BS3_MODE_CODE_V86
     62        je      .just_do_it
     63%endif
     64
     65        ; In protected mode: Check the CPL we're currently at skip syscall if ring-2 already.
    3766        mov     ax, cs
    3867        and     ax, 3
     
    4069        je      .return
    4170
    42         mov     eax, BS3_SYSCALL_TO_RING2
     71.just_do_it:
     72        mov     xAX, BS3_SYSCALL_TO_RING2
    4373        int     BS3_TRAP_SYSCALL
    4474
    4575.return:
    46         pop     sAX
     76        pop     xAX
    4777        ret
    4878BS3_PROC_END_CMN   Bs3SwitchToRing2
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-SwitchToRing3.asm

    r59287 r59949  
    55
    66;
    7 ; Copyright (C) 2007-2015 Oracle Corporation
     7; Copyright (C) 2007-2016 Oracle Corporation
    88;
    99; This file is part of VirtualBox Open Source Edition (OSE), as
     
    2727%include "bs3kit-template-header.mac"
    2828
     29
     30%if TMPL_BITS == 16
     31BS3_EXTERN_DATA16 g_bBs3CurrentMode
     32%endif
     33TMPL_BEGIN_TEXT
     34
     35
    2936;;
    3037; @cproto   BS3_DECL(void) Bs3SwitchToRing3(void);
     
    3340;
    3441BS3_PROC_BEGIN_CMN Bs3SwitchToRing3
    35         push    sAX
     42        push    xAX
    3643
     44%if TMPL_BITS == 16
     45        ; Check the current mode.
     46        push    ds
     47        mov     ax, seg g_bBs3CurrentMode
     48        mov     ds, ax
     49        mov     al, [BS3_DATA16_WRT(g_bBs3CurrentMode)]
     50        pop     ds
     51
     52        ; If real mode: assert, shouldn't call this function in real mode!
     53        cmp     al, BS3_MODE_RM
     54        jne     .not_real_mode
     55        int3
     56        jmp     .return
     57.not_real_mode:
     58
     59        ; If V8086 mode: Have to make the system call (we don't consider v8086 ring-3 here).
     60        and     al, BS3_MODE_CODE_MASK
     61        cmp     al, BS3_MODE_CODE_V86
     62        je      .just_do_it
     63%endif
     64
     65        ; In protected mode: Check the CPL we're currently at skip syscall if ring-3 already.
    3766        mov     ax, cs
    3867        and     ax, 3
     
    4069        je      .return
    4170
    42         mov     eax, BS3_SYSCALL_TO_RING3
     71.just_do_it:
     72        mov     xAX, BS3_SYSCALL_TO_RING3
    4373        int     BS3_TRAP_SYSCALL
    4474
    4575.return:
    46         pop     sAX
     76        pop     xAX
    4777        ret
    4878BS3_PROC_END_CMN   Bs3SwitchToRing3
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-TestSendCmdWithStr.asm

    r59863 r59949  
    4343        BS3_ONLY_16BIT_STMT push ds
    4444
    45         cmp     byte [g_fbBs3VMMDevTesting], 0
     45        mov     ax, seg g_fbBs3VMMDevTesting
     46        mov     ds, ax
     47        cmp     byte [BS3_DATA16_WRT(g_fbBs3VMMDevTesting)], 0
    4648        je      .no_vmmdev
    4749
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-cmn-TestSendCmdWithU32.asm

    r59863 r59949  
    4242        push    xSI
    4343
    44         cmp     byte [g_fbBs3VMMDevTesting], 0
     44        BS3_ONLY_16BIT_STMT push ds
     45        mov     ax, seg g_fbBs3VMMDevTesting
     46        mov     ds, ax
     47        cmp     byte [BS3_DATA16_WRT(g_fbBs3VMMDevTesting)], 0
     48        BS3_ONLY_16BIT_STMT pop  ds
    4549        je      .no_vmmdev
    4650
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-mode-CpuDetect.asm

    r59945 r59949  
    245245        BS3_ONLY_16BIT_STMT mov     bx, seg g_uBs3CpuDetected
    246246        BS3_ONLY_16BIT_STMT mov     ds, bx
    247         mov     [g_uBs3CpuDetected], ax
     247        mov     [BS3_DATA16_WRT(g_uBs3CpuDetected)], ax
    248248        BS3_ONLY_16BIT_STMT pop     ds
    249249
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-mode-EnteredMode.asm

    r59941 r59949  
    172172        ; Set global indicating CPU mode.
    173173        ;
    174         mov     byte [BS3_WRT_RIP(g_bBs3CurrentMode)], TMPL_MODE
     174        mov     byte [BS3_DATA16_WRT(g_bBs3CurrentMode)], TMPL_MODE
    175175
    176176        ;
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-mode-PagingGetRootForLM64.asm

    r59941 r59949  
    5555        BS3_ONLY_16BIT_STMT push    BS3DATA16
    5656        BS3_ONLY_16BIT_STMT pop     ds
    57         mov     eax, [g_PhysPagingRootLM TMPL_WRT_DATA16_OR_FLAT]
     57        mov     eax, [BS3_DATA16_WRT(g_PhysPagingRootLM)]
    5858        BS3_ONLY_16BIT_STMT pop     ds
    5959        cmp     eax, 0ffffffffh
     
    9696        BS3_ONLY_16BIT_STMT push    BS3DATA16
    9797        BS3_ONLY_16BIT_STMT pop     ds
    98         mov     eax, [g_PhysPagingRootLM TMPL_WRT_DATA16_OR_FLAT]
     98        mov     eax, [BS3_DATA16_WRT(g_PhysPagingRootLM)]
    9999
    100100        BS3_ONLY_16BIT_STMT pop     ds
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-mode-PagingGetRootForPAE32.asm

    r59941 r59949  
    5555        BS3_ONLY_16BIT_STMT push    BS3DATA16
    5656        BS3_ONLY_16BIT_STMT pop     ds
    57         mov     eax, [g_PhysPagingRootPAE TMPL_WRT_DATA16_OR_FLAT]
     57        mov     eax, [BS3_DATA16_WRT(g_PhysPagingRootPAE)]
    5858        BS3_ONLY_16BIT_STMT pop     ds
    5959        cmp     eax, 0ffffffffh
     
    9797        BS3_ONLY_16BIT_STMT push    BS3DATA16
    9898        BS3_ONLY_16BIT_STMT pop     ds
    99         mov     eax, [g_PhysPagingRootPAE TMPL_WRT_DATA16_OR_FLAT]
     99        mov     eax, [BS3_DATA16_WRT(g_PhysPagingRootPAE)]
    100100
    101101        BS3_ONLY_16BIT_STMT pop     ds
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-mode-PagingGetRootForPP32.asm

    r59941 r59949  
    5555        BS3_ONLY_16BIT_STMT push    BS3DATA16
    5656        BS3_ONLY_16BIT_STMT pop     ds
    57         mov     eax, [g_PhysPagingRootPP TMPL_WRT_DATA16_OR_FLAT]
     57        mov     eax, [BS3_DATA16_WRT(g_PhysPagingRootPP)]
    5858        BS3_ONLY_16BIT_STMT pop     ds
    5959        cmp     eax, 0ffffffffh
     
    9797        BS3_ONLY_16BIT_STMT push    BS3DATA16
    9898        BS3_ONLY_16BIT_STMT pop     ds
    99         mov     eax, [g_PhysPagingRootPP TMPL_WRT_DATA16_OR_FLAT]
     99        mov     eax, [BS3_DATA16_WRT(g_PhysPagingRootPP)]
    100100
    101101        BS3_ONLY_16BIT_STMT pop     ds
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-mode-SwitchToPAE16.asm

    r59287 r59949  
    8989
    9090        ;
    91         ; Make sure both PAE and PSE are enabled (requires pentium pro).
    92         ;
    93         mov     eax, cr4
    94         mov     ecx, eax
    95         or      eax, X86_CR4_PAE | X86_CR4_PSE
    96         cmp     eax, ecx
    97         je      .cr4_is_fine
    98         mov     cr4, eax
    99 .cr4_is_fine:
    100 
    101         ;
    10291        ; Get the page directory (returned in eax).
    10392        ; Will lazy init page tables (in 16-bit prot mode).
     
    10897        cli
    10998        mov     cr3, eax
     99
     100        ;
     101        ; Make sure PAE, PSE, and VME are enabled (former two require pentium pro, latter 486).
     102        ;
     103        mov     eax, cr4
     104        mov     ecx, eax
     105        or      eax, X86_CR4_PAE | X86_CR4_PSE | X86_CR4_VME
     106        cmp     eax, ecx
     107        je      .cr4_is_fine
     108        mov     cr4, eax
     109.cr4_is_fine:
    110110
    111111        ;
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-mode-SwitchToPAE32.asm

    r59287 r59949  
    7676
    7777        ;
    78         ; Make sure both PAE and PSE are enabled (requires pentium pro).
    79         ;
    80         mov     eax, cr4
    81         mov     ecx, eax
    82         or      eax, X86_CR4_PAE | X86_CR4_PSE
    83         cmp     eax, ecx
    84         je      .cr4_is_fine
    85         mov     cr4, eax
    86 .cr4_is_fine:
    87 
    88         ;
    8978        ; Get the page directory (returned in eax).
    9079        ; Will lazy init page tables (in 16-bit prot mode).
     
    9584        cli
    9685        mov     cr3, eax
     86
     87        ;
     88        ; Make sure PAE, PSE, and VME are enabled (former two require pentium pro, latter 486).
     89        ;
     90        mov     eax, cr4
     91        mov     ecx, eax
     92        or      eax, X86_CR4_PAE | X86_CR4_PSE | X86_CR4_VME
     93        cmp     eax, ecx
     94        je      .cr4_is_fine
     95        mov     cr4, eax
     96.cr4_is_fine:
    9797
    9898        ;
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-mode-SwitchToRM.asm

    r59934 r59949  
    3131BS3_EXTERN_DATA16 g_uBs3CpuDetected
    3232%endif
     33
    3334TMPL_BEGIN_TEXT
    3435
     
    5051        ret
    5152
     53%elif BS3_MODE_IS_V86(TMPL_MODE)
     54        ;
     55        ; V8086 - Switch to 16-bit ring-0 and call worker for that mode.
     56        ;
     57        extern  BS3_CMN_NM(Bs3SwitchToRing0)
     58        call    BS3_CMN_NM(Bs3SwitchToRing0)
     59
     60 %if   TMPL_MODE == BS3_MODE_PE16_V86
     61        extern  _Bs3SwitchToRM_pe16
     62        jmp     _Bs3SwitchToRM_pe16
     63 %elif TMPL_MODE == BS3_MODE_PEV86
     64        extern  _Bs3SwitchToRM_pe32_16
     65        jmp     _Bs3SwitchToRM_pe32_16
     66 %elif TMPL_MODE == BS3_MODE_PP16_V86
     67        extern  _Bs3SwitchToRM_pp16
     68        jmp     _Bs3SwitchToRM_pp16
     69 %elif TMPL_MODE == BS3_MODE_PPV86
     70        extern  _Bs3SwitchToRM_pp32_16
     71        jmp     _Bs3SwitchToRM_pp32_16
     72 %elif TMPL_MODE == BS3_MODE_PAE16_V86
     73        extern  _Bs3SwitchToRM_pae16
     74        jmp     _Bs3SwitchToRM_pae16
     75 %elif TMPL_MODE == BS3_MODE_PAEV86
     76        extern  _Bs3SwitchToRM_pae32_16
     77        jmp     _Bs3SwitchToRM_pae32_16
     78 %else
     79  %error "Unexpected TMPL_MODE=" TMPL_MODE
     80 %endif
     81
    5282%else
     83        ;
     84        ; Protected mode.
     85        ;
    5386        push    sAX
    5487        push    sBX
     
    67100        ; On 80286 we must reset the CPU to get back to real mode.
    68101        ;
    69         mov     ax, seg g_uBs3CpuDetected
     102        mov     ax, BS3_SEL_DATA16
    70103        mov     ds, ax
    71         cmp     byte [g_uBs3CpuDetected], BS3CPU_80286
     104        cmp     byte [BS3_DATA16_WRT(g_uBs3CpuDetected)], BS3CPU_80286
    72105        jne     .is_386_or_better
    73106.implement_this_later:
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3-mode-TrapSystemCallHandler.asm

    r59287 r59949  
    149149        jmp     .return
    150150
     151
     152        ;
     153        ; Switch the caller to ring-0.
     154        ;
    151155.to_ring0:
    152156        int3
     157
    153158        jmp     .return
    154159
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3kit-template-header.mac

    r59946 r59949  
    408408%endif
    409409
     410;; @def TMPL_DATA16_WRT
     411; WRT DATA16 in 16-bit mode, WRT FLAT in 32- and 64-bit modes.
     412; This is important when accessing global variables.
     413;
     414%if TMPL_BITS == 16
     415 %define TMPL_DATA16_WRT(a_Var)     a_Var wrt BS3DATA16
     416%elif TMPL_BITS == 32
     417 %define TMPL_DATA16_WRT(a_Var)     a_Var wrt FLAT
     418%elif TMPL_BITS == 64
     419 %define TMPL_DATA16_WRT(a_Var)     rel a_Var wrt FLAT
     420%else
     421 %error TMPL_BITS
     422%endif
     423
    410424;; @def TMPL_WRT_SYSTEM16_OR_FLAT
    411425; WRT BS3SYSTEM16 in 16-bit mode, WRT FLAT in 32- and 64-bit modes.
  • trunk/src/VBox/ValidationKit/bootsectors/bs3kit/bs3kit.mac

    r59935 r59949  
    189189 %undef   BS3_WRT_RIP
    190190 %if %1 == 64
    191   %ifdef __YASM__
    192    %define BS3_WRT_RIP(a_Sym)       a_Sym wrt rip
    193   %else
    194    %define BS3_WRT_RIP(a_Sym)       rel a_Sym       ; Baka! Why couldn't they do 'wrt rip' like yasm?
    195   %endif
     191  %define BS3_WRT_RIP(a_Sym)        rel a_Sym
    196192 %else
    197193  %define BS3_WRT_RIP(a_Sym)        a_Sym
     
    203199 %else
    204200  %define BS3_LEA_MOV_WRT_RIP(a_DstReg, a_Sym)  mov a_DstReg, a_Sym
     201 %endif
     202
     203 ;; @def BS3_DATA16_WRT
     204 ; For accessing BS3DATA16 correctly.
     205 ; @param a_Var The BS3DATA16 variable.
     206 %undef BS3_DATA16_WRT
     207 %if %1 == 16
     208  %define BS3_DATA16_WRT(a_Var)     a_Var wrt BS3DATA16
     209 %elif %1 == 32
     210  %define BS3_DATA16_WRT(a_Var)     a_Var wrt FLAT
     211 %else
     212  %define BS3_DATA16_WRT(a_Var)     BS3_WRT_RIP(a_Var) wrt FLAT
    205213 %endif
    206214
注意: 瀏覽 TracChangeset 來幫助您使用更動檢視器

© 2024 Oracle Support Privacy / Do Not Sell My Info Terms of Use Trademark Policy Automated Access Etiquette