Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class AuthAgent agent where
- getPublicKeys :: agent -> IO [PublicKey]
- getSignature :: ByteArrayAccess hash => agent -> PublicKey -> hash -> IO (Maybe Signature)
- data KeyPair = KeyPairEd25519 PublicKey SecretKey
- newKeyPair :: IO KeyPair
- decodePrivateKeyFile :: (MonadFail m, ByteArray input, ByteArrayAccess passphrase, ByteArray comment) => passphrase -> input -> m [(KeyPair, comment)]
- class (InputStream stream, OutputStream stream) => DuplexStream stream
- class InputStream stream where
- peek :: stream -> Int -> IO ByteString
- receive :: stream -> Int -> IO ByteString
- receiveUnsafe :: stream -> MemView -> IO Int
- receiveAll :: InputStream stream => stream -> Int -> IO ByteString
- class OutputStream stream where
- send :: stream -> ByteString -> IO Int
- sendUnsafe :: stream -> MemView -> IO Int
- sendAll :: OutputStream stream => stream -> ByteString -> IO ()
- data TransportConfig = TransportConfig {}
- data Disconnect = Disconnect DisconnectParty DisconnectReason DisconnectMessage
- data DisconnectParty
- data DisconnectReason
- = DisconnectHostNotAllowedToConnect
- | DisconnectProtocolError
- | DisconnectKeyExchangeFailed
- | DisconnectReserved
- | DisconnectMacError
- | DisconnectCompressionError
- | DisconnectServiceNotAvailable
- | DisconnectProtocolVersionNotSupported
- | DisconnectHostKeyNotVerifiable
- | DisconnectConnectionLost
- | DisconnectByApplication
- | DisconnectTooManyConnection
- | DisconnectAuthCancelledByUser
- | DisconnectNoMoreAuthMethodsAvailable
- | DisconnectIllegalUsername
- | DisconnectOtherReason Word32
- newtype DisconnectMessage = DisconnectMessage ByteString
- data Name
- type UserName = Name
- type ServiceName = Name
- class HasName a where
- data HostKeyAlgorithm = SshEd25519
- data KeyExchangeAlgorithm = Curve25519Sha256AtLibsshDotOrg
- data EncryptionAlgorithm = Chacha20Poly1305AtOpensshDotCom
- data CompressionAlgorithm = None
- data PublicKey
- data Signature
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.
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.
Instances
AuthAgent KeyPair Source # | |
Defined in Network.SSH.AuthAgent getPublicKeys :: KeyPair -> IO [PublicKey] Source # getSignature :: ByteArrayAccess hash => KeyPair -> PublicKey -> hash -> IO (Maybe Signature) Source # |
newKeyPair
newKeyPair :: IO KeyPair Source #
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 # | |
Defined in Network.SSH.TStreamingQueue |
receive, receiveAll
class InputStream stream where Source #
An InputStream
is something that bytes can be read from.
peek :: stream -> Int -> IO ByteString Source #
Like receive
, but does not actually remove anything
from the input buffer.
- 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.
- This method shall block until at least one byte becomes available or the connection got closed.
- 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!
- The second parameter determines how many bytes to receive at most,
but the
ByteString
returned might be shorter. - 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.
Instances
InputStream TStreamingQueue Source # | |
Defined in Network.SSH.TStreamingQueue peek :: TStreamingQueue -> Int -> IO ByteString Source # receive :: TStreamingQueue -> Int -> IO ByteString Source # receiveUnsafe :: TStreamingQueue -> MemView -> IO Int Source # |
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.
send :: stream -> ByteString -> IO Int Source #
Send a chunk of bytes into the stream.
- This method shall block until at least one byte could be sent or the connection got closed.
- 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.
Instances
OutputStream TStreamingQueue Source # | |
Defined in Network.SSH.TStreamingQueue send :: TStreamingQueue -> ByteString -> IO Int Source # sendUnsafe :: TStreamingQueue -> MemView -> IO Int Source # |
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
data TransportConfig Source #
Instances
Default TransportConfig Source # | |
Defined in Network.SSH.Transport def :: TransportConfig # |
Misc
Disconnect
data Disconnect Source #
Instances
Eq Disconnect Source # | |
Defined in Network.SSH.Exception (==) :: Disconnect -> Disconnect -> Bool # (/=) :: Disconnect -> Disconnect -> Bool # | |
Ord Disconnect Source # | |
Defined in Network.SSH.Exception compare :: Disconnect -> Disconnect -> Ordering # (<) :: Disconnect -> Disconnect -> Bool # (<=) :: Disconnect -> Disconnect -> Bool # (>) :: Disconnect -> Disconnect -> Bool # (>=) :: Disconnect -> Disconnect -> Bool # max :: Disconnect -> Disconnect -> Disconnect # min :: Disconnect -> Disconnect -> Disconnect # | |
Show Disconnect Source # | |
Defined in Network.SSH.Exception showsPrec :: Int -> Disconnect -> ShowS # show :: Disconnect -> String # showList :: [Disconnect] -> ShowS # | |
Exception Disconnect Source # | |
Defined in Network.SSH.Exception toException :: Disconnect -> SomeException # fromException :: SomeException -> Maybe Disconnect # displayException :: Disconnect -> String # |
data DisconnectParty Source #
Instances
Eq DisconnectParty Source # | |
Defined in Network.SSH.Exception (==) :: DisconnectParty -> DisconnectParty -> Bool # (/=) :: DisconnectParty -> DisconnectParty -> Bool # | |
Ord DisconnectParty Source # | |
Defined in Network.SSH.Exception compare :: DisconnectParty -> DisconnectParty -> Ordering # (<) :: DisconnectParty -> DisconnectParty -> Bool # (<=) :: DisconnectParty -> DisconnectParty -> Bool # (>) :: DisconnectParty -> DisconnectParty -> Bool # (>=) :: DisconnectParty -> DisconnectParty -> Bool # max :: DisconnectParty -> DisconnectParty -> DisconnectParty # min :: DisconnectParty -> DisconnectParty -> DisconnectParty # | |
Show DisconnectParty Source # | |
Defined in Network.SSH.Exception showsPrec :: Int -> DisconnectParty -> ShowS # show :: DisconnectParty -> String # showList :: [DisconnectParty] -> ShowS # |
data DisconnectReason Source #
Instances
Eq DisconnectReason Source # | |
Defined in Network.SSH.Exception (==) :: DisconnectReason -> DisconnectReason -> Bool # (/=) :: DisconnectReason -> DisconnectReason -> Bool # | |
Ord DisconnectReason Source # | |
Defined in Network.SSH.Exception compare :: DisconnectReason -> DisconnectReason -> Ordering # (<) :: DisconnectReason -> DisconnectReason -> Bool # (<=) :: DisconnectReason -> DisconnectReason -> Bool # (>) :: DisconnectReason -> DisconnectReason -> Bool # (>=) :: DisconnectReason -> DisconnectReason -> Bool # max :: DisconnectReason -> DisconnectReason -> DisconnectReason # min :: DisconnectReason -> DisconnectReason -> DisconnectReason # | |
Show DisconnectReason Source # | |
Defined in Network.SSH.Exception showsPrec :: Int -> DisconnectReason -> ShowS # show :: DisconnectReason -> String # showList :: [DisconnectReason] -> ShowS # | |
Encoding DisconnectReason Source # | |
Defined in Network.SSH.Message put :: Builder b => DisconnectReason -> b Source # |
newtype DisconnectMessage Source #
Instances
Name
type ServiceName = Name Source #
class HasName a where Source #
Instances
HasName PublicKey Source # | |
HasName Signature Source # | |
HasName AuthMethod Source # | |
Defined in Network.SSH.Message name :: AuthMethod -> Name Source # | |
HasName CompressionAlgorithm Source # | |
Defined in Network.SSH.Algorithms name :: CompressionAlgorithm -> Name Source # | |
HasName EncryptionAlgorithm Source # | |
Defined in Network.SSH.Algorithms name :: EncryptionAlgorithm -> Name Source # | |
HasName KeyExchangeAlgorithm Source # | |
Defined in Network.SSH.Algorithms name :: KeyExchangeAlgorithm -> Name Source # | |
HasName HostKeyAlgorithm Source # | |
Defined in Network.SSH.Algorithms name :: HostKeyAlgorithm -> Name Source # |
Algorithms
data HostKeyAlgorithm Source #
Instances
Eq HostKeyAlgorithm Source # | |
Defined in Network.SSH.Algorithms (==) :: HostKeyAlgorithm -> HostKeyAlgorithm -> Bool # (/=) :: HostKeyAlgorithm -> HostKeyAlgorithm -> Bool # | |
Show HostKeyAlgorithm Source # | |
Defined in Network.SSH.Algorithms showsPrec :: Int -> HostKeyAlgorithm -> ShowS # show :: HostKeyAlgorithm -> String # showList :: [HostKeyAlgorithm] -> ShowS # | |
HasName HostKeyAlgorithm Source # | |
Defined in Network.SSH.Algorithms name :: HostKeyAlgorithm -> Name Source # |
data KeyExchangeAlgorithm Source #
Instances
Eq KeyExchangeAlgorithm Source # | |
Defined in Network.SSH.Algorithms (==) :: KeyExchangeAlgorithm -> KeyExchangeAlgorithm -> Bool # (/=) :: KeyExchangeAlgorithm -> KeyExchangeAlgorithm -> Bool # | |
Show KeyExchangeAlgorithm Source # | |
Defined in Network.SSH.Algorithms showsPrec :: Int -> KeyExchangeAlgorithm -> ShowS # show :: KeyExchangeAlgorithm -> String # showList :: [KeyExchangeAlgorithm] -> ShowS # | |
HasName KeyExchangeAlgorithm Source # | |
Defined in Network.SSH.Algorithms name :: KeyExchangeAlgorithm -> Name Source # |
data EncryptionAlgorithm Source #
Instances
Eq EncryptionAlgorithm Source # | |
Defined in Network.SSH.Algorithms (==) :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool # (/=) :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool # | |
Show EncryptionAlgorithm Source # | |
Defined in Network.SSH.Algorithms showsPrec :: Int -> EncryptionAlgorithm -> ShowS # show :: EncryptionAlgorithm -> String # showList :: [EncryptionAlgorithm] -> ShowS # | |
HasName EncryptionAlgorithm Source # | |
Defined in Network.SSH.Algorithms name :: EncryptionAlgorithm -> Name Source # |
data CompressionAlgorithm Source #
Instances
Eq CompressionAlgorithm Source # | |
Defined in Network.SSH.Algorithms (==) :: CompressionAlgorithm -> CompressionAlgorithm -> Bool # (/=) :: CompressionAlgorithm -> CompressionAlgorithm -> Bool # | |
Show CompressionAlgorithm Source # | |
Defined in Network.SSH.Algorithms showsPrec :: Int -> CompressionAlgorithm -> ShowS # show :: CompressionAlgorithm -> String # showList :: [CompressionAlgorithm] -> ShowS # | |
HasName CompressionAlgorithm Source # | |
Defined in Network.SSH.Algorithms name :: CompressionAlgorithm -> Name Source # |