Add traceIf function for conditional tracing.
[matthijs/master-project/cλash.git] / cλash / CLasH / Utils.hs
index 484fe15ae2e33d43e3dd4b9bfee6fa4ee30117b1..d85b25b5f415a817a82f54fa5471e1ef5b1aa409 100644 (file)
@@ -3,13 +3,11 @@ module CLasH.Utils where
 -- Standard Imports
 import qualified Maybe
 import Data.Accessor
 -- Standard Imports
 import qualified Maybe
 import Data.Accessor
+import qualified Data.Accessor.Monad.Trans.State as MonadState
 import qualified Data.Map as Map
 import qualified Control.Monad as Monad
 import qualified Control.Monad.Trans.State as State
 import qualified Data.Map as Map
 import qualified Control.Monad as Monad
 import qualified Control.Monad.Trans.State as State
-
--- GHC API
-
--- Local Imports
+import qualified Debug.Trace as Trace
   
 -- Make a caching version of a stateful computatation.
 makeCached :: (Monad m, Ord k) =>
   
 -- Make a caching version of a stateful computatation.
 makeCached :: (Monad m, Ord k) =>
@@ -19,14 +17,14 @@ makeCached :: (Monad m, Ord k) =>
   -> State.StateT s m v -- ^ The resulting value, from the cache or freshly
                         --   computed.
 makeCached key accessor create = do
   -> State.StateT s m v -- ^ The resulting value, from the cache or freshly
                         --   computed.
 makeCached key accessor create = do
-  cache <- getA accessor
+  cache <- MonadState.get accessor
   case Map.lookup key cache of
     -- Found in cache, just return
     Just value -> return value
     -- Not found, compute it and put it in the cache
     Nothing -> do
       value <- create
   case Map.lookup key cache of
     -- Found in cache, just return
     Just value -> return value
     -- Not found, compute it and put it in the cache
     Nothing -> do
       value <- create
-      modA accessor (Map.insert key value)
+      MonadState.modify accessor (Map.insert key value)
       return value
 
 unzipM :: (Monad m) =>
       return value
 
 unzipM :: (Monad m) =>
@@ -44,3 +42,28 @@ concatM :: (Monad m) =>
   -> m [a]
 concatM = Monad.liftM concat
 
   -> m [a]
 concatM = Monad.liftM concat
 
+isJustM :: (Monad m) => m (Maybe a) -> m Bool
+isJustM = Monad.liftM Maybe.isJust
+
+andM, orM :: (Monad m) => m [Bool] -> m Bool
+andM = Monad.liftM and
+orM = Monad.liftM or
+
+-- | Monadic versions of any and all. We reimplement them, since there
+-- is no ready-made lifting function for them.
+allM, anyM :: (Monad m) => (a -> m Bool) -> [a] -> m Bool
+allM f = andM . (mapM f)
+anyM f = orM . (mapM f)
+
+mapAccumLM :: (Monad m) => (acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
+mapAccumLM _ s []        =  return (s, [])
+mapAccumLM f s (x:xs)    =  do
+  (s',  y ) <- f s x
+  (s'', ys) <- mapAccumLM f s' xs
+  return (s'', y:ys)
+
+-- Trace the given string if the given bool is True, do nothing
+-- otherwise.
+traceIf :: Bool -> String -> a -> a
+traceIf True = Trace.trace
+traceIf False = flip const