Introduction | Example | Tutorial | Applications

Introduction - Fade UserForm

Fade your VBA UserForm in and out with the macros in this tutorial. This VBA tutorial will also teach you how to force your userform to appear partially transparent. In other words, you’ll be able to customize the opacity of your VBA userforms.

This macro is similar to the one I used to set a transparent userform color last year and it’s great for making your own Excel Splash Screens. Thanks to one of our readers, Freeman, the macro now lets you fade userforms in and out on both 32-bit and 64-bit machines.


Example - Fade UserForm

'PLACE IN YOUR USERFORM CODE
Option Explicit
#If VBA7 Then
Private Declare PtrSafe Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As LongPtr
Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As LongPtr, ByVal nIndex As Long) As Long
Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As LongPtr, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Private Declare PtrSafe Function DrawMenuBar Lib "user32" (ByVal hwnd As LongPtr) As Long
Private Declare PtrSafe Function SetLayeredWindowAttributes Lib "user32" (ByVal hwnd As LongPtr, ByVal crKey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long 
#Else
Private Declare Function FindWindow Lib "user32" _
    Alias "FindWindowA" ( _
    ByVal lpClassName As String, _
    ByVal lpWindowName As String) As Long
                       
Private Declare Function GetWindowLong Lib "user32" _
    Alias "GetWindowLongA" ( _
    ByVal hwnd As Long, _
    ByVal nIndex As Long) As Long
 
Private Declare Function SetWindowLong Lib "user32" _
    Alias "SetWindowLongA" ( _
    ByVal hwnd As Long, _
    ByVal nIndex As Long, _
    ByVal dwNewLong As Long) As Long
 
Private Declare Function DrawMenuBar Lib "user32" ( _
    ByVal hwnd As Long) As Long
 
Private Declare Function SetLayeredWindowAttributes Lib "user32" ( _
                ByVal hwnd As Long, _
                ByVal crKey As Long, _
                ByVal bAlpha As Byte, _
                ByVal dwFlags As Long) As Long

#End If
'Constants for title bar
Private Const GWL_STYLE As Long = (-16)           'The offset of a window's style
Private Const GWL_EXSTYLE As Long = (-20)         'The offset of a window's extended style
Private Const WS_CAPTION As Long = &HC00000

'Style to add a titlebar
Private Const WS_EX_DLGMODALFRAME As Long = &H1   'Controls if the window has an icon
 
'Constants for transparency
Private Const WS_EX_LAYERED = &H80000
Private Const LWA_COLORKEY = &H1                  'Chroma key for fading a certain color on your Form
Private Const LWA_ALPHA = &H2                     'Only needed if you want to fade the entire userform

'sleep
#If VBA7 Then
    Private Declare PtrSafe Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As LongPtr) 'For 64-Bit versions of Excel
    Dim formhandle As LongPtr
#Else
    Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long) 'For 32-Bit versions of Excel
    Dim formhandle As Long
#End If

Private Sub UserForm_Initialize()
'force the form to fully transparent before it even loads
formhandle = FindWindow(vbNullString, Me.Caption)
SetWindowLong formhandle, GWL_EXSTYLE, GetWindowLong(formhandle, GWL_EXSTYLE) Or WS_EX_LAYERED
SetOpacity (0)
End Sub

Private Sub UserForm_Activate()
'HideTitleBarAndBorder Me 'hide the titlebar and border
FadeUserform Me, True 'Fade your userform in
End Sub
 
Private Sub UserForm_QueryClose(Cancel As Integer, CloseMode As Integer)
FadeUserform Me, False 'Fade your userform in
End Sub

Sub FadeUserform(frm As Object, Optional FadeIn As Boolean = True)
'Defaults to fade your userform in.
'Set the 2nd argument to False to Fade Out.
Dim iOpacity As Integer
 
formhandle = FindWindow(vbNullString, Me.Caption)
 
SetWindowLong formhandle, GWL_EXSTYLE, GetWindowLong(formhandle, GWL_EXSTYLE) Or WS_EX_LAYERED
'The following line sets the userform opacity equal to whatever value you have in iOpacity (0 to 255).
If FadeIn = True Then 'fade in
    For iOpacity = 0 To 255 Step 15
        Call SetOpacity(iOpacity)
    Next
Else 'fade out
    For iOpacity = 255 To 0 Step -15
        Call SetOpacity(iOpacity)
    Next
    Unload Me 'unload form once faded out
End If
End Sub
 
Sub SetOpacity(Opacity As Integer)
        SetLayeredWindowAttributes formhandle, Me.BackColor, Opacity, LWA_ALPHA
        Me.Repaint
Sleep 50
End Sub

Sub HideTitleBarAndBorder(frm As Object)
'Hide title bar and border around userform
'Source: https://wellsr.com/vba/2017/excel/remove-window-border-title-bar-around-userform-vba/
#If VBA7 Then
    Dim lFrmHdl As LongPtr
#Else
    Dim lFrmHdl As Long
#End If
    Dim lngWindow As Long
    lFrmHdl = FindWindow(vbNullString, frm.Caption)
'Build window and set window until you remove the caption, title bar and frame around the window
    lngWindow = GetWindowLong(lFrmHdl, GWL_STYLE)
    lngWindow = lngWindow And (Not WS_CAPTION)
    SetWindowLong lFrmHdl, GWL_STYLE, lngWindow
    lngWindow = GetWindowLong(lFrmHdl, GWL_EXSTYLE)
    lngWindow = lngWindow And Not WS_EX_DLGMODALFRAME
    SetWindowLong lFrmHdl, GWL_EXSTYLE, lngWindow
    DrawMenuBar lFrmHdl
End Sub

Tutorial - Fade UserForm

All you have to do is copy and paste the macro above into your Userform and it will fade in when it’s loaded and fade out when it’s closed. The secret is in the FadeUserform macro. The macro accepts two arguments: your userform object and a boolean representing whether you want to fade in or fade out. To call it, all you have to do is type:

FadeUserform Me, False 'to fade out

to fade out or type:

FadeUserform Me, True 'to fade in

to fade in.

You would enter that code somewhere in your actual userform module. All this is done for you in the example macro, but keep reading if you want to learn more about how it works.

Step 1: Create your UserForm

If you made it this far, you probably already have a UserForm designed. If not, go ahead and do it now.

I’m going to make a simple UserForm with a title and three buttons, like this:

UserForm Design

[Optional] ShowModal UserForms

If you want your user to be able to click around your spreadsheet while your UserForm is displayed, you’ll need to set the ShowModal property of your UserForm to false. I’m not going to do this in my form, but I have a full tutorial explaining the ShowModal property if you’re interesed.


Step 2: Add the Macros

Right-click your UserForm and select “View Code.” Copy and paste the example macro into the UserForm code block.

The macro I included is a lot longer than it has to be if the only thing you wanted to do was fade your userform in and out. That’s because I gave you the option to hide the title bar around your Userform when it’s displayed. If you want to enable this feature, just uncomment the following line in the UserForm_Activate routine:

'HideTitleBarAndBorder Me

Uncommenting this line will give you a clean userform without a distracting border and red X. I’m not going to do that in this tutorial, but you can!


Step 3: Launch UserForm

Here’s where you get to see all your hard work pay off. Launch your UserForm by pressing F5 or hitting the play button in your Visual Basic Editor. The userform should slowly fade in.

When you’re ready to close your userform, it will fade out. Note: If you hid the title bar and border, you’ll have to click the userform and hit Alt-F4 to exit the form unless you already have an unload me button.

Here’s what my userform looks like when it’s launched and closed:

Fade UserForm Animation


Bonus Step: Setting Custom Transparency

Instead of fading your userform in and out, you may just want to display it partially transparent. For example, you may want your form to just sit there at 50% opacity. I developed the example macro so it’s easy for you to do just that.

First, you’ll want to comment out the FadeUserform Me line in your UserForm_Activate and your UserForm_QueryClose routines.

Then, you’ll add the following lines to wherever you want to set your opacity:

formhandle = FindWindow(vbNullString, Me.Caption)
SetWindowLong formhandle, GWL_EXSTYLE, GetWindowLong(formhandle, GWL_EXSTYLE) Or WS_EX_LAYERED
SetOpacity (128) 'ranges from 0 (fully transparent) to 255 (fully opaque)

I like to place it in the UserForm_Initialize routine.

The SetOpacity line is the important one. The opacity of your userform can vary from 0 to 255, where 0 is fully transparent and 255 is fully opaque. I chose 128 because it’s about 50% transparent. Here’s what my partially transparent userform looks like:

Partially Transparent UserForm


Application Ideas

Fading userforms with hidden borders is a surefire way to improve your Excel Splash Screens. I also use them to make little wizard guides for users. These guides are slightly transparent nonmodal userforms that pop up in certain spots on the screen with instructions for users if they appear to be having trouble.

I’m sure you can think of even better uses for fading your userforms in and fading them out.

This was an impressive tutorial, but we’re just getting started. When you’re ready to take your VBA to the next level, subscribe using the form below.