{-# LANGUAGE CPP, NoImplicitPrelude #-}
module Control.Monad.Compat (
module Base
, Monad
#if MIN_VERSION_base(4,9,0)
, MonadFail
#endif
, fail
, MonadPlus(..)
#if !(MIN_VERSION_base(4,8,0))
, foldM
, foldM_
, forM
, forM_
, guard
, mapM
, mapM_
, msum
, sequence
, sequence_
, unless
, when
, (<$!>)
#endif
#if !(MIN_VERSION_base(4,9,0))
, forever
, filterM
, mapAndUnzipM
, zipWithM
, zipWithM_
, replicateM
, replicateM_
#endif
) where
#if MIN_VERSION_base(4,9,0)
import Control.Monad as Base hiding (fail)
import Control.Monad.Fail as Base
#else
import Control.Monad as Base hiding (
forever
, filterM
, mapAndUnzipM
, zipWithM
, zipWithM_
, replicateM
, replicateM_
# if !(MIN_VERSION_base(4,8,0))
, foldM
, foldM_
, forM
, forM_
, guard
, mapM
, mapM_
, msum
, sequence
, sequence_
, unless
, when
# endif
)
import Control.Applicative
import Data.Foldable.Compat
import Data.Traversable
import Prelude.Compat
#endif
#if !(MIN_VERSION_base(4,8,0))
when :: (Applicative f) => Bool -> f () -> f ()
{-# INLINEABLE when #-}
{-# SPECIALISE when :: Bool -> IO () -> IO () #-}
{-# SPECIALISE when :: Bool -> Maybe () -> Maybe () #-}
when p s = if p then s else pure ()
guard :: (Alternative f) => Bool -> f ()
guard True = pure ()
guard False = empty
unless :: (Applicative f) => Bool -> f () -> f ()
{-# INLINEABLE unless #-}
{-# SPECIALISE unless :: Bool -> IO () -> IO () #-}
{-# SPECIALISE unless :: Bool -> Maybe () -> Maybe () #-}
unless p s = if p then pure () else s
foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
{-# INLINEABLE foldM #-}
{-# SPECIALISE foldM :: (a -> b -> IO a) -> a -> [b] -> IO a #-}
{-# SPECIALISE foldM :: (a -> b -> Maybe a) -> a -> [b] -> Maybe a #-}
foldM = foldlM
foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
{-# INLINEABLE foldM_ #-}
{-# SPECIALISE foldM_ :: (a -> b -> IO a) -> a -> [b] -> IO () #-}
{-# SPECIALISE foldM_ :: (a -> b -> Maybe a) -> a -> [b] -> Maybe () #-}
foldM_ f a xs = foldlM f a xs >> return ()
infixl 4 <$!>
(<$!>) :: Monad m => (a -> b) -> m a -> m b
{-# INLINE (<$!>) #-}
f <$!> m = do
x <- m
let z = f x
z `seq` return z
#endif
#if !(MIN_VERSION_base(4,9,0))
forever :: (Applicative f) => f a -> f b
{-# INLINE forever #-}
forever a = let a' = a *> a' in a'
{-# INLINE filterM #-}
filterM :: (Applicative m) => (a -> m Bool) -> [a] -> m [a]
filterM p = foldr (\ x -> liftA2 (\ flg -> if flg then (x:) else id) (p x)) (pure [])
mapAndUnzipM :: (Applicative m) => (a -> m (b,c)) -> [a] -> m ([b], [c])
{-# INLINE mapAndUnzipM #-}
mapAndUnzipM f xs = unzip <$> traverse f xs
zipWithM :: (Applicative m) => (a -> b -> m c) -> [a] -> [b] -> m [c]
{-# INLINE zipWithM #-}
zipWithM f xs ys = sequenceA (zipWith f xs ys)
zipWithM_ :: (Applicative m) => (a -> b -> m c) -> [a] -> [b] -> m ()
{-# INLINE zipWithM_ #-}
zipWithM_ f xs ys = sequenceA_ (zipWith f xs ys)
replicateM :: (Applicative m) => Int -> m a -> m [a]
{-# INLINEABLE replicateM #-}
{-# SPECIALISE replicateM :: Int -> IO a -> IO [a] #-}
{-# SPECIALISE replicateM :: Int -> Maybe a -> Maybe [a] #-}
replicateM cnt0 f =
loop cnt0
where
loop cnt
| cnt <= 0 = pure []
| otherwise = liftA2 (:) f (loop (cnt - 1))
replicateM_ :: (Applicative m) => Int -> m a -> m ()
{-# INLINEABLE replicateM_ #-}
{-# SPECIALISE replicateM_ :: Int -> IO a -> IO () #-}
{-# SPECIALISE replicateM_ :: Int -> Maybe a -> Maybe () #-}
replicateM_ cnt0 f =
loop cnt0
where
loop cnt
| cnt <= 0 = pure ()
| otherwise = f *> loop (cnt - 1)
#endif