Writer + log each computation to stdout

Hello, I have a bunch of little database IO functions. Each does something to the database, and returns a log string describing what it did, and possibly a meaningful result from the database. query :: IO (String, a) update :: a -> IO (String, ()) ...and a few functions that orchestrate all the little functions into doing useful work. syncWeek :: Week -> IO () syncAll : : IO () I don't want the individual functions to know what is done with the log string describing what they did. Top-level orchestrating functions should make that decision, which can be one of: 1) Collect and print all to a log once all computations are done. 2) Print to stdout *as each computation is run*. 3) Ignore them. Here is my understanding of how common monads would handle these requirements: Writer: 1 and 3 are easy. This is what I originally attempted to use, but I couldn't figure out how to accomplish #2. Reader: 2 and 3 can be accomplished if each function reads a shouldLog config variable from the reader and does a putStrLn depending on the value. Very ugly, as now each function has to know how to log output. State: Not sure, but the Writer docs in the transformers package points to this monad as maybe solving requirement #2 above. The use case is that when I call the top-level functions from a command line script, I want to see logging happening in real-time to stdout, but I may call the same top-level functions from a larger application that may be logging to somewhere other than stdout, and may call the top-level functions from yet another larger application which doesn't want anything to be logged. How can I glue together a bunch of smaller computations, which may call each other, and decide at a higher level what to do with the logging result of each computation? Seems like a perfect fit for Writer, except for the requirement to be able to print to stdout at each step. Bryan Vicknair

Hi, Bryan Vicknair wrote:
I have a bunch of little database IO functions. Each does something to the database, and returns a log string describing what it did, and possibly a meaningful result from the database.
query :: IO (String, a) update :: a -> IO (String, ())
...and a few functions that orchestrate all the little functions into doing useful work.
syncWeek :: Week -> IO () syncAll : : IO ()
I don't want the individual functions to know what is done with the log string describing what they did. Top-level orchestrating functions should make that decision, which can be one of:
1) Collect and print all to a log once all computations are done. 2) Print to stdout *as each computation is run*. 3) Ignore them.
Instead of using an existing monad transformer, I would consider to write my own set of logging monad transformers. This could give you this interface: class MonadLog m where log :: String -> m () query :: (MonadIO m, MonadLog m) => m a update :: (MonadIO m, MonadLog m) => a -> m () And then you can provide different implementations for MonadLog: newtype IgnoreLogT m a = IgnoreLogT { runIgnoreLogT :: m a } instance MonadLog (IgnoreLogT m) where log _ = return () newtype ConsoleLogT m a = ConsoleLogT { runConsoleLogT :: m a } instance MonadIO m => MonadLog (ConsoleLogT m) where log msg = liftIO (putStrLn msg) newtype StringLogT m a = StringLogT { runStringLogT :: WriterT String m a } instance MonadLog (StringLogT m) where log msg = StringLogT $ tell msg Tillmann

I have very little experience with monad transformers, so I took this
opportunity to learn by implementing one that will (hopefully!) solve
your problem. Here goes:
import Data.Monoid
import Control.Monad
import Control.Monad.Trans
-- Needed for an example stdout logger.
import System.IO.Unsafe
-- | LoggerT monad transformer.
-- runLoggerT demands a logging function of type a -> b (where b is a monoid).
-- It returns a monad-wrapped tuple, where the first entry is the logs and the
-- second is some value.
-- So, a is the log input type, b the log output type (probably [a]), m a monad,
-- and c some arbitrary type.
newtype LoggerT a b m c = LogT {
runLoggerT :: (a -> b) -> m (b, c)
}
instance (Monoid b, Monad m) => Monad (LoggerT a b m) where
-- return is straightforward: ignore the log function and give mempty as the
-- partial log.
return x = LogT $ \_ -> return (mempty, x)
-- Follow the steps for bind...
(>>=) x k = LogT $ \l ->
-- First we run the logger against the supplied logging function to get a
-- base monad value
let y = runLoggerT x l
-- Now we exploit the base monad's bind twice:
in y >>= (\(log0, v) ->
-- First to feed a value to k and run the produced logger...
let z = log0 `seq` runLoggerT (k v) l
-- And again to concatenate the logs.
in z >>= (\(log1, w) ->
-- Note the use of seq here and above; without this, the stdout logger
-- that we define later will not work.
return $ log1 `seq` (log0 `mappend` log1, w)))
instance Monoid b => MonadTrans (LoggerT a b) where
lift x = LogT $ \l ->
x >>= (\v -> return (mempty, v))
-- | This function will put a message in the log.
putLog :: (Monoid b, Monad m) => a -> LoggerT a b m ()
putLog msg = LogT $ \l ->
let msg' = l msg
in return (msg', ())
-- | Give this to (runLoggerT m) and you'll get a list log.
runListLog action = runLoggerT action (\x -> [x])
-- | Give this to (runLoggerT m) and you'll get logs printed
-- to stdout.
runStdoutLog action = runLoggerT action spitString
where spitString = unsafePerformIO . print
stupidExample :: Monoid b => LoggerT String b IO ()
stupidExample = do
l <- lift getLine
putLog $ "Got line: " ++ l
m <- lift getLine
putLog $ "Got another: " ++ m
Try loading it up and evaluating runStdoutLog stupidExample and
runListLog stupidExample.
If you don't like the use of unsafePerformIO, you could import
Debug.Trace instead and use
runTraceLog action = runLoggerT action (\x -> trace x ())
Alex
On 11/25/13, Tillmann Rendel
Hi,
Bryan Vicknair wrote:
I have a bunch of little database IO functions. Each does something to the database, and returns a log string describing what it did, and possibly a meaningful result from the database.
query :: IO (String, a) update :: a -> IO (String, ())
...and a few functions that orchestrate all the little functions into doing useful work.
syncWeek :: Week -> IO () syncAll : : IO ()
I don't want the individual functions to know what is done with the log string describing what they did. Top-level orchestrating functions should make that decision, which can be one of:
1) Collect and print all to a log once all computations are done. 2) Print to stdout *as each computation is run*. 3) Ignore them.
Instead of using an existing monad transformer, I would consider to write my own set of logging monad transformers. This could give you this interface:
class MonadLog m where log :: String -> m ()
query :: (MonadIO m, MonadLog m) => m a update :: (MonadIO m, MonadLog m) => a -> m ()
And then you can provide different implementations for MonadLog:
newtype IgnoreLogT m a = IgnoreLogT { runIgnoreLogT :: m a }
instance MonadLog (IgnoreLogT m) where log _ = return ()
newtype ConsoleLogT m a = ConsoleLogT { runConsoleLogT :: m a }
instance MonadIO m => MonadLog (ConsoleLogT m) where log msg = liftIO (putStrLn msg)
newtype StringLogT m a = StringLogT { runStringLogT :: WriterT String m a }
instance MonadLog (StringLogT m) where log msg = StringLogT $ tell msg
Tillmann _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, 25 Nov 2013 14:54:20 -0800, Bryan Vicknair
Hello,
I have a bunch of little database IO functions. Each does something to the database, and returns a log string describing what it did, and possibly a meaningful result from the database.
query :: IO (String, a) update :: a -> IO (String, ())
...and a few functions that orchestrate all the little functions into doing useful work.
syncWeek :: Week -> IO () syncAll : : IO ()
I don't want the individual functions to know what is done with the log string describing what they did. Top-level orchestrating functions should make that decision, which can be one of:
1) Collect and print all to a log once all computations are done. 2) Print to stdout *as each computation is run*. 3) Ignore them.
Here is my understanding of how common monads would handle these requirements:
Writer: 1 and 3 are easy. This is what I originally attempted to use, but I couldn't figure out how to accomplish #2. Reader: 2 and 3 can be accomplished if each function reads a shouldLog config variable from the reader and does a putStrLn depending on the value. Very ugly, as now each function has to know how to log output. State: Not sure, but the Writer docs in the transformers package points to this monad as maybe solving requirement #2 above.
The use case is that when I call the top-level functions from a command line script, I want to see logging happening in real-time to stdout, but I may call the same top-level functions from a larger application that may be logging to somewhere other than stdout, and may call the top-level functions from yet another larger application which doesn't want anything to be logged.
How can I glue together a bunch of smaller computations, which may call each other, and decide at a higher level what to do with the logging result of each computation? Seems like a perfect fit for Writer, except for the requirement to be able to print to stdout at each step.
Bryan Vicknair _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Looks like a free monad construction should work: {-# LANGUAGE DeriveFunctor #-} import Prelude hiding (log) import Control.Monad.Free data LogF a = LogF { log :: String, act :: IO a } deriving Functor type Log = Free LogF test :: Log () test = liftF $ LogF "logging" (putStrLn "acting") interactLog :: Log a -> IO a interactLog (Pure x) = return x interactLog (Free l) = do putStrLn $ "[Log] " ++ log l act l >>= interactLog
interactLog $ replicateM_ 3 test [Log] logging acting [Log] logging acting [Log] logging acting

The Workflow package does logging (and recovery), and you can orchestrate
the process using the normal do notation. You can also inspect the log
after or during the process. You can also stop and restart it.
main= exec1 "weekllystuff" $ do
result <- step mylittleprocess1
result2 <- step mylittleprocess2
. ...
At the end you have a single log with the intermediate result (in the
folder .tcachedata/workflows) . If it is interrupted at any step,
re-executing the program continue in the following step.
if you use read-show instances for the intermediate result, the log will be
textual and you can inspect it with a text editor.
2013/11/25 Bryan Vicknair
Hello,
I have a bunch of little database IO functions. Each does something to the database, and returns a log string describing what it did, and possibly a meaningful result from the database.
query :: IO (String, a) update :: a -> IO (String, ())
...and a few functions that orchestrate all the little functions into doing useful work.
syncWeek :: Week -> IO () syncAll : : IO ()
I don't want the individual functions to know what is done with the log string describing what they did. Top-level orchestrating functions should make that decision, which can be one of:
1) Collect and print all to a log once all computations are done. 2) Print to stdout *as each computation is run*. 3) Ignore them.
Here is my understanding of how common monads would handle these requirements:
Writer: 1 and 3 are easy. This is what I originally attempted to use, but I couldn't figure out how to accomplish #2. Reader: 2 and 3 can be accomplished if each function reads a shouldLog config variable from the reader and does a putStrLn depending on the value. Very ugly, as now each function has to know how to log output. State: Not sure, but the Writer docs in the transformers package points to this monad as maybe solving requirement #2 above.
The use case is that when I call the top-level functions from a command line script, I want to see logging happening in real-time to stdout, but I may call the same top-level functions from a larger application that may be logging to somewhere other than stdout, and may call the top-level functions from yet another larger application which doesn't want anything to be logged.
How can I glue together a bunch of smaller computations, which may call each other, and decide at a higher level what to do with the logging result of each computation? Seems like a perfect fit for Writer, except for the requirement to be able to print to stdout at each step.
Bryan Vicknair _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Alberto.
participants (5)
-
Alberto G. Corona
-
Alex Vieth
-
Bryan Vicknair
-
Niklas Haas
-
Tillmann Rendel