{- This is a minimal telnet server that echoes its input back to the client: * All data that arrives on the socket is logged to stdout with a "Socket: " prefix and then fed to the state tracker. * When the event handler is called with a 'Telnet.Received' event, it prints the received data to stdout with an "R: " prefix, and sends it to the same state tracker. * This triggers a 'Telnet.Send' event - "you should send this over the wire" - so we log it to stdout with an "S: " prefix and send it back over the socket. * All other telnet features (IAC sequences, option negotiation, etc.) are ignored. -} module Main where import Control.Monad.Loops (whileJust_) import qualified Data.ByteString.Char8 as B8 import Network.Simple.TCP (HostPreference(..), Socket, recv, send, serve) import qualified Network.Telnet.LibTelnet as Telnet telnetH :: Socket -> Telnet.EventHandler telnetH _ t (Telnet.Received b) = putStr "R: " *> B8.putStrLn b *> Telnet.telnetSend t b telnetH s _ (Telnet.Send b) = putStr "S: " *> send s b telnetH _ _ _ = pure () main :: IO () main = serve HostAny "4000" (\(s, _) -> handle s) where handle s = do telnet <- Telnet.telnetInit [] [] (telnetH s) whileJust_ (recv s 4096) $ \bs -> do putStr "Socket: " B8.putStrLn bs Telnet.telnetRecv telnet bs