Module.ProcOfLine 屬性 (Access)
ProcOfLine 屬性會傳回包含在標準模組或類別模組中的某一指定的行的程序的名稱。 唯讀的字串。
語法
運算式。ProcOfLine (Line、 ProcKind)
表達 代表 Module 物件的變數。
參數
名稱 | 必要/選用 | 資料類型 | 描述 |
---|---|---|---|
Line | 必要 | Long | 模組中某一行的編號。 |
ProcKind | 必要 | vbext_ProcKind | 程序的類型。 請參閱這些可能設定的「備註」小節。 |
註解
ProcKind 引數可以為下列其中一個 vbext_ProcKind 常數:
常數 | 描述 |
---|---|
vbext_pk_Get | Property Get 程序。 |
vbext_pk_Let | Property Let 程序。 |
vbext_pk_Proc | Sub 或 Function 程序。 |
vbext_pk_Set | Property Set 程序。 |
任何的特定的行號、 ProcOfLine 屬性會傳回包含該線條的程序名稱。 因為緊接在程式定義前面的批註和編譯常數會被視為該程式的一部分, 所以 ProcOfLine 屬性可能會針對不在程式主體內的程式傳回程序的名稱。
ProcStartLine 屬性會指出的線條程序開始; ProcBodyLine 屬性會指出的線條的程序定義開始 (本文的程序)。
請注意, ProcKind 自 變數指出線條屬於 Sub 或 Function 程式、 Property Get 程式、 Property Let 程式或 Property Set 程式。 若要判斷線條所在的程式類型,請將 Long 類型的變數傳遞至 ProcOfLine 屬性,然後檢查該變數的值。
注意事項
ProcOfLine屬性會以類似的方式處理Sub和Function程式,但會區分每種類型的 Property 程式。
範例
下列函式程式會列出指定模組中所有程式的名稱。
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
支援和意見反應
有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應。