libtelnet-0.1.0.0: Bindings to libtelnet

Copyright(c) 2017-2019 Jack Kelly
LicenseGPL-3.0-or-later
Maintainerjack@jackkelly.name
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Network.Telnet.LibTelnet.Types

Description

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

Documentation

data TelnetT Source #

Uninhabited type for pointer safety (telnet_t).

Instances
HasTelnetPtr TelnetPtr Source #

No unwrapping needed.

Instance details

Defined in Network.Telnet.LibTelnet

Methods

withTelnetPtr :: TelnetPtr -> (TelnetPtr -> IO a) -> IO a Source #

HasTelnetPtr Telnet Source #

Unwrap with withForeignPtr.

Instance details

Defined in Network.Telnet.LibTelnet

Methods

withTelnetPtr :: Telnet -> (TelnetPtr -> IO a) -> IO a Source #

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.

Instances
Eq TelnetException Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Show TelnetException Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Generic TelnetException Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Associated Types

type Rep TelnetException :: Type -> Type #

Exception TelnetException Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

type Rep TelnetException Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

type Rep TelnetException = D1 (MetaData "TelnetException" "Network.Telnet.LibTelnet.Types" "libtelnet-0.1.0.0-FZXraNOtRYpGr85da3Gc4W" False) ((C1 (MetaCons "NullTelnetPtr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UnexpectedEventType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TelnetEventTypeT))) :+: (C1 (MetaCons "UnexpectedEnvironCmd" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ECmd)) :+: (C1 (MetaCons "UnexpectedEnvironVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EVar)) :+: C1 (MetaCons "UnexpectedTerminalTypeCmd" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TCmd)))))

newtype Flag Source #

Flags for telnet_init.

Constructors

Flag 

Fields

data TelnetTeloptT Source #

Wraps telnet_telopt_t.

Constructors

TelnetTeloptT 

Fields

eventZmp :: TelnetEventTypeT Source #

Data in Warning and Error events, modeled after struct error_t inside telnet_event_t.

data ErrorT Source #

Constructors

ErrorT 

eventError :: TelnetEventTypeT Source #

Constants from telnet_error_t.

errCompress :: TelnetErrorT Source #

Constants for TERMINAL-TYPE commands.

newtype TCmd Source #

Constructors

TCmd 

Fields

Instances
Eq TCmd Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

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

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

Show TCmd Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

showsPrec :: Int -> TCmd -> ShowS #

show :: TCmd -> String #

showList :: [TCmd] -> ShowS #

Storable TCmd Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

sizeOf :: TCmd -> Int #

alignment :: TCmd -> Int #

peekElemOff :: Ptr TCmd -> Int -> IO TCmd #

pokeElemOff :: Ptr TCmd -> Int -> TCmd -> IO () #

peekByteOff :: Ptr b -> Int -> IO TCmd #

pokeByteOff :: Ptr b -> Int -> TCmd -> IO () #

peek :: Ptr TCmd -> IO TCmd #

poke :: Ptr TCmd -> TCmd -> IO () #

newtype ECmd Source #

Constants for ENVIRON/NEW-ENVIRON commands.

Constructors

ECmd 

Fields

Instances
Eq ECmd Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

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

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

Show ECmd Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

showsPrec :: Int -> ECmd -> ShowS #

show :: ECmd -> String #

showList :: [ECmd] -> ShowS #

Storable ECmd Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

sizeOf :: ECmd -> Int #

alignment :: ECmd -> Int #

peekElemOff :: Ptr ECmd -> Int -> IO ECmd #

pokeElemOff :: Ptr ECmd -> Int -> ECmd -> IO () #

peekByteOff :: Ptr b -> Int -> IO ECmd #

pokeByteOff :: Ptr b -> Int -> ECmd -> IO () #

peek :: Ptr ECmd -> IO ECmd #

poke :: Ptr ECmd -> ECmd -> IO () #

newtype EVar Source #

Constants for ENVIRON/NEW-ENVIRON variables.

Constructors

EVar 

Fields

Instances
Eq EVar Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

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

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

Show EVar Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

showsPrec :: Int -> EVar -> ShowS #

show :: EVar -> String #

showList :: [EVar] -> ShowS #

Storable EVar Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

sizeOf :: EVar -> Int #

alignment :: EVar -> Int #

peekElemOff :: Ptr EVar -> Int -> IO EVar #

pokeElemOff :: Ptr EVar -> Int -> EVar -> IO () #

peekByteOff :: Ptr b -> Int -> IO EVar #

pokeByteOff :: Ptr b -> Int -> EVar -> IO () #

peek :: Ptr EVar -> IO EVar #

poke :: Ptr EVar -> EVar -> IO () #

newtype MsspVar Source #

Constants for MSSP.

Constructors

MsspVar 

Fields

Instances
Eq MsspVar Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Methods

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

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

Show MsspVar Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

Storable MsspVar Source # 
Instance details

Defined in Network.Telnet.LibTelnet.Types

data TelnetEnvironT Source #

ENVIRONMENT/NEW-ENVIRONMENT/MSSP messages, wrapping telnet_environ_t.

Constructors

TelnetEnvironT 

Fields