Consulting

Results 1 to 5 of 5

Thread: Using VBA in Excel 2010, need to change text of many cond formats, but how?

  1. #1
    VBAX Newbie
    Joined
    Aug 2014
    Posts
    3
    Location

    Using VBA in Excel 2010, need to change text of many cond formats, but how?

    I have a worksheet that has a number of different conditional format formulas. They look something like this:
    ='2. Coverage Analysis-TEMPLATE'!$D14+'2. Coverage Analysis-TEMPLATE'!$E14=0
    or this:
    ='2. Coverage Analysis-TEMPLATE'!$C28*'2. Coverage Analysis-TEMPLATE'!$Q28=0
    or this:
    ='2. Coverage Analysis-TEMPLATE'!$T12-'2. Coverage Analysis-TEMPLATE'!$Z12=0

    I want to replace the word TEMPLATE in each formula with the word PRIMARY

    I've been trying to loop through the ConditionalFormats collection, use the .modify statement, use .delete and .add and have had no success and many confusing error messages... typically Invalid Procedure Call or Argument.

    How can I do this?

  2. #2
    Hi
    Welcome to the board

    In this example I set 3 formatting conditions for Sheet1!C1
    I add expressions similar to yours:

    =(Sheet2!$A$1+Sheet3!$A$1=2) (colour yellow)
    =(Sheet2!$A$1+Sheet3!$A$1=3) (colour red)
    =(Sheet2!$A$1+Sheet3!$A$1=4) (colour green)

    I then change the 2nd conditions, replacing Sheet2 with Sheet4, so that the 2nd condition is modified to

    =(Sheet4!$A$1+Sheet3!$A$1=3) (colour blue)

    I print the conditions before and after modifying the second condition so that it's easy to check if it's OK.

    See if this helps:


    Sub ModifyCF()
    Dim cfs As FormatConditions
    Dim cf As FormatCondition
    
    Set cfs = Worksheets("Sheet1").Range("C1").FormatConditions
    
    ' for test, delete format conditions
    cfs.Delete
    
    ' add 3 format conditions
    Set cf = cfs.Add(Type:=xlExpression, Formula1:="=(Sheet2!$A$1+Sheet3!$A$1=2)")
    cf.Interior.Color = vbYellow
    Set cf = cfs.Add(xlExpression, Formula1:="=(Sheet2!$A$1+Sheet3!$A$1=3)")
    cf.Interior.Color = vbRed
    Set cf = cfs.Add(Type:=xlExpression, Formula1:="=(Sheet2!$A$1+Sheet3!$A$1=4)")
    cf.Interior.Color = vbGreen
    
    ' print the format conditions
    Debug.Print "First format condition: " & cfs(1).Formula1
    Debug.Print "Second format condition: " & cfs(2).Formula1
    Debug.Print "Third format condition: " & cfs(3).Formula1
    
    ' modify the second format condition
    Set cf = cfs(2)
    cf.Modify xlExpression, Formula1:=Replace(cf.Formula1, "Sheet2", "Sheet4")
    cf.Interior.Color = vbBlue
    cf.Priority = 2
    
    ' print the format conditions
    Debug.Print "First format condition: " & cfs(1).Formula1
    Debug.Print "Second format condition: " & cfs(2).Formula1
    Debug.Print "Third format condition: " & cfs(3).Formula1
    
    End Sub

  3. #3
    Knowledge Base Approver VBAX Wizard
    Joined
    Apr 2012
    Posts
    5,645
    I'd prefer:

    "=sum('2. Coverage Analysis-TEMPLATE'!$D14:$E14)=0"

    Sub M_snb()
        For Each cl In sheet1.Cells.SpecialCells(-4172)
            cl.FormatConditions(1).Modify cl.FormatConditions(1).Type, , Replace(cl.FormatConditions(1).Formula1, "TEMPLATE", "PRIMARY")
        Next
    End Sub

  4. #4
    VBAX Newbie
    Joined
    Aug 2014
    Posts
    3
    Location
    The .Add method is less desireable because then I'll have to go through and find and copy all the properties of the Conditional format.

    The .Modify is what I want, but it doesn't work properly.

    I execute this command:
    NewFormula1 = Replace(CFRange.FormatConditions(1).Formula1, FindText, ReplaceText)
    Debug.Print "Before Modify Formula: " & CFRange.FormatConditions(1).Formula1
    Call CFRange.FormatConditions(1).Modify(Type:=CFRange.FormatConditions(1).Type, Formula1:=NewFormula1)
    Debug.Print "After Modify Formula: " & CFRange.FormatConditions(1).Formula1
    And these are the results:
    Before Modify Formula: ='2. Coverage Analysis-TEMPLATE'!$D14+'2. Coverage Analysis-TEMPLATE'!$E14=0
    After Modify Formula: ='2. Coverage Analysis-COHORT1'!$D1048567+'2. Coverage Analysis-COHORT1'!$E1048567=0

    As you can see, it changes the text, but it also WILDLY and inexplicably changes the addresses in the formula!
    Any idea as to why that may be happening?

  5. #5
    VBAX Newbie
    Joined
    Aug 2014
    Posts
    3
    Location
    OK,

    I found something that works. My best guess is that the problem is that the range covers more than one contiguous group of cells. I'd actually call it more of a bug than a problem.

    What I did was:
    1. find the addresses of the ranges covered by the rule
    2. Save off the those original addresses
    3. use the ModifyAppliesTo method to change the AppliesTo address to just the first contiguous range
    4. Use the .Modify method to change the formula
    5. use the ModifyAppliesTo method to change the AppliesTo address back to the original group of ranges

    That seems to work:
                         ' Save the addresses of the ranges to which this CondFormat item applies
                        Set FormatConditionItem = CFRange.FormatConditions(1)
                        OrigAddr = FormatConditionItem.AppliesTo.Address
        
                        ' To be able to use the .modify method, we can only do it on a contiguos range or it doesn't work properly
                        ' Change the addresses of where this applies to just the first contiguous range
                        OrigAddrAry = Split(OrigAddr, ",")
                        Call CFRange.FormatConditions(1).ModifyAppliesToRange(CFRange.Worksheet.Range(OrigAddrAry(0)))
        
                        ' Create a new Range item based on the first contiguos range
                        Set NewCFRange = CFRange.Worksheet.Range(OrigAddrAry(0))
        
                        ' Change the formula on the first contiguos range
                        NewFormula1 = Replace(NewCFRange.FormatConditions(1).Formula1, FindText, ReplaceText)
                        Call NewCFRange.FormatConditions(1).Modify(Type:=OrigType, Formula1:=NewFormula1)
        
                        ' Change the applied to addresses back to what it originally was
                        Call NewCFRange.FormatConditions(1).ModifyAppliesToRange(CFRange.Worksheet.Range(OrigAddr))

Posting Permissions

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