Skip to content

Commit 07959fe

Browse files
author
Brian Huffman
committed
Compute Cryptol type directly from LLVM type in crucible_fresh_var.
Fixes #583.
1 parent 4e2623f commit 07959fe

File tree

2 files changed

+53
-51
lines changed

2 files changed

+53
-51
lines changed

src/SAWScript/Crucible/Common/Setup/Type.hs

+9-5
Original file line numberDiff line numberDiff line change
@@ -35,8 +35,10 @@ import Control.Lens
3535
import Control.Monad.State (StateT)
3636
import Control.Monad.IO.Class (MonadIO(liftIO))
3737

38-
import Verifier.SAW.TypedTerm (TypedTerm, mkTypedTerm)
39-
import Verifier.SAW.SharedTerm (Term, SharedContext, scFreshGlobal)
38+
import qualified Cryptol.TypeCheck.Type as Cryptol (Type, tMono)
39+
import qualified Verifier.SAW.Cryptol as Cryptol (importType, emptyEnv)
40+
import Verifier.SAW.TypedTerm (TypedTerm(..))
41+
import Verifier.SAW.SharedTerm (SharedContext, scFreshGlobal)
4042

4143
import qualified SAWScript.Crucible.Common.MethodSpec as MS
4244

@@ -99,9 +101,11 @@ freshVariable ::
99101
MonadIO m =>
100102
SharedContext {- ^ shared context -} ->
101103
String {- ^ variable name -} ->
102-
Term {- ^ variable type -} ->
104+
Cryptol.Type {- ^ variable type -} ->
103105
CrucibleSetupT arch m TypedTerm
104-
freshVariable sc name ty =
105-
do tt <- liftIO (mkTypedTerm sc =<< scFreshGlobal sc name ty)
106+
freshVariable sc name cty =
107+
do ty <- liftIO $ Cryptol.importType sc Cryptol.emptyEnv cty
108+
trm <- liftIO $ scFreshGlobal sc name ty
109+
let tt = TypedTerm (Cryptol.tMono cty) trm
106110
currentState . MS.csFreshVars %= cons tt
107111
return tt

src/SAWScript/Crucible/LLVM/Builtins.hs

+44-46
Original file line numberDiff line numberDiff line change
@@ -91,12 +91,16 @@ import Text.PrettyPrint.ANSI.Leijen hiding ((<$>), (<>))
9191
import qualified Text.PrettyPrint.ANSI.Leijen as PP
9292
import qualified Control.Monad.Trans.Maybe as MaybeT
9393

94+
-- parameterized-utils
9495
import Data.Parameterized.Classes
95-
9696
import Data.Parameterized.NatRepr
9797
import Data.Parameterized.Nonce
9898
import Data.Parameterized.Some
9999

100+
-- cryptol
101+
import qualified Cryptol.TypeCheck.Type as Cryptol
102+
103+
-- what4
100104
import qualified What4.Concrete as W4
101105
import qualified What4.Config as W4
102106
import qualified What4.FunctionName as W4
@@ -105,6 +109,7 @@ import qualified What4.ProgramLoc as W4
105109
import qualified What4.Interface as W4
106110
import qualified What4.Expr.Builder as W4
107111

112+
-- crucible
108113
import qualified Lang.Crucible.Backend as Crucible
109114
import qualified Lang.Crucible.Backend.SAWCore as CrucibleSAW
110115
import qualified Lang.Crucible.CFG.Core as Crucible
@@ -117,6 +122,7 @@ import qualified Lang.Crucible.Simulator.GlobalState as Crucible
117122
import qualified Lang.Crucible.Simulator.PathSatisfiability as Crucible
118123
import qualified Lang.Crucible.Simulator.SimError as Crucible
119124

125+
-- crucible-llvm
120126
import qualified Lang.Crucible.LLVM.ArraySizeProfile as Crucible
121127
import qualified Lang.Crucible.LLVM.DataLayout as Crucible
122128
import Lang.Crucible.LLVM.Extension (LLVM)
@@ -125,16 +131,18 @@ import qualified Lang.Crucible.LLVM.Translation as Crucible
125131

126132
import qualified SAWScript.Crucible.LLVM.CrucibleLLVM as Crucible
127133

134+
-- parameterized-utils
128135
import qualified Data.Parameterized.TraversableFC as Ctx
129136
import qualified Data.Parameterized.Context as Ctx
130137

138+
-- saw-core
131139
import Verifier.SAW.FiniteValue (ppFirstOrderValue)
132-
import Verifier.SAW.Prelude
133140
import Verifier.SAW.SharedTerm
134141
import Verifier.SAW.TypedAST
135142
import Verifier.SAW.Recognizer
136143
import Verifier.SAW.TypedTerm
137144

145+
-- saw-script
138146
import SAWScript.Proof
139147
import SAWScript.Prover.SolverStats
140148
import SAWScript.Prover.Versions
@@ -1287,37 +1295,28 @@ crucible_execute_func bic opts args =
12871295
getLLVMCrucibleContext :: CrucibleSetup (LLVM arch) (LLVMCrucibleContext arch)
12881296
getLLVMCrucibleContext = view Setup.csCrucibleContext <$> get
12891297

1290-
-- | Returns logical type of actual type if it is an array or primitive
1298+
-- | Returns Cryptol type of actual type if it is an array or primitive
12911299
-- type, or an appropriately-sized bit vector for pointer types.
1292-
logicTypeOfActual :: Crucible.DataLayout -> SharedContext -> Crucible.MemType
1293-
-> IO (Maybe Term)
1294-
logicTypeOfActual _ sc (Crucible.IntType w) = Just <$> logicTypeForInt sc w
1295-
logicTypeOfActual _ sc Crucible.FloatType = Just <$> scApplyPrelude_Float sc
1296-
logicTypeOfActual _ sc Crucible.DoubleType = Just <$> scApplyPrelude_Double sc
1297-
logicTypeOfActual dl sc (Crucible.ArrayType n ty) = do
1298-
melTyp <- logicTypeOfActual dl sc ty
1299-
case melTyp of
1300-
Just elTyp -> do
1301-
lTm <- scNat sc (fromIntegral n)
1302-
Just <$> scVecType sc lTm elTyp
1303-
Nothing -> return Nothing
1304-
logicTypeOfActual dl sc (Crucible.PtrType _) = do
1305-
bType <- scBoolType sc
1306-
lTm <- scNat sc (fromIntegral (Crucible.ptrBitwidth dl))
1307-
Just <$> scVecType sc lTm bType
1308-
logicTypeOfActual dl sc (Crucible.StructType si) = do
1309-
let memtypes = V.toList (Crucible.siFieldTypes si)
1310-
melTyps <- traverse (logicTypeOfActual dl sc) memtypes
1311-
case sequence melTyps of
1312-
Just elTyps -> Just <$> scTupleType sc elTyps
1313-
Nothing -> return Nothing
1314-
logicTypeOfActual _ _ t = fail (show t) -- return Nothing
1315-
1316-
logicTypeForInt :: SharedContext -> Natural -> IO Term
1317-
logicTypeForInt sc w =
1318-
do bType <- scBoolType sc
1319-
lTm <- scNat sc (fromIntegral w)
1320-
scVecType sc lTm bType
1300+
cryptolTypeOfActual :: Crucible.DataLayout -> Crucible.MemType -> Maybe Cryptol.Type
1301+
cryptolTypeOfActual dl mt =
1302+
case mt of
1303+
Crucible.IntType w ->
1304+
return $ Cryptol.tWord (Cryptol.tNum w)
1305+
Crucible.FloatType ->
1306+
Nothing -- FIXME: update when Cryptol gets float types
1307+
Crucible.DoubleType ->
1308+
Nothing -- FIXME: update when Cryptol gets float types
1309+
Crucible.ArrayType n ty ->
1310+
do cty <- cryptolTypeOfActual dl ty
1311+
return $ Cryptol.tSeq (Cryptol.tNum n) cty
1312+
Crucible.PtrType _ ->
1313+
return $ Cryptol.tWord (Cryptol.tNum (Crucible.ptrBitwidth dl))
1314+
Crucible.StructType si ->
1315+
do let memtypes = V.toList (Crucible.siFieldTypes si)
1316+
ctys <- traverse (cryptolTypeOfActual dl) memtypes
1317+
return $ Cryptol.tTuple ctys
1318+
_ ->
1319+
Nothing
13211320

13221321
-- | Generate a fresh variable term. The name will be used when
13231322
-- pretty-printing the variable in debug output.
@@ -1327,16 +1326,16 @@ crucible_fresh_var ::
13271326
String {- ^ variable name -} ->
13281327
L.Type {- ^ variable type -} ->
13291328
LLVMCrucibleSetupM TypedTerm {- ^ fresh typed term -}
1330-
crucible_fresh_var bic _opts name lty = LLVMCrucibleSetupM $ do
1331-
cctx <- getLLVMCrucibleContext
1332-
let ?lc = cctx ^. ccTypeCtx
1333-
lty' <- memTypeForLLVMType bic lty
1334-
let sc = biSharedContext bic
1335-
let dl = Crucible.llvmDataLayout (cctx^.ccTypeCtx)
1336-
mty <- liftIO $ logicTypeOfActual dl sc lty'
1337-
case mty of
1338-
Nothing -> fail $ "Unsupported type in crucible_fresh_var: " ++ show (L.ppType lty)
1339-
Just ty -> Setup.freshVariable sc name ty
1329+
crucible_fresh_var bic _opts name lty =
1330+
LLVMCrucibleSetupM $
1331+
do cctx <- getLLVMCrucibleContext
1332+
let ?lc = cctx ^. ccTypeCtx
1333+
lty' <- memTypeForLLVMType bic lty
1334+
let sc = biSharedContext bic
1335+
let dl = Crucible.llvmDataLayout (cctx^.ccTypeCtx)
1336+
case cryptolTypeOfActual dl lty' of
1337+
Nothing -> fail $ "Unsupported type in crucible_fresh_var: " ++ show (L.ppType lty)
1338+
Just cty -> Setup.freshVariable sc name cty
13401339

13411340
-- | Use the given LLVM type to compute a setup value that
13421341
-- covers expands all of the struct, array, and pointer
@@ -1370,8 +1369,8 @@ constructExpandedSetupValue ::
13701369
constructExpandedSetupValue cc sc loc t = do
13711370
case t of
13721371
Crucible.IntType w ->
1373-
do ty <- liftIO (logicTypeForInt sc w)
1374-
fv <- Setup.freshVariable sc "" ty
1372+
do let cty = Cryptol.tWord (Cryptol.tNum w)
1373+
fv <- Setup.freshVariable sc "" cty
13751374
pure $ mkAllLLVM (SetupTerm fv)
13761375

13771376
Crucible.StructType si -> do
@@ -1515,8 +1514,7 @@ crucible_alloc_global ::
15151514
String ->
15161515
LLVMCrucibleSetupM ()
15171516
crucible_alloc_global _bic _opts name = LLVMCrucibleSetupM $
1518-
do cc <- getLLVMCrucibleContext
1519-
loc <- getW4Position "crucible_alloc_global"
1517+
do loc <- getW4Position "crucible_alloc_global"
15201518
Setup.addAllocGlobal . LLVMAllocGlobal loc $ L.Symbol name
15211519

15221520
crucible_fresh_pointer ::

0 commit comments

Comments
 (0)