libssh2-0.2.0.8: FFI bindings to libssh2 SSH2 client library (http://libssh2.org/)
Safe HaskellNone
LanguageHaskell2010

Network.SSH.Client.LibSSH2.Foreign

Synopsis

Types

data KnownHosts Source #

Instances

Instances details
Eq KnownHosts Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

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

ToPointer KnownHosts Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

toPointer :: KnownHosts -> Ptr () Source #

data KnownHostResult Source #

Constructors

MATCH 
MISMATCH 
NOTFOUND 
FAILURE 

data KnownHost Source #

Constructors

KnownHost 

Instances

Instances details
Eq KnownHost Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Foreign

Show KnownHost Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Foreign

Session functions

initialize :: Bool -> IO () Source #

Initialize libssh2. Pass True to enable encryption or False to disable it.

exit :: IO () Source #

Deinitialize libssh2.

initSession :: IO Session Source #

Create Session object

freeSession :: Session -> IO () Source #

Free Session object's memory

disconnectSession Source #

Arguments

:: Session 
-> String

Goodbye message

-> IO () 

Disconnect session (but do not free memory)

handshake :: Session -> Socket -> IO () Source #

Run SSH handshake on network socket.

Known hosts functions

initKnownHosts :: Session -> IO KnownHosts Source #

Create KnownHosts object for given session.

freeKnownHosts :: KnownHosts -> IO () Source #

Free KnownHosts object's memory

knownHostsReadFile Source #

Arguments

:: KnownHosts 
-> FilePath

Path to known_hosts file

-> IO Int 

Read known hosts from file

getHostKey :: Session -> IO (String, Size, CInt) Source #

Get remote host public key

checkKnownHost Source #

Arguments

:: KnownHosts 
-> String

Host name

-> Int

Port number (usually 22)

-> String

Host public key

-> [KnownHostType]

Host flags (see libssh2 documentation)

-> IO KnownHostResult 

Check host data against known hosts.

Authentication

publicKeyAuthFile Source #

Arguments

:: Session

Session

-> String

Username

-> String

Path to public key

-> String

Path to private key

-> String

Passphrase

-> IO () 

Perform public key authentication.

usernamePasswordAuth Source #

Arguments

:: Session

Session

-> String

Username

-> String

Password

-> IO () 

Perform username/password authentication.

Channel functions

openChannelSession :: Session -> IO Channel Source #

Open a channel for session.

closeChannel :: Channel -> IO () Source #

Close channel (but do not free memory)

freeChannel :: Channel -> IO () Source #

Free channel object's memory

readChannel Source #

Arguments

:: Channel 
-> Size

Amount of data to read

-> IO ByteString 

Read data from channel.

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

Write data to channel.

writeChannelFromHandle :: Channel -> Handle -> IO Integer Source #

Write all data to channel from handle. Returns amount of transferred data.

readChannelToHandle :: Channel -> Handle -> Offset -> IO Integer Source #

Read all data from channel to handle. Returns amount of transferred data.

channelExecute :: Channel -> String -> IO () Source #

Execute command

channelShell :: Channel -> IO () Source #

Execute shell command

channelExitStatus :: Channel -> IO Int Source #

Get channel exit status

channelExitSignal :: Channel -> IO (Int, String, Maybe String, Maybe String) Source #

Get channel exit signal. Returns: (possibly error code, exit signal name, possibly error message, possibly language code).

scpSendChannel :: Session -> String -> Int -> Int64 -> POSIXTime -> POSIXTime -> IO Channel Source #

Create SCP file send channel.

scpReceiveChannel :: Session -> FilePath -> IO (Channel, Offset) Source #

Create SCP file receive channel. TODO: receive struct stat also.

SFTP functions

sftpOpenDir :: Sftp -> String -> IO SftpHandle Source #

Open directory file handler

sftpReadDir :: SftpHandle -> IO (Maybe (ByteString, SftpAttributes)) Source #

Read directory from file handler

sftpCloseHandle :: SftpHandle -> IO () Source #

Close file handle

sftpOpenFile :: Sftp -> String -> Int -> [SftpFileTransferFlags] -> IO SftpHandle Source #

Open regular file handler

sftpRenameFile Source #

Arguments

:: Sftp

Opened sftp session

-> FilePath

Old file name

-> FilePath

New file name

-> IO () 

Rename a file on the sftp server

sftpRenameFileEx Source #

Arguments

:: Sftp

Opened sftp session

-> FilePath

Old file name

-> FilePath

New file name

-> [RenameFlag]

Rename flags

-> IO () 

Rename a file on the sftp server

sftpWriteFileFromHandler :: SftpHandle -> Handle -> IO Integer Source #

Upload file to the sftp server

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

SSH Agent functions

data Agent Source #

Instances

Instances details
Show Agent Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

showsPrec :: Int -> Agent -> ShowS #

show :: Agent -> String #

showList :: [Agent] -> ShowS #

ToPointer Agent Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Methods

toPointer :: Agent -> Ptr () Source #

data AgentPublicKey Source #

Instances

Instances details
Eq AgentPublicKey Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

Data AgentPublicKey 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) -> AgentPublicKey -> c AgentPublicKey #

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

toConstr :: AgentPublicKey -> Constr #

dataTypeOf :: AgentPublicKey -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AgentPublicKey Source # 
Instance details

Defined in Network.SSH.Client.LibSSH2.Types

agentInit :: Session -> IO Agent Source #

Agent support

Initialize a new ssh agent handle.

agentConnect :: Agent -> IO () Source #

Attempt to establish a connection to an ssh agent process. | The environment variable SSH_AUTH_SOCK is used to determine where to connect on unix.

agentDisconnect :: Agent -> IO () Source #

Cleans up a connection to an ssh agent.

agentListIdentities :: Agent -> IO () Source #

Get or update the list of known identities. Must be called at least once.

agentGetIdentity Source #

Arguments

:: Agent

Agent handle.

-> Maybe AgentPublicKey

Previous key returned.

-> IO (Maybe AgentPublicKey) 

Copies one identity from the agent to the local process.

agentGetIdentities :: Agent -> IO [AgentPublicKey] Source #

Copies all the keys from the agent to the local process.

agentPublicKeyComment :: AgentPublicKey -> IO ByteString Source #

Return the comment from the given agent public key.

agentPublicKeyBlob :: AgentPublicKey -> IO ByteString Source #

Return the bytes of the given agent public key.

agentUserAuth Source #

Arguments

:: Agent

Agent handle.

-> String

Username to authenticate with.

-> AgentPublicKey

Public key to use from the agent.

-> IO () 

Perform agent based public key authentication. You almost certainly want @agentAuthenticate instead of this, since this only does one round of authentication with the agent.

agentAuthenticate Source #

Arguments

:: String

Remote user name.

-> Agent

Connection to an agent.

-> IO () 

Authenticate with an ssh agent. Takes a user and an agent and tries each key from the agent in succession. Throws AUTHENTICATION_FAILED if it's unable to authenticate. If you call this, you need to call @agentListIdentities at least once.

Debug