Text To Clipboard in VBA Windows 10 Issue

前端 未结 7 2036
抹茶落季
抹茶落季 2020-12-03 09:04

I have a function that I use to send a string to the windows clipboard:

Sub TextToClipboard(ByVal Text As String)

  With CreateObject(\"new:{1C3B4210-F441-1         


        
相关标签:
7条回答
  • 2020-12-03 09:41

    These answers dosen't work for me, and I think they are kinda overkill.

    The following code works @ 64-bit Windows 10 & 64-bit Office Excel 2016

    Usage:

    Call SetClipboard("Clipboard this text")
    

    Insert below code to some VBA-module

    Option Explicit
    Private Declare Function OpenClipboard Lib "user32.dll" (ByVal hWnd As Long) As Long
    Private Declare Function EmptyClipboard Lib "user32.dll" () As Long
    Private Declare Function CloseClipboard Lib "user32.dll" () As Long
    Private Declare Function IsClipboardFormatAvailable Lib "user32.dll" (ByVal wFormat As Long) As Long
    Private Declare Function GetClipboardData Lib "user32.dll" (ByVal wFormat As Long) As Long
    Private Declare Function SetClipboardData Lib "user32.dll" (ByVal wFormat As Long, ByVal hMem As Long) As Long
    Private Declare Function GlobalAlloc Lib "kernel32.dll" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
    Private Declare Function GlobalLock Lib "kernel32.dll" (ByVal hMem As Long) As Long
    Private Declare Function GlobalUnlock Lib "kernel32.dll" (ByVal hMem As Long) As Long
    Private Declare Function GlobalSize Lib "kernel32" (ByVal hMem As Long) As Long
    Private Declare Function lstrcpy Lib "kernel32.dll" Alias "lstrcpyW" (ByVal lpString1 As Long, ByVal lpString2 As Long) As Long
    
    Public Sub SetClipboard(sUniText As String)
        Dim iStrPtr As Long
        Dim iLen As Long
        Dim iLock As Long
    
        Const GMEM_MOVEABLE As Long = &H2
        Const GMEM_ZEROINIT As Long = &H40
        Const CF_UNICODETEXT As Long = &HD
    
        OpenClipboard 0&
        EmptyClipboard
        iLen = LenB(sUniText) + 2&
        iStrPtr = GlobalAlloc(GMEM_MOVEABLE Or GMEM_ZEROINIT, iLen)
        iLock = GlobalLock(iStrPtr)
        lstrcpy iLock, StrPtr(sUniText)
        GlobalUnlock iStrPtr
        SetClipboardData CF_UNICODETEXT, iStrPtr
        CloseClipboard
    End Sub
    
    Public Function GetClipboard() As String
        Dim iStrPtr As Long
        Dim iLen As Long
        Dim iLock As Long
        Dim sUniText As String
    
        Const CF_UNICODETEXT As Long = 13&
    
        OpenClipboard 0&
    
        If IsClipboardFormatAvailable(CF_UNICODETEXT) Then
            iStrPtr = GetClipboardData(CF_UNICODETEXT)
            If iStrPtr Then
                iLock = GlobalLock(iStrPtr)
                iLen = GlobalSize(iStrPtr)
                sUniText = String$(iLen \ 2& - 1&, vbNullChar)
                lstrcpy StrPtr(sUniText), iLock
                GlobalUnlock iStrPtr
            End If
            GetClipboard = sUniText
        End If
    
        CloseClipboard
    End Function
    

    Source: https://msdn.microsoft.com/en-us/library/office/ff192913.aspx

    Officially developed by Chris Macro

    0 讨论(0)
  • 2020-12-03 09:46

    I was having similar problems after moving to a new machine but it was solved by repointing to the microsoft forms dll. the data objects object (and simplified brief code posted by a few people towards the bottom here) will still work.

    Go to references and add the microsoft forms 2.0 object library reference. if it is not shown click browse and select fm20.dll in the \system32 folder.

    0 讨论(0)
  • 2020-12-03 09:47

    Thanks to the comments under my question I figured out the error was declaring my variables as Long instead of LongPtr. It's still not 100% clear if my first method "TextToClipboard" is failing because of my office instance being 64-bit, but the second method seems to overcome that fine. If anyone else is interested here is the code I modified to read and write to the clipboard that shouldn't be affected by 64 or 32-bit versions of office. My modifications also included getting all of the text even if it's longer than 4096 characters.

    For context I'm putting this in a module called 'mClipboard' so that when I call these methods I use 'mClipboard.GetText'.

    Hope this helps someone else too!

    Option Explicit
    
    #If VBA7 Then
    
    Private Declare PtrSafe Function GlobalUnlock Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr
    Private Declare PtrSafe Function GlobalLock Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr
    Private Declare PtrSafe Function GlobalAlloc Lib "kernel32" (ByVal wFlags As LongPtr, ByVal dwBytes As LongPtr) As LongPtr
    Private Declare PtrSafe Function CloseClipboard Lib "User32" () As LongPtr
    Private Declare PtrSafe Function OpenClipboard Lib "User32" (ByVal hwnd As LongPtr) As LongPtr
    Private Declare PtrSafe Function EmptyClipboard Lib "User32" () As LongPtr
    Private Declare PtrSafe Function lstrcpy Lib "kernel32" (ByVal lpString1 As Any, ByVal lpString2 As Any) As LongPtr
    Private Declare PtrSafe Function SetClipboardData Lib "User32" (ByVal wFormat As LongPtr, ByVal hMem As LongPtr) As LongPtr
    Private Declare PtrSafe Function GetClipboardData Lib "User32" (ByVal wFormat As LongPtr) As LongPtr
    Private Declare PtrSafe Function GlobalSize Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr
    
    #Else
    
    Private Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As Long
    Private Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long
    Private Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
    Private Declare Function CloseClipboard Lib "User32" () As Long
    Private Declare Function OpenClipboard Lib "User32" (ByVal hwnd As Long) As Long
    Private Declare Function EmptyClipboard Lib "User32" () As Long
    Private Declare Function lstrcpy Lib "kernel32" (ByVal lpString1 As Any, ByVal lpString2 As Any) As Long
    Private Declare Function SetClipboardData Lib "User32" (ByVal wFormat, As Long, ByVal hMem As Long) As Long
    Private Declare Function GetClipboardData Lib "User32" (ByVal wFormat As Long) As Long
    Private Declare Function GlobalSize Lib "kernel32" (ByVal hMem As Long) As Long
    
    #End If
    
    
    
    Public Sub SetText(Text As String)
    
    
    #If VBA7 Then
    
    Dim hGlobalMemory As LongPtr
    Dim lpGlobalMemory As LongPtr
    Dim hClipMemory As LongPtr
    
    #Else
    
    Dim hGlobalMemory As Long
    Dim lpGlobalMemory As Long
    Dim hClipMemory As Long
    
    #End If
    
    
    
    Const GHND = &H42
    Const CF_TEXT = 1
    
       ' Allocate moveable global memory.
       '-------------------------------------------
       hGlobalMemory = GlobalAlloc(GHND, Len(Text) + 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, Text)
    
       ' Unlock the memory.
       If GlobalUnlock(hGlobalMemory) <> 0 Then
          MsgBox "Could not unlock memory location. Copy aborted."
          GoTo CloseClipboard
       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.
       Call EmptyClipboard
    
       ' Copy the data to the Clipboard.
       hClipMemory = SetClipboardData(CF_TEXT, hGlobalMemory)
    
    CloseClipboard:
    
       If CloseClipboard() = 0 Then
          MsgBox "Could not close Clipboard."
       End If
    
    End Sub
    
    Public Property Get GetText()
    
    
    #If VBA7 Then
    
    Dim hClipMemory As LongPtr
    Dim lpClipMemory As LongPtr
    
    #Else
    
    Dim hClipMemory As Long
    Dim lpClipMemory As Long
    
    #End If
    
    
    
    Dim MaximumSize As Long
    Dim ClipText As String
    
    Const CF_TEXT = 1
    
       If OpenClipboard(0&) = 0 Then
          MsgBox "Cannot open Clipboard. Another app. may have it open"
          Exit Property
       End If
    
       ' Obtain the handle to the global memory block that is referencing the text.
       hClipMemory = GetClipboardData(CF_TEXT)
       If IsNull(hClipMemory) Then
          MsgBox "Could not allocate memory"
          GoTo CloseClipboard
       End If
    
       ' Lock Clipboard memory so we can reference the actual data string.
       lpClipMemory = GlobalLock(hClipMemory)
    
       If Not IsNull(lpClipMemory) Then
          MaximumSize = 64
    
          Do
            MaximumSize = MaximumSize * 2
    
            ClipText = Space$(MaximumSize)
            Call lstrcpy(ClipText, lpClipMemory)
            Call GlobalUnlock(hClipMemory)
    
          Loop Until ClipText Like "*" & vbNullChar & "*"
    
          ' Peel off the null terminating character.
          ClipText = Left$(ClipText, InStrRev(ClipText, vbNullChar) - 1)
    
       Else
          MsgBox "Could not lock memory to copy string from."
       End If
    
    CloseClipboard:
    
       Call CloseClipboard
       GetText = ClipText
    
    End Property
    
    0 讨论(0)
  • 2020-12-03 09:55

    Refined @Unicco's answer, which supports Unicode well.

    • Declare
    Option Explicit
    #If VBA7 Then
    
    Private Declare PtrSafe Function OpenClipboard Lib "User32" (ByVal hWnd As LongPtr) As LongPtr
    Private Declare PtrSafe Function EmptyClipboard Lib "User32" () As LongPtr
    Private Declare PtrSafe Function CloseClipboard Lib "User32" () As LongPtr
    Private Declare PtrSafe Function IsClipboardFormatAvailable Lib "User32" (ByVal wFormat As LongPtr) As LongPtr
    Private Declare PtrSafe Function GetClipboardData Lib "User32" (ByVal wFormat As LongPtr) As LongPtr
    Private Declare PtrSafe Function SetClipboardData Lib "User32" (ByVal wFormat As LongPtr, ByVal hMem As LongPtr) As LongPtr
    Private Declare PtrSafe Function GlobalAlloc Lib "kernel32.dll" (ByVal wFlags As Long, ByVal dwBytes As Long) As LongPtr
    Private Declare PtrSafe Function GlobalLock Lib "kernel32.dll" (ByVal hMem As LongPtr) As LongPtr
    Private Declare PtrSafe Function GlobalUnlock Lib "kernel32.dll" (ByVal hMem As LongPtr) As LongPtr
    Private Declare PtrSafe Function GlobalSize Lib "kernel32" (ByVal hMem As LongPtr) As Long
    Private Declare PtrSafe Function lstrcpy Lib "kernel32.dll" Alias "lstrcpyW" (ByVal lpString1 As Any, ByVal lpString2 As Any) As LongPtr
    
    #Else
    
    Private Declare Function OpenClipboard Lib "user32.dll" (ByVal hWnd As Long) As Long
    Private Declare Function EmptyClipboard Lib "user32.dll" () As Long
    Private Declare Function CloseClipboard Lib "user32.dll" () As Long
    Private Declare Function IsClipboardFormatAvailable Lib "user32.dll" (ByVal wFormat As Long) As Long
    Private Declare Function GetClipboardData Lib "user32.dll" (ByVal wFormat As Long) As Long
    Private Declare Function SetClipboardData Lib "user32.dll" (ByVal wFormat As Long, ByVal hMem As Long) As Long
    Private Declare Function GlobalAlloc Lib "kernel32.dll" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
    Private Declare Function GlobalLock Lib "kernel32.dll" (ByVal hMem As Long) As Long
    Private Declare Function GlobalUnlock Lib "kernel32.dll" (ByVal hMem As Long) As Long
    Private Declare Function GlobalSize Lib "kernel32" (ByVal hMem As Long) As Long
    Private Declare Function lstrcpy Lib "kernel32.dll" Alias "lstrcpyW" (ByVal lpString1 As Long, ByVal lpString2 As Long) As Long
    
    #End If
    
    • SetClipboard
    Public Sub SetClipboard(sUniText As String)
    
    #If VBA7 Then
        Dim iStrPtr As LongPtr
        Dim iLock As LongPtr
    #Else
        Dim iStrPtr As Long
        Dim iLock As Long
    #End If
    
        Dim iLen As Long
    
        Const GMEM_MOVEABLE As Long = &H2
        Const GMEM_ZEROINIT As Long = &H40
        Const CF_UNICODETEXT As Long = &HD
    
        OpenClipboard 0&
        EmptyClipboard
        iLen = LenB(sUniText) + 2&
        iStrPtr = GlobalAlloc(GMEM_MOVEABLE + GMEM_ZEROINIT, iLen)
        iLock = GlobalLock(iStrPtr)
        lstrcpy iLock, StrPtr(sUniText)
        GlobalUnlock iStrPtr
        SetClipboardData CF_UNICODETEXT, iStrPtr
        CloseClipboard
    End Sub
    
    • GetClipboard
    Public Function GetClipboard() As String
    #If VBA7 Then
        Dim iStrPtr As LongPtr
        Dim iLock As LongPtr
    #Else
        Dim iStrPtr As Long
        Dim iLock As Long
    #End If
        Dim iLen As Long
        Dim sUniText As String
    
        Const CF_UNICODETEXT As Long = 13&
    
        OpenClipboard 0&
    
        If IsClipboardFormatAvailable(CF_UNICODETEXT) Then
            iStrPtr = GetClipboardData(CF_UNICODETEXT)
            If iStrPtr Then
                iLock = GlobalLock(iStrPtr)
                iLen = GlobalSize(iStrPtr)
                sUniText = String$(iLen \ 2& - 1&, vbNullChar)
                lstrcpy StrPtr(sUniText), iLock
                GlobalUnlock iStrPtr
            End If
            GetClipboard = sUniText
        End If
    
        CloseClipboard
    End Function
    
    0 讨论(0)
  • 2020-12-03 09:56

    Had same issue Windows 10 x64 and Office Excel 2016 x64.

    Finally I was able to copy Cell's string value to Windows API Clipboard :)

    Code:

    Option Explicit
    
    #If VBA7 Then
       Declare PtrSafe Function OpenClipboard Lib "user32.dll" (ByVal hWnd As LongPtr) As LongPtr
     Declare PtrSafe Function EmptyClipboard Lib "user32.dll" () As LongPtr
     Declare PtrSafe Function CloseClipboard Lib "user32.dll" () As LongPtr
     Declare PtrSafe Function IsClipboardFormatAvailable Lib "user32.dll" (ByVal wFormat As LongPtr) As LongPtr
     Declare PtrSafe Function GetClipboardData Lib "user32.dll" (ByVal wFormat As LongPtr) As LongPtr
     Declare PtrSafe Function SetClipboardData Lib "user32.dll" (ByVal wFormat As LongPtr, ByVal hMem As LongPtr) As LongPtr
     Declare PtrSafe Function GlobalAlloc Lib "kernel32.dll" (ByVal wFlags As LongPtr, ByVal dwBytes As LongPtr) As LongPtr
     Declare PtrSafe Function GlobalLock Lib "kernel32.dll" (ByVal hMem As LongPtr) As LongPtr
     Declare PtrSafe Function GlobalUnlock Lib "kernel32.dll" (ByVal hMem As LongPtr) As LongPtr
     Declare PtrSafe Function GlobalSize Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr
     Declare PtrSafe Function lstrcpy Lib "kernel32.dll" Alias "lstrcpyW" (ByVal lpString1 As LongPtr, ByVal lpString2 As LongPtr) As LongPtr
     #Else
    Private Declare Function OpenClipboard Lib "user32.dll" (ByVal hWnd As Long) As Long
    Private Declare Function EmptyClipboard Lib "user32.dll" () As Long
    Private Declare Function CloseClipboard Lib "user32.dll" () As Long
    Private Declare Function IsClipboardFormatAvailable Lib "user32.dll" (ByVal wFormat As Long) As Long
    Private Declare Function GetClipboardData Lib "user32.dll" (ByVal wFormat As Long) As Long
    Private Declare Function SetClipboardData Lib "user32.dll" (ByVal wFormat As Long, ByVal hMem As Long) As Long
    Private Declare Function GlobalAlloc Lib "kernel32.dll" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
    Private Declare Function GlobalLock Lib "kernel32.dll" (ByVal hMem As Long) As Long
    Private Declare Function GlobalUnlock Lib "kernel32.dll" (ByVal hMem As Long) As Long
    Private Declare Function GlobalSize Lib "kernel32" (ByVal hMem As Long) As Long
    Private Declare Function lstrcpy Lib "kernel32.dll" Alias "lstrcpyW" (ByVal lpString1 As Long, ByVal lpString2 As Long) As Long
    #End If
    
    
    
    Public Sub SetClipboard(sUniText As String)
    #If Win64 Then
        Dim iStrPtr As LongPtr
        Dim iLen As LongPtr
        Dim iLock As LongPtr
    #Else
        Dim iStrPtr As Long
        Dim iLen As Long
        Dim iLock As Long
    #End If
        Const GMEM_MOVEABLE As Long = &H2
        Const GMEM_ZEROINIT As Long = &H40
        Const CF_UNICODETEXT As Long = &HD
        OpenClipboard 0&
        EmptyClipboard
        iLen = LenB(sUniText) + 2&
        iStrPtr = GlobalAlloc(GMEM_MOVEABLE Or GMEM_ZEROINIT, iLen)
        iLock = GlobalLock(iStrPtr)
        lstrcpy iLock, StrPtr(sUniText)
        GlobalUnlock iStrPtr
        SetClipboardData CF_UNICODETEXT, iStrPtr
        CloseClipboard
    End Sub
    
    0 讨论(0)
  • 2020-12-03 10:05

    Found this answer on reddit just in case someone needs help.

    Option Explicit
    Private Sub CopyCellContents()
    
    Dim objData As New DataObject
    Dim strTemp As String
    
    strTemp = ActiveSheet.Range("E23").Value
    
    strTemp = Replace(strTemp, Chr(10), vbCrLf)
    
    objData.SetText strTemp
    objData.PutInClipboard
    
    End Sub
    
    0 讨论(0)
提交回复
热议问题