Results 1 to 6 of 6

Thread: VBA to show text "Enter Text Here" in excel cell

  1. #1
    Member
    Join Date
    May 2020
    Posts
    66
    Rep Power
    5

    VBA to show text "Enter Text Here" in excel cell

    I want to show "Enter Text Here" in fade color in a cell, say C5, when it is empty.

    As per my knowledge, it can't be done by Conditional Formatting.

    One way I found is to create a transperent Text Box Mask linked with other cell. But masking text box is time consuming, especially if I have more than 10 cells to show the text.

    Is there any VBA code to solve this problem??

  2. #2
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,385
    Rep Power
    10
    Hi
    I am not sure if I understand fully what it is that you want…
    ( I do not know what a “Text Box Mask linked with other cell” is )

    It would be quite easy in VBA to use an Event type coding similar to what you have seen before to make a cell have a particular text in the case that it gets changed to being empty.

    For me personally, the only problem in such coding is the cell formatting syntax, since I can never remember all the different color and format options.

    So my start point would be to record a macro ( https://de.lmgtfy.com/?q=vba+using+the+macro+recorder
    https://de.lmgtfy.com/?q=using+the+m...hindi+tutorial
    )
    whilst putting text as I want in an arbitrary cell

    For example, I recorded a macro whilst putting in some text in a cell , first by pasting it in, and then by wriring it in. In both cases I changed the text color.

    This what the macro recording produced
    Code:
    Sub Macro1()
    '
    ' Macro1 Macro
        ActiveSheet.Paste
        With Selection.Font
            .ThemeColor = xlThemeColorDark1
            .TintAndShade = -0.149998474074526
        End With
    End Sub
    Sub Macro2()
    '
    ' Macro2 Macro
        Range("B1").Select
        ActiveCell.FormulaR1C1 = "Enter Text Here"
        Range("B1").Select
        With Selection.Font
            .ThemeColor = xlThemeColorDark1
            .TintAndShade = -0.149998474074526
        End With
    End Sub
    So I have now some basic formatting information

    Thinking ahead, I also may need to change the format back to normal, if text is entered into a cell. So I recorded a macro whilst doing that, and got this
    Code:
    Sub Macro3()
    '
    ' Macro3 Macro
        Range("C2").Select
        With Selection.Font
            .ColorIndex = xlAutomatic
            .TintAndShade = 0
        End With
    End Sub



    This might help you get started on coding to do what you want. This will need to go in a worksheets object code module, as you have been familiar with in the past.
    Code:
    Option Explicit
    Private Sub Worksheet_Change(ByVal Target As Range)
        If Target.Value = "" Then  '  case a cell was emptied
         Let Application.EnableEvents = False
         Let Target.Value = "Enter Text Here"
         Let Application.EnableEvents = True
            With Target.Font
            .ThemeColor = xlThemeColorDark1
            .TintAndShade = -0.149998474074526
            End With
        Else  '  case a text was entered
            With Target.Font
            .ColorIndex = xlAutomatic
            .TintAndShade = 0
            End With
        End If
    End Sub
    Alan
    Attached Files Attached Files
    Last edited by DocAElstein; 08-26-2020 at 01:14 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  3. #3
    Member
    Join Date
    May 2020
    Posts
    66
    Rep Power
    5
    Superb! Thank you!

    If I want to use the VBA for multiple cell, say B5, D9, M4 and H3, then, what change I should make in the VBA code??
    (Actually I want to use the code for more than 15 cells in a single sheet)

  4. #4
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,385
    Rep Power
    10
    Currently the macro is working on all cells.
    If you want to restrict it to just specific cells, then we have a few ways that we have done that
    For example

    Code:
    Private Sub Worksheet_Change(ByVal Target As Range)
        If Target.Address = "$B$5" Or Target.Address = "$D$9" Or Target.Address = "$M$4" Or Target.Address = "$H$3" Then
            If Target.Value = "" Then  '  case a cell was emptied
             Let Application.EnableEvents = False
             Let Target.Value = "Enter Text Here"
             Let Application.EnableEvents = True
                With Target.Font
                .ThemeColor = xlThemeColorDark1
                .TintAndShade = -0.149998474074526
                End With
            Else  '  case a text was entered
                With Target.Font
                .ColorIndex = xlAutomatic
                .TintAndShade = 0
                End With
            End If
        Else
        ' Target is Not a cell to be acted on
        End If
    End Sub
    

    Quote Originally Posted by Anshu View Post
    (Actually I want to use the code for more than 15 cells in a single sheet)
    For a lot of cells, this other way we have done before may be a bit neater
    Code:
    Private Sub Worksheet_Change(ByVal Target As Range)
        If Not Application.Intersect(Target, Range("B5,D9,M4,H3")) Is Nothing Then
            If Target.Value = "" Then  '  case a cell was emptied
             Let Application.EnableEvents = False
             Let Target.Value = "Enter Text Here"
             Let Application.EnableEvents = True
                With Target.Font
                .ThemeColor = xlThemeColorDark1
                .TintAndShade = -0.149998474074526
                End With
            Else  '  case a text was entered
                With Target.Font
                .ColorIndex = xlAutomatic
                .TintAndShade = 0
                End With
            End If
        Else
        ' Target is Not a cell to be acted on
        End If
    End Sub
    Last edited by DocAElstein; 08-31-2020 at 12:51 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  5. #5
    Member
    Join Date
    May 2020
    Posts
    66
    Rep Power
    5
    Thank you so much!!!
    This is perfectly what I was looking for.

    In between, may I know how can I mark the thread as SOLVED!

  6. #6
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,385
    Rep Power
    10
    We don't have any system of marking Threads as SOLVED at excelfox
    Just remember to tell us that a solution worked, and possibly thank all the people that helped you, as you have done here.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

Similar Threads

  1. Replies: 3
    Last Post: 11-17-2019, 11:08 PM
  2. VBA Versions of my "Get Field" and "Get Reverse Field" formulas
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 4
    Last Post: 06-02-2017, 06:15 PM
  3. Get "Reversed" Field from Delimited Text String
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 3
    Last Post: 02-22-2015, 09:01 AM
  4. Find a text substring that matches a given "pattern"
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 2
    Last Post: 02-10-2013, 06:19 AM
  5. Ordinal Suffix (i.e., "st", "nd", "rd" and "th")
    By Rick Rothstein in forum Rick Rothstein's Corner
    Replies: 0
    Last Post: 03-20-2012, 03:46 AM

Posting Permissions

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