当前位置:编程学习 > VB >>

内存扫描可实现数值小于255的查找

’模块
Option Explicit
Public Type SYSTEM_INFO
        dwOemID As Long
        dwPageSize As Long
        lpMinimumApplicationAddress As Long
        lpMaximumApplicationAddress As Long
        dwActiveProcessorMask As Long
        dwNumberOrfProcessors As Long
        dwProcessorType As Long
        dwAllocationGranularity As Long
        dwReserved As Long
End Type
Public Const STANDARD_RIGHTS_REQUIRED = &HF0000
Public Const SYNCHRONIZE = &H100000
Public Const SPECIFIC_RIGHTS_ALL = &HFFFF
Public Const STANDARD_RIGHTS_ALL = &H1F0000
Public Const PROCESS_ALL_ACCESS = STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or &HFFF
Public Const PROCESS_VM_OPERATION = &H8&
Public Const PROCESS_VM_READ = &H10&
Public Const PROCESS_VM_WRITE = &H20&
Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Public Declare Function ReadProcessMemory Lib "kernel32" (ByVal hProcess As Long, lpBaseAddress As Long, lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Public Declare Function WriteProcessMemory Lib "kernel32" (ByVal hProcess As Long, lpBaseAddress As Any, lpBuffer As Any, ByVal nSize As Long, lpNumberOfBytesWritten As Long) As Long
Public Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Public Declare Sub GetSystemInfo Lib "kernel32" (lpSystemInfo As SYSTEM_INFO)
Public Declare Function GetWindowThreadProcessId Lib "user32" _
(ByVal hwnd As Long, lpdwProcessId As Long) As Long
Public Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Public Type MEMORY_BASIC_INFORMATION
     BaseAddress As Long
     AllocationBase As Long
     AllocationProtect As Long
     RegionSize As Long
     State As Long
     Protect As Long
     lType As Long
End Type
Public Declare Function VirtualQueryEx Lib "kernel32" (ByVal hProcess As Long, lpAddress As Any, lpBuffer As MEMORY_BASIC_INFORMATION, ByVal dwLength As Long) As Long
'Public Const STANDARD_RIGHTS_REQUIRED = &HF0000
'Public Const SYNCHRONIZE = &H100000
'Public Const SPECIFIC_RIGHTS_ALL = &HFFFF
'Public Const STANDARD_RIGHTS_ALL = &H1F0000
'Public Const PROCESS_ALL_ACCESS = STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or &HFFF

Public Const MEM_COMMIT = &H1000
Public Const MEM_FREE = &H10000
Public Const MEM_RESERVE = &H2000

Public Const PAGE_NOACCESS = &H1
Public Const PAGE_READONLY = &H2
Public Const PAGE_READWRITE = &H4
Public Const PAGE_WRITECOPY = &H8
Public Const PAGE_EXECUTE = &H10
Public Const PAGE_EXECUTE_READ = &H20
Public Const PAGE_EXECUTE_READWRITE = &H40
Public Const PAGE_EXECUTE_WRITECOPY = &H80
Public Const PAGE_GUARD = &H100
Public Const PAGE_NOCACHE = &H200

Public Const SEC_IMAGE = &H1000000
Public Const MEM_MAPPED = &H40000
Public Const MEM_PRIVATE = &H20000
Public Const MEM_IMAGE = SEC_IMAGE

’窗体
Option Explicit
Dim hProcess As Long
Dim hProcessID As Long
Dim hThreadID As Long
Dim hWndOfApp As Long
Dim hSysInfo As SYSTEM_INFO
Dim lBassAddr As Long
Private Sub Command1_Click()
List2.Clear
Dim s() As Byte, n As Long, i As Long
lBassAddr = Text2.Text
n = Text3.Text
ReDim s(n - 1)
hWndOfApp = FindWindow(vbNullString, Text1.Text)
If hWndOfApp = 0 Then
    MsgBox "無法找到該視窗"
    Exit Sub
End If
hThreadID = GetWindowThreadProcessId(hWndOfApp, hProcessID)
If hProcessID = 0 Then
    MsgBox "無法取得ProcessID"
    Exit Sub
End If
    
hProcess = OpenProcess(PROCESS_ALL_ACCESS, 0, hProcessID)

If hProcess = 0 Then
    MsgBox "無法開啟該Process"
    Exit Sub
End If
 
ReadProcessMemory hProcess, ByVal lBassAddr, s(0), n, ByVal 0&
For i = 0 To n - 1
    List2.AddItem "位址:" & (i + lBassAddr) & "= " & s(i)
Next


CloseHandle hProcess
End Sub

Private Sub Command2_Click()
Dim s() As Byte, n As Long, i As Long
Dim Data1 As Byte, Data2 As Integer, Data4 As Long
lBassAddr = Text4.Text
If Option1(0).Value Then
    n = 1
    ReDim s(0)
    Data1 = Text5.Text
    CopyMemory s(0), Data1, n
ElseIf Option1(1).Value Then
    n = 2
    ReDim s(0 To 1)
    Data2 = Text5.Text
    CopyMemory s(0), Data2, n
ElseIf Option1(2).Value Then
    n = 4
    ReDim s(0 To 3)
    Data4 = Text5.Text
    CopyMemory s(0), Data4, n
End If

'ReDim s(n - 1)
hWndOfApp = FindWindow(vbNullString, Text1.Text)
hThreadID = GetWindowThreadProcessId(hWndOfApp, hProcessID)
hProcess = OpenProcess(PROCESS_ALL_ACCESS, 0, hProcessID)
WriteProcessMemory hProcess, ByVal lBassAddr, s(0), n, ByVal 0&
CloseHandle hProcess
End Sub

Private Sub Command3_Click()
Dim mbi As MEMORY_BASIC_INFORMATION
Dim hwnd As Long, hProcessID As Long
Dim tmpBassAddr As Double, lBassAddr As Long
Dim BassAddr() As Long, PageSize() As Long, PageNum As Long
hwnd = FindWindow(vbNullString, Text1.Text)
If hwnd = 0 Then
    MsgBox "無法找到該視窗"
    Exit Sub
End If
Call GetWindowThreadProcessId(hwnd, hProcessID)
If hProcessID = 0 Then
    MsgBox "無法取得ProcessID"
    Exit Sub
End If
    List1.Clear
    List3.Clear
    Text7 = hProcessID
hProcess = OpenProcess(PROCESS_ALL_ACCESS, 0, hProcessID)
If hProcess = 0 Then
    MsgBox "無法開啟該Process"
    Exit Sub
End If

Do While VirtualQueryEx(hProcess, ByVal lBassAddr, mbi, Len(mbi))
    tmpBassAddr = mbi.BaseAddress
    tmpBassAddr = tmpBassAddr + mbi.RegionSize
    If tmpBassAddr > hSysInfo.lpMaximumApplicationAddress Then '預防溢位
        Exit Do
    End If
    
    If mbi.State = MEM_COMMIT Then '已配置
        If mbi.Protect And (PAGE_READWRITE Or PAGE_EXECUTE_READWRITE Or PAGE_EXECUTE_WRITECOPY) Then
            '符合 紀錄基底位址以及區塊大小
            ReDim Preserve BassAddr(PageNum)
            ReDim Preserve PageSize(PageNum)
            BassAddr(PageNum) = mbi.BaseAddress
            PageSize(PageNum) = mbi.RegionSize
            PageNum = PageNum + 1
        End If
    End If
    
    lBassAddr = tmpBassAddr '對應下一筆
Loop

Dim data() As Byte, i As Long, j As Long, k As Long
Dim finded As Long, fio As Byte, buffer As Long
fio = CByte(Text6.Text)
For i = 0 To PageNum - 1
    ReDim data(1 To PageSize(i))
    ReadProcessMemory hProcess, ByVal BassAddr(i), data(1), PageSize(i), ByVal 0&
    For j = 1 To PageSize(i)
        If data(j) = fio Then
            List1.AddItem Hex(BassAddr(i) + j - 1)
             ReadProcessMemory hProcess, ByVal BassAddr(i) + j - 1, buffer, 4, ByVal 0&
            If buffer = Text6 Then List3.AddItem BassAddr(i) + j - 1
            DoEvents
            finded = finded + 1
        End If
    Next
Next
MsgBox "執行完畢 一共找到 " & finded & "筆資料"
CloseHandle hProcess

Erase BassAddr
Erase PageSize
End Sub

Private Sub Command4_Click()
'Timer1.Enabled = True
Dim i, buffer As Long
List4.Clear
hProcessID = Text7
Call OpenProcess(PROCESS_ALL_ACCESS, 0, hProcessID)
'Do While Text7 <> ""
For i = 0 To List3.ListCount - 1
Text8 = List3.List(i)
If Text8 <> "" Then
List4.AddItem buffer
If ReadProcessMemory(hProcess, ByVal CLng(Text8), buffer, 4, ByVal 0&) Then
If buffer <> Text6 Then List3.RemoveItem (i)
End If


End If
DoEvents
Next
'Loop

CloseHandle hProcess
End Sub

Private Sub Form_Load()

GetSystemInfo hSysInfo
Text2.Text = hSysInfo.lpMinimumApplicationAddress
Text4.Text = hSysInfo.lpMaximumApplicationAddress
Label5.Caption = "可用位址從" & hSysInfo.lpMinimumApplicationAddress & _
" 到 " & hSysInfo.lpMaximumApplicationAddress

End Sub

Private Sub Form_Unload(Cancel As Integer)
CloseHandle hProcess
End Sub

Private Sub List3_Click()
Text8 = List3.Text
End Sub

Private Sub Timer1_Timer()
Dim i, buffer As Long
For i = 0 To List3.ListCount - 1

Next
End Sub

我想实现查找字符串和长整数,请大家帮我改下,如果能改进此方法,使查找更快就更好了
--------------------编程问答-------------------- 直接读取内存地址,试问你怎么分辨它是Long?我看不可能 --------------------编程问答-------------------- 我想搜索518,这个数填在text6里,运行就会出错了呀 --------------------编程问答-------------------- 用byte型数组获得的每一个字节内容全部都是小于等于255的. --------------------编程问答--------------------
引用 3 楼 wallescai 的回复:
用byte型数组获得的每一个字节内容全部都是小于等于255的.

老蔡就喜欢挖帖子玩。。。
沉贴挖掘专家 --------------------编程问答-------------------- 我也来挖一下吧.

顺便发两个网上下载的内存搜索代码:

[分享]网上流传的一个游戏修改器(VB6代码)

【开源】CheatMaster内存地址查找或修改器
--------------------编程问答--------------------
引用 4 楼 veron_04 的回复:
引用 3 楼 wallescai 的回复:
用byte型数组获得的每一个字节内容全部都是小于等于255的.

老蔡就喜欢挖帖子玩。。。
沉贴挖掘专家


汗啊, 这个帖子不算久吧... --------------------编程问答--------------------
引用 5 楼 myjian 的回复:
我也来挖一下吧.

顺便发两个网上下载的内存搜索代码:

[分享]网上流传的一个游戏修改器(VB6代码)

【开源】CheatMaster内存地址查找或修改器

都打不开。 --------------------编程问答-------------------- 这个很简单吧,发个自己用的模块

'Attribute VB_Name = "modMemory"
'内存搜索、读取、写入通用模块,biqiang 2007年11月24日

Option Explicit

Private Declare Function GetWindowThreadProcessId Lib "user32.dll" ( _
     ByVal hwnd As Long, _
     ByRef lpdwProcessId As Long) As Long
Private Declare Function OpenProcess Lib "kernel32.dll" ( _
     ByVal dwDesiredAccess As Long, _
     ByVal bInheritHandle As Long, _
     ByVal dwProcessId As Long) As Long
Private Declare Function CloseHandle Lib "kernel32.dll" ( _
     ByVal hObject As Long) As Long
Private Declare Function ReadProcessMemory Lib "kernel32.dll" ( _
     ByVal hProcess As Long, _
     ByVal lpBaseAddress As Long, _
     ByRef lpBuffer As Any, _
     ByVal nSize As Long, _
     ByRef lpNumberOfBytesWritten As Long) As Long
Private Declare Function WriteProcessMemory Lib "kernel32.dll" ( _
     ByVal hProcess As Long, _
     ByVal lpBaseAddress As Long, _
     ByRef lpBuffer As Any, _
     ByVal nSize As Long, _
     ByRef lpNumberOfBytesWritten As Long) As Long
Private Declare Function VirtualQueryEx Lib "kernel32.dll" ( _
     ByVal hProcess As Long, _
     ByVal lpAddress As Long, _
     ByRef lpBuffer As MEMORY_BASIC_INFORMATION, _
     ByVal dwLength As Long) As Long
Private Type MEMORY_BASIC_INFORMATION
    BaseAddress As Long
    AllocationBase As Long
    AllocationProtect As Long
    RegionSize As Long
    State As Long
    Protect As Long
    lType As Long
End Type

Private Const STANDARD_RIGHTS_REQUIRED As Long = &HF0000
Private Const SYNCHRONIZE As Long = &H100000
Private Const SPECIFIC_RIGHTS_ALL As Long = &HFFFF&
Private Const STANDARD_RIGHTS_ALL As Long = &H1F0000
Private Const PROCESS_ALL_ACCESS As Long = (STANDARD_RIGHTS_REQUIRED Or SYNCHRONIZE Or &HFFF)
Private Const PROCESS_VM_OPERATION As Long = (&H8)
Private Const PROCESS_VM_READ As Long = (&H10)
Private Const PROCESS_VM_WRITE As Long = (&H20)
Private Const PROCESS_QUERY_INFORMATION As Long = (&H400)
Private Const MEM_COMMIT As Long = &H1000

'通过窗口句柄进行搜索
'参数: hwnd            窗口句柄
'       StartAddr       开始地址
'       SearchData()    要搜索的数据,Byte数组形式
'       FindData()      搜索到的数据,Byte数组形式
'       FindLen         希望返回搜索到数据的长度
'返回:搜索到内存地址,返回-1失败
Public Function SearchMemByHwnd(ByVal hwnd As Long, ByVal StartAddr As Long, SearchData() As Byte) As Long
    Dim ProcessId As Long
    GetWindowThreadProcessId hwnd, ProcessId
    SearchMemByHwnd = SearchMemByProcessId(ProcessId, StartAddr, SearchData())
End Function

'通过进程标识符进行搜索
'参数: ProcessId       进程标识符
'       StartAddr       开始地址
'       SearchData()    要搜索的数据,Byte数组形式
'       FindData()      搜索到的数据,Byte数组形式
'       FindLen         希望返回搜索到数据的长度
'返回:搜索到的内存地址,返回-1失败
Public Function SearchMemByProcessId(ByVal ProcessId As Long, ByVal StartAddr As Long, SearchData() As Byte) As Long
    Dim hProcess As Long, ret As Long, FindPos As Long, pAddr As Long
    Dim mi As MEMORY_BASIC_INFORMATION, miLen As Long
    Dim ReadData() As Byte, dwRead As Long
    SearchMemByProcessId = -1
    '赋予所有权限有可能无法进行,只是读内存数据的话,没必要赋予所有权限
    'hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or PROCESS_VM_OPERATION Or PROCESS_VM_READ Or PROCESS_VM_WRITE, 0, ProcessId)
    hProcess = OpenProcess(PROCESS_QUERY_INFORMATION Or PROCESS_VM_READ, 0, ProcessId)
    If hProcess Then
        miLen = Len(mi)
        pAddr = StartAddr
        ret = VirtualQueryEx(hProcess, ByVal pAddr, mi, miLen)
        Do While (ret = miLen)
            If mi.State = MEM_COMMIT Then
                ReDim ReadData(0 To mi.RegionSize - 1)
                ret = ReadProcessMemory(hProcess, ByVal mi.BaseAddress, ReadData(0), mi.RegionSize, dwRead)
                If ret <> 0 And dwRead = mi.RegionSize Then
                    If pAddr = StartAddr And StartAddr > mi.BaseAddress Then
                        FindPos = InStrB(StartAddr - mi.BaseAddress + 1, ReadData, SearchData)
                    Else
                        FindPos = InStrB(1, ReadData, SearchData)
                    End If
                    If FindPos > 0 Then
                        SearchMemByProcessId = mi.BaseAddress + FindPos - 1
                        Exit Do
                    End If
                End If
            End If
            pAddr = mi.BaseAddress + mi.RegionSize
            ret = VirtualQueryEx(hProcess, ByVal pAddr, mi, miLen)
        Loop
        CloseHandle (hProcess)
    End If
End Function

'通过窗口句柄读取内存
'参数: hwnd            窗口句柄
'       StartAddr       读取内容的起始地址
'       ReadLen         读取内容的长度
'       ReadBuf()       接收读取内容的缓冲区,Byte数组形式
'返回: Long型,返回实际读取的长度,0表示不成功
Public Function ReadMemByHwnd(ByVal hwnd As Long, ByVal StartAddr As Long, ByVal ReadLen As Long, ReadBuf() As Byte) As Long
    Dim ProcessId As Long
    GetWindowThreadProcessId hwnd, ProcessId
    ReadMemByHwnd = ReadMemByProcessId(ProcessId, StartAddr, ReadLen, ReadBuf())
End Function

'通过进程标识符读取内存
'参数: ProcessId       进程标识符
'       StartAddr       读取内容的起始地址
'       ReadLen         读取内容的长度
'       ReadBuf()       接收读取内容的缓冲区,Byte数组形式
'返回: Long型,返回实际读取的长度,0表示不成功
Public Function ReadMemByProcessId(ByVal ProcessId As Long, ByVal StartAddr As Long, ByVal ReadLen As Long, ReadBuf() As Byte) As Long
    Dim ret As Long, dwRead As Long, hProcess As Long
    hProcess = OpenProcess(PROCESS_VM_READ, 0, ProcessId)
    If hProcess = 0 Then
        ReadMemByProcessId = 0
    Else
        If ReadLen > 0 Then
            ReDim ReadBuf(0 To ReadLen - 1)
            ret = ReadProcessMemory(hProcess, ByVal StartAddr, ReadBuf(0), ReadLen, dwRead)
            If ret <> 0 Then
                ReadMemByProcessId = dwRead
            Else
                ReadMemByProcessId = 0
            End If
        Else
            ReadMemByProcessId = 0
        End If
    End If
End Function

'通过窗口句柄写入内存
'参数: hwnd            窗口句柄
'       StartAddr       写入内容的起始地址
'       WriteLen        写入内容的长度
'       WriteBuf()      需要写入内容的缓冲区,Byte数组形式
'返回: Long型,返回实际写入的长度,0表示不成功
Public Function WriteMemByHwnd(ByVal hwnd As Long, ByVal StartAddr As Long, ByVal WriteLen As Long, WriteData) As Long
    Dim ProcessId As Long
    GetWindowThreadProcessId hwnd, ProcessId
    WriteMemByHwnd = WriteMemByProcessId(ProcessId, StartAddr, WriteLen, WriteData)
End Function

'通过进程标识符写入内存
'参数: ProcessId       进程标识符
'       StartAddr       写入内容的起始地址
'       WriteLen        写入内容的长度
'       WriteBuf()      需要写入内容的缓冲区,Byte数组形式
'返回: Long型,返回实际写入的长度,0表示不成功
Public Function WriteMemByProcessId(ByVal ProcessId As Long, ByVal StartAddr As Long, ByVal WriteLen As Long, WriteData) As Long
    Dim ret As Long, dwWrite As Long, hProcess As Long
    hProcess = OpenProcess(PROCESS_VM_WRITE, 0, ProcessId)
    If hProcess = 0 Then
        WriteMemByProcessId = 0
    Else
        If WriteLen > 0 Then
            ret = WriteProcessMemory(hProcess, ByVal StartAddr, WriteData, WriteLen, dwWrite)
            If ret <> 0 Then
                WriteMemByProcessId = dwWrite
            Else
                WriteMemByProcessId = 0
            End If
        Else
            WriteMemByProcessId = 0
        End If
    End If
End Function


要搜索数值型数据的话,将数值按字节依次传送给SearchData()字节数组就行了,用CopyMemory可能方便些吧。
要搜索字符串数据的话,就更简单了。如果搜索内存中的Unicode字符串,直接进行赋值就行了:

    Dim a() As Byte, s As String
    s = "VB还是不错的!"
    a = s '数组a即可作为参数的SearchData()字节数组进行传递

如果搜索内存中的ANSI字符串,就要转换一下了:

    Dim a() As Byte, s As String
    s = StrConv("VB还是不错的!", vbFromUnicode)
    a = s '数组a即可作为参数的SearchData()字节数组进行传递
--------------------编程问答-------------------- 这个模块的写入功能好久没用,参数的说明与实际好像有些出入,函数中好像可以写入任意数据,说明是字节数组,不过没什么大关系吧 --------------------编程问答--------------------
引用 7 楼  的回复:
引用 5 楼 myjian 的回复:
我也来挖一下吧.

顺便发两个网上下载的内存搜索代码:

[分享]网上流传的一个游戏修改器(VB6代码)

【开源】CheatMaster内存地址查找或修改器

都打不开。

不是吧.

这IP目前还没被墙吧.
补充:VB ,  API
CopyRight © 2012 站长网 编程知识问答 www.zzzyk.com All Rights Reserved
部份技术文章来自网络,