This VBA tutorial will show you how to copy text to your clipboard, paste from your clipboard and clear the contents of your clipboard. These macros work with 32-bit versions Excel, Outlook, Word and many more Microsoft Office products.

2018 Update: This tutorial has been updated to teach you how to use VBA to copy text to your clipboard in Windows 8 and Windows 10. In this tutorial, I’ll present two solutions. The first solution uses the Microsoft Forms 2.0 Object Library to copy text to your clipboard in Windows 7 and earlier. With the rollout of Windows 8 and Windows 10, this solution no longer works reliably, so I’ve presented a second solution that uses Windows API calls to copy and paste using VBA.

Let’s take a look at the first, and oldest, solution:

Initial Setup

Microsoft Forms 2.0 Object Library

To gain access to the clipboard methods in the clipboard class in older versions of Windows, you could declare a reference to the Microsoft Forms 2.0 Object Library by following these steps:

  1. Open your VBA editor.
  2. Click Tools > References.
  3. Check the box next to “Microsoft Forms 2.0 Object Library.”

    Microsoft Forms 2.0 Object Library

  4. Press “OK.”

Once your initial setup is complete, insert a module and continue reading to discover how to control your clipboard.

VBA Copy To Clipboard

Solution 1: Windows 7 and earlier

To copy to your clipboard in Windows 7 and earlier, you’ll need to first declare a variable as type MSForms.DataObject. The DataObject will be the bridge between your data and your clipboard.

Copy String to Clipboard

Sub CopyToClipboard()
    Dim clipboard As MSForms.DataObject    
    Dim strSample As String

    Set clipboard = New MSForms.DataObject
    strSample = "This is a sample string"
    
    clipboard.SetText strSample
    clipboard.PutInClipboard
End Sub

The SetText method is used to store a string in a DataObject. The string can be a VBA variable, as demonstrated above, or a cell in your worksheet, as demonstrated below. The PutInClipboard method is the magical piece that places the text in your clipboard.

Copy Cell to Clipboard

Sub CopyToClipboard2()
    Dim clipboard As MSForms.DataObject
    Set clipboard = New MSForms.DataObject
    
    clipboard.SetText ActiveSheet.Range("B2")
    clipboard.PutInClipboard
End Sub

VBA is pretty good at converting your data types to strings before storing them in your clipboard, so you don’t have to worry about using the CStr function to manually convert.

Although I said this is the solution for Windows 7 and earlier, the following solution also works for Windows 7 and earlier. It has the added benefit of working for newer versions of Windows, as well.

Solution 2: Windows 8 and Windows 10

There’s a bit of a bug, if you want to call it that, in Windows 8 and Windows 10 that prevents the Microsoft Forms 2.0 Object Library solution from copying text to your clipboard. The workaround for this is to use Windows API calls, instead. Although intended to be used in newer versions of Windows, this VBA macro will successfully copy to your clipboard on all versions of Windows.

These macros are much longer than the previous solution, but they’re still easy to use since all you have to do is copy and paste. In many ways, this solution is actually easier to use because you don’t need to add a reference to the Microsoft Forms 2.0 Object Library to add text to your clipboard! You will still need to add the reference to the Microsoft Forms 2.0 Object Library to paste from your clipboard, so you might as well go ahead and add it.

#If Mac Then
    ' do nothing
#Else
    #If VBA7 Then
        Declare PtrSafe Function GlobalUnlock Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr
        Declare PtrSafe Function GlobalLock Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr
        Declare PtrSafe Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, _
                                                             ByVal dwBytes As LongPtr) As LongPtr

        Declare PtrSafe Function CloseClipboard Lib "User32" () As Long
        Declare PtrSafe Function OpenClipboard Lib "User32" (ByVal hwnd As LongPtr) As LongPtr
        Declare PtrSafe Function EmptyClipboard Lib "User32" () As Long

        Declare PtrSafe Function lstrcpy Lib "kernel32" (ByVal lpString1 As Any, _
                                                         ByVal lpString2 As Any) As LongPtr

        Declare PtrSafe Function SetClipboardData Lib "User32" (ByVal wFormat _
                                                                As Long, ByVal hMem As LongPtr) As LongPtr
    #Else
        Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As Long
        Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long
        Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, _
                                                     ByVal dwBytes As Long) As Long

        Declare Function CloseClipboard Lib "User32" () As Long
        Declare Function OpenClipboard Lib "User32" (ByVal hwnd As Long) As Long
        Declare Function EmptyClipboard Lib "User32" () As Long

        Declare Function lstrcpy Lib "kernel32" (ByVal lpString1 As Any, _
                                                 ByVal lpString2 As Any) As Long

        Declare Function SetClipboardData Lib "User32" (ByVal wFormat _
                                                        As Long, ByVal hMem As Long) As Long
    #End If
#End If
Public Const GHND = &H42
Public Const CF_TEXT = 1
Public Const MAXSIZE = 4096

Sub ClipBoard_SetData(MyString As String)
    #If Mac Then
        With New MSForms.DataObject
            .SetText MyString
            .PutInClipboard
        End With
    #Else
        #If VBA7 Then
            Dim hGlobalMemory As LongPtr
            Dim hClipMemory   As LongPtr
            Dim lpGlobalMemory    As LongPtr
        #Else
            Dim hGlobalMemory As Long
            Dim hClipMemory   As Long
            Dim lpGlobalMemory    As Long
        #End If

        Dim x                 As Long

        ' Allocate moveable global memory.
       '-------------------------------------------
       hGlobalMemory = GlobalAlloc(GHND, Len(MyString) + 1)

        ' Lock the block to get a far pointer
       ' to this memory.
       lpGlobalMemory = GlobalLock(hGlobalMemory)

        ' Copy the string to this global memory.
       lpGlobalMemory = lstrcpy(lpGlobalMemory, MyString)

        ' Unlock the memory.
       If GlobalUnlock(hGlobalMemory) <> 0 Then
            MsgBox "Could not unlock memory location. Copy aborted."
            GoTo PrepareToClose
        End If

        ' Open the Clipboard to copy data to.
       If OpenClipboard(0&) = 0 Then
            MsgBox "Could not open the Clipboard. Copy aborted."
            Exit Sub
        End If

        ' Clear the Clipboard.
       x = EmptyClipboard()

        ' Copy the data to the Clipboard.
       hClipMemory = SetClipboardData(CF_TEXT, hGlobalMemory)

PrepareToClose:

        If CloseClipboard() = 0 Then
            MsgBox "Could not close Clipboard."
        End If
    #End If

End Sub

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.

I'll take a free VBA Developer Kit

To actually place text on you clipboard, you would simply pass the ClipBoard_SetData macro an argument containing the string you want to store in your clipboard, like this:

Sub CopyToClipBoardWindows10()
ClipBoard_SetData "This is a sample string"
End Sub

This solution was adapted from a macro I saw here.

VBA Paste from Clipboard

Once you know how to copy, pasting is cinch. The syntax is practically identical to the Windows 7 copy examples shown earlier. Take a look.

Retrieve Clipboard Content

Sub PasteFromClipboard3()
    Dim clipboard As MSForms.DataObject
    Dim str1 As String

    Set clipboard = New MSForms.DataObject
    
    clipboard.GetFromClipboard
    str1 = clipboard.GetText
End Sub

The GetFromClipboard method takes data from your clipboard and stores the data in the DataObject. The GetText method takes the string from the DataObject and puts it in your string variable - in this case, in the string variable str1. You successfully pasted the content of your clipboard to a string variable that can be manipulated within your VBA macro.


VBA Clear Clipboard

How do you clear the content stored in the clipboard, you ask? There are several ways to clear your clipboard. The simplest is to set your clipboard equal to an empty string.

Set Clipboard to Empty String

Windows 7 and earlier

Sub ClearClipboard()
    Dim clipboard As MSForms.DataObject
    Set clipboard = New MSForms.DataObject
    
    clipboard.SetText ""
    clipboard.PutInClipboard
End Sub

Windows 8 and later

Sub ClearClipboard2()
    ClipBoard_SetData ""
End Sub

A more thorough way of clearing your clipboard with VBA is to use our good friend, the user32 library.

Clear Entire Clipboard Contents

'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
'These first 3 declarations are only needed if you used Solution 1
'!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
Private Declare Function OpenClipboard Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function EmptyClipboard Lib "user32" () As Long
Private Declare Function CloseClipboard Lib "user32" () As Long

Sub ClearClipboard3()
    OpenClipboard (0&)
    EmptyClipboard
    CloseClipboard
End Sub

If you’re a long-time follower of the wellsr.com VBA blog, you’ll recognize user32. It’s a staple of computer automation, and I’ve showcased it in several tutorials. In addition to controlling your clipboard, user32.dll can be used to move your mouse and activate windows.

Note, the Private declarations must be pasted at the very top of your module, before any procedures. If you already pasted the big “Solution 2” macro for copying and pasting to your clipboard, you won’t need to add the Private declarations again, since they’re already there.


Final Thoughts

The ability to control your clipboard is a powerful feature of VBA. You can use it to automate complex tasks. For example, in my nuclear engineering career, I regularly work with large ASCII files on UNIX machines. I’ll copy the text to my clipboard, run a VBA macro on Windows to perform string manipulation on the text, then store the final content in my desired format back to my clipboard. I’ll then use this newly formatted string to continue my work on the UNIX boxes. Clipboard manipulation makes for a wonderful post-processor!

For more VBA tips, techniques, and tactics, subscribe to our VBA Insiders email series using the form below.

Share this article on Twitter and Facebook, then leave a comment below and let’s have a discussion.