Skip to content

Instantly share code, notes, and snippets.

@enolan
Created July 3, 2009 05:36
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save enolan/139922 to your computer and use it in GitHub Desktop.
Save enolan/139922 to your computer and use it in GitHub Desktop.
{-
Read from a tcp socket and copy the stream to stdout using iteratee-based I/O.
To try this: in GHCI, run testEnumSocket; in another terminal, run
'nc localhost 31337'. Anything typed in the netcat terminal will show up in the
GHCI terminal. Go nuts!
Needs network-bytestring and iteratee from Hackage.
-}
module IterateeNetcat where
import qualified Data.ByteString as B
import Data.Iteratee.Base
import Data.Iteratee.WrappedByteString
import Data.Monoid
import Data.Word
import Network.Socket
import qualified Network.Socket.ByteString as SB
testEnumSocket = do
s <- socket AF_INET Stream 0
setSocketOption s ReuseAddr 1
addr <- inet_addr "127.0.0.1"
bindSocket s $ SockAddrInet 31337 addr
listen s 1
(s', _) <- accept s
iterG <- enumSocket s' printThem
_res <- run iterG
mapM_ sClose [s,s']
-- If I want to get this into the iteratee library it needs to use the
-- ReadableChunk class rather than Network.Socket.ByteString.
-- | Run an iteratee over input from a socket. The socket must be connected.
enumSocket :: Socket -> EnumeratorGM WrappedByteString Word8 IO a
enumSocket s iter = do
bs <- SB.recv s 4096
case B.length bs of
0 -> enumErr "Remote closed socket" iter
_ -> do
igv <- runIter iter (Chunk $ WrapBS bs)
case igv of
Done x _ -> return . return $ x
Cont i Nothing -> enumSocket s i
Cont _ (Just e) -> return $ throwErr e
printThem :: IterateeG WrappedByteString Word8 IO ()
printThem = IterateeG $ \s -> case s of
EOF Nothing -> do
putStrLn "Got EOF Nothing"
return (Done () mempty)
EOF (Just (Err str)) -> do
putStrLn ("Got error: " ++ str)
return (Done () mempty)
EOF (Just (Seek offs)) -> do
putStrLn ("Got seek request: " ++ show offs)
return (Done () mempty)
Chunk (WrapBS bs) -> do
B.putStr bs
return $ Cont printThem Nothing
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment