hssh-0.1.0.0: SSH protocol implementation

Safe HaskellNone
LanguageHaskell2010

Network.SSH

Contents

Synopsis

Authentication & Identity

AuthAgent

class AuthAgent agent where Source #

An AuthAgent is something that is capable of cryptographic signing using a public key algorithm like Ed25519 or RSA.

Currently, KeyPair is the only instance, but the method signatures have been designed with other mechanisms like HSM's or agent-forwarding in mind.

Methods

getPublicKeys :: agent -> IO [PublicKey] Source #

Get a list of public keys for which the agent holds the corresponding private keys.

The list contents may change when called subsequently.

getSignature :: ByteArrayAccess hash => agent -> PublicKey -> hash -> IO (Maybe Signature) Source #

Sign the given hash with the requested public key.

The signature may be denied in case the key is no longer available. This method shall not throw exceptions, but rather return Nothing if possible.

data KeyPair Source #

Instances
Eq KeyPair Source # 
Instance details

Defined in Network.SSH.Key

Methods

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

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

Show KeyPair Source # 
Instance details

Defined in Network.SSH.Key

AuthAgent KeyPair Source # 
Instance details

Defined in Network.SSH.AuthAgent

newKeyPair

decodePrivateKeyFile

decodePrivateKeyFile :: (MonadFail m, ByteArray input, ByteArrayAccess passphrase, ByteArray comment) => passphrase -> input -> m [(KeyPair, comment)] Source #

Input / Output

class (InputStream stream, OutputStream stream) => DuplexStream stream Source #

A DuplexStream is an abstraction over all things that behave like file handles or sockets.

Instances
DuplexStream TStreamingQueue Source # 
Instance details

Defined in Network.SSH.TStreamingQueue

receive, receiveAll

class InputStream stream where Source #

An InputStream is something that bytes can be read from.

Minimal complete definition

peek, receive

Methods

peek :: stream -> Int -> IO ByteString Source #

Like receive, but does not actually remove anything from the input buffer.

  1. Use with care! There are very few legitimate use cases for this.

receive :: stream -> Int -> IO ByteString Source #

Receive a chunk of bytes from the stream.

  1. This method shall block until at least one byte becomes available or the connection got closed.
  2. As with sockets, the chunk boundaries are not guaranteed to be preserved during transmission although this will be most often the case. Never rely on this behaviour!
  3. The second parameter determines how many bytes to receive at most, but the ByteString returned might be shorter.
  4. Returns a chunk which is guaranteed to be shorter or equal than the given limit. It is empty when the connection got closed and all subsequent attempts to read shall return the empty string. This must be checked when collecting chunks in a loop or the program will get stuck in endless recursion!

receiveUnsafe :: stream -> MemView -> IO Int Source #

Like receive, but allows for more efficiency with less memory allocations when working with builders and re-usable buffers.

receiveAll :: InputStream stream => stream -> Int -> IO ByteString Source #

Try to receive a ByteString of the designated length in bytes.

  • Blocks until either the complete ByteString has been received or throws an exception when the connection got terminated before enough bytes arrived.

send, sendAll

class OutputStream stream where Source #

An OutputStream is something that chunks of bytes can be written to.

Minimal complete definition

send

Methods

send :: stream -> ByteString -> IO Int Source #

Send a chunk of bytes into the stream.

  1. This method shall block until at least one byte could be sent or the connection got closed.
  2. Returns the number of bytes sent or 0 if the other side closed the connection. The return value must be checked when using a loop for sending or the program will get stuck in endless recursion!

sendUnsafe :: stream -> MemView -> IO Int Source #

Like send, but allows for more efficiency with less memory allocations when working with builders and re-usable buffers.

sendAll :: OutputStream stream => stream -> ByteString -> IO () Source #

Try to send the complete ByteString.

  • Blocks until either the ByteString has been sent or throws an exception when the connection got terminated while sending it.

Transport

Misc

Disconnect

data DisconnectReason Source #

newtype DisconnectMessage Source #

Instances
Eq DisconnectMessage Source # 
Instance details

Defined in Network.SSH.Exception

Ord DisconnectMessage Source # 
Instance details

Defined in Network.SSH.Exception

Show DisconnectMessage Source # 
Instance details

Defined in Network.SSH.Exception

IsString DisconnectMessage Source # 
Instance details

Defined in Network.SSH.Exception

Semigroup DisconnectMessage Source # 
Instance details

Defined in Network.SSH.Exception

Monoid DisconnectMessage Source # 
Instance details

Defined in Network.SSH.Exception

Name

data Name Source #

Instances
Eq Name Source # 
Instance details

Defined in Network.SSH.Name

Methods

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

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

Ord Name Source # 
Instance details

Defined in Network.SSH.Name

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Network.SSH.Name

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in Network.SSH.Name

Methods

fromString :: String -> Name #

class HasName a where Source #

Methods

name :: a -> Name Source #

Algorithms

PublicKey

data PublicKey Source #

Instances
Eq PublicKey Source # 
Instance details

Defined in Network.SSH.Key

Show PublicKey Source # 
Instance details

Defined in Network.SSH.Key

HasName PublicKey Source # 
Instance details

Defined in Network.SSH.Key

Methods

name :: PublicKey -> Name Source #

Encoding PublicKey Source # 
Instance details

Defined in Network.SSH.Message

Methods

put :: Builder b => PublicKey -> b Source #

get :: Get PublicKey Source #

Signature

data Signature Source #

Instances
Eq Signature Source # 
Instance details

Defined in Network.SSH.Message

Show Signature Source # 
Instance details

Defined in Network.SSH.Message

HasName Signature Source # 
Instance details

Defined in Network.SSH.Message

Methods

name :: Signature -> Name Source #

Encoding Signature Source # 
Instance details

Defined in Network.SSH.Message

Methods

put :: Builder b => Signature -> b Source #

get :: Get Signature Source #