module MonadUtils
( Applicative(..)
, (<$>)
, MonadFix(..)
, MonadIO(..)
, liftIO1, liftIO2, liftIO3, liftIO4
, zipWith3M, zipWith3M_, zipWith4M, zipWithAndUnzipM
, mapAndUnzipM, mapAndUnzip3M, mapAndUnzip4M, mapAndUnzip5M
, mapAccumLM
, mapSndM
, concatMapM
, mapMaybeM
, fmapMaybeM, fmapEitherM
, anyM, allM, orM
, foldlM, foldlM_, foldrM
, maybeMapM
, whenM, unlessM
) where
import GhcPrelude
import Maybes
import Control.Monad
import Control.Monad.Fix
import Control.Monad.IO.Class
liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b
liftIO1 = (.) liftIO
liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c
liftIO2 = ((.).(.)) liftIO
liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d
liftIO3 = ((.).((.).(.))) liftIO
liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e
liftIO4 = (((.).(.)).((.).(.))) liftIO
zipWith3M :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m [d]
zipWith3M _ [] _ _ = return []
zipWith3M _ _ [] _ = return []
zipWith3M _ _ _ [] = return []
zipWith3M f (x:xs) (y:ys) (z:zs)
= do { r <- f x y z
; rs <- zipWith3M f xs ys zs
; return $ r:rs
}
zipWith3M_ :: Monad m => (a -> b -> c -> m d) -> [a] -> [b] -> [c] -> m ()
zipWith3M_ f as bs cs = do { _ <- zipWith3M f as bs cs
; return () }
zipWith4M :: Monad m => (a -> b -> c -> d -> m e)
-> [a] -> [b] -> [c] -> [d] -> m [e]
zipWith4M _ [] _ _ _ = return []
zipWith4M _ _ [] _ _ = return []
zipWith4M _ _ _ [] _ = return []
zipWith4M _ _ _ _ [] = return []
zipWith4M f (x:xs) (y:ys) (z:zs) (a:as)
= do { r <- f x y z a
; rs <- zipWith4M f xs ys zs as
; return $ r:rs
}
zipWithAndUnzipM :: Monad m
=> (a -> b -> m (c, d)) -> [a] -> [b] -> m ([c], [d])
{-# INLINABLE zipWithAndUnzipM #-}
zipWithAndUnzipM f (x:xs) (y:ys)
= do { (c, d) <- f x y
; (cs, ds) <- zipWithAndUnzipM f xs ys
; return (c:cs, d:ds) }
zipWithAndUnzipM _ _ _ = return ([], [])
mapAndUnzip3M :: Monad m => (a -> m (b,c,d)) -> [a] -> m ([b],[c],[d])
mapAndUnzip3M _ [] = return ([],[],[])
mapAndUnzip3M f (x:xs) = do
(r1, r2, r3) <- f x
(rs1, rs2, rs3) <- mapAndUnzip3M f xs
return (r1:rs1, r2:rs2, r3:rs3)
mapAndUnzip4M :: Monad m => (a -> m (b,c,d,e)) -> [a] -> m ([b],[c],[d],[e])
mapAndUnzip4M _ [] = return ([],[],[],[])
mapAndUnzip4M f (x:xs) = do
(r1, r2, r3, r4) <- f x
(rs1, rs2, rs3, rs4) <- mapAndUnzip4M f xs
return (r1:rs1, r2:rs2, r3:rs3, r4:rs4)
mapAndUnzip5M :: Monad m => (a -> m (b,c,d,e,f)) -> [a] -> m ([b],[c],[d],[e],[f])
mapAndUnzip5M _ [] = return ([],[],[],[],[])
mapAndUnzip5M f (x:xs) = do
(r1, r2, r3, r4, r5) <- f x
(rs1, rs2, rs3, rs4, rs5) <- mapAndUnzip5M f xs
return (r1:rs1, r2:rs2, r3:rs3, r4:rs4, r5:rs5)
mapAccumLM :: Monad m
=> (acc -> x -> m (acc, y))
-> acc
-> [x]
-> m (acc, [y])
mapAccumLM _ s [] = return (s, [])
mapAccumLM f s (x:xs) = do
(s1, x') <- f s x
(s2, xs') <- mapAccumLM f s1 xs
return (s2, x' : xs')
mapSndM :: Monad m => (b -> m c) -> [(a,b)] -> m [(a,c)]
mapSndM _ [] = return []
mapSndM f ((a,b):xs) = do { c <- f b; rs <- mapSndM f xs; return ((a,c):rs) }
concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM f xs = liftM concat (mapM f xs)
mapMaybeM :: (Monad m) => (a -> m (Maybe b)) -> [a] -> m [b]
mapMaybeM f = liftM catMaybes . mapM f
fmapMaybeM :: (Monad m) => (a -> m b) -> Maybe a -> m (Maybe b)
fmapMaybeM _ Nothing = return Nothing
fmapMaybeM f (Just x) = f x >>= (return . Just)
fmapEitherM :: Monad m => (a -> m b) -> (c -> m d) -> Either a c -> m (Either b d)
fmapEitherM fl _ (Left a) = fl a >>= (return . Left)
fmapEitherM _ fr (Right b) = fr b >>= (return . Right)
anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool
anyM _ [] = return False
anyM f (x:xs) = do b <- f x
if b then return True
else anyM f xs
allM :: Monad m => (a -> m Bool) -> [a] -> m Bool
allM _ [] = return True
allM f (b:bs) = (f b) >>= (\bv -> if bv then allM f bs else return False)
orM :: Monad m => m Bool -> m Bool -> m Bool
orM m1 m2 = m1 >>= \x -> if x then return True else m2
foldlM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a
foldlM = foldM
foldlM_ :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m ()
foldlM_ = foldM_
foldrM :: (Monad m) => (b -> a -> m a) -> a -> [b] -> m a
foldrM _ z [] = return z
foldrM k z (x:xs) = do { r <- foldrM k z xs; k x r }
maybeMapM :: Monad m => (a -> m b) -> (Maybe a -> m (Maybe b))
maybeMapM _ Nothing = return Nothing
maybeMapM m (Just x) = liftM Just $ m x
whenM :: Monad m => m Bool -> m () -> m ()
whenM mb thing = do { b <- mb
; when b thing }
unlessM :: Monad m => m Bool -> m () -> m ()
unlessM condM acc = do { cond <- condM
; unless cond acc }