Module.ProcOfLine property (Access)

The ProcOfLine property returns the name of the procedure that contains a specified line in a standard module or a class module. Read-only string.

Syntax

expression.ProcOfLine (Line, ProcKind)

expression A variable that represents a Module object.

Parameters

Name Required/Optional Data type Description
Line Required Long The number of a line in the module.
ProcKind Required vbext_ProcKind The type of procedure. See the Remarks section for the possible settings.

Remarks

The ProcKind argument can be one of the following vbext_ProcKind constants:

Constant Description
vbext_pk_Get A Property Get procedure.
vbext_pk_Let A Property Let procedure.
vbext_pk_Proc A Sub or Function procedure.
vbext_pk_Set A Property Set procedure.

For any given line number, the ProcOfLine property returns the name of the procedure that contains that line. Because comments and compilation constants immediately preceding a procedure definition are considered part of that procedure, the ProcOfLine property may return the name of a procedure for a line that isn't within the body of the procedure.

The ProcStartLine property indicates the line on which a procedure begins; the ProcBodyLine property indicates the line on which the procedure definition begins (the body of the procedure).

Note that the ProcKind argument indicates whether the line belongs to a Sub or Function procedure, a Property Get procedure, a Property Let procedure, or a Property Set procedure. To determine what type of procedure a line is in, pass a variable of type Long to the ProcOfLine property, and then check the value of that variable.

Note

The ProcOfLine property treats Sub and Function procedures similarly, but distinguishes between each type of Property procedure.

Example

The following function procedure lists the names of all procedures in a specified module.

Public Function AllProcs(ByVal strModuleName As String) 
 
 Dim mdl As Module 
 Dim lngCount As Long 
 Dim lngCountDecl As Long 
 Dim lngI As Long 
 Dim strProcName As String 
 Dim astrProcNames() As String 
 Dim intI As Integer 
 Dim strMsg As String 
 Dim lngR As Long 
 
 ' Open specified Module object. 
 DoCmd.OpenModule strModuleName 
 
 ' Return reference to Module object. 
 Set mdl = Modules(strModuleName) 
 
 ' Count lines in module. 
 lngCount = mdl.CountOfLines 
 
 ' Count lines in Declaration section in module. 
 lngCountDecl = mdl.CountOfDeclarationLines 
 
 ' Determine name of first procedure. 
 strProcName = mdl.ProcOfLine(lngCountDecl + 1, lngR) 
 
 ' Initialize counter variable. 
 intI = 0 
 
 ' Redimension array. 
 ReDim Preserve astrProcNames(intI) 
 
 ' Store name of first procedure in array. 
 astrProcNames(intI) = strProcName 
 
 ' Determine procedure name for each line after declarations. 
 For lngI = lngCountDecl + 1 To lngCount 
 ' Compare procedure name with ProcOfLine property value. 
 If strProcName <> mdl.ProcOfLine(lngI, lngR) Then 
 ' Increment counter. 
 intI = intI + 1 
 strProcName = mdl.ProcOfLine(lngI, lngR) 
 ReDim Preserve astrProcNames(intI) 
 ' Assign unique procedure names to array. 
 astrProcNames(intI) = strProcName 
 End If 
 Next lngI 
 
 strMsg = "Procedures in module '" & strModuleName & "': " & vbCrLf & vbCrLf 
 For intI = 0 To UBound(astrProcNames) 
 strMsg = strMsg & astrProcNames(intI) & vbCrLf 
 Next intI 
 
 ' Message box listing all procedures in module. 
 MsgBox strMsg 
End Function

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.