Consulting

Results 1 to 9 of 9

Thread: Complex IF Formula Errors as VBA Code

  1. #1
    VBAX Regular
    Joined
    Nov 2011
    Posts
    7
    Location

    Complex IF Formula Errors as VBA Code

    Hello! I sincerely appreciate any help as I'm just stuck. When I record the following formula, and the code is written, the macro will error out.

    System:
    Running MAC OSX
    Excel 2004 for Mac

    Formula to input into G24:
    HTML Code:
    =G26+IF(OR(H38={"Reg Photo Paper","Matte Photo Poster","Moab","Giclee","Canvas","Reg Photo Paper ","Matte Photo Poster ","Moab ","Giclee ","Canvas "}),IF(G28=1,2,IF(G28=7,3,IF(G28={5,6},IF(G29="10pm",4,IF(OR(G29={"2pm","6am"}),3,0)),IF(OR(G28={2,3,4,5}),IF(G29="10pm",2,IF(OR(G29={"2pm","6am"}),1,0)),IF(AND(OR(G28={2,3,4,5}),OR(G29={"2pm","6am"})),1,0))))),IF(OR(H38={"Premium Photo Paper","Laminate","Premium Photo Paper ","Laminate "}),IF(G28=1,4,IF(G28=7,5,IF(OR(G28={4,5,6}),IF(OR(G29={"2pm","6am"}),5,IF(G29="10pm",6,0)),IF(OR(G28={2,3}),IF(G29="10pm",4,3),0)))),0))

    Output from recording:
    [VBA] Range("G24").Select
    ActiveCell.FormulaR1C1 = _
    "=R[2]C OR(R[14]C[1]={""Reg Photo Paper"",""Matte Photo Poster"",""Moab"",""Giclee"",""Canvas"",""Reg Photo Paper "",""Matte Photo Poster "",""Moab "",""Giclee "",""Canvas ""})""10pm"",4,IF(OR(R[5]C={""2pm"",""6am""}),3,0))"
    Range("G25").Select[/VBA]


    Error code when macro is run:
    Run-time error '1004'
    Method "formulaR1C1' of object 'Range' failed


    Are there any red flags with the code? The formula works great when input into a cell.

    Many thanks!

  2. #2
    VBAX Regular
    Joined
    Oct 2011
    Posts
    41
    Location
    Try it like this, inside a With grouping:

    Sub RunTheFormula()
    Dim myFormula As String
    Dim wks As Worksheet
    Dim LastRow As Long
    Set wks = Worksheets("Sheet1")
    Application.ScreenUpdating = False
    myFormula = "=R[2]C OR(R[14]C[1]={""Reg Photo Paper"",""Matte Photo Poster"",""Moab"",""Giclee"",""Canvas"",""Reg Photo Paper "",""Matte Photo Poster "",""Moab "",""Giclee "",""Canvas ""})""10pm"",4,IF(OR(R[5]C={""2pm"",""6am""}),3,0))"
    With wks
    'what to use to run formula on
    LastRow = .Cells(.Rows.Count, "A").End(xlUp).Row
    ' where to put the formula results
    .Range("F1:F" & LastRow).Formula = myFormula
    End With
    Application.ScreenUpdating = True
    End Sub

  3. #3
    VBAX Regular
    Joined
    Nov 2011
    Posts
    7
    Location
    Can you clarify for me the following:

    With wks
    'what to use to run formula on

    'where to put the formula results
    (would this be Range("G24").Select)

  4. #4
    VBAX Regular
    Joined
    Nov 2011
    Posts
    7
    Location
    Would it be helpful to post an example worksheet and the macro?

  5. #5
    VBAX Regular
    Joined
    Oct 2011
    Posts
    41
    Location
    I wasn't sure how you were actually using that formula, so I just dropped it into an existing sub I use which places the formula results in row F. It calculates the last row of data entered in A and then in row F puts in the formula.

    If you want that formula in G24, I think you'd change this part:

    With wks
    'what to use to run formula on
    .Range("G24").Formula = myFormula
    End With
    Can you display your whole Sub that has your formula in it after you recorded it?

  6. #6
    VBAX Regular
    Joined
    Nov 2011
    Posts
    7
    Location
    [VBA] ActiveWorkbook.SaveAs Range("A22").Value & ".xls"

    Range("G25").Select
    ActiveCell.FormulaR1C1 = ActiveWorkbook.BuiltinDocumentProperties.Item _
    ("Creation date").Value

    Range("F24").Select
    ActiveCell.FormulaR1C1 = "Due Date"
    Range("F25").Select
    ActiveCell.FormulaR1C1 = "Order Date"
    Range("F26").Select
    ActiveCell.FormulaR1C1 = "Create Date"
    Range("F27").Select
    ActiveCell.FormulaR1C1 = "Create Time"
    Range("F28").Select
    ActiveCell.FormulaR1C1 = "DOW"
    Range("F29").Select
    ActiveCell.FormulaR1C1 = "Drop Time"
    Range("G29").Select
    ActiveCell.FormulaR1C1 = _
    "=IF(R[-2]C>=15/23.99,""10pm"",IF(R[-2]C>=7/24,""2pm"",IF(R[-2]C>=0/23.99,""6am"")))"
    Range("G30").Select
    Range("G28").Select
    ActiveCell.FormulaR1C1 = "=WEEKDAY(R[-2]C)"
    Range("G27").Select
    ActiveCell.FormulaR1C1 = "=R[-2]C-INT(R[-2]C)"
    Range("G26").Select
    ActiveCell.FormulaR1C1 = "=INT(R[-1]C)"
    Range("F29:G29").Select
    With Selection.Interior
    .ColorIndex = 6
    .Pattern = xlSolid
    End With
    Range("F24:G24").Select
    With Selection.Interior
    .ColorIndex = 6
    .Pattern = xlSolid
    End With
    Range("G24:G29").Select
    Range("G29").Activate
    With Selection
    .HorizontalAlignment = xlRight
    .VerticalAlignment = xlBottom
    .WrapText = False
    .Orientation = 0
    .AddIndent = False
    .ShrinkToFit = False
    .MergeCells = False
    End With
    Range("G29").Select
    Selection.Font.Bold = True
    Range("G24").Select
    Selection.Font.Bold = True
    Range("E23:G30").Select
    Selection.Borders(xlDiagonalDown).LineStyle = xlNone
    Selection.Borders(xlDiagonalUp).LineStyle = xlNone
    Selection.Borders(xlEdgeLeft).LineStyle = xlNone
    Selection.Borders(xlEdgeTop).LineStyle = xlNone
    Selection.Borders(xlEdgeBottom).LineStyle = xlNone
    Selection.Borders(xlEdgeRight).LineStyle = xlNone
    Selection.Borders(xlInsideVertical).LineStyle = xlNone
    Selection.Borders(xlInsideHorizontal).LineStyle = xlNone
    Range("F24:G24").Select
    Selection.Interior.ColorIndex = 6
    Range("F29:G29").Select
    Selection.Interior.ColorIndex = 6
    Range("E22:G31").Select
    Selection.Borders(xlDiagonalDown).LineStyle = xlNone
    Selection.Borders(xlDiagonalUp).LineStyle = xlNone
    Selection.Borders(xlEdgeLeft).LineStyle = xlNone
    Selection.Borders(xlEdgeTop).LineStyle = xlNone
    Selection.Borders(xlEdgeBottom).LineStyle = xlNone
    Selection.Borders(xlEdgeRight).LineStyle = xlNone
    Selection.Borders(xlInsideVertical).LineStyle = xlNone
    Selection.Borders(xlInsideHorizontal).LineStyle = xlNone
    Range("G28").Select
    Selection.NumberFormat = "0"
    Range("G27").Select
    Selection.NumberFormat = "h:mm AM/PM"
    Range("G26").Select
    Selection.NumberFormat = "d-mmm-yy"
    Range("G25").Select
    Selection.NumberFormat = "m/d/yy h:mm"
    Range("G24").Select
    Selection.NumberFormat = "d-mmm-yy"
    Range("G24").Select
    Selection.Font.Bold = True
    Range("G24").Select
    Range("G25").Select
    ActiveWindow.SmallScroll Down:=-1
    Columns("G:G").ColumnWidth = 10
    Columns("G:G").EntireColumn.AutoFit

    Range("G24").Select
    ActiveCell.FormulaR1C1 = _
    "=R[2]C OR(R[14]C[1]={""Reg Photo Paper"",""Matte Photo Poster"",""Moab"",""Giclee"",""Canvas"",""Reg Photo Paper "",""Matte Photo Poster "",""Moab "",""Giclee "",""Canvas ""})""10pm"",4,IF(OR(R[5]C={""2pm"",""6am""}),3,0))"
    Range("G25").Select[/VBA]

    It's a little messy, but that's not my biggest concern right now. Thanks again, monarchd!

  7. #7
    VBAX Regular
    Joined
    Oct 2011
    Posts
    41
    Location
    This worked for me after adjusting the formula line:

    Option Explicit
    Sub Test()
    Range("G25").Select
    ActiveCell.FormulaR1C1 = ActiveWorkbook.BuiltinDocumentProperties.Item _
    ("Creation date").Value
     
    Range("F24").Select
    ActiveCell.FormulaR1C1 = "Due Date"
    Range("F25").Select
    ActiveCell.FormulaR1C1 = "Order Date"
    Range("F26").Select
    ActiveCell.FormulaR1C1 = "Create Date"
    Range("F27").Select
    ActiveCell.FormulaR1C1 = "Create Time"
    Range("F28").Select
    ActiveCell.FormulaR1C1 = "DOW"
    Range("F29").Select
    ActiveCell.FormulaR1C1 = "Drop Time"
    Range("G29").Select
    ActiveCell.FormulaR1C1 = _
    "=IF(R[-2]C>=15/23.99,""10pm"",IF(R[-2]C>=7/24,""2pm"",IF(R[-2]C>=0/23.99,""6am"")))"
    Range("G30").Select
    Range("G28").Select
    ActiveCell.FormulaR1C1 = "=WEEKDAY(R[-2]C)"
    Range("G27").Select
    ActiveCell.FormulaR1C1 = "=R[-2]C-INT(R[-2]C)"
    Range("G26").Select
    ActiveCell.FormulaR1C1 = "=INT(R[-1]C)"
    Range("F29:G29").Select
    With Selection.Interior
        .ColorIndex = 6
        .Pattern = xlSolid
    End With
    Range("F24:G24").Select
    With Selection.Interior
        .ColorIndex = 6
        .Pattern = xlSolid
    End With
    Range("G24:G29").Select
    Range("G29").Activate
    With Selection
        .HorizontalAlignment = xlRight
        .VerticalAlignment = xlBottom
        .WrapText = False
        .Orientation = 0
        .AddIndent = False
        .ShrinkToFit = False
        .MergeCells = False
    End With
    Range("G29").Select
    Selection.Font.Bold = True
    Range("G24").Select
    Selection.Font.Bold = True
    Range("E23:G30").Select
    Selection.Borders(xlDiagonalDown).LineStyle = xlNone
    Selection.Borders(xlDiagonalUp).LineStyle = xlNone
    Selection.Borders(xlEdgeLeft).LineStyle = xlNone
    Selection.Borders(xlEdgeTop).LineStyle = xlNone
    Selection.Borders(xlEdgeBottom).LineStyle = xlNone
    Selection.Borders(xlEdgeRight).LineStyle = xlNone
    Selection.Borders(xlInsideVertical).LineStyle = xlNone
    Selection.Borders(xlInsideHorizontal).LineStyle = xlNone
    Range("F24:G24").Select
    Selection.Interior.ColorIndex = 6
    Range("F29:G29").Select
    Selection.Interior.ColorIndex = 6
    Range("E22:G31").Select
    Selection.Borders(xlDiagonalDown).LineStyle = xlNone
    Selection.Borders(xlDiagonalUp).LineStyle = xlNone
    Selection.Borders(xlEdgeLeft).LineStyle = xlNone
    Selection.Borders(xlEdgeTop).LineStyle = xlNone
    Selection.Borders(xlEdgeBottom).LineStyle = xlNone
    Selection.Borders(xlEdgeRight).LineStyle = xlNone
    Selection.Borders(xlInsideVertical).LineStyle = xlNone
    Selection.Borders(xlInsideHorizontal).LineStyle = xlNone
    Range("G28").Select
    Selection.NumberFormat = "0"
    Range("G27").Select
    Selection.NumberFormat = "h:mm AM/PM"
    Range("G26").Select
    Selection.NumberFormat = "d-mmm-yy"
    Range("G25").Select
    Selection.NumberFormat = "m/d/yy h:mm"
    Range("G24").Select
    Selection.NumberFormat = "d-mmm-yy"
    Range("G24").Select
    Selection.Font.Bold = True
    Range("G24").Select
    Range("G25").Select
    ActiveWindow.SmallScroll Down:=-1
    Columns("G:G").ColumnWidth = 10
    Columns("G:G").EntireColumn.AutoFit
    With ActiveSheet
    Range("G24").Select
    ActiveCell.Formula = _
    "=G26+IF(OR(H38={""Reg Photo Paper"",""Matte Photo Poster"",""Moab"",""Giclee"",""Canvas"",""Reg Photo Paper "",""Matte Photo Poster "",""Moab "",""Giclee "",""Canvas ""}),IF(G28=1,2,IF(G28=7,3,IF(G28={5,6},IF(G29=""10pm"",4,IF(OR(G29={""2pm"",""6am""}),3,0)),IF(OR(G28={2,3,4,5}),IF(G29=""10pm"",2,IF(OR(G29={""2pm"",""6am""}),1,0)),IF(AND(OR(G28={2,3,4,5}),OR(G29={""2pm"",""6am""})),1,0))))),IF(OR(H38={""Premium Photo Paper"",""Laminate"",""Premium Photo Paper "",""Laminate ""}),IF(G28=1,4,IF(G28=7,5,IF(OR(G28={4,5,6}),IF(OR(G29={""2pm"",""6am""}),5,IF(G29=""10pm"",6,0)),IF(OR(G28={2,3}),IF(G29=""10pm"",4,3),0)))),0))"
    End With
    Range("G25").Select
    End Sub

  8. #8
    VBAX Regular
    Joined
    Nov 2011
    Posts
    7
    Location
    Wow! This is great! I knew the recorder was truncating my final formula but couldn't figure out how to code it myself. Thanks so very much for taking the time to figure this out. All best, Tucker.

  9. #9
    Administrator
    VP-Knowledge Base
    VBAX Grand Master mdmackillop's Avatar
    Joined
    May 2004
    Location
    Scotland
    Posts
    14,489
    Location
    The code above can be cleaned up a lot. Remove all selection; combine ranges with similar formatting.
    [VBA]Option Explicit
    Sub Test()
    Range("G25") = ActiveWorkbook.BuiltinDocumentProperties.Item _
    ("Creation date").Value

    Range("F24") = "Due Date"
    Range("F25") = "Order Date"
    Range("F26") = "Create Date"
    Range("F27") = "Create Time"
    Range("F28") = "DOW"
    Range("F29") = "Drop Time"
    Range("G29").FormulaR1C1 = _
    "=IF(R[-2]C>=15/23.99,""10pm"",IF(R[-2]C>=7/24,""2pm"",IF(R[-2]C>=0/23.99,""6am"")))"
    Range("G28").FormulaR1C1 = "=WEEKDAY(R[-2]C)"
    Range("G27").FormulaR1C1 = "=R[-2]C-INT(R[-2]C)"
    Range("G26").FormulaR1C1 = "=INT(R[-1]C)"
    With Range("F29:G29,F24:G24").Interior
    .ColorIndex = 6
    .Pattern = xlSolid
    End With
    With Range("G24:G29")
    .HorizontalAlignment = xlRight
    .VerticalAlignment = xlBottom
    .WrapText = False
    .Orientation = 0
    .AddIndent = False
    .ShrinkToFit = False
    .MergeCells = False
    End With
    Range("G24,G29").Font.Bold = True
    Range("E23:G30").Borders.LineStyle = xlNone
    Range("F24:G24,F29:G29").Interior.ColorIndex = 6
    Range("E22:G31").Borders.LineStyle = xlNone
    Range("G28").NumberFormat = "0"
    Range("G27").NumberFormat = "h:mm AM/PM"
    Range("G26").NumberFormat = "d-mmm-yy"
    Range("G25").NumberFormat = "m/d/yy h:mm"
    Range("G24").NumberFormat = "d-mmm-yy"
    Range("G24").Font.Bold = True
    Columns("G:G").EntireColumn.AutoFit
    Range("G24").Formula = _
    "=G26+IF(OR(H38={""Reg Photo Paper"",""Matte Photo Poster"",""Moab"",""Giclee"",""Canvas"",""Reg Photo Paper "",""Matte Photo Poster "",""Moab "",""Giclee "",""Canvas ""}),IF(G28=1,2,IF(G28=7,3,IF(G28={5,6},IF(G29=""10pm"",4,IF(OR(G29={""2pm" ",""6am""}),3,0)),IF(OR(G28={2,3,4,5}),IF(G29=""10pm"",2,IF(OR(G29={""2pm"" ,""6am""}),1,0)),IF(AND(OR(G28={2,3,4,5}),OR(G29={""2pm"",""6am""})),1,0))) )),IF(OR(H38={""Premium Photo Paper"",""Laminate"",""Premium Photo Paper "",""Laminate ""}),IF(G28=1,4,IF(G28=7,5,IF(OR(G28={4,5,6}),IF(OR(G29={""2pm"",""6am""}), 5,IF(G29=""10pm"",6,0)),IF(OR(G28={2,3}),IF(G29=""10pm"",4,3),0)))),0))"
    End Sub
    [/VBA]
    MVP (Excel 2008-2010)

    Post a workbook with sample data and layout if you want a quicker solution.


    To help indent your macros try Smart Indent

    Please remember to mark threads 'Solved'

Posting Permissions

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