libssh2-0.2.0.9: FFI bindings to libssh2 SSH2 client library (http://libssh2.org/)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.SSH.Client.LibSSH2

Synopsis

Types

data Session Source #

Instances

Instances details
Data Session Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Session -> c Session #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Session #

toConstr :: Session -> Constr #

dataTypeOf :: Session -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Session) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Session) #

gmapT :: (forall b. Data b => b -> b) -> Session -> Session #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Session -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Session -> r #

gmapQ :: (forall d. Data d => d -> u) -> Session -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Session -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Session -> m Session #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Session -> m Session #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Session -> m Session #

Show Session Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Eq Session Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

(==) :: Session -> Session -> Bool #

(/=) :: Session -> Session -> Bool #

ToPointer Session Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

toPointer :: Session -> Ptr () Source #

data Channel Source #

Instances

Instances details
Data Channel Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Channel -> c Channel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Channel #

toConstr :: Channel -> Constr #

dataTypeOf :: Channel -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Channel) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Channel) #

gmapT :: (forall b. Data b => b -> b) -> Channel -> Channel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Channel -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Channel -> r #

gmapQ :: (forall d. Data d => d -> u) -> Channel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Channel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Channel -> m Channel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Channel -> m Channel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Channel -> m Channel #

Show Channel Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Eq Channel Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

(==) :: Channel -> Channel -> Bool #

(/=) :: Channel -> Channel -> Bool #

ToPointer Channel Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

toPointer :: Channel -> Ptr () Source #

data KnownHosts Source #

Instances

Instances details
Data KnownHosts Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KnownHosts -> c KnownHosts #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KnownHosts #

toConstr :: KnownHosts -> Constr #

dataTypeOf :: KnownHosts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KnownHosts) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KnownHosts) #

gmapT :: (forall b. Data b => b -> b) -> KnownHosts -> KnownHosts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KnownHosts -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KnownHosts -> r #

gmapQ :: (forall d. Data d => d -> u) -> KnownHosts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KnownHosts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KnownHosts -> m KnownHosts #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KnownHosts -> m KnownHosts #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KnownHosts -> m KnownHosts #

Show KnownHosts Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Eq KnownHosts Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

ToPointer KnownHosts Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

toPointer :: KnownHosts -> Ptr () Source #

data Sftp Source #

Instances

Instances details
Show Sftp Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

showsPrec :: Int -> Sftp -> ShowS #

show :: Sftp -> String #

showList :: [Sftp] -> ShowS #

ToPointer Sftp Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

toPointer :: Sftp -> Ptr () Source #

data SftpHandle Source #

Instances

Instances details
Show SftpHandle Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

ToPointer SftpHandle Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

toPointer :: SftpHandle -> Ptr () Source #

Functions

withSSH2 Source #

Arguments

:: FilePath

Path to known_hosts file

-> FilePath

Path to public key file

-> FilePath

Path to private key file

-> String

Passphrase

-> String

Remote user name

-> String

Remote host name

-> Int

Remote port number (usually 22)

-> (Session -> IO a)

Actions to perform on session

-> IO a 

Execute some actions within SSH2 connection. Uses public key authentication.

withSSH2User Source #

Arguments

:: FilePath

Path to known_hosts file

-> String

Remote user name

-> String

Remote password

-> String

Remote host name

-> Int

Remote port number (usually 22)

-> (Session -> IO a)

Actions to perform on session

-> IO a 

Execute some actions within SSH2 connection. Uses username/password authentication.

withSSH2Agent Source #

Arguments

:: String

Path to known_hosts file

-> String

Remote user name

-> String

Remote host name

-> Int

Remote port number (usually 22)

-> (Session -> IO a)

Actions to perform on session

-> IO a 

Execute some actions within SSH2 connection. Uses agent based public key authentication.

withSession Source #

Arguments

:: String

Remote host name

-> Int

Remote port number (usually 22)

-> (Session -> IO a)

Actions to perform on handle and session

-> IO a 

Execute some actions within SSH2 session

withChannel :: Session -> (Channel -> IO a) -> IO (Int, a) Source #

Execute some actions withing SSH2 channel

withChannelBy Source #

Arguments

:: IO a

Create a channel (and possibly other stuff)

-> (a -> Channel)

Extract the channel from "other stuff"

-> (a -> IO b)

Actions to execute on the channel

-> IO (Int, b)

Channel exit status and return value

Generalization of withChannel

checkHost Source #

Arguments

:: Session 
-> String

Remote host name

-> Int

Remote port number (usually 22)

-> FilePath

Path to known_hosts file

-> [KnownHostType]

Flags specifying what format the host name is, what format the key is and what key type it is

-> IO KnownHostResult 

readAllChannel :: Channel -> IO ByteString Source #

Read all data from the channel

Although this function returns a lazy bytestring, the data is not read lazily.

writeAllChannel :: Channel -> ByteString -> IO () Source #

Write a lazy bytestring to the channel

scpSendFile Source #

Arguments

:: Session 
-> Int

File creation mode (0o777, for example)

-> FilePath

Path to local file

-> FilePath

Remote file path

-> IO Integer 

Send a file to remote host via SCP. Returns size of sent data.

scpReceiveFile Source #

Arguments

:: Session 
-> FilePath

Remote file path

-> FilePath

Path to local file

-> IO Integer 

Receive file from remote host via SCP. Returns size of received data.

Sftp Functions

withSFTP Source #

Arguments

:: FilePath

Path to known_hosts file

-> FilePath

Path to public key file

-> FilePath

Path to private key file

-> String

Passphrase

-> String

Remote user name

-> String

Remote host name

-> Int

Remote port number (usually 22)

-> (Sftp -> IO a)

Actions to perform on sftp session

-> IO a 

Execute some actions within SFTP connection. Uses public key authentication.

withSFTPUser Source #

Arguments

:: FilePath

Path to known_hosts file

-> String

Remote user name

-> String

Remote password

-> String

Remote host name

-> Int

Remote port number (usually 22)

-> (Sftp -> IO a)

Actions to perform on sftp session

-> IO a 

Execute some actions within SFTP connection. Uses username/password authentication.

withSftpSession Source #

Arguments

:: Session

Remote host name

-> (Sftp -> IO a)

Actions to perform on sftp session

-> IO a 

Execute some actions within SFTP session

sftpListDir Source #

Arguments

:: Sftp

Opened sftp session

-> FilePath

Remote directory to read

-> IO SftpList 

Reads directory information Returns the list of files with attributes, directory . and .. are not excluded

sftpRenameFile Source #

Arguments

:: Sftp

Opened sftp session

-> FilePath

Old file name

-> FilePath

New file name

-> IO () 

Rename a file on the sftp server

sftpSendFile Source #

Arguments

:: Sftp

Opened sftp session

-> FilePath

Path to local file

-> FilePath

Remote file path

-> Int

File creation mode (0o777, for example)

-> IO Integer 

Send a file to remote host via SFTP Returns size of sent data.

sftpSendFromHandle Source #

Arguments

:: Sftp

Opened sftp session

-> Handle

Handle to read from

-> FilePath

Remote file path

-> Int

File creation mode (0o777, for example)

-> IO Integer 

Send a file to remote host via SFTP Returns size of sent data.

sftpSendBytes Source #

Arguments

:: Sftp

Opened sftp session

-> ByteString

Bytes to write

-> FilePath

Remote file path

-> Int

File creation mode (0o777, for example)

-> IO Integer 

Send bytes to a remote host via SFTP Returns the size of sent data.

sftpReceiveFile Source #

Arguments

:: Sftp

Opened sftp session

-> FilePath

Path to local file

-> FilePath

Remote file path

-> IO Integer 

Received a file from remote host via SFTP Returns size of received data.

sftpReadFileToHandler :: SftpHandle -> Handle -> Int -> IO Int Source #

Download file from the sftp server

sftpFstat :: SftpHandle -> IO SftpAttributes Source #

Get sftp attributes from the sftp handler

sftpDeleteFile Source #

Arguments

:: Sftp

Opened sftp session

-> FilePath

Path to the file to be deleted

-> IO () 

Delete file from SFTP server

Utilities

socketConnect :: String -> Int -> IO Socket Source #

Similar to Network.connectTo, but does not socketToHandle.