Copyright | (c) 2017-2019 Jack Kelly |
---|---|
License | GPL-3.0-or-later |
Maintainer | jack@jackkelly.name |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Wrappers for libtelnet
types, where the wrapping is simple enough to
not need its own module. Interpret-as-command codes live in
Network.Telnet.LibTelnet.Iac, and telnet option codes live in
Network.Telnet.LibTelnet.Options.
Synopsis
- data TelnetT
- data TelnetException
- newtype Flag = Flag {}
- flagProxy :: Flag
- data TelnetTeloptT = TelnetTeloptT {}
- data EventT
- = Data (CString, CSize)
- | Send (CString, CSize)
- | Warning ErrorT
- | Error ErrorT
- | Command Iac
- | Will Option
- | Wont Option
- | Do Option
- | Dont Option
- | Subnegotiation Option (CString, CSize)
- | Zmp (Ptr CString, CSize)
- | TerminalType TCmd CString
- | Compress CUChar
- | Environ ECmd (Ptr TelnetEnvironT, CSize)
- | Mssp (Ptr TelnetEnvironT, CSize)
- newtype TelnetEventTypeT = TelnetEventTypeT {}
- eventData :: TelnetEventTypeT
- eventSend :: TelnetEventTypeT
- eventIac :: TelnetEventTypeT
- eventWill :: TelnetEventTypeT
- eventWont :: TelnetEventTypeT
- eventDo :: TelnetEventTypeT
- eventDont :: TelnetEventTypeT
- eventSubnegotiation :: TelnetEventTypeT
- eventCompress :: TelnetEventTypeT
- eventZmp :: TelnetEventTypeT
- eventTType :: TelnetEventTypeT
- data ErrorT = ErrorT {}
- eventEnviron :: TelnetEventTypeT
- eventMssp :: TelnetEventTypeT
- eventWarning :: TelnetEventTypeT
- eventError :: TelnetEventTypeT
- newtype TelnetErrorT = TelnetErrorT {}
- errOK :: TelnetErrorT
- errBadVal :: TelnetErrorT
- errNoMem :: TelnetErrorT
- errOverflow :: TelnetErrorT
- errProtocol :: TelnetErrorT
- errCompress :: TelnetErrorT
- newtype TCmd = TCmd {}
- tCmdIs :: TCmd
- tCmdSend :: TCmd
- newtype ECmd = ECmd {}
- eCmdIs :: ECmd
- eCmdSend :: ECmd
- eCmdInfo :: ECmd
- newtype EVar = EVar {}
- eVar :: EVar
- eValue :: EVar
- eUserVar :: EVar
- newtype MsspVar = MsspVar {}
- msspVar :: MsspVar
- msspVal :: MsspVar
- data TelnetEnvironT = TelnetEnvironT {}
Documentation
Uninhabited type for pointer safety (telnet_t
).
Instances
HasTelnetPtr TelnetPtr Source # | No unwrapping needed. |
Defined in Network.Telnet.LibTelnet | |
HasTelnetPtr Telnet Source # | Unwrap with |
Defined in Network.Telnet.LibTelnet |
data TelnetException Source #
Exceptions thrown by the binding, for when something has gone
seriously wrong. Errors detected by libtelnet
are not thrown but
instead are passed to the event handler.
NullTelnetPtr | |
UnexpectedEventType TelnetEventTypeT | |
UnexpectedEnvironCmd ECmd | |
UnexpectedEnvironVar EVar | |
UnexpectedTerminalTypeCmd TCmd |
Instances
data TelnetTeloptT Source #
Wraps telnet_telopt_t
.
Instances
Storable TelnetTeloptT Source # | |
Defined in Network.Telnet.LibTelnet.Types sizeOf :: TelnetTeloptT -> Int # alignment :: TelnetTeloptT -> Int # peekElemOff :: Ptr TelnetTeloptT -> Int -> IO TelnetTeloptT # pokeElemOff :: Ptr TelnetTeloptT -> Int -> TelnetTeloptT -> IO () # peekByteOff :: Ptr b -> Int -> IO TelnetTeloptT # pokeByteOff :: Ptr b -> Int -> TelnetTeloptT -> IO () # peek :: Ptr TelnetTeloptT -> IO TelnetTeloptT # poke :: Ptr TelnetTeloptT -> TelnetTeloptT -> IO () # |
Wraps telnet_event_t
.
Instances
Storable EventT Source # | |
newtype TelnetEventTypeT Source #
Constants from telnet_event_type_t
.
Instances
Eq TelnetEventTypeT Source # | |
Defined in Network.Telnet.LibTelnet.Types (==) :: TelnetEventTypeT -> TelnetEventTypeT -> Bool # (/=) :: TelnetEventTypeT -> TelnetEventTypeT -> Bool # | |
Show TelnetEventTypeT Source # | |
Defined in Network.Telnet.LibTelnet.Types showsPrec :: Int -> TelnetEventTypeT -> ShowS # show :: TelnetEventTypeT -> String # showList :: [TelnetEventTypeT] -> ShowS # | |
Storable TelnetEventTypeT Source # | |
Defined in Network.Telnet.LibTelnet.Types sizeOf :: TelnetEventTypeT -> Int # alignment :: TelnetEventTypeT -> Int # peekElemOff :: Ptr TelnetEventTypeT -> Int -> IO TelnetEventTypeT # pokeElemOff :: Ptr TelnetEventTypeT -> Int -> TelnetEventTypeT -> IO () # peekByteOff :: Ptr b -> Int -> IO TelnetEventTypeT # pokeByteOff :: Ptr b -> Int -> TelnetEventTypeT -> IO () # peek :: Ptr TelnetEventTypeT -> IO TelnetEventTypeT # poke :: Ptr TelnetEventTypeT -> TelnetEventTypeT -> IO () # |
eventError :: TelnetEventTypeT Source #
Constants from telnet_error_t
.
newtype TelnetErrorT Source #
Instances
Eq TelnetErrorT Source # | |
Defined in Network.Telnet.LibTelnet.Types (==) :: TelnetErrorT -> TelnetErrorT -> Bool # (/=) :: TelnetErrorT -> TelnetErrorT -> Bool # | |
Show TelnetErrorT Source # | |
Defined in Network.Telnet.LibTelnet.Types showsPrec :: Int -> TelnetErrorT -> ShowS # show :: TelnetErrorT -> String # showList :: [TelnetErrorT] -> ShowS # | |
Storable TelnetErrorT Source # | |
Defined in Network.Telnet.LibTelnet.Types sizeOf :: TelnetErrorT -> Int # alignment :: TelnetErrorT -> Int # peekElemOff :: Ptr TelnetErrorT -> Int -> IO TelnetErrorT # pokeElemOff :: Ptr TelnetErrorT -> Int -> TelnetErrorT -> IO () # peekByteOff :: Ptr b -> Int -> IO TelnetErrorT # pokeByteOff :: Ptr b -> Int -> TelnetErrorT -> IO () # peek :: Ptr TelnetErrorT -> IO TelnetErrorT # poke :: Ptr TelnetErrorT -> TelnetErrorT -> IO () # |
errOK :: TelnetErrorT Source #
errCompress :: TelnetErrorT Source #
Constants for TERMINAL-TYPE
commands.
Constants for ENVIRON
/NEW-ENVIRON
commands.
Constants for ENVIRON
/NEW-ENVIRON
variables.
Constants for MSSP.
Instances
Eq MsspVar Source # | |
Show MsspVar Source # | |
Storable MsspVar Source # | |
data TelnetEnvironT Source #
ENVIRONMENT
/NEW-ENVIRONMENT
/MSSP
messages, wrapping
telnet_environ_t
.
Instances
Storable TelnetEnvironT Source # | |
Defined in Network.Telnet.LibTelnet.Types sizeOf :: TelnetEnvironT -> Int # alignment :: TelnetEnvironT -> Int # peekElemOff :: Ptr TelnetEnvironT -> Int -> IO TelnetEnvironT # pokeElemOff :: Ptr TelnetEnvironT -> Int -> TelnetEnvironT -> IO () # peekByteOff :: Ptr b -> Int -> IO TelnetEnvironT # pokeByteOff :: Ptr b -> Int -> TelnetEnvironT -> IO () # peek :: Ptr TelnetEnvironT -> IO TelnetEnvironT # poke :: Ptr TelnetEnvironT -> TelnetEnvironT -> IO () # |