Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.SSH.Internal
Contents
- Message
- Disconnected (1)
- Ignore (2)
- Unimplemented (3)
- Debug (4)
- ServiceRequest (5)
- ServiceAccept (6)
- KexInit (20)
- KexNewKeys (21)
- KexEcdhInit (30)
- KexEcdhReply (31)
- UserAuthRequest (50)
- UserAuthFailure (51)
- UserAuthSuccess (52)
- UserAuthBanner (53)
- UserAuthPublicKeyOk (60)
- ChannelOpen (90)
- ChannelOpenConfirmation (91)
- ChannelOpenFailure (92)
- ChannelWindowAdjust (93)
- ChannelData (94)
- ChannelExtendedData (95)
- ChannelEof (96)
- ChannelClose (97)
- ChannelRequest (98)
- ChannelSuccess (99)
- ChannelFailure (100)
- Misc
Synopsis
- data HostKeyAlgorithm = SshEd25519
- data KeyExchangeAlgorithm = Curve25519Sha256AtLibsshDotOrg
- data EncryptionAlgorithm = Chacha20Poly1305AtOpensshDotCom
- data CompressionAlgorithm = None
- type Get = Get
- class Encoding a where
- runPut :: ByteArrayBuilder -> ByteString
- runGet :: (MonadFail m, Encoding a) => ByteString -> m a
- putExitCode :: Builder b => ExitCode -> b
- getExitCode :: Get ExitCode
- getFramed :: Get a -> Get a
- putWord8 :: Builder b => Word8 -> b
- getWord8 :: Get Word8
- expectWord8 :: Word8 -> Get ()
- getWord32 :: Get Word32
- putBytes :: Builder b => ByteArrayAccess ba => ba -> b
- getBytes :: ByteArray ba => Word32 -> Get ba
- lenByteString :: ByteString -> Word32
- putByteString :: Builder b => ByteString -> b
- getByteString :: Word32 -> Get ByteString
- getRemainingByteString :: Get ByteString
- putString :: (Builder b, ByteArrayAccess ba) => ba -> b
- putShortString :: Builder b => ShortByteString -> b
- getShortString :: Get ShortByteString
- getString :: ByteArray ba => Get ba
- getName :: Get Name
- putName :: Builder b => Name -> b
- putBool :: Builder b => Bool -> b
- getBool :: Get Bool
- getTrue :: Get ()
- getFalse :: Get ()
- putAsMPInt :: (Builder b, ByteArrayAccess ba) => ba -> b
- 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
- exceptionProtocolVersionNotSupported :: Disconnect
- exceptionConnectionLost :: Disconnect
- exceptionKexInvalidTransition :: Disconnect
- exceptionKexInvalidSignature :: Disconnect
- exceptionKexNoSignature :: Disconnect
- exceptionKexNoCommonKexAlgorithm :: Disconnect
- exceptionKexNoCommonEncryptionAlgorithm :: Disconnect
- exceptionMacError :: Disconnect
- exceptionInvalidPacket :: Disconnect
- exceptionPacketLengthExceeded :: Disconnect
- exceptionAuthenticationTimeout :: Disconnect
- exceptionAuthenticationLimitExceeded :: Disconnect
- exceptionServiceNotAvailable :: Disconnect
- exceptionInvalidChannelId :: Disconnect
- exceptionInvalidChannelRequest :: Disconnect
- exceptionWindowSizeOverflow :: Disconnect
- exceptionWindowSizeUnderrun :: Disconnect
- exceptionPacketSizeExceeded :: Disconnect
- exceptionDataAfterEof :: Disconnect
- exceptionAlreadyExecuting :: Disconnect
- exceptionUnexpectedMessage :: ByteString -> Disconnect
- data KeyPair = KeyPairEd25519 PublicKey SecretKey
- newKeyPair :: IO KeyPair
- data PublicKey
- decodePrivateKeyFile :: (MonadFail m, ByteArray input, ByteArrayAccess passphrase, ByteArray comment) => passphrase -> input -> m [(KeyPair, comment)]
- toPublicKey :: KeyPair -> PublicKey
- data Message
- = MsgDisconnect Disconnected
- | MsgIgnore Ignore
- | MsgUnimplemented Unimplemented
- | MsgDebug Debug
- | MsgServiceRequest ServiceRequest
- | MsgServiceAccept ServiceAccept
- | MsgKexInit KexInit
- | MsgKexNewKeys KexNewKeys
- | MsgKexEcdhInit KexEcdhInit
- | MsgKexEcdhReply KexEcdhReply
- | MsgUserAuthRequest UserAuthRequest
- | MsgUserAuthFailure UserAuthFailure
- | MsgUserAuthSuccess UserAuthSuccess
- | MsgUserAuthBanner UserAuthBanner
- | MsgUserAuthPublicKeyOk UserAuthPublicKeyOk
- | MsgChannelOpen ChannelOpen
- | MsgChannelOpenConfirmation ChannelOpenConfirmation
- | MsgChannelOpenFailure ChannelOpenFailure
- | MsgChannelWindowAdjust ChannelWindowAdjust
- | MsgChannelData ChannelData
- | MsgChannelExtendedData ChannelExtendedData
- | MsgChannelEof ChannelEof
- | MsgChannelClose ChannelClose
- | MsgChannelRequest ChannelRequest
- | MsgChannelSuccess ChannelSuccess
- | MsgChannelFailure ChannelFailure
- | MsgUnknown Word8
- class MessageStream a where
- sendMessage :: forall msg. Encoding msg => a -> msg -> IO ()
- receiveMessage :: forall msg. Encoding msg => a -> IO msg
- data Disconnected = Disconnected {}
- data DisconnectReason
- = DisconnectHostNotAllowedToConnect
- | DisconnectProtocolError
- | DisconnectKeyExchangeFailed
- | DisconnectReserved
- | DisconnectMacError
- | DisconnectCompressionError
- | DisconnectServiceNotAvailable
- | DisconnectProtocolVersionNotSupported
- | DisconnectHostKeyNotVerifiable
- | DisconnectConnectionLost
- | DisconnectByApplication
- | DisconnectTooManyConnection
- | DisconnectAuthCancelledByUser
- | DisconnectNoMoreAuthMethodsAvailable
- | DisconnectIllegalUsername
- | DisconnectOtherReason Word32
- data Ignore = Ignore
- data Unimplemented = Unimplemented Word32
- data Debug = Debug {}
- data ServiceRequest = ServiceRequest ServiceName
- data ServiceAccept = ServiceAccept ServiceName
- data KexInit = KexInit {
- kexCookie :: Cookie
- kexKexAlgorithms :: [Name]
- kexServerHostKeyAlgorithms :: [Name]
- kexEncryptionAlgorithmsClientToServer :: [Name]
- kexEncryptionAlgorithmsServerToClient :: [Name]
- kexMacAlgorithmsClientToServer :: [Name]
- kexMacAlgorithmsServerToClient :: [Name]
- kexCompressionAlgorithmsClientToServer :: [Name]
- kexCompressionAlgorithmsServerToClient :: [Name]
- kexLanguagesClientToServer :: [Name]
- kexLanguagesServerToClient :: [Name]
- kexFirstPacketFollows :: Bool
- data KexNewKeys = KexNewKeys
- data KexEcdhInit = KexEcdhInit {}
- data KexEcdhReply = KexEcdhReply {}
- data UserAuthRequest = UserAuthRequest UserName ServiceName AuthMethod
- data UserAuthFailure = UserAuthFailure [Name] Bool
- data UserAuthSuccess = UserAuthSuccess
- data UserAuthBanner = UserAuthBanner ShortByteString ShortByteString
- data UserAuthPublicKeyOk = UserAuthPublicKeyOk PublicKey
- data ChannelOpen = ChannelOpen ChannelId ChannelWindowSize ChannelPacketSize ChannelOpenType
- data ChannelOpenType
- data ChannelOpenConfirmation = ChannelOpenConfirmation ChannelId ChannelId ChannelWindowSize ChannelPacketSize
- data ChannelOpenFailure = ChannelOpenFailure ChannelId ChannelOpenFailureReason ShortByteString ShortByteString
- data ChannelOpenFailureReason
- data ChannelWindowAdjust = ChannelWindowAdjust ChannelId ChannelWindowSize
- data ChannelData = ChannelData ChannelId ShortByteString
- data ChannelExtendedData = ChannelExtendedData ChannelId Word32 ShortByteString
- data ChannelEof = ChannelEof ChannelId
- data ChannelClose = ChannelClose ChannelId
- data ChannelRequest = ChannelRequest {}
- data ChannelRequestEnv = ChannelRequestEnv {}
- data ChannelRequestPty = ChannelRequestPty {}
- data ChannelRequestWindowChange = ChannelRequestWindowChange {}
- data ChannelRequestShell = ChannelRequestShell
- data ChannelRequestExec = ChannelRequestExec {}
- data ChannelRequestSignal = ChannelRequestSignal {}
- data ChannelRequestExitStatus = ChannelRequestExitStatus {}
- data ChannelRequestExitSignal = ChannelRequestExitSignal {}
- data ChannelSuccess = ChannelSuccess ChannelId
- data ChannelFailure = ChannelFailure ChannelId
- data AuthMethod
- newtype ChannelId = ChannelId Word32
- newtype ChannelType = ChannelType ShortByteString
- type ChannelPacketSize = Word32
- type ChannelWindowSize = Word32
- data Cookie
- newCookie :: MonadRandom m => m Cookie
- nilCookie :: Cookie
- newtype Password = Password ShortByteString
- data PtySettings = PtySettings {}
- data PublicKey
- newtype SessionId = SessionId ShortByteString
- data Signature
- newtype Version = Version ShortByteString
- type ServiceName = Name
- type UserName = Name
- newtype Name = Name ShortByteString
- class HasName a where
- data Connection identity
- data ConnectionConfig identity = ConnectionConfig {
- onSessionRequest :: identity -> SessionRequest -> IO (Maybe SessionHandler)
- onDirectTcpIpRequest :: identity -> DirectTcpIpRequest -> IO (Maybe DirectTcpIpHandler)
- channelMaxCount :: Word16
- channelMaxQueueSize :: Word32
- channelMaxPacketSize :: Word32
- data SessionRequest = SessionRequest
- newtype SessionHandler = SessionHandler (forall stdin stdout stderr. (InputStream stdin, OutputStream stdout, OutputStream stderr) => Environment -> Maybe TermInfo -> Maybe Command -> stdin -> stdout -> stderr -> IO ExitCode)
- newtype Environment = Environment [(ByteString, ByteString)]
- data TermInfo = TermInfo PtySettings
- newtype Command = Command ByteString
- data DirectTcpIpRequest = DirectTcpIpRequest {}
- newtype DirectTcpIpHandler = DirectTcpIpHandler (forall stream. DuplexStream stream => stream -> IO ())
- data ConnectionMsg
- serveConnection :: forall stream identity. MessageStream stream => ConnectionConfig identity -> stream -> identity -> IO ()
- data UserAuthConfig identity = UserAuthConfig {
- onAuthRequest :: UserName -> ServiceName -> PublicKey -> IO (Maybe identity)
- userAuthMaxTime :: Word16
- userAuthMaxAttempts :: Word16
- withAuthentication :: forall identity stream a. MessageStream stream => UserAuthConfig identity -> stream -> SessionId -> (ServiceName -> Maybe (identity -> IO a)) -> IO a
- verifyAuthSignature :: SessionId -> UserName -> ServiceName -> PublicKey -> Signature -> Bool
- class (InputStream stream, OutputStream stream) => DuplexStream stream
- class OutputStream stream where
- send :: stream -> ByteString -> IO Int
- sendUnsafe :: stream -> MemView -> IO Int
- class InputStream stream where
- peek :: stream -> Int -> IO ByteString
- receive :: stream -> Int -> IO ByteString
- receiveUnsafe :: stream -> MemView -> IO Int
- sendAll :: OutputStream stream => stream -> ByteString -> IO ()
- receiveAll :: InputStream stream => stream -> Int -> IO ByteString
- data Transport
- data TransportConfig = TransportConfig {}
- data Disconnected = Disconnected {}
- withTransport :: (DuplexStream stream, AuthAgent agent) => TransportConfig -> Maybe agent -> stream -> (Transport -> SessionId -> IO a) -> IO (Either Disconnect a)
- plainEncryptionContext :: OutputStream stream => stream -> EncryptionContext
- plainDecryptionContext :: InputStream stream => stream -> DecryptionContext
- newChaCha20Poly1305EncryptionContext :: (OutputStream stream, ByteArrayAccess key) => stream -> key -> key -> IO EncryptionContext
- newChaCha20Poly1305DecryptionContext :: InputStream stream => ByteArrayAccess key => stream -> key -> key -> IO DecryptionContext
- data TStreamingQueue = TStreamingQueue {}
- newTStreamingQueue :: Word32 -> TVar Word32 -> STM TStreamingQueue
- capacity :: TStreamingQueue -> Word32
- getSize :: TStreamingQueue -> STM Word32
- getFree :: TStreamingQueue -> STM Word32
- getWindowSpace :: TStreamingQueue -> STM Word32
- addWindowSpace :: TStreamingQueue -> Word32 -> STM ()
- askWindowSpaceAdjustRecommended :: TStreamingQueue -> STM Bool
- fillWindowSpace :: TStreamingQueue -> STM Word32
- terminate :: TStreamingQueue -> STM ()
- enqueue :: TStreamingQueue -> ByteString -> STM Word32
- dequeue :: TStreamingQueue -> Word32 -> STM ByteString
- dequeueShort :: TStreamingQueue -> Word32 -> STM ShortByteString
- lookAhead :: TStreamingQueue -> Word32 -> STM ByteString
Documentation
data HostKeyAlgorithm Source #
Constructors
SshEd25519 |
Instances
Eq HostKeyAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods (==) :: HostKeyAlgorithm -> HostKeyAlgorithm -> Bool # (/=) :: HostKeyAlgorithm -> HostKeyAlgorithm -> Bool # | |
Show HostKeyAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods showsPrec :: Int -> HostKeyAlgorithm -> ShowS # show :: HostKeyAlgorithm -> String # showList :: [HostKeyAlgorithm] -> ShowS # | |
HasName HostKeyAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods name :: HostKeyAlgorithm -> Name Source # |
data KeyExchangeAlgorithm Source #
Constructors
Curve25519Sha256AtLibsshDotOrg |
Instances
Eq KeyExchangeAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods (==) :: KeyExchangeAlgorithm -> KeyExchangeAlgorithm -> Bool # (/=) :: KeyExchangeAlgorithm -> KeyExchangeAlgorithm -> Bool # | |
Show KeyExchangeAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods showsPrec :: Int -> KeyExchangeAlgorithm -> ShowS # show :: KeyExchangeAlgorithm -> String # showList :: [KeyExchangeAlgorithm] -> ShowS # | |
HasName KeyExchangeAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods name :: KeyExchangeAlgorithm -> Name Source # |
data EncryptionAlgorithm Source #
Constructors
Chacha20Poly1305AtOpensshDotCom |
Instances
Eq EncryptionAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods (==) :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool # (/=) :: EncryptionAlgorithm -> EncryptionAlgorithm -> Bool # | |
Show EncryptionAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods showsPrec :: Int -> EncryptionAlgorithm -> ShowS # show :: EncryptionAlgorithm -> String # showList :: [EncryptionAlgorithm] -> ShowS # | |
HasName EncryptionAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods name :: EncryptionAlgorithm -> Name Source # |
data CompressionAlgorithm Source #
Constructors
None |
Instances
Eq CompressionAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods (==) :: CompressionAlgorithm -> CompressionAlgorithm -> Bool # (/=) :: CompressionAlgorithm -> CompressionAlgorithm -> Bool # | |
Show CompressionAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods showsPrec :: Int -> CompressionAlgorithm -> ShowS # show :: CompressionAlgorithm -> String # showList :: [CompressionAlgorithm] -> ShowS # | |
HasName CompressionAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods name :: CompressionAlgorithm -> Name Source # |
class Encoding a where Source #
Instances
runPut :: ByteArrayBuilder -> ByteString Source #
putExitCode :: Builder b => ExitCode -> b Source #
expectWord8 :: Word8 -> Get () Source #
putBytes :: Builder b => ByteArrayAccess ba => ba -> b Source #
lenByteString :: ByteString -> Word32 Source #
putByteString :: Builder b => ByteString -> b Source #
getByteString :: Word32 -> Get ByteString Source #
putString :: (Builder b, ByteArrayAccess ba) => ba -> b Source #
putShortString :: Builder b => ShortByteString -> b Source #
putAsMPInt :: (Builder b, ByteArrayAccess ba) => ba -> b Source #
data Disconnect Source #
Constructors
Disconnect DisconnectParty DisconnectReason DisconnectMessage |
Instances
Eq Disconnect Source # | |
Defined in Network.SSH.Exception | |
Ord Disconnect Source # | |
Defined in Network.SSH.Exception Methods 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 Methods showsPrec :: Int -> Disconnect -> ShowS # show :: Disconnect -> String # showList :: [Disconnect] -> ShowS # | |
Exception Disconnect Source # | |
Defined in Network.SSH.Exception Methods toException :: Disconnect -> SomeException # fromException :: SomeException -> Maybe Disconnect # displayException :: Disconnect -> String # |
data DisconnectParty Source #
Instances
Eq DisconnectParty Source # | |
Defined in Network.SSH.Exception Methods (==) :: DisconnectParty -> DisconnectParty -> Bool # (/=) :: DisconnectParty -> DisconnectParty -> Bool # | |
Ord DisconnectParty Source # | |
Defined in Network.SSH.Exception Methods 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 Methods showsPrec :: Int -> DisconnectParty -> ShowS # show :: DisconnectParty -> String # showList :: [DisconnectParty] -> ShowS # |
data DisconnectReason Source #
Constructors
Instances
Eq DisconnectReason Source # | |
Defined in Network.SSH.Exception Methods (==) :: DisconnectReason -> DisconnectReason -> Bool # (/=) :: DisconnectReason -> DisconnectReason -> Bool # | |
Ord DisconnectReason Source # | |
Defined in Network.SSH.Exception Methods 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 Methods showsPrec :: Int -> DisconnectReason -> ShowS # show :: DisconnectReason -> String # showList :: [DisconnectReason] -> ShowS # | |
Encoding DisconnectReason Source # | |
Defined in Network.SSH.Message |
newtype DisconnectMessage Source #
Constructors
DisconnectMessage ByteString |
Instances
Constructors
KeyPairEd25519 PublicKey SecretKey |
newKeyPair :: IO KeyPair Source #
Constructors
PublicKeyEd25519 PublicKey | |
PublicKeyRSA PublicKey | |
PublicKeyOther Name |
decodePrivateKeyFile :: (MonadFail m, ByteArray input, ByteArrayAccess passphrase, ByteArray comment) => passphrase -> input -> m [(KeyPair, comment)] Source #
toPublicKey :: KeyPair -> PublicKey Source #
Message
Constructors
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 # | |
Defined in Network.SSH.Transport |
Disconnected (1)
data Disconnected Source #
Constructors
Disconnected | |
Instances
Eq Disconnected Source # | |
Defined in Network.SSH.Message | |
Show Disconnected Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> Disconnected -> ShowS # show :: Disconnected -> String # showList :: [Disconnected] -> ShowS # | |
Encoding Disconnected Source # | |
Defined in Network.SSH.Message |
data DisconnectReason Source #
Constructors
Instances
Eq DisconnectReason Source # | |
Defined in Network.SSH.Exception Methods (==) :: DisconnectReason -> DisconnectReason -> Bool # (/=) :: DisconnectReason -> DisconnectReason -> Bool # | |
Ord DisconnectReason Source # | |
Defined in Network.SSH.Exception Methods 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 Methods showsPrec :: Int -> DisconnectReason -> ShowS # show :: DisconnectReason -> String # showList :: [DisconnectReason] -> ShowS # | |
Encoding DisconnectReason Source # | |
Defined in Network.SSH.Message |
Ignore (2)
Unimplemented (3)
data Unimplemented Source #
Constructors
Unimplemented Word32 |
Instances
Eq Unimplemented Source # | |
Defined in Network.SSH.Message Methods (==) :: Unimplemented -> Unimplemented -> Bool # (/=) :: Unimplemented -> Unimplemented -> Bool # | |
Show Unimplemented Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> Unimplemented -> ShowS # show :: Unimplemented -> String # showList :: [Unimplemented] -> ShowS # | |
Encoding Unimplemented Source # | |
Defined in Network.SSH.Message |
Debug (4)
ServiceRequest (5)
data ServiceRequest Source #
Constructors
ServiceRequest ServiceName |
Instances
Eq ServiceRequest Source # | |
Defined in Network.SSH.Message Methods (==) :: ServiceRequest -> ServiceRequest -> Bool # (/=) :: ServiceRequest -> ServiceRequest -> Bool # | |
Show ServiceRequest Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ServiceRequest -> ShowS # show :: ServiceRequest -> String # showList :: [ServiceRequest] -> ShowS # | |
Encoding ServiceRequest Source # | |
Defined in Network.SSH.Message |
ServiceAccept (6)
data ServiceAccept Source #
Constructors
ServiceAccept ServiceName |
Instances
Eq ServiceAccept Source # | |
Defined in Network.SSH.Message Methods (==) :: ServiceAccept -> ServiceAccept -> Bool # (/=) :: ServiceAccept -> ServiceAccept -> Bool # | |
Show ServiceAccept Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ServiceAccept -> ShowS # show :: ServiceAccept -> String # showList :: [ServiceAccept] -> ShowS # | |
Encoding ServiceAccept Source # | |
Defined in Network.SSH.Message |
KexInit (20)
Constructors
KexNewKeys (21)
data KexNewKeys Source #
Constructors
KexNewKeys |
Instances
Eq KexNewKeys Source # | |
Defined in Network.SSH.Message | |
Show KexNewKeys Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> KexNewKeys -> ShowS # show :: KexNewKeys -> String # showList :: [KexNewKeys] -> ShowS # | |
Encoding KexNewKeys Source # | |
Defined in Network.SSH.Message |
KexEcdhInit (30)
data KexEcdhInit Source #
Constructors
KexEcdhInit | |
Fields |
Instances
Eq KexEcdhInit Source # | |
Defined in Network.SSH.Message | |
Show KexEcdhInit Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> KexEcdhInit -> ShowS # show :: KexEcdhInit -> String # showList :: [KexEcdhInit] -> ShowS # | |
Encoding KexEcdhInit Source # | |
Defined in Network.SSH.Message |
KexEcdhReply (31)
data KexEcdhReply Source #
Constructors
KexEcdhReply | |
Fields |
Instances
Eq KexEcdhReply Source # | |
Defined in Network.SSH.Message | |
Show KexEcdhReply Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> KexEcdhReply -> ShowS # show :: KexEcdhReply -> String # showList :: [KexEcdhReply] -> ShowS # | |
Encoding KexEcdhReply Source # | |
Defined in Network.SSH.Message |
UserAuthRequest (50)
data UserAuthRequest Source #
Constructors
UserAuthRequest UserName ServiceName AuthMethod |
Instances
Eq UserAuthRequest Source # | |
Defined in Network.SSH.Message Methods (==) :: UserAuthRequest -> UserAuthRequest -> Bool # (/=) :: UserAuthRequest -> UserAuthRequest -> Bool # | |
Show UserAuthRequest Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> UserAuthRequest -> ShowS # show :: UserAuthRequest -> String # showList :: [UserAuthRequest] -> ShowS # | |
Encoding UserAuthRequest Source # | |
Defined in Network.SSH.Message |
UserAuthFailure (51)
data UserAuthFailure Source #
Constructors
UserAuthFailure [Name] Bool |
Instances
Eq UserAuthFailure Source # | |
Defined in Network.SSH.Message Methods (==) :: UserAuthFailure -> UserAuthFailure -> Bool # (/=) :: UserAuthFailure -> UserAuthFailure -> Bool # | |
Show UserAuthFailure Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> UserAuthFailure -> ShowS # show :: UserAuthFailure -> String # showList :: [UserAuthFailure] -> ShowS # | |
Encoding UserAuthFailure Source # | |
Defined in Network.SSH.Message |
UserAuthSuccess (52)
data UserAuthSuccess Source #
Constructors
UserAuthSuccess |
Instances
Eq UserAuthSuccess Source # | |
Defined in Network.SSH.Message Methods (==) :: UserAuthSuccess -> UserAuthSuccess -> Bool # (/=) :: UserAuthSuccess -> UserAuthSuccess -> Bool # | |
Show UserAuthSuccess Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> UserAuthSuccess -> ShowS # show :: UserAuthSuccess -> String # showList :: [UserAuthSuccess] -> ShowS # | |
Encoding UserAuthSuccess Source # | |
Defined in Network.SSH.Message |
UserAuthBanner (53)
data UserAuthBanner Source #
Constructors
UserAuthBanner ShortByteString ShortByteString |
Instances
Eq UserAuthBanner Source # | |
Defined in Network.SSH.Message Methods (==) :: UserAuthBanner -> UserAuthBanner -> Bool # (/=) :: UserAuthBanner -> UserAuthBanner -> Bool # | |
Show UserAuthBanner Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> UserAuthBanner -> ShowS # show :: UserAuthBanner -> String # showList :: [UserAuthBanner] -> ShowS # | |
Encoding UserAuthBanner Source # | |
Defined in Network.SSH.Message |
UserAuthPublicKeyOk (60)
data UserAuthPublicKeyOk Source #
Constructors
UserAuthPublicKeyOk PublicKey |
Instances
Eq UserAuthPublicKeyOk Source # | |
Defined in Network.SSH.Message Methods (==) :: UserAuthPublicKeyOk -> UserAuthPublicKeyOk -> Bool # (/=) :: UserAuthPublicKeyOk -> UserAuthPublicKeyOk -> Bool # | |
Show UserAuthPublicKeyOk Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> UserAuthPublicKeyOk -> ShowS # show :: UserAuthPublicKeyOk -> String # showList :: [UserAuthPublicKeyOk] -> ShowS # | |
Encoding UserAuthPublicKeyOk Source # | |
Defined in Network.SSH.Message |
ChannelOpen (90)
data ChannelOpen Source #
Instances
Eq ChannelOpen Source # | |
Defined in Network.SSH.Message | |
Show ChannelOpen Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelOpen -> ShowS # show :: ChannelOpen -> String # showList :: [ChannelOpen] -> ShowS # | |
Encoding ChannelOpen Source # | |
Defined in Network.SSH.Message |
data ChannelOpenType Source #
Instances
Eq ChannelOpenType Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelOpenType -> ChannelOpenType -> Bool # (/=) :: ChannelOpenType -> ChannelOpenType -> Bool # | |
Show ChannelOpenType Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelOpenType -> ShowS # show :: ChannelOpenType -> String # showList :: [ChannelOpenType] -> ShowS # |
ChannelOpenConfirmation (91)
data ChannelOpenConfirmation Source #
Instances
Eq ChannelOpenConfirmation Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelOpenConfirmation -> ChannelOpenConfirmation -> Bool # (/=) :: ChannelOpenConfirmation -> ChannelOpenConfirmation -> Bool # | |
Show ChannelOpenConfirmation Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelOpenConfirmation -> ShowS # show :: ChannelOpenConfirmation -> String # showList :: [ChannelOpenConfirmation] -> ShowS # | |
Encoding ChannelOpenConfirmation Source # | |
Defined in Network.SSH.Message Methods put :: Builder b => ChannelOpenConfirmation -> b Source # |
ChannelOpenFailure (92)
data ChannelOpenFailure Source #
Instances
Eq ChannelOpenFailure Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelOpenFailure -> ChannelOpenFailure -> Bool # (/=) :: ChannelOpenFailure -> ChannelOpenFailure -> Bool # | |
Show ChannelOpenFailure Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelOpenFailure -> ShowS # show :: ChannelOpenFailure -> String # showList :: [ChannelOpenFailure] -> ShowS # | |
Encoding ChannelOpenFailure Source # | |
Defined in Network.SSH.Message |
data ChannelOpenFailureReason Source #
Constructors
ChannelOpenAdministrativelyProhibited | |
ChannelOpenConnectFailed | |
ChannelOpenUnknownChannelType | |
ChannelOpenResourceShortage | |
ChannelOpenOtherFailure Word32 |
Instances
Eq ChannelOpenFailureReason Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelOpenFailureReason -> ChannelOpenFailureReason -> Bool # (/=) :: ChannelOpenFailureReason -> ChannelOpenFailureReason -> Bool # | |
Show ChannelOpenFailureReason Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelOpenFailureReason -> ShowS # show :: ChannelOpenFailureReason -> String # showList :: [ChannelOpenFailureReason] -> ShowS # | |
Encoding ChannelOpenFailureReason Source # | |
Defined in Network.SSH.Message Methods put :: Builder b => ChannelOpenFailureReason -> b Source # |
ChannelWindowAdjust (93)
data ChannelWindowAdjust Source #
Constructors
ChannelWindowAdjust ChannelId ChannelWindowSize |
Instances
Eq ChannelWindowAdjust Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelWindowAdjust -> ChannelWindowAdjust -> Bool # (/=) :: ChannelWindowAdjust -> ChannelWindowAdjust -> Bool # | |
Show ChannelWindowAdjust Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelWindowAdjust -> ShowS # show :: ChannelWindowAdjust -> String # showList :: [ChannelWindowAdjust] -> ShowS # | |
Encoding ChannelWindowAdjust Source # | |
Defined in Network.SSH.Message |
ChannelData (94)
data ChannelData Source #
Constructors
ChannelData ChannelId ShortByteString |
Instances
Eq ChannelData Source # | |
Defined in Network.SSH.Message | |
Show ChannelData Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelData -> ShowS # show :: ChannelData -> String # showList :: [ChannelData] -> ShowS # | |
Encoding ChannelData Source # | |
Defined in Network.SSH.Message |
ChannelExtendedData (95)
data ChannelExtendedData Source #
Constructors
ChannelExtendedData ChannelId Word32 ShortByteString |
Instances
Eq ChannelExtendedData Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelExtendedData -> ChannelExtendedData -> Bool # (/=) :: ChannelExtendedData -> ChannelExtendedData -> Bool # | |
Show ChannelExtendedData Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelExtendedData -> ShowS # show :: ChannelExtendedData -> String # showList :: [ChannelExtendedData] -> ShowS # | |
Encoding ChannelExtendedData Source # | |
Defined in Network.SSH.Message |
ChannelEof (96)
data ChannelEof Source #
Constructors
ChannelEof ChannelId |
Instances
Eq ChannelEof Source # | |
Defined in Network.SSH.Message | |
Show ChannelEof Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelEof -> ShowS # show :: ChannelEof -> String # showList :: [ChannelEof] -> ShowS # | |
Encoding ChannelEof Source # | |
Defined in Network.SSH.Message |
ChannelClose (97)
data ChannelClose Source #
Constructors
ChannelClose ChannelId |
Instances
Eq ChannelClose Source # | |
Defined in Network.SSH.Message | |
Show ChannelClose Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelClose -> ShowS # show :: ChannelClose -> String # showList :: [ChannelClose] -> ShowS # | |
Encoding ChannelClose Source # | |
Defined in Network.SSH.Message |
ChannelRequest (98)
data ChannelRequest Source #
Constructors
ChannelRequest | |
Fields
|
Instances
Eq ChannelRequest Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelRequest -> ChannelRequest -> Bool # (/=) :: ChannelRequest -> ChannelRequest -> Bool # | |
Show ChannelRequest Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelRequest -> ShowS # show :: ChannelRequest -> String # showList :: [ChannelRequest] -> ShowS # | |
Encoding ChannelRequest Source # | |
Defined in Network.SSH.Message |
data ChannelRequestEnv Source #
Constructors
ChannelRequestEnv | |
Fields |
Instances
Eq ChannelRequestEnv Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelRequestEnv -> ChannelRequestEnv -> Bool # (/=) :: ChannelRequestEnv -> ChannelRequestEnv -> Bool # | |
Show ChannelRequestEnv Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelRequestEnv -> ShowS # show :: ChannelRequestEnv -> String # showList :: [ChannelRequestEnv] -> ShowS # | |
Encoding ChannelRequestEnv Source # | |
Defined in Network.SSH.Message |
data ChannelRequestPty Source #
Constructors
ChannelRequestPty | |
Fields |
Instances
Eq ChannelRequestPty Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelRequestPty -> ChannelRequestPty -> Bool # (/=) :: ChannelRequestPty -> ChannelRequestPty -> Bool # | |
Show ChannelRequestPty Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelRequestPty -> ShowS # show :: ChannelRequestPty -> String # showList :: [ChannelRequestPty] -> ShowS # | |
Encoding ChannelRequestPty Source # | |
Defined in Network.SSH.Message |
data ChannelRequestWindowChange Source #
Constructors
ChannelRequestWindowChange | |
Fields
|
Instances
Eq ChannelRequestWindowChange Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelRequestWindowChange -> ChannelRequestWindowChange -> Bool # (/=) :: ChannelRequestWindowChange -> ChannelRequestWindowChange -> Bool # | |
Show ChannelRequestWindowChange Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelRequestWindowChange -> ShowS # show :: ChannelRequestWindowChange -> String # showList :: [ChannelRequestWindowChange] -> ShowS # | |
Encoding ChannelRequestWindowChange Source # | |
Defined in Network.SSH.Message Methods put :: Builder b => ChannelRequestWindowChange -> b Source # |
data ChannelRequestShell Source #
Constructors
ChannelRequestShell |
Instances
Eq ChannelRequestShell Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelRequestShell -> ChannelRequestShell -> Bool # (/=) :: ChannelRequestShell -> ChannelRequestShell -> Bool # | |
Show ChannelRequestShell Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelRequestShell -> ShowS # show :: ChannelRequestShell -> String # showList :: [ChannelRequestShell] -> ShowS # | |
Encoding ChannelRequestShell Source # | |
Defined in Network.SSH.Message |
data ChannelRequestExec Source #
Constructors
ChannelRequestExec | |
Fields |
Instances
Eq ChannelRequestExec Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelRequestExec -> ChannelRequestExec -> Bool # (/=) :: ChannelRequestExec -> ChannelRequestExec -> Bool # | |
Show ChannelRequestExec Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelRequestExec -> ShowS # show :: ChannelRequestExec -> String # showList :: [ChannelRequestExec] -> ShowS # | |
Encoding ChannelRequestExec Source # | |
Defined in Network.SSH.Message |
data ChannelRequestSignal Source #
Constructors
ChannelRequestSignal | |
Fields |
Instances
Eq ChannelRequestSignal Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelRequestSignal -> ChannelRequestSignal -> Bool # (/=) :: ChannelRequestSignal -> ChannelRequestSignal -> Bool # | |
Show ChannelRequestSignal Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelRequestSignal -> ShowS # show :: ChannelRequestSignal -> String # showList :: [ChannelRequestSignal] -> ShowS # | |
Encoding ChannelRequestSignal Source # | |
Defined in Network.SSH.Message Methods put :: Builder b => ChannelRequestSignal -> b Source # |
data ChannelRequestExitStatus Source #
Constructors
ChannelRequestExitStatus | |
Fields |
Instances
Eq ChannelRequestExitStatus Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelRequestExitStatus -> ChannelRequestExitStatus -> Bool # (/=) :: ChannelRequestExitStatus -> ChannelRequestExitStatus -> Bool # | |
Show ChannelRequestExitStatus Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelRequestExitStatus -> ShowS # show :: ChannelRequestExitStatus -> String # showList :: [ChannelRequestExitStatus] -> ShowS # | |
Encoding ChannelRequestExitStatus Source # | |
Defined in Network.SSH.Message Methods put :: Builder b => ChannelRequestExitStatus -> b Source # |
data ChannelRequestExitSignal Source #
Constructors
ChannelRequestExitSignal | |
Fields |
Instances
Eq ChannelRequestExitSignal Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelRequestExitSignal -> ChannelRequestExitSignal -> Bool # (/=) :: ChannelRequestExitSignal -> ChannelRequestExitSignal -> Bool # | |
Show ChannelRequestExitSignal Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelRequestExitSignal -> ShowS # show :: ChannelRequestExitSignal -> String # showList :: [ChannelRequestExitSignal] -> ShowS # | |
Encoding ChannelRequestExitSignal Source # | |
Defined in Network.SSH.Message Methods put :: Builder b => ChannelRequestExitSignal -> b Source # |
ChannelSuccess (99)
data ChannelSuccess Source #
Constructors
ChannelSuccess ChannelId |
Instances
Eq ChannelSuccess Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelSuccess -> ChannelSuccess -> Bool # (/=) :: ChannelSuccess -> ChannelSuccess -> Bool # | |
Show ChannelSuccess Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelSuccess -> ShowS # show :: ChannelSuccess -> String # showList :: [ChannelSuccess] -> ShowS # | |
Encoding ChannelSuccess Source # | |
Defined in Network.SSH.Message |
ChannelFailure (100)
data ChannelFailure Source #
Constructors
ChannelFailure ChannelId |
Instances
Eq ChannelFailure Source # | |
Defined in Network.SSH.Message Methods (==) :: ChannelFailure -> ChannelFailure -> Bool # (/=) :: ChannelFailure -> ChannelFailure -> Bool # | |
Show ChannelFailure Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelFailure -> ShowS # show :: ChannelFailure -> String # showList :: [ChannelFailure] -> ShowS # | |
Encoding ChannelFailure Source # | |
Defined in Network.SSH.Message |
Misc
data AuthMethod Source #
Constructors
AuthNone | |
AuthHostBased | |
AuthPassword Password | |
AuthPublicKey PublicKey (Maybe Signature) | |
AuthOther Name |
Instances
Eq AuthMethod Source # | |
Defined in Network.SSH.Message | |
Show AuthMethod Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> AuthMethod -> ShowS # show :: AuthMethod -> String # showList :: [AuthMethod] -> ShowS # | |
HasName AuthMethod Source # | |
Defined in Network.SSH.Message Methods name :: AuthMethod -> Name Source # | |
Encoding AuthMethod Source # | |
Defined in Network.SSH.Message |
Instances
Eq ChannelId Source # | |
Ord ChannelId Source # | |
Show ChannelId Source # | |
Encoding ChannelId Source # | |
newtype ChannelType Source #
Constructors
ChannelType ShortByteString |
Instances
Eq ChannelType Source # | |
Defined in Network.SSH.Message | |
Ord ChannelType Source # | |
Defined in Network.SSH.Message Methods compare :: ChannelType -> ChannelType -> Ordering # (<) :: ChannelType -> ChannelType -> Bool # (<=) :: ChannelType -> ChannelType -> Bool # (>) :: ChannelType -> ChannelType -> Bool # (>=) :: ChannelType -> ChannelType -> Bool # max :: ChannelType -> ChannelType -> ChannelType # min :: ChannelType -> ChannelType -> ChannelType # | |
Show ChannelType Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> ChannelType -> ShowS # show :: ChannelType -> String # showList :: [ChannelType] -> ShowS # | |
Encoding ChannelType Source # | |
Defined in Network.SSH.Message |
type ChannelPacketSize = Word32 Source #
type ChannelWindowSize = Word32 Source #
newCookie :: MonadRandom m => m Cookie Source #
Constructors
Password ShortByteString |
data PtySettings Source #
Constructors
PtySettings | |
Fields |
Instances
Eq PtySettings Source # | |
Defined in Network.SSH.Message | |
Show PtySettings Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> PtySettings -> ShowS # show :: PtySettings -> String # showList :: [PtySettings] -> ShowS # | |
Encoding PtySettings Source # | |
Defined in Network.SSH.Message |
Constructors
PublicKeyEd25519 PublicKey | |
PublicKeyRSA PublicKey | |
PublicKeyOther Name |
Constructors
SessionId ShortByteString |
Instances
Eq SessionId Source # | |
Ord SessionId Source # | |
Show SessionId Source # | |
Encoding SessionId Source # | |
Constructors
SignatureEd25519 Signature | |
SignatureRSA ByteString | |
SignatureOther Name |
Constructors
Version ShortByteString |
type ServiceName = Name Source #
Constructors
Name ShortByteString |
class HasName a where Source #
Instances
HasName PublicKey Source # | |
HasName Signature Source # | |
HasName AuthMethod Source # | |
Defined in Network.SSH.Message Methods name :: AuthMethod -> Name Source # | |
HasName CompressionAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods name :: CompressionAlgorithm -> Name Source # | |
HasName EncryptionAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods name :: EncryptionAlgorithm -> Name Source # | |
HasName KeyExchangeAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods name :: KeyExchangeAlgorithm -> Name Source # | |
HasName HostKeyAlgorithm Source # | |
Defined in Network.SSH.Algorithms Methods name :: HostKeyAlgorithm -> Name Source # |
data Connection identity Source #
data ConnectionConfig identity Source #
Constructors
ConnectionConfig | |
Fields
|
Instances
Default (ConnectionConfig identity) Source # | |
Defined in Network.SSH.Server.Service.Connection Methods def :: ConnectionConfig identity # |
data SessionRequest Source #
Information associated with the session request.
Might be exteded in the future.
Constructors
SessionRequest |
Instances
Eq SessionRequest Source # | |
Defined in Network.SSH.Server.Service.Connection Methods (==) :: SessionRequest -> SessionRequest -> Bool # (/=) :: SessionRequest -> SessionRequest -> Bool # | |
Ord SessionRequest Source # | |
Defined in Network.SSH.Server.Service.Connection Methods compare :: SessionRequest -> SessionRequest -> Ordering # (<) :: SessionRequest -> SessionRequest -> Bool # (<=) :: SessionRequest -> SessionRequest -> Bool # (>) :: SessionRequest -> SessionRequest -> Bool # (>=) :: SessionRequest -> SessionRequest -> Bool # max :: SessionRequest -> SessionRequest -> SessionRequest # min :: SessionRequest -> SessionRequest -> SessionRequest # | |
Show SessionRequest Source # | |
Defined in Network.SSH.Server.Service.Connection Methods showsPrec :: Int -> SessionRequest -> ShowS # show :: SessionRequest -> String # showList :: [SessionRequest] -> ShowS # |
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
andstderr
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 1024sendAll
stdout bs pureExitSuccess
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) |
newtype Environment Source #
The Environment
is list of key-value pairs.
Environment [ ("LC_ALL", "en_US.UTF-8") ]
Constructors
Environment [(ByteString, ByteString)] |
Instances
Eq Environment Source # | |
Defined in Network.SSH.Server.Service.Connection | |
Ord Environment Source # | |
Defined in Network.SSH.Server.Service.Connection Methods compare :: Environment -> Environment -> Ordering # (<) :: Environment -> Environment -> Bool # (<=) :: Environment -> Environment -> Bool # (>) :: Environment -> Environment -> Bool # (>=) :: Environment -> Environment -> Bool # max :: Environment -> Environment -> Environment # min :: Environment -> Environment -> Environment # | |
Show Environment Source # | |
Defined in Network.SSH.Server.Service.Connection Methods showsPrec :: Int -> Environment -> ShowS # show :: Environment -> String # showList :: [Environment] -> ShowS # |
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 |
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
|
Instances
Eq DirectTcpIpRequest Source # | |
Defined in Network.SSH.Server.Service.Connection Methods (==) :: DirectTcpIpRequest -> DirectTcpIpRequest -> Bool # (/=) :: DirectTcpIpRequest -> DirectTcpIpRequest -> Bool # | |
Ord DirectTcpIpRequest Source # | |
Defined in Network.SSH.Server.Service.Connection Methods compare :: DirectTcpIpRequest -> DirectTcpIpRequest -> Ordering # (<) :: DirectTcpIpRequest -> DirectTcpIpRequest -> Bool # (<=) :: DirectTcpIpRequest -> DirectTcpIpRequest -> Bool # (>) :: DirectTcpIpRequest -> DirectTcpIpRequest -> Bool # (>=) :: DirectTcpIpRequest -> DirectTcpIpRequest -> Bool # max :: DirectTcpIpRequest -> DirectTcpIpRequest -> DirectTcpIpRequest # min :: DirectTcpIpRequest -> DirectTcpIpRequest -> DirectTcpIpRequest # | |
Show DirectTcpIpRequest Source # | |
Defined in Network.SSH.Server.Service.Connection Methods showsPrec :: Int -> DirectTcpIpRequest -> ShowS # show :: DirectTcpIpRequest -> String # showList :: [DirectTcpIpRequest] -> ShowS # |
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 ()) |
data ConnectionMsg Source #
Constructors
Instances
Eq ConnectionMsg Source # | |
Defined in Network.SSH.Server.Service.Connection Methods (==) :: ConnectionMsg -> ConnectionMsg -> Bool # (/=) :: ConnectionMsg -> ConnectionMsg -> Bool # | |
Show ConnectionMsg Source # | |
Defined in Network.SSH.Server.Service.Connection Methods showsPrec :: Int -> ConnectionMsg -> ShowS # show :: ConnectionMsg -> String # showList :: [ConnectionMsg] -> ShowS # | |
Encoding ConnectionMsg Source # | |
Defined in Network.SSH.Server.Service.Connection |
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
|
Instances
Default (UserAuthConfig identity) Source # | |
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 #
verifyAuthSignature :: SessionId -> UserName -> ServiceName -> PublicKey -> Signature -> Bool 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 # | |
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
Methods
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 Methods send :: TStreamingQueue -> ByteString -> IO Int Source # sendUnsafe :: TStreamingQueue -> MemView -> IO Int Source # |
class InputStream stream where Source #
An InputStream
is something that bytes can be read from.
Methods
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 Methods peek :: TStreamingQueue -> Int -> IO ByteString Source # receive :: TStreamingQueue -> Int -> IO ByteString Source # receiveUnsafe :: 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.
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.
Instances
MessageStream Transport Source # | |
Defined in Network.SSH.Transport |
data TransportConfig Source #
Constructors
TransportConfig | |
Fields |
Instances
Default TransportConfig Source # | |
Defined in Network.SSH.Transport Methods def :: TransportConfig # |
data Disconnected Source #
Constructors
Disconnected | |
Instances
Eq Disconnected Source # | |
Defined in Network.SSH.Message | |
Show Disconnected Source # | |
Defined in Network.SSH.Message Methods showsPrec :: Int -> Disconnected -> ShowS # show :: Disconnected -> String # showList :: [Disconnected] -> ShowS # | |
Encoding Disconnected Source # | |
Defined in Network.SSH.Message |
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 #
data TStreamingQueue Source #
Constructors
TStreamingQueue | |
Instances
InputStream TStreamingQueue Source # | |
Defined in Network.SSH.TStreamingQueue Methods peek :: TStreamingQueue -> Int -> IO ByteString Source # receive :: TStreamingQueue -> Int -> IO ByteString Source # receiveUnsafe :: TStreamingQueue -> MemView -> IO Int Source # | |
OutputStream TStreamingQueue Source # | |
Defined in Network.SSH.TStreamingQueue Methods send :: TStreamingQueue -> ByteString -> IO Int Source # sendUnsafe :: TStreamingQueue -> MemView -> IO Int Source # | |
DuplexStream TStreamingQueue Source # | |
Defined in Network.SSH.TStreamingQueue |
newTStreamingQueue :: Word32 -> TVar Word32 -> STM TStreamingQueue Source #
capacity :: TStreamingQueue -> Word32 Source #
addWindowSpace :: TStreamingQueue -> Word32 -> STM () Source #
terminate :: TStreamingQueue -> STM () Source #
enqueue :: TStreamingQueue -> ByteString -> STM Word32 Source #
dequeue :: TStreamingQueue -> Word32 -> STM ByteString Source #
dequeueShort :: TStreamingQueue -> Word32 -> STM ShortByteString Source #
lookAhead :: TStreamingQueue -> Word32 -> STM ByteString Source #