|
|
|
Step-By-Step Example
- Create a standard exe project - Add one drive control, one dir control, one file control, three command button controls and one timer control. Set MultiSelect=True for File control - Add the following code in form1 |
Click here to copy the following block | Option Explicit
Private Type POINTAPI x As Long y As Long End Type
Private Declare Function EmptyClipboard Lib "user32" () As Long Private Declare Function OpenClipboard Lib "user32" (ByVal hWnd As Long) As Long Private Declare Function CloseClipboard Lib "user32" () 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 IsClipboardFormatAvailable Lib "user32" (ByVal wFormat As Long) As Long
Private Declare Function DragQueryFile Lib "shell32.dll" Alias "DragQueryFileA" (ByVal hDrop As Long, ByVal UINT As Long, ByVal lpStr As String, ByVal ch As Long) As Long Private Declare Function DragQueryPoint Lib "shell32.dll" (ByVal hDrop As Long, lpPoint As POINTAPI) As Long Private Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long Private Declare Function GlobalFree Lib "kernel32" (ByVal hMem As Long) As Long Private Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long Private Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As Long Private Declare Sub CopyMem Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Private Const CF_TEXT = 1 Private Const CF_BITMAP = 2 Private Const CF_METAFILEPICT = 3 Private Const CF_SYLK = 4 Private Const CF_DIF = 5 Private Const CF_TIFF = 6 Private Const CF_OEMTEXT = 7 Private Const CF_DIB = 8 Private Const CF_PALETTE = 9 Private Const CF_PENDATA = 10 Private Const CF_RIFF = 11 Private Const CF_WAVE = 12 Private Const CF_UNICODETEXT = 13 Private Const CF_ENHMETAFILE = 14 Private Const CF_HDROP = 15 Private Const CF_LOCALE = 16 Private Const CF_MAX = 17
Private Const CFSTR_SHELLIDLIST As String = "Shell IDList Array" Private Const CFSTR_SHELLIDLISTOFFSET As String = "Shell Object Offsets" Private Const CFSTR_NETRESOURCES As String = "Net Resource" Private Const CFSTR_FILEDESCRIPTOR As String = "FileGroupDescriptor" Private Const CFSTR_FILECONTENTS As String = "FileContents" Private Const CFSTR_FILENAME As String = "FileName" Private Const CFSTR_PRINTERGROUP As String = "PrinterFriendlyName" Private Const CFSTR_FILENAMEMAP As String = "FileNameMap"
Private Const GMEM_FIXED = &H0 Private Const GMEM_MOVEABLE = &H2 Private Const GMEM_NOCOMPACT = &H10 Private Const GMEM_NODISCARD = &H20 Private Const GMEM_ZEROINIT = &H40 Private Const GMEM_MODIFY = &H80 Private Const GMEM_DISCARDABLE = &H100 Private Const GMEM_NOT_BANKED = &H1000 Private Const GMEM_SHARE = &H2000 Private Const GMEM_DDESHARE = &H2000 Private Const GMEM_NOTIFY = &H4000 Private Const GMEM_LOWER = GMEM_NOT_BANKED Private Const GMEM_VALID_FLAGS = &H7F72 Private Const GMEM_INVALID_HANDLE = &H8000 Private Const GHND = (GMEM_MOVEABLE Or GMEM_ZEROINIT) Private Const GPTR = (GMEM_FIXED Or GMEM_ZEROINIT)
Private Type DROPFILES pFiles As Long pt As POINTAPI fNC As Long fWide As Long End Type
Public Function ClipCopyFiles(Files() As String) As Boolean Dim data As String Dim df As DROPFILES Dim hGlobal As Long Dim lpGlobal As Long Dim i As Long
If OpenClipboard(0&) Then Call EmptyClipboard
For i = LBound(Files) To UBound(Files) data = data & Files(i) & vbNullChar Next i data = data & vbNullChar
hGlobal = GlobalAlloc(GHND, Len(df) + Len(data)) If hGlobal Then lpGlobal = GlobalLock(hGlobal)
df.pFiles = Len(df) Call CopyMem(ByVal lpGlobal, df, Len(df)) Call CopyMem(ByVal (lpGlobal + Len(df)), ByVal data, Len(data)) Call GlobalUnlock(hGlobal)
If SetClipboardData(CF_HDROP, hGlobal) Then ClipCopyFiles = True End If End If
Call CloseClipboard End If End Function
Public Function clipPasteFiles(Files() As String) As Long Dim hDrop As Long Dim nFiles As Long Dim i As Long Dim filename As String Const MAX_PATH As Long = 260
If IsClipboardFormatAvailable(CF_HDROP) Then If OpenClipboard(0&) Then
hDrop = GetClipboardData(CF_HDROP) nFiles = DragQueryFile(hDrop, -1&, "", 0)
ReDim Files(0 To nFiles - 1) As String filename = Space(MAX_PATH)
For i = 0 To nFiles - 1 Call DragQueryFile(hDrop, i, filename, Len(filename)) Files(i) = TrimNull(filename) Next i
Call CloseClipboard End If
clipPasteFiles = nFiles End If End Function
Private Function TrimNull(ByVal StrIn As String) As String Dim nul As Long nul = InStr(StrIn, vbNullChar) Select Case nul Case Is > 1 TrimNull = Left(StrIn, nul - 1) Case 1 TrimNull = "" Case 0 TrimNull = Trim(StrIn) End Select End Function
Private Sub Command1_Click() Dim Files() As String Dim Path As String Dim i As Long, n As Long
If File1.filename = "" Then MsgBox "Please select file(s)", vbCritical: Exit Sub Path = Dir1.Path If Right(Path, 1) <> "\" Then Path = Path & "\" End If
With File1 For i = 0 To .ListCount - 1 If .Selected(i) Then ReDim Preserve Files(0 To n) As String Files(n) = Path & .List(i) n = n + 1 End If Next i End With
If ClipCopyFiles(Files) Then MsgBox "Files copied to clipboard " & _ "as Dropped Filelist.", , "Success" Else MsgBox "clipCopyFiles failed...", , "Failure" End If End Sub
Private Sub Command2_Click() Dim Files() As String Dim nRet As Long Dim i As Long Dim msg As String
nRet = clipPasteFiles(Files) If nRet Then For i = 0 To nRet - 1 msg = msg & Files(i) & vbCrLf Next i MsgBox msg, , nRet & " Files Retrieved" Else MsgBox "clipPasteFiles failed...", , "Failure" End If End Sub
Private Sub Command3_Click() Call OpenClipboard(0&) Call EmptyClipboard Call CloseClipboard End Sub
Private Sub Dir1_Change() File1.Path = Dir1.Path End Sub
Private Sub Drive1_Change() Dir1.Path = Drive1.Drive End Sub
Private Sub Form_Load() Command1.Caption = "Copy to Clipboard" Command2.Caption = "Read from Clipboard" Command3.Caption = "Clear Clipboard"
Timer1.Enabled = True Timer1.Interval = 100 End Sub
Private Sub Timer1_Timer() If IsClipboardFormatAvailable(CF_HDROP) Then Command2.Enabled = True Else Command2.Enabled = False End If End Sub |
|
|
|
Submitted By :
Nayan Patel
(Member Since : 5/26/2004 12:23:06 PM)
|
 |

|
Job Description :
He is the moderator of this site and currently working as an independent consultant. He works with VB.net/ASP.net, SQL Server and other MS technologies. He is MCSD.net, MCDBA and MCSE. In his free time he likes to watch funny movies and doing oil painting. |
View all (893) submissions by this author
(Birth Date : 7/14/1981 ) |
|
|