diff --git a/lib/Data/Parameterized/AssignTree.hs b/lib/Data/Parameterized/AssignTree.hs index 88cda2a..c7d19cc 100644 --- a/lib/Data/Parameterized/AssignTree.hs +++ b/lib/Data/Parameterized/AssignTree.hs @@ -43,10 +43,10 @@ module Data.Parameterized.AssignTree , revTraverseMapCtxTree ) where -import Unsafe.Coerce -import Data.Proxy +import Data.Functor.Identity (Identity(..)) import Data.Kind -import Control.Monad.Identity hiding (zipWithM) +import Data.Proxy +import Unsafe.Coerce import Data.Parameterized.Context hiding (zipWithM) import qualified Data.Parameterized.Context as Ctx diff --git a/lib/Language/ASL/Formulas/Normalize.hs b/lib/Language/ASL/Formulas/Normalize.hs index df4dd5e..06c453b 100644 --- a/lib/Language/ASL/Formulas/Normalize.hs +++ b/lib/Language/ASL/Formulas/Normalize.hs @@ -73,7 +73,7 @@ import Prelude hiding ( fail ) import GHC.Stack import GHC.TypeLits -import Control.Monad ( forM, void ) +import Control.Monad ( forM, liftM, void ) import Control.Lens hiding (Index, (:>), Empty) import Control.Monad.Fail @@ -338,7 +338,7 @@ getUsedBVs :: Ctx.Assignment (WB.ExprBoundVar t) args -> RebindM t (Set (Some (WB.ExprBoundVar t))) getUsedBVs asn expr = do let allBvs = Set.fromList $ FC.toListFC Some asn - usedbvsSet <- IO.liftIO $ ME.liftM (Set.unions . map snd) $ ST.stToIO $ H.toList =<< WB.boundVars expr + usedbvsSet <- IO.liftIO $ liftM (Set.unions . map snd) $ ST.stToIO $ H.toList =<< WB.boundVars expr return $ Set.intersection allBvs usedbvsSet simplifiedSymFn :: forall t rets args diff --git a/lib/Language/ASL/Translation/Driver.hs b/lib/Language/ASL/Translation/Driver.hs index 87e94d6..510f9e1 100644 --- a/lib/Language/ASL/Translation/Driver.hs +++ b/lib/Language/ASL/Translation/Driver.hs @@ -778,7 +778,7 @@ reportStats sopts sm = do when (not (Set.null unexpectedElems)) $ do putStrLn $ "Unexpected exceptions:" forMwithKey_ (instrExcepts sm) $ \ident -> \e -> - E.when (unexpected (KeyInstr ident) e) $ do + when (unexpected (KeyInstr ident) e) $ do putStrLn $ prettyIdent ident ++ " failed to translate:" putStrLn $ show e putStrLn "----------------------" @@ -807,7 +807,7 @@ reportStats sopts sm = do if not (Map.member ident (instrExcepts sm)) && Set.null (Set.filter (\dep -> Map.member dep (funExcepts sm)) deps) then do - E.when (reportSucceedingInstructions sopts) $ putStrLn $ prettyIdent ident + when (reportSucceedingInstructions sopts) $ putStrLn $ prettyIdent ident return $ Just ident else return Nothing) (instrDeps sm) putStrLn $ "Number of successfully translated functions: " <> show (Map.size $ r) @@ -819,7 +819,7 @@ reportStats sopts sm = do KeyInstr ident -> putStrLn $ "Instruction: " <> prettyIdent ident KeyFun nm -> do putStrLn $ "Function: " <> show nm - E.when (reportFunctionDependencies sopts) $ do + when (reportFunctionDependencies sopts) $ do putStrLn $ "Which is depended on by: " case Map.lookup nm reverseDependencyMap of Just instrs -> mapM_ (\ident -> putStrLn $ " " <> prettyIdent ident) instrs diff --git a/lib/Util/Log.hs b/lib/Util/Log.hs index fc70d20..606da7f 100644 --- a/lib/Util/Log.hs +++ b/lib/Util/Log.hs @@ -17,7 +17,9 @@ module Util.Log , WLog.LogCfg ) where -import Control.Monad.Identity +import Control.Monad (when) +import Data.Functor (void) +import Data.Functor.Identity (Identity) import qualified Control.Monad.IO.Class as IO diff --git a/submodules/crucible b/submodules/crucible index ad4a553..bc64fda 160000 --- a/submodules/crucible +++ b/submodules/crucible @@ -1 +1 @@ -Subproject commit ad4a553487eeb5c6bbb5abf4bde26af905bf0254 +Subproject commit bc64fda29cf2e1f4641b381a739c53d7c4d2aa38 diff --git a/submodules/what4 b/submodules/what4 index 6c462cd..28744e4 160000 --- a/submodules/what4 +++ b/submodules/what4 @@ -1 +1 @@ -Subproject commit 6c462cd46e0ea9ebbfbd6b6ea237984eeb3dc72a +Subproject commit 28744e48e01dc9c35d5aeebb914a9bb425cfe0f1