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

Contents

Description

Getting Started:

  1. Skim the libtelnet documentation, as these bindings follow the C library's conventions quite closely.
  2. Write an event-handling function, of type EventHandler.
  3. When you accept a new connection, create a Telnet state tracker for it using telnetInit. Options and flags are defined in the same way as the C library; option constants are exported from Network.Telnet.LibTelnet.Options.
  4. When you receive data (probably on a socket), tell Telnet about it using telnetRecv.
  5. To send data, negotiate options, &c., use telnetSend, telnetIac, &c.
  6. IAC (Interpret-As-Command) codes are exported from Network.Telnet.LibTelnet.Iac.
Synopsis

Documentation

telnetInit :: [OptionSpec] -> [Flag] -> EventHandler -> IO Telnet Source #

Create a libtelnet state tracker.

data OptionSpec Source #

Configures which options you want to support. The triple's elements are: option code, support on our end (corresponds to WILL/WONT), support on their end (corresponds to DO/DONT).

Constructors

OptionSpec 

Fields

Instances
Eq OptionSpec Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Show OptionSpec Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Generic OptionSpec Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Associated Types

type Rep OptionSpec :: Type -> Type #

type Rep OptionSpec Source # 
Instance details

Defined in Network.Telnet.LibTelnet

type Rep OptionSpec = D1 (MetaData "OptionSpec" "Network.Telnet.LibTelnet" "libtelnet-0.1.0.0-FZXraNOtRYpGr85da3Gc4W" False) (C1 (MetaCons "OptionSpec" PrefixI True) (S1 (MetaSel (Just "_code") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Option) :*: (S1 (MetaSel (Just "_us") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "_him") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

data Flag Source #

Flags for telnet_init.

Telnet pointers

type Telnet = ForeignPtr TelnetT Source #

Garbage-collected pointer to the libtelnet state tracker. Your program should hang on to this.

type TelnetPtr = Ptr TelnetT Source #

Raw pointer to the libtelnet state tracker. This is passed to the event handlers and you shouldn't see it elsewhere.

class HasTelnetPtr t where Source #

The pointer you get back from telnetInit is a ForeignPtr because it carries around its finalizers, but the pointer that gets passed into your EventHandler is a bare Ptr because it's being passed in from C. This class lets us generalise across both types.

Methods

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

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 #

Event handling

type EventHandler = TelnetPtr -> Event -> IO () Source #

Type of the event handler callback.

data Event Source #

Structure provided to the event handler.

Constructors

Received ByteString

Data received; you should pass it to the application.

Send ByteString

Data you need to send out to the socket.

Warning Err

Something has gone wrong inside of libtelnet but recovery is (likely) possible.

Error Err

Something has gone wrong. The application should immediately close the connection.

Iac Iac

Telnet interpret-as-command.

Will Option

Other end offers an option.

Wont Option

Other end cannot support option.

Do Option

Other end asked you to support option.

Dont Option

Other end asked you to stop using option.

Subnegotiation Option ByteString

Subnegotiation received for some option.

Zmp [ByteString]

Zenith Mud Protocol message

TerminalTypeSend

TERMINAL-TYPE SEND message (RFC 1091). The server wants to know about your terminal-type.

TerminalTypeIs ByteString

TERMINAL-TYPE IS message (RFC 1091). The client has told us a terminal-type.

Compress Bool

Would the client like MCCP Version 2?

EnvironSend [(Var, ByteString)]

Request to send the following environment variables, per (RFC 1408) and (RFC 1572).

Environ IsInfo [(Var, ByteString, ByteString)]

ENVIRON/NEW-ENVIRON options, per (RFC 1408) and (RFC 1572). Keys come before values in the tuples.

Mssp [(ByteString, [ByteString])]

Mud Server Status Protocol List is (key, values).

Instances
Eq Event Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Methods

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

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

Show Event Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

type Rep Event Source # 
Instance details

Defined in Network.Telnet.LibTelnet

type Rep Event = D1 (MetaData "Event" "Network.Telnet.LibTelnet" "libtelnet-0.1.0.0-FZXraNOtRYpGr85da3Gc4W" False) ((((C1 (MetaCons "Received" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)) :+: C1 (MetaCons "Send" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) :+: (C1 (MetaCons "Warning" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Err)) :+: C1 (MetaCons "Error" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Err)))) :+: ((C1 (MetaCons "Iac" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Iac)) :+: C1 (MetaCons "Will" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Option))) :+: (C1 (MetaCons "Wont" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Option)) :+: C1 (MetaCons "Do" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Option))))) :+: (((C1 (MetaCons "Dont" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Option)) :+: C1 (MetaCons "Subnegotiation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Option) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) :+: (C1 (MetaCons "Zmp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ByteString])) :+: C1 (MetaCons "TerminalTypeSend" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "TerminalTypeIs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)) :+: C1 (MetaCons "Compress" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) :+: (C1 (MetaCons "EnvironSend" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Var, ByteString)])) :+: (C1 (MetaCons "Environ" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 IsInfo) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Var, ByteString, ByteString)])) :+: C1 (MetaCons "Mssp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(ByteString, [ByteString])])))))))

data Err Source #

Error message from libtelnet.

Constructors

Err 
Instances
Eq Err Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Methods

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

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

Show Err Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Methods

showsPrec :: Int -> Err -> ShowS #

show :: Err -> String #

showList :: [Err] -> ShowS #

Generic Err Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Associated Types

type Rep Err :: Type -> Type #

Methods

from :: Err -> Rep Err x #

to :: Rep Err x -> Err #

type Rep Err Source # 
Instance details

Defined in Network.Telnet.LibTelnet

data IsInfo Source #

Were the Environ fields sent as part of a NEW-ENVIRON IS message, or part of a NEW-ENVIRON INFO message?

Constructors

Is 
Info 
Instances
Eq IsInfo Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Methods

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

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

Show IsInfo Source # 
Instance details

Defined in Network.Telnet.LibTelnet

data Var Source #

In an Environ message, are the vars being sent as VARs or USERVARs?

Constructors

Var 
UserVar 
Instances
Eq Var Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Methods

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

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

Show Var Source # 
Instance details

Defined in Network.Telnet.LibTelnet

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Simple operations

telnetRecv :: HasTelnetPtr t => t -> ByteString -> IO () Source #

Tell the state tracker about received data.

telnetSend :: HasTelnetPtr t => t -> ByteString -> IO () Source #

Send non-command data.

Generic telnet option negotiation

telnetIac :: HasTelnetPtr t => t -> Iac -> IO () Source #

Send a telnet command.

telnetNegotiate :: HasTelnetPtr t => t -> Iac -> Option -> IO () Source #

Send a negotiation command.

telnetSubnegotiation :: HasTelnetPtr t => t -> Option -> ByteString -> IO () Source #

Send a subnegotiation.

Compression (MCCP2)

telnetBeginCompress2 :: HasTelnetPtr t => t -> IO () Source #

Begin sending compressed data, using the COMPRESS2 option. The server should call this command in response to a Compress True event.

NEW-ENVIRON functions (RFC 1572)

telnetNewEnvironSend :: HasTelnetPtr t => t -> [(Var, ByteString)] -> IO () Source #

Ask the client to send us these environment variables.

telnetNewEnviron :: HasTelnetPtr t => t -> IsInfo -> [(Var, ByteString, ByteString)] -> IO () Source #

Tell the server about our environment variables.

TERMINAL-TYPE functions (RFC 1091)

telnetTTypeSend :: HasTelnetPtr t => t -> IO () Source #

Ask the client to give us a terminal type.

telnetTTypeIs :: HasTelnetPtr t => t -> ByteString -> IO () Source #

Tell the server a terminal type.

ZMP (Zenith Mud Protocol)

telnetSendZmp :: HasTelnetPtr t => t -> [ByteString] -> IO () Source #

Send a ZMP command.

MSSP (Mud Server Status Protocol)

telnetSendMssp :: HasTelnetPtr t => t -> [(ByteString, [ByteString])] -> IO () Source #

Send an MSSP status.

Exceptions

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)))))