Module.Lines property (Access)
The Lines property returns a string containing the contents of a specified line or lines in a standard module or a class module. Read-only String.
Syntax
expression.Lines (Line, NumLines)
expression A variable that represents a Module object.
Parameters
Name | Required/Optional | Data type | Description |
---|---|---|---|
Line | Required | Long | The number of the first line to return. |
NumLines | Required | Long | The number of lines to return. |
Remarks
Lines in a module are numbered beginning with 1. For example, if you read the Lines property with a value of 1 for the Line argument and 1 for the NumLines argument, the Lines property returns a string containing the text of the first line in the module.
To insert a line of text into a module, use the InsertLines method.
Example
The following example deletes a specified line from a module.
Function DeleteWholeLine(strModuleName, strText As String) _
As Boolean
Dim mdl As Module, lngNumLines As Long
Dim lngSLine As Long, lngSCol As Long
Dim lngELine As Long, lngECol As Long
Dim strTemp As String
On Error GoTo Error_DeleteWholeLine
DoCmd.OpenModule strModuleName
Set mdl = Modules(strModuleName)
If mdl.Find(strText, lngSLine, lngSCol, lngELine, lngECol) Then
lngNumLines = Abs(lngELine - lngSLine) + 1
strTemp = LTrim$(mdl.Lines(lngSLine, lngNumLines))
strTemp = RTrim$(strTemp)
If strTemp = strText Then
mdl.DeleteLines lngSLine, lngNumLines
Else
MsgBox "Line contains text in addition to '" _
& strText & "'."
End If
Else
MsgBox "Text '" & strText & "' not found."
End If
DeleteWholeLine = True
Exit_DeleteWholeLine:
Exit Function
Error_DeleteWholeLine:
MsgBox Err & " :" & Err.Description
DeleteWholeLine = False
Resume Exit_DeleteWholeLine
End Function
You could call this function from a procedure such as the following, which searches the module Module1 for a constant declaration and deletes it.
Sub DeletePiConst()
If DeleteWholeLine("Module1", "Const conPi = 3.14") Then
Debug.Print "Constant declaration deleted successfully."
Else
Debug.Print "Constant declaration not deleted."
End If
End Sub
Support and feedback
Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.