QODBC: How to use VBA to Disable Non-Updateable QuickBooks® Fields on a Microsoft® Access® Form (Part 1)

Annaliese DellSec-Treas
QODBC and tech tips
Published:
Updated:
Code that checks the QuickBooks schema table for non-updateable fields and then disables those controls on a form so users don't try to update them.

QODBC lets you update QuickBooks directly from a Microsoft Access form using SQL. You can, for example, import all the Fields from the customer table, display them on a form, let users change the data and click a button to update QuickBooks directly from the form.


Users, however, should only be allowed to change data that’s updateable. For example, FullName is not updateable in the customer table. If the FullName text box is enabled on the form, users might think they can change it but they can’t. If they do change the information in Access, it won’t match QuickBooks. Depending on how you create your update SQL, users might also receive an error message for trying to update a non-updateable field.


To prevent this, disable non-updateable fields on the form. This way, they’re displayed for the user’s information but can’t be changed. You don't have to do this manually, though.


The method in this article lets you disable non-updateable fields using VBA so you don't have to look up each field in the schema table to see if it's updateable and then manually disable it on the form. 


The disabled (grayed out) fields on the form below were disabled using VBA in the form's On Open Event.



To see if a field is updateable in QuickBooks, type “sp_columns customer” into VB Demo (supplied with QODBC).


The table below shows the 24 non-updateable fields in the customer table. Each table is different but they all contain non-updateable fields.




Requirements to Implement This Method:


    •QODBC Desktop
    •DAO in a single database
    •Microsoft Access 2016 (also tested on 2010)
    •QuickBooks 2016 (also tested on 2013)



The Process in a Nutshell:


    •Loop through the controls on the form.
    •Ignore Controls other than Text Box and Combo Box.
    •If the Schema table doesn’t exist in the database, create it and resume.
    •Lookup the updateable value in the Schema table.
    •If the field is not updateable, disable the control.


To Use This Method:


    •You must name the controls the QuickBooks field names. For example, a combo box for IsActive must be named: IsActive. 

      A text box for VendorRefFullName must be named VendorRefFullName.

    •Call the DisableNonUpdateableFields from the form’s On Open Event.


Tables This Method Works for:


    •Customer
    •Vendor
    •Employee
    •Entity
    •OtherName
    •ItemFixedAsset


To Test This Method:


    1. Open the QuickBooks sample file.
    2. Create a new database.
    3. If your version of Access doesn’t include DAO, add a reference to it.


Enter the Code


    4. Copy the procedure and function below and paste them into the Visual Basic Editor in a new Module.


Sub DisableNonUpdateableFields(frm As Form, QBTableName As String)
‘This Procedure loops through the Controls on the form and 
‘retrieves the Updateable Value in the Schema Table. 
‘Control s for QuickBooks® Fields must be named the QuickBooks® Field name.
‘In other words, don’t name a List Box for Class: lstClass. Keep it: Class.
On Error GoTo err
Dim ctl As Control, sCrit As String
'Loop through the form controls.
130 For Each ctl In frm.Controls
'Only check Text Boxes and combo boxes (add List Boxes if desired).
140 If (ctl.ControlType = 109 Or ctl.ControlType = 111) Then
‘Assemble  criteria to lookup the Updateable Value in the Schema Table.
150 sCrit = " TABLENAME='" & QBTableName & "' AND COLUMNNAME='" & ctl.Name & "'"
'Set the control's enabled Value to the Updateable Value (true or false)
'If the field doesn't exist in the schema table, DLookup is null and so True.
‘If the Field’s Updateable Property is False , set the control’s enabled Property to false
160 If Nz(DLookup("UPDATEABLE", "Schema_" & QBTableName & "_RL", sCrit), True) = False Then ctl.Enabled = False 
170 End If
180 Next
'This assumes you use ListID (QuickBooks® unique identifier) to locate records with docmd.findrecord.
'If that's the case, ListID needs to be set to enabled = true and locked= true.
‘You don’t want users changing ListIDs.
190 frm.Controls("ListID").Enabled = True
200 frm.Controls("ListID").Locked = True
210 EXITSUB:
220 Exit Sub
230 err:
240 Debug.Print Erl, err.Number, err.Description
'If the schema table doesn't exist, call the procedure that creates it.
If err.Number = 3078 And err.Description Like "*schema*" Then
Call ImportSchemaTable(QBTableName)
Resume
End If
250 Resume EXITSUB
End Sub



Sub ImportSchemaTable(QBTableName As String)
‘Imports the Schema Table from QuickBooks® that contains the Updateable Values of 
‘QuickBooks® Fields.
On Error GoTo err
'create a QODBC query
Dim db As DAO.Database, qDef As QueryDef
Set db = CurrentDb
Set qDef = db.CreateQueryDef("qryTemp")
qDef.ODBCTimeout = 60
qDef.Connect = "ODBC;DSN=QuickBooks Data;SERVER=QODBC"
qDef.SQL = "sp_columns " & QBTableName

'put the query results into a database schema table
DoCmd.SetWarnings False
DoCmd.RunSQL ("select * into Schema_" & QBTableName & "_RL from qryTemp")
DoCmd.SetWarnings True

EXITSUB:
Set qDef = Nothing
Set db = Nothing
Exit Sub
err:
If err.Description Like "*failed*" Then
'if the connection failed, could be QuickBooks is closed
MsgBox "Either QuickBooks is closed or there is another problem. Run a test query.", vbOKOnly
End
ElseIf err.Number = 3012 Then
'the query already exists so delete it and resume
DoCmd.DeleteObject acQuery, "qryTemp"
Resume
End If
'some other error, print information to the imemediate window
Debug.Print Erl, err.Number, err.Description
Resume EXITSUB
End Sub


Create a Pass-Through Query to Import the Customer Table


5. Click the Create Tab on the Ribbon and then Query Design.



6. Close the Show Table window.
7. Right click in the gray area of the Query window to show the pop up menu.
8. Highlight: SQL Specific.
9. Click: Pass-Through Query.



10. In the Query in SQL View, type: select * from customer.



11. If the Query’s Property Sheet is not open:
        1. Click the Design Tab on the Ribbon.
        2. Click Property Sheet to open the Query’s Property Sheet.


12. Click the Ellipsis on the ODBC Connect Str line to open the Select Data Source dialog box.



13. Click the Machine Data Source tab.
14. Select QuickBooks Data as the Data Source Name.



15. Select whether you want to save the password in the connection string or not.
16. Click OK.
17. Close and save the Query as: qryTemp



Create a Customer Table From the Pass-Through Query


18. In the Immediate Window of the Visual Basic Editor type:


            Docmd.runsql(“select * into Customer from qryTemp”)


19. Hit enter at the end of the statement and wait while QODBC retrieves the information.



Create a Customer Form


20. Return to the Database Window and Click the Create Tab on the Ribbon.
21. Click: Form Wizard.



22. Select the new Customer table as the Record Source from the drop down box.
23. Select these Fields:



24. Click next, select columnar as the layout, next and finish.
25. The new form will open with all fields enabled.


Call the Procedure


26. Switch the form to Design View.
27. Open the form’s Property Sheet.
28. Click the Event Tab.
29. Click the Ellipsis on the On Click line and create an Event Procedure (choose Code Builder if you didn’t set your database to always use            Event Procedures).



30. Inside the new Procedure type:


         Call DisableNonUpdateableFields(Form, "Customer")



31. Save the form and open it in Form View.


Notice some of the Fields are grayed out and can’t be edited. VBA did this for you.


Notice ListID is enabled but locked.



Update Exceptions


Notice ParentRefFullName is enabled in the sample form above. ParentRefFullName is only updateable under certain conditions. When you find an exception like this, manually disable the control and it will stay disabled. The code won’t change controls from disabled to enabled, only from enabled to disabled.

There is an easy workaround for exceptions and it doesn't require manually disabling controls. See below for a link to Part 2.


Summary


There is no need to look up the updateable value of every single field and manually disable non-updateable fields on forms. Let VBA do the work for you. Manually disable exceptions like ParentRefFullName.


Click here for Part 2.


0
2,466 Views

Comments (0)

Have a question about something in this article? You can receive help directly from the article author. Sign up for a free trial to get started.