Form object (Access)
A Form object refers to a particular Microsoft Access form.
Remarks
A Form object is a member of the Forms collection, which is a collection of all currently open forms. Within the Forms collection, individual forms are indexed beginning with zero. Refer to an individual Form object in the Forms collection either by referring to the form by name, or by referring to its index within the collection.
If you want to refer to a specific form in the Forms collection, it's better to refer to the form by name because a form's collection index may change. If the form name includes a space, the name must be surrounded by brackets ([ ]).
Syntax | Example |
---|---|
AllForms!formname | AllForms!OrderForm |
AllForms![form name] | AllForms![Order Form] |
AllForms("formname") | AllForms("OrderForm") |
AllForms(index) | AllForms(0) |
Each Form object has a Controls collection, which contains all controls on the form. Refer to a control on a form either by implicitly or explicitly referring to the Controls collection. Your code will be faster if you refer to the Controls collection implicitly. The following examples show two of the ways you might refer to a control named NewData on the form called OrderForm.
' Implicit reference.
Forms!OrderForm!NewData
' Explicit reference.
Forms!OrderForm.Controls!NewData
The next two examples show how you might refer to a control named NewData on a subform ctlSubForm contained in the form called OrderForm.
Forms!OrderForm.ctlSubForm.Form!Controls.NewData
Forms!OrderForm.ctlSubForm!NewData
Example
The following example shows how to use TextBox controls to supply date criteria for a query.
Private Sub cmdSearch_Click()
Dim db As DAO.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 [PayeeID]=" + Me.cboPayeeID
If Nz(Me.txtEndDate, "") <> "" And Nz(Me.txtStartDate, "") <> "" Then
vWhere = vWhere & " AND [RefundProcessed] Between #" & _
Me.txtStartDate & "# AND #" & Me.txtEndDate & "#"
Else
If Nz(Me.txtEndDate, "") = "" And Nz(Me.txtStartDate, "") <> "" Then
vWhere = vWhere & " AND [RefundProcessed]>=#" _
+ Me.txtStartDate & "#"
Else
If Nz(Me.txtEndDate, "") <> "" And Nz(Me.txtStartDate, "") = "" Then
vWhere = vWhere & " AND [RefundProcessed] <=#" _
+ Me.txtEndDate & "#"
End If
End If
End If
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
The following example shows how to use the BeforeUpdate event of a form to require that a value be entered into one control when another control also has data.
Private Sub Form_BeforeUpdate(Cancel As Integer)
If (IsNull(Me.FieldOne)) Or (Me.FieldOne.Value = "") Then
' No action required
Else
If (IsNull(Me.FieldTwo)) or (Me.FieldTwo.Value = "") Then
MsgBox "You must provide data for field 'FieldTwo', " & _
"if a value is entered in FieldOne", _
vbOKOnly, "Required Field"
Me.FieldTwo.SetFocus
Cancel = True
Exit Sub
End If
End If
End Sub
The following example shows how to use the OpenArgs property to prevent a form from being opened from the navigation pane.
Private Sub Form_Open(Cancel As Integer)
If Me.OpenArgs() <> "Valid User" Then
MsgBox "You are not authorized to use this form!", _
vbExclamation + vbOKOnly, "Invalid Access"
Cancel = True
End If
End Sub
The following example shows how to use the WhereCondition argument of the OpenForm method to filter the records displayed on a form as it is opened.
Private Sub cmdShowOrders_Click()
If Not Me.NewRecord Then
DoCmd.OpenForm "frmOrder", _
WhereCondition:="CustomerID=" & Me.txtCustomerID
End If
End Sub
Events
- Activate
- AfterDelConfirm
- AfterFinalRender
- AfterInsert
- AfterLayout
- AfterRender
- AfterUpdate
- ApplyFilter
- BeforeDelConfirm
- BeforeInsert
- BeforeQuery
- BeforeRender
- BeforeScreenTip
- BeforeUpdate
- Click
- Close
- CommandBeforeExecute
- CommandChecked
- CommandEnabled
- CommandExecute
- Current
- DataChange
- DataSetChange
- DblClick
- Deactivate
- Delete
- Dirty
- Error
- Filter
- GotFocus
- KeyDown
- KeyPress
- KeyUp
- Load
- LostFocus
- MouseDown
- MouseMove
- MouseUp
- MouseWheel
- OnConnect
- OnDisconnect
- Open
- PivotTableChange
- Query
- Resize
- SelectionChange
- Timer
- Undo
- Unload
- ViewChange
Methods
Properties
- ActiveControl
- AfterDelConfirm
- AfterFinalRender
- AfterInsert
- AfterLayout
- AfterRender
- AfterUpdate
- AllowAdditions
- AllowDatasheetView
- AllowDeletions
- AllowEdits
- AllowFilters
- AllowFormView
- AllowLayoutView
- AllowPivotChartView
- AllowPivotTableView
- Application
- AutoCenter
- AutoResize
- BeforeDelConfirm
- BeforeInsert
- BeforeQuery
- BeforeRender
- BeforeScreenTip
- BeforeUpdate
- Bookmark
- BorderStyle
- Caption
- ChartSpace
- CloseButton
- CommandBeforeExecute
- CommandChecked
- CommandEnabled
- CommandExecute
- ControlBox
- Controls
- Count
- CurrentRecord
- CurrentSectionLeft
- CurrentSectionTop
- CurrentView
- Cycle
- DataChange
- DataEntry
- DataSetChange
- DatasheetAlternateBackColor
- DatasheetBackColor
- DatasheetBorderLineStyle
- DatasheetCellsEffect
- DatasheetColumnHeaderUnderlineStyle
- DatasheetFontHeight
- DatasheetFontItalic
- DatasheetFontName
- DatasheetFontUnderline
- DatasheetFontWeight
- DatasheetForeColor
- DatasheetGridlinesBehavior
- DatasheetGridlinesColor
- DefaultControl
- DefaultView
- Dirty
- DisplayOnSharePointSite
- DividingLines
- FastLaserPrinting
- FetchDefaults
- Filter
- FilterOn
- FilterOnLoad
- FitToScreen
- Form
- FrozenColumns
- GridX
- GridY
- HasModule
- HelpContextId
- HelpFile
- HorizontalDatasheetGridlineStyle
- Hwnd
- InputParameters
- InsideHeight
- InsideWidth
- KeyPreview
- LayoutForPrint
- MaxRecButton
- MaxRecords
- MenuBar
- MinMaxButtons
- Modal
- Module
- MouseWheel
- Moveable
- Name
- NavigationButtons
- NavigationCaption
- NewRecord
- OnActivate
- OnApplyFilter
- OnClick
- OnClose
- OnConnect
- OnCurrent
- OnDblClick
- OnDeactivate
- OnDelete
- OnDirty
- OnDisconnect
- OnError
- OnFilter
- OnGotFocus
- OnInsert
- OnKeyDown
- OnKeyPress
- OnKeyUp
- OnLoad
- OnLostFocus
- OnMouseDown
- OnMouseMove
- OnMouseUp
- OnOpen
- OnResize
- OnTimer
- OnUndo
- OnUnload
- OpenArgs
- OrderBy
- OrderByOn
- OrderByOnLoad
- Orientation
- Page
- Pages
- Painting
- PaintPalette
- PaletteSource
- Parent
- Picture
- PictureAlignment
- PictureData
- PicturePalette
- PictureSizeMode
- PictureTiling
- PictureType
- PivotTable
- PivotTableChange
- PopUp
- Printer
- Properties
- PrtDevMode
- PrtDevNames
- PrtMip
- Query
- RecordLocks
- RecordSelectors
- Recordset
- RecordsetClone
- RecordsetType
- RecordSource
- RecordSourceQualifier
- ResyncCommand
- RibbonName
- RowHeight
- ScrollBars
- Section
- SelectionChange
- SelHeight
- SelLeft
- SelTop
- SelWidth
- ServerFilter
- ServerFilterByForm
- ShortcutMenu
- ShortcutMenuBar
- SplitFormDatasheet
- SplitFormOrientation
- SplitFormPrinting
- SplitFormSize
- SplitFormSplitterBar
- SplitFormSplitterBarSave
- SubdatasheetExpanded
- SubdatasheetHeight
- Tag
- TimerInterval
- Toolbar
- UniqueTable
- UseDefaultPrinter
- VerticalDatasheetGridlineStyle
- ViewChange
- ViewsAllowed
- Visible
- Width
- WindowHeight
- WindowLeft
- WindowTop
- WindowWidth
See also
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.