module Control.Monad.HT where import Control.Monad (liftM, liftM2, ) import Prelude hiding (repeat, until, ) infixr 1 <=< {- | Also present in newer versions of the 'base' package. -} (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c) (<=<) f g = (f =<<) . g {- | Monadic 'List.repeat'. -} repeat :: (Monad m) => m a -> m [a] repeat x = let go = liftM2 (:) x go in go {-# DEPRECATED untilM "use M.until" #-} {- | repeat action until result fulfills condition -} until, untilM :: (Monad m) => (a -> Bool) -> m a -> m a untilM = until until p m = let go = do x <- m if p x then return x else go in go {-# DEPRECATED iterateLimitM "use M.iterateLimit" #-} {- | parameter order equal to that of 'nest' -} iterateLimit, iterateLimitM :: Monad m => Int -> (a -> m a) -> a -> m [a] iterateLimitM = iterateLimit iterateLimit m f = let aux n x = liftM (x:) $ if n==0 then return [] else aux (n-1) =<< f x in aux m {- | Lazy monadic conjunction. That is, when the first action returns @False@, then @False@ is immediately returned, without running the second action. -} andLazy :: (Monad m) => m Bool -> m Bool -> m Bool andLazy m0 m1 = m0 >>= \b -> if b then m1 else return False {- | Lazy monadic disjunction. That is, when the first action returns @True@, then @True@ is immediately returned, without running the second action. -} orLazy :: (Monad m) => m Bool -> m Bool -> m Bool orLazy m0 m1 = m0 >>= \b -> if b then return True else m1