Jan Stranik wrote:
My question was why does the output from writer shows first all output from server, then followed by all output from client.

The effect of "mfix" is that the side-effects of the calculation still occur in the lexical order.

Since server is before client, the output of the server precedes the client.

I would like to see output from client and server to alternate in the order in which the computation occurs, namely [server, client, server, client, server, client, …].

Then you have to restructure the code slightly.  This works:

import Control.Monad

import Control.Monad.Writer.Lazy

client:: [Integer] -> Writer [String] [Integer]
client as = do
  dc <- doClient as
  return (0:dc)
    where
      doClient (a:as) = do
              tell ["Client " ++ show a]
              as' <- doClient as
              return ((a+1):as')
      doClient [] = return []

server :: [Integer] -> Writer [String] [Integer]
server [] = return []
server (a:as) = do
  tell ["Server " ++ show a]
  rs <- server as
  return (2*a:rs)

simulation :: [(String,String)]
simulation = let (clientOut,clientLog) = runWriter (client serverOut)
      (serverOut,serverLog) = runWriter (server clientOut)
  in zip serverLog clientLog

main = print (take 10 simulation)

_______________________________________________
Haskell mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to