We’ve published quite a few tutorials showing how to play audio from Excel. For example, our VBA Beep Sound on Error tutorial described adding VBA’s Beep statement in a macro to provide an audible signal when an On Error error-handler is activated. Another tutorial discussed Excel’s Application.Speech.Speak to make Excel talk. We even published a tutorial showing how to use VBA to control your computer’s volume with the Windows’ keybd_event for volume control.
This tutorial will discuss Windows’ PlaySound function, which is introduced in this Microsoft article. PlaySound can be used to play standard system sounds such as the Exclamation sound or the Question sound; it will also play any waveform-audio (WAV) file such as Tada.wav. We will develop an Excel user-defined function (UDF) named BeepThis2 to enable these sounds based on spreadsheet results. If you’re new to custom functions, I encourage you to read our VBA User-Defined Functions tutorial to help you get starting with your own UDFs.
Basic BeepThis1 UDF
Previous tutorials have used VBA’s Beep statement in a macro or Sub procedure. Here is a simple user-defined function named Beep sound whenever it is part of a cell’s formula that requires calculation. The Beep sound is referred to as “Default Beep” in the Windows’ Control Panel > Sound menu.
Public Function BeepThis1(Optional ByVal ThisSound As String = "Beep" _
, Optional ByVal ThisValue As Variant) As Variant
If IsMissing(ThisValue) Then ThisValue = ThisSound
BeepThis1 = ThisValue
Beep
End FunctionThe Optional which means they do not have to be expressed when the function is called from a VBA procedure or used in a cell formula. Both arguments are also declared ByVal which means only their value is passed to the function; reassignment of ByVal arguments within a function will have no effect outside of the function. If ByVal was not included, the default ByRef would apply; changes made to a ByRef argument within the function are duplicated in the procedure that called the function. Choosing ByVal or ByRef does not usually matter when the function is used in a cell formula, but it could be important if the function is called from a VBA procedure.
The IsMissing function determines whether an Optional argument (which must be Variant) was passed to the function. Since Variant it can return a variety of results. Here are some cell formula examples illustrating use of the
=BeepThis1()
=BeepThis1(,A1)
=BeepThis1(,A1<0)
=BeepThis1(,SUM(A1:A4))
="Day #"&BeepThis1(,WEEKDAY(TODAY(),2))
=IF(WEEKDAY(TODAY(),2)>5,BeepThis1(,"Weekend"),"Workday")Notice the first argument is never entered in any of these examples. Again, that’s because we plan on using the first argument in our
BeepThis2 UDF With System Sounds and WAV Files
The Windows’ PlaySound function can play system sounds (also known as “Program Events”) presented in the table below.
The table’s first column identifies the first argument of our BeepThis2 function. Each sound corresponds to a WAV file normally located in the Windows\Media folder.
All these sounds (plus others) can be modified by navigating to Control Panel > Sound and editing the sound corresponding to the table’s second column. (The Sound control panel applet is also opened by Settings > Personalization > Themes > Sounds or by right-clicking the Taskbar’s speaker icon and picking Sounds.)
The sound data is stored in Registry keys that begin with HKCU\AppEvents\Schemes\Apps\.Default. Each key is identified by the table’s third column.
In addition to playing system sounds, the VBA PlaySound function can also play any WAV file when given a full filepath.
| VBA UDF |
Program Event | AppEvent |
|---|---|---|
| Beep | Default Beep | .Default |
| Asterisk | Asterisk | SystemAsterisk |
| Exclamation | Exclamation | SystemExclamation |
| Hand | Critical Stop | SystemHand |
| Notification | System Notification | SystemNotification |
| Question | Question | SystemQuestion |
| Connect | Device Connect | DeviceConnect |
| Disconnect | Device Disconnect | DeviceDisconnect |
| Fail | Device Failed | DeviceFail |
| New Mail | Notification.Mail | |
| Reminder | Calendar Reminder | Notification.Reminder |
| Text | New Text Message | Notification.SMS |
| Message | Instant Message | Notification.IM |
| Fax | New Fax | FaxBeep |
| Select | Select | CCSelect |
| Error | Program Error | AppGPFault |
| Close | Close Program | Close |
| Maximize | Maximize | Maximize |
| Minimize | Minimize | Minimize |
| Open | Open Program | Open |
| Default | Default Beep | .Default |
The PlaySound function is available in a dynamic-link library (DLL); therefore, we must use VBA’s Declare statement along with related global constants before any Sub or Function statement in our VBAProject’s module. Here’s our full UDF for playing sounds with VBA:
#If VBA7 Then
Public Declare PtrSafe Function PlaySound Lib "winmm.dll" Alias "PlaySoundA" _
(ByVal lpszName As String, ByVal hModule As LongPtr, ByVal dwFlags As Long) As Long
#Else
Public Declare Function PlaySound Lib "winmm.dll" Alias "PlaySoundA" _
(ByVal lpszName As String, ByVal hModule As Long, ByVal dwFlags As Long) As Long
#End If
Const SND_SYNC = &H0 ' wait for sound to play
Const SND_ASYNC = &H1 ' no wait
Const SND_NODEFAULT = &H2 ' no default sound on error
Const SND_NOSTOP = &H10 ' skip sound if another is playing
Const SND_ALIAS = &H10000 ' play system sound
Const SND_FILENAME = &H20000 ' play WAV file
Public Function BeepThis2(Optional ByVal ThisSound As String = "Beep" _
, Optional ByVal ThisValue As Variant _
, Optional ByVal ThisCount As Integer = 1 _
, Optional ByVal Wait As Boolean = False) As Variant
Dim sPath As String, flags As Long
Const sMedia As String = "\Media\"
If IsMissing(ThisValue) Then ThisValue = ThisSound
BeepThis2 = ThisValue ' return value
If ThisCount > 1 Then Wait = True
flags = SND_ALIAS
sPath = StrConv(ThisSound, vbProperCase)
Select Case sPath
Case "Beep"
Beep ' ignore ThisCount and Wait
Exit Function
Case "Asterisk", "Exclamation", "Hand", "Notification", "Question"
sPath = "System" + sPath
Case "Connect", "Disconnect", "Fail"
sPath = "Device" + sPath
Case "Mail", "Reminder"
sPath = "Notification." + sPath
Case "Text"
sPath = "Notification.SMS"
Case "Message"
sPath = "Notification.IM"
Case "Fax"
sPath = "FaxBeep"
Case "Select"
sPath = "CCSelect"
Case "Error"
sPath = "AppGPFault"
Case "Close", "Maximize", "Minimize", "Open"
' ok
Case "Default"
sPath = "." & sPath
Case "Chimes", "Chord", "Ding", "Notify", "Recycle", "Ringout", "Tada"
sPath = Environ("SystemRoot") & sMedia & sPath & ".wav"
flags = SND_FILENAME
Case Else
If LCase(Right(ThisSound, 4)) <> ".wav" Then ThisSound = ThisSound & ".wav"
sPath = ThisSound
If Dir(sPath) = "" Then ' file is not in working directory
sPath = ActiveWorkbook.Path & "\" & ThisSound
If Dir(sPath) = "" Then sPath = Environ("SystemRoot") & sMedia & ThisSound
End If
flags = SND_FILENAME
End Select
flags = flags + IIf(Wait, SND_SYNC, SND_ASYNC)
Do While ThisCount > 0 ' skip if ThisCount < 1
PlaySound sPath, 0, flags ' if error, .Default sound will play
ThisCount = ThisCount - 1
Loop
End FunctionMake 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.
Explaining the BeepThis2 Function
All four arguments are Optional in our BeepThis2 function. Just like our simplified BeepThis1 function from earlier, the first argument
When the Boolean fourth argument False (its default value), the BeepThis2 function will return as soon as PlaySound has started playing your sound. This is called asynchronous playing. Setting this argument to True will force the function to wait until PlaySound has finished playing the sound Wait is forced to True whenever ThisCount>1, so be careful when using the PlaySound function will not play if ThisCount<1.
We made this UDF so the BeepThis1 function from earlier.
The table above indicates
Any other WAV file can also be specified; in this case, “.wav” will automatically be appended if you forgot. If the file’s complete path is not defined by Environ("SystemRoot") returns the %SystemRoot% environment varaible, which is normally C:\Windows. (If necessary, the PlaySound function might also search for the file in the Windows directory, the Windows system directory, directories listed in the %PATH% environment variable, and the list of directories mapped in a network.)
Notice the second argument when calling the PlaySound function. This argument must be equal to zero. Its third argument flags must be SND_ALIAS for system sounds or SND_FILENAME for WAV files. VBA’s IIf function works like Excel’s IF function to add SND_SYNC for wait or SND_ASYNCH for no wait. If the PlaySound will instead play the default system sound (Default Beep). You can avoid this behavior by adding SND_NODEFAULT to the flags variable. Feel free to give it a shot!
Using BeepThis2 to play sounds with VBA
Here are some cell formula examples illustrating how to use the BeepThis2 function to play sounds using VBA.
=BeepThis2()
=BeepThis2(,"Once",10)
=IF(A1<0,BeepThis2("HAND","A1<0",,TRUE),BeepThis2("reminder"))
="Total="&BeepThis2("Notify",SUM(A1:A4),,TRUE)
=IF(WEEKDAY(TODAY(),2)>5,BeepThis2("tada","Weekend",2),BeepThis2("chord","Workday"))
=BeepThis2("Windows Logon","Welcome",,TRUE)No sound is played unless the cell’s formula is recalculated and ThisCount>0 or ThisSound is “Beep” (the default). Since Excel’s TODAY function is Volatile, the 5th example will be recalculated whenever any other cell is calculated. Also notice the last calculated BeepThis2 will interrupt any other call to the BeepThis2 function with ThisCount=1 and Wait=False (the default values); this can be prevented by adding SND_NOSTOP to the flags variable.
Final Thoughts
If you decide to include BeepThis2 in your Personal Macro Workbook (PERSONAL.XLSB) or in a Custom Excel Add-In (XLAM), consider adding details to Excel’s Insert Function dialog as described in our VBA MacroOptions tutorial. Some of the arguments may be hard to remember, so the visual cue that MacroOptions provides can certainly be helpful.
If you’re serious about writing macros, subscribe for more VBA tips. Simply fill out the form below and we’ll share our best time-saving VBA tips.

