Access JumpStart 2.0 | Blog

A Rapid Development Framework for Microsoft Access

I have not written anything for a week. Bad me. So, the nice thing about testing is that I was able to fire up my tests and run them and I see right where I was working when I left off last time.

Continuing from last time, I am going to add the same form getting functions (which allow me to substitute a test form getting object where I can just set the values in the test. I already did that with the main class I was testing, but the test still couldn’t pass due to another dependency in the LineControlManager class. I will add the new functions to this class as well so I can complete the test and get it to pass.

I just got it passing. Here is the code:

The Test

'@TestMethod("POLineController")
Private Sub GivenConcreteLine_WhenNothingOrderedAndSomethingUsed_ThenLineIsValid()
    On Error GoTo TestFail
    Dim LineController As ECI_POLineController
    Set LineController = New ECI_POLineController
    Dim testDictionary As New Scripting.Dictionary
    testDictionary.Add "Phase_Number", "10"
    testDictionary.Add "Item_Description", "Test Description"
    testDictionary.Add "Cost_Type_ID", "2"
    testDictionary.Add "Qty_Ordered", "10"
    testDictionary.Add "Qty_Used", "10"
    testDictionary.Add "Unit_of_Measure", "EA"
    testDictionary.Add "Taxable", "True"
    Dim frmGet As New FormValueGetter_Test
    Set frmGet.FieldValues = testDictionary
    Set LineController.frmGet = frmGet
    
    Assert.AreEqual True, LineController.IsLineValid

TestExit:
    Exit Sub
TestFail:
    Assert.Fail "Test raised an error: #" & Err.Number & " - " & Err.Description
    Resume TestExit
End Sub

The ECI_POLineController applicable code

' In the declarations section at the top this variable was added:
Private m_objfrmGet As FormValueGetterI

' The function being tested is IsLineValid, following are the support functions for IsLineValid
Public Function IsLineValid() As Boolean
    IsLineValid = IsPhaseValid _
            And IsItemDescriptionValid _
            And IsQtyValid _
            And IsUnitOfMeasureValid And IsCostTypeValid And IsTaxableValid
End Function

Private Function IsPhaseValid() As Boolean
    IsPhaseValid = Not IsNull(thisFormGet("Phase_Number")) And thisFormGet("Phase_Number") <> "" And thisFormGet("Phase_Number") <> 0
End Function

Private Function IsItemDescriptionValid() As Boolean
    IsItemDescriptionValid = Not IsNull(thisFormGet("Item_Description")) And thisFormGet("Item_Description") <> ""
End Function

Private Function IsQtyValid() As Boolean
    Dim retVal As Boolean
    If LineControlManager.LineIsConcrete Then
        retVal = IsQtyOrderedValid Or IsQtyUsedValid
    Else
        retVal = IsQtyOrderedValid
    End If
    IsQtyValid = retVal
End Function

Private Function IsQtyOrderedValid() As Boolean
    IsQtyOrderedValid = Not IsNull(thisFormGet("Qty_Ordered")) And thisFormGet("Qty_Ordered") <> "" And thisFormGet("Qty_Ordered") <> 0
End Function

Private Function IsQtyUsedValid() As Boolean
    IsQtyUsedValid = Not IsNull(thisFormGet("Qty_Used")) And thisFormGet("Qty_Used") <> "" And thisFormGet("Qty_Used") <> 0
End Function

Private Function IsUnitOfMeasureValid() As Boolean
    IsUnitOfMeasureValid = Not IsNull(thisFormGet("Unit_of_Measure")) And thisFormGet("Unit_of_Measure") <> ""
End Function

Private Function IsCostTypeValid() As Boolean
    IsCostTypeValid = IsNull(thisFormGet("Cost_Type_ID")) = False
End Function

Private Function IsTaxableValid() As Boolean
    IsTaxableValid = IsNull(thisFormGet("Taxable")) = False
End Function

' This function is what allowed us to break the form dependency for testing
' Formerly, the IsLineValid code was checking form values directly.
' Here we set the FormValueGetterI object to the live version which looks
'  at the form if it's not already set.  This gives us an insertion point at which we
'  can use a setter to use our test FormValueGetter
Private Function thisFormGet(FieldName As String) As Variant
    Dim retVal As Variant
    If m_objfrmGet Is Nothing Then Set m_objfrmGet = New FormValueGetter_orderlineitemsForm
    retVal = m_objfrmGet.ReadFormValue(FieldName)
    thisFormGet = retVal
End Function

' This function is only run by the test harness during testing
Public Property Set frmGet(ByVal objNewValue As FormValueGetterI)
    Set m_objfrmGet = objNewValue
    If LineControlManager Is Nothing Then Set LineControlManager = New ECI_PoLineControlManager
    Set LineControlManager.frmGet = objNewValue
End Property

Additional code changes in ECI_PoLineControlManager

' This is just mainly copied code from the former object, with a slight modification to the
'  Setter to only set this object's getter.
Private m_objfrmGet As FormValueGetterI

Private Function thisFormGet(FieldName As String) As Variant
    Dim retVal As Variant
    If m_objfrmGet Is Nothing Then Set m_objfrmGet = New FormValueGetter_orderlineitemsForm
    retVal = m_objfrmGet.ReadFormValue(FieldName)
    thisFormGet = retVal
End Function

Public Property Set frmGet(ByVal objNewValue As FormValueGetterI)
    Set m_objfrmGet = objNewValue
End Property

' And I changed the intersecting code for the test to use the getter here:
Public Function LineIsConcrete() As Boolean
   LineIsConcrete = Not LineIsNotConcrete
End Function

Public Function LineIsNotConcrete() As Boolean
   LineIsNotConcrete = Nz(thisFormGet("Cost_Type_ID"), 0) <> 2
End Function

FormValueGetterI

Option Compare Database
Option Explicit

Public Function ReadFormValue(FieldName As String) As Variant: End Function

FormValueGetter_orderlineitemsForm

Option Compare Database
Option Explicit

Implements FormValueGetterI

Private Function FormValueGetterI_ReadFormValue(FieldName As String) As Variant
    Dim retVal As Variant: retVal = Null
    If HALform.IsFormLoaded("order") Then
        retVal = Form_orders_line_items_subform(FieldName).Value
    End If
    FormValueGetterI_ReadFormValue = retVal
End Function

FormValueGetter_Test

Option Compare Database
Option Explicit

Implements FormValueGetterI

Private m_objFieldValues As Scripting.Dictionary

Private Function FormValueGetterI_ReadFormValue(FieldName As String) As Variant
    Dim retVal As Variant
    retVal = m_objFieldValues(FieldName)
    FormValueGetterI_ReadFormValue = retVal
End Function

Public Property Set FieldValues(ByVal objNewValue As Scripting.Dictionary): Set m_objFieldValues = objNewValue: End Property

So that got us to a new passing test and now we can create more tests for this particular case and we have a new interface we can use to put other classes under test by changing the live code to use FormValueGetterI objects instead of directly accessing the form. Yay!