Maintainer | defanor <defanor@uberspace.net> |
---|---|
Stability | unstable |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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 $ doauthenticateWithKeys
session Nothing "id_rsa.pub" "id_rsa" NothingwithSessionChannel
session $ \channel ->channelRequestExec
channel "uname -a" >>channelReadAll
channel >>= BS.putStrLnwithSFTPSession
session $ \sftp -> dosftpRead
sftp "/tmp/example.txt" >>= BS.putStrLnsftpUnlink
sftp "/tmp/example.txt"
Synopsis
- withSSH :: IO a -> IO a
- withPublicKeyFile :: FilePath -> (SSHKey -> IO a) -> IO a
- withPrivateKeyFile :: FilePath -> Maybe String -> (SSHKey -> IO a) -> IO a
- data SSHOption
- = 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
- setOption :: SSHSession -> SSHOption -> IO ()
- withSession :: [SSHOption] -> (SSHSession -> IO a) -> IO a
- withConnection :: SSHSession -> IO a -> IO a
- authenticateWithKeys :: SSHSession -> Maybe String -> FilePath -> FilePath -> Maybe String -> IO ()
- authenticateWithPassword :: SSHSession -> Maybe String -> String -> IO ()
- authenticateWithAgent :: SSHSession -> Maybe String -> IO ()
- authenticateWithNone :: SSHSession -> Maybe String -> IO ()
- withChannel :: SSHSession -> (SSHChannel -> IO a) -> IO a
- withSessionChannel :: SSHSession -> (SSHChannel -> IO a) -> IO a
- channelRequestExec :: SSHChannel -> String -> IO CInt
- channelReadAll :: SSHChannel -> IO ByteString
- withSFTPSession :: SSHSession -> (SFTPSession -> IO a) -> IO a
- sftpRead :: SFTPSession -> FilePath -> IO ByteString
- sftpUnlink :: SFTPSession -> FilePath -> IO ()
- data SSHErrorType
- = SSHErrorCode Int
- | SSHNull
- data SSHError = SSHError String SSHErrorType
- throwOnError :: Integral a => String -> IO a -> IO a
- throwOnNull :: String -> IO (Ptr a) -> IO (Ptr a)
- readAll :: (Integral a, Integral b) => String -> (CString -> a -> IO b) -> IO ByteString
- withCStringMaybe :: Maybe String -> (CString -> IO a) -> IO a
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
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 |
setOption :: SSHSession -> SSHOption -> IO () Source #
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
Arguments
:: SSHSession | |
-> Maybe String | Username, SHOULD be |
-> 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 |
-> String | Password |
-> IO () |
Authenticates using a password
authenticateWithAgent Source #
Arguments
:: SSHSession | |
-> Maybe String | Username, SHOULD be |
-> IO () |
Authenticates using SSH agent.
Arguments
:: SSHSession | |
-> Maybe String | Username, SHOULD be |
-> 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
Show SSHErrorType Source # | |
Defined in Network.LibSSH Methods showsPrec :: Int -> SSHErrorType -> ShowS show :: SSHErrorType -> String showList :: [SSHErrorType] -> ShowS |
Constructors
SSHError String SSHErrorType |
Instances
Exception SSHError Source # | |
Defined in Network.LibSSH Methods toException :: SSHError -> SomeException fromException :: SomeException -> Maybe SSHError displayException :: SSHError -> String | |
Show SSHError 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.
Arguments
:: String | Function name |
-> IO (Ptr a) | Action to run |
-> IO (Ptr a) |
Throws an exception if the performed action returns a NULL.
Arguments
:: (Integral a, Integral b) | |
=> String | Function name |
-> (CString -> a -> IO b) | A reader action, such as |
-> 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
.