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 |
Getting Started:
- Skim the libtelnet documentation, as these bindings follow the C library's conventions quite closely.
- Write an event-handling function, of type
EventHandler
. - When you accept a new connection, create a
Telnet
state tracker for it usingtelnetInit
. Options and flags are defined in the same way as the C library; option constants are exported from Network.Telnet.LibTelnet.Options. - When you receive data (probably on a socket), tell
Telnet
about it usingtelnetRecv
. - To send data, negotiate options, &c., use
telnetSend
,telnetIac
, &c. - IAC (Interpret-As-Command) codes are exported from Network.Telnet.LibTelnet.Iac.
Synopsis
- telnetInit :: [OptionSpec] -> [Flag] -> EventHandler -> IO Telnet
- data OptionSpec = OptionSpec {}
- data Flag
- flagProxy :: Flag
- type Telnet = ForeignPtr TelnetT
- type TelnetPtr = Ptr TelnetT
- class HasTelnetPtr t where
- withTelnetPtr :: t -> (TelnetPtr -> IO a) -> IO a
- type EventHandler = TelnetPtr -> Event -> IO ()
- data Event
- = Received ByteString
- | Send ByteString
- | Warning Err
- | Error Err
- | Iac Iac
- | Will Option
- | Wont Option
- | Do Option
- | Dont Option
- | Subnegotiation Option ByteString
- | Zmp [ByteString]
- | TerminalTypeSend
- | TerminalTypeIs ByteString
- | Compress Bool
- | EnvironSend [(Var, ByteString)]
- | Environ IsInfo [(Var, ByteString, ByteString)]
- | Mssp [(ByteString, [ByteString])]
- data Err = Err {
- _file :: ByteString
- _func :: ByteString
- _msg :: ByteString
- _line :: Int
- _errcode :: TelnetErrorT
- data IsInfo
- data Var
- telnetRecv :: HasTelnetPtr t => t -> ByteString -> IO ()
- telnetSend :: HasTelnetPtr t => t -> ByteString -> IO ()
- telnetIac :: HasTelnetPtr t => t -> Iac -> IO ()
- telnetNegotiate :: HasTelnetPtr t => t -> Iac -> Option -> IO ()
- telnetSubnegotiation :: HasTelnetPtr t => t -> Option -> ByteString -> IO ()
- telnetBeginCompress2 :: HasTelnetPtr t => t -> IO ()
- telnetNewEnvironSend :: HasTelnetPtr t => t -> [(Var, ByteString)] -> IO ()
- telnetNewEnviron :: HasTelnetPtr t => t -> IsInfo -> [(Var, ByteString, ByteString)] -> IO ()
- telnetTTypeSend :: HasTelnetPtr t => t -> IO ()
- telnetTTypeIs :: HasTelnetPtr t => t -> ByteString -> IO ()
- telnetSendZmp :: HasTelnetPtr t => t -> [ByteString] -> IO ()
- telnetSendMssp :: HasTelnetPtr t => t -> [(ByteString, [ByteString])] -> IO ()
- data TelnetException
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
).
Instances
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.
Instances
HasTelnetPtr TelnetPtr Source # | No unwrapping needed. |
Defined in Network.Telnet.LibTelnet | |
HasTelnetPtr Telnet Source # | Unwrap with |
Defined in Network.Telnet.LibTelnet |
Event handling
Structure provided to the event handler.
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 |
|
TerminalTypeIs ByteString |
|
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)] |
|
Mssp [(ByteString, [ByteString])] | Mud Server Status Protocol
List is |
Instances
Error message from libtelnet
.
Err | |
|
Instances
Eq Err Source # | |
Show Err Source # | |
Generic Err Source # | |
type Rep Err Source # | |
Defined in Network.Telnet.LibTelnet type Rep Err = D1 ('MetaData "Err" "Network.Telnet.LibTelnet" "libtelnet-0.1.0.1-inplace" 'False) (C1 ('MetaCons "Err" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_file") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "_func") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :*: (S1 ('MetaSel ('Just "_msg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: (S1 ('MetaSel ('Just "_line") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_errcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TelnetErrorT))))) |
Were the Environ
fields sent as part of a NEW-ENVIRON IS
message, or part of a NEW-ENVIRON INFO
message?
In an Environ
message, are the vars being sent as VAR
s or USERVAR
s?
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
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
event.Compress
True
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.
NullTelnetPtr | |
UnexpectedEventType TelnetEventTypeT | |
UnexpectedEnvironCmd ECmd | |
UnexpectedEnvironVar EVar | |
UnexpectedTerminalTypeCmd TCmd |