Introduction | Example | Tutorial | Applications
Introduction - VBA InputBox Password
Use this VBA InputBox to mask passwords. This private InputBox was originally created by Daniel Klann many years ago, but I’ll teach you how to use it. I’ll be the first to tell you, this isn’t original content. This macro has been known to the VBA community for well over a dozen years. Stay with me here!
A VBA InputBox that masks your password protects you and your users from prying eyes. You can use a private InputBox for many things, like storing a password to log onto terminal or making a user type a password before continuing your macro. Take a look!
February 2019 Update: This code has been updated so it now works on both 32-bit and 64-bit versions of Excel! The PtrSafe keyword and the VBA7 checks ensure compatibility with 64-bit machines and changing the appropriate Long variables to LongPtr prevents type mismatch errors.
I want to give special thanks to readers JustSome Guy, huhugrub, and Alexey Tseluiko for leaving comments on this article while we pieced together a 64-bit solution.
Example - VBA InputBox Password
Option Explicit
'----------------------------------
'API CONSTANTS FOR PRIVATE INPUTBOX
'----------------------------------
#If VBA7 Then
Private Declare PtrSafe Function CallNextHookEx Lib "user32" (ByVal hHook As LongPtr, _
ByVal ncode As Long, ByVal wParam As LongPtr, lParam As Any) As LongPtr
Private Declare PtrSafe Function GetModuleHandle Lib "kernel32" Alias _
"GetModuleHandleA" (ByVal lpModuleName As String) As LongPtr
Private Declare PtrSafe Function SetWindowsHookEx Lib "user32" Alias "SetWindowsHookExA" _
(ByVal idHook As Long, ByVal lpfn As LongPtr, ByVal hmod As LongPtr, ByVal dwThreadId As Long) As LongPtr
Private Declare PtrSafe Function UnhookWindowsHookEx Lib "user32" (ByVal hHook As LongPtr) As Long
Private Declare PtrSafe Function SendDlgItemMessage Lib "user32" Alias "SendDlgItemMessageA" _
(ByVal hDlg As LongPtr, ByVal nIDDlgItem As Long, ByVal wMsg As Long, ByVal wParam As LongPtr, ByVal lParam As LongPtr) As LongPtr
Private Declare PtrSafe Function GetClassName Lib "user32" Alias "GetClassNameA" _
(ByVal hwnd As LongPtr, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
Private Declare PtrSafe Function GetCurrentThreadId Lib "kernel32" () As Long
#Else
Private Declare Function CallNextHookEx Lib "user32" (ByVal hHook As Long, _
ByVal ncode As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function GetModuleHandle Lib "kernel32" Alias _
"GetModuleHandleA" (ByVal lpModuleName As String) As Long
Private Declare Function SetWindowsHookEx Lib "user32" Alias "SetWindowsHookExA" _
(ByVal idHook As Long, ByVal lpfn As Long, ByVal hmod As Long, _
ByVal dwThreadId As Long) As Long
Private Declare Function UnhookWindowsHookEx Lib "user32" (ByVal hHook As Long) As Long
Private Declare Function SendDlgItemMessage Lib "user32" Alias "SendDlgItemMessageA" _
(ByVal hDlg As Long, ByVal nIDDlgItem As Long, ByVal wMsg As Long, _
ByVal wParam As Long, ByVal lParam As Long) As Long
Private Declare Function GetClassName Lib "user32" Alias "GetClassNameA" _
(ByVal hwnd As Long, ByVal lpClassName As String, ByVal nMaxCount As Long) As Long
Private Declare Function GetCurrentThreadId Lib "kernel32" () As Long
#End If
'Constants to be used in our API functions
Private Const EM_SETPASSWORDCHAR = &HCC
Private Const WH_CBT = 5
Private Const HCBT_ACTIVATE = 5
Private Const HC_ACTION = 0
#If VBA7 Then
Private hHook As LongPtr
#Else
Private hHook As Long
#End If
'----------------------------------
'PRIVATE PASSWORDS FOR INPUTBOX
'----------------------------------
'////////////////////////////////////////////////////////////////////
'Password masked inputbox
'Allows you to hide characters entered in a VBA Inputbox.
'
'Code written by Daniel Klann
'March 2003
'64-bit modifications developed by Alexey Tseluiko
'and Ryan Wells (wellsr.com)
'February 2019
'////////////////////////////////////////////////////////////////////
#If VBA7 Then
Public Function NewProc(ByVal lngCode As Long, ByVal wParam As Long, ByVal lParam As Long) As LongPtr
#Else
Public Function NewProc(ByVal lngCode As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
#End If
Dim RetVal
Dim strClassName As String, lngBuffer As Long
If lngCode < HC_ACTION Then
NewProc = CallNextHookEx(hHook, lngCode, wParam, lParam)
Exit Function
End If
strClassName = String$(256, " ")
lngBuffer = 255
If lngCode = HCBT_ACTIVATE Then 'A window has been activated
RetVal = GetClassName(wParam, strClassName, lngBuffer)
If Left$(strClassName, RetVal) = "#32770" Then
'This changes the edit control so that it display the password character *.
'You can change the Asc("*") as you please.
SendDlgItemMessage wParam, &H1324, EM_SETPASSWORDCHAR, asc("*"), &H0
End If
End If
'This line will ensure that any other hooks that may be in place are
'called correctly.
CallNextHookEx hHook, lngCode, wParam, lParam
End Function
Function InputBoxDK(Prompt, Title) As String
#If VBA7 Then
Dim lngModHwnd As LongPtr
#Else
Dim lngModHwnd As Long
#End If
Dim lngThreadID As Long
lngThreadID = GetCurrentThreadId
lngModHwnd = GetModuleHandle(vbNullString)
hHook = SetWindowsHookEx(WH_CBT, AddressOf NewProc, lngModHwnd, lngThreadID)
InputBoxDK = InputBox(Prompt, Title)
UnhookWindowsHookEx hHook
End Function
Make powerful macros with our free VBA Developer Kit It’s easy to copy and paste a macro like this, but it’s harder make one on your own. To help you make macros like this, we built a free VBA Developer Kit and wrote the Big Book of Excel VBA Macros full of hundreds of pre-built macros to help you master file I/O, arrays, strings and more - grab your free copy below.
Tutorial - VBA InputBox Password
There are a lot of moving parts in the private InputBox macro above. Fortunuately, you won’t have to modify it much. Daniel Klann did a good job providing comments just in case you do want to change a few things. The only thing you may want to change is the masking character. By default, it’s set to an asterisk - which I like - but you can change the masking character by modifying the character inside the quotes in Asc("*")
.
Normally, you would call an InputBox by typing InputBox in your VBA editor. To call this awesome password masking InputBox, you’ll type InputBoxDK. The DK, of course, is a shoutout to the original developer, Daniel Klann. He did a great job developing this InputBox in the early 2000s and deserves all the credit.
Check if Cancel is Pressed or Password is Blank
Here’s an example of how to use the macro. This VBA code sample looks to see if a password is entered or if the cancel button is pressed.
Sub Demo()
101:
x = InputBoxDK("Enter your Password.", "Password Required")
If StrPtr(x) = 0 Then
'Cancel pressed
Exit Sub
ElseIf x = "" Then
MsgBox "Please enter a password"
GoTo 101:
Else
'Ok pressed
'Continue with your macro.
'Password is stored in the variable "x"
End If
End Sub
When you run this macro, an InputBox will appear. The InputBox looks like a normal InputBox until you start typing. Once you type, your text will be replaced with your masking character.
Check for Correct Password
This is a neat VBA macro that prevents a user from progressing through your macro until he/she types your secret password! Your user is given 3 chances to type the right password,
Sub Demo2()
101:
x = InputBoxDK("Enter your Password.", "Password Required")
If x = "MyPassword" Then
'Success!
'Continue with your macro because the user typed the correct macro
MsgBox "Welcome!"
Else
If i <= 1 Then
MsgBox "Invalid Password. Try again"
i = i + 1
GoTo 101:
Else
MsgBox "Incorrect password entered too many times. Try again later."
Exit Sub
End If
End If
End Sub
Application Ideas - VBA InputBox Password
Like I said in the introduction, you can use a private InputBox for many things. I use it to programmatically allow users to automate interactions with FTP servers or Linux terminals without blasting their passwords publicly all over their screens.
My second example shows how to prevent unauthorized users from running a macro on your Excel spreadsheet. It’s not meant to be a secure means of preventing unauthorized runs. It’s just supposed to slow people down and give them a minute to think “do I really want to run this?”
That’s all for this tutorial. When you’re ready to take your VBA to the next level, subscribe using the form below.