從剪貼簿擷取資訊

使用 RunCommand 方法

使用 RunCommand 方法搭配 acCmdPaste 常數,將剪貼簿的內容貼到表單或報表上的作用中控制項。

以下範例會說明如何把剪貼簿的內容貼入名為 txtNotes 的文字方塊中。

Private Sub cmdPaste_Click() 
   Me!txtNotes.SetFocus 
   DoCmd.RunCommand acCmdPaste 
End Sub

使用 Windows API

若要使用 API 呼叫從剪貼簿擷取資訊,請將以下程式碼貼入標準模組的宣告區段中。

Declare Function OpenClipboard Lib "User32" (ByVal hwnd As Long) _ 
   As Long 
Declare Function CloseClipboard Lib "User32" () As Long 
Declare Function GetClipboardData Lib "User32" (ByVal wFormat As _ 
   Long) As Long 
Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags&, ByVal _ 
   dwBytes As Long) As Long 
Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) _ 
   As Long 
Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) _ 
   As Long 
Declare Function GlobalSize Lib "kernel32" (ByVal hMem As Long) _ 
   As Long 
Declare Function lstrcpy Lib "kernel32" (ByVal lpString1 As Any, _ 
   ByVal lpString2 As Any) As Long 
 
Public Const GHND = &H42 
Public Const CF_TEXT = 1 
Public Const MAXSIZE = 4096

將以下程式碼貼入標準模組中。

Function ClipBoard_GetData() 
   Dim hClipMemory As Long 
   Dim lpClipMemory As Long 
   Dim MyString As String 
   Dim RetVal As Long 
 
   If OpenClipboard(0&) = 0 Then 
      MsgBox "Cannot open Clipboard. Another app. may have it open" 
      Exit Function 
   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 OutOfHere 
   End If 
 
   ' Lock Clipboard memory so we can reference 
   ' the actual data string. 
   lpClipMemory = GlobalLock(hClipMemory) 
 
   If Not IsNull(lpClipMemory) Then 
      MyString = Space$(MAXSIZE) 
      RetVal = lstrcpy(MyString, lpClipMemory) 
      RetVal = GlobalUnlock(hClipMemory) 
       
      ' Peel off the null terminating character. 
      MyString = Mid(MyString, 1, InStr(1, MyString, Chr$(0), 0) - 1) 
   Else 
      MsgBox "Could not lock memory to copy string from." 
   End If 
 
OutOfHere: 
 
   RetVal = CloseClipboard() 
   ClipBoard_GetData = MyString 
 
End Function

若要測試函式,請將一些文字複製到剪貼簿。 在 [即時運算] 視窗中貼上下列程式碼,然後按 Enter。 隨即會出現訊息方塊,其中包含剪貼簿上的文字。

strClip = ClipBoard_GetData: MsgBox strClip

支援和意見反應

有關於 Office VBA 或這份文件的問題或意見反應嗎? 如需取得支援服務並提供意見反應的相關指導,請參閱 Office VBA 支援與意見反應