VB6 - Huge (>2GB) Text and Binary File I/O Classes
I swear I did a search or two first but I hadn't seen this here.
HugeBinaryFile.cls is a VB6 Class that is based on an old MS KB article for VB4.
It works a bit like using Get#/Put# with Byte arrays, and supports absolute seeks to a byte position using a Currency value from 0 to far beyond the usual 2GB limit. It can also do seeks relative to the current file position accepting a signed Long value, and seek to EOF for appending. Its FileLen property returns the open file's length in bytes as a Currency value.
Currency was used for convenience since huge files need a 64-bit position value. Since Currency values have an implied decimal point the class does scaling so that you can use 1 to mean 1 (1.0000) instead of using 0.0001 to mean byte 1.
If you find this imperfect you can always modify the Class to accept and return a pair of unsigned Long values instead. In the end these can get pretty clumsy to work with though.
I did a certain amount of testing, but I won't claim this code is bug-free.
The Class is provided here bundled in a small demo project. To add it to your own projects simply copy the .cls file into your project folder and Add|File... to make it part of your project.
It would be fairly easy to create another Class that wraps this one for doing text I/O.
Look at the posts below for my HugeTextFile class.
Last edited by dilettante; Jun 27th, 2011 at 05:37 PM.
Reason: Added HugeTextFile Class
Here's another example. Somebody wrote this for me a few years ago.
Put it in a module.
Code:
Option Explicit
Const MOVEFILE_REPLACE_EXISTING = &H1
Const FILE_ATTRIBUTE_TEMPORARY = &H100
Const FILE_BEGIN = 0
Const FILE_SHARE_READ = &H1
Const FILE_SHARE_WRITE = &H2
Const CREATE_NEW = 1
Const OPEN_EXISTING = 3
Const OPEN_ALLWAYS = 4
Const GENERIC_READ = &H80000000
Const GENERIC_WRITE = &H40000000
Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length 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 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 Any) 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 Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject 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 GetFileSize Lib "kernel32" (ByVal hFile As Long, lpFileSizeHigh As Long) As Long
Private Declare Function SetEndOfFile Lib "kernel32" (ByVal hFile As Long) As Long
Public File_Num As Long
Public File_Len As Currency
Public Sub API_OpenFile(ByVal FileName As String, ByRef FileNumber As Long, ByRef FileSize As Currency)
Dim FileH As Long
Dim Ret As Long
On Error Resume Next
FileH = CreateFile(FileName, GENERIC_READ Or GENERIC_WRITE, FILE_SHARE_READ Or FILE_SHARE_WRITE, 0&, OPEN_ALLWAYS, 0, 0)
If Err.Number > 0 Then
Err.Clear
FileNumber = -1
Else
FileNumber = FileH
Ret = SetFilePointer(FileH, 0, 0, FILE_BEGIN)
API_FileSize FileH, FileSize
End If
On Error GoTo 0
End Sub
Public Sub API_FileSize(ByVal FileNumber As Long, ByRef FileSize As Currency)
Dim FileSizeL As Long
Dim FileSizeH As Long
FileSizeH = 0
FileSizeL = GetFileSize(FileNumber, FileSizeH)
Long2Size FileSizeL, FileSizeH, FileSize
End Sub
Public Sub API_ReadFile(ByVal FileNumber As Long, ByVal Position As Currency, ByRef BlockSize As Long, ByRef Data() As Byte)
Dim PosL As Long
Dim PosH As Long
Dim SizeRead As Long
Dim Ret As Long
Size2Long Position, PosL, PosH
Ret = SetFilePointer(FileNumber, PosL, PosH, FILE_BEGIN)
Ret = ReadFile(FileNumber, Data(0), BlockSize, SizeRead, 0&)
BlockSize = SizeRead
End Sub
Public Sub API_CloseFile(ByVal FileNumber As Long)
Dim Ret As Long
Ret = CloseHandle(FileNumber)
End Sub
Public Sub API_WriteFile(ByVal FileNumber As Long, ByVal Position As Currency, ByRef BlockSize As Long, ByRef Data() As Byte)
Dim PosL As Long
Dim PosH As Long
Dim SizeWrit As Long
Dim Ret As Long
Size2Long Position - 1, PosL, PosH
Ret = SetFilePointer(FileNumber, PosL, PosH, FILE_BEGIN)
Ret = WriteFile(FileNumber, Data(0), BlockSize, SizeWrit, 0&)
BlockSize = SizeWrit
End Sub
Private Sub Size2Long(ByVal FileSize As Currency, ByRef LongLow As Long, ByRef LongHigh As Long)
'&HFFFFFFFF unsigned = 4294967295
Dim Cutoff As Currency
Cutoff = 2147483647
Cutoff = Cutoff + 2147483647
Cutoff = Cutoff + 1 ' now we hold the value of 4294967295 and not -1
LongHigh = 0
Do Until FileSize < Cutoff
LongHigh = LongHigh + 1
FileSize = FileSize - Cutoff
Loop
If FileSize > 2147483647 Then
LongLow = -CLng(Cutoff - (FileSize - 1))
Else
LongLow = CLng(FileSize)
End If
End Sub
Private Sub Long2Size(ByVal LongLow As Long, ByVal LongHigh As Long, ByRef FileSize As Currency)
'&HFFFFFFFF unsigned = 4294967295
Dim Cutoff As Currency
Cutoff = 2147483647
Cutoff = Cutoff + 2147483647
Cutoff = Cutoff + 1 ' now we hold the value of 4294967295 and not -1
FileSize = Cutoff * LongHigh
If LongLow < 0 Then
FileSize = FileSize + (Cutoff + (LongLow + 1))
Else
FileSize = FileSize + LongLow
End If
End Sub
Here's another example. Somebody wrote this for me a few years ago.
Put it in a module.
Code:
Option Explicit
Const MOVEFILE_REPLACE_EXISTING = &H1
Const FILE_ATTRIBUTE_TEMPORARY = &H100
Const FILE_BEGIN = 0
Const FILE_SHARE_READ = &H1
Const FILE_SHARE_WRITE = &H2
Const CREATE_NEW = 1
Const OPEN_EXISTING = 3
Const OPEN_ALLWAYS = 4
Const GENERIC_READ = &H80000000
Const GENERIC_WRITE = &H40000000
Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length 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 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 Any) 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 Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject 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 GetFileSize Lib "kernel32" (ByVal hFile As Long, lpFileSizeHigh As Long) As Long
Private Declare Function SetEndOfFile Lib "kernel32" (ByVal hFile As Long) As Long
Public File_Num As Long
Public File_Len As Currency
Public Sub API_OpenFile(ByVal FileName As String, ByRef FileNumber As Long, ByRef FileSize As Currency)
Dim FileH As Long
Dim Ret As Long
On Error Resume Next
FileH = CreateFile(FileName, GENERIC_READ Or GENERIC_WRITE, FILE_SHARE_READ Or FILE_SHARE_WRITE, 0&, OPEN_ALLWAYS, 0, 0)
If Err.Number > 0 Then
Err.Clear
FileNumber = -1
Else
FileNumber = FileH
Ret = SetFilePointer(FileH, 0, 0, FILE_BEGIN)
API_FileSize FileH, FileSize
End If
On Error GoTo 0
End Sub
Public Sub API_FileSize(ByVal FileNumber As Long, ByRef FileSize As Currency)
Dim FileSizeL As Long
Dim FileSizeH As Long
FileSizeH = 0
FileSizeL = GetFileSize(FileNumber, FileSizeH)
Long2Size FileSizeL, FileSizeH, FileSize
End Sub
Public Sub API_ReadFile(ByVal FileNumber As Long, ByVal Position As Currency, ByRef BlockSize As Long, ByRef Data() As Byte)
Dim PosL As Long
Dim PosH As Long
Dim SizeRead As Long
Dim Ret As Long
Size2Long Position, PosL, PosH
Ret = SetFilePointer(FileNumber, PosL, PosH, FILE_BEGIN)
Ret = ReadFile(FileNumber, Data(0), BlockSize, SizeRead, 0&)
BlockSize = SizeRead
End Sub
Public Sub API_CloseFile(ByVal FileNumber As Long)
Dim Ret As Long
Ret = CloseHandle(FileNumber)
End Sub
Public Sub API_WriteFile(ByVal FileNumber As Long, ByVal Position As Currency, ByRef BlockSize As Long, ByRef Data() As Byte)
Dim PosL As Long
Dim PosH As Long
Dim SizeWrit As Long
Dim Ret As Long
Size2Long Position - 1, PosL, PosH
Ret = SetFilePointer(FileNumber, PosL, PosH, FILE_BEGIN)
Ret = WriteFile(FileNumber, Data(0), BlockSize, SizeWrit, 0&)
BlockSize = SizeWrit
End Sub
Private Sub Size2Long(ByVal FileSize As Currency, ByRef LongLow As Long, ByRef LongHigh As Long)
'&HFFFFFFFF unsigned = 4294967295
Dim Cutoff As Currency
Cutoff = 2147483647
Cutoff = Cutoff + 2147483647
Cutoff = Cutoff + 1 ' now we hold the value of 4294967295 and not -1
LongHigh = 0
Do Until FileSize < Cutoff
LongHigh = LongHigh + 1
FileSize = FileSize - Cutoff
Loop
If FileSize > 2147483647 Then
LongLow = -CLng(Cutoff - (FileSize - 1))
Else
LongLow = CLng(FileSize)
End If
End Sub
Private Sub Long2Size(ByVal LongLow As Long, ByVal LongHigh As Long, ByRef FileSize As Currency)
'&HFFFFFFFF unsigned = 4294967295
Dim Cutoff As Currency
Cutoff = 2147483647
Cutoff = Cutoff + 2147483647
Cutoff = Cutoff + 1 ' now we hold the value of 4294967295 and not -1
FileSize = Cutoff * LongHigh
If LongLow < 0 Then
FileSize = FileSize + (Cutoff + (LongLow + 1))
Else
FileSize = FileSize + LongLow
End If
End Sub
I remember that. I think I did, but I actually got it from another site. I needed it for large files > 2 and 4GB for my Winsock downloader.
A couple of queries from a beginner re setfilepointer ...
1. is the pointer 0-based or 1-based for the 1st byte of a file ?
ie by way of example, what value do I give setfilepointer to then read the 2nd byte of a file ... 1 or 2 ?
2. But... In the 2nd set of code above from DigiRev, for a READ it does setfilepointer to (Position) yet for a WRITE it does setfilepointer to (Position - 1) first ... which seems to me to overwrite starting on the top of the previous byte... that isn't how GET/PUT work, is it ?
eg if position 2 were specified, it would do a setfilepointer to position 1 and then start writing on the top of position 1 onward ... is that a bug ?
1) 0-based. First byte = position 0, second byte = position 1
2) It should not be (Position - 1). I used that code for an application where I always had to write to (Position - 1) and to make it easier for myself I added (- 1) to the API_WriteFile sub. You need to remove that.
Last edited by Chris001; May 9th, 2009 at 02:04 PM.
A quick note for anyone that might come through here and want to use the code posted above. The API_FileSize method incorrectly reports 0-byte file sizes as being 4294967295 bytes in length. To fix this, modify the last line in the method from
Code:
Long2Size FileSizeL, FileSizeH, FileSize
to this
Code:
If FileSizeL = -1 Then
FileSize = 0
Else
Long2Size FileSizeL, FileSizeH, FileSize
End If
I also have a HugeTextFile class you can use for processing text files.
It works fine for both "normal" sized files and "huge" ones. It also processes both ANSI and Unicode files (Windows "Unicode" i.e. UTF-16LE), with either CRLF or LF line delimiters.. There are ReadLine, WriteLine, and SkipLines methods, a Rewind, etc. as well as an EOF property, LineCount property reflecting current "progress", and so forth.
Even for moderately-sized files the performance will probably beat the memory-hungry "split-de-split" technique people often clumsily use to read a file in one gulp and create an array of text lines. If the files are bigger you may want to specify larger buffers when you call the OpenFile method.
The demo project HugeTextDemo uses Timers to keep the UI responsive but feel free to use straight-line looping through entire files in your programs. That is an entirely separate matter from the HugeTextFile class itself.
The attachment also contains a secondary project MakeFile you should run first to create "old.txt" that HugeTextFile needs.
Thanks, but I can't answer questions about the code the thread hijackers posted above. Feel free to PM them directly since they never established their own threads.
If you have questions about the code code samples I attached here ask in the thread. PMs are sort of clunky for that.
Re: VB6 - Huge (>2GB) Text and Binary File I/O Classes
Originally Posted by dilettante
I swear I did a search or two first but I hadn't seen this here.
HugeBinaryFile.cls is a VB6 Class that is based on an old MS KB article for VB4.
It works a bit like using Get#/Put# with Byte arrays, and supports absolute seeks to a byte position using a Currency value from 0 to far beyond the usual 2GB limit. It can also do seeks relative to the current file position accepting a signed Long value, and seek to EOF for appending. Its FileLen property returns the open file's length in bytes as a Currency value.
Currency was used for convenience since huge files need a 64-bit position value. Since Currency values have an implied decimal point the class does scaling so that you can use 1 to mean 1 (1.0000) instead of using 0.0001 to mean byte 1.
If you find this imperfect you can always modify the Class to accept and return a pair of unsigned Long values instead. In the end these can get pretty clumsy to work with though.
I did a certain amount of testing, but I won't claim this code is bug-free.
The Class is provided here bundled in a small demo project. To add it to your own projects simply copy the .cls file into your project folder and Add|File... to make it part of your project.
It would be fairly easy to create another Class that wraps this one for doing text I/O.
Look at the posts below for my HugeTextFile class.
' a small bug in Boundary
'For Unicode support,you should use W-Type API
Code:
Private Declare Function CreateFileW Lib "kernel32" (ByVal lpFileName As Long, 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 lstrlenW Lib "kernel32" (ByVal psString As Any) As Long
Private Declare Function LCMapStringW Lib "kernel32" (ByVal Locale As Long, ByVal dwMapFlags As Long, ByVal lpSrcStr As Long, ByVal cchSrc As Long, ByVal lpDestStr As Long, ByVal cchDest As Long) As Long
Private Declare Function CreateFile Lib "KERNEL32.dll" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, ByRef lpSecurityAttributes As Long, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Private Declare Function LCMapString Lib "KERNEL32.dll" Alias "LCMapStringA" (ByVal Locale As Long, ByVal dwMapFlags As Long, ByVal lpSrcStr As String, ByVal cchSrc As Long, ByVal lpDestStr As String, ByVal cchDest As Long) As Long
Private Declare Function lstrlen Lib "KERNEL32.dll" Alias "lstrlenA" (ByVal lpString As String) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) 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 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 GetFileSize Lib "kernel32" (ByVal hFile As Long, lpFileSizeHigh 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 Const INVALID_HANDLE_VALUE = -1
Private Const GENERIC_READ = &H80000000
Private Const GENERIC_WRITE = &H40000000
Private Const FILE_SHARE_READ = &H1
Private Const FILE_SHARE_WRITE = &H2
Private Const CREATE_NEW = 1
Private Const CREATE_ALWAYS = 2
Private Const OPEN_EXISTING = 3
Private Const OPEN_ALWAYS = 4
Private Const TRUNCATE_EXISTING = 5
Private Const FILE_ATTRIBUTE_NORMAL = &H80
Private Const FILE_BEGIN = 0
Private Const FILE_CURRENT = 1
Private Const FILE_END = 2
Public Function ReadBytes(ByRef Buffer() As Byte) As Long
RaiseErrorIfClosed
If ReadFile(hFile, _
Buffer(LBound(Buffer)), _
UBound(Buffer) - LBound(Buffer) + 1, _
ReadBytes, _
0) Then
If ReadBytes = 0 Then
fEOF = True
ElseIf ReadBytes < UBound(Buffer) - LBound(Buffer) + 1 Then
ReDim Preserve Buffer(ReadBytes - 1)
End If
Else
RaiseError HBF_READ_FAILURE
End If
End Function
Since this Class does not deal with text at all, there is no need for the W entrypoints.
However if you want to use Unicode file names then you have a valid point, and CreateFile needs to be CreateFileW with a few other minor changes to its signature and call.
I have no idea why you are using LCMapString though, except perhaps as a fancy version of StrConv?
The nice thing about having the source is that you can hack away and make any customization you want though. If there really is a bug perhaps you can explain it in more detail?
Since this Class does not deal with text at all, there is no need for the W entrypoints.
However if you want to use Unicode file names then you have a valid point, and CreateFile needs to be CreateFileW with a few other minor changes to its signature and call.
Use CreateFileW in your OpenFile function.
I have no idea why you are using LCMapString though, except perhaps as a fancy version of StrConv?
I just copy all APIs from my another project which deal with Unicode text file. LCMAPStringW for GB2GBK conversion.
Code:
Public Function GB2GBK(ByVal CSstring As String) As String
Dim lLen As Long
Dim CTString As String
On Error GoTo ToExit
If CSstring = vbNullString Then Exit Function
If m_bisNT Then
lLen = lstrlenW(StrPtr(CSstring))
CTString = Space$(lLen)
LCMapStringW &H804, &H4000000, StrPtr(CSstring), lLen, StrPtr(CTString), lLen * 2
GB2GBK = CTString
Else
lLen = lstrlen(CSstring)
CTString = Space$(lLen)
LCMapString &H804, &H4000000, CSstring, lLen, CTString, lLen
GB2GBK = CTString
End If
Exit Function
ToExit:
GB2GBK = vbNullString
End Function
The nice thing about having the source is that you can hack away and make any customization you want though. If there really is a bug perhaps you can explain it in more detail?
Public Function ReadBytes(ByRef Buffer() As Byte) As Long
RaiseErrorIfClosed
If ReadFile(hFile, _
Buffer(LBound(Buffer)), _ UBound(Buffer) - LBound(Buffer) + 1, _
ReadBytes, _
0) Then
If ReadBytes = 0 Then
fEOF = True ElseIf ReadBytes < UBound(Buffer) - LBound(Buffer) + 1 Then
ReDim Preserve Buffer(ReadBytes - 1)
End If
Else
RaiseError HBF_READ_FAILURE
End If
End Function
Instead of relying on the return value to know how many bytes were read you want to truncate the user's buffer (byte array). I had chosen not to do that intentionally. For example the buffer might not be a dynamic array at all, so your change would crash the program. It also adds a bit of extra cost to the read operation.
There is a reason why this is a function returning the length read.
Even if you did want to do this, you should preserve the user's buffer LBound when redimensioning it. One more reason to just let the caller do this costly extra step if it is desired.
I remember that. I think I did, but I actually got it from another site. I needed it for large files > 2 and 4GB for my Winsock downloader.
Lol .. It's quite strange to see this thread... Considering that I'm the Original Author of the posted Code.. (API_OpenFile, API_FileSize, API_ReadFile, API_WriteFile).. My original article 'Getting Past the 2 Gb File Limit' giving full details about how the modules works and why it's needed was done in Jan of 2007 (Long before this thread started).
But it's so nice to see my work has gotten around, and i figured i'd just let everyone know the original source...
Lol .. It's quite strange to see this thread... Considering that I'm the Original Author of the posted Code.. (API_OpenFile, API_FileSize, API_ReadFile, API_WriteFile).. My original article 'Getting Past the 2 Gb File Limit' giving full details about how the modules works and why it's needed was done in Jan of 2007 (Long before this thread started).
But it's so nice to see my work has gotten around, and i figured i'd just let everyone know the original source...
You must be talking about the thread hijackers, because my code was 100% original work. As much as anything so simple can be original anyway. Earlier versions of the code this thread is about date back a lot further than 2007.
You must be talking about the thread hijackers, because my code was 100% original work. As much as anything so simple can be original anyway. Earlier versions of the code this thread is about date back a lot further than 2007.
No .. not your Class.. If you noted my quote... The code posted by Chris001 and referenced by DigiRev was taken directly from the article that I wrote (which is long before this thread started...)
Also DigiRev say's 'but I actually got it from another site', so i figured i'll simply put up a link to the original source of his.. (also considering, Codeguru is a sister site to VBForums, he could have found the original source very easily...)
Hi, I just tried the first solution because i need to read random a huge file, but when I arrive beside the 2147483647 bytes I've got an overflow calling the readfile api: it's because the readfile param are declared as long.
Here my code : someone can help me?
Many thanks in advance!
Code:
Public Sub ReadFile_2GB(xfilename As String, xlenFile As Double, xlenRec As Double, xStartRecord As Double, xRec As String, xFineFile As Boolean)
' ATTENTION record 1 is with DStartRecord = 0, the second has DStartRecord = 1...
' take care how you call this function!!!
Dim Temp As Variant
Dim i As Long
Dim Ilen As Double
'----xlenRec = record len + CR/FL
If bFirstTime Then
F.SeekAbsolute 0, 0 'STARTING FROM POSITION 0 OF THE FILE (Seeks 2 bytes (0*2^32 + 2) = 1 character.
'----F.SeekRelative -2 ' Seeks forward 1 character (inizio file)
bFirstTime = False
Else
If xlenRec * DStartRecord < xlenFile Then
'test!!!!
If xlenRec * DStartRecord <= 2147483647 Then
F.SeekAbsolute 0, xlenRec * DStartRecord ' overflow with value = 2.147.483.647! because param is a LONG!!!!)
Else
'F.SeekRelative (xlenRec * DStartRecord) ' overflow with value = 2.147.483.647! because param is a LONG!!!!)
F.SeekAbsolute 1, (xlenRec * DStartRecord) - 2147483647 ' overflow with value = 2.147.483.647! because param is a LONG!!!!)
End If
Else
bEndFile = True
End If
End If
Temp = F.ReadBytes(xlenRec)
Ilen = Len(Temp)
xRec = ""
'from unicode to ASCII
For i = LBound(Temp) To UBound(Temp)
xRec = xRec & ChrW(Temp(i))
Next
xStartRecord = xStartRecord + 1
End Sub
There is an issue that someone may be able to answer. I can open a log file that is being written to by another process with any other means except for this one. Is there a way to open a file in use, using this class?
Are you using the text file I/O class? If so, have you tried opening the file passing HTF_OPEN_EXISTING and HTF_SHARE_READ values?
If you are using the binary I/O class you should be able to accomplish the same thing by dealing with the sharing flags and such when opening the file. The other class should work better for you though since most log files are CRLF-delimited text streams on Windows.
Yes I am using the txt file class and yes crashes the application/vb.
looks similar to this.
Dim strLine as string
Set htfIn = New HugeTextFile
htfIn.OpenFile "C:\Windows\System32\LogFiles\Firewall\pfirewall.log", HTF_ACCESS_READ, HTF_OPEN_EXISTING, HTF_SHARE_READ , BufferSize:=256& * 1024&
With htfIn
Do Until .EOF
strLine = .ReadLine()
Loop
.CloseFile
end with
Yes I am using the txt file class and yes crashes the application/vb.
looks similar to this.
Dim strLine as string
Set htfIn = New HugeTextFile
htfIn.OpenFile "C:\Windows\System32\LogFiles\Firewall\pfirewall.log", HTF_ACCESS_READ, HTF_OPEN_EXISTING, HTF_SHARE_READ , BufferSize:=256& * 1024&
With htfIn
Do Until .EOF
strLine = .ReadLine()
Loop
.CloseFile
end with
vb6 crashes with Exception code: 0xc0000005 if I compile the application it hangs and never does anything forcing me to kill the application. No error msg/number. It's relatively a small file at this point so it should hang at all unless there is a problem opening the file. Before it would crash vb but would give an error that the file was in use before I changed the HTF_OPEN_EXISTING, HTF_SHARE_READ
edit:
so if I do this..
With htfIn
Do Until .EOF
strLine = .ReadLine() if .eof then
.CloseFile
end if
Loop
.CloseFile
end with
then i get run time error 45602 error opening file. error 32
Last edited by brandoncampbell; Sep 6th, 2012 at 02:07 PM.
The error 45602 reports system error 32 as the reason. The system error 32 is ERROR_SHARING_VIOLATION ("The process cannot access the file because it is being used by another process."). I have no idea how the code you show can get this, since I don't see an open, just two CloseFile() calls.
The other problems most likely come from trying to read a file actively being written, until EOF. Because the process logging to this file is still writing and has not set EOF yet by closing it or calling SetEOF there is no EOF to be detected.
Perhaps it hangs waiting to read a new buffer of data, and then hangs again waiting for another after that, and so on.
Basically, what you are trying to do is impractical. The only way I can imagine making it work at all probably requires the use of GetFileSize()/GetFileSizeEx() to figure out "where to call it quits" instead of relying on an EOF indication from the ReadFile() function. If you really need to do this you could probably rewrite the class to work that way.
Note that you will never get all of the data though, only the part the logging process has flushed to disk. Even then the last "line" of text you retrieve will be an incomplete line most of the time, and you may even get back "garbage" for the part of the file that hasn't been flushed-to yet.
then I read the lines from the array.. later.. I read the lines starting at the last line I read based on that same array which is stored as a variable. I was just trying to see if I could get a little more speed using this method.
You're right.. so I was wondering if you think it would be better to copy the file.. for example to a .bak extension and then read the file.. then I wont risk the chance of not getting the data as it is being written.. I am not sure it would be worth changing. Have you done any speed calculations on this method as to other ways of reading files?
The purpose of the examples I provided isn't speed, but very large file I/O. I don't think they are partcularly faster or slower than most ways of doing file I/O though.
If you have a special case you need help with perhaps starting a question thread will get you some helpful answers.
dilettante, thanks for the awsome code.
I was about to quit my project but thanks to your code I can continue to work on it again.
Is it possible to open two files at the same time? I want to compare thier bytes one by one and decide on it, so I need both of them open at the same time, if not possible then I have to use For ... Next and bunch of huge amount of arrays which slows down the routine for sure.
Hello,
Thanks for sharing the Class/Module, But I am having problem on understanding its using.
would you please tell me with an example of using the module with a 2gb file?
Example: Suppose I have a 2Gb file called "hfile.dat". Now how may I read its 1GB bytes and Write them into a New file "hfile_new.dat" ?
Create two instances of the class. Open one for read and the other for write. Read/write in chunks of 32K or so until you have copied over everything you want. Close both.