Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Mike Lewis on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

FTP with Access - Here is the Anwer 13

Status
Not open for further replies.

1DMF

Programmer
Jan 18, 2005
8,795
0
0
GB
I've spent days researching and pullling my hair out trying to use the wininet.dll and finally I have cracked it.

For all those wanting to FTP with Access here is the answer.

==========================================================
Firstly define the constants
Code:
' Set Constants
Const FTP_TRANSFER_TYPE_ASCII = &H1
Const FTP_TRANSFER_TYPE_BINARY = &H2
Const INTERNET_DEFAULT_FTP_PORT = 21
Const INTERNET_SERVICE_FTP = 1
Const INTERNET_FLAG_PASSIVE = &H8000000
Const GENERIC_WRITE = &H40000000
Const BUFFER_SIZE = 100
Const PassiveConnection As Boolean = True
Then declare the wininet.dll functions (i've included more than i use should you want to use them)
Code:
' Declare wininet.dll API Functions
Public Declare Function FtpSetCurrentDirectory Lib "wininet.dll" Alias "FtpSetCurrentDirectoryA" _
    (ByVal hFtpSession As Long, ByVal lpszDirectory As String) As Boolean

Public Declare Function FtpGetCurrentDirectory Lib "wininet.dll" Alias "FtpGetCurrentDirectoryA" _
   (ByVal hFtpSession As Long, ByVal lpszCurrentDirectory As String, lpdwCurrentDirectory As Long) As Boolean
   
Public Declare Function InternetWriteFile Lib "wininet.dll" _
(ByVal hFile As Long, ByRef sBuffer As Byte, ByVal lNumBytesToWite As Long, _
dwNumberOfBytesWritten As Long) As Integer

Public Declare Function FtpOpenFile Lib "wininet.dll" Alias "FtpOpenFileA" _
(ByVal hFtpSession As Long, ByVal sBuff As String, ByVal Access As Long, ByVal Flags As Long, ByVal Context As Long) As Long

Public Declare Function FtpPutFile Lib "wininet.dll" Alias "FtpPutFileA" _
(ByVal hFtpSession As Long, ByVal lpszLocalFile As String, _
      ByVal lpszRemoteFile As String, _
      ByVal dwFlags As Long, ByVal dwContext As Long) As Boolean
      
Public Declare Function FtpDeleteFile Lib "wininet.dll" _
    Alias "FtpDeleteFileA" (ByVal hFtpSession As Long, _
    ByVal lpszFileName As String) As Boolean
Public Declare Function InternetCloseHandle Lib "wininet.dll" _
(ByVal hInet As Long) As Long

Public Declare Function InternetOpen Lib "wininet.dll" Alias "InternetOpenA" _
(ByVal sAgent As String, ByVal lAccessType As Long, ByVal sProxyName As String, _
ByVal sProxyBypass As String, ByVal lFlags As Long) As Long

Public Declare Function InternetConnect Lib "wininet.dll" Alias "InternetConnectA" _
(ByVal hInternetSession As Long, ByVal sServerName As String, ByVal nServerPort As Integer, _
ByVal sUsername As String, ByVal sPassword As String, ByVal lService As Long, _
ByVal lFlags As Long, ByVal lContext As Long) As Long


Public Declare Function FtpGetFile Lib "wininet.dll" Alias "FtpGetFileA" _
(ByVal hFtpSession As Long, ByVal lpszRemoteFile As String, _
      ByVal lpszNewFile As String, ByVal fFailIfExists As Boolean, ByVal dwFlagsAndAttributes As Long, _
      ByVal dwFlags As Long, ByVal dwContext As Long) As Boolean

Declare Function InternetGetLastResponseInfo Lib "wininet.dll" _
      Alias "InternetGetLastResponseInfoA" _
       (ByRef lpdwError As Long, _
       ByVal lpszErrorBuffer As String, _
       ByRef lpdwErrorBufferLength As Long) As Boolean
I then wrote this function to upload
Code:
Function FTPFile(ByVal HostName As String, _
    ByVal UserName As String, _
    ByVal Password As String, _
    ByVal LocalFileName As String, _
    ByVal RemoteFileName As String, _
    ByVal sDir As String, _
    ByVal sMode As String) As Boolean
    
    On Error GoTo Err_Function
        
' Declare variables
Dim hConnection, hOpen, hFile  As Long ' Used For Handles
Dim iSize As Long ' Size of file for upload
Dim Retval As Variant ' Used for progress meter
Dim iWritten As Long ' Used by InternetWriteFile to report bytes uploaded
Dim iLoop As Long ' Loop for uploading chuncks
Dim iFile As Integer ' Used for Local file handle
Dim FileData(BUFFER_SIZE - 1) As Byte ' buffer array of BUFFER_SIZE (100) elements 0 to 99

' Open Internet Connecion
hOpen = InternetOpen("FTP", 1, "", vbNullString, 0)

' Connect to FTP
hConnection = InternetConnect(hOpen, HostName, INTERNET_DEFAULT_FTP_PORT, UserName, Password, INTERNET_SERVICE_FTP, IIf(PassiveConnection, INTERNET_FLAG_PASSIVE, 0), 0)

' Change Directory
Call FtpSetCurrentDirectory(hConnection, sDir)

' Open Remote File
hFile = FtpOpenFile(hConnection, RemoteFileName, GENERIC_WRITE, IIf(sMode = "Binary", FTP_TRANSFER_TYPE_BINARY, FTP_TRANSFER_TYPE_ASCII), 0)

' Check for successfull file handle
If hFile = 0 Then
    MsgBox "Internet - Failed!"
    ShowError
    FTPFile = False
    GoTo Exit_Function
End If

' Set Upload Flag to True
FTPFile = True

' Get next file handle number
iFile = FreeFile

' Open local file
Open LocalFileName For Binary Access Read As iFile

' Set file size
iSize = LOF(iFile)

' Iinitialise progress meter
Retval = SysCmd(acSysCmdInitMeter, "Uploading File (" & RemoteFileName & ")", iSize / 1000)

' Loop file size
For iLoop = 1 To iSize \ BUFFER_SIZE
        
    ' Update progress meter
    Retval = SysCmd(acSysCmdUpdateMeter, (BUFFER_SIZE * iLoop) / 1000)
        
    'Get file data
    Get iFile, , FileData
      
    ' Write chunk to FTP checking for success
    If InternetWriteFile(hFile, FileData(0), BUFFER_SIZE, iWritten) = 0 Then
        MsgBox "Upload - Failed!"
        ShowError
        FTPFile = False
       GoTo Exit_Function
    Else
        ' Check buffer was written
        If iWritten <> BUFFER_SIZE Then
            MsgBox "Upload - Failed!"
            ShowError
            FTPFile = False
            GoTo Exit_Function
        End If
    End If
    
Next iLoop

' Handle remainder using MOD

    ' Update progress meter
    Retval = SysCmd(acSysCmdUpdateMeter, iSize / 1000)

    ' Get file data
    Get iFile, , FileData
    
    ' Write remainder to FTP checking for success
    If InternetWriteFile(hFile, FileData(0), iSize Mod BUFFER_SIZE, iWritten) = 0 Then
        MsgBox "Upload - Failed!"
        ShowError
        FTPFile = False
        GoTo Exit_Function
    Else
        ' Check buffer was written
        If iWritten <> iSize Mod BUFFER_SIZE Then
            MsgBox "Upload - Failed!"
            ShowError
            FTPFile = False
            GoTo Exit_Function
        End If
    End If
               
Exit_Function:

' remove progress meter
Retval = SysCmd(acSysCmdRemoveMeter)

'close remote file
Call InternetCloseHandle(hFile)

'close local file
Close iFile

' Close Internet Connection
Call InternetCloseHandle(hOpen)
Call InternetCloseHandle(hConnection)

Exit Function

Err_Function:
MsgBox "Error in FTPFile : " & Err.Description
GoTo Exit_Function

End Function
You will need the following ShowError routine that is used above
Code:
Sub ShowError()
   Dim lErr As Long, sErr As String, lenBuf As Long
   'get the required buffer size
   InternetGetLastResponseInfo lErr, sErr, lenBuf
   'create a buffer
   sErr = String(lenBuf, 0)
   'retrieve the last respons info
   InternetGetLastResponseInfo lErr, sErr, lenBuf
   'show the last response info
   MsgBox "Last Server Response : " + sErr, vbOKOnly + vbCritical
End Sub
Then simply call the function from anywhere like so
Code:
' Upload file
If FTPFile("ftp.domain.com", "myUserName", "myPassword", "Full path and Filename of local file","Target Filename without path", "Directory on FTP server", "Upload Mode - Binary or ASCII") Then
    MsgBox "Upload - Complete!"
End If

I hope it is of help to someone and saves them the time and hastle it took me to get it working.

If you want a full working example then follow this link,


I have uploaded an Access MDB in 97, 2000 & 2003 format.

Enjoy and happy FTP'ing
1DMF
 
how do i do that?
 
Out of interest other than the fact that you have used the access environment for your forms and code does this have anything to do with Access? This is not a critisism just interest in what you were doing that led you to this code.

Red - trying to get my head around it - apples

Want the best answers? See FAQ181-2886
 
Enter the faq section of the forum - at the bottom, there's a submit faq window, similar to the reply window, where you can paste the code. You can also choose relevant category to post it in, whithin the faq section.

Roy-Vidar
 
Sorry I don't fully understand the question.

This code as far as I know will ONLY work in MS Access VBA, although VB + VBA are similar they are not the same and so variables and syntax I believe are different.

I don't know any VB or C/C++ I write all my Web stuff in PERL and front end our SQL server with MS Access.

So the way I see it is it's a solution to FTP'ing especially in Access.
 

I've submitted the post as an FAQ, so let's hope people find it usefull.

Regards,

1DMF
 
user="1DMF" said:
Sorry I don't fully understand the question.

This code as far as I know will ONLY work in MS Access VBA, although VB + VBA are similar they are not the same and so variables and syntax I believe are different.

I don't know any VB or C/C++ I write all my Web stuff in PERL and front end our SQL server with MS Access.

So the way I see it is it's a solution to FTP'ing especially in Access.
I'll be more clear.

You could have used the same VBA code in any office application persumably. What specific Database tasks were yout trying to achieve that required these methods?

Want the best answers? See FAQ181-2886
 
I have no experience with VBA in anything other than Access.

I understand it means Visual Basic for Applications, and can only guess if the code would work exactly the same in Excel or Word etc.

This FTP function is not the only thing our Access DB does, this was a small tool needed so I could continue to develop our internal systems linked to our website members area via our SQL database and our FTP/Web host.

Our database runs the company , it produces letters, manages the membership, does document management including audit trail for compliance, runs reports for MI and membership management, has email integration etc. etc....

The code is not for a "Standalone" application, it is purely an example to anyone using MS Access so they can incorporate FTP functionality into their system if they need it (like i did).

However by all means if it works, use it in any program that handles VB and the windows API.

Or convert the logic to any other language if you can like FoxPro, FileMaker, etc...

All i know is this code works in an MS Access environment, which when I hunted the net could not find a working example, only many other people asking the same thing with a similar problem.

Hope that clears things up a bit.

Regards,
1DMF
 
Hi 1DMF,

Thanks a lot for sharing this, I've been looking for some time for it, before I found this.
Unfortunately, it doesn't work ! Maybe because I have a dutch version (office 2000) ?
The form opens, but there it stops. File browsing is not responding either.. any ideas ?
I'd really like this to work.. unfortunately I'm not a programmer, but adjusting code goes fine (most of the time.)

Thanks a lot in advance !
Hans
 
Hello,

If we can get you working you are more than welcome, I know what it was like to hunt for this code and that is why I took the time to post it for others.

First of all I need to know the error msg you are getting.

Also the filedialog used for the browse button must be set in the references section.

Go into the code editor, select tools and then references and check you have the Microsoft Office Object Library referenced.

 
Hi,
Thanks for replying.
I'm at home (office 2003,UK version) and the 2000 and the 2003 mdb's you zipped are both working fine here..
I will check my PC at work tomorrow and let you know.

Cheers
 
cool - glad you got it running.

Hope to hear good news tomorrow also.

Regards,

1DMF
 
I appreciate the post and haven't had time to look at it. Of much more use to me would be the ability to scan an FTP directory, file by file, similar to the Dir function which would returns the file name and another function to download a file. I plan to look at this further, eventually, but if you could maybe point me in the right direction of some resources on the API that would be most helpful.

To keep redapples happy, my application is downloading files that a third party makes available that I need to import and process. The best thing to do would be to check if each file has previously been imported or downloaded and fetch missing files for processing. Hmmm... thinking of the specific application, being able to detect and ignore 0 sized files would be useful too.

Thanks for any insight.
 
Hello lameid,

What you want to do can be done with this wininet.dll API.

The api commands you need are

FtpSetCurrentDirectory
FtpFindFirstFile
FtpGetFileSize
FtpGetFile
InternetFindNextFile

if you want to use a progress meter you will need to use

InternetReadFileEx - along with the FtpOpenFile command to create the file on the local machine downloading it.

You will also need to define the WIN32_FIND_DATA structure to store directory info for you to then step through.

here is the Microsoft link regarding the use of FtpFindFirstFile so you can look at how it gets the directory listing of the files and stores in the FIND_DATA structure

I don't have all the declare statements for these wininet functions, but you will find them if you search the net, there are a lot of examples out there for getting files from an FTP connection, my solution was for putting file to an FTP connection, but the FtpSetCurrentDirectory, InternetOpen, InternetConnect, InternetGetLastResponseInfo, InternetCloseHandle will work exactly the same way as I use them.

Hope this help, let me know how you get on.

Regards,

1DMF
 
Hi 1DMF,

I can't fine the time today, real busy at work.. (it's my private project..)
I will get back hopefully in a couple af days..
Thanks for your support !!
 
1DMF,
About two years ago, I looked into automating the ftp push of an Access table to our remote data entry shop. Spent a couple of days. Never did get it to work. This example, along with my recordset logic, will allow me to accomplish that.

Thanks for sharing it with us. Have a star.

Tranman

"Adam was not alone in the Garden of Eden, however,...much is due to Eve, the first woman, and Satan, the first consultant." Mark Twain
 
Hi 1DMF,
I found another piece of code and just want to share it and let everyone review it, maybe enhance (if possible)
Does anyone reading this topic has a clue of how to update a MySQL db with the uploaded data file ?

Sub FTP()

On Error GoTo FTP_Err

Dim UploadFile As String
UploadFile = Application.CurrentProject.Path & "\Export.txt"

DoCmd.Hourglass True
With New FTPClient
.ServerName = "your.domain.com"
.UserName = "FTP_Username"
.Password = "your_FTP_Password"
.LocalFile = UploadFile
.RemoteDir = "."
.RemoteFile = ""
.TransferType = "ASC"
.OpenFTP
.OpenServer
.PutFile
.CloseServer
.CloseFTP
End With
MsgBox "Your info message.", 64, "Uploading"
DoCmd.Hourglass False

FTP_Exit:
Exit Sub

FTP_Err:
MsgBox Err.Description, vbCritical
Resume FTP_Exit

End Sub



=========

Option Compare Database
Option Explicit
'
'''''''''''''''''''''''''''''''
' FTPClient '
'''''''''''''''''''''''''''''''
' Author Stuart McCall '
' 100620.2641@compuserve.com '
' smccall@smsb.demon.co.uk '
' ' < this site is offline :-(
'''''''''''''''''''''''''''''''
' July 1998 '
'''''''''''''''''''''''''''''''
'
'''''''''''''''''''''''''''''''
'Member Variables
'''''''''''''''''''''''''''''''
Private m_ProxyName As String
Private m_RemoteDir As String
Private m_RemoteFile As String
Private m_NewFileName As String
Private m_LocalFile As String
Private m_ServerName As String
Private m_UserName As String
Private m_Password As String
Private m_TransferType As Long
Private m_FileSpec As String
'
'''''''''''''''''''''''''''''''
'Collections
'''''''''''''''''''''''''''''''
Public FileNames As New Collection
'
'''''''''''''''''''''''''''''''
'Private Variables
'''''''''''''''''''''''''''''''
Private m_hFTP As Long 'Handle to the FTP session
Private m_hCon As Long 'Handle to the server connection
'
'''''''''''''''''''''''''''''''
'Private Constants
'''''''''''''''''''''''''''''''
Private Const mc_AGENTNAME = "FTP Class"
'
'''''''''''''''''''''''''''''''
'Error values (See the RaiseError routine)
'''''''''''''''''''''''''''''''
Private Const errOpenFTP As String = "1;Call to InternetOpen failed."
Private Const errOpenCon As String = "2;Call to InternetConnect failed."
Private Const errGetFile As String = "3;Call to FtpGetFile failed."
Private Const errPutFile As String = "4;Call to FtpPutFile failed."
Private Const errDelFile As String = "5;Call to FtpDeleteFile failed."
Private Const errRenFile As String = "6;Call to FtpRenameFile failed."
Private Const errGetDir As String = "7;Call to FtpGetCurrentDirectory failed."
Private Const errSetDir As String = "8;Call to FtpSetCurrentDirectory failed."
Private Const errCreateDir As String = "9;Call to FtpCreateDirectory failed."
Private Const errFindFirst As String = "10;Call to FtpFindFirstFile failed."
Private Const errFindNext As String = "11;Call to InternetFindNextFile failed."
Private Const errDelDir As String = "12;Call to FtpRemoveDirectory failed."
Private Const errNotOpen As String = "13;FTP session not open. Call OpenFTP first."
Private Const errNotConnected As String = "14;Not connected to a server. Call OpenServer first."
Private Const errNoServer As String = "15;No Server Name specified."
Private Const errNoLocalFile As String = "16;No Local File specified."
Private Const errNoRemoteFile As String = "17;No Remote File specified."
'
'''''''''''''''''''''''''''''''
'API Declarations
'''''''''''''''''''''''''''''''
Private Const MAX_PATH = &H104
'
Private Const INTERNET_INVALID_PORT_NUMBER = &H0
Private Const INTERNET_SERVICE_FTP = &H1
Private Const INTERNET_OPEN_TYPE_DIRECT = &H1
Private Const INTERNET_OPEN_TYPE_PROXY = &H3
Private Const INTERNET_FLAG_RELOAD = &H80000000
Private Const INTERNET_FLAG_PASSIVE = &H8000000
'
Private Const FTP_TRANSFER_TYPE_ASCII = &H0
Private Const FTP_TRANSFER_TYPE_BINARY = &H1
'
Private Const NO_ERROR = &H0
Private Const ERROR_NO_MORE_FILES = &H12
Private Const ERROR_INTERNET_EXTENDED_ERROR = &H2EE3
'
Private Type FILETIME
dwLowDateTime As Long
dwHighDateTime As Long
End Type
'
Private Type WIN32_FIND_DATA
dwFileAttributes As Long
ftCreationTime As FILETIME
ftLastAccessTime As FILETIME
ftLastWriteTime As FILETIME
nFileSizeHigh As Long
nFileSizeLow As Long
dwReserved0 As Long
dwReserved1 As Long
cFileName As String * MAX_PATH
cAlternate As String * 14
End Type
'
Private Declare Function FtpCreateDirectory Lib "wininet.dll" _
Alias "FtpCreateDirectoryA" (ByVal hFtpSession As Long, ByVal lpszDirectory As String) As Boolean
Private Declare Function FtpDeleteFile Lib "wininet.dll" _
Alias "FtpDeleteFileA" (ByVal hFtpSession As Long, ByVal lpszFileName As String) As Boolean
Private Declare Function FtpFindFirstFile Lib "wininet.dll" Alias "FtpFindFirstFileA" _
(ByVal hFtpSession As Long, ByVal lpszSearchFile As String, _
lpFindFileData As WIN32_FIND_DATA, ByVal dwFlags As Long, ByVal dwContent As Long) As Long
Private Declare Function FtpGetCurrentDirectory Lib "wininet.dll" Alias "FtpGetCurrentDirectoryA" _
(ByVal hFtpSession As Long, ByVal lpszBuffer As String, lpdwBufferLength As Long) As Boolean
Private Declare Function FtpGetFile Lib "wininet.dll" Alias "FtpGetFileA" _
(ByVal hFtpSession As Long, ByVal lpszRemoteFile As String, _
ByVal lpszNewFile As String, ByVal fFailIfExists As Boolean, ByVal dwFlagsAndAttributes As Long, _
ByVal dwFlags As Long, ByVal dwContext As Long) As Boolean
Private Declare Function FtpPutFile Lib "wininet.dll" Alias "FtpPutFileA" _
(ByVal hFtpSession As Long, ByVal lpszLocalFile As String, _
ByVal lpszRemoteFile As String, _
ByVal dwFlags As Long, ByVal dwContext As Long) As Boolean
Private Declare Function FtpRemoveDirectory Lib "wininet.dll" _
Alias "FtpRemoveDirectoryA" (ByVal hFtpSession As Long, ByVal lpszDirectory As String) As Boolean
Private Declare Function FtpRenameFile Lib "wininet.dll" Alias "FtpRenameFileA" _
(ByVal hFtpSession As Long, ByVal lpszExistFile As String, ByVal lpszNewFile As String) As Boolean
Private Declare Function FtpSetCurrentDirectory Lib "wininet.dll" Alias "FtpSetCurrentDirectoryA" _
(ByVal hFtpSession As Long, ByVal lpszDirectory As String) As Boolean
Private Declare Function InternetCloseHandle Lib "wininet.dll" _
(ByVal hInet As Long) As Integer
Private Declare Function InternetConnect Lib "wininet.dll" Alias "InternetConnectA" _
(ByVal hInternetSession As Long, ByVal sServerName As String, ByVal nServerPort As Integer, _
ByVal sUsername As String, ByVal sPassword As String, ByVal lService As Long, _
ByVal lFlags As Long, ByVal lContext As Long) As Long
Private Declare Function InternetFindNextFile Lib "wininet.dll" Alias "InternetFindNextFileA" _
(ByVal hFind As Long, lpvFindData As WIN32_FIND_DATA) As Long
Private Declare Function InternetGetLastResponseInfo Lib "wininet.dll" Alias "InternetGetLastResponseInfoA" _
(lpdwError As Long, ByVal lpszBuffer As String, lpdwBufferLength As Long) As Boolean
Private Declare Function InternetOpen Lib "wininet.dll" Alias "InternetOpenA" _
(ByVal sAgent As String, ByVal lAccessType As Long, ByVal sProxyName As String, _
ByVal sProxyBypass As String, ByVal lFlags As Long) As Long

'''''''''''''''''''''''''''''''
'Properties
'''''''''''''''''''''''''''''''
Public Property Get ProxyName() As String
ProxyName = m_ProxyName
End Property
Public Property Let ProxyName(NewData As String)
m_ProxyName = NewData
End Property

Public Property Get RemoteDir() As String
RemoteDir = m_RemoteDir
End Property
Public Property Let RemoteDir(NewData As String)
m_RemoteDir = NewData
End Property

Public Property Get RemoteFile() As String
RemoteFile = m_RemoteFile
End Property
Public Property Let RemoteFile(NewData As String)
m_RemoteFile = NewData
End Property

Public Property Get LocalFile() As String
LocalFile = m_LocalFile
End Property
Public Property Let LocalFile(NewData As String)
m_LocalFile = NewData
End Property

Public Property Let NewFileName(NewData As String)
m_NewFileName = NewData
End Property

Public Property Get ServerName() As String
ServerName = m_ServerName
End Property
Public Property Let ServerName(NewData As String)
m_ServerName = NewData
End Property

Public Property Get UserName() As String
UserName = m_UserName
End Property
Public Property Let UserName(NewData As String)
m_UserName = NewData
End Property

Public Property Get Password() As String
Password = m_Password
End Property
Public Property Let Password(NewData As String)
m_Password = NewData
End Property

Public Property Get TransferType() As String
TransferType = IIf(m_TransferType = FTP_TRANSFER_TYPE_BINARY, "BINARY", "ASCII")
End Property
Public Property Let TransferType(NewData As String)
m_TransferType = IIf(UCase(left(NewData, 3)) = "BIN", FTP_TRANSFER_TYPE_BINARY, FTP_TRANSFER_TYPE_ASCII)
End Property

Public Property Get FileSpec() As String
FileSpec = m_FileSpec
End Property
Public Property Let FileSpec(NewData As String)
m_FileSpec = NewData
End Property

'''''''''''''''''''''''''''''''
'Methods
'''''''''''''''''''''''''''''''
Public Sub OpenFTP(Optional pProxyName)
'Initiate FTP session

'Handle optional parameters
If Not IsMissing(pProxyName) Then m_ProxyName = pProxyName
'
If Len(m_ProxyName) Then
m_hFTP = InternetOpen(mc_AGENTNAME, INTERNET_OPEN_TYPE_PROXY, _
m_ProxyName, vbNullString, 0)
Else
m_hFTP = InternetOpen(mc_AGENTNAME, INTERNET_OPEN_TYPE_DIRECT, _
vbNullString, vbNullString, 0)
End If
If m_hFTP = 0 Then RaiseError errOpenFTP

End Sub

Public Sub CloseFTP()
'Terminate FTP session

If m_hCon Then Me.CloseServer
If m_hFTP Then InternetCloseHandle m_hFTP
m_hCon = 0
m_hFTP = 0

End Sub

Public Sub OpenServer(Optional pServerName, Optional pUserName, Optional pPassword)
'Establish connection to server

'If FTP session not initiated
If m_hFTP = 0 Then RaiseError errNotOpen
'
'Handle optional parameters
If Not IsMissing(pServerName) Then m_ServerName = pServerName
If Not IsMissing(pUserName) Then m_UserName = pUserName
If Not IsMissing(pPassword) Then m_Password = pPassword
'
'Handle empty properties
If Len(m_ServerName) = 0 Then RaiseError errNoServer
'
'The following are translated to:
' UserName: Anonymous
' Password: default email address
'by the API, if nulls passed
If Len(m_UserName) = 0 Then m_UserName = vbNullString
If Len(m_Password) = 0 Then m_Password = vbNullString
'
m_hCon = InternetConnect(m_hFTP, m_ServerName, INTERNET_INVALID_PORT_NUMBER, _
m_UserName, m_Password, INTERNET_SERVICE_FTP, _
INTERNET_FLAG_PASSIVE, 0)
If m_hCon = 0 Then RaiseError errOpenCon

End Sub

Public Sub CloseServer()
'Terminate connection to server

If m_hCon Then InternetCloseHandle m_hCon
m_hCon = 0

End Sub

Public Sub GetFile(Optional pRemoteDir, Optional pRemoteFile, _
Optional pLocalFile, Optional pTransferType)
'Retrieve a file from server
'pTransferType accepts "ASCII" or "BINARY"

'Bail out if server connection not established
If m_hCon = 0 Then RaiseError errNotConnected
'
'Handle optional parameters
If Not IsMissing(pRemoteDir) Then m_RemoteDir = pRemoteDir
If Not IsMissing(pRemoteFile) Then m_RemoteFile = pRemoteFile
If Not IsMissing(pLocalFile) Then m_LocalFile = pLocalFile
If Not IsMissing(pTransferType) Then Me.TransferType = pTransferType
'
'Handle empty properties
If Len(m_RemoteDir) = 0 Then m_RemoteDir = "."
If Len(m_RemoteFile) = 0 Then RaiseError errNoRemoteFile
If Len(m_LocalFile) = 0 Then RaiseError errNoLocalFile
If Len(m_TransferType) = 0 Then Me.TransferType = "BINARY"
'
'Change directory on server
Me.SetDir m_RemoteDir
'
If FtpGetFile(m_hCon, m_RemoteFile, m_LocalFile, False, _
INTERNET_FLAG_RELOAD, m_TransferType, 0) = False Then
RaiseError errGetFile
End If

End Sub

Public Sub PutFile(Optional pRemoteDir, Optional pRemoteFile, _
Optional pLocalFile, Optional pTransferType)
'Transmit a file to server
'pTransferType accepts "ASCII" or "BINARY"

'Bail out if server connection not established
If m_hCon = 0 Then RaiseError errNotConnected
'
'Handle optional parameters
If Not IsMissing(pRemoteDir) Then m_RemoteDir = pRemoteDir
If Not IsMissing(pRemoteFile) Then m_RemoteFile = pRemoteFile
If Not IsMissing(pLocalFile) Then m_LocalFile = pLocalFile
If Not IsMissing(pTransferType) Then Me.TransferType = pTransferType
'
'Handle empty properties
If Len(m_RemoteDir) = 0 Then m_RemoteDir = "."
If Len(m_RemoteFile) = 0 Then RaiseError errNoRemoteFile
If Len(m_LocalFile) = 0 Then RaiseError errNoLocalFile
If Len(m_TransferType) = 0 Then Me.TransferType = "BINARY"
'
'Change directory on server
Me.SetDir m_RemoteDir
'
If FtpPutFile(m_hCon, m_LocalFile, m_RemoteFile, m_TransferType, 0) = False Then
RaiseError errPutFile
End If

End Sub

Public Sub DelFile(Optional pRemoteDir, Optional pRemoteFile)
'Delete a file on server

'Bail out if server connection not established
If m_hCon = 0 Then RaiseError errNotConnected
'
'Handle optional parameters
If Not IsMissing(pRemoteDir) Then m_RemoteDir = pRemoteDir
If Not IsMissing(pRemoteFile) Then m_RemoteFile = pRemoteFile
'
'Handle empty properties
If Len(m_RemoteDir) = 0 Then m_RemoteDir = "."
If Len(m_RemoteFile) = 0 Then RaiseError errNoRemoteFile
'
'Change directory on server
Me.SetDir m_RemoteDir
'
If FtpDeleteFile(m_hCon, m_RemoteFile) = False Then
RaiseError errDelFile
End If

End Sub

Public Sub RenFile(Optional pOldName, Optional pNewName)
'Rename a file on server

'Bail out if server connection not established
If m_hCon = 0 Then RaiseError errNotConnected
'
'Handle optional parameters
If Not IsMissing(pOldName) Then m_RemoteFile = pOldName
If Not IsMissing(pNewName) Then m_NewFileName = pNewName
'
'Handle empty properties
If Len(m_RemoteFile) = 0 Then RaiseError errNoRemoteFile
If Len(m_NewFileName) = 0 Then m_NewFileName = m_RemoteFile
'
'Change directory on server
Me.SetDir m_RemoteDir
'
If FtpRenameFile(m_hCon, m_RemoteFile, m_NewFileName) = False Then
RaiseError errRenFile
End If

End Sub

Public Function GetDir() As String
'Determine current directory on server

Dim Buffer As String
Dim BufLen As Long
'
'Bail out if server connection not established
If m_hCon = 0 Then RaiseError errNotConnected
'
BufLen = MAX_PATH
Buffer = String(BufLen, 0)
If FtpGetCurrentDirectory(m_hCon, Buffer, BufLen) = False Then
RaiseError errGetDir
End If
GetDir = left(Buffer, BufLen)

End Function

Public Sub SetDir(Optional pRemoteDir)
'Change current directory on server

'Bail out if server connection not established
If m_hCon = 0 Then RaiseError errNotConnected
'
'Handle optional parameters
If Not IsMissing(pRemoteDir) Then m_RemoteDir = pRemoteDir
'
'Handle empty properties
If Len(m_RemoteDir) = 0 Then m_RemoteDir = "."
'
If FtpSetCurrentDirectory(m_hCon, m_RemoteDir) = False Then
RaiseError errSetDir
End If

End Sub

Public Sub CreateDir(Optional pRemoteDir)
'Create directory on server

'Bail out if server connection not established
If m_hCon = 0 Then RaiseError errNotConnected
'
'Handle optional parameters
If Not IsMissing(pRemoteDir) Then m_RemoteDir = pRemoteDir
'
'Handle empty properties
If Len(m_RemoteDir) = 0 Then m_RemoteDir = "."
'
If FtpCreateDirectory(m_hCon, m_RemoteDir) = False Then
RaiseError errCreateDir
End If

End Sub

Public Sub DelDir(Optional pRemoteDir)
'Delete directory on server

'Bail out if server connection not established
If m_hCon = 0 Then RaiseError errNotConnected
'
'Handle optional parameters
If Not IsMissing(pRemoteDir) Then m_RemoteDir = pRemoteDir
'
'Handle empty properties
If Len(m_RemoteDir) = 0 Then m_RemoteDir = "."
'
If FtpRemoveDirectory(m_hCon, m_RemoteDir) = False Then
RaiseError errDelDir
End If

End Sub

Public Sub GetFileNames(Optional pRemoteDir, Optional pFileSpec)
'Fill the FileNames collection with list
'of files matching pFileSpec from server's
'current directory

Dim hFind As Long
Dim LastErr As Long
Dim fData As WIN32_FIND_DATA
'
'Bail out if server connection not established
If m_hCon = 0 Then RaiseError errNotConnected
'
'Handle optional parameters
If Not IsMissing(pRemoteDir) Then m_RemoteDir = pRemoteDir
If Not IsMissing(pFileSpec) Then m_FileSpec = pFileSpec
'
'Handle empty properties
If Len(m_RemoteDir) = 0 Then m_RemoteDir = "."
If Len(m_FileSpec) = 0 Then m_FileSpec = "*.*"
'
'Change directory on server
Me.SetDir m_RemoteDir
'
'Find first file matching FileSpec
fData.cFileName = String(MAX_PATH, 0)
'Obtain search handle if successful
hFind = FtpFindFirstFile(m_hCon, m_FileSpec, fData, 0, 0)
LastErr = Err.LastDllError
If hFind = 0 Then
'Bail out if reported error isn't end-of-file-list
If LastErr <> ERROR_NO_MORE_FILES Then
RaiseError errFindFirst
End If
'Must be no more files
Exit Sub
End If
'
'Reset variable for next call
LastErr = NO_ERROR
'
'Add filename to the collection
FileNames.Add left(fData.cFileName, _
InStr(1, fData.cFileName, vbNullChar, vbBinaryCompare) - 1)
Do
'Find next file matching FileSpec
fData.cFileName = String(MAX_PATH, 0)
If InternetFindNextFile(hFind, fData) = False Then
LastErr = Err.LastDllError
If LastErr = ERROR_NO_MORE_FILES Then
'Bail out if no more files
Exit Do
Else
'Must be a 'real' error
InternetCloseHandle hFind
RaiseError errFindNext
End If
Else
'Add filename to the collection
FileNames.Add left(fData.cFileName, _
InStr(1, fData.cFileName, vbNullChar, vbBinaryCompare) - 1)
End If
Loop
'
'Release the search handle
InternetCloseHandle hFind

End Sub

Public Sub ClearFileNames()
'Clear contents of FileNames collection

Dim itm As Long
'
With FileNames
For itm = 1 To .Count
.Remove 1
Next
End With

End Sub

Private Sub Class_Initialize()
'Set property defaults

m_RemoteDir = "."
m_RemoteFile = vbNullString
m_LocalFile = vbNullString
m_NewFileName = vbNullString
m_UserName = vbNullString
m_Password = vbNullString
m_ProxyName = vbNullString
m_ServerName = vbNullString
m_TransferType = FTP_TRANSFER_TYPE_BINARY

End Sub

Private Sub Class_Terminate()
Me.ClearFileNames
End Sub

'''''''''''''''''''''''''''''''
'Utility Routines
'''''''''''''''''''''''''''''''
Private Sub RaiseError(ByVal ErrValue As String)
'Extracts the value to be added to the vbObjectError
'constant from the 1st section of ErrValue, and
'the error description from the 2nd section
'(Sections delimited with ';')
'Appends the last internet response string

Dim ptr As Integer
Dim InetErr As Long
'
'If we have a session handle, destroy the session
If m_hCon <> 0 Or m_hFTP <> 0 Then Me.CloseFTP
'
ptr = InStr(1, ErrValue, ";")
InetErr = Err.LastDllError
Err.Raise vbObjectError + Val(left$(ErrValue, ptr - 1)), _
"FTP Class", _
Mid$(ErrValue, ptr + 1) & ". (OS error code = " & InetErr & ")" & _
vbCrLf & "Internet Response: " & LastResponse(InetErr)

End Sub

Private Function LastResponse(ByVal ErrNum As Long) As String
'Obtains the last response string issued by server

Dim Buffer As String
Dim BufLen As Long
'
If ErrNum = ERROR_INTERNET_EXTENDED_ERROR Then
ErrNum = 0
InternetGetLastResponseInfo ErrNum, vbNullString, BufLen
Buffer = String(BufLen + 1, 0)
InternetGetLastResponseInfo ErrNum, Buffer, BufLen
LastResponse = left(Buffer, BufLen)
End If

End Function
 
Regarding updating SQL, how do you want to do this ?

Are you storing just the url to the file, you can use followhyperlink to then link to it.

Or is the SQL a local database, ie. are you downloading a file from FTP and want to store the file in the SQL DB, if so you can write the BLOB into the SQL DB, which I can supply code for you to do.

However if you are uploading the file and then want to use serverside web application to do this then this is something I haven't done, I use PERL as my web language of choice, what would you be trying to do it with?

Give me more info and i'll try to help.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top