VBA
VBA 및 파일 해시에서 바이너리로 2GB + 파일 읽기
수색…
소개
VBA 내에서 바이너리 파일을 쉽게 읽을 수있는 방법이 있지만 2GB (2,147,483,647 바이트 - 최대 Long 데이터 유형)의 제한이 있습니다. 기술이 발전함에 따라이 2GB 제한이 쉽게 위반됩니다. 운영 체제 설치 DVD 디스크의 ISO 이미지). 마이크로 소프트는 저수준 Windows API를 통해 이것을 극복 할 수있는 방법을 제공하고 있습니다.
또한 Microsoft의 fciv.exe
와 같은 외부 프로그램없이 파일 해시를 계산하는 방법을 설명하는 부분을 읽으십시오.
비고
MICROSOFT 클래스에 대한 메서드
메서드 이름 | 기술 |
---|---|
IsOpen | 파일이 열려 있는지 여부를 나타내는 부울을 반환합니다. |
OpenFile (문자열로 sFileNam ) | sFileName 인수로 지정된 파일을 엽니 다. |
CloseFile | 현재 열려있는 파일을 닫습니다. |
ReadBytes ( ByteCount As Long) | ByteCount 바이트를 읽고 Variant 바이트 배열로 반환하고 포인터를 이동합니다. |
WriteBytes (Byte로 DataBytes () ) | 바이트 배열의 내용을 파일의 현재 위치에 씁니다. |
플러시 | Windows가 쓰기 캐시를 플러시하도록합니다. |
SeekAbsolute ( LongPos As Long, LongPos Long) | 파일 포인터를 파일의 처음부터 지정된 위치로 이동합니다. VBA는 DWORDS를 부호있는 값으로 처리하지만 API는 부호없는 값으로 처리합니다. 상위 인수가 0이 아닌 값을 4GB를 초과하도록합니다. 낮은 순서 DWORD는 2GB와 4GB 사이의 값이 음수입니다. |
SeekRelative (오랫동안 오프셋 ) | 파일 포인터를 현재 위치에서 +/- 2GB까지 위로 이동합니다. 이 방법을 다시 작성하여 64 비트 부호있는 오프셋을 두 개의 32 비트 값으로 변환하여 2GB보다 큰 오프셋을 허용 할 수 있습니다. |
MICROSOFT 클래스의 속성
재산 | 기술 |
---|---|
FileHandle | 현재 열려있는 파일의 파일 핸들입니다. VBA 파일 핸들과 호환되지 않습니다. |
파일 이름 | 현재 열려있는 파일의 이름입니다. |
자동 플래시 | WriteBytes가 자동으로 Flush 메서드를 호출할지 여부를 설정하거나 지정합니다. |
NORMAL MODULE
기능 | 노트 |
---|---|
GetFileHash (sFile으로 문자열, 더블로 uBlockSize 문자열로 sHashType) | 해시 할 전체 경로, 단순히 사용할 블록 수 (바이트 수) 및 사용할 해시 유형 ( HashTypeMD5 , HashTypeSHA1 , HashTypeSHA256 , HashTypeSHA384 , HashTypeSHA512) 중 하나를 사용하면 됩니다 . 이것은 가능한 한 포괄적으로 설계되었습니다. |
그에 따라 uFileSize As Double을 주석 해제 / 주석 처리해야합니다. 나는 MD5와 SHA1을 테스트했다.
이것은 Class 모듈에 있어야하며 나중에 예제는 "Random"
' How To Seek Past VBA's 2GB File Limit
' Source: https://support.microsoft.com/en-us/kb/189981 (Archived)
' This must be in a Class Module
Option Explicit
Public Enum W32F_Errors
W32F_UNKNOWN_ERROR = 45600
W32F_FILE_ALREADY_OPEN
W32F_PROBLEM_OPENING_FILE
W32F_FILE_ALREADY_CLOSED
W32F_Problem_seeking
End Enum
Private Const W32F_SOURCE = "Win32File Object"
Private Const GENERIC_WRITE = &H40000000
Private Const GENERIC_READ = &H80000000
Private Const FILE_ATTRIBUTE_NORMAL = &H80
Private Const CREATE_ALWAYS = 2
Private Const OPEN_ALWAYS = 4
Private Const INVALID_HANDLE_VALUE = -1
Private Const FILE_BEGIN = 0, FILE_CURRENT = 1, FILE_END = 2
Private Const FORMAT_MESSAGE_FROM_SYSTEM = &H1000
Private Declare Function FormatMessage Lib "kernel32" Alias "FormatMessageA" ( _
ByVal dwFlags As Long, _
lpSource As Long, _
ByVal dwMessageId As Long, _
ByVal dwLanguageId As Long, _
ByVal lpBuffer As String, _
ByVal nSize As Long, _
Arguments As Any) As Long
Private Declare Function ReadFile Lib "kernel32" ( _
ByVal hFile As Long, _
lpBuffer As Any, _
ByVal nNumberOfBytesToRead As Long, _
lpNumberOfBytesRead As Long, _
ByVal lpOverlapped As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function WriteFile Lib "kernel32" ( _
ByVal hFile As Long, _
lpBuffer As Any, _
ByVal nNumberOfBytesToWrite As Long, _
lpNumberOfBytesWritten As Long, _
ByVal lpOverlapped As Long) As Long
Private Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" ( _
ByVal lpFileName As String, _
ByVal dwDesiredAccess As Long, _
ByVal dwShareMode As Long, _
ByVal lpSecurityAttributes As Long, _
ByVal dwCreationDisposition As Long, _
ByVal dwFlagsAndAttributes As Long, _
ByVal hTemplateFile As Long) As Long
Private Declare Function SetFilePointer Lib "kernel32" ( _
ByVal hFile As Long, _
ByVal lDistanceToMove As Long, _
lpDistanceToMoveHigh As Long, _
ByVal dwMoveMethod As Long) As Long
Private Declare Function FlushFileBuffers Lib "kernel32" (ByVal hFile As Long) As Long
Private hFile As Long, sFName As String, fAutoFlush As Boolean
Public Property Get FileHandle() As Long
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
FileHandle = hFile
End Property
Public Property Get FileName() As String
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
FileName = sFName
End Property
Public Property Get IsOpen() As Boolean
IsOpen = hFile <> INVALID_HANDLE_VALUE
End Property
Public Property Get AutoFlush() As Boolean
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
AutoFlush = fAutoFlush
End Property
Public Property Let AutoFlush(ByVal NewVal As Boolean)
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
fAutoFlush = NewVal
End Property
Public Sub OpenFile(ByVal sFileName As String)
If hFile <> INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_OPEN, sFName
End If
hFile = CreateFile(sFileName, GENERIC_WRITE Or GENERIC_READ, 0, 0, OPEN_ALWAYS, FILE_ATTRIBUTE_NORMAL, 0)
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_PROBLEM_OPENING_FILE, sFileName
End If
sFName = sFileName
End Sub
Public Sub CloseFile()
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
CloseHandle hFile
sFName = ""
fAutoFlush = False
hFile = INVALID_HANDLE_VALUE
End Sub
Public Function ReadBytes(ByVal ByteCount As Long) As Variant
Dim BytesRead As Long, Bytes() As Byte
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
ReDim Bytes(0 To ByteCount - 1) As Byte
ReadFile hFile, Bytes(0), ByteCount, BytesRead, 0
ReadBytes = Bytes
End Function
Public Sub WriteBytes(DataBytes() As Byte)
Dim fSuccess As Long, BytesToWrite As Long, BytesWritten As Long
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
BytesToWrite = UBound(DataBytes) - LBound(DataBytes) + 1
fSuccess = WriteFile(hFile, DataBytes(LBound(DataBytes)), BytesToWrite, BytesWritten, 0)
If fAutoFlush Then Flush
End Sub
Public Sub Flush()
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
FlushFileBuffers hFile
End Sub
Public Sub SeekAbsolute(ByVal HighPos As Long, ByVal LowPos As Long)
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
LowPos = SetFilePointer(hFile, LowPos, HighPos, FILE_BEGIN)
End Sub
Public Sub SeekRelative(ByVal Offset As Long)
Dim TempLow As Long, TempErr As Long
If hFile = INVALID_HANDLE_VALUE Then
RaiseError W32F_FILE_ALREADY_CLOSED
End If
TempLow = SetFilePointer(hFile, Offset, ByVal 0&, FILE_CURRENT)
If TempLow = -1 Then
TempErr = Err.LastDllError
If TempErr Then
RaiseError W32F_Problem_seeking, "Error " & TempErr & "." & vbCrLf & CStr(TempErr)
End If
End If
End Sub
Private Sub Class_Initialize()
hFile = INVALID_HANDLE_VALUE
End Sub
Private Sub Class_Terminate()
If hFile <> INVALID_HANDLE_VALUE Then CloseHandle hFile
End Sub
Private Sub RaiseError(ByVal ErrorCode As W32F_Errors, Optional sExtra)
Dim Win32Err As Long, Win32Text As String
Win32Err = Err.LastDllError
If Win32Err Then
Win32Text = vbCrLf & "Error " & Win32Err & vbCrLf & _
DecodeAPIErrors(Win32Err)
End If
Select Case ErrorCode
Case W32F_FILE_ALREADY_OPEN
Err.Raise W32F_FILE_ALREADY_OPEN, W32F_SOURCE, "The file '" & sExtra & "' is already open." & Win32Text
Case W32F_PROBLEM_OPENING_FILE
Err.Raise W32F_PROBLEM_OPENING_FILE, W32F_SOURCE, "Error opening '" & sExtra & "'." & Win32Text
Case W32F_FILE_ALREADY_CLOSED
Err.Raise W32F_FILE_ALREADY_CLOSED, W32F_SOURCE, "There is no open file."
Case W32F_Problem_seeking
Err.Raise W32F_Problem_seeking, W32F_SOURCE, "Seek Error." & vbCrLf & sExtra
Case Else
Err.Raise W32F_UNKNOWN_ERROR, W32F_SOURCE, "Unknown error." & Win32Text
End Select
End Sub
Private Function DecodeAPIErrors(ByVal ErrorCode As Long) As String
Dim sMessage As String, MessageLength As Long
sMessage = Space$(256)
MessageLength = FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM, 0&, ErrorCode, 0&, sMessage, 256&, 0&)
If MessageLength > 0 Then
DecodeAPIErrors = Left(sMessage, MessageLength)
Else
DecodeAPIErrors = "Unknown Error."
End If
End Function
표준 모듈에서 파일 해시 계산을위한 코드
Private Const HashTypeMD5 As String = "MD5" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.md5cryptoserviceprovider(v=vs.110).aspx
Private Const HashTypeSHA1 As String = "SHA1" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.sha1cryptoserviceprovider(v=vs.110).aspx
Private Const HashTypeSHA256 As String = "SHA256" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.sha256cryptoserviceprovider(v=vs.110).aspx
Private Const HashTypeSHA384 As String = "SHA384" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.sha384cryptoserviceprovider(v=vs.110).aspx
Private Const HashTypeSHA512 As String = "SHA512" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.sha512cryptoserviceprovider(v=vs.110).aspx
Private uFileSize As Double ' Comment out if not testing performance by FileHashes()
Sub FileHashes()
Dim tStart As Date, tFinish As Date, sHash As String, aTestFiles As Variant, oTestFile As Variant, aBlockSizes As Variant, oBlockSize As Variant
Dim BLOCKSIZE As Double
' This performs performance testing on different file sizes and block sizes
aBlockSizes = Array("2^12-1", "2^13-1", "2^14-1", "2^15-1", "2^16-1", "2^17-1", "2^18-1", "2^19-1", "2^20-1", "2^21-1", "2^22-1", "2^23-1", "2^24-1", "2^25-1", "2^26-1")
aTestFiles = Array("C:\ISO\clonezilla-live-2.2.2-37-amd64.iso", "C:\ISO\HPIP201.2014_0902.29.iso", "C:\ISO\SW_DVD5_Windows_Vista_Business_W32_32BIT_English.ISO", "C:\ISO\Win10_1607_English_x64.iso", "C:\ISO\SW_DVD9_Windows_Svr_Std_and_DataCtr_2012_R2_64Bit_English.ISO")
Debug.Print "Test files: " & Join(aTestFiles, " | ")
Debug.Print "BlockSizes: " & Join(aBlockSizes, " | ")
For Each oTestFile In aTestFiles
Debug.Print oTestFile
For Each oBlockSize In aBlockSizes
BLOCKSIZE = Evaluate(oBlockSize)
tStart = Now
sHash = GetFileHash(CStr(oTestFile), BLOCKSIZE, HashTypeMD5)
tFinish = Now
Debug.Print sHash, uFileSize, Format(tFinish - tStart, "hh:mm:ss"), oBlockSize & " (" & BLOCKSIZE & ")"
Next
Next
End Sub
Private Function GetFileHash(ByVal sFile As String, ByVal uBlockSize As Double, ByVal sHashType As String) As String
Dim oFSO As Object ' "Scripting.FileSystemObject"
Dim oCSP As Object ' One of the "CryptoServiceProvider"
Dim oRnd As Random ' "Random" Class by Microsoft, must be in the same file
Dim uBytesRead As Double, uBytesToRead As Double, bDone As Boolean
Dim aBlock() As Byte, aBytes As Variant ' Arrays to store bytes
Dim aHash() As Byte, sHash As String, i As Long
'Dim uFileSize As Double ' Un-Comment if GetFileHash() is to be used individually
Set oRnd = New Random ' Class by Microsoft: Random
Set oFSO = CreateObject("Scripting.FileSystemObject")
Set oCSP = CreateObject("System.Security.Cryptography." & sHashType & "CryptoServiceProvider")
If oFSO Is Nothing Or oRnd Is Nothing Or oCSP Is Nothing Then
MsgBox "One or more required objects cannot be created"
GoTo CleanUp
End If
uFileSize = oFSO.GetFile(sFile).Size ' FILELEN() has 2GB max!
uBytesRead = 0
bDone = False
sHash = String(oCSP.HashSize / 4, "0") ' Each hexadecimal has 4 bits
Application.ScreenUpdating = False
' Process the file in chunks of uBlockSize or less
If uFileSize = 0 Then
ReDim aBlock(0)
oCSP.TransformFinalBlock aBlock, 0, 0
bDone = True
Else
With oRnd
.OpenFile sFile
Do
If uBytesRead + uBlockSize < uFileSize Then
uBytesToRead = uBlockSize
Else
uBytesToRead = uFileSize - uBytesRead
bDone = True
End If
' Read in some bytes
aBytes = .ReadBytes(uBytesToRead)
aBlock = aBytes
If bDone Then
oCSP.TransformFinalBlock aBlock, 0, uBytesToRead
uBytesRead = uBytesRead + uBytesToRead
Else
uBytesRead = uBytesRead + oCSP.TransformBlock(aBlock, 0, uBytesToRead, aBlock, 0)
End If
DoEvents
Loop Until bDone
.CloseFile
End With
End If
If bDone Then
' convert Hash byte array to an hexadecimal string
aHash = oCSP.hash
For i = 0 To UBound(aHash)
Mid$(sHash, i * 2 + (aHash(i) > 15) + 2) = Hex(aHash(i))
Next
End If
Application.ScreenUpdating = True
' Clean up
oCSP.Clear
CleanUp:
Set oFSO = Nothing
Set oRnd = Nothing
Set oCSP = Nothing
GetFileHash = sHash
End Function
결과는 꽤 흥미 롭습니다. 테스트 파일에
BLOCKSIZE = 131071
(2 ^ 17-1) 이 Windows 7 x64에서 32 비트 Office 2010으로 가장 좋은 성능을 제공하고 그 다음으로 가장 좋은 것은 2 ^ 16-1 (65535) 입니다. 참고2^27-1
메모리가 부족 합니다.
파일 크기 (바이트) | 파일 이름 |
---|---|
146,800,640 | clonezilla-live-2.2.2-37-amd64.iso |
798,210,048 | HPIP201.2014_0902.29.iso |
2,073,016,320 | SW_DVD5_Windows_Vista_Business_W32_32BIT_English.ISO |
4,380,387,328 | Win10_1607_English_x64.iso |
5,400,115,200 | SW_DVD9_Windows_Svr_Std_and_DataCtr_2012_R2_64Bit_English.ISO |
루트 폴더에서 모든 파일 해시 계산
위 코드의 또 다른 변형은 모든 하위 폴더를 포함하여 루트 폴더에서 모든 파일의 해시 코드를 가져올 때 더 많은 성능을 제공합니다.
워크 시트의 예 :
암호
Option Explicit
Private Const HashTypeMD5 As String = "MD5" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.md5cryptoserviceprovider(v=vs.110).aspx
Private Const HashTypeSHA1 As String = "SHA1" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.sha1cryptoserviceprovider(v=vs.110).aspx
Private Const HashTypeSHA256 As String = "SHA256" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.sha256cryptoserviceprovider(v=vs.110).aspx
Private Const HashTypeSHA384 As String = "SHA384" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.sha384cryptoserviceprovider(v=vs.110).aspx
Private Const HashTypeSHA512 As String = "SHA512" ' https://msdn.microsoft.com/en-us/library/system.security.cryptography.sha512cryptoserviceprovider(v=vs.110).aspx
Private Const BLOCKSIZE As Double = 131071 ' 2^17-1
Private oFSO As Object
Private oCSP As Object
Private oRnd As Random ' Requires the Class from Microsoft https://support.microsoft.com/en-us/kb/189981
Private sHashType As String
Private sRootFDR As String
Private oRng As Range
Private uFileCount As Double
Sub AllFileHashes() ' Active-X button calls this
Dim oWS As Worksheet
' | A: FileHash | B: FileSize | C: FileName | D: FilaName and Path | E: File Last Modification Time | F: Time required to calculate has code (seconds)
With ThisWorkbook
' Clear All old entries on all worksheets
For Each oWS In .Worksheets
Set oRng = Intersect(oWS.UsedRange, oWS.UsedRange.Offset(2))
If Not oRng Is Nothing Then oRng.ClearContents
Next
With .Worksheets(1)
sHashType = Trim(.Range("A1").Value) ' Range(A1)
sRootFDR = Trim(.Range("C1").Value) ' Range(C1) Column B for file size
If Len(sHashType) = 0 Or Len(sRootFDR) = 0 Then Exit Sub
Set oRng = .Range("A3") ' First entry on First Page
End With
End With
uFileCount = 0
If oRnd Is Nothing Then Set oRnd = New Random ' Class by Microsoft: Random
If oFSO Is Nothing Then Set oFSO = CreateObject("Scripting.FileSystemObject") ' Just to get correct FileSize
If oCSP Is Nothing Then Set oCSP = CreateObject("System.Security.Cryptography." & sHashType & "CryptoServiceProvider")
ProcessFolder oFSO.GetFolder(sRootFDR)
Application.StatusBar = False
Application.ScreenUpdating = True
oCSP.Clear
Set oCSP = Nothing
Set oRng = Nothing
Set oFSO = Nothing
Set oRnd = Nothing
Debug.Print "Total file count: " & uFileCount
End Sub
Private Sub ProcessFolder(ByRef oFDR As Object)
Dim oFile As Object, oSubFDR As Object, sHash As String, dStart As Date, dFinish As Date
Application.ScreenUpdating = False
For Each oFile In oFDR.Files
uFileCount = uFileCount + 1
Application.StatusBar = uFileCount & ": " & Right(oFile.Path, 255 - Len(uFileCount) - 2)
oCSP.Initialize ' Reinitialize the CryptoServiceProvider
dStart = Now
sHash = GetFileHash(oFile, BLOCKSIZE, sHashType)
dFinish = Now
With oRng
.Value = sHash
.Offset(0, 1).Value = oFile.Size ' File Size in bytes
.Offset(0, 2).Value = oFile.Name ' File name with extension
.Offset(0, 3).Value = oFile.Path ' Full File name and Path
.Offset(0, 4).Value = FileDateTime(oFile.Path) ' Last modification timestamp of file
.Offset(0, 5).Value = dFinish - dStart ' Time required to calculate hash code
End With
If oRng.Row = Rows.Count Then
' Max rows reached, start on Next sheet
If oRng.Worksheet.Index + 1 > ThisWorkbook.Worksheets.Count Then
MsgBox "All rows in all worksheets have been used, please create more sheets"
End
End If
Set oRng = ThisWorkbook.Sheets(oRng.Worksheet.Index + 1).Range("A3")
oRng.Worksheet.Activate
Else
' Move to next row otherwise
Set oRng = oRng.Offset(1)
End If
Next
'Application.StatusBar = False
Application.ScreenUpdating = True
oRng.Activate
For Each oSubFDR In oFDR.SubFolders
ProcessFolder oSubFDR
Next
End Sub
Private Function GetFileHash(ByVal sFile As String, ByVal uBlockSize As Double, ByVal sHashType As String) As String
Dim uBytesRead As Double, uBytesToRead As Double, bDone As Boolean
Dim aBlock() As Byte, aBytes As Variant ' Arrays to store bytes
Dim aHash() As Byte, sHash As String, i As Long, oTmp As Variant
Dim uFileSize As Double ' Un-Comment if GetFileHash() is to be used individually
If oRnd Is Nothing Then Set oRnd = New Random ' Class by Microsoft: Random
If oFSO Is Nothing Then Set oFSO = CreateObject("Scripting.FileSystemObject") ' Just to get correct FileSize
If oCSP Is Nothing Then Set oCSP = CreateObject("System.Security.Cryptography." & sHashType & "CryptoServiceProvider")
If oFSO Is Nothing Or oRnd Is Nothing Or oCSP Is Nothing Then
MsgBox "One or more required objects cannot be created"
Exit Function
End If
uFileSize = oFSO.GetFile(sFile).Size ' FILELEN() has 2GB max
uBytesRead = 0
bDone = False
sHash = String(oCSP.HashSize / 4, "0") ' Each hexadecimal is 4 bits
' Process the file in chunks of uBlockSize or less
If uFileSize = 0 Then
ReDim aBlock(0)
oCSP.TransformFinalBlock aBlock, 0, 0
bDone = True
Else
With oRnd
On Error GoTo CannotOpenFile
.OpenFile sFile
Do
If uBytesRead + uBlockSize < uFileSize Then
uBytesToRead = uBlockSize
Else
uBytesToRead = uFileSize - uBytesRead
bDone = True
End If
' Read in some bytes
aBytes = .ReadBytes(uBytesToRead)
aBlock = aBytes
If bDone Then
oCSP.TransformFinalBlock aBlock, 0, uBytesToRead
uBytesRead = uBytesRead + uBytesToRead
Else
uBytesRead = uBytesRead + oCSP.TransformBlock(aBlock, 0, uBytesToRead, aBlock, 0)
End If
DoEvents
Loop Until bDone
.CloseFile
CannotOpenFile:
If Err.Number <> 0 Then ' Change the hash code to the Error description
oTmp = Split(Err.Description, vbCrLf)
sHash = oTmp(1) & ":" & oTmp(2)
End If
End With
End If
If bDone Then
' convert Hash byte array to an hexadecimal string
aHash = oCSP.hash
For i = 0 To UBound(aHash)
Mid$(sHash, i * 2 + (aHash(i) > 15) + 2) = Hex(aHash(i))
Next
End If
GetFileHash = sHash
End Function
Modified text is an extract of the original Stack Overflow Documentation
아래 라이선스 CC BY-SA 3.0
와 제휴하지 않음 Stack Overflow