Objeto Form (Access)
Um objeto Form refere-se a um formulário do Microsoft Access em particular.
Comentários
Um objeto Form é um membro da coleção Forms, que é uma coleção de todos os formulários abertos no momento. Na coleção Forms, os formulários individuais são indexados a partir do zero. Você pode fazer referência a um objeto de Formulários individual na coleção de Formulários ao fazer referência ao formulário por nome ou ao fazer referência a seu índice na coleção.
Se quiser se referir a um formulário específico na coleção Forms, será melhor fazer referência ao formulário por nome porque o índice de coleção de um formulário pode ser alterado. Se o nome do formulário incluir um espaço, o nome deverá ficar entre colchetes ([ ]).
Sintaxe | Exemplo |
---|---|
AllForms!formname | AllForms!OrderForm |
AllForms![form name] | AllForms![Order Form] |
AllForms("formname") | AllForms("OrderForm") |
AllForms(index) | AllForms(0) |
Cada objeto Form tem uma coleçãoControls, que contém todos os controles do formulário. Você pode fazer referência a um controle em um formulário ao fazer referência de forma implícita ou explícita à coleção Controles. Seu código será mais rápido se você fizer referencia à coleção Controls implicitamente. Os exemplos a seguir mostram duas das maneiras para fazer referência a um controle chamado NewData no formulário chamado OrderForm.
' Implicit reference.
Forms!OrderForm!NewData
' Explicit reference.
Forms!OrderForm.Controls!NewData
Os próximos dois exemplos mostram como você poderia se referir a um controle chamado NewData em um subformulário ctlSubForm contido no formulário chamado OrderForm.
Forms!OrderForm.ctlSubForm.Form!Controls.NewData
Forms!OrderForm.ctlSubForm!NewData
Exemplo
O exemplo a seguir mostra como usar os controles TextBox para fornecer critérios de data para uma consulta.
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
O exemplo a seguir mostra como usar o evento BeforeUpdate de um formulário para exigir que um valor seja inserido em um controle quando outro controle também tem dados.
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
O exemplo a seguir mostra como usar a propriedade OpenArgs para impedir que um formulário seja aberto a partir do painel de navegação.
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
O exemplo a seguir mostra como usar o argumento WhereCondition do método OpenForm para filtrar os registros exibidos em um formulário quando ele é aberto.
Private Sub cmdShowOrders_Click()
If Not Me.NewRecord Then
DoCmd.OpenForm "frmOrder", _
WhereCondition:="CustomerID=" & Me.txtCustomerID
End If
End Sub
Eventos
- 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
Métodos
Propriedades
- 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
Confira também
Suporte e comentários
Tem dúvidas ou quer enviar comentários sobre o VBA para Office ou sobre esta documentação? Confira Suporte e comentários sobre o VBA para Office a fim de obter orientação sobre as maneiras pelas quais você pode receber suporte e fornecer comentários.