VBA Read Text File (Read, Parse, and Import)
In this Article
This tutorial will demonstrate how to read content from text files and paste it into worksheets with VBA.
Read Text File Content into Worksheet
The simplest way of reading a text file’s content is to copy it into a worksheet’s cell.
Sub FSOPasteTextFileContent()
Dim FSO As New FileSystemObject
Set FSO = CreateObject("Scripting.FileSystemObject")
Set FileToRead = FSO.OpenTextFile("C:\Test\TestFile.txt", ForReading) 'add here the path of your text file
TextString = FileToRead.ReadAll
FileToRead.Close
ThisWorkbook.Sheets(1).Range("A1").Value = TextString 'you can specify the worksheet and cell where to paste the text file’s content
End Sub
The above code uses the FileSystemObject. In order to use it, you will need to set a reference to the VB script run-time library. See here for more information.
Without using FileSystemObject you can paste your text file’s content with the below code. If your text file contains line separator, it will be pasted line by line.
Sub PasteTextFileContent ()
Dim wbExcel As Workbook, wbText As Workbook
Dim wsExcel As Worksheet
Set wbExcel = ThisWorkbook 'specify here which Excel file the text file’s content is to be pasted into
Set wsExcel = wbExcel.Sheets(1) 'specify here which worksheet to use
Set wbText = Workbooks.Open("C:\Test\TestFile.txt") 'add here the path of your text file
wbText.Sheets(1).Cells.Copy wsExcel.Cells
wbText.Close SaveChanges:=False
End Sub
Read Text File Content Line by Line, Column by Column
Your text file may have several rows and several elements listed in the rows separated by comma, semicolon, tab, space, etc.. In order to read and paste the text file’s content correctly, you may need this code below:
Sub PasteTextFileContentWithSeparators()
Dim StrLine As String
Dim FSO As New FileSystemObject
Dim TSO as Object
Dim StrLineElements As Variant
Dim Index As Long
Dim i As Long
Dim Delimiter as String
Set FSO = CreateObject("Scripting.FileSystemObject")
Set TSO = FSO.OpenTextFile("C:\Test\TestFile.txt")
Delimiter=", " 'the delimiter that is used in your text file
Index = 1
Do While TSO.AtEndOfStream = False
StrLine = TSO.ReadLine
StrLineElements = Split(StrLine, Delimiter)
For i = LBound(StrLineElements) To UBound(StrLineElements)
Cells(Index, i + 1).Value = StrLineElements(i) 'this code will start pasting the text file’s content from the active worksheet’s A1 (Cell(1,1)) cell
Next i
Index = Index + 1
Loop
TSO.Close
End Sub
The delimiter that is used in your text file can be comma (“,”), comma with space (“, “), semicolon (“;”), semicolon with space (“; “), space (“ “), tab (change then Delimiter = vbTab) or in rare cases any other character.
Read Text Files into Arrays
If you need to read your text file’s content into an array and paste is line by line, column by column into your worksheet, you will need this code below:
Sub ReadDelimitedTextFileIntoArray()
Dim Delimiter As String
Dim TextFile As Integer
Dim FilePath As String
Dim FileContent As String
Dim LineArray() As String
Dim DataArray() As String
Dim TempArray() As String
Dim rw As Long, col As Long
Delimiter = vbTab 'the delimiter that is used in your text file
FilePath = "C:\Test\TestFileTab.txt"
rw = 1
TextFile = FreeFile
Open FilePath For Input As TextFile
FileContent = Input(LOF(TextFile), TextFile)
Close TextFile
LineArray() = Split(FileContent, vbNewLine) 'change vbNewLine to vbCrLf or vbLf depending on the line separator that is used in your text file
For x = LBound(LineArray) To UBound(LineArray)
If Len(Trim(LineArray(x))) <> 0 Then
TempArray = Split(LineArray(x), Delimiter)
col = UBound(TempArray)
ReDim Preserve DataArray(col, rw)
For y = LBound(TempArray) To UBound(TempArray)
DataArray(y, rw) = TempArray(y)
Cells(x + 1, y + 1).Value = DataArray(y, rw) 'this code will start pasting the text file’s content from the active worksheet’s A1 (Cell(1,1)) cell
Next y
End If
rw = rw + 1
Next x
End Sub
Line separators in your text file can be carriage return and linefeed combination (Chr(13)+Chr(10)) or linefeed (Chr(10)). Use vbCrLf or vbLf, accordingly. If you are not sure, use vbNewLine for indicating the line separator.