<div dir="ltr"><div class="gmail_extra"><div class="gmail_quote"><div> Hi,</div><div><br></div><div> Although I don't really understand the contents of your code, I think the type error results from the fact that the 3rd field of the Accept constructor has type (chan ->  next). In the context of 'acc', (chan :: a) and (next :: NetworkActivity a Text).</div><div>I'm guessing the type error refers to when you used 'identity' (which I'm hoping is just 'id' from Prelude); its type gets inferred to be (NetworkActivity a Text -> NetworkActivity a text) instead of what it expected (chan -> next, i.e. a ->NetworkActivity a Text). Whether or not acc is the right type for your needs, I don't know.<br></div><div><br></div><div>Hope that helps,</div><div><br></div><div>toz</div><div><br></div><div>P.S. I don't know if it's good practice, but I usually use type variables in data declarations consistently in other type signatures, e.g. since you declared NetworkActivity using 'chan' and 'next', in 'clse', it'd make more sense (to me) to use (clse :: chan -> Free (NetworkActivity chan) Text) since it seems that 'chan' as a word has some extra connotations as opposed to 'a', which when I read, I think it can be absolutely anything.</div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
<br>
------------------------------<br>
<br>
Message: 2<br>
Date: Thu, 13 Oct 2016 13:15:43 +1100<br>
From: Sumit Raja <<a href="mailto:sumitraja@gmail.com">sumitraja@gmail.com</a>><br>
To: <a href="mailto:beginners@haskell.org">beginners@haskell.org</a><br>
Subject: [Haskell-beginners] Monadic functions definitions for free<br>
        monadic DSL<br>
Message-ID:<br>
        <CAD4nrSc3pZ-K72GBt3=<a href="mailto:fRDuziWP0UtGsmX9RHGGaEYSB9ewMcQ@mail.gmail.com">fRDuziWP0<wbr>UtGsmX9RHGGaEYSB9ewMcQ@mail.<wbr>gmail.com</a>><br>
Content-Type: text/plain; charset=UTF-8<br>
<br>
Hello,<br>
<br>
I am trying to get my head around free monads by developing a simple<br>
network abstraction DSL.<br>
I've made good progress before adding TCP/IP semantics of accepting<br>
connections. I'm now stuck with the creation of monadic functions.<br>
<br>
I've defined the following:<br>
<br>
    data NetworkActivity chan next = Accept chan next (chan -> next) |<br>
            Send chan ByteString (Bool -> next) |<br>
            Recv chan (ByteString -> next) |<br>
            Close chan (() -> next)<br>
<br>
    clse :: a -> Free (NetworkActivity a) Text<br>
    clse chan = liftF (Close chan (const "Quit"))<br>
<br>
    chatterServer :: a -> Free (NetworkActivity a) Text<br>
    chatterServer svrchan = Free $ Accept svrchan (chatterServer<br>
svrchan) chatterLoop<br>
<br>
    chatterLoop :: a -> Free (NetworkActivity a) Text<br>
    chatterLoop chan = Free $ Recv chan $ \bs -> case BS.uncons bs of<br>
      Nothing -> clse chan<br>
      Just x -> if bs == "Bye" then<br>
          Free $ Close chan (\_ -> Pure "Quit")<br>
        else<br>
          Free (Send chan bs (\_ -> chatterLoop chan))<br>
<br>
This works fine with the interpretTCP interpreter below accepting<br>
multiple connections:<br>
<br>
    interpretTCP :: Free (NetworkActivity TCPSocket) r -> IO r<br>
    interpretTCP prg = case prg of<br>
      Free (Accept serverSock svrLoop acceptProc) -> bracket (return serverSock)<br>
        (\s-> interpretTCP (clse s))<br>
        (\s-> do<br>
          (ss, sa) <- accept s<br>
          forkIO $ do<br>
            _ <- interpretTCP (acceptProc ss)<br>
            return ()<br>
          interpretTCP svrLoop<br>
        )<br>
      Free (Recv sock g) -> do<br>
        bs <- receive sock 4096 mempty<br>
        putStrLn (decodeUtf8 bs)<br>
        interpretTCP (g bs)<br>
      Free (Close sock g) -> do<br>
        close sock<br>
        putStrLn ("Server bye!" :: Text)<br>
        interpretTCP (g ())<br>
      Pure r -> return r<br>
      Free (Send sock pl g) -> do<br>
        sent <- send sock pl mempty<br>
        interpretTCP (g (sent > 0))<br>
<br>
Where I'm stuck is defining the monadic version of accept and I'm<br>
beginning to think my original<br>
data type defined above may be wrong. As an initial step I've defined<br>
the following:<br>
<br>
    recv :: a -> Free (NetworkActivity a) ByteString<br>
    recv chan = liftF (Recv chan identity)<br>
<br>
    sendit :: a -> ByteString -> Free (NetworkActivity a) Bool<br>
    sendit chan pl = liftF (Send chan pl identity)<br>
<br>
    mchatterServer :: a -> Free (NetworkActivity a) Text<br>
    mchatterServer chan = Free $ Accept chan (mchatterServer chan)<br>
                                                                   (\s<br>
-> return (identity s) >>= mchatterLoop)<br>
<br>
mchatterServer works as is, the interpreter accepts multiple<br>
connections. Similarly all good with recv and sendit.<br>
I am struggling with converting the Accept in mchatterServer into a<br>
function to use in the do syntax. The signature I think I should be<br>
using is<br>
<br>
    acc :: a -> NetworkActivity a Text -> Free (NetworkActivity a)<br>
(NetworkActivity a Text)<br>
<br>
What I can't figure out is why it can't follow the pattern of recv and<br>
sendit above:<br>
<br>
    acc chan next = liftF $ Accept chan next identity<br>
<br>
Which results in error on identity (using Protolude):<br>
<br>
    Expected type: a -> NetworkActivity a Text<br>
    Actual type: NetworkActivity a Text -> NetworkActivity a Text<br>
<br>
I can't really see how to get the types to line up and have now can't<br>
see through the type fog. What am I missing in my reasoning about the<br>
types?<br>
<br>
Help much appreciated!<br>
<br>
Thanks<br>
<br>
Sumit<br></blockquote></div></div></div>