I\'m not even sure this is possible in any kind of monad; does it violate monad laws? But it seems like something that should be possible in some kind of construct or other. S
I assume that you want the steps to be displayed automatically, without having to sprinkle you code with logging statements.
The problem of doing this with monads is that they are too flexible: at any point, the "shape" of the rest of the computation can depend on values obtained during the computation itself. This is made explicit in the type of (>>=)
, which is m a -> (a -> m b) -> m b
.
As a consequence, there is no fixed number N
of total steps that you can know before running the computation.
However, Haskell offers two other abstractions which trade some of the power and flexibility of monads for the chance to perform a greater amount of "static" analysis beforehand: applicative functors and arrows.
Applicative functors, while hugely useful, are perhaps too "weak" for your needs. You can´t write a function inside an applicative functor that, when applied to a value, prints that value to console. This is explained in the paper "Idioms are oblivious, arrows are meticulous, monads are promiscuous" which contains some enlightening examples of the limits of each abstraction (applicative functors are called "idioms" in that paper.)
Arrows offer a better compromise between expressive power and amenability to static analysis. The "shape" of arrow computations is fixed in a static pipeline. Data obtained during the computation can influence effects later in the pipeline (for example, you can print a value obtained by a previous effect in the computation) but not change the shape of the pipeline, or the number of steps.
So, if you could express your computation using Kleisli arrows (the arrows of a monad), perhaps you could write some kind of arrow transformer (not monad transformer) which added automated logging capabilities.
The arrows package offers a number of arrow transformers. I think StaticArrow could be used to automatically track the total number of steps. But you would still need to write some functionality to actually emit the messages.
Edit: Here's an example of how to keep count of the number of steps in a computation, using arrows:
module Main where
import Data.Monoid
import Control.Monad
import Control.Applicative
import Control.Arrow
import Control.Arrow.Transformer
import Control.Arrow.Transformer.Static
type SteppedIO a b = StaticArrow ((,) (Sum Int)) (Kleisli IO) a b
step :: (a -> IO b) -> SteppedIO a b
step cmd = wrap (Sum 1, Kleisli cmd)
countSteps :: SteppedIO a b -> Int
countSteps = getSum . fst . unwrap
exec :: SteppedIO a b -> a -> IO b
exec = runKleisli . snd . unwrap
program :: SteppedIO () ()
program =
step (\_ -> putStrLn "What is your name?")
>>>
step (\_ -> getLine)
>>>
step (putStrLn . mappend "Hello, ")
main :: IO ()
main = do
putStrLn $ "Number of steps: " ++ show (countSteps program)
exec program ()
Notice that the effect of step 3 is influenced by a value produced in step 2. This can't be done using applicatives.
We do use the (,) (Sum Int)
applicative, required by StaticArrow
to encode the static information (here, just the number of steps).
Displaying the steps as they are executed would require a bit more work.
Edit#2 If we are dealing with a sequence of commands in which no effect depends on a value produced by a previous effect, then we can avoid using arrows and count the steps using only applicative functors:
module Main where
import Data.Monoid
import Control.Applicative
import Data.Functor.Compose
type SteppedIO a = Compose ((,) (Sum Int)) IO a
step :: IO a -> SteppedIO a
step cmd = Compose (Sum 1, cmd)
countSteps :: SteppedIO a -> Int
countSteps = getSum . fst . getCompose
exec :: SteppedIO a -> IO a
exec = snd . getCompose
program :: SteppedIO ()
program =
step (putStrLn "aaa")
*>
step (putStrLn "bbb")
*>
step (putStrLn "ccc")
main :: IO ()
main = do
putStrLn $ "Number of steps: " ++ show (countSteps program)
exec program
Data.Functor.Compose
comes from the transformers
package.
Edit#3 The following code extends the previous Applicative
step counting solution, using the pipes
package to actually emit notifications. The arrow-based solution could be adapted in a similar manner.
module Main where
import Data.Monoid
import Control.Applicative
import Control.Monad.State
import Data.Functor.Compose
import Pipes
import Pipes.Lift
type SteppedIO a = Compose ((,) (Sum Int)) (Producer () IO) a
step :: IO a -> SteppedIO a
step cmd = Compose (Sum 1, yield () *> lift cmd)
countSteps :: SteppedIO a -> Int
countSteps = getSum . fst . getCompose
exec :: SteppedIO a -> Producer () IO a
exec = snd . getCompose
stepper :: MonadIO m => Int -> Consumer () m a
stepper n = evalStateP 0 $ forever $ do
await
lift $ modify succ
current <- lift get
liftIO $ putStrLn $ "step " ++ show current ++ " of " ++ show n
program :: SteppedIO ()
program = *** does not change relative to the previous example ***
main :: IO ()
main = runEffect $ exec program >-> stepper (countSteps program)
While I think Daniel Díaz' arrow solution is he perfect way to do this, there is sure enough a simpler one (which, I just see, he also indicates in the comments already) provided, as in your example, no data is passed between the different function calls.
Remember that, since Haskell is lazy, functions can do lots of stuff that would require macros in other languages. In particular, it's no problem whatsoever to have a list of IO
actions. (Absolutely safe, too: due to pureness, there's no way these could "go off early" in Haskell!) Then you can simply take the length of this list as the total count, interleave it with printing statements, and be done. All in the core language, don't need TH!
sequenceWithStepCount :: [IO()] -> IO()
sequenceWithStepCount actions = go actions 0
where nTot = length actions
go [] _ = putStrLn "Done!"
go (act:remains) n = do
putStrLn ("Step "++show n++" of "++show nTot)
act
go remains $ succ n
To be used like
do
sequenceWithStepCount [
someOp ()
, someOtherOp ()
, thirdOp ()
]
There are a lot of logger libraries.
If you are interested in Monad-Logger - here you are: Control.Monad.Logger
And at the Hackage you could find other libraries
There are two ways that this might violate the laws, depending on what you mean.
For example, if return
were to count as a step, then you'd have a violation because the first monad law would not hold:
do x <- return /= f x
f x
Similarly, if abstracting out two steps into another named function counts as removing a step, then you also violate the monad laws, because the third monad law would not hold:
m' = do x <- m
f x
do y <- m' /= do x <- m
g y y <- f x
g y
However, if you have commands explicitly emit the "step" output, then there is no violation. This is because return
could then not emit any output at all, and sequencing two commands would just add their step outputs together. Here's an example:
import Control.Monad.Trans.State
import Control.Monad.Trans.Class (lift)
step :: StateT Int IO ()
step = do
n <- get
lift $ putStrLn $ "Step " ++ show n
put (n + 1)
command1 = do
command1' -- The command1 logic without the step behavior
step
command2 = do
command2'
step
-- etc.
Note that I don't include the total number of steps. There's no way to have access to that information for a monad. For that I recommend Daniel's answer, because Applicative
s are an excellent solution to this problem of determining the number of steps statically without any Template Haskell.
Use a monad transformer to stack on a WriterT that counts how many >>
's and >>=
's have been applied to the underlying monad.