+ Reply to Thread
Results 1 to 7 of 7

highlight/color cells with specific character inside

  1. #1
    markx
    Guest

    highlight/color cells with specific character inside

    Hi guys,

    Some time ago, I posted the question below, but didn't receive any 100%
    satisfactory answer. Could you take a look at this? Thanks!

    -------------
    What is the best way to highlight (or even color) all the cells in a
    worksheet (or even in a workbook) containing a specific character? For
    exemple, I would like to make visually distinctive all the cells containing
    somewhere a "?" character (or "mmm" string, or "!" mark, or "=" sign).

    Are you aware of any special easy macro doing (and also undoing) this kind
    of stuff?
    Or do you have idea how to write a special formula to put in "conditionnal
    formatting" part?
    -------------
    (To be more precise, I would like to find not only the cells where the
    reqested sign is the only one (f. ex. "?" in cell A1="?"), but also the
    cells where this sign is one parmi others (like f. ex. finding "?" in cell
    A2="mxz?wptex").

    * * *
    One of my goals is to find (through this method) all the formulas (as they
    contain "=" sign), references to other sheets (looking for the "!" sign) and
    worksheets ("[", "]" and ".xls" signs). Please let me know if there is any
    other (simplier and more reliable) way to do this...

    Once again, many thanks folks!
    Mark



  2. #2
    Bob Phillips
    Guest

    Re: highlight/color cells with specific character inside

    Mark,

    I don't know what answers that you got previously, but have you tried a
    simple UDF, like so

    Function IsFormula(rng As Range)
    IsFormula = rng.HasFormula
    End Function


    and use that in the CF.

    Or are you looking for just external reference formulae?

    --
    HTH

    Bob Phillips

    (remove nothere from email address if mailing direct)

    "markx" <[email protected]> wrote in message
    news:[email protected]...
    > Hi guys,
    >
    > Some time ago, I posted the question below, but didn't receive any 100%
    > satisfactory answer. Could you take a look at this? Thanks!
    >
    > -------------
    > What is the best way to highlight (or even color) all the cells in a
    > worksheet (or even in a workbook) containing a specific character? For
    > exemple, I would like to make visually distinctive all the cells

    containing
    > somewhere a "?" character (or "mmm" string, or "!" mark, or "=" sign).
    >
    > Are you aware of any special easy macro doing (and also undoing) this kind
    > of stuff?
    > Or do you have idea how to write a special formula to put in "conditionnal
    > formatting" part?
    > -------------
    > (To be more precise, I would like to find not only the cells where the
    > reqested sign is the only one (f. ex. "?" in cell A1="?"), but also the
    > cells where this sign is one parmi others (like f. ex. finding "?" in cell
    > A2="mxz?wptex").
    >
    > * * *
    > One of my goals is to find (through this method) all the formulas (as they
    > contain "=" sign), references to other sheets (looking for the "!" sign)

    and
    > worksheets ("[", "]" and ".xls" signs). Please let me know if there is any
    > other (simplier and more reliable) way to do this...
    >
    > Once again, many thanks folks!
    > Mark
    >
    >




  3. #3
    markx
    Guest

    Re: highlight/color cells with specific character inside



    The answer I received before was basically to put "conditional formatting"
    on cells and specify that if cell value is equal to "my value", than it
    should format it in a specific way.
    Of course, it works only if "my value" is the only value in the analysed
    cell (and is not a part of a larger string), and that's the problem.

    To respond to your question, I'm really looking for something very general,
    as described below (highlighting/coloring all cells where a particular
    character is placed). Then, of course, I can apply it to my curret specific
    needs, which are finding:
    - simple formula (character "=") -> a cell responding to this condition
    could be colored in green
    - formula relating to another worksheet (characters "=" and "!") -> a cell
    responding to this condition could be colored in yellow
    - formula relating to another workbook (characters "=", "[", "]" and
    ".xls") -> a cell responding to this condition could be colored in red

    It would be also great (hope it's not too complicated) to create a new
    worksheet where all these formulas are listed, f. ex. in the following
    format:

    Cell Address: Formula in cell address refering to:
    Sheet1!A2 '=Sheet1!B4
    Sheet1!M15 '=Sheet5!F122
    Sheet2!B3 '=[Other_file.xls]Sheet4!B4
    Sheet4!F14 '=Sheet1!B5
    Sheet6!AD12 '=Sheet1!B5

    but you can leave this last feature (it's not essential).

    Thanks for any hints,
    Mark





    "Bob Phillips" <[email protected]> wrote in message
    news:[email protected]...
    > Mark,
    >
    > I don't know what answers that you got previously, but have you tried a
    > simple UDF, like so
    >
    > Function IsFormula(rng As Range)
    > IsFormula = rng.HasFormula
    > End Function
    >
    >
    > and use that in the CF.
    >
    > Or are you looking for just external reference formulae?
    >
    > --
    > HTH
    >
    > Bob Phillips
    >
    > (remove nothere from email address if mailing direct)
    >
    > "markx" <[email protected]> wrote in message
    > news:[email protected]...
    >> Hi guys,
    >>
    >> Some time ago, I posted the question below, but didn't receive any 100%
    >> satisfactory answer. Could you take a look at this? Thanks!
    >>
    >> -------------
    >> What is the best way to highlight (or even color) all the cells in a
    >> worksheet (or even in a workbook) containing a specific character? For
    >> exemple, I would like to make visually distinctive all the cells

    > containing
    >> somewhere a "?" character (or "mmm" string, or "!" mark, or "=" sign).
    >>
    >> Are you aware of any special easy macro doing (and also undoing) this
    >> kind
    >> of stuff?
    >> Or do you have idea how to write a special formula to put in
    >> "conditionnal
    >> formatting" part?
    >> -------------
    >> (To be more precise, I would like to find not only the cells where the
    >> reqested sign is the only one (f. ex. "?" in cell A1="?"), but also the
    >> cells where this sign is one parmi others (like f. ex. finding "?" in
    >> cell
    >> A2="mxz?wptex").
    >>
    >> * * *
    >> One of my goals is to find (through this method) all the formulas (as
    >> they
    >> contain "=" sign), references to other sheets (looking for the "!" sign)

    > and
    >> worksheets ("[", "]" and ".xls" signs). Please let me know if there is
    >> any
    >> other (simplier and more reliable) way to do this...
    >>
    >> Once again, many thanks folks!
    >> Mark
    >>
    >>

    >
    >




  4. #4
    Gary''s Student
    Guest

    Re: highlight/color cells with specific character inside

    Hi markx:

    Bob's approach to conditionally highlighing formulae is probably the best.
    Looking for the = symbol will lead you to treat the formula:
    =A1+B1
    the same as the text:
    Hard Work = Success

    Looking for the ! symbol will lead you to treat the linkage formula:
    =Sheet1!$A$1
    the same as the text:
    Have a good day!!!
    --
    Gary''s Student


    "markx" wrote:

    >
    >
    > The answer I received before was basically to put "conditional formatting"
    > on cells and specify that if cell value is equal to "my value", than it
    > should format it in a specific way.
    > Of course, it works only if "my value" is the only value in the analysed
    > cell (and is not a part of a larger string), and that's the problem.
    >
    > To respond to your question, I'm really looking for something very general,
    > as described below (highlighting/coloring all cells where a particular
    > character is placed). Then, of course, I can apply it to my curret specific
    > needs, which are finding:
    > - simple formula (character "=") -> a cell responding to this condition
    > could be colored in green
    > - formula relating to another worksheet (characters "=" and "!") -> a cell
    > responding to this condition could be colored in yellow
    > - formula relating to another workbook (characters "=", "[", "]" and
    > ".xls") -> a cell responding to this condition could be colored in red
    >
    > It would be also great (hope it's not too complicated) to create a new
    > worksheet where all these formulas are listed, f. ex. in the following
    > format:
    >
    > Cell Address: Formula in cell address refering to:
    > Sheet1!A2 '=Sheet1!B4
    > Sheet1!M15 '=Sheet5!F122
    > Sheet2!B3 '=[Other_file.xls]Sheet4!B4
    > Sheet4!F14 '=Sheet1!B5
    > Sheet6!AD12 '=Sheet1!B5
    >
    > but you can leave this last feature (it's not essential).
    >
    > Thanks for any hints,
    > Mark
    >
    >
    >
    >
    >
    > "Bob Phillips" <[email protected]> wrote in message
    > news:[email protected]...
    > > Mark,
    > >
    > > I don't know what answers that you got previously, but have you tried a
    > > simple UDF, like so
    > >
    > > Function IsFormula(rng As Range)
    > > IsFormula = rng.HasFormula
    > > End Function
    > >
    > >
    > > and use that in the CF.
    > >
    > > Or are you looking for just external reference formulae?
    > >
    > > --
    > > HTH
    > >
    > > Bob Phillips
    > >
    > > (remove nothere from email address if mailing direct)
    > >
    > > "markx" <[email protected]> wrote in message
    > > news:[email protected]...
    > >> Hi guys,
    > >>
    > >> Some time ago, I posted the question below, but didn't receive any 100%
    > >> satisfactory answer. Could you take a look at this? Thanks!
    > >>
    > >> -------------
    > >> What is the best way to highlight (or even color) all the cells in a
    > >> worksheet (or even in a workbook) containing a specific character? For
    > >> exemple, I would like to make visually distinctive all the cells

    > > containing
    > >> somewhere a "?" character (or "mmm" string, or "!" mark, or "=" sign).
    > >>
    > >> Are you aware of any special easy macro doing (and also undoing) this
    > >> kind
    > >> of stuff?
    > >> Or do you have idea how to write a special formula to put in
    > >> "conditionnal
    > >> formatting" part?
    > >> -------------
    > >> (To be more precise, I would like to find not only the cells where the
    > >> reqested sign is the only one (f. ex. "?" in cell A1="?"), but also the
    > >> cells where this sign is one parmi others (like f. ex. finding "?" in
    > >> cell
    > >> A2="mxz?wptex").
    > >>
    > >> * * *
    > >> One of my goals is to find (through this method) all the formulas (as
    > >> they
    > >> contain "=" sign), references to other sheets (looking for the "!" sign)

    > > and
    > >> worksheets ("[", "]" and ".xls" signs). Please let me know if there is
    > >> any
    > >> other (simplier and more reliable) way to do this...
    > >>
    > >> Once again, many thanks folks!
    > >> Mark
    > >>
    > >>

    > >
    > >

    >
    >
    >


  5. #5
    Bob Phillips
    Guest

    Re: highlight/color cells with specific character inside

    Mark,

    How about this macro

    Sub FindFormulae()
    Dim this As Worksheet
    Dim sh As Worksheet
    Dim cell As Range
    Dim i As Long
    Set this = ActiveSheet
    On Error Resume Next
    Set sh = Worksheets("FormulaeList")
    On Error GoTo 0
    If sh Is Nothing Then
    Set sh = Worksheets.Add
    sh.Name = "FormulaeList"
    Else
    sh.Cells.ClearContents
    End If
    For Each cell In this.UsedRange
    If cell.HasFormula Then
    i = i + 1
    sh.Cells(i, "A").Value = "'" & cell.Formula
    Select Case True
    Case cell.Formula Like "*]*"
    sh.Cells(i, "A").Offset(0, 1).Interior.Color = vbRed
    cell.Interior.Color = vbRed
    Case cell.Formula Like "*!*"
    sh.Cells(i, "A").Offset(0, 1).Interior.Color = vbBlue
    cell.Interior.Color = vbBlue
    Case Else
    sh.Cells(i, "A").Offset(0, 1).Interior.Color = vbGreen
    cell.Interior.Color = vbGreen
    End Select
    End If
    Next cell
    sh.Columns(1).AutoFit
    End Sub

    --
    HTH

    Bob Phillips

    (remove nothere from email address if mailing direct)

    "markx" <[email protected]> wrote in message
    news:uZM9%[email protected]...
    >
    >
    > The answer I received before was basically to put "conditional formatting"
    > on cells and specify that if cell value is equal to "my value", than it
    > should format it in a specific way.
    > Of course, it works only if "my value" is the only value in the analysed
    > cell (and is not a part of a larger string), and that's the problem.
    >
    > To respond to your question, I'm really looking for something very

    general,
    > as described below (highlighting/coloring all cells where a particular
    > character is placed). Then, of course, I can apply it to my curret

    specific
    > needs, which are finding:
    > - simple formula (character "=") -> a cell responding to this condition
    > could be colored in green
    > - formula relating to another worksheet (characters "=" and "!") -> a cell
    > responding to this condition could be colored in yellow
    > - formula relating to another workbook (characters "=", "[", "]" and
    > ".xls") -> a cell responding to this condition could be colored in red
    >
    > It would be also great (hope it's not too complicated) to create a new
    > worksheet where all these formulas are listed, f. ex. in the following
    > format:
    >
    > Cell Address: Formula in cell address refering to:
    > Sheet1!A2 '=Sheet1!B4
    > Sheet1!M15 '=Sheet5!F122
    > Sheet2!B3 '=[Other_file.xls]Sheet4!B4
    > Sheet4!F14 '=Sheet1!B5
    > Sheet6!AD12 '=Sheet1!B5
    >
    > but you can leave this last feature (it's not essential).
    >
    > Thanks for any hints,
    > Mark
    >
    >
    >
    >
    >
    > "Bob Phillips" <[email protected]> wrote in message
    > news:[email protected]...
    > > Mark,
    > >
    > > I don't know what answers that you got previously, but have you tried a
    > > simple UDF, like so
    > >
    > > Function IsFormula(rng As Range)
    > > IsFormula = rng.HasFormula
    > > End Function
    > >
    > >
    > > and use that in the CF.
    > >
    > > Or are you looking for just external reference formulae?
    > >
    > > --
    > > HTH
    > >
    > > Bob Phillips
    > >
    > > (remove nothere from email address if mailing direct)
    > >
    > > "markx" <[email protected]> wrote in message
    > > news:[email protected]...
    > >> Hi guys,
    > >>
    > >> Some time ago, I posted the question below, but didn't receive any 100%
    > >> satisfactory answer. Could you take a look at this? Thanks!
    > >>
    > >> -------------
    > >> What is the best way to highlight (or even color) all the cells in a
    > >> worksheet (or even in a workbook) containing a specific character? For
    > >> exemple, I would like to make visually distinctive all the cells

    > > containing
    > >> somewhere a "?" character (or "mmm" string, or "!" mark, or "=" sign).
    > >>
    > >> Are you aware of any special easy macro doing (and also undoing) this
    > >> kind
    > >> of stuff?
    > >> Or do you have idea how to write a special formula to put in
    > >> "conditionnal
    > >> formatting" part?
    > >> -------------
    > >> (To be more precise, I would like to find not only the cells where the
    > >> reqested sign is the only one (f. ex. "?" in cell A1="?"), but also the
    > >> cells where this sign is one parmi others (like f. ex. finding "?" in
    > >> cell
    > >> A2="mxz?wptex").
    > >>
    > >> * * *
    > >> One of my goals is to find (through this method) all the formulas (as
    > >> they
    > >> contain "=" sign), references to other sheets (looking for the "!"

    sign)
    > > and
    > >> worksheets ("[", "]" and ".xls" signs). Please let me know if there is
    > >> any
    > >> other (simplier and more reliable) way to do this...
    > >>
    > >> Once again, many thanks folks!
    > >> Mark
    > >>
    > >>

    > >
    > >

    >
    >




  6. #6
    markx
    Guest

    Re: highlight/color cells with specific character inside

    Wow Bob,
    Thank you very much, it's excellent!

    However, I wouldn't be myself if I didn't ask some additional questions :-):

    Do you also know how should I modify this macro in order to make the
    "formula research" not only on the current sheet, but on the whole workbook?
    (suppose I have to change "Set this = ActiveSheet" to something like "Set
    this = ActiveWorkbook", but I'm not sure if it's enough...)

    Also, do you have an idea how to create an additional column on the
    "FormulaeList" worksheet that will give me the addresses of the cells with
    formulas (and not only the sole formulas)?

    Thanks again for your time and involvement,
    I appreciate this a lot,
    Mark





    "Bob Phillips" <[email protected]> wrote in message
    news:[email protected]...
    > Mark,
    >
    > How about this macro
    >
    > Sub FindFormulae()
    > Dim this As Worksheet
    > Dim sh As Worksheet
    > Dim cell As Range
    > Dim i As Long
    > Set this = ActiveSheet
    > On Error Resume Next
    > Set sh = Worksheets("FormulaeList")
    > On Error GoTo 0
    > If sh Is Nothing Then
    > Set sh = Worksheets.Add
    > sh.Name = "FormulaeList"
    > Else
    > sh.Cells.ClearContents
    > End If
    > For Each cell In this.UsedRange
    > If cell.HasFormula Then
    > i = i + 1
    > sh.Cells(i, "A").Value = "'" & cell.Formula
    > Select Case True
    > Case cell.Formula Like "*]*"
    > sh.Cells(i, "A").Offset(0, 1).Interior.Color = vbRed
    > cell.Interior.Color = vbRed
    > Case cell.Formula Like "*!*"
    > sh.Cells(i, "A").Offset(0, 1).Interior.Color = vbBlue
    > cell.Interior.Color = vbBlue
    > Case Else
    > sh.Cells(i, "A").Offset(0, 1).Interior.Color = vbGreen
    > cell.Interior.Color = vbGreen
    > End Select
    > End If
    > Next cell
    > sh.Columns(1).AutoFit
    > End Sub
    >
    > --
    > HTH
    >
    > Bob Phillips
    >
    > (remove nothere from email address if mailing direct)
    >
    > "markx" <[email protected]> wrote in message
    > news:uZM9%[email protected]...
    >>
    >>
    >> The answer I received before was basically to put "conditional
    >> formatting"
    >> on cells and specify that if cell value is equal to "my value", than it
    >> should format it in a specific way.
    >> Of course, it works only if "my value" is the only value in the analysed
    >> cell (and is not a part of a larger string), and that's the problem.
    >>
    >> To respond to your question, I'm really looking for something very

    > general,
    >> as described below (highlighting/coloring all cells where a particular
    >> character is placed). Then, of course, I can apply it to my curret

    > specific
    >> needs, which are finding:
    >> - simple formula (character "=") -> a cell responding to this condition
    >> could be colored in green
    >> - formula relating to another worksheet (characters "=" and "!") -> a
    >> cell
    >> responding to this condition could be colored in yellow
    >> - formula relating to another workbook (characters "=", "[", "]" and
    >> ".xls") -> a cell responding to this condition could be colored in red
    >>
    >> It would be also great (hope it's not too complicated) to create a new
    >> worksheet where all these formulas are listed, f. ex. in the following
    >> format:
    >>
    >> Cell Address: Formula in cell address refering to:
    >> Sheet1!A2 '=Sheet1!B4
    >> Sheet1!M15 '=Sheet5!F122
    >> Sheet2!B3 '=[Other_file.xls]Sheet4!B4
    >> Sheet4!F14 '=Sheet1!B5
    >> Sheet6!AD12 '=Sheet1!B5
    >>
    >> but you can leave this last feature (it's not essential).
    >>
    >> Thanks for any hints,
    >> Mark
    >>
    >>
    >>
    >>
    >>
    >> "Bob Phillips" <[email protected]> wrote in message
    >> news:[email protected]...
    >> > Mark,
    >> >
    >> > I don't know what answers that you got previously, but have you tried a
    >> > simple UDF, like so
    >> >
    >> > Function IsFormula(rng As Range)
    >> > IsFormula = rng.HasFormula
    >> > End Function
    >> >
    >> >
    >> > and use that in the CF.
    >> >
    >> > Or are you looking for just external reference formulae?
    >> >
    >> > --
    >> > HTH
    >> >
    >> > Bob Phillips
    >> >
    >> > (remove nothere from email address if mailing direct)
    >> >
    >> > "markx" <[email protected]> wrote in message
    >> > news:[email protected]...
    >> >> Hi guys,
    >> >>
    >> >> Some time ago, I posted the question below, but didn't receive any
    >> >> 100%
    >> >> satisfactory answer. Could you take a look at this? Thanks!
    >> >>
    >> >> -------------
    >> >> What is the best way to highlight (or even color) all the cells in a
    >> >> worksheet (or even in a workbook) containing a specific character? For
    >> >> exemple, I would like to make visually distinctive all the cells
    >> > containing
    >> >> somewhere a "?" character (or "mmm" string, or "!" mark, or "=" sign).
    >> >>
    >> >> Are you aware of any special easy macro doing (and also undoing) this
    >> >> kind
    >> >> of stuff?
    >> >> Or do you have idea how to write a special formula to put in
    >> >> "conditionnal
    >> >> formatting" part?
    >> >> -------------
    >> >> (To be more precise, I would like to find not only the cells where the
    >> >> reqested sign is the only one (f. ex. "?" in cell A1="?"), but also
    >> >> the
    >> >> cells where this sign is one parmi others (like f. ex. finding "?" in
    >> >> cell
    >> >> A2="mxz?wptex").
    >> >>
    >> >> * * *
    >> >> One of my goals is to find (through this method) all the formulas (as
    >> >> they
    >> >> contain "=" sign), references to other sheets (looking for the "!"

    > sign)
    >> > and
    >> >> worksheets ("[", "]" and ".xls" signs). Please let me know if there is
    >> >> any
    >> >> other (simplier and more reliable) way to do this...
    >> >>
    >> >> Once again, many thanks folks!
    >> >> Mark
    >> >>
    >> >>
    >> >
    >> >

    >>
    >>

    >
    >




  7. #7
    Bob Phillips
    Guest

    Re: highlight/color cells with specific character inside

    Mark,

    This should address both points

    Sub FindFormulae()
    Dim this As Worksheet
    Dim sh As Worksheet
    Dim cell As Range
    Dim i As Long

    On Error Resume Next
    Set sh = Worksheets("FormulaeList")
    On Error GoTo 0
    If sh Is Nothing Then
    Set sh = Worksheets.Add
    sh.Name = "FormulaeList"
    Else
    sh.Cells.ClearContents
    End If

    For Each this In ActiveWorkbook.Worksheets
    If this.Name <> sh.Name Then
    For Each cell In this.UsedRange
    If cell.HasFormula Then
    i = i + 1
    sh.Cells(i, "A").Resize(, 3).Interior.ColorIndex =
    xlColorIndexNone
    Select Case True
    Case cell.Formula Like "*]*"
    sh.Cells(i, "A").Interior.Color = vbRed
    cell.Interior.Color = vbRed
    Case cell.Formula Like "*!*"
    sh.Cells(i, "A").Interior.Color = vbBlue
    cell.Interior.Color = vbBlue
    Case Else
    sh.Cells(i, "A").Interior.Color = vbGreen
    cell.Interior.Color = vbGreen
    End Select
    sh.Cells(i, "B").Value = "'" & cell.Formula
    sh.Cells(i, "C").Value = cell.Parent.Name & "!" &
    cell.Address
    End If
    Next cell
    End If
    Next this

    sh.Columns("A:C").AutoFit
    End Sub

    --
    HTH

    Bob Phillips

    (remove nothere from email address if mailing direct)

    "markx" <[email protected]> wrote in message
    news:[email protected]...
    > Wow Bob,
    > Thank you very much, it's excellent!
    >
    > However, I wouldn't be myself if I didn't ask some additional questions

    :-):
    >
    > Do you also know how should I modify this macro in order to make the
    > "formula research" not only on the current sheet, but on the whole

    workbook?
    > (suppose I have to change "Set this = ActiveSheet" to something like "Set
    > this = ActiveWorkbook", but I'm not sure if it's enough...)
    >
    > Also, do you have an idea how to create an additional column on the
    > "FormulaeList" worksheet that will give me the addresses of the cells with
    > formulas (and not only the sole formulas)?
    >
    > Thanks again for your time and involvement,
    > I appreciate this a lot,
    > Mark
    >
    >
    >
    >
    >
    > "Bob Phillips" <[email protected]> wrote in message
    > news:[email protected]...
    > > Mark,
    > >
    > > How about this macro
    > >
    > > Sub FindFormulae()
    > > Dim this As Worksheet
    > > Dim sh As Worksheet
    > > Dim cell As Range
    > > Dim i As Long
    > > Set this = ActiveSheet
    > > On Error Resume Next
    > > Set sh = Worksheets("FormulaeList")
    > > On Error GoTo 0
    > > If sh Is Nothing Then
    > > Set sh = Worksheets.Add
    > > sh.Name = "FormulaeList"
    > > Else
    > > sh.Cells.ClearContents
    > > End If
    > > For Each cell In this.UsedRange
    > > If cell.HasFormula Then
    > > i = i + 1
    > > sh.Cells(i, "A").Value = "'" & cell.Formula
    > > Select Case True
    > > Case cell.Formula Like "*]*"
    > > sh.Cells(i, "A").Offset(0, 1).Interior.Color = vbRed
    > > cell.Interior.Color = vbRed
    > > Case cell.Formula Like "*!*"
    > > sh.Cells(i, "A").Offset(0, 1).Interior.Color = vbBlue
    > > cell.Interior.Color = vbBlue
    > > Case Else
    > > sh.Cells(i, "A").Offset(0, 1).Interior.Color =

    vbGreen
    > > cell.Interior.Color = vbGreen
    > > End Select
    > > End If
    > > Next cell
    > > sh.Columns(1).AutoFit
    > > End Sub
    > >
    > > --
    > > HTH
    > >
    > > Bob Phillips
    > >
    > > (remove nothere from email address if mailing direct)
    > >
    > > "markx" <[email protected]> wrote in message
    > > news:uZM9%[email protected]...
    > >>
    > >>
    > >> The answer I received before was basically to put "conditional
    > >> formatting"
    > >> on cells and specify that if cell value is equal to "my value", than it
    > >> should format it in a specific way.
    > >> Of course, it works only if "my value" is the only value in the

    analysed
    > >> cell (and is not a part of a larger string), and that's the problem.
    > >>
    > >> To respond to your question, I'm really looking for something very

    > > general,
    > >> as described below (highlighting/coloring all cells where a particular
    > >> character is placed). Then, of course, I can apply it to my curret

    > > specific
    > >> needs, which are finding:
    > >> - simple formula (character "=") -> a cell responding to this condition
    > >> could be colored in green
    > >> - formula relating to another worksheet (characters "=" and "!") -> a
    > >> cell
    > >> responding to this condition could be colored in yellow
    > >> - formula relating to another workbook (characters "=", "[", "]" and
    > >> ".xls") -> a cell responding to this condition could be colored in red
    > >>
    > >> It would be also great (hope it's not too complicated) to create a new
    > >> worksheet where all these formulas are listed, f. ex. in the following
    > >> format:
    > >>
    > >> Cell Address: Formula in cell address refering to:
    > >> Sheet1!A2 '=Sheet1!B4
    > >> Sheet1!M15 '=Sheet5!F122
    > >> Sheet2!B3 '=[Other_file.xls]Sheet4!B4
    > >> Sheet4!F14 '=Sheet1!B5
    > >> Sheet6!AD12 '=Sheet1!B5
    > >>
    > >> but you can leave this last feature (it's not essential).
    > >>
    > >> Thanks for any hints,
    > >> Mark
    > >>
    > >>
    > >>
    > >>
    > >>
    > >> "Bob Phillips" <[email protected]> wrote in message
    > >> news:[email protected]...
    > >> > Mark,
    > >> >
    > >> > I don't know what answers that you got previously, but have you tried

    a
    > >> > simple UDF, like so
    > >> >
    > >> > Function IsFormula(rng As Range)
    > >> > IsFormula = rng.HasFormula
    > >> > End Function
    > >> >
    > >> >
    > >> > and use that in the CF.
    > >> >
    > >> > Or are you looking for just external reference formulae?
    > >> >
    > >> > --
    > >> > HTH
    > >> >
    > >> > Bob Phillips
    > >> >
    > >> > (remove nothere from email address if mailing direct)
    > >> >
    > >> > "markx" <[email protected]> wrote in message
    > >> > news:[email protected]...
    > >> >> Hi guys,
    > >> >>
    > >> >> Some time ago, I posted the question below, but didn't receive any
    > >> >> 100%
    > >> >> satisfactory answer. Could you take a look at this? Thanks!
    > >> >>
    > >> >> -------------
    > >> >> What is the best way to highlight (or even color) all the cells in a
    > >> >> worksheet (or even in a workbook) containing a specific character?

    For
    > >> >> exemple, I would like to make visually distinctive all the cells
    > >> > containing
    > >> >> somewhere a "?" character (or "mmm" string, or "!" mark, or "="

    sign).
    > >> >>
    > >> >> Are you aware of any special easy macro doing (and also undoing)

    this
    > >> >> kind
    > >> >> of stuff?
    > >> >> Or do you have idea how to write a special formula to put in
    > >> >> "conditionnal
    > >> >> formatting" part?
    > >> >> -------------
    > >> >> (To be more precise, I would like to find not only the cells where

    the
    > >> >> reqested sign is the only one (f. ex. "?" in cell A1="?"), but also
    > >> >> the
    > >> >> cells where this sign is one parmi others (like f. ex. finding "?"

    in
    > >> >> cell
    > >> >> A2="mxz?wptex").
    > >> >>
    > >> >> * * *
    > >> >> One of my goals is to find (through this method) all the formulas

    (as
    > >> >> they
    > >> >> contain "=" sign), references to other sheets (looking for the "!"

    > > sign)
    > >> > and
    > >> >> worksheets ("[", "]" and ".xls" signs). Please let me know if there

    is
    > >> >> any
    > >> >> other (simplier and more reliable) way to do this...
    > >> >>
    > >> >> Once again, many thanks folks!
    > >> >> Mark
    > >> >>
    > >> >>
    > >> >
    > >> >
    > >>
    > >>

    > >
    > >

    >
    >




+ Reply to Thread

Thread Information

Users Browsing this Thread

There are currently 1 users browsing this thread. (0 members and 1 guests)

Bookmarks

Posting Permissions

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

Search Engine Friendly URLs by vBSEO 3.6.0 RC 1