libssh-0.1.0.0: libssh bindings
Maintainerdefanor <defanor@uberspace.net>
Stabilityunstable
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.LibSSH

Description

See the libssh documentation for its API reference and a usage tutorial.

These bindings are intended to be simple, predictable, and stay close to the original library, only providing a Haskell API with more conventional types, replacing error codes with exceptions, helping to ensure that allocated resources are freed (using the "with" functions). All the used types and utility functions are exposed.

A usage example:

import Network.LibSSH as SSH
import qualified Data.ByteString.Char8 as BS

main :: IO ()
main = withSSH $
  withSession [OptHost "example.com", OptPort 22, OptUser (Just "user"),
               OptKnownhosts Nothing, OptTimeout 600] $ \session ->
  withConnection session $ do
  authenticateWithKeys session Nothing "id_rsa.pub" "id_rsa" Nothing
  withSessionChannel session $ \channel ->
    channelRequestExec channel "uname -a"
    >> channelReadAll channel >>= BS.putStrLn
  withSFTPSession session $ \sftp -> do
    sftpRead sftp "/tmp/example.txt" >>= BS.putStrLn
    sftpUnlink sftp "/tmp/example.txt"
Synopsis

Documentation

withSSH :: IO a -> IO a Source #

Invokes ssh_init and ssh_finalize. Library usage must be wrapped into it for correct functioning if libssh is linked statically, or with its versions before 0.8.0. Not necessary, but still safe to use otherwise.

Public Key Infrastructure

withPublicKeyFile :: FilePath -> (SSHKey -> IO a) -> IO a Source #

Imports a public key from a file or a PKCS #11 device, performs an action with it.

withPrivateKeyFile :: FilePath -> Maybe String -> (SSHKey -> IO a) -> IO a Source #

Imports a private key from a file or a PKCS #11 device, performs an action with it.

Session

data SSHOption Source #

Constructors

OptHost String 
OptPort Int 
OptPortStr String 
OptFd Int 
OptBindaddr String 
OptUser (Maybe String) 
OptSSHDir (Maybe FilePath) 
OptKnownhosts (Maybe FilePath) 
OptIdentity String 
OptTimeout Int 
OptTimeoutUsec Int 

withSession :: [SSHOption] -> (SSHSession -> IO a) -> IO a Source #

Performs an action with a new session, with options set for it.

withConnection :: SSHSession -> IO a -> IO a Source #

Connects, performs an action, disconnects.

Authentication

authenticateWithKeys Source #

Arguments

:: SSHSession 
-> Maybe String

Username, SHOULD be Nothing.

-> FilePath

Public key file

-> FilePath

Private key file

-> Maybe String

Passphrase

-> IO () 

Authenticates using the provided key pair.

authenticateWithPassword Source #

Arguments

:: SSHSession 
-> Maybe String

Username, SHOULD be Nothing.

-> String

Password

-> IO () 

Authenticates using a password

authenticateWithAgent Source #

Arguments

:: SSHSession 
-> Maybe String

Username, SHOULD be Nothing.

-> IO () 

Authenticates using SSH agent.

authenticateWithNone Source #

Arguments

:: SSHSession 
-> Maybe String

Username, SHOULD be Nothing.

-> IO () 

Authenticates using the "none" method.

Channels

withChannel :: SSHSession -> (SSHChannel -> IO a) -> IO a Source #

Performs an action with a new channel (ssh_channel_new).

withSessionChannel :: SSHSession -> (SSHChannel -> IO a) -> IO a Source #

Performs an action with a new session channel (ssh_channel_open_session).

channelRequestExec :: SSHChannel -> String -> IO CInt Source #

Executes a shell command with ssh_channel_request_exec.

channelReadAll :: SSHChannel -> IO ByteString Source #

Reads all data from a channel with ssh_channel_read and readAll.

SFTP

withSFTPSession :: SSHSession -> (SFTPSession -> IO a) -> IO a Source #

Performs an action with a new SFTP session.

sftpRead :: SFTPSession -> FilePath -> IO ByteString Source #

Reads file contents over SFTP.

sftpUnlink :: SFTPSession -> FilePath -> IO () Source #

Unlinks (deletes, removes) a remote file.

Utility functions and exceptions

data SSHErrorType Source #

Constructors

SSHErrorCode Int 
SSHNull 

Instances

Instances details
Show SSHErrorType Source # 
Instance details

Defined in Network.LibSSH

Methods

showsPrec :: Int -> SSHErrorType -> ShowS

show :: SSHErrorType -> String

showList :: [SSHErrorType] -> ShowS

data SSHError Source #

Constructors

SSHError String SSHErrorType 

Instances

Instances details
Exception SSHError Source # 
Instance details

Defined in Network.LibSSH

Methods

toException :: SSHError -> SomeException

fromException :: SomeException -> Maybe SSHError

displayException :: SSHError -> String

Show SSHError Source # 
Instance details

Defined in Network.LibSSH

Methods

showsPrec :: Int -> SSHError -> ShowS

show :: SSHError -> String

showList :: [SSHError] -> ShowS

throwOnError Source #

Arguments

:: Integral a 
=> String

Function name

-> IO a

Action to run

-> IO a 

Throws an exception if the number returned by the provided action is less than 0.

throwOnNull Source #

Arguments

:: String

Function name

-> IO (Ptr a)

Action to run

-> IO (Ptr a) 

Throws an exception if the performed action returns a NULL.

readAll Source #

Arguments

:: (Integral a, Integral b) 
=> String

Function name

-> (CString -> a -> IO b)

A reader action, such as ssh_channel_read or sftp_read

-> IO ByteString 

Reads data using a provided action, until the returned number is 0 (indicating EOF) or less (indicating an error, leading to an exception).

withCStringMaybe :: Maybe String -> (CString -> IO a) -> IO a Source #

Like withCString, but provides a nullPtr on Nothing.