elhacker.net cabecera Bienvenido(a), Visitante. Por favor Ingresar o Registrarse
¿Perdiste tu email de activación?.

 

 


Tema destacado: Recuerda que debes registrarte en el foro para poder participar (preguntar y responder)


+  Foro de elhacker.net
|-+  Programación
| |-+  Programación General
| | |-+  .NET (C#, VB.NET, ASP)
| | | |-+  Programación Visual Basic (Moderadores: LeandroA, seba123neo)
| | | | |-+  AddressOf Form_Initialize()
0 Usuarios y 1 Visitante están viendo este tema.
Páginas: [1] Ir Abajo Respuesta Imprimir
Autor Tema: AddressOf Form_Initialize()  (Leído 5,275 veces)
F3B14N

Desconectado Desconectado

Mensajes: 47


Ver Perfil
AddressOf Form_Initialize()
« en: 28 Febrero 2011, 23:41 pm »

Hola gente, estoy buscando obtener la direccion de Form_Initialize. A mi se me ocurre por medio de un hook, pero no me gusta es muy groncho  :-X

Gracias


En línea

raul338


Desconectado Desconectado

Mensajes: 2.633


La sonrisa es la mejor forma de afrontar las cosas


Ver Perfil WWW
Re: AddressOf Form_Initialize()
« Respuesta #1 en: 28 Febrero 2011, 23:49 pm »

AdressOf no funciona con algo que no sea una funcion de modulo publico :xD


En línea

F3B14N

Desconectado Desconectado

Mensajes: 47


Ver Perfil
Re: AddressOf Form_Initialize()
« Respuesta #2 en: 1 Marzo 2011, 00:08 am »

AdressOf no funciona con algo que no sea una funcion de modulo publico :xD

por ello hice este post  :silbar:
En línea

raul338


Desconectado Desconectado

Mensajes: 2.633


La sonrisa es la mejor forma de afrontar las cosas


Ver Perfil WWW
Re: AddressOf Form_Initialize()
« Respuesta #3 en: 1 Marzo 2011, 01:12 am »

Lo siento :xD tuve una larga interrupcion cuando intentaba responder y mande eso solo :xD

Yo te diria (era mi idea tambien, pero no dispongo de muucho tiempo disponible) que se podria hacer con TypeLib Library (lo que Mr Frog uso para hacer un CallByNameEx en su clsContest) pero junto con ASM (vi una cierta tecnica que era lanzar un CallWndProc a un puntero cualquiera que apunte a una interfaz)
No se nada de ello, pero confio e investigare si se puede o no
En línea

LeandroA
Moderador
***
Desconectado Desconectado

Mensajes: 760


www.leandroascierto.com


Ver Perfil WWW
Re: AddressOf Form_Initialize()
« Respuesta #4 en: 1 Marzo 2011, 02:03 am »

hola, por curiosidad para que nececistas el adress de Form_Initialize? si vos estas buscando interceptar la inicializacion de una ventana es combeniente interceptarlo con un hook (fuera del formulario obiamente) digo fuera del formulario porque este aun no se creo, me refiero exactamente a arrancar la aplicacion desde un sub main crear el gancho llamar al form y interceptar el msg WM_CREATE

ejemplo
 
Código:
Option Explicit

Private Declare Function SetWindowsHookEx Lib "user32" Alias "SetWindowsHookExA" (ByVal idHook As Long, ByVal lpfn As Long, ByVal hmod As Long, ByVal dwThreadId As Long) As Long
Private Declare Function UnhookWindowsHookEx Lib "user32" (ByVal hHook As Long) As Long
Private Declare Function CallNextHookEx Lib "user32" (ByVal hHook As Long, ByVal ncode As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function GetClassName Lib "user32" Alias "GetClassNameA" (ByVal hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long

Private Type CWPSTRUCT
    lParam As Long
    wParam As Long
    message As Long
    hwnd As Long
End Type

Private Enum HookConstants
    HC_ACTION = 0
    HC_GETNEXT = 1
    HC_SKIP = 2
    HC_NOREMOVE = 3
    HC_NOREM = HC_NOREMOVE
    HC_SYSMODALOFF = 5
    HC_SYSMODALON = 4
End Enum

Private Const WH_CALLWNDPROC = 4
Private Const WM_CREATE = &H1
Private Const WM_DESTROY As Long = &H2

Private hHook As Long

Private Sub main()
    StartHooking
    Form1.Show
End Sub

Public Function HookProc(ByVal uCode As Long, ByVal wParam As Long, lParam As CWPSTRUCT) As Long

    HookProc = CallNextHookEx(hHook, uCode, wParam, lParam)

    If uCode = HC_ACTION Then
   
        Select Case lParam.message
       
            Case WM_CREATE
                If GetWinClassName(lParam.hwnd) = "ThunderFormDC" Then
                    Debug.Print "Inicializa Form: " & lParam.hwnd
                End If
               
            Case WM_DESTROY
                Call EndHooking
   
        End Select
   
    End If
End Function



Public Sub EndHooking()
    If hHook <> 0 Then
        UnhookWindowsHookEx hHook
        hHook = 0
    End If
End Sub

Public Sub StartHooking()
    hHook = SetWindowsHookEx(WH_CALLWNDPROC, AddressOf HookProc, 0, App.ThreadID)
End Sub


Public Function GetWinClassName(hwnd As Long) As String
    Dim sClass As String * 255, ret&
    sClass = String(255, 0)
    ret = GetClassName(hwnd, ByVal sClass, 255)
    GetWinClassName = Left$(sClass, ret)
End Function
En línea

F3B14N

Desconectado Desconectado

Mensajes: 47


Ver Perfil
Re: AddressOf Form_Initialize()
« Respuesta #5 en: 1 Marzo 2011, 03:57 am »

Gracias Leandro, pero no es eso lo que busco sino:

Código:
Option Explicit

Private Type GUID
    Data1 As Long
    Data2 As Integer
    Data3 As Integer
    Data4(7) As Byte
End Type

Public Declare Function VirtualProtect Lib "kernel32" (lpAddress As Any, ByVal dwSize As Long, ByVal flNewProtect As Long, lpflOldProtect As Long) As Long
Private Declare Function CreateThread Lib "kernel32" (ByVal lpSecurityAttributes As Long, ByVal dwStackSize As Long, ByVal lpStartAddress As Long, lpParameter As Long, ByVal dwCreationFlags As Long, lpThreadId As Long) As Long
Public Declare Function ReadProcessMemory Lib "kernel32" (ByVal hProcess As Long, ByRef lpBaseAddress As Any, ByRef lpBuffer As Any, ByVal nSize As Long, ByRef lpNumberOfBytesWritten As Long) As Long
Private Declare Function VBDllGetClassObject Lib "MSVBVM60" (g1 As Long, g2 As Long, ByVal g3_vbHeader As Long, REFCLSID As Long, REFIID As GUID, ppv As Long) As Long
Private Declare Function CreateIExprSrvObj Lib "MSVBVM60" (ByVal p1_0 As Long, ByVal p2_4 As Long, ByVal p3_0 As Long) As Long
Private Declare Function CoInitialize Lib "OLE32" (ByVal pvReserved As Long) As Long
Private Declare Sub CoUninitialize Lib "OLE32" ()
Private m_nFakeHeader As Long
Public Declare Function MessageBox Lib "user32" Alias "MessageBoxA" (ByVal hwnd As Long, ByVal lpText As String, ByVal lpCaption As String, ByVal wType As Long) As Long

Public Sub CreateNewThread(ByVal lAddress As Long, ByVal lVal As Long, Optional ByRef lHandle As Long, Optional ByRef lThread As Long)
    If m_nFakeHeader = 0 Then
        Call GetFakeHeader

    End If
    lHandle = CreateThread(ByVal 0&, ByVal 0&, lAddress, ByVal lVal, 0, lThread)
End Sub

Public Sub InitCurrentThread()
    Call CreateIExprSrvObj(0, 4, 0)
    Call CoInitialize(0)
    Call InitVBdll
End Sub

Public Sub TerminateCurrentThread()
    Call CoUninitialize
End Sub

Public Sub GetFakeHeader()
    Dim lPtr            As Long
    Dim lProc           As Long
    Dim bdata(1024)     As Byte
    Dim sData           As String
    Dim lRet            As Long
       
    lPtr = App.hInstance
    Do While lRet = 0
        If Not ReadProcessMemory(-1, ByVal lPtr, bdata(0), 1024, 0&) = 0 Then
            sData = StrConv(bdata, vbUnicode)
            lRet = InStr(1, sData, "VB5!", vbBinaryCompare)
        Else
            Exit Sub
        End If
        lPtr = lPtr + 1024
    Loop
    m_nFakeHeader = lPtr + lRet - 1024 - 1
End Sub

Private Sub InitVBdll()
    Dim pIID As GUID

    With pIID
        .Data1 = 1
        .Data4(0) = &HC0
        .Data4(7) = &H46
    End With
   
    'Escribir en (AddressOf Main o AddressOf Form_Initialize): &HC3 (RETN)
    Call VBDllGetClassObject(0, 0, m_nFakeHeader, 0, pIID, 0)
End Sub

Public Sub aaa()
InitCurrentThread
Form2.Show vbModal
TerminateCurrentThread
End Sub

Si probas el código, podrás ver que al crear un thread nuevo se ejecuta la función principal del programa (Main o Form_Init..), yo creo poder evitar eso escribiendo un RETN &HC3, en la dirección de "la función principal" pero no se crear una función genérica que me devuelva la dirección sea un modulo o form.

La función principal es llamada al llamar VBDllGetClassObject, estuve viendo las estructuras http://vb-decompiler.com/viewtopic.php?t=2 , pensando que podria encontrar la dirección ahi pero tampoco  :-\

Bueno eso es lo que quiero hacer, pero necesito ayuda  :-X Saludos  :)
En línea

MCKSys Argentina
Moderador Global
***
Desconectado Desconectado

Mensajes: 5.465


Diviértete crackeando, que para eso estamos!


Ver Perfil
Re: AddressOf Form_Initialize()
« Respuesta #6 en: 4 Marzo 2011, 00:17 am »

Podrias usar las estructuras definidas en este script de IDA: http://www.openrce.org/downloads/details/245/VB_Helper_Script

Solo debes convertirlas para usarlas con VB y listo...

Saludos!
En línea

MCKSys Argentina

"Si piensas que algo está bien sólo porque todo el mundo lo cree, no estás pensando."

F3B14N

Desconectado Desconectado

Mensajes: 47


Ver Perfil
Re: AddressOf Form_Initialize()
« Respuesta #7 en: 9 Marzo 2011, 21:47 pm »

Podrias usar las estructuras definidas en este script de IDA: http://www.openrce.org/downloads/details/245/VB_Helper_Script

Solo debes convertirlas para usarlas con VB y listo...

Saludos!

Gracias, pero aún sigo sin lograr lo que busco, seguiré intentandolo  :-\
Aca dejo las estructuras y poco mas para quienes las puedan necesitar:

Código
  1. Private Type VBHeader
  2.    szVbMagic As Long '0x00, VB5! String
  3.    wRuntimeBuild  As Integer '0x04, Build of the VB6 Runtime
  4.    szLangDll(13) As Byte '0x06, Language Extension DLL
  5.    szSecLangDll(13) As Byte '0x14, Language Extension DLL
  6.    wRuntimeRevision As Integer '0x22, Internal Runtime Revision
  7.    dwLcid  As Long '0x24, LCID of Language DLL
  8.    dwSecLCID   As Long '0x28, LCID of 2nd Language DLL
  9.    lpSubMain   As Long '0x2C, Pointer to Sub Main Code
  10.    lpProjectData As Long '0x30, Pointer to Project Data
  11.    fMdlIntCtls As Long '0x34, VB Control Flags for IDs < 32
  12.    fMdlIntCtls2 As Long '0x38, VB Control Flags for IDs > 32
  13.    dwThreadFlags As Long '0x3C, Threading Mode
  14.    dwThreadCount As Long '0x40, Threads to support in pool
  15.    wFormCount As Long '0x44, Number of forms present
  16.    wExternalCount As Integer '0x46, Number of external controls
  17.    dwThunkCount As Long '0x48, Number of thunks to create
  18.    lpGuiTable As Long '0x4C, Pointer to GUI Table
  19.    lpExternalTable As Long '0x50, Pointer to External Table
  20.    lpComRegisterData As Long '0x54, Pointer to COM Information
  21.    bSZProjectDescription As Long '0x58, Offset to Project Description
  22.    bSZProjectExeName As Long '0x5C, Offset to Project EXE Name
  23.    bSZProjectHelpFile As Long '0x60, Offset to Project Help File
  24.    bSZProjectName As Long '0x64, Offset to Project Name
  25. End Type
  26.  
  27. Private Type COMRegistrationData
  28.    bRegInfo As Long '0x00, Offset to COM Interfaces Info
  29.    bSZProjectName As Long '0x04, Offset to Project/Typelib Name
  30.    bSZHelpDirectory As Long '0x08, Offset to Help Directory
  31.    bSZProjectDescription As Long '0x0C, Offset to Project Description
  32.    uuidProjectClsId(15) As Byte ' 0x10, CLSID of Project/Typelib
  33.    dwTlbLcid As Long '0x20, LCID of Type Library
  34.    wUnknown As Integer '0x24, Might be something. Must check
  35.    wTlbVerMajor As Integer '0x26, Typelib Major Version
  36. End Type
  37.  
  38. Private Type COMRegistrationInfo
  39.    bNextObject     As Long '0x00, Offset to COM Interfaces Info
  40.    bObjectName     As Long '0x04, Offset to Object Name
  41.    bObjectDescription  As Long '0x08, Offset to Object Description
  42.    dwInstancing    As Long '0x0C, Instancing Mode
  43.    dwObjectId  As Long '0x10, Current Object ID in the Project
  44.    uuidObject(15) As Byte  '0x14, CLSID of Object
  45.    fIsInterface    As Long '0x24, Specifies if the next CLSID is valid
  46.    bUuidObjectIFace    As Long '0x28, Offset to CLSID of Object Interface
  47.    bUuidEventsIFace    As Long '0x2C, Offset to CLSID of Events Interface
  48.    fHasEvents  As Long '0x30, Specifies if the CLSID above is valid
  49.    dwMiscStatus    As Long '0x34, OLEMISC Flags (see MSDN docs)
  50.    fClassType As Byte '0x38, Class Type
  51.    fObjectType As Byte '0x39, Flag identifying the Object Type
  52.    wToolboxBitmap32 As Integer '0x3A, Control Bitmap ID in Toolbox
  53.    wDefaultIcon As Integer '0x3C, Minimized Icon of Control Window
  54.    fIsDesigner As Integer ' 0x3E, Specifies whether this is a Designer
  55.    bDesignerData As Long '0x40, Offset to Designer Data
  56. End Type
  57.  
  58. Private Type DesignerInfo
  59.    uuidDesigner(15) As Byte '0x00, CLSID of the Addin/Designer
  60.    cbStructSize As Long '0x10, Total Size of the next fields.
  61.    '    ea = ea + 0x18;
  62.    '    MakeDword       (ea - 0x04
  63.    'bstrAddinRegKey     FixStr          (ea, Registry Key of the Addin
  64.    '    ea = ea + 0x04 + Dword(ea - 0x04
  65.    '    MakeDword       (ea - 0x04
  66.    'bstrAddinName   FixStr          (ea, Friendly Name of the Addin
  67.    '    ea = ea + 0x04 + Dword(ea - 0x04
  68.    '    MakeDword       (ea - 0x04
  69.    'bstrAddinDescription    FixStr          (ea, Description of Addin
  70.    '    ea = ea + Dword(ea - 0x04
  71.    'dwLoadBehaviour     FixDword        (ea, CLSID of Object
  72.    '    ea = ea + 0x08;
  73.    '    MakeDword       (ea - 0x04
  74.    'bstrSatelliteDll    FixStr          (ea, Satellite DLL, if specified
  75.    '    ea = ea + 0x04 + Dword(ea - 0x04
  76.    '    MakeDword       (ea - 0x04
  77.    'bstrAdditionalRegKey    FixStr          (ea, Extra Registry Key, if specified
  78.    '    ea = ea + Dword(ea - 0x04
  79.    'dwCommandLineSafe   FixDword        (ea, Specifies a GUI-less Addin if 1.
  80. End Type
  81.  
  82. Private Type ProjectInformation
  83.    dwVersion   As Long '0x00, 5.00 in Hex (0x1F4). Version.
  84.    lpObjectTable   As Long '0x04, Pointer to the Object Table
  85.    dwNull  As Long '0x08, Unused value after compilation.
  86.    lpCodeStart     As Long '0x0C, Points to start of code. Unused.
  87.    lpCodeEnd   As Long '0x10, Points to end of code. Unused.
  88.    dwDataSize  As Long '0x14, Size of VB Object Structures. Unused.
  89.    lpThreadSpace   As Long '0x18, Pointer to Pointer to Thread Object.
  90.    lpVbaSeh    As Long '0x1C, Pointer to VBA Exception Handler
  91.    lpNativeCode    As Long '0x20, Pointer to .DATA section.
  92.    szPathInformation(527) As Byte '0x24, Contains Path and ID string. < SP6
  93.    lpExternalTable     As Long '0x234, Pointer to External Table.
  94.    dwExternalCount     As Long '0x238, Objects in the External Table.
  95. End Type
  96.  
  97. Private Type SecondaryProjectInformation
  98.    lpHeapLink  As Long '0x00, Unused after compilation, always 0.
  99.    lpObjectTable   As Long '0x04, Back-Pointer to the Object Table.
  100.    dwReserved  As Long '0x08, Always set to -1 after compiling. Unused
  101.    dwUnused    As Long '0x0C, Not written or read in any case.
  102.    lpObjectList    As Long '0x10, Pointer to Object Descriptor Pointers.
  103.    dwUnused2   As Long '0x14, Not written or read in any case.
  104.    szProjectDescription    As Long '0x18, Pointer to Project Description
  105.    szProjectHelpFile   As Long '0x1C, Pointer to Project Help File
  106.    dwReserved2     As Long '0x20, Always set to -1 after compiling. Unused
  107.    dwHelpContextId     As Long '0x24, Help Context ID set in Project Settings.
  108. End Type
  109.  
  110. Private Type ObjectTable
  111.    lpHeapLink  As Long '0x00, Unused after compilation, always 0.
  112.    lpExecProj  As Long '0x04, Pointer to VB Project Exec COM Object.
  113.    lpProjectInfo2  As Long '0x08, Secondary Project Information.
  114.    dwReserved  As Long '0x0C, Always set to -1 after compiling. Unused
  115.    dwNull  As Long '0x10, Not used in compiled mode.
  116.    lpProjectObject     As Long '0x14, Pointer to in-memory Project Data.
  117.    uuidObject(15) As Byte '0x18, GUID of the Object Table.
  118.    fCompileState   As Integer '0x28, Internal flag used during compilation.
  119.    dwTotalObjects  As Integer '0x2A, Total objects present in Project.
  120.    dwCompiledObjects   As Integer '0x2C, Equal to above after compiling.
  121.    dwObjectsInUse  As Integer '0x2E, Usually equal to above after compile.
  122.    lpObjectArray   As Long '0x30, Pointer to Object Descriptors
  123.    fIdeFlag    As Long '0x34, Flag/Pointer used in IDE only.
  124.    lpIdeData   As Long '0x38, Flag/Pointer used in IDE only.
  125.    lpIdeData2  As Long '0x3C, Flag/Pointer used in IDE only.
  126.    lpszProjectName     As Long '0x40, Pointer to Project Name.
  127.    dwLcid  As Long '0x44, LCID of Project.
  128.    dwLcid2     As Long '0x48, Alternate LCID of Project.
  129.    lpIdeData3  As Long '0x4C, Flag/Pointer used in IDE only.
  130.    dwIdentifier    As Long '0x50, Template Version of Structure.
  131. End Type
  132.  
  133. Private Type PrivateObjectDescriptor
  134.    lpHeapLink  As Long '0x00, Unused after compilation, always 0.
  135.    lpObjectInfo    As Long '0x04, Pointer to the Object Info for this Object.
  136.    dwReserved  As Long '0x08, Always set to -1 after compiling.
  137.    dwIdeData   As Long '0x0C, [3] Not valid after compilation.
  138.    Unknown1 As Long '0x10
  139.    Unknown2 As Long '0x14
  140.    lpObjectList    As Long '0x18, Points to the Parent Structure (Array)
  141.    dwIdeData2  As Long '0x1C, Not valid after compilation.
  142.    lpObjectList2   As Long '0x20, [3] Points to the Parent Structure (Array).
  143.    Unknown3 As Long '0x24
  144.    Unknown4 As Long ' 0x28
  145.    wIdeData3  As Long '0x2C, [3] Not valid after compilation.
  146.    Unknown5 As Long '0x30
  147.    Unknown6 As Long '0x34
  148.    dwObjectType    As Long '0x38, Type of the Object described.
  149.    dwIdentifier    As Long '0x3C, Template Version of Structure.
  150. End Type
  151.  
  152. Private Type PublicObjectDescriptor
  153.    lpObjectInfo    As Long '0x00, Pointer to the Object Info for this Object.
  154.    dwReserved  As Long '0x04, Always set to -1 after compiling.
  155.    lpPublicBytes   As Long '0x08, Pointer to Public Variable Size integers.
  156.    lpStaticBytes   As Long '0x0C, Pointer to Static Variable Size integers.
  157.    lpModulePublic  As Long '0x10, Pointer to Public Variables in DATA section
  158.    lpModuleStatic  As Long '0x14, Pointer to Static Variables in DATA section
  159.    lpszObjectName  As Long '0x18, Name of the Object.
  160.    dwMethodCount   As Long '0x1C, Number of Methods in Object.
  161.    lpMethodNames   As Long '0x20, If present, pointer to Method names array.
  162.    bStaticVars     As Long '0x24, Offset to where to copy Static Variables.
  163.    fObjectType     As Long '0x28, Flags defining the Object Type.
  164.    dwNull  As Long '0x2C, Not valid after compilation.
  165. End Type
  166.  
  167. Private Type ObjectInformation
  168.    wRefCount   As Integer '0x00, Always 1 after compilation.
  169.    wObjectIndex    As Integer '0x02, Index of this Object.
  170.    lpObjectTable   As Long '0x04, Pointer to the Object Table
  171.    lpIdeData   As Long '0x08, Zero after compilation. Used in IDE only.
  172.    lpPrivateObject     As Long '0x0C, Pointer to Private Object Descriptor.
  173.    dwReserved  As Long '0x10, Always -1 after compilation.
  174.    dwNull  As Long '0x14, Unused.
  175.    lpObject    As Long '0x18, Back-Pointer to Public Object Descriptor.
  176.    lpProjectData   As Long '0x1C, Pointer to in-memory Project Object.
  177.    wMethodCount    As Integer '0x20, Number of Methods
  178.    wMethodCount2   As Integer '0x22, Zeroed out after compilation. IDE only.
  179.    lpMethods   As Long '0x24, Pointer to Array of Methods.
  180.    wConstants  As Integer '0x28, Number of Constants in Constant Pool.
  181.    wMaxConstants   As Integer '0x2A, Constants to allocate in Constant Pool.
  182.    lpIdeData2  As Long '0x2C, Valid in IDE only.
  183.    lpIdeData3  As Long '0x30, Valid in IDE only.
  184.    lpConstants     As Long '0x34, Pointer to Constants Pool.
  185. End Type
  186.  
  187. Private Type OptionalObjectInformation
  188.    dwObjectGuids   As Long '0x00, How many GUIDs to Register. 2 = Designer
  189.    lpObjectGuid    As Long '0x04, Unique GUID of the Object *VERIFY*
  190.    dwNull  As Long '0x08, Unused.
  191.    lpuuidObjectTypes   As Long '0x0C, Pointer to Array of Object Interface GUIDs
  192.    dwObjectTypeGuids   As Long '0x10, How many GUIDs in the Array above.
  193.    lpControls2     As Long '0x14, Usually the same as lpControls.
  194.    dwNull2     As Long '0x18, Unused.
  195.    lpObjectGuid2   As Long '0x1C, Pointer to Array of Object GUIDs.
  196.    dwControlCount  As Long '0x20, Number of Controls in array below.
  197.    lpControls  As Long '0x24, Pointer to Controls Array.
  198.    wEventCount     As Integer '0x28, Number of Events in Event Array.
  199.    wPCodeCount     As Integer '0x2A, Number of P-Codes used by this Object.
  200.    bWInitializeEvent   As Integer '0x2C, Offset to Initialize Event from Event Table.
  201.    bWTerminateEvent    As Integer '0x2E, Offset to Terminate Event in Event Table.
  202.    lpEvents    As Long '0x30, Pointer to Events Array.
  203.    lpBasicClassObject  As Long '0x34, Pointer to in-memory Class Objects.
  204.    dwNull3     As Long '0x38, Unused.
  205.    lpIdeData   As Long '0x3C, Only valid in IDE.
  206. End Type
  207.  
  208. Private Type ControlInformation
  209.    fControlType    As Long '0x00, Type of control.
  210.    wEventCount     As Integer '0x04, Number of Event Handlers supported.
  211.    bWEventsOffset  As Integer '0x06, Offset in to Memory struct to copy Events.
  212.    lpGuid  As Long '0x08, Pointer to GUID of this Control.
  213.    dwIndex     As Long '0x0C, Index ID of this Control.
  214.    dwNull  As Long '0x10, Unused.
  215.    dwNull2     As Long '0x14, Unused.
  216.    lpEventTable    As Long '0x18, Pointer to Event Handler Table.
  217.    lpIdeData   As Long '0x1C, Valid in IDE only.
  218.    lpszName    As Long '0x20, Name of this Control.
  219.    dwIndexCopy     As Long '0x24, Secondary Index ID of this Control.
  220. End Type
  221.  
  222. Private Function GetFakeHeader() As Long
  223.    Dim lPtr            As Long
  224.    Dim lProc           As Long
  225.    Dim bData(1024)     As Byte
  226.    Dim sData           As String
  227.    Dim lRet            As Long
  228.  
  229.    lPtr = App.hInstance
  230.    Do While lRet = 0
  231.        Call ReadProcessMemory(-1, ByVal lPtr, bData(0), 1024, 0&)
  232.        sData = StrConv(bData, vbUnicode)
  233.        lRet = InStr(1, sData, "VB5!", vbBinaryCompare)
  234.        lPtr = lPtr + 1024
  235.    Loop
  236.    GetFakeHeader = lPtr + lRet - 1024 - 1
  237. End Function
  238.  
  239. Public Function GetFormAddress() As Long
  240. Dim dd As VBHeader
  241. Dim tt As ProjectInformation
  242. Dim ss As ObjectTable
  243. Dim aa As PublicObjectDescriptor
  244. Dim jj As OptionalObjectInformation
  245. Dim yy As ControlInformation
  246.  
  247. Call ReadProcessMemory(-1, ByVal GetFakeHeader, dd, LenB(dd), 0)
  248. Call ReadProcessMemory(-1, ByVal dd.lpProjectData, tt, LenB(tt), 0)
  249. Call ReadProcessMemory(-1, ByVal tt.lpObjectTable, ss, LenB(ss), 0)
  250. Call ReadProcessMemory(-1, ByVal ss.lpObjectArray, aa, LenB(aa), 0)
  251.  
  252. Call ReadProcessMemory(-1, ByVal aa.lpObjectInfo, jj, LenB(jj), 0)
  253. Call ReadProcessMemory(-1, ByVal jj.lpControls, yy, LenB(yy), 0)
  254. MsgBox jj.bWInitializeEvent
  255. MsgBox jj.bWTerminateEvent
  256. MsgBox yy.lpEventTable
En línea

Páginas: [1] Ir Arriba Respuesta Imprimir 

Ir a:  

Mensajes similares
Asunto Iniciado por Respuestas Vistas Último mensaje
Operador AddressOf
Programación Visual Basic
Kizar 4 2,157 Último mensaje 13 Mayo 2006, 14:10 pm
por Kizar
form_load y form_initialize ?
Programación Visual Basic
carlitrosss6 2 3,799 Último mensaje 30 Mayo 2009, 22:44 pm
por xpchacker
Problema con AddressOf [Solucionado]
Programación Visual Basic
Slek Hacker 6 4,599 Último mensaje 26 Septiembre 2010, 23:05 pm
por Slek Hacker
AddressOf / Tamaño de funcion
Programación Visual Basic
Miseryk 1 1,485 Último mensaje 10 Mayo 2011, 20:41 pm
por Karcrack
WAP2 - Aviso Legal - Powered by SMF 1.1.21 | SMF © 2006-2008, Simple Machines