Line Break Codes
When processing text in VBA, proper handling of line break codes is crucial. This article explains the different types of line break codes in VBA and how they behave.
Types of Line Break Codes in VBA
There are two primary line break characters used in VBA:
- CR (Carriage Return): ASCII code 13
- LF (Line Feed): ASCII code 10
In Windows environments, the combination of CR and LF—called CRLF (Carriage Return + Line Feed)—is the standard.
Examples of Using Line Break Codes
Here’s a typical example of handling line breaks in VBA:
Sub InsertNewLine()
Dim str As String
str = "This line has a break after it." & vbCrLf & "This is a new line."
MsgBox str
End Sub
Using vbCrLf for Line Breaks
vbCrLf is the CRLF combination commonly used in Windows. It starts a new line. In this example, vbCrLf displays two lines of text in a message box.
Using vbCr and vbLf Individually
VBA also provides vbCr (Carriage Return) and vbLf (Line Feed), but vbCrLf is generally recommended. Using vbCr or vbLf alone is rare, but can be useful when working with specific legacy systems or file formats.
Sub UseCrAndLfIndividually()
Dim strCr As String
Dim strLf As String
strCr = "After this line comes a carriage return." & vbCr & "This text follows."
strLf = "After this line comes a line feed." & vbLf & "This text follows."
MsgBox strCr
MsgBox strLf
End Sub
Line Break Behavior
Line Breaks in Text Boxes and Cells
When inserting line breaks in Excel cells using VBA, vbCrLf creates proper line breaks. However, when manually entering line breaks in cells with Alt + Enter, Excel internally uses vbLf only.
Line Breaks in File I/O
When reading from or writing to files, pay attention to line break handling. Windows uses CRLF as standard, but Unix-based systems use only LF. When exchanging files between different systems, you may need to convert line break codes appropriately.
Sub WriteToFile()
Dim fileNum As Integer
Dim text As String
fileNum = FreeFile
Open "C:\example.txt" For Output As #fileNum
text = "This line ends here" & vbCrLf & "Next line starts here."
Print #fileNum, text
Close #fileNum
End Sub
Different line break codes can cause issues when exchanging text files between platforms. For example, a file created in Windows may display incorrectly when opened on a Unix system, appearing as improper line breaks or showing extra characters.
VBA Line Break Constants
Here’s a summary of all line break-related constants in VBA:
| Constant | Value | Description |
|---|---|---|
| vbCrLf | Chr(13) & Chr(10) | Carriage Return + Line Feed (Windows standard) |
| vbCr | Chr(13) | Carriage Return only |
| vbLf | Chr(10) | Line Feed only |
| vbNewLine | Same as vbCrLf | Platform-specific line break |
Practical Examples
Splitting Text by Line Breaks
Sub SplitByLineBreak()
Dim text As String
Dim lines() As String
text = "Line 1" & vbCrLf & "Line 2" & vbCrLf & "Line 3"
' Split by CRLF
lines = Split(text, vbCrLf)
Dim i As Integer
For i = LBound(lines) To UBound(lines)
Debug.Print "Line " & (i + 1) & ": " & lines(i)
Next i
End Sub
Converting Line Break Formats
Sub ConvertLineBreaks()
Dim text As String
' Original text with Unix line breaks (LF only)
text = "Line 1" & vbLf & "Line 2" & vbLf & "Line 3"
' Convert to Windows format (CRLF)
text = Replace(text, vbLf, vbCrLf)
Debug.Print text
End Sub
Handling Mixed Line Breaks
Sub NormalizeLineBreaks()
Dim text As String
' Text with mixed line breaks
text = "Line 1" & vbCrLf & "Line 2" & vbLf & "Line 3" & vbCr & "Line 4"
' Normalize all to CRLF
text = Replace(text, vbCrLf, vbLf) ' First convert CRLF to LF
text = Replace(text, vbCr, vbLf) ' Convert remaining CR to LF
text = Replace(text, vbLf, vbCrLf) ' Convert all LF to CRLF
Debug.Print text
End Sub
Working with Cell Line Breaks
Sub WorkWithCellLineBreaks()
Dim cellValue As String
' Set cell value with line break
Range("A1").Value = "First line" & vbLf & "Second line"
' Read and process
cellValue = Range("A1").Value
' Check if cell contains line breaks
If InStr(cellValue, vbLf) > 0 Then
Debug.Print "Cell contains line breaks"
' Split into lines
Dim lines() As String
lines = Split(cellValue, vbLf)
Debug.Print "Number of lines: " & (UBound(lines) + 1)
End If
End Sub
Excel cells use vbLf for internal line breaks, not vbCrLf. When working with cell values
containing line breaks, use vbLf for splitting and joining.
Summary
Understanding line break codes is essential when working with text in VBA:
- Use
vbCrLffor general-purpose line breaks in Windows - Be aware that Excel cells use
vbLfinternally - When exchanging files between systems, convert line break codes as needed
- Use the appropriate constant for your specific use case
By understanding these differences, you can improve program compatibility and avoid unexpected errors when processing text.