Send Beginners mailing list submissions to beginners@haskell.org To subscribe or unsubscribe via the World Wide Web, visit http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners or, via email, send a message with subject or body 'help' to beginners-requ...@haskell.org
You can reach the person managing the list at beginners-ow...@haskell.org When replying, please edit your Subject line so it is more specific than "Re: Contents of Beginners digest..." Today's Topics: 1. Re: Monadic functions definitions for free monadic DSL (David McBride) ---------------------------------------------------------------------- Message: 1 Date: Fri, 14 Oct 2016 10:16:45 -0400 From: David McBride <toa...@gmail.com> To: The Haskell-Beginners Mailing List - Discussion of primarily beginner-level topics related to Haskell <beginners@haskell.org> Subject: Re: [Haskell-beginners] Monadic functions definitions for free monadic DSL Message-ID: <CAN+Tr41K3wS7+gm6Nk64v1z3+JjPzzoZUJEw44+=v_w9xfd...@mail.gmail.com> Content-Type: text/plain; charset="utf-8" I feel like you are close to a something, but the recursion makes it difficult. You need to think about what types you've given and what you need. The types of Send, Recv and Close make sense to me. Send takes a chan and a bytestring and returns bool. Recv takes a chan and returns a bytestring, close takes a chan and returns nothing. Accept takes a chan, and something? and returns a chan? I feel like if you can figure out what you actually want Accept to do, it will become clearer. Here's my attempt. Accept takes a chan, takes a procedure to loop on, a procedure to accept on, and then returns the server chan to continue the loop. I don't know if this is entirely right, but it type checks and hopefully it will give you some ideas. {-# LANGUAGE NoImplicitPrelude, DeriveFunctor, OverloadedStrings #-} module Lib where import Protolude import Control.Monad.Free import System.Socket import System.Socket.Family.Inet import System.Socket.Type.Stream import System.Socket.Protocol.TCP import Control.Exception ( bracket, catch ) import Data.ByteString as BS (uncons) data NetworkActivity chan next = Accept chan (Free (NetworkActivity chan) chan) (chan -> Free (NetworkActivity chan) Text) (chan -> next) | Send chan ByteString (Bool -> next) | Recv chan (ByteString -> next) | Close chan (() -> next) | Forked chan deriving Functor recv :: a -> Free (NetworkActivity a) ByteString recv chan = liftF (Recv chan identity) sendit :: a -> ByteString -> Free (NetworkActivity a) Bool sendit chan pl = liftF (Send chan pl identity) clse :: a -> Free (NetworkActivity a) Text clse chan = liftF (Close chan (const "Quit")) acc :: a -> Free (NetworkActivity a) a -> (a -> Free (NetworkActivity a) Text) -> Free (NetworkActivity a) a acc chan srv acc = liftF (Accept chan srv acc identity) mchatterServer :: a -> Free (NetworkActivity a) a mchatterServer chan = acc chan (mchatterServer chan) mchatterLoop mchatterLoop :: a -> Free (NetworkActivity a) Text mchatterLoop chan = do str <- recv chan case BS.uncons str of Nothing -> do msg <- clse chan Pure msg Just x -> if str == "Bye" then clse chan else do _ <- sendit chan str mchatterLoop chan interpretStdIO :: Free (NetworkActivity ()) r -> IO r interpretStdIO prg = case prg of Free (Accept sock _ _ g) -> interpretStdIO (g sock) Free (Recv _ g) -> do ln <- getLine interpretStdIO (g (encodeUtf8 ln)) Free (Close _ r) -> do putStrLn ("Server bye!" :: Text) interpretStdIO (r ()) Pure r -> return r Free (Send _ pl f) -> do putStrLn (decodeUtf8 pl) interpretStdIO (f True) type TCPSocket = Socket Inet Stream TCP tcpSock :: IO TCPSocket tcpSock = do s <- socket :: IO (Socket Inet Stream TCP) setSocketOption s (ReuseAddress True) bind s (SocketAddressInet inetAny 5000) listen s 5 return s interpretTCP :: Free (NetworkActivity TCPSocket) r -> IO r interpretTCP prg = case prg of Free (Accept serverSock svrLoop acceptProc g) -> bracket (return serverSock) (\s-> interpretTCP (clse s)) (\s-> do (ss, sa) <- accept s forkIO $ do _ <- interpretTCP (acceptProc ss) return () interpretTCP (g s) ) Free (Recv sock g) -> do bs <- receive sock 4096 mempty putStrLn (decodeUtf8 bs) interpretTCP (g bs) Free (Close sock g) -> do close sock putStrLn ("Server bye!" :: Text) interpretTCP (g ()) Pure r -> return r Free (Send sock pl g) -> do sent <- send sock pl mempty interpretTCP (g (sent > 0)) I feel like it should be able to be written without Free in the NetworkActivity datatype, but it will require some pattern matching on Free and maybe some liftF's that I couldn't quite figure out. On Wed, Oct 12, 2016 at 10:15 PM, Sumit Raja <sumitr...@gmail.com> wrote: > Hello, > > I am trying to get my head around free monads by developing a simple > network abstraction DSL. > I've made good progress before adding TCP/IP semantics of accepting > connections. I'm now stuck with the creation of monadic functions. > > I've defined the following: > > data NetworkActivity chan next = Accept chan next (chan -> next) | > Send chan ByteString (Bool -> next) | > Recv chan (ByteString -> next) | > Close chan (() -> next) > > clse :: a -> Free (NetworkActivity a) Text > clse chan = liftF (Close chan (const "Quit")) > > chatterServer :: a -> Free (NetworkActivity a) Text > chatterServer svrchan = Free $ Accept svrchan (chatterServer > svrchan) chatterLoop > > chatterLoop :: a -> Free (NetworkActivity a) Text > chatterLoop chan = Free $ Recv chan $ \bs -> case BS.uncons bs of > Nothing -> clse chan > Just x -> if bs == "Bye" then > Free $ Close chan (\_ -> Pure "Quit") > else > Free (Send chan bs (\_ -> chatterLoop chan)) > > This works fine with the interpretTCP interpreter below accepting > multiple connections: > > interpretTCP :: Free (NetworkActivity TCPSocket) r -> IO r > interpretTCP prg = case prg of > Free (Accept serverSock svrLoop acceptProc) -> bracket (return > serverSock) > (\s-> interpretTCP (clse s)) > (\s-> do > (ss, sa) <- accept s > forkIO $ do > _ <- interpretTCP (acceptProc ss) > return () > interpretTCP svrLoop > ) > Free (Recv sock g) -> do > bs <- receive sock 4096 mempty > putStrLn (decodeUtf8 bs) > interpretTCP (g bs) > Free (Close sock g) -> do > close sock > putStrLn ("Server bye!" :: Text) > interpretTCP (g ()) > Pure r -> return r > Free (Send sock pl g) -> do > sent <- send sock pl mempty > interpretTCP (g (sent > 0)) > > Where I'm stuck is defining the monadic version of accept and I'm > beginning to think my original > data type defined above may be wrong. As an initial step I've defined > the following: > > recv :: a -> Free (NetworkActivity a) ByteString > recv chan = liftF (Recv chan identity) > > sendit :: a -> ByteString -> Free (NetworkActivity a) Bool > sendit chan pl = liftF (Send chan pl identity) > > mchatterServer :: a -> Free (NetworkActivity a) Text > mchatterServer chan = Free $ Accept chan (mchatterServer chan) > (\s > -> return (identity s) >>= mchatterLoop) > > mchatterServer works as is, the interpreter accepts multiple > connections. Similarly all good with recv and sendit. > I am struggling with converting the Accept in mchatterServer into a > function to use in the do syntax. The signature I think I should be > using is > > acc :: a -> NetworkActivity a Text -> Free (NetworkActivity a) > (NetworkActivity a Text) > > What I can't figure out is why it can't follow the pattern of recv and > sendit above: > > acc chan next = liftF $ Accept chan next identity > > Which results in error on identity (using Protolude): > > Expected type: a -> NetworkActivity a Text > Actual type: NetworkActivity a Text -> NetworkActivity a Text > > I can't really see how to get the types to line up and have now can't > see through the type fog. What am I missing in my reasoning about the > types? > > Help much appreciated! > > Thanks > > Sumit > _______________________________________________ > Beginners mailing list > Beginners@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners > -------------- next part -------------- An HTML attachment was scrubbed... URL: <http://mail.haskell.org/pipermail/beginners/attachments/20161014/9edf77aa/attachment-0001.html> ------------------------------ Subject: Digest Footer _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners ------------------------------ End of Beginners Digest, Vol 100, Issue 12 ******************************************