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

Annaliese DellSec-Treas
QODBC and tech tips
Published:
Instead of error trapping or hard-coding for non-updateable fields when using QODBC, let VBA automatically disable them when forms open. This way, users can view but not change the data. Part 1 explained how to use schema tables to do this. Part 2 handles schema table exceptions.

Part 1 Review

In Part 1 (click here) of How to use VBA to Disable Non-Updateable QuickBooks® Fields on a Microsoft® Access®Form , we:


    • Imported a Schema table.

    • Used DLookup to retrieve the Updateable value of each field.

    • Used VBA to disable form controls if their corresponding fields were not Updateable.


We need a bit more code to automate this process even more.


Schema Tables Are Not Always Correct


As an example, ParentRefFullName's Updateable value is 1 (True) in the Customer Schema Table but is not always Updateable.


ParentRefFullName Exception Explained


You don't need this explanation to use this method. It's only provided for the curious. If you don't care, skip to the next heading.


The customer table FullName field contains the name of the customer and also any jobs as follows:


Customer #1

Customer #1: Job 1

Customer #1: Job 2: Work order A

Customer #1: Job 2: Work order B

Customer #2:

Customer #2: Job 1A

etc.


Each FullName is assigned a sublevel. In the above list, the sublevels are:


Customer: 0

Job: 1 

Work order: 2


Moving a job to a customer (Sublevel zero) is done by updating the ParentRefFullName of the job. As an example, to move Job 1A to Customer #1, you simply change Job 1A's ParentRefFullName from Customer #2 to Customer #1.


That's how it's accomplished programmatically but this is not always possible even directly inside the QuickBooks interface. You can see a demonstration of that in this youtube video: https://www.youtube.com/watch?v=UivtLjJsQ1g or the video below.



Why would anyone want to move a job from one customer to another? Who knows but since it's possible, some user somewhere, and probably more than one user, will try it so you need to plan for it. Besides, ParentRefFullName is only one of several schema table exceptions.


There are a few reasons why you wouldn't be allowed to update the ParentRefFullName of a job:


  1. You can’t change the Parent Name (customer) from a child record (job). You must go to the parent record and change the name there. Child records will then reflect the change.

  2. A job can only be moved to an existing customer. Therefore, when working with Access, you need a Combo Box of existing Customers to choose from. You can’t type a new customer name in a text box and have it inserted while updating job info.

  3. You can move the job to another customer but only if that customer has no job info. If you try to move a job to a customer that already has job info, you get this message:


To see if a customer or job has job info, open the customer in QuickBooks®. If you don’t see the job info tab, the customer does not have job info.



If you do see the Job Info tab but no information is entered for a job, that counts as no job info.


This was an example of how tricky exceptions can get and they get even trickier in the item tables like ItemService, ItemOtherCharge, etc. That’s why you need an easy way to handle any that you find.


Known Exceptions


Below is a list of known exceptions for QuickBooks® Premier Contractor 2016:


                • Customer Table:

                                ClassRefFullName

                                ParentRefFullName

                • Vendor Table:

                                IsTaxAgency

                                ClassRefFullName

                • ItemFixedAsset:

                                AcquiredAs

                                ClassRefFullName

                                Any sales field


The easiest way around exceptions is to use an additional table and DLookup.


Create an Exceptions Table


We could create an exceptions table manually but if you've ever deleted a table by mistake, you'll appreciate letting VBA create tables for you. Then simply check for their existence before use and create them if need be.


We won’t add all the possible exceptions using VBA, just a few. The rest we’ll add manually.


In the Visual Basic Editor, insert a new Module and paste the following Procedure:


Sub ExceptionsTable()
On Error GoTo err
DoCmd.SetWarnings False
DoCmd.RunSQL "Select 'ALL' as QBTable,'ListID,TimeCreated,TimeModified' as ColumnName," & _
"'Guid, Edit, Currency, Parent' as ColumnNameLike into UpdateExceptions"
DoCmd.RunSQL "ALTER TABLE UpdateExceptions ADD COLUMN Updateable YESNO"
DoCmd.SetWarnings True
Exit Sub
err:
Debug.Print "Error in Sub ExceptionsTable on Line: " & Erl, "Error#", err.Number
Debug.Print err.Description
Resume Next
End Sub


In the Immediate Window, call the above procedure by typing ExceptionsTable and hit enter at the end of the statement.



Add More Exceptions to the Table


Now that we have an exceptions table with a few basic exceptions, we can add more.


Return to the database window and the navigation pane. Open the UpdateExceptions table. The first record applies to ALL tables. You can’t update any of those fields. You can try updating currency in your QuickBooks® version and if you can, simply remove it from the table and from the procedure that creates the table.



Now let's add more exceptions.


We already know some fields say updateable in the Schema table even though they aren't. Add these Fields now:



Function That Returns Exceptions


Next, we need a Function that returns these exceptions.


The UpdateExceptions table has two columns we need to Query for strings: 

  1.     ColumnName (exact match)
  2.     ColumnNameLike (like match)


The table also has two rows we need to Query for fields: 

  1. ALL (Ie: all fields) 
  2. Customer (or whatever table you’re working on, for example, Vendor or ItemFixedAsset)


We'll use an array for each so that's two arrays.


Next, we need to parse the return string from DLookup because we’re adding strings and separating them with commas. For example, under ColumnNameLike and row ALL, the return string is: “Guid, Edit, Currency, Parent”.


We parse this string into:


                Guid

                Edit

                Currency

                Parent


Then we compare each string to the control name. Remember, for this to work, use field names as control names. That way you can loop through controls and use DLookup on the schema table to see if the control is a field and then do something with it.


If the control name is LIKE or EQUAL TO one of the strings retrieved from DLookup (ie.: Guid, Edit, etc. above), then the control is an Update Exception, in other words, the control field does not honour the Schema table updateable Value.


The strings we extracted from DLookup require another array.


That's three arrays for this function:


  1. Columns: sColumn(i)
  2. Rows: sRow(j)
  3. Split strings: aryResult(k)


The blnUpdateException function is actually short, albeit strange, without all the notations and declarations.


I left the debug.print statements in as comments. If you want to see the process in action, remove the apostrophes from all the debug.print statements.


Function blnUpdateException(QBTable As String, sFieldName As String) As Boolean
On Error GoTo err
'set blnUpdateException to true to begin
blnUpdateException = True
Dim sResult As String, aryResult() As String, sRow(), sColumn()
Dim i As Integer, j As Integer, k As Integer, s As String
'create an array for the rows: ALL and QBTAble (ie.: customer, vendor, etc.)
sRow = Array("QBTable='ALL'", "QBTable='" & QBTable & "'")
'create an array for the columns: match and like match
sColumn = Array("ColumnName", "ColumnNameLike")
'loop through the columns first
'Debug.Print "Looking for: " & sFieldName
For i = 0 To UBound(sColumn)
'then loop through the rows
For j = 0 To UBound(sRow)
'retrieve the record for the column and row
sResult = Nz(DLookup(sColumn(i), "UpdateExceptions", sRow(j)))
'create an array to hold the split results (using commas)
aryResult = Split(sResult, ",")
'Debug.Print "-------------------"
'Debug.Print "DLookup returned: " & UBound(aryResult) + 1 & " words for Column: " & sColumn(i) & ", Row " & Replace(sRow(j), "QBTable=", "")
'Debug.Print
'loop through the array of split results
For k = 0 To UBound(aryResult)
'create a criteria string for the DLookup statement
'for example:  QBTable='vendor' AND ColumnName='IsTaxAgency'
s = sRow(j) & " AND " & sColumn(i) & "='" & sResult & "'"
'if sColumn is ColumnName (exact match) and
'the split result exactly matches the field name (control name) then
'look up the updateable value for that record
'Debug.Print k & ". " & Trim(aryResult(k)),
If sColumn(i) = "ColumnName" And Trim(aryResult(k)) = sFieldName Then
blnUpdateException = DLookup("Updateable", "UpdateExceptions", s)
'Debug.Print "**EXACT MATCH!"
Exit For
'if sColumn is ColumnNameLike (like match) and
'the split result is contained in the field name (control name) then
'look up the updateable value for that record
ElseIf sColumn(i) = "ColumnNameLike" And InStr(1, sFieldName, Trim(aryResult(k)), vbTextCompare) > 0 Then
blnUpdateException = DLookup("Updateable", "UpdateExceptions", s)
'Debug.Print "**LIKE MATCH!"
Exit For
Else
'Debug.Print
End If
Next k 'split result
If blnUpdateException = False Then
Exit For
Else
'Debug.Print "no match"
End If
Next j 'row
If blnUpdateException = False Then Exit For

Next i 'column
Exit Function
err:
If err.Number = 94 Then Resume Next
If err.Number = 3078 And err.Description Like "*cannot find*updateexceptions*" Then
ExceptionsTable
Resume
End If
Debug.Print Erl, err.Number, err.Description
Resume Next
End Function


Test the Function


To test the above function, type a few Call Statements into the Immediate Window. The return value will be True if the control is Updateable (not an exception) and False if the control is not Updateable (is an exception). I know this sounds a bit convoluted, but it works.


For example, we know IsTaxAgency (as of this writing in QuickBooks® Premier Contractor 2016) is not updateable in the vendor table. You can write an SQL update string and try to update it but nothing happens. We don’t want users to think they can update IsTaxAgency so we add it to our UpdateExceptions table.


To test the blnUpdateException Function on the vendor table, we need the vendor schema table.


Since this is Part 2, you should already have the Function ImportSchemaTable so call it now from the Immediate Window.



Now test the blnUpdateException function by typing some statements in the Immediate window. That's what I did and below are the results. 



The statement above returned False because the function checked the UpdateExceptions table and found IsTaxAgency so no matter what the schema table says, the Updateable value of IsTaxAgency is False as far as the database is concerned.



The statement above returned True because Name is updateable and doesn't exist in the UpdateExceptions table.



The statement above returned True because Name is Updateable in the customer Table.



The statement above returned False because “classref” is not Updateable in the customer table so we added it to the UpdateExceptions table.


You can see a youtube video of the update exceptions table in action here: https://www.youtube.com/watch?v=w7QoxJhKSU0&t=24s or in the video below.



Insert the blnUpdateException Function Call Statement


Now that you have a working function that returns update exceptions, you need to incorporate it into the function that retrieves update values from Schema tables.


Find the Procedure: DisableNonUpdateableFields.


You wrote this Procedure in Part 1 of this 2 Part series.


Copy this statement:


If blnUpdateException(QBTableName, ctl.Name) = False Then ctl.Enabled = False


Paste the statement between these two lines (160 and 170 if you didn’t change the line numbers from Part 1):



How to Find Update Exceptions


Any time you try to update a record and get an error, run the SQL Statement in VB Demo (that comes with QODBC). 


In your update procedure, right before the update, insert a debug.print statement to print the update SQL in the immediate window. You can keep an apostrophe in front of this statement and remove it when you need to see the update SQL.


If you run the SQL in VBDemo and still get an error and your SQL is constructed properly, delete fields from the SQL Statement until you no longer get an error. That tells you the last field you deleted from the SQL Statement was at fault. Simply add it to the UpdateExceptions Table with an Updateable Value of zero so it’s disabled on the form.


Here's something else you can do with this function. If you don’t want users to change data in certain fields, add those fields to the UpdateExceptions table as well. If users don’t have access to tables, or at least the UpdateExceptions table, this works great.


Summary


Some advantages of using VBA to disable non-updateable fields when forms open are:


  • No hard coding for each individual non-updateable field.
  • No error trapping for non-updateable fields.
  • You can construct update SQL by looping through updateable controls.
  • Users can't change non-updateable data because those controls are disabled.
  • You can keep users from updating any field by adding it to the UpdateExceptions table.
  • If QuickBooks adds new fields or changes existing fields' updateable values, the form will reflect this so long as the schema table is correct. If the schema table is not correct or the field is only updateable under certain conditions, add it to the Update Exceptions table.


Remember, this method works for these list tables:


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


Item tables other than ItemFixedAsset require additional functions, some of them available in my 2017 book.



0
1,851 Views
Annaliese DellSec-Treas
QODBC and tech tips

Comments (1)

Annaliese DellSec-Treas

Author

Commented:
Hi Andrew! Thank you for your kind words and for editing the article. I don't know how I got along without QODBC in the offce. It would take volumes to document all the things I do with it but at least a few articles about the simple things might help a few people.

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.