Skip to content

Instantly share code, notes, and snippets.

@danidiaz
Last active December 29, 2015 19:49
Show Gist options
  • Select an option

  • Save danidiaz/7720246 to your computer and use it in GitHub Desktop.

Select an option

Save danidiaz/7720246 to your computer and use it in GitHub Desktop.
Using applicatives and pipes to track the number of steps in a computation, and show progress. http://stackoverflow.com/questions/20292694/how-to-write-a-monad-that-prints-step-i-of-n-when-executing-each-statement-in
module Main where
import Data.Monoid
import Control.Applicative
import Control.Monad.State
import Data.Functor.Compose
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
ticker :: MonadIO m => Int -> Consumer () m a
ticker n = evalStateP 0 $ forever $ do
await
lift $ modify succ
current <- lift get
liftIO $ putStrLn $ "tick " ++ show current ++ " of " ++ show n
program :: SteppedIO ()
program =
step (putStrLn "aaa")
*>
step (putStrLn "bbb")
*>
step (putStrLn "ccc")
main :: IO ()
main = runEffect $ exec program >-> ticker (countSteps program)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment