hssh-0.1.0.0: SSH protocol implementation

Safe HaskellNone
LanguageHaskell2010

Network.SSH.Internal

Contents

Synopsis

Documentation

type Get = Get Source #

class Encoding a where Source #

Methods

put :: forall b. Builder b => a -> b Source #

get :: Get a Source #

Instances
Encoding PublicKey Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get PublicKey Source #

Encoding PublicKey Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get PublicKey Source #

Encoding Signature Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Signature Source #

Encoding DisconnectReason Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get DisconnectReason Source #

Encoding PublicKey Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get PublicKey Source #

Encoding ChannelId Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelId Source #

Encoding ChannelType Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelType Source #

Encoding SessionId Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get SessionId Source #

Encoding Version Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Version Source #

Encoding Cookie Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Cookie Source #

Encoding PtySettings Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get PtySettings Source #

Encoding Signature Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Signature Source #

Encoding AuthMethod Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get AuthMethod Source #

Encoding ChannelFailure Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelFailure Source #

Encoding ChannelSuccess Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelSuccess Source #

Encoding ChannelRequestExitSignal Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelRequestExitStatus Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelRequestSignal Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelRequestExec Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelRequestShell Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelRequestWindowChange Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelRequestPty Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelRequestPty Source #

Encoding ChannelRequestEnv Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelRequestEnv Source #

Encoding ChannelRequest Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelRequest Source #

Encoding ChannelClose Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelClose Source #

Encoding ChannelEof Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelEof Source #

Encoding ChannelExtendedData Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelData Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelData Source #

Encoding ChannelWindowAdjust Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelOpenFailureReason Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelOpenFailure Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelOpenConfirmation Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelOpen Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelOpen Source #

Encoding UserAuthPublicKeyOk Source # 
Instance details

Defined in Network.SSH.Message

Encoding UserAuthBanner Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get UserAuthBanner Source #

Encoding UserAuthSuccess Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get UserAuthSuccess Source #

Encoding UserAuthFailure Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get UserAuthFailure Source #

Encoding UserAuthRequest Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get UserAuthRequest Source #

Encoding KexEcdhReply Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get KexEcdhReply Source #

Encoding KexEcdhInit Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get KexEcdhInit Source #

Encoding KexNewKeys Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get KexNewKeys Source #

Encoding KexInit Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get KexInit Source #

Encoding ServiceAccept Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ServiceAccept Source #

Encoding ServiceRequest Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ServiceRequest Source #

Encoding Debug Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Debug Source #

Encoding Unimplemented Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Unimplemented Source #

Encoding Ignore Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Ignore Source #

Encoding Disconnected Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Disconnected Source #

Encoding Message Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Message Source #

Encoding ConnectionMsg Source # 
Instance details

Defined in Network.SSH.Server.Service.Connection

Methods

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

get :: Get ConnectionMsg Source #

runPut :: ByteArrayBuilder -> ByteString Source #

putExitCode :: Builder b => ExitCode -> b Source #

putWord8 :: Builder b => Word8 -> b Source #

putBytes :: Builder b => ByteArrayAccess ba => ba -> b Source #

putByteString :: Builder b => ByteString -> b Source #

putString :: (Builder b, ByteArrayAccess ba) => ba -> b Source #

putShortString :: Builder b => ShortByteString -> b Source #

putName :: Builder b => Name -> b Source #

putBool :: Builder b => Bool -> b Source #

putAsMPInt :: (Builder b, ByteArrayAccess ba) => ba -> b Source #

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

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

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 #

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

Message

class MessageStream a where Source #

Methods

sendMessage :: forall msg. Encoding msg => a -> msg -> IO () Source #

receiveMessage :: forall msg. Encoding msg => a -> IO msg Source #

Instances
MessageStream Transport Source # 
Instance details

Defined in Network.SSH.Transport

Methods

sendMessage :: Encoding msg => Transport -> msg -> IO () Source #

receiveMessage :: Encoding msg => Transport -> IO msg Source #

Disconnected (1)

data DisconnectReason Source #

Ignore (2)

data Ignore Source #

Constructors

Ignore 
Instances
Eq Ignore Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

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

Show Ignore Source # 
Instance details

Defined in Network.SSH.Message

Encoding Ignore Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Ignore Source #

Unimplemented (3)

Debug (4)

data Debug Source #

Instances
Eq Debug Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

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

Show Debug Source # 
Instance details

Defined in Network.SSH.Message

Methods

showsPrec :: Int -> Debug -> ShowS #

show :: Debug -> String #

showList :: [Debug] -> ShowS #

Encoding Debug Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Debug Source #

ServiceRequest (5)

ServiceAccept (6)

KexInit (20)

KexNewKeys (21)

data KexNewKeys Source #

Constructors

KexNewKeys 
Instances
Eq KexNewKeys Source # 
Instance details

Defined in Network.SSH.Message

Show KexNewKeys Source # 
Instance details

Defined in Network.SSH.Message

Encoding KexNewKeys Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get KexNewKeys Source #

KexEcdhInit (30)

data KexEcdhInit Source #

Instances
Eq KexEcdhInit Source # 
Instance details

Defined in Network.SSH.Message

Show KexEcdhInit Source # 
Instance details

Defined in Network.SSH.Message

Encoding KexEcdhInit Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get KexEcdhInit Source #

KexEcdhReply (31)

UserAuthRequest (50)

UserAuthFailure (51)

UserAuthSuccess (52)

UserAuthBanner (53)

UserAuthPublicKeyOk (60)

ChannelOpen (90)

ChannelOpenConfirmation (91)

ChannelOpenFailure (92)

ChannelWindowAdjust (93)

ChannelData (94)

data ChannelData Source #

Instances
Eq ChannelData Source # 
Instance details

Defined in Network.SSH.Message

Show ChannelData Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelData Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelData Source #

ChannelExtendedData (95)

ChannelEof (96)

data ChannelEof Source #

Constructors

ChannelEof ChannelId 
Instances
Eq ChannelEof Source # 
Instance details

Defined in Network.SSH.Message

Show ChannelEof Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelEof Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelEof Source #

ChannelClose (97)

data ChannelClose Source #

Constructors

ChannelClose ChannelId 
Instances
Eq ChannelClose Source # 
Instance details

Defined in Network.SSH.Message

Show ChannelClose Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelClose Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelClose Source #

ChannelRequest (98)

ChannelSuccess (99)

ChannelFailure (100)

Misc

newtype ChannelId Source #

Constructors

ChannelId Word32 
Instances
Eq ChannelId Source # 
Instance details

Defined in Network.SSH.Message

Ord ChannelId Source # 
Instance details

Defined in Network.SSH.Message

Show ChannelId Source # 
Instance details

Defined in Network.SSH.Message

Encoding ChannelId Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get ChannelId Source #

data Cookie Source #

Instances
Eq Cookie Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

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

Ord Cookie Source # 
Instance details

Defined in Network.SSH.Message

Show Cookie Source # 
Instance details

Defined in Network.SSH.Message

Encoding Cookie Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Cookie Source #

newtype Password Source #

Instances
Eq Password Source # 
Instance details

Defined in Network.SSH.Message

Ord Password Source # 
Instance details

Defined in Network.SSH.Message

Show Password Source # 
Instance details

Defined in Network.SSH.Message

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 #

newtype SessionId Source #

Instances
Eq SessionId Source # 
Instance details

Defined in Network.SSH.Message

Ord SessionId Source # 
Instance details

Defined in Network.SSH.Message

Show SessionId Source # 
Instance details

Defined in Network.SSH.Message

Encoding SessionId Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get SessionId Source #

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 #

newtype Version Source #

Constructors

Version ShortByteString 
Instances
Eq Version Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

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

Ord Version Source # 
Instance details

Defined in Network.SSH.Message

Show Version Source # 
Instance details

Defined in Network.SSH.Message

Encoding Version Source # 
Instance details

Defined in Network.SSH.Message

Methods

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

get :: Get Version Source #

newtype Name Source #

Constructors

Name ShortByteString 
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 #

data Connection identity Source #

data ConnectionConfig identity Source #

Constructors

ConnectionConfig 

Fields

Instances
Default (ConnectionConfig identity) Source # 
Instance details

Defined in Network.SSH.Server.Service.Connection

Methods

def :: ConnectionConfig identity #

newtype SessionHandler Source #

The session handler contains the application logic that serves a client's shell or exec request.

  • The Command parameter will be present if this is an exec request and absent for shell requests.
  • The TermInfo parameter will be present if the client requested a pty.
  • The Environment parameter contains the set of all env requests the client issued before the actual shell or exec request.
  • stdin, stdout and stderr are streams. The former can only be read from while the latter can only be written to. After the handler has gracefully terminated, the implementation assures that all bytes will be sent before sending an eof and actually closing the channel. has gracefully terminated. The client will then receive an eof and close.
  • A SIGILL exit signal will be sent if the handler terminates with an exception. Otherwise the client will receive the returned exit code.
handler :: SessionHandler
handler = SessionHandler $ \env mterm mcmd stdin stdout stderr -> case mcmd of
    Just "echo" -> do
        bs <- receive stdin 1024
        sendAll stdout bs
        pure ExitSuccess
    Nothing ->
        pure (ExitFailure 1)

Constructors

SessionHandler (forall stdin stdout stderr. (InputStream stdin, OutputStream stdout, OutputStream stderr) => Environment -> Maybe TermInfo -> Maybe Command -> stdin -> stdout -> stderr -> IO ExitCode) 

data TermInfo Source #

The TermInfo describes the client's terminal settings if it requested a pty.

NOTE: This will follow in a future release. You may access the constructor through the Internal module, but should not rely on it yet.

Constructors

TermInfo PtySettings 

newtype Command Source #

The Command is what the client wants to execute when making an exec request (shell requests don't have a command).

Constructors

Command ByteString 

data DirectTcpIpRequest Source #

When the client makes a DirectTcpIpRequest it requests a TCP port forwarding.

Constructors

DirectTcpIpRequest 

Fields

newtype DirectTcpIpHandler Source #

The DirectTcpIpHandler contains the application logic that handles port forwarding requests.

There is of course no need to actually do a real forwarding - this mechanism might also be used to give access to process internal services like integrated web servers etc.

  • When the handler exits gracefully, the implementation assures that all bytes will be sent to the client before terminating the stream with an eof and actually closing the channel.

Constructors

DirectTcpIpHandler (forall stream. DuplexStream stream => stream -> IO ()) 

serveConnection :: forall stream identity. MessageStream stream => ConnectionConfig identity -> stream -> identity -> IO () Source #

data UserAuthConfig identity Source #

Configuration for the user authentication layer.

After a successful key exchange the client will usually request the user-auth service to authenticate against. In this implementation, the user-auth service is the only service available after key exchange and the client must request the connection layer through the authentication layer. Except for transport messages, all other message types will result in a disconnect as long as user authentication is in progress (looking at you, libssh ;-)

Constructors

UserAuthConfig 

Fields

  • onAuthRequest :: UserName -> ServiceName -> PublicKey -> IO (Maybe identity)

    This handler will be called for each authentication attempt.

    1. The client might try several methods and keys: Just return Nothing for every request that is not sufficient to determine the user's identity.
    2. When access shall be granted, return Just. The identity may contain whatever is desired; it may be just the UserName.
    3. When the client uses public key authentication, the transport layer has already determined that the client is in posession of the corresponding private key (by requesting and validating a signature).
    4. The default rejects all authentication attempts unconditionally.
  • userAuthMaxTime :: Word16

    Timeout for user authentication in seconds (default is 60).

    1. A SSH_DISCONNECT_BY_APPLICATION will be sent to the client when the timeout occurs before successful authentication.
  • userAuthMaxAttempts :: Word16

    A limit for the number of failed attempts per connection (default is 20).

    1. A SSH_DISCONNECT_BY_APPLICATION will be sent to the client when limit has been exceeded.
Instances
Default (UserAuthConfig identity) Source # 
Instance details

Defined in Network.SSH.Server.Service.UserAuth

Methods

def :: UserAuthConfig identity #

withAuthentication :: forall identity stream a. MessageStream stream => UserAuthConfig identity -> stream -> SessionId -> (ServiceName -> Maybe (identity -> IO a)) -> IO a Source #

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

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.

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.

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.

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.

data Transport Source #

Instances
MessageStream Transport Source # 
Instance details

Defined in Network.SSH.Transport

Methods

sendMessage :: Encoding msg => Transport -> msg -> IO () Source #

receiveMessage :: Encoding msg => Transport -> IO msg Source #

withTransport :: (DuplexStream stream, AuthAgent agent) => TransportConfig -> Maybe agent -> stream -> (Transport -> SessionId -> IO a) -> IO (Either Disconnect a) Source #

plainEncryptionContext :: OutputStream stream => stream -> EncryptionContext Source #

plainDecryptionContext :: InputStream stream => stream -> DecryptionContext Source #

newChaCha20Poly1305EncryptionContext :: (OutputStream stream, ByteArrayAccess key) => stream -> key -> key -> IO EncryptionContext Source #

newChaCha20Poly1305DecryptionContext :: InputStream stream => ByteArrayAccess key => stream -> key -> key -> IO DecryptionContext Source #