⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 mod_mapmemory.bas

📁 使用底层技术结束进程。The use of the underlying technology end of the process.
💻 BAS
字号:
Attribute VB_Name = "mod_MapMemory"
Option Explicit

'Private Const STATUS_INFO_LENGTH_MISMATCH = &HC0000004

Private Const STATUS_ACCESS_DENIED = &HC0000022

'Private Const STATUS_INVALID_HANDLE = &HC0000008

'Private Const ERROR_SUCCESS = 0&

Private Const SECTION_MAP_WRITE = &H2

Private Const SECTION_MAP_READ = &H4

Private Const READ_CONTROL = &H20000

Private Const WRITE_DAC = &H40000

Private Const NO_INHERITANCE = 0

Private Const DACL_SECURITY_INFORMATION = &H4

'Private Type IO_STATUS_BLOCK
'        Status As Long
'        Information As Long
'End Type

Private Type UNICODE_STRING
        Length As Integer
        MaximumLength As Integer
        Buffer As Long
End Type

'Private Const OBJ_INHERIT = &H2

'Private Const OBJ_PERMANENT = &H10

'Private Const OBJ_EXCLUSIVE = &H20

'Private Const OBJ_CASE_INSENSITIVE = &H40

'Private Const OBJ_OPENIF = &H80

Private Const OBJ_OPENLINK = &H100

'Private Const OBJ_KERNEL_HANDLE = &H200

Private Const OBJ_VALID_ATTRIBUTES = &H3F2

Private Type OBJECT_ATTRIBUTES
        Length As Long
        RootDirectory As Long
        ObjectName As Long
        Attributes As Long
        SecurityDescriptor As Long
        SecurityQualityOfService As Long
End Type

'Private Type ACL
'        AclRevision As Byte
'        Sbz1 As Byte
'        AclSize As Integer
'        AceCount As Integer
'        Sbz2 As Integer
'End Type

Private Enum ACCESS_MODE
        NOT_USED_ACCES
        GRANT_ACCESS
        SET_ACCESS
        DENY_ACCESS
        REVOKE_ACCESS
        SET_AUDIT_SUCCESS
        SET_AUDIT_FAILURE
End Enum

Private Enum MULTIPLE_TRUSTEE_OPERATION
        NO_MULTIPLE_TRUSTEE
        TRUSTEE_IS_IMPERSONATE
End Enum

Private Enum TRUSTEE_FORM
        TRUSTEE_IS_SID
        TRUSTEE_IS_NAME
End Enum

Private Enum TRUSTEE_TYPE
        TRUSTEE_IS_UNKNOWN
        TRUSTEE_IS_USER
        TRUSTEE_IS_GROUP
End Enum

Private Type TRUSTEE
        pMultipleTrustee         As Long
        MultipleTrusteeOperation   As MULTIPLE_TRUSTEE_OPERATION
        TrusteeForm             As TRUSTEE_FORM
        TrusteeType             As TRUSTEE_TYPE
        ptstrName             As String
End Type

Private Type EXPLICIT_ACCESS
        grfAccessPermissions       As Long
        grfAccessMode           As ACCESS_MODE
        grfInheritance           As Long
        TRUSTEE               As TRUSTEE
End Type

'Private Type AceArray
'        List() As EXPLICIT_ACCESS
'End Type

Private Enum SE_OBJECT_TYPE
        SE_UNKNOWN_OBJECT_TYPE = 0
        SE_FILE_OBJECT
        SE_SERVICE
        SE_PRINTER
        SE_REGISTRY_KEY
        SE_LMSHARE
        SE_KERNEL_OBJECT
        SE_WINDOW_OBJECT
        SE_DS_OBJECT
        SE_DS_OBJECT_ALL
        SE_PROVIDER_DEFINED_OBJECT
        SE_WMIGUID_OBJECT
End Enum

Private Declare Function SetSecurityInfo _
                Lib "advapi32.dll" (ByVal Handle As Long, _
                                    ByVal ObjectType As SE_OBJECT_TYPE, _
                                    ByVal SecurityInfo As Long, _
                                    ppsidOwner As Long, _
                                    ppsidGroup As Long, _
                                    ppDacl As Any, _
                                    ppSacl As Any) As Long

Private Declare Function GetSecurityInfo _
                Lib "advapi32.dll" (ByVal Handle As Long, _
                                    ByVal ObjectType As SE_OBJECT_TYPE, _
                                    ByVal SecurityInfo As Long, _
                                    ppsidOwner As Long, _
                                    ppsidGroup As Long, _
                                    ppDacl As Any, _
                                    ppSacl As Any, _
                                    ppSecurityDescriptor As Long) As Long
                                        
Private Declare Function SetEntriesInAcl _
                Lib "advapi32.dll" _
                Alias "SetEntriesInAclA" (ByVal cCountOfExplicitEntries As Long, _
                                          pListOfExplicitEntries As EXPLICIT_ACCESS, _
                                          ByVal OldAcl As Long, _
                                          NewAcl As Long) As Long

'Private Declare Sub BuildExplicitAccessWithName _
                Lib "advapi32.dll" _
                Alias "BuildExplicitAccessWithNameA" (pExplicitAccess As EXPLICIT_ACCESS, _
                                                      ByVal pTrusteeName As String, _
                                                      ByVal AccessPermissions As Long, _
                                                      ByVal AccessMode As ACCESS_MODE, _
                                                      ByVal Inheritance As Long)
                                      
Private Declare Sub RtlInitUnicodeString _
                Lib "NTDLL.DLL" (DestinationString As UNICODE_STRING, _
                                 ByVal SourceString As Long)

Private Declare Function ZwOpenSection _
                Lib "NTDLL.DLL" (SectionHandle As Long, _
                                 ByVal DesiredAccess As Long, _
                                 ObjectAttributes As Any) As Long

Private Declare Function LocalFree _
                Lib "kernel32" (ByVal hMem As Any) As Long

Private Declare Function CloseHandle _
                Lib "kernel32" (ByVal hObject As Long) As Long

Private Declare Function MapViewOfFile _
                Lib "kernel32" (ByVal hFileMappingObject As Long, _
                                ByVal dwDesiredAccess As Long, _
                                ByVal dwFileOffsetHigh As Long, _
                                ByVal dwFileOffsetLow As Long, _
                                ByVal dwNumberOfBytesToMap As Long) As Long

Private Declare Function UnmapViewOfFile _
                Lib "kernel32" (lpBaseAddress As Any) As Long

Private Declare Sub CopyMemory _
                Lib "kernel32" _
                Alias "RtlMoveMemory" (ByVal Destination As Long, _
                                       ByVal Source As Long, _
                                       ByVal Length As Long)

'Private g_hNtDLL As Long

Private g_pMapPhysicalMemory As Long

Private g_hMPM As Long
Dim aByte(3) As Byte

'=========Checking OS staff=============
Public Type OSVERSIONINFO
        dwOSVersionInfoSize As Long
        dwMajorVersion As Long
        dwMinorVersion As Long
        dwBuildNumber As Long
        dwPlatformId As Long
        szCSDVersion As String * 128
End Type

Private Declare Function GetVersionEx _
                Lib "kernel32" _
                Alias "GetVersionExA" (LpVersionInformation As OSVERSIONINFO) As Long
Public VerInfo As OSVERSIONINFO

Private Function ByteArrToLong(inByte() As Byte) As Double
        Dim I As Integer

        For I = 0 To 3
                ByteArrToLong = ByteArrToLong + inByte(I) * (&H100 ^ I)
        Next I
  
End Function

Public Function GetData(addr As Long) As Long
        Dim phys As Long, tmp As Long, ret As Long
  
        phys = LinearToPhys(g_pMapPhysicalMemory, addr)
        tmp = MapViewOfFile(g_hMPM, 4, 0, phys And &HFFFFF000, &H1000)

        If tmp <> 0 Then
                ret = tmp + ((phys And &HFFF) / (2 ^ 2)) * 4
                CopyMemory VarPtr(ret), ret, 4
                UnmapViewOfFile tmp
                GetData = ret
        End If

End Function

Private Function LinearToPhys(BaseAddress As Long, _
                              addr As Long) As Long
        Dim VAddr As Long, PGDE As Long, PTE As Long, PAddr As Long
        Dim lTemp As Long
 
        VAddr = addr
        CopyMemory VarPtr(aByte(0)), VarPtr(VAddr), 4
        lTemp = Fix(ByteArrToLong(aByte) / (2 ^ 22))
  
        PGDE = BaseAddress + lTemp * 4
        CopyMemory VarPtr(PGDE), PGDE, 4
 
        If (PGDE And 1) <> 0 Then
                lTemp = PGDE And &H80

                If lTemp <> 0 Then
                        PAddr = (PGDE And &HFFC00000) + (VAddr And &H3FFFFF)
                Else
                        PGDE = MapViewOfFile(g_hMPM, 4, 0, PGDE And &HFFFFF000, &H1000)
                        lTemp = (VAddr And &H3FF000) / (2 ^ 12)
                        PTE = PGDE + lTemp * 4
                        CopyMemory VarPtr(PTE), PTE, 4

                        If (PTE And 1) <> 0 Then
                                PAddr = (PTE And &HFFFFF000) + (VAddr And &HFFF)
                                UnmapViewOfFile PGDE
                        End If
                End If
        End If
  
        LinearToPhys = PAddr

End Function

Public Function OpenPhysicalMemory() As Long
        Dim Status As Long
        Dim PhysmemString As UNICODE_STRING
        Dim Attributes As OBJECT_ATTRIBUTES
 
        RtlInitUnicodeString PhysmemString, StrPtr("\Device\PhysicalMemory")
        Attributes.Length = Len(Attributes)
        Attributes.RootDirectory = 0
        Attributes.ObjectName = VarPtr(PhysmemString)
        Attributes.Attributes = 0
        Attributes.SecurityDescriptor = 0
        Attributes.SecurityQualityOfService = 0
  
        Status = ZwOpenSection(g_hMPM, SECTION_MAP_READ Or SECTION_MAP_WRITE, Attributes)

        If Status = STATUS_ACCESS_DENIED Then
                Status = ZwOpenSection(g_hMPM, READ_CONTROL Or WRITE_DAC, Attributes)
                SetPhyscialMemorySectionCanBeWrited g_hMPM
                CloseHandle g_hMPM
                Status = ZwOpenSection(g_hMPM, SECTION_MAP_READ Or SECTION_MAP_WRITE, Attributes)
        End If
  
        Dim lDirectoty As Long
        VerInfo.dwOSVersionInfoSize = Len(VerInfo)

        If (GetVersionEx(VerInfo)) <> 0 Then
                If VerInfo.dwPlatformId = 2 Then
                        If VerInfo.dwMajorVersion = 5 Then

                                Select Case VerInfo.dwMinorVersion

                                        Case 0
                                                lDirectoty = &H30000

                                        Case 1
                                                lDirectoty = &H39000
                                End Select

                        End If
                End If
        End If
  
        If Status = 0 Then
                g_pMapPhysicalMemory = MapViewOfFile(g_hMPM, 4, 0, lDirectoty, &H1000)

                If g_pMapPhysicalMemory <> 0 Then OpenPhysicalMemory = g_hMPM
        End If
  
End Function

Public Function SetData(ByVal addr As Long, _
                         ByVal data As Long) As Boolean
        Dim phys As Long, tmp As Long, x As Long
  
        phys = LinearToPhys(g_pMapPhysicalMemory, addr)
        tmp = MapViewOfFile(g_hMPM, SECTION_MAP_WRITE, 0, phys And &HFFFFF000, &H1000)

        If tmp <> 0 Then
                x = tmp + ((phys And &HFFF) / (2 ^ 2)) * 4
                CopyMemory x, VarPtr(data), 4
      
                UnmapViewOfFile tmp
                SetData = True
        End If

End Function

Private Sub SetPhyscialMemorySectionCanBeWrited(ByVal hSection As Long)
        Dim pDacl As Long
        Dim pNewDacl As Long
        Dim pSD As Long
        'Dim dwRes As Long
        Dim ea As EXPLICIT_ACCESS
  
        GetSecurityInfo hSection, SE_KERNEL_OBJECT, DACL_SECURITY_INFORMATION, 0, 0, pDacl, 0, pSD
      
        ea.grfAccessPermissions = SECTION_MAP_WRITE
        ea.grfAccessMode = GRANT_ACCESS
        ea.grfInheritance = NO_INHERITANCE
        ea.TRUSTEE.TrusteeForm = TRUSTEE_IS_NAME
        ea.TRUSTEE.TrusteeType = TRUSTEE_IS_USER
        ea.TRUSTEE.ptstrName = "CURRENT_USER" & vbNullChar

        SetEntriesInAcl 1, ea, pDacl, pNewDacl
  
        SetSecurityInfo hSection, SE_KERNEL_OBJECT, DACL_SECURITY_INFORMATION, 0, 0, ByVal pNewDacl, 0
                      
CleanUp:
        LocalFree pSD
        LocalFree pNewDacl
End Sub

Public Function ModifyKernelMemory(ByVal StartAddr As Long, ByVal Length As Long, ByRef lpBuffer() As Byte, Optional ByRef RetStatus As Long) As Boolean
On Error GoTo ModifyKernelMemory_Err_Hdl

        Dim phys As Long, tmp As Long, ret As Long
        Dim writeLength As Long 'read=have read
        Dim leftLength As Long
        Dim mappedLength As Long
        Const MapMemLength = &H1000
        Do
  
                phys = LinearToPhys(g_pMapPhysicalMemory, StartAddr + writeLength)
                tmp = MapViewOfFile(g_hMPM, SECTION_MAP_WRITE, 0, phys And &HFFFFF000, MapMemLength)
                
                If tmp <> 0 Then
                        mappedLength = IIf(leftLength > MapMemLength, MapMemLength, leftLength)
                        ret = tmp + ((phys And &HFFF) / (2 ^ 2)) * 4
                        CopyMemory ret, (VarPtr(lpBuffer(LBound(lpBuffer))) + writeLength), mappedLength
                        writeLength = writeLength + mappedLength
                        UnmapViewOfFile tmp
                        leftLength = Length - writeLength
                End If
        Loop Until (writeLength >= Length)
        ModifyKernelMemory = True
Exit Function
ModifyKernelMemory_Err_Hdl:
        ModifyKernelMemory = False
End Function

Public Function ClosePhysicalMemory() As Boolean
Call CloseHandle(g_pMapPhysicalMemory)
Call CloseHandle(g_hMPM)
ClosePhysicalMemory = True
End Function

Public Function DumpKernelMemory(ByVal StartAddr As Long, ByVal Length As Long, ByRef lpBuffer() As Byte) As Boolean
On Error GoTo DumpKernelMemory_Err_Hdl

        Dim phys As Long, tmp As Long, ret As Long
        Dim readLength As Long 'read=have read
        Dim leftLength As Long
        Const MapMemLength = &H1000
        Do
  
                phys = LinearToPhys(g_pMapPhysicalMemory, StartAddr + readLength)
                tmp = MapViewOfFile(g_hMPM, SECTION_MAP_READ, 0, phys And &HFFFFF000, MapMemLength)
                
                If tmp <> 0 Then
                        ret = tmp + ((phys And &HFFF) / (2 ^ 2)) * 4
                        If (leftLength > MapMemLength) Then leftLength = MapMemLength
                        CopyMemory (VarPtr(lpBuffer(LBound(lpBuffer))) + readLength), ret, leftLength
                        readLength = readLength + MapMemLength
                        UnmapViewOfFile tmp
                        leftLength = Length - readLength
                End If
        Loop Until (readLength >= Length)

        DumpKernelMemory = True
Exit Function
DumpKernelMemory_Err_Hdl:
        DumpKernelMemory = False
End Function

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -