ComboBox 对象 (Access)
此对象对应于一个组合框控件。 组合框控件兼具文本框和列表框的功能。 如果您希望用户既可以键入值又可以从预定义列表中选择值,则可使用组合框。
控制 | 工具 |
---|---|
在“窗体”视图中,只有单击组合框的箭头时 Microsoft Access 才会显示列表。
如果在选择组合框工具之前已打开了“控件向导”,则可以使用向导来创建组合框。 若要打开或关闭“控件向导”,请单击工具箱中的“控件向导”工具。
LimitToList 属性的设置确定是否可以输入不在列表中的值。
列表可以是单列也可以是多列,而且列可以显示也可以不显示列标题。
以下示例演示如何使用多个“组合框”控件,以提供查询条件。
Private Sub cmdSearch_Click()
Dim db As Database
Dim qd As QueryDef
Dim vWhere As Variant
Set db = CurrentDb()
On Error Resume Next
db.QueryDefs.Delete "Query1"
On Error GoTo 0
vWhere = Null
vWhere = vWhere & " AND [PymtTypeID]=" & Me.cboPaymentTypes
vWhere = vWhere & " AND [RefundTypeID]=" & Me.cboRefundType
vWhere = vWhere & " AND [RefundCDMID]=" & Me.cboRefundCDM
vWhere = vWhere & " AND [RefundOptionID]=" & Me.cboRefundOption
vWhere = vWhere & " AND [RefundCodeID]=" & Me.cboRefundCode
If Nz(vWhere, "") = "" Then
MsgBox "There are no search criteria selected." & vbCrLf & vbCrLf & _
"Search Cancelled.", vbInformation, "Search Canceled."
Else
Set qd = db.CreateQueryDef("Query1", "SELECT * FROM tblRefundData WHERE " & _
Mid(vWhere, 6))
db.Close
Set db = Nothing
DoCmd.OpenQuery "Query1", acViewNormal, acReadOnly
End If
End Sub
以下示例演示在加载窗体时如何设置组合框的“RowSource”属性。 当显示该窗体时,存储在“tblDepartment”组合框的“Department”字段中的项目将显示在“cboDept”组合框中。
Private Sub Form_Load()
Me.Caption = "Today is " & Format$(Date, "dddd mmm-d-yyyy")
Me.RecordSource = "tblDepartments"
DoCmd.Maximize
txtDept.ControlSource = "Department"
cmdClose.Caption = "&Close"
cboDept.RowSourceType = "Table/Query"
cboDept.RowSource = "SELECT Department FROM tblDepartments"
End Sub
以下示例演示如何创建绑定到一个列而显示另一列的组合框。 将“ColumnCount”属性设置为 2 可指定“cboDept”组合框将显示由“RowSource”属性指定的数据源的前两列。 将“BoundColumn”属性设置为 1 可指定在检查组合框的值时将会返回存储在第一列中的值。
ColumnWidths 属性指定两列的宽度。 通过将第一列的宽度设置为 0in.,可以在组合框中不显示第一列。
Private Sub cboDept_Enter()
With cboDept
.RowSource = "SELECT * FROM tblDepartments ORDER BY Department"
.ColumnCount = 2
.BoundColumn = 1
.ColumnWidths = "0in.;1in."
End With
End Sub
以下示例演示如何将项目添加到绑定的组合框。
Private Sub cboMainCategory_NotInList(NewData As String, Response As Integer)
On Error GoTo Error_Handler
Dim intAnswer As Integer
intAnswer = MsgBox("""" & NewData & """ is not an approved category. " & vbcrlf _
& "Do you want to add it now?", vbYesNo + vbQuestion, "Invalid Category")
Select Case intAnswer
Case vbYes
DoCmd.SetWarnings False
DoCmd.RunSQL "INSERT INTO tlkpCategoryNotInList (Category) " & _
"Select """ & NewData & """;"
DoCmd.SetWarnings True
Response = acDataErrAdded
Case vbNo
MsgBox "Please select an item from the list.", _
vbExclamation + vbOKOnly, "Invalid Entry"
Response = acDataErrContinue
End Select
Exit_Procedure:
DoCmd.SetWarnings True
Exit Sub
Error_Handler:
MsgBox Err.Number & ", " & Err.Description
Resume Exit_Procedure
Resume
End Sub
- AfterUpdate
- BeforeUpdate
- Change
- Click
- DblClick
- Dirty
- Enter
- 退出
- GotFocus
- KeyDown
- KeyPress
- KeyUp
- LostFocus
- MouseDown
- MouseMove
- MouseUp
- NotInList
- Undo
- AddColon
- AfterUpdate
- AllowAutoCorrect
- AllowValueListEdits
- Application
- AutoExpand
- AutoLabel
- BackColor
- BackShade
- BackStyle
- BackThemeColorIndex
- BackTint
- BeforeUpdate
- BorderColor
- BorderShade
- BorderStyle
- BorderThemeColorIndex
- BorderTint
- BorderWidth
- BottomMargin
- BottomPadding
- BoundColumn
- CanGrow
- CanShrink
- Column
- ColumnCount
- ColumnHeads
- ColumnHidden
- ColumnOrder
- ColumnWidth
- ColumnWidths
- Controls
- ControlSource
- ControlTipText
- ControlType
- DecimalPlaces
- DefaultValue
- DisplayAsHyperlink
- DisplayWhen
- Enabled
- EventProcPrefix
- FontBold
- FontItalic
- FontName
- FontSize
- FontUnderline
- FontWeight
- ForeColor
- ForeShade
- ForeThemeColorIndex
- ForeTint
- Format
- FormatConditions
- GridlineColor
- GridlineShade
- GridlineStyleBottom
- GridlineStyleLeft
- GridlineStyleRight
- GridlineStyleTop
- GridlineThemeColorIndex
- GridlineTint
- GridlineWidthBottom
- GridlineWidthLeft
- GridlineWidthRight
- GridlineWidthTop
- Height
- HelpContextId
- HideDuplicates
- HorizontalAnchor
- Hyperlink
- IMEHold
- IMEMode
- IMESentenceMode
- InheritValueList
- InputMask
- InSelection
- IsHyperlink
- IsVisible
- ItemData
- ItemsSelected
- KeyboardLanguage
- LabelAlign
- LabelX
- LabelY
- Layout
- LayoutID
- Left
- LeftMargin
- LeftPadding
- LimitToList
- ListCount
- ListIndex
- ListItemsEditForm
- ListRows
- ListWidth
- Locked
- 名称
- NumeralShapes
- OldBorderStyle
- OldValue
- OnChange
- OnClick
- OnDblClick
- OnDirty
- OnEnter
- OnExit
- OnGotFocus
- OnKeyDown
- OnKeyPress
- OnKeyUp
- OnLostFocus
- OnMouseDown
- OnMouseMove
- OnMouseUp
- OnNotInList
- OnUndo
- Parent
- Properties
- ReadingOrder
- Recordset
- RightMargin
- RightPadding
- RowSource
- RowSourceType
- ScrollBarAlign
- Section
- Selected
- SelLength
- SelStart
- SelText
- SeparatorCharacters
- ShortcutMenuBar
- ShowOnlyRowSourceValues
- SmartTags
- SpecialEffect
- StatusBarText
- TabIndex
- TabStop
- Tag
- Text
- TextAlign
- ThemeFontIndex
- Top
- TopMargin
- TopPadding
- ValidationRule
- ValidationText
- 值
- VerticalAnchor
- Visible
- Width
有关于 Office VBA 或本文档的疑问或反馈? 请参阅 Office VBA 支持和反馈,获取有关如何接收支持和提供反馈的指南。