[VB6][SNIPPET] mAPIPatchByID - Carga APIs dinamicamente (Late binding)

Iniciado por Karcrack, Junio 16, 2013, 06:27:34 PM

Tema anterior - Siguiente tema

0 Miembros y 2 Visitantes están viendo este tema.

Código: vb
'---------------------------------------------------------------------------------------
' Module    : mAPIPatchByID
' Author    : Karcrack
' Now       : 23/04/2011 14:13
' Purpose   : Patch API functions by ID
' History   : 23/04/2011 First cut .........................................................
'---------------------------------------------------------------------------------------

Option Explicit

'KERNEL32
Private Declare Function NtWriteVirtualMemory Lib "NTDLL" (ByVal hProcess As Long, ByRef lpBaseAddress As Any, ByRef lpBuffer As Any, ByVal nSize As Long, ByRef lpNumberOfBytesWritten As Long) As Long

Public Sub PatchAPIAddr(ByVal lID As Long, ByVal lAddr As Long)
    Dim hInstance       As Long
    Dim lExtTablePtr    As Long
   
    hInstance = App.hInstance
    lExtTablePtr = GetDWORD(GetDWORD((hInstance + GetDWORD(hInstance + GetDWORD(hInstance + &H3C) + &H28)) + &H1) + &H30) + &H234
    If GetDWORD(lExtTablePtr + &H4) >= lID Then
        Call PutDWORD(GetDWORD(GetDWORD(GetDWORD(lExtTablePtr) + (8 * lID) + 4) + &H19), lAddr)
    End If
End Sub

Private Sub PutDWORD(ByVal lAddr As Long, ByVal lDWORD As Long)
    Call NtWriteVirtualMemory(-1, ByVal lAddr, lDWORD, 4, ByVal 0&)
End Sub

Private Function GetDWORD(ByVal lAddr As Long) As Long
    Call NtWriteVirtualMemory(-1, GetDWORD, ByVal lAddr, 4, ByVal 0&)
End Function


Para que sirve? Para cargar APIs dinamicamente :D

Un ejemplo:
Código: vb
Option Explicit

'USER32
Private Declare Function MessageBox Lib "nadaesloqueparece" Alias "Karcrack" (ByVal hwnd As Long, ByVal lpText As String, ByVal lpCaption As String, ByVal wType As Long) As Long
'KERNEL32
Private Declare Function GetProcAddress Lib "KERNEL32" (ByVal hModule As Long, ByVal lpProcName As String) As Long
Private Declare Function LoadLibrary Lib "KERNEL32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long

Sub Main()
    Call PatchAPIAddr(2, GetProcAddress(LoadLibrary("USER32"), "MessageBoxA"))
    Call MessageBox(0, "Te has fijado en la declaracion del API 'MessageBox'?", "Hola :)", 0)
End Sub

Otro un poco mas enrevesado:
Código: vb
Option Explicit

'USER32
Private Declare Function fnc1& Lib "whatever" (ByVal a&, ByVal b&, ByVal c&, ByVal d&)
Private Declare Function fnc2& Lib "whatever" (ByVal a&, ByVal b&)
'KERNEL32
Private Declare Function GetProcAddress Lib "KERNEL32" (ByVal hModule As Long, ByVal lpProcName As String) As Long
Private Declare Function LoadLibrary Lib "KERNEL32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long

Private Const u32$ = "ZXJW87"
Private Const msgbx$ = "RjxxfljGt}\"
Private Const ktmr$ = "PnqqYnrjw"
Private Const stmr$ = "XjyYnrjw"
Private x&
Private bo&

Sub Main()
    Dim p&
   
    p = GetProcAddress(LoadLibrary(d(u32)), d(stmr))
    Call PatchAPIAddr(3, p)
    x = fnc1(0, 0, 2 * 1000, AddressOf tproc)
    p = GetProcAddress(LoadLibrary(d(u32)), d(msgbx))
    Call PatchAPIAddr(3, p)
    p = GetProcAddress(LoadLibrary(d(u32)), d(ktmr))
    Call PatchAPIAddr(2, p)
    bo = 1
    While bo
        DoEvents
    Wend
End Sub

Private Function d$(s$)
    Dim i&
    d = s
    For i = 1 To Len(d)
        Mid$(d, i, 1) = Chr$(Asc(Mid$(d, i, 1)) - 5)
    Next i
End Function

Private Function tproc&(ByVal a&, ByVal b&, ByVal c&, ByVal d&)
    If fnc1(0, StrPtr("Seguimos?"), StrPtr(":)"), vbYesNo) = vbNo Then
        bo = 0
        Call fnc2(0, x)
    End If
End Function


Los ejemplos han de ir en un modulo aparte puesto después del modulo 'mAPIPatchByID' para que los IDs se correspondiesen... en caso contrario hay que calcular los IDs usando por ejemplo el OllyDbg :P

Cualquier duda preguntad!
I code for $$$.

(PGP ID 0xCC050E77)
ASM, C, C++, VB6... skilled [malware] developer