Skip to content

Commit

Permalink
Support building with mtl-2.3.* (GHC 9.6)
Browse files Browse the repository at this point in the history
This patch contains two changes needed to make `asl-translator` compile with
GHC 9.6:

* GHC 9.6 bundles `mtl-2.3.*`, which no longer re-exports `Control.Monad`
  and similar modules from `mtl`-related modules.  To accommodate this, various
  imports have been made more explicit.
* I have bumped the following submodules to bring in GHC 9.6–related changes:
  * `crucible`: GaloisInc/crucible#1102
  * `what4`: GaloisInc/what4#235
  • Loading branch information
RyanGlScott committed Aug 7, 2023
1 parent 404e06f commit a5a1028
Show file tree
Hide file tree
Showing 6 changed files with 13 additions and 11 deletions.
6 changes: 3 additions & 3 deletions lib/Data/Parameterized/AssignTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions lib/Language/ASL/Formulas/Normalize.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down Expand Up @@ -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
Expand Down
6 changes: 3 additions & 3 deletions lib/Language/ASL/Translation/Driver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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 "----------------------"
Expand Down Expand Up @@ -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)
Expand All @@ -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
Expand Down
4 changes: 3 additions & 1 deletion lib/Util/Log.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down
2 changes: 1 addition & 1 deletion submodules/crucible
Submodule crucible updated 3566 files

0 comments on commit a5a1028

Please sign in to comment.