TextBox.SelStart 属性 (Access)

SelStart 属性指定或确定所选文本的起始点或者插入点的位置,如果未不选择任何文本。 Integer 型,可读/写。

语法

表达式SelStart

表达 一个代表 TextBox 对象的变量。

备注

SelStart 属性使用一个 整数 范围在 0 到组合框的文本框部分中的字符总数。

若要设置或返回控件的这个属性,控件必须获得焦点。 若要将焦点移到某个控件,使用 SetFocus 方法。

SelStart 属性更改取消所选内容,将插入点放在文本中,并将 SelLength 属性设置为 0。

示例

下面的示例使用两个事件过程来搜索用户指定的文本。 要搜索的文本在窗体的 Load 事件过程中设置。 “查找”按钮的 Click 事件过程 (用户单击以开始搜索) 提示用户输入要搜索的文本,并在搜索成功时选择文本框中的文本。

Private Sub Form_Load() 
 
 Dim ctlTextToSearch As Control 
 Set ctlTextToSearch = Forms!Form1!Textbox1 
 
 ' SetFocus to text box. 
 ctlTextToSearch.SetFocus 
 ctlTextToSearch.Text = "This company places large orders twice " & _ 
 "a year for garlic, oregano, chilies and cumin." 
 Set ctlTextToSearch = Nothing 
 
End Sub 
 
Public Sub Find_Click() 
 
 Dim strSearch As String 
 Dim intWhere As Integer 
 Dim ctlTextToSearch As Control 
 
 ' Get search string from user. 
 With Me!Textbox1 
 strSearch = InputBox("Enter text to find:") 
 
 ' Find string in text. 
 intWhere = InStr(.Value, strSearch) 
 If intWhere Then 
 ' If found. 
 .SetFocus 
 .SelStart = intWhere - 1 
 .SelLength = Len(strSearch) 
 Else 
 ' Notify user. 
 MsgBox "String not found." 
 End If 
 End With 
 
End Sub

支持和反馈

有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。