Any Improvements to be made?

tmyers

Well-known member
Local time
Today, 12:00
Joined
Sep 8, 2020
Messages
1,091
I just wanted to post one of my modules that I successfully wrote from scratch with more or less no help for once and see how I did. This works exactly as I intended it to for committing essentially transactions to various reels of wire and solves an ongoing problem I had been having with committing the right transaction to the correct reel.

Are there any improvements I could make? Did I do something outright wrong that I should have done differently? Just looking for feedback to continue improving :giggle:

Code:
Public Sub CommitMultiCut(NoError As Boolean)
Dim DB                  As DAO.Database
Dim RS                  As DAO.Recordset
Dim RS2                 As DAO.Recordset
Dim Wrk                 As DAO.Workspace
Dim vMultiID            As Long
Dim vReelID             As Long
Dim vTicketID           As Long
Dim vCurrentLength      As Long
Dim vCutLength          As Long
Dim vCutNum             As Long
Dim TotalLength         As Long
Dim strsql              As String

On Error GoTo ErrHandler

'Get TicketID, create workspace and set recordsets
vTicketID = [Forms]![frmWireRoom]![TicketID]
Set DB = CurrentDB()
Set Wrk = DBEngine.Workspaces(0)
Set RS = CurrentDb.OpenRecordset("SELECT * FROM tblMultiConductorCut WHERE TicketID = " & vTicketID & "")

With RS
    Wrk.BeginTrans
        Do While Not .EOF
            If !MultiComplete = True Then
            'if cut is already flagged as complete, skip to prevent double dipping
                .MoveNext
            Else
                vMultiID = ![MultiID]
                vReelID = ![WireReelID]
                vCutLength = ![CutLength]
                vCutNum = ![CutNum]
                If IsNull(vCutNum) Then
                    TotalLength = vCutLength
                Else
                    TotalLength = vCutLength * vCutNum
                End If
             
                Set RS2 = CurrentDb.OpenRecordset("SELECT * FROM tblWireRoom WHERE [ReelID] = " & vReelID & "")
                'Update the wire reel to reflect the cut
                With RS2
                    'make sure we are working on the correct reel
                    If ![ReelID] = vReelID Then
                        RS2.Edit
                        vCurrentLength = ![CurrentLength]
                        RS2!CurrentLength = vCurrentLength - TotalLength
                        RS2.Update
                    End If
                 
                End With
             
                With RS
                    'once again make sure we havent deviated from the current record for whatever reason
                    If ![MultiID] = vMultiID Then
                        RS.Edit
                        ![MultiComplete] = True
                        RS.Update
                    End If
                 
                End With
             
                 
                'run query to log cut to audit table using the DAO method
                strsql = "INSERT INTO tblCutLog ( CutReelID, StartingLength, CutLength, EndLength, TicketID) "
                strsql = strsql & "VALUES (" & vReelID & ", " & vCurrentLength & ", " & TotalLength & ", " & vCurrentLength - TotalLength & ", " & vTicketID & ");"
                CurrentDb.Execute strsql, dbFailOnError
             
                .MoveNext
            End If
        Loop
    Wrk.CommitTrans
    NoError = True
End With
Exit Sub

ErrHandler:
NoError = False
    Select Case Err.Number
     
        Case 3317
            'one of the choosen reels did not have enough length
            MsgBox "One of the choosen source(s) has insufficient length. Please choose a different source. Operation has been canacelled and no changes have been made", vbOKOnly, "Error"
            Wrk.Rollback
            NoError = False
            Exit Sub
         
        Case Else
            MsgBox Err.Description, vbOKOnly, Err.Number
         
     End Select

End Sub
 
Last edited:
Code:
Dim MID         As Long     'Variable for MultiID
Dim RID         As Long     'Variable for ReelID
Dim TID         As Long     'Variable for TicketID
[...]
If you already had the feeling that these very short, non-descript variable names require an explanation, you could have just named them:
Code:
Dim MultiId   As Long
Dim ReelId    As Long
Dim TicketId  As Long
[...]
The same applies to the other variables in the list.
I only had a short glance over the rest of the code, but it's very obvious that its readability would hugely benefit from these more meaningful variable names.
 
As this was one of my first ventures into DAO without seeking help I wasn't sure how it would behave if I started naming my variables the same as the fields themselves. If that doesn't cause issues, I will most certainly change it.

Actually, I will make the change regardless and just add a lowercase v to the start to delineate between the field and the variable.
 
Code:
Set RS2 = CurrentDb.OpenRecordset("SELECT * FROM tblWireRoom WHERE [ReelID] = " & RID & "")
Where does RID above get a value?

Code:
If !MultiComplete = True Then
            'if cut is already flagged as complete, skip to prevent double dipping
                .MoveNext
            Else
If I saw it correctly, the records with MultiComplete=True are not processed.
Why are they included in the data source?


Code:
'Update the wire reel to reflect the cut
                With RS2
                    'make sure we are working on the correct reel
                    If ![ReelID] = RID Then
Here I miss the connection between RS and RS2. RS2 will always be empty in my opinion - unless there is ReelID = 0.
 
I just noticed when I moved setting the second recordset higher up before posting that I moved it up to before I set that value.
Derp.
I moved it back down to just above where I work with said recordset.

For the second part, it is mostly due to the fact I know how to exclude them this way and would second guess myself writing it out in the SQL string. The recordsets I am dealing with a really tiny (typically less than 10) so I figured there wouldn't be any performance loss or gains by doing it this way.

For your third, I believe that was a result of my errant placement setting the 2nd recordset before I actually set the ReelID variable. It is what I get for just moving things for the sake of neatness.

I have edited the code in the OP to reflect its current state and changes to the variable names.
 
Code:
If ![ReelID] = RID Then
If this is now in the original code and did not trigger a compiler error, please add Option Explicit in the module header.

A small thing that does not matter with 10 data sets: Since CurrentDb is used several times, I would use a DAO.Database variable, then CurrentDb only needs to be created once.
Code:
dim db as DAO.Database
..
set db = CurrentDb
..
... = db.OpenRecordset

Note:
I look at the whole thing as a DAO exercise. I don't see any complex checks or calculations in the code that would prevent bulk processing of the data using SQL.
But maybe I'm missing something.


For consideration: outsource the code inside the recordset loop to an extra procedure. Could increase the readability.

Code:
With RS
    Wrk.BeginTrans
        Do While Not .EOF
            If !MultiComplete = True Then
            'if cut is already flagged as complete, skip to prevent double dipping
                 ' do nothing (movenext after end if)
            Else
                vMultiID = ![MultiID]
                vReelID = ![WireReelID]
                vCutLength = ![CutLength]
                vCutNum = ![CutNum]
                If IsNull(vCutNum) Then
                    TotalLength = vCutLength
                Else
                    TotalLength = vCutLength * vCutNum
                End If
             
               CutWire vReelID, TotalLength  ' find a better name ;)

               'once again make sure we havent deviated from the current record for whatever reason
               If ![MultiID] = vMultiID Then
                   .Edit
                   ![MultiComplete] = True
                   .Update
                End If
                 
                'run query to log cut to audit table using the DAO method  
                LogCutToAuditTable  vReelID, vCurrentLength, TotalLength, vCurrentLength - TotalLength, vTicketID
           
            End if

            .MoveNext
        Loop
    Wrk.CommitTrans
    NoError = True
End With
 
Last edited:
I just ran a check and that first one got flagged (yay option explicit) where I missed it when renaming all my variables per Sonics suggestion.

I didn't notice that with CurrentDB and honestly didnt know I could do that. I will make that change :). I did notice that in one form or another, I reuse these variables a lot so now plan to go through my entire file and make them global.

I originally had tried to do this whole operation with queries, but kept running into problem after problem so decided to make it an exercise in writing out a module using DAO.
 
I didn't notice that with CurrentDB and honestly didnt know I could do that. I will make that change :). I did notice that in one form or another, I reuse these variables a lot so now plan to go through my entire file and make them global.
I would be careful with gobal variables.
 
That is fair. I already am going to backtrack on that as just glancing through all my modules, it would be quite the pain to make that change at this point.
 
Stylewise:
1. I don't use With x when working with multiple objects like recordsets. It is just too confusing when reading the code as to which object the code refers to. rs and rs2 are short enough that you can type the extra characters for clarity.
2. I don't create intermediate variables to move data from one recordset to another. rs2!fldA = rs!fldA works just fine. Is obvious and shortens the code. Using an intermediate field means the reader is never really sure of the source of the from value.
 
Could the With block be removed?
They are not required. They are used as a shortcut. If you have a vvvvvvvvvveeeeeeeeeeeeeeeerrrrrrrrrrryyyyyyyyyLong Recordset name, no one wants to have to keep typing that so the With is a way of substituting a ! for the name. And that's fine if the names are exceptionally long but no one forces you to create long names for this type of object. Also, if there is only one object you are using a With for in any procedure, there is no confusion but if i'm reading code and I see !somename in a procedure that uses multiple With clauses, I have to translate that to somerecordset!somename by reading backwards through the code to find the controlling With statement. Easy to get to the wrong one. Today, you remember which fields are in which recordset but how about next month or next year.

So, to summarize; I use short rs names and I never use With, if I have multiple objects I am working with at the same time to avoid confusion.
 
I present a refactoring for discussion:
Code:
Public Sub CommitMultiCut(ByRef NoError As Boolean)  ' I don't like the NoError parameter

    CommitTicketMultiCut [Forms]![frmWireRoom]![TicketID], NoError

End Sub

Public Sub CommitTicketMultiCut(ByVal vTicketID As Long, ByRef NoError As Boolean)

    Dim DB                  As DAO.Database
    Dim Wrk                 As DAO.Workspace
    Dim TicketSql           As String
    Dim TotalCutLength      As Long

On Error GoTo ErrHandler

    Set DB = CurrentDb()
    Set Wrk = DBEngine.Workspaces(0)

    TicketSql = "SELECT * FROM tblMultiConductorCut WHERE TicketID = " & vTicketID
     'if cut is already flagged as complete, skip to prevent double dipping
    TicketSql = TicketSql & " and MultiComplete = False"

    Wrk.BeginTrans ' ... before or after OpenRecordset?

    With DB.OpenRecordset(TicketSql, dbOpenDynaset)

        Do While Not .EOF

            TotalCutLength = !CutLength * Nz(!CutNum, 1)
            CutWireReel DB, vTicketID, !WireReelID, TotalCutLength
   
            .Edit
            ![MultiComplete] = True
            .Update
   
            .MoveNext
        Loop
        .Close
    End With

    Wrk.CommitTrans

    NoError = True

ExitHere:
Exit Sub

ErrHandler:
NoError = False
    Select Case Err.Number

        Case 3317
            'one of the choosen reels did not have enough length
            Wrk.Rollback ' Close transaction before MsgBox (timing / locking)
            MsgBox "One of the choosen source(s) has insufficient length. Please choose a different source. Operation has been canacelled and no changes have been made", vbOKOnly, "Error"
       
            NoError = False
            Resume ExitHere

        Case Else
            ' Rollback? / Commit?
            MsgBox Err.Description, vbOKOnly, Err.Number

     End Select

End Sub

Private Sub CutWireReel(ByVal DB As DAO.Database, ByVal vTickedID As Long, ByVal vReelID As Long, ByVal LengthToCut As Long)

    Dim vStartingLength As Long

    With DB.OpenRecordset("SELECT * FROM tblWireRoom WHERE [ReelID] = " & vReelID, dbOpenDynaset)
        vStartingLength = ![CurrentLength]
        .Edit
        !CurrentLength = StartingLength - LengthToCut
        .Update
        .Close
    End With

    LogCutToAuditTable DB, vTicketID, vReelID, vStartingLength, LengthToCut

End Sub

Private Sub LogCutToAuditTable(ByVal DB As DAO.Database, ByVal TickedID As Long, ByVal CutReelID As Long, _
                               ByVal StartingLength As Long, ByVal CutLength As Long)
    Dim InsertSql As String

    InsertSql = "INSERT INTO tblCutLog ( CutReelID, StartingLength, CutLength, EndLength, TicketID)" & _
                " VALUES (" & CutReelID & ", " & StartingLength & ", " & CutLength & ", " & StartingLength - CutLength & ", " & TickedID & ");"

    DB.Execute InsertSql, dbFailOnError

End Sub


Note: Do not forget to close opened recordsets.
 
Last edited:
It appears you originally had a variable called MID. Mid is a function name and should never be used as a variable. Avoid using reserved words for anything.

Values should be passed to functions via parameters, not though Global Variables. Study the programming concept of Encapsulation.

Parameters should always be explicitly declared as ByVal or ByRef.
 
I also wouldn't keep running an insert query for the third table. Just keep a recordset open to the third table and use .AddNew to insert the rows. Remember, every time you run a query created in VBA, you are forcing Access to compile it and calculate an execution plan. That is totally unnecessary overhead in this context ESPECIALLY within a loop. If the loop processes 10 records, who cares. If it processes 10,000 rows, YOU care!!
 
I also wouldn't keep running an insert query for the third table. Just keep a recordset open to the third table and use .AddNew to insert the rows. Remember, every time you run a query created in VBA, you are forcing Access to compile it and calculate an execution plan. That is totally unnecessary overhead in this context ESPECIALLY within a loop. If the loop processes 10 records, who cares. If it processes 10,000 rows, YOU care!!
@Pat Hartman I have a linked table to sql server with more than 2 million records. On a click event of a button, I create an INSERT statement in a loop to add 10 to 120 records. (The count depends on a lot of factors)
I thought opening a recordset that huge may have some impact on performance, so I chose the insert method.
Do you think it's better to change it to opening a recordset and use AddNew?

thank you.
 
May I ask why using ByRef explicitly when the default is ByRef?
It makes it clear to anyone looking at the code that the intent is to send information back through the parameter without having to locate every mention of it in the code to see whether or not it is affected.

If the parameter is only for input then it is best to declare it ByVal (on applicable types) as this makes that intent obvious.

Personally I would use a Function rather than a Sub so it is obvious that the exit code is being returned. I only use parameters for output when I need to return more than one piece of information.
 
I have a linked table to sql server with more than 2 million records. On a click event of a button, I create an INSERT statement in a loop to add 10 to 120 records. (The count depends on a lot of factors)
I thought opening a recordset that huge may have some impact on performance, so I chose the insert method
You could base the recordset on a query that excludes existing the records.

I would expect the RecordsetOption dbAppendOnly to not return records but I'm not completely sure of that.

Remember, every time you run a query created in VBA, you are forcing Access to compile it and calculate an execution plan.
An alternative would be running a parameterised stored query from VBA rather than building a whole query in VBA on each loop. Though that might be swapping one kind of overhead for another.

I have not looked at the code but generally it is rare that a query would not be able to do the whole job in one hit. Using recordsets and loops is best avoided if possible.
 
It makes it clear to anyone looking at the code that the intent is to send information back through the parameter without having to locate every mention of it in the code to see whether or not it is affected.

You could base the recordset on a query that excludes existing the records.

I would expect the RecordsetOption dbAppendOnly to not return records but I'm not completely sure of that.
@Galaxiom thanks for solving the mysteries.
 

Users who are viewing this thread

Back
Top Bottom