Consulting

Page 1 of 2 1 2 LastLast
Results 1 to 20 of 28

Thread: VBA for MORE Conditional Formating Excel 2003

  1. #1
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location

    Question VBA for MORE Conditional Formating Excel 2003

    Hello Friends....
    I have a worksheet in which one column (B) I have named countries using a vertical look up formula and in column C i have a dollar figure also with a lookup formula that comes from the country looked up in column B......What I want is a conditional format turning the interior cell of COLumn C to turn GREEN whenever a specific country is in column B. In excell 2003 I only have 3 allowances. I need at least 15.

    So, if in column B i have Germany, I want Column C to turn green because Germany is in Column B...

    Not sure If I explain this clearly enough..

  2. #2
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    [vba]

    '-----------------------------------------------------------------
    Private Sub Worksheet_Change(ByVal Target As Range)
    '-----------------------------------------------------------------
    Const WS_RANGE As String = "B:B" '<=== change to suit
    Dim iCol As Long

    On Error GoTo ws_exit:
    Application.EnableEvents = False
    If Not Intersect(Target, Me.Range(WS_RANGE)) Is Nothing Then

    With Target

    Select Case .Value

    Case "Germany": iCol = 10 'green
    Case "France": iCol = 6 'yellow
    Case "Italy": iCol = 5 'blue
    Case "UK": iCol = 3 'red
    'etc
    End Select
    .Offset(0, 1).Interior.ColorIndex = iCol
    End With
    End If

    ws_exit:
    Application.EnableEvents = True
    End Sub
    [/vba]

    This is worksheet event code, which means that it needs to be
    placed in the appropriate worksheet code module, not a standard
    code module. To do this, right-click on the sheet tab, select
    the View Code option from the menu, and paste the code in.
    ____________________________________________
    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

  3. #3
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location

    VBA for More Conditional Formatting Excel 2003

    Wow, great, thank you my friend. It works wonderful. I was last night trying to figure it out. I'm grateful. HAve a great day from all of us here in the Tropical Island with many many miles of sandy beaches and clear blue warm waters.....

  4. #4
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Which tropicall island? I would be jealous but I suffer in the heat
    ____________________________________________
    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
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location

    VBA for MORE (HELP) Conditional Formating Excel 2003

    Quote Originally Posted by xld
    Which tropicall island? I would be jealous but I suffer in the heat
    Puerto Rico...The Shinning Star of the Caribbean. It's close to about 95 in San Juan, but I am in an A/C office so it is KOOL....

    OK. The code works great BUT i forgot to mentioned another condition which i needed. The condition I have now which you greatly helped is changing column C cell to a color based on the given condition of column B, which is great and it works fine. The other condition i need is that the conditions on column B when it is met can change the color of the cell on column G...

    Example: This is what it is doing right now: Colomn "B" row 4 cell has Germany, it changes color on column "C" row4 cell to green.

    Colomn "B" row 5 cell has "Italy", I need it to change color on column "G" row 5 cell to blue and not colum C row 4 to green.

    I offset the colomn son the ---.Offset(0, 3).Interior.ColorIndex = iCol---
    but it changes the first condition.

  6. #6
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    [vba]

    '-----------------------------------------------------------------
    Private Sub Worksheet_Change(ByVal Target As Range)
    '-----------------------------------------------------------------
    Const WS_RANGE As String = "B:B" '<=== change to suit
    Dim iCol As Long, iCI As Long

    On Error GoTo ws_exit:
    Application.EnableEvents = False
    If Not Intersect(Target, Me.Range(WS_RANGE)) Is Nothing Then

    With Target

    Select Case .Value

    Case "Germany": iCol = 1: iCI = 10 'green
    Case "France": iCol = 2: iCI = 6 'yellow
    Case "Italy": iCol = 5: iCI = 5 'blue
    Case "UK": iCol = 4: iCI = 3 'red
    'etc
    End Select
    .Offset(0, iCol).Interior.ColorIndex = iCI
    End With
    End If

    ws_exit:
    Application.EnableEvents = True
    End Sub
    [/vba]
    ____________________________________________
    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

  7. #7
    Moderator VBAX Wizard lucas's Avatar
    Joined
    Jun 2004
    Location
    Tulsa, Oklahoma
    Posts
    7,323
    Location
    Probably not the best but it seems to work:
    [VBA]Option Explicit
    Private Sub Worksheet_Change(ByVal Target As Range)
    '-----------------------------------------------------------------
    Const WS_RANGE As String = "B:B" '<=== change to suit
    Dim iCol As Long

    On Error GoTo ws_exit:
    Application.EnableEvents = False
    If Not Intersect(Target, Me.Range(WS_RANGE)) Is Nothing Then

    With Target

    If Target.Value = "Germany" Then .Offset(0, 1).Interior.ColorIndex = 10
    If Target.Value = "France" Then .Offset(0, 1).Interior.ColorIndex = 6
    If Target.Value = "Italy" Then .Offset(0, 5).Interior.ColorIndex = 5
    If Target.Value = "UK" Then .Offset(0, 1).Interior.ColorIndex = 3
    End With
    End If

    ws_exit:
    Application.EnableEvents = True
    End Sub[/VBA]
    Steve
    "Nearly all men can stand adversity, but if you want to test a man's character, give him power."
    -Abraham Lincoln

  8. #8
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location
    Mr. XLD,

    Is it possible to also change the color of data on column B to match those colors of column C and G. I just though of that now. since the user will be alerted of the colors they can see it form the beginning, the COUNTRY NAME.

    Thanks Friend

  9. #9
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    [vba]


    '-----------------------------------------------------------------
    Private Sub Worksheet_Change(ByVal Target As Range)
    '-----------------------------------------------------------------
    Const WS_RANGE As String = "B:B" '<=== change to suit
    Dim iCol As Long, iCI As Long

    On Error Goto ws_exit:
    Application.EnableEvents = False
    If Not Intersect(Target, Me.Range(WS_RANGE)) Is Nothing Then

    With Target

    Select Case .Value

    Case "Germany": iCol = 1: iCI = 10 'green
    Case "France": iCol = 2: iCI = 6 'yellow
    Case "Italy": iCol = 5: iCI = 5 'blue
    Case "UK": iCol = 4: iCI = 3 'red
    'etc
    End Select
    .Offset(0, iCol).Interior.ColorIndex = iCI
    .Interior.ColorIndex = iCI
    End With
    End If

    ws_exit:
    Application.EnableEvents = True
    End Sub
    [/vba]
    ____________________________________________
    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

  10. #10
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location
    Hi Fellas, something is not working. the cells do not change color unless I manually enter the data. Right now the data is being fed into the columns and rows via a formula. Unless i enter the data manually the conditional format is not triggered. Is there anyway around this? I'm sorry to keeo bothering everyone,,,,

  11. #11
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location
    Fellas, this is what i had, but it only changed the colors on the range that I specified. It works even though the cells have formulas in them. The only Thing I do is refresh the cells so that the colors appears... Can this be changed to to included the changes in other columns as with the vba code that you had provided earlier?...Thanks again

    [vba]
    'Conditional Formats, Looking for Friendly Fronts on Premium Collections Worksheet
    Private Sub Worksheet_SelectionChange(ByVal Target As Range)
    Dim icolor As Integer
    If Not Intersect(Target, Range("e24:g176")) Is Nothing Then
    Select Case Target
    Case "Dom. Republic": icolor = 4
    Case "Bolivia": icolor = 4
    Case "Paraguay": icolor = 4
    Case "Peru" To "Peru": icolor = 4
    Case "Costa Rica": icolor = 4
    Case "Nicaragua": icolor = 4
    Case "Panama": icolor = 4

    'Tarrif rated countries must be pre-approved or approved by superintendency
    Case "Bangladesh": icolor = 6
    Case "Belarus": icolor = 6
    Case "Belgium": icolor = 6
    Case "Brazil": icolor = 6
    Case "Brunei": icolor = 6
    Case "China": icolor = 6
    Case "Dom. Republic": icolor = 6
    'Tarrif rated countries Guatemala must be approved by superintendency
    Case "Guatemala": icolor = 3
    Case "Spain": icolor = 14
    Case "Uganda": icolor = 6
    Case "Virgin Islands US": icolor = 6

    Case Else
    icolor = 20
    End Select
    Target.Interior.ColorIndex = icolor
    End If
    End Sub
    [/vba]
    Last edited by Bob Phillips; 07-02-2009 at 02:58 PM. Reason: Added VBA tags

  12. #12
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Is this what you mean?

    [vba]

    'Conditional Formats, Looking for Friendly Fronts on Premium Collections Worksheet
    Private Sub Worksheet_SelectionChange(ByVal Target As Range)
    Dim iColor As Long
    Dim iColumn As Long
    If Not Intersect(Target, Range("e24:g176")) Is Nothing Then
    Select Case Target
    Case "Dom. Republic", "Bolivia", "Paraguay", "Peru", "Costa Rica", "Nicaragua", "Panama"
    iColor = 4
    iColumn = 5

    'Tarrif rated countries must be pre-approved or approved by superintendency
    Case "Bangladesh", "Belarus", "Belgium", "Brazil", "Brunei", "China", "Dom. Republic"
    iColor = 6
    iColumn = 1

    'Tarrif rated countries Guatemala must be approved by superintendency
    Case "Guatemala"
    iColor = 3
    iColumn = 1

    Case "Spain"
    iColor = 14
    iColumn = 7

    Case "Uganda"
    iColor = 6
    iColumn = 5

    Case "Virgin Islands US"
    iColor = 6
    iColumn = 3

    Case Else
    iColor = 20
    iColumn = 78

    End Select
    Target.Offset(0, iColumn).Interior.ColorIndex = iColor
    Target.Interior.ColorIndex = iColor
    End If
    End Sub
    [/vba]
    ____________________________________________
    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

  13. #13
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location
    XLD,

    I had something similar to this, it work but only half way, so it was not really good. Yours by BTW works perfectly.

    Question, the original (I think) allowed for the colors to reset themelves back to its original color whenever the condition was changed to a country not on the "Conditional Formatted" list.

    Example: China is a condition that happens to fall in cell G5, it changes cell color to Yellow (column g) and also column K (K5) . Now when China is not selected and on that same cell and lets say Trinidad is selected, the G column
    reverts back to original color but column K5 stays green, I have to change it manually to a no-fill color.

    Could there be a way around this?.

    Gracias....

  14. #14
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    The difficult klutz is in knowing what was in that cell before, that it was China. There would be no problem removing the colour in the whole line, but identifying particular cells would be tricky(ish).
    ____________________________________________
    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

  15. #15
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location
    XLD, I received a Run Type 13 Type Mismatch Error on the code at this specific line:

    Case "Dom. Republic", "Bolivia", "Paraguay", "Peru", "Costa Rica", "Nicaragua", "Panama"
    iColor = 4
    iColumn = 5

    It only happens when I select or high the complete row or 2 or more cells within the column where the range is :

    If Not Intersect(Target, Range("e24:g176")) Is Nothing Then

    What could be happening? Thanks again...

  16. #16
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location
    Oh Man, here I go again....Is there a way to be able to select 2 or more columns to be formatted for the same target case:

    Example-

    Case "Ireland" , "Sweden:
    iColor = 4
    iColumn = 5 and another column like column 10 and 15 ?
    pray2: " pray2: "

    Thanks...

  17. #17
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location
    Last edited by klutz; 07-03-2009 at 10:26 PM. Reason: Entered same message twice

  18. #18
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    Quote Originally Posted by klutz
    XLD, I received a Run Type 13 Type Mismatch Error on the code at this specific line:

    Case "Dom. Republic", "Bolivia", "Paraguay", "Peru", "Costa Rica", "Nicaragua", "Panama"
    iColor = 4
    iColumn = 5

    It only happens when I select or high the complete row or 2 or more cells within the column where the range is :

    If Not Intersect(Target, Range("e24:g176")) Is Nothing Then

    What could be happening? Thanks again...
    [vba]

    'Conditional Formats, Looking for Friendly Fronts on Premium Collections Worksheet
    Private Sub Worksheet_SelectionChange(ByVal Target As Range)
    Dim iColor As Long
    Dim iColumn As Long
    Dim cell As Range

    If Not Intersect(Target, Range("e24:g176")) Is Nothing Then

    For Each cell In Target

    If cell.Value <> "" Then

    Select Case Target
    Case "Dom. Republic", "Bolivia", "Paraguay", "Peru", "Costa Rica", "Nicaragua", "Panama"
    iColor = 4
    iColumn = 5

    'Tarrif rated countries must be pre-approved or approved by superintendency
    Case "Bangladesh", "Belarus", "Belgium", "Brazil", "Brunei", "China", "Dom. Republic"
    iColor = 6
    iColumn = 1

    'Tarrif rated countries Guatemala must be approved by superintendency
    Case "Guatemala"
    iColor = 3
    iColumn = 1

    Case "Spain"
    iColor = 14
    iColumn = 7

    Case "Uganda"
    iColor = 6
    iColumn = 5

    Case "Virgin Islands US"
    iColor = 6
    iColumn = 3

    Case Else
    iColor = 20
    iColumn = 78

    End Select
    Target.Offset(0, iColumn).Interior.ColorIndex = iColor
    Target.Interior.ColorIndex = iColor
    End If
    Next cell
    End If
    End Sub
    [/vba]
    ____________________________________________
    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

  19. #19
    VBAX Contributor
    Joined
    Jun 2009
    Posts
    110
    Location

    Thax..But error remains

    Thanks XID, but the run time error 13 type mismatch remains, . The code points to :

    [VBA]Case "Dom. Republic", "Bolivia", "Paraguay", "Peru", "Costa Rica", "Nicaragua", "Panama"
    iColor = 4
    iColumn = 5[/VBA]

    Also, how can I make it to format 2 or more columns with colors whenever the condition is met?

    Thanx.

    The Klutz...

  20. #20
    Administrator
    VP-Knowledge Base
    VBAX Grand Master mdmackillop's Avatar
    Joined
    May 2004
    Location
    Scotland
    Posts
    14,489
    Location
    Try
    [VBA]Select Case Target.value [/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
  •