Change your VBA MsgBox text color by using the SetSysColors user32 API function. This macro example makes changing your MsgBox text color extremely easy.

I’m going to be honest with you. I didn’t know you could change the MsgBox text color until wellsrPRO community member Giancarlo submitted this macro to me via the wellsrPRO Excel Add-in. This is why I love user-generated content! We can all learn a lot more from each other than we can by ourselves. That’s why I keep saying wellsrPRO is the new best way to learn VBA.


Reader’s Note: The macro in this article was submitted by a member of my incredible wellsrPRO community. If you’re an existing wellsrPRO member, don’t forget to submit your own macros to the wellsrPRO community using the Share My Macros button. wellsrPRO users can automatically import this community submission, and all other community submissions, directly into their spreadsheet. Just look for “Community Submissions” in the Auto-Import dropdown menu.


Change VBA MsgBox Text Color

Submitted by Giancarlo

Option Explicit

#If Win64 Then
    Private Declare PtrSafe Function GetSysColor Lib "user32" _
        (ByVal nIndex As Long) As Long
    Private Declare PtrSafe Function SetSysColors Lib "user32" _
        (ByVal nChanges As Long, lpSysColor As Long, lpColorValues As Long) As Long
#Else
    Private Declare Function GetSysColor Lib "user32" _
        (ByVal nIndex As Long) As Long
    Private Declare Function SetSysColors Lib "user32" _
        (ByVal nChanges As Long, lpSysColor As Long, lpColorValues As Long) As Long
#End If

Private Const COLOR_WINDOWTEXT As Long = 8
Private Const CHANGE_INDEX As Long = 1

Public Sub MsgBoxColorDemo()
   Dim defaultColour As Long

   'Store the default system color
   defaultColour = GetSysColor(COLOR_WINDOWTEXT)

   'Set system color to red
   SetSysColors CHANGE_INDEX, COLOR_WINDOWTEXT, vbRed
   MsgBox "Incorrect", vbCritical, "Your result is..."

   'Set system color to green
   SetSysColors CHANGE_INDEX, COLOR_WINDOWTEXT, RGB(0, 128, 0)
   MsgBox "Correct", , "Your result is..."
   
   'Restore default value
   SetSysColors CHANGE_INDEX, COLOR_WINDOWTEXT, defaultColour

End Sub

Make powerful macros with our free VBA Developer Kit

This is actually pretty neat. If you have trouble understanding or remembering it, our free VBA Developer Kit can help. It’s loaded with VBA shortcuts to help you make your own macros like this one - we’ll send a copy, along with our Big Book of Excel VBA Macros, to your email address below.

I'll take a free VBA Developer Kit

This macro changes your MsgBox text color by temporarily changing your window text default color. It does this by using the SetSysColors API function from the user32 library.

The macro changes your text to red at first using the vbRed color constant. It then changes your text to green using the RGB function. The ability to use the RGB function means you can set the color to whatever you want!

To prove you’re really changing the system text color, let’s run the macro and open up a notepad with some text typed out. You’ll see that when your MsgBox text is red, your notepad text is red, too.

Windows System Text Color

You’ll also see the text in your VBA editor and in Excel change. In other words, when you change the text color of your MsgBox, the color of almost anything with typed out windows text will temporarily change with it.

That’s why it’s important to change your system color back to the default value when you’re done. You don’t want to type in red or green text, do you?

If you noticed, the macro stored the starting text color into variable defaultColour. After changing colors a couple times, the macro restores back to this default value by setting it back to whatever it was when it first started the macro. In case you forget to change back to the default color, the standard windows default text color is black, so just set it to vbBlack using the SetSysColors function.

That’s all for this tutorial. When you’re ready to take your VBA to the next level, subscribe using the form below.