X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=c%CE%BBash%2FCLasH%2FUtils.hs;h=d85b25b5f415a817a82f54fa5471e1ef5b1aa409;hb=2884f7deed39c010b7c246d164afcf1056588a25;hp=c539c790125937b00363e77f0b333367a5c685ef;hpb=20bfd1175196d07cb1da80813d6eb958560e62bd;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git "a/c\316\273ash/CLasH/Utils.hs" "b/c\316\273ash/CLasH/Utils.hs" index c539c79..d85b25b 100644 --- "a/c\316\273ash/CLasH/Utils.hs" +++ "b/c\316\273ash/CLasH/Utils.hs" @@ -1,49 +1,69 @@ -module CLasH.Utils - ( listBindings - , listBind - ) where +module CLasH.Utils where -- 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 Debug.Trace as Trace + +-- Make a caching version of a stateful computatation. +makeCached :: (Monad m, Ord k) => + k -- ^ The key to use for the cache + -> Accessor s (Map.Map k v) -- ^ The accessor to get at the cache + -> State.StateT s m v -- ^ How to compute the value to cache? + -> State.StateT s m v -- ^ The resulting value, from the cache or freshly + -- computed. +makeCached key accessor create = do + 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 + MonadState.modify accessor (Map.insert key value) + return value --- GHC API -import qualified CoreSyn -import qualified CoreUtils -import qualified HscTypes -import qualified Outputable -import qualified Var +unzipM :: (Monad m) => + m [(a, b)] + -> m ([a], [b]) +unzipM = Monad.liftM unzip --- Local Imports -import CLasH.Utils.GhcTools -import CLasH.Utils.Pretty - -listBindings :: FilePath -> [FilePath] -> IO [()] -listBindings libdir filenames = do - (cores,_,_,_,_) <- loadModules libdir filenames bogusFinder bogusFinder bogusFinder - let binds = concat $ map (CoreSyn.flattenBinds . HscTypes.cm_binds) cores - mapM (listBinding) binds - where - bogusFinder = (\x -> return $ Nothing) - -listBinding :: (CoreSyn.CoreBndr, CoreSyn.CoreExpr) -> IO () -listBinding (b, e) = do - putStr "\nBinder: " - putStr $ show b - putStr "\nType of Binder: \n" - putStr $ Outputable.showSDoc $ Outputable.ppr $ Var.varType b - putStr "\n\nExpression: \n" - putStr $ prettyShow e - putStr "\n\n" - putStr $ Outputable.showSDoc $ Outputable.ppr e - putStr "\n\nType of Expression: \n" - putStr $ Outputable.showSDoc $ Outputable.ppr $ CoreUtils.exprType e - putStr "\n\n" - --- | Show the core structure of the given binds in the given file. -listBind :: FilePath -> [FilePath] -> String -> IO () -listBind libdir filenames name = do - (_,corebind,_,coreexpr,_) <- loadModules libdir filenames bindFinder bindFinder exprFinder - listBinding (Maybe.fromJust $ head corebind, Maybe.fromJust $ head coreexpr) - where - bindFinder = findBind (hasVarName name) - exprFinder = findExpr (hasVarName name) \ No newline at end of file +catMaybesM :: (Monad m) => + m [Maybe a] + -> m [a] +catMaybesM = Monad.liftM Maybe.catMaybes + +concatM :: (Monad m) => + m [[a]] + -> 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