Confused about my IterIO code

Hi Hakell Cafe, I'm struggling to understand my unambitious IterIO code that somehow manages to work. Basically I run an echo server that is supposed to read from a socket line by line and write back to the socket with all the characters in the line reversed: import Control.Exception import Control.Monad import Control.Monad.Trans import Data.IterIO import Data.IterIO.Inum import Network import System.IO import System.IO.Error (isEOFError) import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy.Char8 as C iterHandle' :: (MonadIO m) => Handle -> IO (Iter L.ByteString m (), Onum L.ByteString m a) iterHandle' = iterHandle main = withSocketsDo $ do sListen <- listenOn (PortNumber 8000) putStrLn "Listening on Port 8000" forkIO $ forever $ do (sSession, hostname, port) <- accept sListen hSetBuffering sSession NoBuffering putStrLn ("Connected to " ++ hostname ++ ":" ++ show port) forkIO $ do (iter, enum) <- iterHandle' sSession enum |$ inumReverseLines .| iter putStrLn "Press <CTRL-D> to quit." exitOnCtrlD inumReverseLines :: (Monad m) => Inum L.ByteString L.ByteString m a inumReverseLines = mkInum $ do line <- lineI return (L.reverse (L.concat [line, C.pack "\n"])) exitOnCtrlD = try getLine >>= either (\e -> unless (isEOFError e) $ ioError e) (const exitOnCtrlD) When I run it, it does this: asdfghc7@hoggy-nn:/home/hoggy$ nc localhost 8000 1234 4321 4321 1234 abcde edcba The red lines are the replies from my echo server. But all I've done is: enum |$ inumReverseLines .| iter inumReverseLines = mkInum $ do line <- lineI return (L.reverse (L.concat [line, C.pack "\n"])) No attempt was made to reverse more than one line - at least as far as I can see. What have I done wrong that it should work so well? Also, is there a better way to do this? Cheers, -John

On Thu, Jun 30, 2011 at 09:53, John Ky
enum |$ inumReverseLines .| iter inumReverseLines = mkInum $ do line <- lineI return (L.reverse (L.concat [line, C.pack "\n"]))
No attempt was made to reverse more than one line - at least as far as I can see. What have I done wrong that it should work so well?
An iterator that doesn't iterate isn't very useful. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

At Thu, 30 Jun 2011 23:53:02 +1000, John Ky wrote:
But all I've done is:
enum |$ inumReverseLines .| iter
inumReverseLines = mkInum $ do line <- lineI return (L.reverse (L.concat [line, C.pack "\n"]))
mkInum repeatedly invokes its iter argument so as to keep producing chunks. If you want to reverse only one line, it might be easiest to use something along the lines of: mkInumM $ do line <- lineI ifeed (L.reverse (L.concat [line, C.pack "\n"])) mkInumM is a more manual Inum construction function that doesn't automatically do things like loop or handle EOF conditions. David

Thanks David,
Right - it invokes its iter repeatedly because mkInumC does that and mkInum is
defined as:
mkInum = mkInumC id noCtl
So to do it all manually is:
inumReverseLines :: (Monad m) => Inum L.ByteString L.ByteString m a
inumReverseLines = mkInumM $ loop where
loop = do
eof <- atEOFI
unless eof $ do
line <- lineI
ifeed (L.concat [L.reverse line, C.pack "\n"])
loop
Cheers,
-John
On 1 July 2011 01:20,
At Thu, 30 Jun 2011 23:53:02 +1000, John Ky wrote:
But all I've done is:
enum |$ inumReverseLines .| iter
inumReverseLines = mkInum $ do line <- lineI return (L.reverse (L.concat [line, C.pack "\n"]))
mkInum repeatedly invokes its iter argument so as to keep producing chunks. If you want to reverse only one line, it might be easiest to use something along the lines of:
mkInumM $ do line <- lineI ifeed (L.reverse (L.concat [line, C.pack "\n"]))
mkInumM is a more manual Inum construction function that doesn't automatically do things like loop or handle EOF conditions.
David
participants (3)
-
Brandon Allbery
-
dm-list-haskell-cafe@scs.stanford.edu
-
John Ky