[ASM+VB6][INVOKE] Llamas APIs sin declararlas - kInvoke.bas

Iniciado por Karcrack, 9 Abril 2010, 16:17 PM

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

Karcrack

Existen gran cantidad de códigos por la red (algunos míos :rolleyes:) que permiten llamar APIs de forma Dinámica... es decir sin declararlas...

Que tiene este de especial? Que las llama mediante un Hash... Tal y como hacen los Shellcodes ;-)

Aquí un ejemplo de llamada:
Código (vb,1) [Seleccionar]
Call Invoke("USER32", &HBC4DA2BE, 0, StrPtr("Soy Karcrack :D"), StrPtr("Ejemplo"), 0)

&HBC4DA2BE es el Hash de la cadena "MessageBoxW", para generar los Hashes se utiliza el siguiente algoritmo:
Código (asm) [Seleccionar]

;ESI = Puntero cadena
compute_hash:
xor edi, edi     ;EDI = 0
xor eax, eax   ;EAX = 0
cld
compute_hash_again:
lodsb                ;AL = BYTE[ESI] , ESI = ESI + 1
test al, al
       jz compute_hash_finished
ror edi, 0xD
add edi, eax
       jmp compute_hash_again
compute_hash_finished:
;EDI = El Hash de la cadena


De todas formas he hecho una pequeña herramienta para que genera los Hashes :D
Citar
http://www.box.net/shared/0ld4yy6bmy
Codigo Fuente incluido ;)



Bueno, aquí esta el código principal:
Código (vb) [Seleccionar]
'---------------------------------------------------------------------------------------
' Module    : kInvoke
' Author    : Karcrack
' Date      : 09/04/2010
' Purpose   : Call APIs By Hash
'---------------------------------------------------------------------------------------

Option Explicit

'USER32
Private Declare Function CallWindowProcW Lib "USER32" (ByVal lpCode As Long, Optional ByVal lParam1 As Long, Optional ByVal lParam2 As Long, Optional ByVal lParam3 As Long, Optional ByVal lParam4 As Long) As Long

Private Const THUNK_GETAPIPTR       As String = "E82200000068A44E0EEC50E84300000083C408FF742404FFD0FF74240850E83000000083C408C3565531C0648B70308B760C8B761C8B6E088B7E208B3638471875F3803F6B7407803F4B7402EBE789E85D5EC35552515356578B6C241C85ED74438B453C8B54057801EA8B4A188B5A2001EBE330498B348B01EE31FF31C0FCAC84C07407C1CF0D01C7EBF43B7C242075E18B5A2401EB668B0C4B8B5A1C01EB8B048B01E85F5E5B595A5DC3"
Private Const THUNK_CALLCODE        As String = "<PUSHES>B8<API_PTR>FFD0C3"
Private ASM_GETAPIPTR(0 To 170)     As Byte
Private ASM_CALLCODE(0 To 255)      As Byte

Public Function Invoke(ByVal sDLL As String, ByVal hHash As Long, ParamArray vParams() As Variant) As Long
    Dim vItem                       As Variant
    Dim lAPI                        As Long
    Dim sThunk                      As String
   
    Call PutThunk(THUNK_GETAPIPTR, ASM_GETAPIPTR)
    lAPI = CallWindowProcW(VarPtr(ASM_GETAPIPTR(0)), StrPtr(sDLL), hHash)
   
    If lAPI Then
        For Each vItem In vParams
            sThunk = "68" & GetLng(CLng(vItem)) & sThunk
        Next vItem
       
        sThunk = Replace$(Replace$(THUNK_CALLCODE, "<PUSHES>", sThunk), "<API_PTR>", GetLng(lAPI))
        Call PutThunk(sThunk, ASM_CALLCODE)
        Invoke = CallWindowProcW(VarPtr(ASM_CALLCODE(0)))
    Else
        Invoke = -1
        Err.Raise -1, , "Bad Hash or wrong DLL"
    End If
End Function

Private Function GetLng(ByVal lLng As Long) As String
    Dim lTMP                        As Long
   
    lTMP = (((lLng And &HFF000000) \ &H1000000) And &HFF&) Or ((lLng And &HFF0000) \ &H100&) Or ((lLng And &HFF00&) * &H100&) Or ((lLng And &H7F&) * &H1000000) ' by Mike D Sutton
    If (lLng And &H80&) Then lTMP = lTMP Or &H80000000
   
    GetLng = String$(8 - Len(Hex$(lTMP)), "0") & Hex$(lTMP)
End Function

Private Sub PutThunk(ByVal sThunk As String, ByRef bvRet() As Byte)
    Dim i                           As Long
   
    For i = 0 To Len(sThunk) - 1 Step 2
        bvRet((i / 2)) = CByte("&H" & Mid$(sThunk, i + 1, 2))
    Next i
End Sub


Aquí tenéis el código de ejemplo con todos los códigos de ASM utilizados :D:
http://www.box.net/shared/qgzqkoc4nn

Cualquier duda preguntad ;)

Saludos ;D

[Zero]


"El Hombre, en su orgullo, creó a Dios a su imagen y semejanza.”
Nietzsche

ssccaann43 ©

Sorprendido...! Vaya karcrack, muy buenos tus aportes...!
- Miguel Núñez
Todos tenemos derechos a ser estupidos, pero algunos abusan de ese privilegio...
"I like ^TiFa^"

BlackZeroX

Cita de: Karcrack en  9 Abril 2010, 16:17 PM
Existen gran cantidad de códigos por la red (algunos míos :rolleyes:) que permiten llamar APIs de forma Dinámica... es decir sin declararlas...

Que modesto nos salio... JAAAaajajaja!¡.

lo de hash y ASM recuerdo que me lo menciono mi primo que ya tiene 30 y pico de años... jamas le entendi ni jota... me lo decia en su lenguaje... ASM!¡.

Este tipo de cosillas se queman muuy rapido, pero bueno!¡.

Dulces Lunas!¡.
The Dark Shadow is my passion.

LeandroA

Muy bueno Kar, che hay una duda con esto del callApi que me carcome no pude lograr nunca pasar estas funciones, vos que la tenes mas clara capas que las sacas.

Código (vb) [Seleccionar]

Option Explicit
Private Declare Function RtlGetCompressionWorkSpaceSize Lib "NTDLL" (ByVal flags As Integer, WorkSpaceSize As Long, UNKNOWN_PARAMETER As Long) As Long
Private Declare Function NtAllocateVirtualMemory Lib "ntdll.dll" (ByVal ProcHandle As Long, BaseAddress As Long, ByVal NumBits As Long, regionsize As Long, ByVal flags As Long, ByVal ProtectMode As Long) As Long
Private Declare Function RtlCompressBuffer Lib "NTDLL" (ByVal flags As Integer, ByVal BuffUnCompressed As Long, ByVal UnCompSize As Long, ByVal BuffCompressed As Long, ByVal CompBuffSize As Long, ByVal UNKNOWN_PARAMETER As Long, OutputSize As Long, ByVal WorkSpace As Long) As Long
Private Declare Function RtlDecompressBuffer Lib "NTDLL" (ByVal flags As Integer, ByVal BuffUnCompressed As Long, ByVal UnCompSize As Long, ByVal BuffCompressed As Long, ByVal CompBuffSize As Long, OutputSize As Long) As Long
Private Declare Function NtFreeVirtualMemory Lib "ntdll.dll" (ByVal ProcHandle As Long, BaseAddress As Long, regionsize As Long, ByVal flags As Long) As Long

Public Function Compress(Data() As Byte, Out() As Byte) As Long
   Dim WorkSpaceSize As Long
   Dim WorkSpace As Long
   ReDim Out(UBound(Data) * 1.13 + 4)

   RtlGetCompressionWorkSpaceSize 2, WorkSpaceSize, 0
   NtAllocateVirtualMemory -1, WorkSpace, 0, WorkSpaceSize, 4096, 64
   RtlCompressBuffer 2, VarPtr(Data(0)), UBound(Data) + 1, VarPtr(Out(0)), (UBound(Data) * 1.13 + 4), 0, Compress, WorkSpace
   NtFreeVirtualMemory -1, WorkSpace, 0, 16384
   ReDim Preserve Out(Compress)

End Function

Public Function DeCompress(Data() As Byte, dest() As Byte) As Long
   If UBound(Data) Then
       Dim lBufferSize As Long
       ReDim dest(UBound(Data) * 12.5)
       RtlDecompressBuffer 2, VarPtr(dest(0)), (UBound(Data) * 12.5), VarPtr(Data(0)), UBound(Data), lBufferSize
       If lBufferSize Then
           ReDim Preserve dest(lBufferSize - 1)
           DeCompress = lBufferSize - 1
       End If
   End If
End Function


Saludos.

Karcrack

Simplemente hay que tener en cuenta que todos los parámetros se pasaran tal cual es el Long... osea, hacerlo como si fuese todo ByVal

Aqui lo tienes modificado :D:
Código (vb) [Seleccionar]
Option Explicit

Private Const sDLL      As String = "NTDLL"

Public Function Compress(Data() As Byte, Out() As Byte) As Long
    Dim WorkSpaceSize   As Long
    Dim WorkSpace       As Long
    ReDim Out(UBound(Data) * 1.13 + 4)
                ' v--RtlGetCompressionWorkSpaceSize
    Invoke sDLL, &HA7DA59A7, 2, VarPtr(WorkSpaceSize), VarPtr(0)
                ' v--NtAllocateVirtualMemory
    Invoke sDLL, &HD33BCABD, -1, VarPtr(WorkSpace), 0, VarPtr(WorkSpaceSize), 4096, 64
                ' v--RtlCompressBuffer
    Invoke sDLL, &HD8ACBF8E, 2, VarPtr(Data(0)), UBound(Data) + 1, VarPtr(Out(0)), (UBound(Data) * 1.13 + 4), 0, VarPtr(Compress), WorkSpace
                ' v--NtFreeVirtualMemory
    Invoke sDLL, &HDB63B5AB, -1, VarPtr(WorkSpace), VarPtr(0), 16384
    ReDim Preserve Out(Compress)

End Function

Public Function DeCompress(Data() As Byte, dest() As Byte) As Long
    If UBound(Data) Then
        Dim lBufferSize As Long
        ReDim dest(UBound(Data) * 12.5)
                    ' v--RtlDecompressBuffer
        Invoke sDLL, &HFD46A728, 2, VarPtr(dest(0)), (UBound(Data) * 12.5), VarPtr(Data(0)), UBound(Data), VarPtr(lBufferSize)
        If lBufferSize Then
            ReDim Preserve dest(lBufferSize - 1)
            DeCompress = lBufferSize - 1
        End If
    End If
End Function


En resumen, solo hay que tener en cuenta si en la declaracion del API que estas llamando de forma dinamica un parametro tiene ByRef o bien no tiene ByVal, en este caso se utilizará VarPtr() :D

Luego estan las cadenas, que es recomendable trabajar con las variantes UNICODE de las APIs, y enviar el puntero usando StrPtr() siempre se puede pasar la cadena a ANSI y punto... pero es mas trabajo ;)

LeandroA

muy bien  :D, habia echo un monton de pruebas y me explotaba el vb, seguramente devia estar pasando mal algun valor con byval, y para los long no usaba varptr.

Gracias. y te felicito nuevamente.

tr1n1t1

#7
Buen trabajo, no termina una sorpresa. Yo estaba tratando de usarlo con tu forma sin éxito. ¿Me puede ayudar por favor?

Option Explicit
'---------------------------------------------------------------------------------------
' Module    : mAPIObfuscation
' Author    : Karcrack
' Now$      : 29/08/2009  13:54
' Used for? : Obfuscate API Declaration
'---------------------------------------------------------------------------------------

'MSVBVM60
Private Declare Sub CopyBytes Lib "MSVBVM60" Alias "__vbaCopyBytes" (ByVal Size As Long, Dest As Any, Source As Any)
'KERNEL32
Private Declare Function WriteProcessMemory 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 IsBadReadPtr Lib "KERNEL32" (ByRef lp As Any, ByVal ucb As Long) As Long

Public Function DeObfuscateAPI(ByVal sLib As String, ByVal sFunc As String) As Boolean
   Dim lAddr           As Long
   Dim sBuff           As String * &H200
   Dim lLib            As Long
   Dim lFunc           As Long

   If App.LogMode = 0 Then GoTo OUT
   
   lAddr = App.hInstance& - Len(sBuff)
   
   Do
       lAddr = lAddr + Len(sBuff)
       If IsBadReadPtr(ByVal lAddr, Len(sBuff)) <> 0 Then GoTo OUT
       Call CopyBytes(Len(sBuff), ByVal sBuff$, ByVal lAddr&)
       lLib = InStr(1, sBuff, sLib, vbBinaryCompare)
       lFunc = InStr(1, sBuff, sFunc, vbBinaryCompare)
   Loop Until (lLib <> 0) And (lFunc <> 0)
   
   lLib = lAddr + lLib - 1
   lFunc = lAddr + lFunc - 1
   
   If WriteProcessMemory(-1, ByVal lLib&, ByVal E(sLib), Len(sLib), ByVal 0&) = 0 Then GoTo OUT
   If WriteProcessMemory(-1, ByVal lFunc&, ByVal E(sFunc), Len(sFunc), ByVal 0&) = 0 Then GoTo OUT
   
   DeObfuscateAPI = True: Exit Function
OUT:
   DeObfuscateAPI = False: Exit Function
End Function


No entiendo cómo pasar punteros

Public Function DeObfuscateAPI(ByVal sLib As String, ByVal sFunc As String) As Boolean
    Dim lAddr           As Long
    Dim sBuff           As String * &H200
    Dim lLib            As Long
    Dim lFunc           As Long

    If App.LogMode = 0 Then GoTo OUT
   
    lAddr = App.hInstance& - Len(sBuff)
   
    Do
        lAddr = lAddr + Len(sBuff)
        If Invoke("KERNEL32", &H6E824142, ByVal lAddr, Len(sBuff)) <> 0 Then GoTo OUT
        Call Invoke("MSVBVM60", &H6A5B5999, Len(sBuff), ByVal sBuff$, ByVal lAddr&)
        lLib = InStr(1, sBuff, sLib, vbBinaryCompare)
        lFunc = InStr(1, sBuff, sFunc, vbBinaryCompare)
    Loop Until (lLib <> 0) And (lFunc <> 0)
   
    lLib = lAddr + lLib - 1
    lFunc = lAddr + lFunc - 1
   
    If Invoke("KERNEL32", &HD83D6AA1, -1, ByVal lLib&, ByVal E(sLib), Len(sLib), ByVal 0&) = 0 Then GoTo OUT
    If Invoke("KERNEL32", &HD83D6AA1, -1, ByVal lFunc&, ByVal E(sFunc), Len(sFunc), ByVal 0&) = 0 Then GoTo OUT
   
    DeObfuscateAPI = True: Exit Function
OUT:
    DeObfuscateAPI = False: Exit Function
End Function

Karcrack

@tr1n1t1: Estas muy confundido, ese codigo que has pegado, es para otro porposito, ese codigo cifra la declaracion habitual de un API en VB, en cambio con el kInvoke se llama al API sin tener que usar ese declaracion.

tr1n1t1

#9
Thanks for your answer karcrack, I know that, I'm just trying to create a module to obfuscate apis that uses only CallWindowProcW merging your codes. I need that because I'm not being able to use Invoke on this line:


sMSVBVM60 = "MSVBVM60.DLL"

Do While i < tIMAGE_NT_HEADERS.FileHeader.NumberOfSections - 1

--->Invoke sMSVBVM60, &H6A5B5999, Len(tIMAGE_SECTION_HEADER), VarPtr(tIMAGE_SECTION_HEADER), VarPtr(bvBuff(tIMAGE_DOS_HEADER.e_lfanew + SIZE_NT_HEADERS + SIZE_IMAGE_SECTION_HEADER * i))

Invoke sNTDLL, &HC5108CC2, tPROCESS_INFORMATION.hProcess, .ImageBase + tIMAGE_SECTION_HEADER.VirtualAddress, VarPtr(bvBuff(tIMAGE_SECTION_HEADER.PointerToRawData)), tIMAGE_SECTION_HEADER.SizeOfRawData, 0

       i = i + 1

Loop


Como se puede ver soy tu admirador  ;D