JinGanTec Studio@桂花园

大量多年原生桂花树待售中;Coding in Csharp,Ruby,VBS!

导航

Game Monitor script base on this article

get  "other version information" to define the processes is a game or not ! 

'-- This file is the fully commented version of the class.

'-- This script includes a class and a demo. Drop any PE file onto the script (EXE, DLL, OCX)
'-- to get file properties. The class, ClsProps, is a complete set of all functions needed
'-- get file properties using only VBS and the Textstream object.
'-- The file properties returned are those that are found when a file is right-clicked,
'-- Properties menu is clicked, and Version tab is selected. This information
'-- is included in most PE (portable executable) files.

'-- Thank you to Ed Gruberman (http://www.rjump.com) for help with this code.
'-- He corrected a bug and also worked out the "aspack" variation whereby some
'-- PE files have been compressed and require a different method to find the version info.  j.

'-- NOTE: This script is written to be compact for pasting into scripts. It uses simplified versions of some functions from
'-- the Textstream Binary Ops and Base 64 download, using only the functionality needed to get file version info.,
'--  in order to keep this class as small as possible. If you want to use functions such as GetArray or GetByteString
'-- you may want to download the other package. It provides a fairly complete set of methods for working with binary files.

'  Functions in this class. (All functions are needed for getting file version information.)
'
'   Public Function GetVersionInfo(sFilePath, ARet2)  - returns version information For PE files.
'                                                                On success ARet2 returns array(5) containing version info. strings for file.
'    Function return error codes:    0 = success.      1 = invalid file path.      2 = no .rsrc table listed in section table.
'    3 = failed to find version info.       4 = not a PE file.       5 = file is a 16-bit executable. ("NE" file rather than "PE")
'
'     Private (internal) functions:
'        GetArray(StringIn) - convert a string to an array of byte values.
'        GetByteString(StringIn, SnipUnicode) - convert a string to a manageable version. If SnipUnicode = True then get only every 2nd byte.
'        GetNumFromBytes(array) - takes array of ubound 1 or 3. return numeric value for 2 or 4 bytes.
'
'------- BEGIN CLASS --------------------------------------------------------------------

Class ClsProps
   Private FSO, i, TS, sAst, ANums, Char1
  
  Private Sub Class_Initialize()
       sAst = "*"
       Char1 = Chr(1)
      Set FSO = CreateObject("Scripting.FileSystemObject")
  End Sub
         
  Private Sub Class_Terminate()
      Set TS = Nothing   '-- just in case.
      Set FSO = Nothing
  End Sub

  '-- The public function in this class: GetVersionInfo ----------------------------------------- 


   '-- This reads the resource section tables to find version info.
   '-- After finding the offset of the resource section from the section table,
   '-- it goes through the resource section tables, which are a complex, hierarchical
   '-- index to the Resource section. 1st ("Type") level: This top level lists types of resources
   '-- and points to next layer. find a table entry for a resource with ID 16. That's version info.
   '--  2nd ("Name") level: pointer from 1st level points to a group of resource pointers
   '-- of the specific type. For version info. there's usually just one entry at this level, so just
   '-- get the next pointer from that entry; add that offset to resource section offset, and
   '-- find next (3rd level) table entry. 3rd ("language") level: The 3rd level is one or more
   '-- entries that point to different language versions. This script just gets the first one but
   '-- you could also Write it to iterate through the entries at this level. Each entry of 8 bytes
   '-- will indicate language in first 4 bytes. Example: 09 04 00 00 56 04 00 00.
   '-- Those eight bytes indicate that the American English version info. (H409) pointer can be found
   '-- at 1110 bytes beyond beginning of Resource Section. (1110 = H456).
  '--  That pointer (H456 in the example) should then point to address and size values for version info.
  '--  but it refers to a virtual offset (offset when the file is loaded into memory.
  '--  So the virtual offset of the resource section is deducted from this number to get the offset of file version info. into
  '-- the resource section, then that number is added back to the "raw" offset, as it appears in the file.
  '-- If that method fails to find the offset of "VS_VERSION_INFO" properly then there is one other
  '-- variation here: Some EXEs are compressed using "Aspack". In that case the resource offset will be
  '-- wrong but it can be recalculated by substituting the raw and virtual offsets of the ".aspack" section
  '-- for the raw and virtual offsets of the ".rsrc" section.

Public Function GetVersionInfo(sFilePath, ARet2)  '-- return array(5)
Dim ARet, s1, sB, Pt1, sRes, A1, A4(3), A2(1), LocRes, VLocRes, SizeRes, iOffSet, Boo, sVerString, sMarker
Dim iNum1, iNum2, iReadPt, iNum3, LocAspack, VLocAspack, VIOffset, ReadOffset, BooAspack
     On Error Resume Next
               If (FSO.FileExists(sFilePath) = False) Then
                    GetVersionInfo = 1  'bad path.
                    Exit Function
               End If
       sRes = ".rsrc"
       sVerString = "VS_VER"
       BooAspack = False
          
   Set TS = FSO.OpenTextFile(sFilePath, 1)
       s1 = TS.Read(2048) '-- Read first 2 KB.
       TS.Close
   Set TS = Nothing   
      A1 = GetArray(Mid(s1, 61, 2))  '-- get number value at offset 60 that points to PE signature address.
      iNum1 = (GetNumFromBytes(A1) + 1)     '-- get offset of "PE00"
      sB = GetByteString(s1, False)  '-- get a workable string with Chr(0) replaced by "*".      
       sMarker = Mid(sB, iNum1, 4)
         If (sMarker <> "PE**") Then
                 If Left(sMarker, 2) = "NE" Then
                     GetVersionInfo = 5  '-- 16 bit.
                 Else
                     GetVersionInfo = 4  '-- no PE signature found.
                 End If  
             Exit Function
         End If
         
     Pt1 = InStr(1, sB, sRes)   '-- find .rsrc table.
         If (Pt1 = 0) Then  
              GetVersionInfo = 2  'no resource table header found.
              Exit Function
         End If
     Pt1 = Pt1 + 12  '--  size of raw data is 4 bytes at offset of 16 into the .rsrc table.
        A1 = GetArray(Mid(s1, Pt1, 12))  '-- get the same string as a numeric array to Read offset numbers. 
      

        '----- get virtual offset of .rsrc section ---------------------------------  
           For iOffSet = 0 to 3
                A4(iOffSet) = A1(iOffSet)
           Next
             VLocRes = GetNumFromBytes(A4)

      '----- get raw data size of .rsrc section ---------------------------------  
           For iOffSet = 0 to 3
                A4(iOffSet) = A1(iOffSet + 4)
           Next
             SizeRes = GetNumFromBytes(A4) '--size of resource section in bytes.

   '----- get raw data offset of .rsrc table ---------------------------------
           For iOffSet = 0 to 3
                A4(iOffSet) = A1(iOffSet + 8)
           Next
              LocRes = GetNumFromBytes(A4)    '-- offset location of resource section. 

  
   '------------ Code to check for files compressed with Aspack. Such files will not return
                '-- accurate version info. data with the normal method. Checking for this here because
                '-- the section table info. is handy and a file compressed with Aspack will will have
                '-- a section table listing. If there is a listing, get the raw offset and virtual offset, as
                '-- with the .rsrc section data. Later, if "VS_VER" is not found by the normal method then
                '-- the Aspack offsets will be substituted for the .rsrc offsets.   

          Pt1 = InStr(1, sB, ".aspack")   '-- find .rsrc table.
             If (Pt1 > 0) Then
                  BooAspack = True
                      Pt1 = Pt1 + 12    '--  virtual offset is first 4 bytes; raw offset is bytes 9-12.
                      A1 = GetArray(Mid(s1, Pt1, 12)) 

               '----- get virtual offset of aspack section ---------------------------------                      
                   For iOffSet = 0 to 3
                      A4(iOffSet) = A1(iOffSet)
                   Next
                     VLocAspack = GetNumFromBytes(A4)   

                '----- get raw data offset of aspack section ---------------------------------           
                   For iOffSet = 0 to 3
                      A4(iOffSet) = A1(iOffSet + 8)
                   Next
                     LocAspack = GetNumFromBytes(A4)
              End If   
        '------------------------------ End special file compression aspack code ----------

'---- start Read for search.
   Boo = False
     Set TS = FSO.OpenTextFile(sFilePath, 1)

         '-- go to rsrc section and look in root directory to find number of resources.
         '-- looking for a number resource that's #16, the number designated for File Version Info.

      TS.Skip LocRes + 12  '-- get number of names from bytes 13,14 in top level "Type" directory.
        s1 = TS.Read(2)       '-- Read bytes 13,14 to get number of named resource types.
          iNum1 = Asc(s1)       '-- number of names.
        s1 = TS.Read(2)       '-- Read bytes 15,16 to get number of numbered resource types.
          iNum2 = Asc(s1)       '-- number of nums.
       
  '-- The named resource entries are of no use but the number is required in order to
         '-- Skip past them. Each top-level entry is 8 bytes. The first 4 bytes are name or number.
         '-- The second four bytes are the next offset to look at.
         '-- This needs to find a numbered resource with number 16 (version info.)
         '-- All other data here is irrelevant for this script.

       If (iNum2 = 0) Then '-- no numbered entries. have to quit here.
            TS.Close
            Set TS = Nothing
            GetVersionInfo = 3  'failed to find version info in resource table.
            Exit Function
       End If

  '-- now at end of root directory. Find version info. entry.
    
     If (iNum1 > 0) Then TS.Skip (iNum1 * 8) '-- Skip past named entries.
     iReadPt = LocRes + 16 + (iNum1 * 8)  '-- update file offset variable because this will be needed.
     Boo = False
             '-- loop through numbered directory entries looking for a value of 16 in first 4 bytes.
             '-  (This only checks 1 byte, assuming that there are far less than 255 entries.
             '-- There are only designated, numeric resource IDs going up to about 22.)

        For iOffSet = 1 to iNum2
           s1 = TS.Read(8)
           iReadPt = iReadPt + 8
              If (Asc(s1) = 16) Then  '-- this is version info. entry.
                 Boo = True
                 Exit For
              End If
        Next
     If (Boo = False) Then  '-- have to quit. no version info. entry found.
         TS.Close
         Set TS = Nothing
         GetVersionInfo = 3  'failed to find version info in resource table.
         Exit Function
     End If
      
     A1 = GetArray(s1)  '-- get a byte array for version info entry at top level.
     iOffSet = 0
     iNum3 = 1
   Do

       '-- this should get an offset from first-level entry and use it to go to second-level entry.
         '-- the next loop then gets 3rd-level entry (language). Finally, it gets the offset of
         '-- the actual version info. specs: an 8 byte structure that tells size and address of
         '-- version info. for specified language.
         '-- The way this knows when to stop looping is because an entry will have the high byte
         '-- set in the 4 address bytes if the pointer is to another entry. It will be unset if the
         '-- pointer is to the actual offset data for version info. 2nd level example: 01 00 00 00 70 03 00 80.
         '-- That indicates that the first (and probably only) version info. resource ("1" from first four bytes)
         '-- is indexed in the 3rd level at offset 880 (H370) from beginning of resource section.
         '-- The "80" indicates the high byte is set, which means that H370 is only going to another
         '-- index pointer.

       For iNum1 = 0 to 2  '-- get offset number to next level from 2nd 4 bytes of entry structure. 
          A4(iNum1) = A1(iNum1 + 4)
       Next
            A4(3) = 0
            iNum2 = GetNumFromBytes(A4)       
       If (A1(7) > 127) Then  '-- high bit was set in entry offset value, so it's just a pointer to another pointer.   
             iNum2 = LocRes + iNum2 + 16
             TS.Skip (iNum2 - iReadPt)   '- 1)
             s1 = TS.Read(8)
             iReadPt = iReadPt + ((iNum2 - iReadPt) + 8)
             A1 = GetArray(s1)
       Else  '-- this is the offset of version info offset info.!
              iOffSet = (iNum2 + LocRes)
              Exit Do
       End If
    '-- just to avoid being stuck in this loop if there's an unforseen problem.
          iNum3 = iNum3 + 1
          If (iNum3 > 10) Then Exit Do
   Loop   
       If (iOffSet = 0) Then  '-- have to quit. no final offset found.      
            TS.Close
            Set TS = Nothing
            GetVersionInfo = 3  'failed to find version info in resource table.
            Exit Function
       End If

'-- iOffSet is now the location of version info pointer structure.

   TS.Skip (iOffSet - iReadPt)
   s1 = TS.Read(8)
   iReadPt = iReadPt + ((iOffSet - iReadPt) + 8)
    A1 = GetArray(s1)
       For iNum1 = 0 to 3
         A4(iNum1) = A1(iNum1)
       Next  

     '-- now VIOffset will be the actual address value of the version info. data.
          '-- That value represents the virtual offset of the resource section + the offset
          '-- into the resource section. (Contrary to some sources that say it represents
          '-- the raw data offset.) The virtual offset is the offset when the file is loaded into
          '-- memory. Therefore ReadOffset - the actual file offset to read from to get file version info -
          '-- will be the VIOffset value minus the virtual offset of the resource section (which yields
          '-- the offset into the resource section); then that value will be added to the actual (raw) offset
          '-- of the resource section in the file.

           VIOffset = GetNumFromBytes(A4)  '--offset of version info. given in .rsrc section.
           ReadOffset = ((VIOffset - VLocRes) + LocRes)

      '-- get size of version info. from first four bytes. 
       For iNum1 = 0 to 3
         A4(iNum1) = A1(iNum1 + 4)
       Next     
           SizeRes = GetNumFromBytes(A4)
    TS.Skip (ReadOffset - iReadPt)
    s1 = TS.Read(SizeRes)  '-- read out the entire FileVersionInfo data area.
    TS.Close
  Set TS = Nothing

      sB = GetByteString(s1, True) '-- snip unicode.
   
  Pt1 = InStr(1, sB, sVerString)                                                          
           If (Pt1 > 0) Then        '-- "VS_VER" was found, so process the string and quit.
                ARet = ProcessRes(sB)    
                ARet2 = ARet
                GetVersionInfo = 0  ' ok             
      
           ElseIf (BooAspack = True) Then   '-- if "VS_VER" was not found but there is an "aspack" section then try that.
              ReadOffset = ((VIOffset - VLocAspack) + LocAspack)  '-- calculate a new file version info data offset.          
                Set TS = FSO.OpenTextFile(sFilePath, 1)  '-- The file was closed and is now re-opened here. Keeping the file
                   TS.Skip ReadOffset                            '-- open "just in case" wouldn't have helped because the file pointer
                     s1 = TS.Read(SizeRes)                     '-- for this read may be further back thean the pointer was when the file
                   TS.Close                                  '-- was closed. So rather than try to sort out the read point, the file is just
                Set TS = Nothing                        '-- opened fresh and Skip is used.
                   sB = GetByteString(s1, True)
                   Pt1 = InStr(1, sB, sVerString)
                     If (Pt1 > 0) Then       
                        ARet = ProcessRes(sB)    
                        ARet2 = ARet
                        GetVersionInfo = 0  ' ok
                     Else  
                        GetVersionInfo = 3  'failed to find version info in resource table.
                     End If 
        
           Else  
                 GetVersionInfo = 3  'failed to find version info in resource table.      
 
           End If
End Function 

 '-- Once a section is found that contains "VS_VER", this function picks out the version strings.
Private Function ProcessRes(sDat)
  Dim AInfo(5)
      On Error Resume Next
      AInfo(0) = GetInfo(sDat, "CompanyName")
      AInfo(1) = GetInfo(sDat, "FileDescription")
      AInfo(2) = GetInfo(sDat, "FileVersion")
      AInfo(3)  = GetInfo(sDat, "ProductName")
      AInfo(4) = GetInfo(sDat, "LegalCopyright")
      AInfo(5) = GetInfo(sDat, "OriginalFilename")
    ProcessRes = AInfo 
End Function

'-- small function to handle repetitive parsing of version data string.
Private Function GetInfo(sStr, sVal)
  Dim Pta, Ptb, LenVal, s4
       On Error Resume Next
         GetInfo = ""
    LenVal = Len(sVal) + 1  '-- length of info string: "CompanyName" = 11
     Pta = InStr(1, sStr, sVal)  '-- find string name.
       If (Pta > 0) Then
          Pta = Pta + LenVal
          Ptb = InStr((Pta + 1), sStr, sAst)   '-- look for next *. some properties are Name**value** and some are
            If Ptb > (Pta + 2) Then              '-- Name*value**. So start looking at 3rd character after. If that                     
               s4 = Mid(sStr, Pta, (Ptb - Pta))    '-- character is * then it's Name*** which means there's
               s4 = Replace(s4, sAst, "")                                           '--no value for that specific property.
              If InStr(1, s4, Char1, 0) = 0 Then GetInfo = s4   '-- check for Chr(1) which seems to be found
           End If                             ' between values. If it's in the string that means there is no value for
                                               ' this property and function has actually read next property name.
      End If
End Function
'-------------- simplified version of GetByteString For this Class. ---------------------

  '-- Returns a usable string from a Textstream Read.
  '-- This can be used for reading string data but is not useful for
  '-- byte data because it must change some values in order to
  '-- return usable string. It substitutes all Chr(0) with "*" in order to
  '-- make the string readable in VBS. (Any character could be used but in this case
 '-- "*" is reasonably safe.

Private Function GetByteString(sStr, SnipUnicode)
  Dim sRet, iLen, iA, iLen2, A2()
   On Error Resume Next
      iLen2 = 0
   If (SnipUnicode = False) Then
       ReDim A2(len(sStr) - 1)
        For iLen = 1 to Len(sStr)
            iA = Asc(Mid(sStr, iLen, 1))
              If iA = 0 Then iA = 42  '-- converts 0-byte to *
            A2(iLen - 1) = Chr(iA)
        Next
   Else    
      ReDim A2((len(sStr) \ 2) - 1)
       For iLen = 1 to Len(sStr) step 2
             iA = Asc(Mid(sStr, iLen, 1))
                If iA = 0 Then iA = 42  '-- converts 0-byte to *
              A2(iLen2) = Chr(iA)
              iLen2 = iLen2 + 1
       Next 
   End If    
       GetByteString = Join(A2, "")
End Function
'-------------------------------- Simplified version of GetArray. -----------------------


 '-- returns an array of byte values from a string. This is a way to leave the 0-bytes alone
 '-- while still being able to Read numeric values from the bytes.

Private Function GetArray(sStr)
Dim iA, Len1, Len2, AStr()
  On Error Resume Next
    Len1 = Len(sStr)
    ReDim AStr(Len1 - 1)
     For iA = 1 to Len1
        AStr(iA - 1) = Asc(Mid(sStr, iA, 1))
     Next     
         GetArray = AStr   
End Function
'-------------------- return a number from 2 or 4 bytes. ---------------
Private Function GetNumFromBytes(ABytes)
   Dim Num1
    Err.Clear
        On Error Resume Next
        GetNumFromBytes = -1
    Num1 = ABytes(0) + (ABytes(1) * 256)
      If (UBound(ABytes) = 3) Then
          Num1 = Num1 + (ABytes(2) * 65536) + (ABytes(3) * 16777216)
      End If
    If (Err.number = 0) Then GetNumFromBytes = Num1
End Function
 
End Class
   

 

posted on 2005-11-21 10:45  Roopeman  阅读(199)  评论(0编辑  收藏  举报