Click here to Skip to main content
15,914,066 members
Home / Discussions / Visual Basic
   

Visual Basic

 
AnswerRe: Is it the right approach to speed up the copy process? Pin
riced3-Jul-10 19:42
riced3-Jul-10 19:42 
GeneralRe: Is it the right approach to speed up the copy process? Pin
Sonhospa4-Jul-10 0:03
Sonhospa4-Jul-10 0:03 
GeneralRe: Is it the right approach to speed up the copy process? Pin
riced4-Jul-10 0:57
riced4-Jul-10 0:57 
GeneralRe: Is it the right approach to speed up the copy process? Pin
DaveAuld4-Jul-10 1:19
professionalDaveAuld4-Jul-10 1:19 
NewsRe: Is it the right approach to speed up the copy process? Pin
Sonhospa4-Jul-10 4:39
Sonhospa4-Jul-10 4:39 
GeneralRe: Is it the right approach to speed up the copy process? Pin
Аslam Iqbal4-Jul-10 11:13
professionalАslam Iqbal4-Jul-10 11:13 
GeneralRe: Is it the right approach to speed up the copy process? Pin
Sonhospa5-Jul-10 21:12
Sonhospa5-Jul-10 21:12 
GeneralRe: Is it the right approach to speed up the copy process? Pin
Аslam Iqbal6-Jul-10 11:19
professionalАslam Iqbal6-Jul-10 11:19 
You can do it very easy way following this codes:
Open an project in vb6 and paste this codes:

Option Explicit
Private Sub Command1_Click()
Dim Files() As String 'contains the list of folders or files
'if more 1 file/folder then chage it
ReDim Preserve Files(0) As String
Files(0) = Text1.Text
'Example of multiple folder/files
'With Me.ListView1
'For i = 1 To .ListItems.Count
'If .ListItems.Item(i).Selected Then
'ReDim Preserve FS(j) As String
'FS(j) = CRDIR & .ListItems.Item(i).Text
'j = j + 1
'End If
'Next i
ClipBoard.clipCopyFiles Files
End Sub

Private Sub Command2_Click()
Dim PasteOn As String
PasteOn = Text2.Text
On Error Resume Next
' Handle your destinition folder. if not exist then create
MkDir PasteOn
Dim R As Long
R = ShellEx(PasteOn, 0, "Paste")
    If R <= 32 Then MsgBox "Error"
End Sub

Add a module named clipboard and paste this code:

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 Const FO_MOVE As Long = &H1
Public Const FO_COPY As Long = &H2
Public Const FO_DELETE As Long = &H3
Public Const FO_RENAME As Long = &H4
Public Const FOF_MULTIDESTFILES As Long = &H1
Public Const FOF_CONFIRMMOUSE As Long = &H2
Public Const FOF_SILENT As Long = &H4
Public Const FOF_RENAMEONCOLLISION As Long = &H8
Public Const FOF_NOCONFIRMATION As Long = &H10
Public Const FOF_WANTMAPPINGHANDLE As Long = &H20
Public Const FOF_CREATEPROGRESSDLG As Long = &H0
Public Const FOF_ALLOWUNDO As Long = &H40
Public Const FOF_FILESONLY As Long = &H80
Public Const FOF_SIMPLEPROGRESS As Long = &H100
Public Const FOF_NOCONFIRMMKDIR As Long = &H200

Type SHFILEOPSTRUCT
     hWnd As Long
     wFunc As Long
     pFrom As String
     pTo As String
     fFlags As Long
     fAnyOperationsAborted As Long
     hNameMappings As Long
     lpszProgressTitle As String
End Type

Declare Function SHFileOperation Lib "shell32.dll" Alias "SHFileOperationA" (lpFileOp As SHFILEOPSTRUCT) As Long
'''''''''''''''''''''SHELL
Private Type SHELLEXECUTEINFO
    cbSize As Long
    fMask As Long
    hWnd As Long
    lpVerb As String
    lpFile As String
    lpParameters  As String
    lpDirectory   As String
    nShow As Long
    hInstApp As Long
    lpIDList      As Long
    lpClass       As String
    hkeyClass     As Long
    dwHotKey      As Long
    hIcon         As Long
    hProcess      As Long
End Type
Private Const WM_PASTE = &H302
Private Const SEE_MASK_INVOKEIDLIST = &HC
Private Const SEE_MASK_NOCLOSEPROCESS = &H40
Private Const SEE_MASK_FLAG_NO_UI = &H400

Declare Function ShellExecuteEX Lib "shell32.dll" Alias "ShellExecuteEx" (SEI As SHELLEXECUTEINFO) As Long
Public Function ShellEx(FileName As String, OwnerhWnd As Long, ByVal Operation$) As Long
    Dim SEI As SHELLEXECUTEINFO
    With SEI
        .cbSize = Len(SEI)
        .fMask = SEE_MASK_NOCLOSEPROCESS Or SEE_MASK_INVOKEIDLIST Or SEE_MASK_FLAG_NO_UI
        .hWnd = OwnerhWnd
        .lpVerb = Operation
         .lpFile = FileName
        .lpParameters = vbNullChar
        .lpDirectory = vbNullChar
        .nShow = 0
        .hInstApp = 0
        .lpIDList = 0
    End With
    ShellExecuteEX SEI
     ShellEx = SEI.hInstApp
 End Function

'''''''''''''''''SHELL  END--------------------------------------




'Public FL As New EnumFiles, DS As New Iqbal

'''''''''
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 desc As String
   Dim FileName As String
   Dim pt As POINTAPI
   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
   Else  ''not copy
   Files = Split("")
   clipPasteFiles = -1
   End If

End Function
Public Function clipPasteble() As Boolean
   If IsClipboardFormatAvailable(CF_HDROP) Then
    clipPasteble = True
         Call CloseClipboard
   Else  ''not copy
   clipPasteble = False
   End If
End Function

 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

You will see a copy progress window as like you copy using explorer.exe. It copyes all sub foldes and files as explorer does.
You have every thing you need.
Suspicious | :suss:
GeneralRe: Is it the right approach to speed up the copy process? Pin
DaveAuld4-Jul-10 11:31
professionalDaveAuld4-Jul-10 11:31 
GeneralRe: Is it the right approach to speed up the copy process? Pin
Sonhospa5-Jul-10 21:12
Sonhospa5-Jul-10 21:12 
QuestionDatagrid to database Pin
.NetDeveloper092-Jul-10 23:37
.NetDeveloper092-Jul-10 23:37 
AnswerRe: Datagrid to database Pin
Abhinav S3-Jul-10 0:01
Abhinav S3-Jul-10 0:01 
Questionsplash screen and timer control Pin
.NetDeveloper092-Jul-10 22:14
.NetDeveloper092-Jul-10 22:14 
AnswerRe: splash screen and timer control Pin
Mycroft Holmes2-Jul-10 22:45
professionalMycroft Holmes2-Jul-10 22:45 
AnswerRe: splash screen and timer control Pin
Wayne Gaylard2-Jul-10 22:53
professionalWayne Gaylard2-Jul-10 22:53 
GeneralRe: splash screen and timer control Pin
.NetDeveloper094-Jul-10 6:22
.NetDeveloper094-Jul-10 6:22 
GeneralRe: splash screen and timer control Pin
Wayne Gaylard4-Jul-10 20:26
professionalWayne Gaylard4-Jul-10 20:26 
GeneralRe: splash screen and timer control Pin
.NetDeveloper095-Jul-10 4:59
.NetDeveloper095-Jul-10 4:59 
Generalhow can i save multiple values from datagrid into database Pin
.NetDeveloper0911-Jul-10 1:16
.NetDeveloper0911-Jul-10 1:16 
AnswerRe: splash screen and timer control Pin
Anubhava Dimri3-Jul-10 2:43
Anubhava Dimri3-Jul-10 2:43 
Questiondynamic printing pictures in vb6.0 Pin
lynn630282-Jul-10 11:16
lynn630282-Jul-10 11:16 
AnswerRe: dynamic printing pictures in vb6.0 Pin
Ian_Sharpe2-Jul-10 11:45
Ian_Sharpe2-Jul-10 11:45 
AnswerRe: dynamic printing pictures in vb6.0 Pin
Anubhava Dimri3-Jul-10 2:49
Anubhava Dimri3-Jul-10 2:49 
GeneralRe: dynamic printing pictures in vb6.0 Pin
lynn630288-Jul-10 8:51
lynn630288-Jul-10 8:51 
QuestionFailed to create setup file using Visual Studio 2005 Pin
Andraw Tang2-Jul-10 4:49
Andraw Tang2-Jul-10 4:49 

General General    News News    Suggestion Suggestion    Question Question    Bug Bug    Answer Answer    Joke Joke    Praise Praise    Rant Rant    Admin Admin   

Use Ctrl+Left/Right to switch messages, Ctrl+Up/Down to switch threads, Ctrl+Shift+Left/Right to switch pages.