flat assembler
Message board for the users of flat assembler.

Index > Main > Mixing 16 and 32 bit program

Author
Thread Post new topic Reply to topic
Overflowz



Joined: 03 Sep 2010
Posts: 1044
Overflowz 12 May 2011, 20:48
hello everyone)) is that possible to mix 16 and 32 bit programs ? for example, I'm trying this but it's not working Sad
Code:
format PE CONSOLE 4.0
include 'WIN32AX.INC'
entry main
section '.data' data readable writeable
msg db "Hello World!",0
section '.text' code readable executable
proc main
     cinvoke printf,msg
use16
     mov al,9
     mov edx,msg
     int 0x21
     mov ax,0x4c00
     int 0x21
     ret
endp
section '.idata' import data readable
library msvcrt,'msvcrt.dll'
import msvcrt,printf,'printf'    

Thanks.
Post 12 May 2011, 20:48
View user's profile Send private message Reply with quote
edfed



Joined: 20 Feb 2006
Posts: 4358
Location: Now
edfed 12 May 2011, 20:57
to mix 16 and 32, you should create 16 and 32 bits descriptors, as windows don't let you do it manually, you can maybe use something like a system api.

every 16 bits sections should be called through a 16 bit descriptor. it is not an easy task.

but mixing 16bits code with 32 bits code is not a reasonable thing.
Post 12 May 2011, 20:57
View user's profile Send private message Visit poster's website Reply with quote
LocoDelAssembly
Your code has a bug


Joined: 06 May 2005
Posts: 4623
Location: Argentina
LocoDelAssembly 12 May 2011, 21:02
But even if you do what edfed says, Int21 won't be the DOS interrupt, you'll be calling whatever thing is hooked on that interrupt (if anything). If you are in a 32-bit system, your option could be creating COM files and execute them, or see it there is some hack to gain access to the ntvdm. Note that in my method you must make sure that the msg string is also included in the COM file and the addresses fixed to reference only stuff located in the COM file.
Post 12 May 2011, 21:02
View user's profile Send private message Reply with quote
edfed



Joined: 20 Feb 2006
Posts: 4358
Location: Now
edfed 12 May 2011, 21:29
oh! sorry, i didn't notices the int21h stuff, just the question mix 16 and 32 was enough to say it is not easy.
the correct question would be mix pm and rm code.
and then, the answer is:
impossible under windows.
possible under dos (with many swicthes).
if really you want to exacute real mode code under windows, use some .com code as stated by locodelassembly.
for that, you are not forced to create the .com code by hand, you can create it within the win32 program, save it as a xxx.com file, and shell execute it.
Post 12 May 2011, 21:29
View user's profile Send private message Visit poster's website Reply with quote
Overflowz



Joined: 03 Sep 2010
Posts: 1044
Overflowz 12 May 2011, 21:49
I got it. Thank you. Smile
Post 12 May 2011, 21:49
View user's profile Send private message Reply with quote
ouadji



Joined: 24 Dec 2008
Posts: 1080
Location: Belgium
ouadji 12 May 2011, 22:12
Quote:

to mix 16 and 32, you should create 16 and 32 bits descriptors, as windows don't let you do it manually,
you can maybe use something like a system api.
windows don't let you do it manually ? Laughing

of course that is possible, I did it under Windows XP Pro.
protected mode --> unprotected mode ( physical addressing)
--> real mode ( 16 bit code) --> and back to protected mode.
I even performed an interrupt in real mode (16 bits code with IDT below 1Mb)
Everything manually, no api. Create the necessary descriptors, change the page tables to have a memory space identity-mapped (for transition between virtual addressing and physical addressing) ... ... All this is absolutely possible without using Windows itself.

_________________
I am not young enough to know everything (Oscar Wilde)- Image


Last edited by ouadji on 12 May 2011, 22:14; edited 1 time in total
Post 12 May 2011, 22:12
View user's profile Send private message Send e-mail Reply with quote
edfed



Joined: 20 Feb 2006
Posts: 4358
Location: Now
edfed 12 May 2011, 22:14
cool, you seems to have a great talent in assembler.

i suppose you will participate the 512b contest and kickass?
Post 12 May 2011, 22:14
View user's profile Send private message Visit poster's website Reply with quote
ouadji



Joined: 24 Dec 2008
Posts: 1080
Location: Belgium
ouadji 12 May 2011, 22:22

just a little bit about it


Code:
;stdcall GoToPhysique, Go_XX, Go_YY
;---> (Go_XX/Go_YY) ---> proc PhysiqueToReal_16 (right below)

proc        GoToPhysique            Code_alpha:DWORD, Code_omega:DWORD
;===================
locals
   GoPhysique           dd ?
   MaPileLinéaire      dd ?
   CopieDataLinéaire   dd ?    ;début Adresse Linéaire Copie de mes Data
   CopieDataPhysique     dd ?
   SizeAllocLin         dd ?
   BaseAllocLin         dd ?    ;début "Linéaire" de ma zône d'allocation continue
   IDTR_Phys_addr   dd ?
endl

            pushad
              pushfd

          cld
         xor     eax,eax
             mov     [CptBoum],eax

           mov     [passageNP_a],eax
           mov     [passageNP_b],eax

;------------------------------------------------------------- "PAGE_SIZE" dans ntddk (= 0x1000)

             mov     ebx,[Code_omega]
            sub     ebx,[Code_alpha]
            lea     eax,[ebx + (Go_B - Go_A) + (Go_Z - Go_Y)]

               add     eax,PAGE_SIZE
               and     eax,not 0xFFF                           ;j'aligne sur une page complète

               mov     [CopieDataPhysique],eax                 ;adresse relative 1er octet pour mes Data.
          mov     [CopieDataLinéaire],eax

;——————————————————————————————————————————————————————————————————————————————

             lea     eax,[eax + EndData - StartData]

         add     eax,PAGE_SIZE                           ;le nb de pages pour mes Data.
              and     eax,not 0xFFF                           ;déplacement 1er octet de l'espace Pile.

;——————————————————————————————————————————————————————————————————————————————

           mov     [IDTR_Phys_addr],eax            ;IDTR(physique) à la base de la Pile(physique)

;——————————————————————————————————————————————————————————————————————————————

      sizeof.PilePhys equ 0xF00               ;J'ai 0xFF octets vers "le dessus" pour "[ebp + xx]"

               add     eax,sizeof.PilePhys     ;start relatif pour ma Pile.
                mov     [MaPileLinéaire],eax
               mov     [XS_._offset],eax
           
            add     eax,PAGE_SIZE
               and     eax,not 0xFFF

           mov     [SizeAllocLin],eax      ;Espace total nécessaire en bytes (multiple de 0x1000)
             
;——————————————————————————————————————————————————————————————————————————————
;Les calculs d'adresses ci-dessus sont "relatives", 
;il faut les "ajouter" à la "Base_adresse" d'allocation pour avoir les "Linéaire"
;et convertir pour avoir les "Physique".
;0x000FFFFF = 1Mo       0x80000000 = 2Go        0xC0000000 = 3Go
;——————————————————————————————————————————————————————————————————————————————

               mov     [BaseAllocLin],0

                invoke MmAllocateContiguousMemorySpecifyCache,eax,\
\
          0x00020000,0x00000000 ,\       ;LowestAcceptable       0x200F0000
          0x000FFFFF,0x00000000 ,\       ;HighestAcceptable      0xC0000000
          0,0,MmNonCached

         mov     [error_phys],0xBAD00001

         cmp     eax,NULL
            je      err_phys

mov [gloups],eax
            mov     [BaseAllocLin],eax              ;Base Alloc pour copie code/data et désalloc
               add     [MaPileLinéaire],eax           ;start Linéaire pour ma Pile
               add     [CopieDataLinéaire],eax        ;start Linéaire pour mes Data

;—— copie —————————————————————————————————————————————————————————————————————

/*Prologue*/ ;stop

           mov     edi,eax
             
            mov     esi,Go_A
            mov     ecx,Go_B - Go_A

         rep     movsb

/*Code Cible*/     mov     esi,[Code_alpha]
            mov     ecx,[Code_omega]
            sub     ecx,esi

         rep     movsb

/*Epilogue*/       mov     esi,Go_Y
            mov     ecx,Go_Z - Go_Y

         rep     movsb

;/*mes Data*/   mov     ecx,Sizeof.mesData
;               mov     esi,StartData
;               mov     edi,[CopieDataLinéaire]
;               rep     movsd

;——————————————————————————————————————————————————————————————————————————————
stop
            invoke  MmGetPhysicalAddress,eax

                mov     [GoPhysique],eax                ;start Physique ("Go_A")
          add     [XS_._offset],eax               ;start Physique pour ma Pile
                add     [IDTR_Phys_addr],eax            ;start IDTR Physique
                add     [CopieDataPhysique],eax         ;start Physique pour mes Data

;——————————————————————————————————————————————————————————————————————————————

                mov     eax,[CopieDataPhysique]
             sub     eax,StartData

           stdcall GetDescriptor, eax, 0xCF93

              mov     [error_phys],0xBAD00002

         or      eax,eax
             jnz     err_phys

;------------------------------------------------GDTR

           mov     esi,[MaPileLinéaire]           ;0x07FF 0x8003F400 (1µP) _xDT

          sgdt    fword[esi+08h]                  ;GDTR_Full_Lin

          mov     ax,[esi+08h]
                mov     [esi],ax                        ;GDTR_Physique(size)

            invoke  MmGetPhysicalAddress,\
                     dword[esi+0Ah]

          mov     [esi+02h],eax                   ;GDTR_Physique(address)

;------------------------------------------------IDTR

            sidt    fword[esi+18h]                  ;IDTR_Full_Lin

          mov     word[esi+10h],0xFF              ;IDTR_Physique(size)

            mov     eax,[IDTR_Phys_addr]            ;IDTR(Physique) = la base de la Pile(physique)
              mov     [esi+12h],eax                   ;IDTR_Physique(address)

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

                sub     [XS_._offset],0Ch + (2 * 04h)   ;(X * 04h) => "X" = nb de "push" en (ZZ)


             stdcall TablePage, [GoPhysique], 1, 0


               invoke  MmGetPhysicalAddress, arrayP    ;LockData
           mov     [esp+4],eax                     ;edi "derrière" le "pushfd"

boucle_phys:

;——————————————————————————————————————————————————————————————————————————————

/*Activite*/ mov     ecx,256/4
           xor     eax,eax
             mov     edi,Activite
           rep  stosd

/*mes Data*/       mov     ecx,Sizeof.mesData
          mov     esi,StartData
               mov     edi,[CopieDataLinéaire]
            rep     movsd

;——————————————————————————————————————————————————————————————————————————————
            mov     ebx,1
               cmp     [flag_table_hook],TRUE
              jne     abort_phys_a

            mov     ebx,2
               mov     eax,[GoPhysique]
            mov     eax,[eax]
           cmp     eax,[Go_A]
          jne     abort_phys_a
;——————————————————————————————————————————————————————————————————————————————

             popfd
               popad

           cli
;                                               <----- (xx01)
             push    Back_P
              push    [GoPhysique]
                ret                             ;GO vers (Linéaire = Physique)

abort_phys_a:        stop
                mov     ebx,ebx
             jmp     abort_phys_b

;////////////////////full Linéaire => (Linéaire = Physique) 4M Perso //////////
;Valable en "Linéaire = Physique" ET en "Physique"
;-------------------------------------------------

;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;maximum, dernier octet disponible à [ebp + 0xFF]
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;dispo_                 equ     [ebp + 0x24]    ;DD     0 1 2 3
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;_CR3_                  equ     [ebp + 0x20]    ;DD     0 1 2 3
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;                                                       (E/F libres)
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;                               [ebp + 0x1A]    ;DD     A B C D
;IDTR_Full_Lin          equ     [ebp + 0x18]    ;DW     8 9
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;                                                       (6/7 libres)
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;IDTR_Physique_Base     equ     [ebp + 0x12]    ;DD     2 3 4 5 <--- alpha_1
;IDTR_Physique          equ     [ebp + 0x10]    ;DW     0 1
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;                                                       (E/F libres)
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;                               [ebp + 0x0A]    ;DD     A B C D
;GDTR_Full_Lin          equ     [ebp + 0x08]    ;DW     8 9
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;                                                       (6/7 libres)
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;GDTR_Physique_Base     equ     [ebp + 0x02]    ;DD     2 3 4 5
;GDTR_Physique          equ     [ebp]           ;DW     0 1     <--- START ebp dans (Linéaire = Physique)
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;Pile_LP_Push           equ     [ebp - 0x04]    ;DD     4 3 2 1
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;                                                       (6/5 libres)
;———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———  ———
;DS_Origine             equ     [ebp - 0x08]    ;DW     8 7
;Pile_Full_Lineaire     equ     [ebp - 0x0C]    ;DD     C B A 9 (*)
;                                                               (*) <--- "ebp-0Ch"
;—————————————————————————————————————————————————————————————————————————————————————————————

Go_A: ;<--------[BaseAllocLin]

                push    ebp                             ;EIP est "Linéaire = Physique"
           mov     ebp,[MaPileLinéaire]           ;mais "ESP" est toujours "Linéaire"

                mov     word DS_Origine,ds

              mov     Pile_Full_Lineaire,esp

          mov     esp,cr3
             mov     _CR3_,esp

               lea     esp,[ebp-0Ch]

           push    ebp
         pushfd                                  ;(ZZ) "push" dans l'espace "Linéaire = Physique"

          ;sub    [XS_._offset],0Ch + (2 * 04h)   ;(X * 04h) => "X" = nb de "push" en (ZZ)

         mov     Pile_LP_Push,esp

;STOP SYSER --->

             lds     esp,[XS_]               ;je récupère ESP Physique + DS Physique
                                           ;ESP Physique pointe sur "+00h - 14h" (le "push" ZZ)
            mov     ebp,cr0
             btr     ebp,31                  ;bit PG - Paging (bit 31 of CR0)

                ;wbinvd

         mov     cr0,ebp

         jmp     short .LinPhys

;START PHYSIQUE ---------------------------------------------------------------

.LinPhys:      xor     ebp,ebp
             mov     cr3,ebp                         ;CR3:=0 to flush the TLB.

           lea     ebp,[esp + 0Ch + (2 * 04h)]     ;(X * 04h) => "X" = nb de "push" en (ZZ)

         popfd                                   ;from (ZZ) "pop" dans l'espace "Physique"
                                                      ;mon "ebp" Physique (pointe sur "START")
                lgdt    fword GDTR_Physique
         lidt    fword IDTR_Physique             ;SERIALIZING

Go_B:
;----------     START CODE CIBLE --------------------------------------------------
;//////////////////////////////////////////////////////////////////////////////
;----------     END CODE CIBLE ----------------------------------------------------
Go_Y:
         lgdt    fword GDTR_Full_Lin             ;SERIALIZING
                lidt    fword IDTR_Full_Lin

             pushfd                                  ;"push" dans l'espace "Physique"

           mov     esp,Pile_LP_Push                ;je récupère "Pile_LP_Push"

         mov     ebp,_CR3_
           mov     cr3,ebp

         mov     ebp,cr0
             bts     ebp,31

          wbinvd

          mov     cr0,ebp                         ;SERIALIZING

            jmp     short .PhysLin

;END PHYSIQUE ----- (retour Paginé, Linéaire=Physique, 4M) --------------------

.PhysLin:    popfd                                   ;"pop" dans l'espace "Linéaire = Physique"

                pop     ebp                             ;récup de ebp = [MaPileLinéaire]

              lds     esp,Pile_Full_Lineaire          ;ESP Full Linéaire + DS Origine

;OK SYSER --->
;stop
;mov edx,edx
          ;mfence

         pop     ebp                             ;EBP Full linéaire

             mfence
              ret                                     ;fait repasser EIP en full Linéaire 4K (=>Back_P)

Go_Z:          db 4 dup 07

;//////////////////// (Linéaire = Physique) => full Linéaire  4K //////////////
;4K     Entrée origine
;Back to Protected Mode
;======================
Back_P:         nop             ;<----- pile == valeur en (xx01)

     stop
                pushad
              pushfd

          mov     ecx,[esp]
           test    ecx,20000h
          jz      @F
          stop
                mov     ecx,20000h
@@:
               sti
         bts     dword[esp],9

abort_phys_b:

           ;inc    [CptBoum]
           ;cmp    [CptBoum],1000h
             ;;wbinvd
            ;jc     boucle_phys

             mov     ecx,256/4
           mov     esi,Activite
                mov     edi,CopieActivite
      rep  movsd

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

/*Back Data*/  mov     ecx,Sizeof.mesData
          mov     esi,[CopieDataLinéaire]
            mov     edi,StartData
          rep  movsd

;--------------------------------------------------------------------
stop
          mov     ecx,[passageNP_a]
           mov     eax,[passageNP_b]

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

          call    ClearEntryTable_and_Unmap       ;[error_phys]???
            jnc     err_phys

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

cleaning:      call    RemoveDescriptor

                cmp     [BaseAllocLin],0
            je      done_phys

               mov     eax,[gloups]
                invoke  MmFreeContiguousMemory,[BaseAllocLin]

   stop

done_phys:      popfd
               popad

           retproc

err_phys:    stop
                mov     eax,[error_phys]
            jmp     cleaning

endp

;——————————————————————————————————————————————————————————————————————————————
proc ClearEntryTable_and_Unmap       uses all
;================================

           cmp     [flag_table_hook],TRUE
              jne     .fail_CaU

               invoke  KeGetCurrentIrql
            cmp     eax,DISPATCH_LEVEL
          ja      .fail_CaU

               mov     esi,[EntryLineaire]

             mov     eax,[esi]
           mov     edx,[esi+4]

             mov     ebx,[original_a]
            mov     ecx,[original_b]

                push    ss
          pop     ss
    lock  cmpxchg8b [esi]

         mov     eax,[_FROM_invlpg]
          invlpg  [eax]                   ;invlpg = serializing instruction (3A/8.3) [eax]

                invoke  MmUnmapIoSpace, [TempoMap], PAGE_SIZE           ;from "TablePage"

             stc
         retproc

.fail_CaU:   clc
         retproc

endp
    
Code:
proc  PhysiqueToReal_16
;========================

Go_XX:                push    ds                              ;(P)

            ;mov    ds,DS_Origine
               ;mov    ax,0x23
             ;mov    ds,ax

           call    .base
.base:
 old_1 = $
   org 0000h

               pop     esi                             ;esi == .base:

              lea     eax,[esi + .FarToRM]            ;adresse de "FarToRM"
             lea     ebx,[esi + .ToRM]               ;adresse de "ToRM"

            mov     [ss:eax + 1],bx

             and     ebx,0x000F0000
              shr     ebx,4
               mov     [ss:eax + 3],bx

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

          mov     edi,IDTR_Physique_Base

          lea     ebx,[esi + .ISR_INT_0]

          mov     [ss:edi],bx                 ;Offset Interrupt Vector 0
          and     ebx,0x000F0000
              shr     ebx,4
               mov     [ss:edi+2],bx                       ;Segment Selector (3A/17.1.4)

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

                lea     eax,[esi + .FarToPM]            ;adresse de "FarToPM"
             lea     ebx,[esi + .ToPM]               ;adresse de "ToPM"

            mov     [ss:eax + 2],ebx
                mov     [ss:eax + 6],cs

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

          lea     eax,[esi + .FarToXX]            ;adresse de "FarToXX"
             lea     ebx,[esi + .ToXX]               ;adresse de "ToXX"

            mov     [ss:eax + 2],bx
         mov     [ss:eax + 4],cs

;==========================================================

          ;push   ds                              ;from (P)
           push    es
          push    fs
          push    gs

              and     ebx,0x000F0000                  ;3A/3.4.5/figure 3-8, 3.4.5.1/table 3-1
             shr     ebx,16                          ;3A/5.2 figure 5-1
          or      ebx,0x00009A00                  ;operation size = 16bits , limit = 64Ko

         mov     eax,GDTR_Physique_Base          ;CS = 08 = GDT/Descripteur n°1
             add     eax,0Ch                         ;+0Ch = dd n°2 du descripteur n°1, soit le dd n°3 de GDT
         xchg    [ss:eax],ebx                        ;<--- modif du descripteur de CS

             mov     ecx,esp                         ;|(Q) ici, CS base = toujours 0 (why?->descriptor cache)
         push    ss                              ;|    3A/3.4.3
              push    ecx                             ;|

              push    eax                             ;|(N)
               push    ebx                             ;|

;==========================================================

.FarToXX:      jmp     far dword 0000:0000         ;jmp far to CS:ToXX (je recharge CS base from GDT)
                                                      ;ici, CS base != 0, CS base = 000X----
      use16

.ToXX:         mov     eax,cr0
             btr     eax,0                   ;bit PE - Protection Enable (bit 0 of CR0)
          mov     cr0,eax                 ;SERIALIZING

;----------------------------------------------------------<<< IN Real Mode

.FarToRM:   jmp     far dword 0000:0000 ;jmp far to ".ToRM"
                                               ;The far address is loaded directly into CS and EIP
                                         ;Far Jumps in Real-Address Mode (Vol. 2A, page 3-572/3)
;----------------------------------------------------------

.ISR_INT_0:   nopx 4                                  ;ISR INT 0
          nopx 4
              sub     ecx,esp
             add     ecx,0x66990000

          pushfd
              pop     eax

             mov     [passageNP_a],eax ;ecx

          iret

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

.ToRM:               mov     eax,esp
             and     eax,0x000F0000
              shr     eax,4
               mov     ss,ax                   ;il n'y a plus de Descripteur/cache en mode réel
          and     esp,0x0000FFFF          ;le chargement de SS est immédiat.

             xor     ax,ax
               mov     es,ax
               mov     fs,ax
               mov     gs,ax

;——————————————————————————————————————————————————————————> Mon espace "Mode Réel" perso

                mov     si,sp
               call    .yopla
.yopla:   sub     si,sp
               pop     ax

              movzx   eax,si
              mov     [passageNP_b],eax

               mov     ecx,esp

;/////////////////////////////////////////////

           int 0 ;<------------------- interrupt / real mode

;/////////////////////////////////////////////

              mov     esi,esp
             push    ebx
         or      esp,0xFFFF0000                  ;seul sp est utilisé.
              pop     ebx
         mov     esp,esi

;——————————————————————————————————————————————————————————< Mon espace "Mode Réel" perso

              pop     ebx                             ;|from (N)
          pop     eax                             ;|
          mov     [es:eax],ebx

                mov     eax,cr0
             bts     eax,0
               mov     cr0,eax                         ;SERIALIZING

;----------------------------------------------------------<<< OUT Real Mode

.FarToPM:  jmp     far fword 0000:00000000     ;jmp far to ".ToPM"

   use32

.ToPM:
;----------------------------------------------------------
              lss     esp,[esp]                       ;from (Q)

               pop     gs
          pop     fs
          pop     es
          pop     ds

;==========================================================

           xor     eax,eax
             mov     ax,ds
               ;mov    [passageNP_a],ecx   ;eax

                org $ - $$ + old_1              ;"$"    : offset courant
                                              ;"$$"   : base-adresse du segment (ici 0)
Go_YY:

endp
    
Code:
proc    TablePage       _FROM_:dword, demande:dword, _TO_:dword
;================
;http://technet.microsoft.com/en-us/library/cc736309%28WS.10%29.aspx


                pushad

          xor     eax,eax

         mov     [mask_],eax
         mov     [_FROM_invlpg],eax
          mov     [EntryLineaire],eax
         mov     [flag_table_hook],FALSE

         mov     eax,cr3
             mov     [EntryPhysique],eax

             invoke  MmMapIoSpace, eax, 0, PAGE_SIZE, MmNonCached
                mov     [TempoMap],eax

;========================================================== Physical Address Extension (PAE) ?
;PAE oui/non ?

          mov     ebx,cr4       ;cr4 = 0x000006F9
             bt      ebx,5         ;cr4/bit5 = 1 = PAE oui
               mov     ebx,[_FROM_]
                jc      .PAE_oui

;==============================================================================
.PAE_non:   stop

         mov     ecx,ebx
             and     ecx,0xFFC00000
              shr     ecx,20
              add     eax,ecx

         mov     ebx,[eax]
           bt      ebx,7                           ;déjà une page de 2Mo en place ?
          jc      .4Mo_non_PAE

            or      ebx,ebx
             jz      .4Mo_non_PAE

;————————————————————————————————————————————————
.4Ko_non_PAE:      ;stop

           and     ebx,0xFFFFF000

          mov     [EntryPhysique],ebx
         push    MmNonCached PAGE_SIZE 0 ebx

             invoke  MmUnmapIoSpace, [TempoMap], PAGE_SIZE
 
          invoke  MmMapIoSpace
                mov     [TempoMap],eax

          mov     ebx,[_FROM_]
                mov     ecx,ebx
             and     ecx,0x003FF000
              shr     ecx,10
              add     eax,ecx                       ;eax = Page-Table Entry (4 KByte Page)

            mov     [mask_],0xFFFFF963

              and     ebx,0xFFFFF000                ;NOT "0xFFFFF000" = 4Ko
             or      ebx,0x00000963                ;963 ??

           jmp     .placing
                    
;————————————————————————————————————————————————
.4Mo_non_PAE:      mov     [mask_],0xFFC001E3

              and     ebx,0xFFC00000                ;NOT "0xFFC00000" = 4Mo
             or      ebx,0x000001E3

          jmp     .placing


;==============================================================================
.PAE_oui:    ;intel 3A/4.4.2/figure 4.5
          ;0xC0000000(31-30) + 0x3FE00000(29-21) + 0x001FF000(20-12) = 0xFFFFF000

 ;stop
               and     ebx,0xC0000000          ;shr 27 = shr 30 + shl 3 => (bits 31/30 => bits 1/0) + "x8"
         shr     ebx,27

;-------------------------------------------
;               mov     ecx,[_FROM_]
;               and     ecx,0xC0000000          ;shr 18 = shr 30 + shl 12  => (bits 31/30 => bits 1/0) + "x4096"
;               shr     ecx,18                  ;4096 (bytes) = sizeof.Page_Directory(PAE=1)(512*64bits)
;               add     ecx,0xC0600000          ;page directory base virtual address when PAE is set
;-------------------------------------------

              mov     eax,[eax+ebx]           ;Table avec 4 entrées de 64bits
            and     eax,0xFFFFF000          ;eax = Page_Directory_Pointer_Table_ Entry (PDPTE)

              mov     [EntryPhysique],eax
         push    MmNonCached PAGE_SIZE 0 eax

             invoke  MmUnmapIoSpace, [TempoMap], PAGE_SIZE

           invoke  MmMapIoSpace
                mov     [TempoMap],eax

          mov     ebx,[_FROM_]
                mov     ecx,ebx
             and     ecx,0x3FE00000
              shr     ecx,18
              add     eax,ecx

         mov     esi,[eax]
           bt      esi,7
               jc      .2Mo_oui_PAE            ;cy=1 => déjà une page de 2Mo en place

             or      esi,esi
             jz      .2Mo_oui_PAE

;————————————————————————————————————————————————
.4Ko_oui_PAE:      and     esi,0xFFFFF000

          mov     [EntryPhysique],esi
         push    MmNonCached PAGE_SIZE 0 esi

             invoke  MmUnmapIoSpace, [TempoMap], PAGE_SIZE

           invoke  MmMapIoSpace
                mov     [TempoMap],eax
;stop
             mov     ebx,[_FROM_]
                mov     ecx,ebx
             and     ecx,0x001FF000
              shr     ecx,9
               add     eax,ecx

         mov     [mask_],0xFFFFF963

              and     ebx,0xFFFFF000          ;not "0xFFFFF000" = 4Ko
           or      ebx,0x00000963          ;963

            jmp     .placing

;————————————————————————————————————————————————
;2Mo PAE

.2Mo_oui_PAE:  mov     [mask_],0xFFE001E3

              and     ebx,0xFFE00000          ;not "0xFFE00000" = 2Mo
           or      ebx,0x000001E3          ;1E3

;——————————————————————————————————————————————————————————————————————————————
.placing:   ;stop

                mov     [mon_input],ebx

         mov     esi,eax

         mov     [EntryLineaire],esi

             mov     eax,[esi]
           mov     edx,[esi+4]

             mov     [original_a],eax
            mov     [original_b],edx

                or      eax,eax
             jnz     .no_map
             or      edx,edx
             jnz     .no_map

         cmp     [demande],0
         je      .no_map

         mov     ecx,[_FROM_]
                mov     [_FROM_invlpg],ecx

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

             cmp     [demande],1
         je      .identity_map

           push    eax
         invoke  MmGetPhysicalAddress,[_TO_]
         mov     ebx,eax
             pop     eax

             mov     ecx,[mask_]
         and     ecx,0xFFFFF000
              and     ebx,ecx
             mov     ecx,[mask_]
         and     ecx,0x00000FFF
              or      ebx,ecx

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

.identity_map:      xor     ecx,ecx

         push    ss
          pop     ss              ;"pop ss" inhibe toutes les interruptions, y compris NMI,
   lock  cmpxchg8b [esi]         ;jusqu'à la fin de la prochaine instruction.

          ;invlpg [?]             ;invlpg = serializing instruction (3A/8.3)

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

             mov     [flag_table_hook],TRUE

          and     esi,0xFFF
           add     [EntryPhysique],esi

             stc
         popad
               retproc

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

.no_map:    clc
         popad
               retproc

;------------------------------------------------------------------------------
;
;EntryLineaire
;
;mask_  0xFFFFF963 = 4Ko
;       0xFFE001E3 = 2Mo
;       0xFFC001E3 = 4Mo
;
endp
    

_________________
I am not young enough to know everything (Oscar Wilde)- Image
Post 12 May 2011, 22:22
View user's profile Send private message Send e-mail 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-2025, Tomasz Grysztar. Also on GitHub, YouTube.

Website powered by rwasa.