sendKeys

J

judith

I have a field on my form that concatenates the address fields and i want to
use a button to copy the contens onto the clipboard so the customer can paste
it to word

Me.copyBox.SetFocus
SendKeys "^C", True

This does not seem to work but if I use the Ctrl C manually at this point it
does. Any suggestions please
 
S

Stefan Hoffmann

hi Judith,
This does not seem to work but if I use the Ctrl C manually at this point it
does. Any suggestions please
Forget the sendkeys method. Use the Clipboard_SetData methode (some line
breaks are from my mailer):


Option Compare Database
Option Explicit

'MS KB Artikel Q138910
'INF: How to Retrieve Information from the Clipboard (ACC 7.0, 97)
' Function ClipBoard_GetData()

'MS KB Artikel Q138909
'INF: How to Send Information to the Clipboard (ACC 7.0, 97)
' Function ClipBoard_SetData(MyString As String)

'MS KB Artikel Q148392
'INF: How to Capture Screens of Your Forms (ACC 7.0/97) into Clipboard
' Function ScreenDump()

'Function PrtScn(Alles As Boolean)
' Alles = True - Gesamter Bildschirm
' Alles = False - Aktives Fenster

'Function ClipBoard_Clear()

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 SetClipboardData Lib "user32" (ByVal wFormat As
Long, ByVal hMem As Long) As Long
Declare Function EmptyClipboard Lib "user32" () 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

Declare Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal
bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)

Public Const VK_SNAPSHOT = &H2C

Type RECT_Type
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type

Declare Function GetActiveWindow Lib "user32" () As Long
Declare Function GetDesktopWindow Lib "user32" () As Long
Declare Sub GetWindowRect Lib "user32" (ByVal hWnd As Long, lpRect
As RECT_Type)

Declare Function GetDC Lib "user32" (ByVal hWnd As Long) As Long
Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long)
As Long
Declare Function CreateCompatibleBitmap Lib "gdi32" (ByVal hdc _
As Long, ByVal nWidth As Long, _
ByVal nHeight As Long) As Long
Declare Function SelectObject Lib "gdi32" (ByVal hdc As Long, _
ByVal hObject As Long) As Long

Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, _
ByVal X As Long, ByVal Y _
As Long, ByVal nWidth As Long, _
ByVal nHeight As Long, _
ByVal hSrcDC As Long, _
ByVal XSrc As Long, _
ByVal YSrc As Long, _
ByVal dwRop As Long) As Long

Declare Function ReleaseDC Lib "user32" (ByVal hWnd As Long, ByVal
hdc As Long) As Long
Declare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As Long

Public Const GHND = &H42
Public Const CF_TEXT = 1
Public Const MAXSIZE = 4096

Global Const SRCCOPY = &HCC0020
Global Const CF_BITMAP = 2



'MS KB Artikel Q138910

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

'MS KB Artikel Q138909

Function ClipBoard_SetData(MyString As String)

Dim hGlobalMemory As Long, lpGlobalMemory As Long

Dim hClipMemory As Long, 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 OutOfHere2
End If

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

' Clear the Clipboard.
X = EmptyClipboard()

' Copy the data to the Clipboard.

hClipMemory = SetClipboardData(CF_TEXT, hGlobalMemory)

OutOfHere2:

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

End Function


'MS KB Artikel Q148392

Function ScreenDump()
Dim AccessHwnd As Long, DeskHwnd As Long
Dim hdc As Long
Dim hdcMem As Long
Dim Rect As RECT_Type
Dim junk As Long
Dim fwidth As Long, fheight As Long
Dim hBitmap As Long

DoCmd.Hourglass True

'---------------------------------------------------
' Get window handle to Windows and Microsoft Access
'---------------------------------------------------
DeskHwnd = GetDesktopWindow()
AccessHwnd = GetActiveWindow()

'---------------------------------------------------
' Get screen coordinates of Microsoft Access
'---------------------------------------------------
Call GetWindowRect(AccessHwnd, Rect)
fwidth = Rect.Right - Rect.Left
fheight = Rect.Bottom - Rect.Top

'---------------------------------------------------
' Get the device context of Desktop and allocate memory
'---------------------------------------------------
hdc = GetDC(DeskHwnd)
hdcMem = CreateCompatibleDC(hdc)
hBitmap = CreateCompatibleBitmap(hdc, fwidth, fheight)

If hBitmap <> 0 Then
junk = SelectObject(hdcMem, hBitmap)

'---------------------------------------------
' Copy the Desktop bitmap to memory location
' based on Microsoft Access coordinates.
'---------------------------------------------
junk = BitBlt(hdcMem, 0, 0, fwidth, fheight, hdc, Rect.Left, _
Rect.Top, SRCCOPY)

'---------------------------------------------
' Set up the Clipboard and copy bitmap
'---------------------------------------------
junk = OpenClipboard(DeskHwnd)
junk = EmptyClipboard()
junk = SetClipboardData(CF_BITMAP, hBitmap)
junk = CloseClipboard()
End If

'---------------------------------------------
' Clean up handles
'---------------------------------------------
junk = DeleteDC(hdcMem)
junk = ReleaseDC(DeskHwnd, hdc)

DoCmd.Hourglass False

End Function

Function PrtScn(Alles As Boolean)

' Alles = True - entire screen
' Alles = False - Actives window

If Not Alles Then
keybd_event VK_SNAPSHOT, 0, 0, 0
Else
keybd_event VK_SNAPSHOT, 1, 0, 0
End If

End Function

'***** Code start ********
'code courtesy of
'Terry Kreft
'
Function ClipBoard_Clear()
Call OpenClipboard(0&)
Call EmptyClipboard
Call CloseClipboard
End Function
'***** Code End ********





mfG
--> stefan <--
 
J

judith

i looked at this and thought it was way over my head but it works and is
brilliant ... thanks
 
D

Douglas J. Steele

While Stefan's pointed you to the better way, I thought I'd answer your
specific question.

SendKeys "^C", True

is the equivalent of pressing the Control key, releasing it, then pressing
the letter C. To get the equivalent of Ctrl-C, you need:

SendKeys "(^C)", True
 

Ask a Question

Want to reply to this thread or ask your own question?

You'll need to choose a username for the site, which only take a couple of moments. After that, you can post your question and our members will help you out.

Ask a Question

Top