Splash Screen - danielep71/VBA-PERFORMANCE GitHub Wiki

Home


Splash screens are typically to notify the user that the program is in the process of loading.

They provide feedback that a lengthy process is underway. Occasionally, a progress bar within the splash screen indicates the loading progress.

A splash screen disappears when the application's main window appears.

Excel itself, as well as all MS Office products, show a splash screen. Below you can find the appearance of MS Excel splash screen until 2000.

image

Splash screens typically serve to enhance the look and feel of an application hence they are often visually appealing. They may also have animations, graphics, and sound.

The splash screen must appear when Excel first starts showing the splash user form in the Workbook Open event.

Private Sub Workbook_Open()
    FrmSplash.Show
End Sub

FrmSplash is the name of the form that you want to display.

Normally, in a splash screen it is common to find:

  • a logo;
  • the title of the project;
  • the developer name or the developer company;
  • a copyright year;
  • a link to your website;
  • sometimes hardware and user’s information;
  • a label at the bottom used to update the status (e.g., “Loading data…”, “Creating Forms…”, “Opening…”,…).

The following code displays the splash screen UserForm:

  • It first disables keyboard input.
  • Next the code creates the form
  • sets the form's public TaskDone variable to False,
  • and displays the form non-modally.
  • It then enters a loop where it simulates a long task.
  • Each time through the outer loop, the code updates the form's progress bar prgStatus so the user can see that the program is doing something.
  • After the task is complete, the code sets the form's TaskDone variable to True and closes the form.

It then re-enables keyboard input.

Private Sub cmdShowSplash_Click()
    Dim frm As frmSplash
    Dim i As Integer
    Dim j As Integer

'Deactivate the keyboard
    Application.OnKey "^d", "KeyboardOn"
    Application.DataEntryMode = True

'Display the splash form non-modally
    Set frm = New frmSplash
    frm.TaskDone = False
    frm.prgStatus.Value = 0
    frm.Show False

'Perform the long task
    For i = 0 To 100 Step 10
        frm.prgStatus.Value = i
    'Waste some time.
        For j = 1 To 1000
            DoEvents
        Next j
    Next i
' Close the splash form
    frm.TaskDone = True
    Unload frm
' Re-activate the keyboard
    Application.DataEntryMode = False
End Sub

The UserForm contains the following code. Variables TaskDone indicates whether the long task is complete. The QueryClose event handler uses it to decide whether it should allow the form to close.

'Set true when the long task is done.    
    Public TaskDone As Boolean
Private Sub UserForm_QueryClose(Cancel As Integer, _
    CloseMode As Integer)
    Cancel = Not TaskDone
End Sub

To make the splash screen look more professional, you can remove the title bar, which contains the title of the window, and the close button, as well as remove the border that surrounds the form.

Note: before you do this, you must have a way to close the form, either by placing a close button on the form, making a click-event that closes the form or by having the form auto-close after so many seconds.

#If VBA7 Then
    Public Declare PtrSafe Function FindWindow Lib "user32" _
            Alias "FindWindowA" _
           (ByVal lpClassName As String, _
            ByVal lpWindowName As String) As LongPtr

    Public Declare PtrSafe Function GetWindowLong Lib "user32" _
            Alias "GetWindowLongA" _
           (ByVal hWnd As Long, _
            ByVal nIndex As Long) As LongPtr

    Public Declare PtrSafe Function SetWindowLong Lib "user32" _
            Alias "SetWindowLongA" _
           (ByVal hWnd As Long, _
            ByVal nIndex As Long, _
            ByVal dwNewLong As Long) As LongPtr

    Public Declare PtrSafe Function DrawMenuBar Lib "user32" _
           (ByVal hWnd As Long) As LongPtr
#Else
    Public Declare Function FindWindow Lib "user32" _
            Alias "FindWindowA" _
           (ByVal lpClassName As String, _
            ByVal lpWindowName As String) As Long

    Public Declare Function GetWindowLong Lib "user32" _
            Alias "GetWindowLongA" _
           (ByVal hWnd As Long, _
            ByVal nIndex As Long) As Long

    Public Declare Function SetWindowLong Lib "user32" _
            Alias "SetWindowLongA" _
           (ByVal hWnd As Long, _
            ByVal nIndex As Long, _
            ByVal dwNewLong As Long) As Long

    Public Declare Function DrawMenuBar Lib "user32" _
           (ByVal hWnd As Long) As Long
#End If

Sub HideBar(frm As Object)

    Dim Style As Long
    Dim Menu As Long
    Dim hWndForm As Long

    hWndForm = FindWindow("ThunderDFrame", frm.Caption)
    Style = GetWindowLong(hWndForm, &HFFF0)
    Style = Style And Not &HC00000
    SetWindowLong hWndForm, &HFFF0, Style
    DrawMenuBar hWndForm

End Sub

Home