module Control.Carbonara.Tools where import Control.Exception ( SomeException(SomeException), try ) import Control.Monad (liftM2) import Data.Time.Clock (diffUTCTime, getCurrentTime) --time import Data.Typeable (typeOf) infixr 7 .&&. , .||. (.&&.) :: Monad m => m Bool -> m Bool -> m Bool (.&&.) = liftM2 (&&) -- filter (even .&&. (>5)) [1..10] --> [6,8,10] -- filter (even .&&. (>5) .&&. (<9)) [1..10] --> [6,8] (.||.) :: Monad m => m Bool -> m Bool -> m Bool (.||.) = liftM2 (||) -- filter (even .||. (>5)) [1..10] --> [2,4,6,7,8,9,10] -- filter (even .||. (>5) .||. (==1)) [1..10] --> [1,2,4,6,7,8,9,10] timer :: IO a -> IO () timer action = do start <- getCurrentTime action end <- getCurrentTime putStrLn $ show (end `diffUTCTime` start) ++ " elapsed." --example: ghci> timer $ print [1..1000000] trying :: IO () -> IO () trying x = do v <- try x case v of Right x -> return x Left (SomeException e) -> print (typeOf e) --example: ghci> mapM_ (\x -> trying $ someIOactionX) [0..10]