Did you know you can use VBA to control your computers speakers? This tutorial shows you how to mute and unmute your volume and turn your volume up and down all by using VBA.
Volume control is a good skill to have when you have a macro that makes Excel talk with VBA.
At the end of this VBA tutorial, I’ll show you an obnoxious macro you can make that takes advantage of volume control. Oh, imagine the fun possibilities!
Control your Volume with VBA
Option Explicit
Const VK_VOLUME_MUTE = &HAD
Const VK_VOLUME_DOWN = &HAE
Const VK_VOLUME_UP = &HAF
#If VBA7 Then
Private Declare PtrSafe Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)
#Else
Private Declare Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)
#End If
Sub VolUp()
keybd_event VK_VOLUME_UP, 0, 1, 0
keybd_event VK_VOLUME_UP, 0, 3, 0
End Sub
Sub VolDown()
keybd_event VK_VOLUME_DOWN, 0, 1, 0
keybd_event VK_VOLUME_DOWN, 0, 3, 0
End Sub
Sub VolToggle()
keybd_event VK_VOLUME_MUTE, 0, 1, 0
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.
How to use the Volume Control Macros
Copy and paste the example above to the top of a module in Excel. There are 3 unique macros in the example, each performing a different volume control function.
- VolUp - turns the volume up on your computer a little at a time
- VolDown - turns the volume down on your computer a little at a time
- VolToggle - A toggle to mute and unmute your computer
Anytime you want to change the volume settings on your computer, you would just call one of the macros. Here’s an example to turn your volume up slightly:
Sub ControlMyVolume()
'turn your volume up (Call keyword is optional)
Call VolUp
End Sub
Turn volume all the way up with VBA
If you’re feeling devious, you can turn your volume (or someone elses volume!) all the way up by running the following macro:
Sub MaximumVolume()
Dim i As Integer
For i = 1 To 100
Call VolUp
Next i
End Sub
It throws the
Turn volume all the way down with VBA
You can do the same thing to turn your volume all the way down:
Sub MinimumVolume()
Dim i As Integer
For i = 1 To 100
Call VolDown
Next i
End Sub
Because the mute button is a toggle command, it gets a little complicated to tell whether or not your computer is muted or unmuted. Calling the
That’s why I prefer to mute my computer using VBA by forcing my volume all the way down instead of relying on the Toggle feature.
Turn Volume Up and Prevent User from Turning it down
You ready for the grand finale? Let’s combine everything we learned to make one seriously annoying macro. This is probably the most annoying piece of VBA I’ve ever written.
Copy and paste the macros below into an Excel Module and run the
Option Explicit
Const VK_VOLUME_MUTE = &HAD
Const VK_VOLUME_DOWN = &HAE
Const VK_VOLUME_UP = &HAF
#If VBA7 Then
Private Declare PtrSafe Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)
Private Declare PtrSafe Function GetTickCount Lib "kernel32" () As Long
#Else
Private Declare Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)
Private Declare Function GetTickCount Lib "kernel32" () As Long
#End If
Sub SongThatNeverEnds()
Dim i As Integer
Call PumpUpTheVolume
Application.Speech.Speak "This is the song that never ends, yes it goes on and on my friend. Some people started singing it, not knowing what it was, and they'll continue singing it forever just because..." & _
"This is the song that never ends, yes it goes on and on my friend. Some people started singing it, not knowing what it was, and they'll continue singing it forever just because..." & _
"This is the song that never ends, yes it goes on and on my friend. Some people started singing it, not knowing what it was, and they'll continue singing it forever just because..." & _
"This is the song that never ends, yes it goes on and on my friend. Some people started singing it, not knowing what it was, and they'll continue singing it forever just because..." & _
"This is the song that never ends, yes it goes on and on my friend. Some people started singing it, not knowing what it was, and they'll continue singing it forever just because..." & _
"This is the song that never ends, yes it goes on and on my friend. Some people started singing it, not knowing what it was, and they'll continue singing it forever just because..." _
, SpeakAsync:=True
For i = 1 To 6
Call DoNothing(10)
Call PumpUpTheVolume
Next i
End Sub
Sub PumpUpTheVolume()
DoEvents
Call MinimumVolume
Call MaximumVolume
End Sub
Sub DoNothing(Finish As Long)
Dim NowTick As Long
Dim EndTick As Long
EndTick = GetTickCount + (Finish * 1000)
Do
NowTick = GetTickCount
DoEvents
Loop Until NowTick >= EndTick
End Sub
Sub MaximumVolume()
Dim i As Integer
For i = 1 To 100
Call VolUp
Next i
End Sub
Sub MinimumVolume()
Dim i As Integer
For i = 1 To 100
Call VolDown
Next i
End Sub
Sub VolUp()
keybd_event VK_VOLUME_UP, 0, 1, 0
keybd_event VK_VOLUME_UP, 0, 3, 0
End Sub
Sub VolDown()
keybd_event VK_VOLUME_DOWN, 0, 1, 0
keybd_event VK_VOLUME_DOWN, 0, 3, 0
End Sub
Sub VolToggle()
keybd_event VK_VOLUME_MUTE, 0, 1, 0
End Sub
If you haven’t guessed by now, this turns the volume all the way up on your speakers and plays the “this is the song that never ends” song. Every 10 seconds, the macro will turn the volume all the way down on your computer and turn it all the way back up. That way, even if your coworker mutes his or her computer, the macro wins in the end and starts to annoy them all over again!
Don’t worry. Unlike the song, this macro eventually ends! It only lasts about one minute.
Still, use it at your own peril. I’m not responsible for your loss of friends after you trick them with this…
If you haven’t already done so, join our VBA Insiders using the form below. After that, share this article on social media and follow me on Twitter for even more great VBA content.