License | Public Domain |
---|---|
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Network.FTP.Client
Description
Synopsis
- withFTP :: (MonadIO m, MonadMask m) => String -> Int -> (Handle -> FTPResponse -> m a) -> m a
- withFTPS :: (MonadMask m, MonadIO m) => String -> Int -> (Handle -> FTPResponse -> m a) -> m a
- login :: MonadIO m => Handle -> String -> String -> m FTPResponse
- pasv :: MonadIO m => Handle -> m (String, Int)
- rename :: MonadIO m => Handle -> String -> String -> m FTPResponse
- dele :: MonadIO m => Handle -> String -> m FTPResponse
- cwd :: MonadIO m => Handle -> String -> m FTPResponse
- size :: MonadIO m => Handle -> String -> m Int
- mkd :: MonadIO m => Handle -> String -> m String
- rmd :: MonadIO m => Handle -> String -> m FTPResponse
- pwd :: MonadIO m => Handle -> m String
- quit :: MonadIO m => Handle -> m FTPResponse
- nlst :: (MonadIO m, MonadMask m) => Handle -> [String] -> m ByteString
- retr :: (MonadIO m, MonadMask m) => Handle -> String -> m ByteString
- list :: (MonadIO m, MonadMask m) => Handle -> [String] -> m ByteString
- stor :: (MonadIO m, MonadMask m) => Handle -> String -> ByteString -> RTypeCode -> m ()
- mlsd :: (MonadIO m, MonadMask m) => Handle -> String -> m [MlsxResponse]
- mlst :: (MonadIO m, MonadMask m) => Handle -> String -> m MlsxResponse
- data FTPCommand
- = User String
- | Pass String
- | Acct String
- | RType RTypeCode
- | Retr String
- | Nlst [String]
- | Port HostAddress PortNumber
- | Stor String
- | List [String]
- | Rnfr String
- | Rnto String
- | Dele String
- | Size String
- | Mkd String
- | Rmd String
- | Pbsz Int
- | Prot ProtType
- | Mlsd String
- | Mlst String
- | Cwd String
- | Cdup
- | Ccc
- | Auth
- | Pwd
- | Abor
- | Pasv
- | Quit
- data FTPResponse = FTPResponse {}
- data FTPMessage
- data ResponseStatus
- = Wait
- | Success
- | Continue
- | FailureRetry
- | Failure
- data MlsxResponse = MlsxResponse {}
- data RTypeCode
- data PortActivity
- data ProtType
- data Security
- data Handle = Handle {
- send :: ByteString -> IO ()
- sendLine :: ByteString -> IO ()
- recv :: Int -> IO ByteString
- recvLine :: IO ByteString
- security :: Security
- data FTPException
- sIOHandleImpl :: Handle -> Handle
- tlsHandleImpl :: Connection -> Handle
- sendCommand :: MonadIO m => Handle -> FTPCommand -> m FTPResponse
- sendCommandS :: MonadIO m => Handle -> FTPCommand -> m FTPResponse
- recvAll :: (MonadIO m, MonadCatch m) => Handle -> m ByteString
- sendAll :: MonadIO m => Handle -> [FTPCommand] -> m [FTPResponse]
- sendAllS :: MonadIO m => Handle -> [FTPCommand] -> m [FTPResponse]
- getLineResp :: Handle -> IO ByteString
- getResponse :: MonadIO m => Handle -> m FTPResponse
- getResponseS :: MonadIO m => Handle -> m FTPResponse
- sendCommandLine :: MonadIO m => Handle -> ByteString -> m ()
- createSendDataCommand :: (MonadIO m, MonadMask m) => Handle -> PortActivity -> FTPCommand -> m Handle
- createTLSSendDataCommand :: (MonadIO m, MonadMask m) => Handle -> PortActivity -> FTPCommand -> m Connection
- parseMlsxLine :: ByteString -> MlsxResponse
Main Entrypoints
withFTP :: (MonadIO m, MonadMask m) => String -> Int -> (Handle -> FTPResponse -> m a) -> m a Source #
Takes a host name and port. A handle for interacting with the server will be returned in a callback.
withFTP "ftp.server.com" 21 $ h welcome -> do print welcome login h "username" "password" print =<< nlst h []
withFTPS :: (MonadMask m, MonadIO m) => String -> Int -> (Handle -> FTPResponse -> m a) -> m a Source #
Takes a host name and port. A handle for interacting with the server will be returned in a callback. The commands will be protected with TLS.
withFTPS "ftps.server.com" 21 $ h welcome -> do print welcome login h "username" "password" print =<< nlst h []
Control Commands
Data Commands
Types
data FTPCommand Source #
Commands according to the FTP specification
Constructors
Instances
Show FTPCommand Source # | |
Defined in Network.FTP.Client Methods showsPrec :: Int -> FTPCommand -> ShowS # show :: FTPCommand -> String # showList :: [FTPCommand] -> ShowS # |
data FTPResponse Source #
Response from an FTP command. ex "200 Welcome!"
Constructors
FTPResponse | |
Fields
|
Instances
Show FTPResponse Source # | |
Defined in Network.FTP.Client Methods showsPrec :: Int -> FTPResponse -> ShowS # show :: FTPResponse -> String # showList :: [FTPResponse] -> ShowS # | |
Eq FTPResponse Source # | |
Defined in Network.FTP.Client |
data FTPMessage Source #
Constructors
SingleLine ByteString | |
MultiLine [ByteString] |
Instances
Show FTPMessage Source # | |
Defined in Network.FTP.Client Methods showsPrec :: Int -> FTPMessage -> ShowS # show :: FTPMessage -> String # showList :: [FTPMessage] -> ShowS # | |
Eq FTPMessage Source # | |
Defined in Network.FTP.Client |
data ResponseStatus Source #
First digit of an FTP response
Constructors
Wait | 1 |
Success | 2 |
Continue | 3 |
FailureRetry | 4 |
Failure | 5 |
Instances
Show ResponseStatus Source # | |
Defined in Network.FTP.Client Methods showsPrec :: Int -> ResponseStatus -> ShowS # show :: ResponseStatus -> String # showList :: [ResponseStatus] -> ShowS # | |
Eq ResponseStatus Source # | |
Defined in Network.FTP.Client Methods (==) :: ResponseStatus -> ResponseStatus -> Bool # (/=) :: ResponseStatus -> ResponseStatus -> Bool # |
data MlsxResponse Source #
Constructors
MlsxResponse | |
Instances
Show MlsxResponse Source # | |
Defined in Network.FTP.Client Methods showsPrec :: Int -> MlsxResponse -> ShowS # show :: MlsxResponse -> String # showList :: [MlsxResponse] -> ShowS # |
data PortActivity Source #
Can send and recieve a ByteString
.
Constructors
Handle | |
Fields
|
Exceptions
data FTPException Source #
Constructors
FailureRetryException FTPResponse | |
FailureException FTPResponse | |
UnsuccessfulException FTPResponse | |
BogusResponseFormatException FTPResponse | |
BadProtocolResponseException ByteString |
Instances
Exception FTPException Source # | |
Defined in Network.FTP.Client Methods toException :: FTPException -> SomeException # fromException :: SomeException -> Maybe FTPException # displayException :: FTPException -> String # | |
Show FTPException Source # | |
Defined in Network.FTP.Client Methods showsPrec :: Int -> FTPException -> ShowS # show :: FTPException -> String # showList :: [FTPException] -> ShowS # |
Handle Implementations
sIOHandleImpl :: Handle -> Handle Source #
tlsHandleImpl :: Connection -> Handle Source #
Lower Level Functions
sendCommand :: MonadIO m => Handle -> FTPCommand -> m FTPResponse Source #
Send a command to the server and get a response back.
Some commands use a data Handle
, and their data is not returned here.
sendCommandS :: MonadIO m => Handle -> FTPCommand -> m FTPResponse Source #
recvAll :: (MonadIO m, MonadCatch m) => Handle -> m ByteString Source #
Recieve all data and return it as a ByteString
sendAll :: MonadIO m => Handle -> [FTPCommand] -> m [FTPResponse] Source #
Equvalent to
mapM . sendCommand
sendAllS :: MonadIO m => Handle -> [FTPCommand] -> m [FTPResponse] Source #
Equvalent to
mapM . sendCommandS
getLineResp :: Handle -> IO ByteString Source #
Get a line from the server
getResponse :: MonadIO m => Handle -> m FTPResponse Source #
Get a full response from the server
Used in sendCommand
getResponseS :: MonadIO m => Handle -> m FTPResponse Source #
sendCommandLine :: MonadIO m => Handle -> ByteString -> m () Source #
createSendDataCommand :: (MonadIO m, MonadMask m) => Handle -> PortActivity -> FTPCommand -> m Handle Source #
Send setup commands to the server and
create a data Handle
createTLSSendDataCommand :: (MonadIO m, MonadMask m) => Handle -> PortActivity -> FTPCommand -> m Connection Source #
Send setup commands to the server and create a data TLS connection