Consulting

Results 1 to 15 of 15

Thread: Translating Excel formula into VBA code

  1. #1

    Translating Excel formula into VBA code

    Hey everybody,

    I am trying to translate the following array formula into a code but it does not seem to work:

    {=MIN(IF($C$5:$C$24216=$C23;IF($AL$5:$AL$24216="Apples";$AC$5:$AC$24216)))}

    C$24216, $AL$24216, and AC$24216 should be of course flexible, as the lastrow varies accordingly.

    Could you please give me a hint how to do it? my VBA knowledge is kind of poor..

    Thanks a lot!

  2. #2
    Why translating ?

  3. #3
    I meant to write the formula as a VBA code, keeping in mind that the last rows vary..

  4. #4
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Dim lastrow As Long
    
        With ActiveSheet
        
            lastrow = .Cells(.Rows.Count, "C").End(xlUp).Row
            MsgBox .Evaluate("MIN(IF($C$5:$C$" & lastrow & "=$C23,IF($AL$5:$AL$" & lastrow & "=""Apples"",$AC$5:$AC$" & lastrow & ")))")
        End With
    But why? Formulas are more efficient.
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

  5. #5
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    You could also do a UDF

    Public Function MinValue( _
        ByVal rngTest As Range, _
        ByVal testCell As Range, _
        ByVal rngFruit As Range, _
        ByVal rngValues As Range) As Double
    Dim lastrow As Long
    
        With ActiveSheet
        
            lastrow = .Cells(.Rows.Count, rngTest.Column).End(xlUp).Row
            Set rngTest = rngTest.Resize(lastrow)
            Set rngFruit = rngFruit.Resize(lastrow)
            Set rngValues = rngValues.Resize(lastrow)
            MinValue = .Evaluate("MIN(IF(" & rngTest.Address & "=" & testCell.Address & ",IF(" & rngFruit.Address & "=""Apples""," & rngValues.Address & ")))")
        End With
    End Function
    and call from the sheet like so
    =MinValue(C5,C23,AL5,AC5)
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

  6. #6
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,730
    Location
    @XLD - I think that if rngTest = C5, and there is only data to (say) C10 then

    Set rngTest = rngTest.Resize(lastrow)
    returns a range of C5:C14, not C5:C10



    @vio.comam --

    Another way is a sub to put the values instead of formula. I had to add another parameter to say where to put the results (A5 in the example) and for good measure since there's a lot of fruits, I decided to pass that as a second parameter

    There some error protection and checks that would make this more robust

    Option Explicit
    Sub test()
        Call MinValues(Range("A5"), "Apples", Range("C5"), Range("C23"), Range("AL5"), Range("AC5"))
    End Sub
    
    Public Sub MinValues( _
        rngDest As Range, _
        strFruit As String, _
        rngTest As Range, _
        testCell As Range, _
        rngFruit As Range, _
        rngValues As Range)
        
        Dim lastrow As Long
         
        With ActiveSheet
             
            lastrow = .Cells(.Rows.Count, rngValues.Column).End(xlUp).Row
            Set rngTest = rngTest.Resize(lastrow - rngTest.Row + 1)
            Set rngFruit = rngFruit.Resize(lastrow - rngFruit.Row + 1)
            Set rngValues = rngValues.Resize(lastrow - rngValues.Row + 1)
            
            rngDest.FormulaArray = "=MIN(IF(" & rngTest.Address & "=" & testCell.Address & ",IF(" & rngFruit.Address & "=""" & strFruit & """," & rngValues.Address & ")))"
            rngDest.Value = rngDest.Value ' comment out for formula
            
        End With
    End Sub
    Attached Files Attached Files
    Last edited by Paul_Hossler; 10-26-2016 at 06:18 AM. Reason: used prelim ver of file
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  7. #7
    Thanks a lot guys!

    I am now having the issue that in the line MIN(IF($C$5:$C$" & lastrow & "=$C23 does not move along with the rows.

    That is, I am getting
    $C23 all along the way regardless I am in row 23 or some other row...

    Any ideas? thanks!

  8. #8
    Thanks Paul,

    I am having the problem that the code writes the result into the first cell only, without moving down in the column...

    Regards

  9. #9
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,730
    Location
    In


    {=MIN(IF($C$5:$C$24216=$C23;IF($AL$5:$AL$24216="Apples";$AC$5:$AC$24216)))}

    All the ranges had fixed rows and fixed columns, except $C23, so I put results into just A5



    Call MinValues(Range("A5"), "Apples", Range("C5"), Range("C23"), Range("AL5"), Range("AC5"))
    Going by my attachment which had data in just rows 5-10, do you want (say)


    a. -- A5:A10 to have the same fixed cells EXCEPT A5 use C23, A6 use C24, A7 use C25, etc.?

    b. -- A5:A10 to have the same fixed value cells and all using C23?
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  10. #10
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,730
    Location
    If you're looking for this (which seems more likely to my guessing ...)

    a. -- A5:A10 to have the same fixed cells EXCEPT A5 use C23, A6 use C24, A7 use C25, etc.?
    which gives this


    Capture.JPG


    Let me know, or of course you could use the UDF approach which also has some advanages


    Option Explicit
    
    Sub test()
        Call MinValues(Range("A5"), "Apples", Range("C5"), Range("C23"), Range("AL5"), Range("AC5"))
    End Sub
    
    Public Sub MinValues( _
        rngDest As Range, _
        strFruit As String, _
        rngTest As Range, _
        testCell As Range, _
        rngFruit As Range, _
        rngValues As Range)
        
        Dim lastrow As Long
        Dim sFormula As String
         
        With ActiveSheet
             
            lastrow = .Cells(.Rows.Count, rngValues.Column).End(xlUp).Row
            Set rngDest = rngDest.Resize(lastrow - rngTest.Row + 1)
            Set rngTest = rngTest.Resize(lastrow - rngTest.Row + 1)
            Set rngFruit = rngFruit.Resize(lastrow - rngFruit.Row + 1)
            Set rngValues = rngValues.Resize(lastrow - rngValues.Row + 1)
            
            sFormula = "=MIN(IF(" & rngTest.Address(True, True) & _
                "=" & testCell.Address(False, True) & _
                ",IF(" & rngFruit.Address(True, True) & _
                "=""" & strFruit & """," & _
                rngValues.Address(True, True) & _
                ")))"
            
            'msgbox sformula
            
            rngDest.Cells(1, 1).FormulaArray = sFormula
            rngDest.Cells(1, 1).AutoFill Destination:=rngDest, Type:=xlFillDefault
            rngDest.Value = rngDest.Value
            
        End With
    End Sub

    VBX_Example_2.xlsm
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  11. #11
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Quote Originally Posted by Paul_Hossler View Post
    @XLD - I think that if rngTest = C5, and there is only data to (say) C10 then

    Set rngTest = rngTest.Resize(lastrow)
    returns a range of C5:C14, not C5:C10
    You are right of course, but it is worse than that as the check cell is C23. So as well as taking the first data row off the resize I think it should use the values column to calculate last row.
    ____________________________________________
    Nihil simul inventum est et perfectum

    Abusus non tollit usum

    Last night I dreamed of a small consolation enjoyed only by the blind: Nobody knows the trouble I've not seen!
    James Thurber

  12. #12
    Thanks Paul!

    I've uploaded the original file in which I am gonna be using the code.

    The result of the code "as-is" in visible in column BF, whereas the result "to-be" is visible in column BK.
    Something is still not working properly in the code I guess, as it does not lead to the same result as if I would do it by using the formula in column BK.
    For the sake of understanding the example, the results in column BK have the formula behind, however the code should deliver only values in date format.

    Do you think you can have a look?

    Thanks a lot!
    Attached Files Attached Files

  13. #13
    A pivottable:
    Attached Files Attached Files

  14. #14
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,730
    Location
    The call was wrong, parameters out of order and AL5 instead of AL2


    Call MinValues(Range("BF2"), "Maintenance", Range("C2"), Range("C2"), Range("AL5"), Range("AG2"))/

    Now that I had some real data to look at, I could simplify the calling sequence, and use more meaningful variable names


    Try this version, but format BF as 'Date' in number formatting


    Option Explicit
    Sub test2()
        Call MinValues(Range("BF2"), "Maintenance", Range("C2"), Range("AG2"), Range("T2"))
    End Sub
    
    Public Sub MinValues( _
        rGrandStartDates As Range, _
        sServiceDescription As String, _
        rContracts As Range, _
        rServiceDescriptions As Range, _
        rStartDates As Range)
         
        Dim lastrow As Long
        Dim sFormula As String
        Dim rContract As Range
         
        With ActiveSheet
             
            lastrow = .Cells(.Rows.Count, rStartDates.Column).End(xlUp).Row
            Set rGrandStartDates = rGrandStartDates.Resize(lastrow - rGrandStartDates.Row + 1)
            Set rContracts = rContracts.Resize(lastrow - rContracts.Row + 1)
            Set rContract = rContracts.Cells(1, 1)
            
            Set rServiceDescriptions = rServiceDescriptions.Resize(lastrow - rServiceDescriptions.Row + 1)
            Set rStartDates = rStartDates.Resize(lastrow - rStartDates.Row + 1)
             
            sFormula = "=MIN(IF(" & rContracts.Address(True, True) & _
            "=" & rContract.Address(False, True) & _
            ",IF(" & rServiceDescriptions.Address(True, True) & _
            "=""" & sServiceDescription & """," & _
            rStartDates.Address(True, True) & _
            ")))"
             
            rGrandStartDates.Cells(1, 1).FormulaArray = sFormula
            rGrandStartDates.Cells(1, 1).AutoFill Destination:=rGrandStartDates, Type:=xlFillDefault
            rGrandStartDates.Value = rGrandStartDates.Value
             
        End With
    End Sub
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  15. #15
    Thanks a lot Paul, it works perfectly now! ;-)

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •