Skip to content
Snippets Groups Projects
Commit e07185ed authored by batterseapower's avatar batterseapower
Browse files

Move allM to MonadUtils

parent 393f2662
No related branches found
No related tags found
No related merge requests found
...@@ -40,6 +40,7 @@ module Digraph( ...@@ -40,6 +40,7 @@ module Digraph(
import Util ( sortLe ) import Util ( sortLe )
import Outputable import Outputable
import Maybes ( expectJust ) import Maybes ( expectJust )
import MonadUtils ( allM )
-- Extensions -- Extensions
import Control.Monad ( filterM, liftM, liftM2 ) import Control.Monad ( filterM, liftM, liftM2 )
...@@ -588,8 +589,4 @@ vertexGroupsS provided g to_provide ...@@ -588,8 +589,4 @@ vertexGroupsS provided g to_provide
vertexReady :: Set s -> IntGraph -> Vertex -> ST s Bool vertexReady :: Set s -> IntGraph -> Vertex -> ST s Bool
vertexReady provided g v = liftM2 (&&) (liftM not $ provided `contains` v) (allM (provided `contains`) (g!v)) vertexReady provided g v = liftM2 (&&) (liftM not $ provided `contains` v) (allM (provided `contains`) (g!v))
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)
\end{code} \end{code}
...@@ -13,7 +13,7 @@ module MonadUtils ...@@ -13,7 +13,7 @@ module MonadUtils
, mapAccumLM , mapAccumLM
, mapSndM , mapSndM
, concatMapM , concatMapM
, anyM , anyM, allM
, foldlM, foldrM , foldlM, foldrM
) where ) where
...@@ -116,13 +116,18 @@ mapSndM f ((a,b):xs) = do { c <- f b; rs <- mapSndM f xs; return ((a,c):rs) } ...@@ -116,13 +116,18 @@ 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 :: Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM f xs = liftM concat (mapM f xs) concatMapM f xs = liftM concat (mapM f xs)
-- | Monadic version of 'any', aborts the computation at the first False value -- | Monadic version of 'any', aborts the computation at the first @True@ value
anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool anyM :: Monad m => (a -> m Bool) -> [a] -> m Bool
anyM _ [] = return False anyM _ [] = return False
anyM f (x:xs) = do b <- f x anyM f (x:xs) = do b <- f x
if b then return True if b then return True
else anyM f xs else anyM f xs
-- | Monad version of 'all', aborts the computation at the first @False@ value
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)
-- | Monadic version of foldl -- | Monadic version of foldl
foldlM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a foldlM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a
foldlM = foldM foldlM = foldM
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment