Skip to content

Commit aa791c9

Browse files
author
Eddy Westbrook
committed
removed compiler warnings from HintExtract.hs; also removed calls to error in favor of an Except monad
1 parent 80c475b commit aa791c9

File tree

2 files changed

+63
-60
lines changed

2 files changed

+63
-60
lines changed

heapster-saw/src/Verifier/SAW/Heapster/HintExtract.hs

+60-59
Original file line numberDiff line numberDiff line change
@@ -5,23 +5,24 @@
55
{-# Language ScopedTypeVariables #-}
66
{-# LANGUAGE GADTs #-}
77
{-# LANGUAGE ParallelListComp #-}
8+
{-# LANGUAGE LambdaCase #-}
89

910
module Verifier.SAW.Heapster.HintExtract ( heapsterRequireName, extractHints ) where
1011

11-
import Control.Applicative ((<|>))
1212
import Data.String (fromString)
1313
import Data.Functor.Constant (Constant(..))
1414
import Control.Lens ((^.))
15+
import Control.Monad.Except
1516
import Data.Maybe (fromMaybe, maybeToList)
1617
import qualified Data.Map as Map
1718
import Data.Char (chr)
1819
import Text.LLVM.AST as L
1920

20-
import Data.Binding.Hobbits (RAssign ((:>:)))
21-
import Data.Type.RList (mapRAssign, type (:++:), RAssign (MNil))
2221
import Data.Parameterized (toListFC, fmapFC, (:~:)(..), testEquality)
2322
import qualified Data.Parameterized.Context as Ctx
23+
import Data.Parameterized.TraversableFC (traverseFC)
2424

25+
import Data.Type.RList (mapRAssign, (:++:))
2526
import Lang.Crucible.LLVM.Extension ( LLVM, LLVMStmt(..))
2627
import Lang.Crucible.CFG.Core ( Some(Some)
2728
, CtxRepr
@@ -33,14 +34,17 @@ import Lang.Crucible.CFG.Core ( Some(Some)
3334
, StmtSeq(..)
3435
, Stmt (..), BlockID )
3536

36-
import Verifier.SAW.Heapster.CruUtil(globalSymbolName, mkCruCtx, CruCtx(..), CtxToRList, cruCtxLen)
37+
import Verifier.SAW.Heapster.CruUtil
3738
import Verifier.SAW.Heapster.ParsedCtx
38-
import Verifier.SAW.Heapster.Permissions (PermEnv, Hint (..), BlockHintSort(..), BlockHint(..), MbValuePerms, funPermTops, FunPerm)
39+
import Verifier.SAW.Heapster.Permissions
3940
import Verifier.SAW.Heapster.PermParser
4041

4142
heapsterRequireName :: String
4243
heapsterRequireName = "heapster.require"
4344

45+
-- | The monad we use for extracting hints, which just has 'String' errors
46+
type ExtractM = Except String
47+
4448
-- | Extract block hints from calls to `heapster.require` in the Crucible CFG.
4549
extractHints ::
4650
forall ghosts args outs blocks init ret.
@@ -51,34 +55,29 @@ extractHints ::
5155
-- ^ The FunPerm corresponding to the CFG we are scanning
5256
CFG LLVM blocks init ret ->
5357
-- ^ The Crucible CFG for which to build the block hint map
54-
Ctx.Assignment (Constant (Maybe Hint)) blocks
55-
extractHints env modules perm cfg = blocks
58+
Either String (Ctx.Assignment (Constant (Maybe Hint)) blocks)
59+
extractHints env modules perm cfg =
60+
runExcept $ traverseFC extractHint (cfgBlockMap cfg)
5661
where
57-
globals =
58-
Map.fromList
59-
[ (globalSym g, str) | m <- modules,
60-
g <- modGlobals m,
61-
ValString chars <- maybeToList (globalValue g),
62-
let str = chr . fromEnum <$> chars ]
63-
64-
blocks = fmapFC extractHint (cfgBlockMap cfg)
62+
globals =
63+
Map.fromList
64+
[ (globalSym g, str) | m <- modules,
65+
g <- modGlobals m,
66+
ValString chars <- maybeToList (globalValue g),
67+
let str = chr . fromEnum <$> chars ]
6568

66-
extractHint ::
67-
forall ctx.
68-
Block LLVM blocks ret ctx ->
69-
Constant (Maybe Hint) ctx
70-
extractHint block =
71-
case extractBlockHints env globals (funPermTops perm) block of
72-
Constant (Just (SomeHintSpec ghosts valuePerms)) ->
73-
Constant $ Just $
74-
mkBlockEntryHint
75-
cfg
76-
(blockID block)
77-
(funPermTops perm)
78-
ghosts
79-
valuePerms
80-
_ ->
81-
Constant Nothing
69+
extractHint :: Block LLVM blocks ret ctx ->
70+
ExtractM (Constant (Maybe Hint) ctx)
71+
extractHint block =
72+
extractBlockHints env globals (funPermTops perm) block >>= \case
73+
Just (SomeHintSpec ghosts valuePerms) ->
74+
return $ Constant $ Just (mkBlockEntryHint
75+
cfg
76+
(blockID block)
77+
(funPermTops perm)
78+
ghosts
79+
valuePerms)
80+
_ -> return $ Constant Nothing
8281

8382
-- | Packs up the ghosts in a parsed hint permission spec
8483
data SomeHintSpec tops ctx where
@@ -96,14 +95,16 @@ extractBlockHints ::
9695
CruCtx tops ->
9796
-- ^ top context derived from current function's perm
9897
Block LLVM blocks ret ctx ->
99-
Constant (Maybe (SomeHintSpec tops ctx)) blocks
98+
ExtractM (Maybe (SomeHintSpec tops ctx))
10099
extractBlockHints env globals tops block =
101-
Constant $ extractStmtsHint who env globals tops inputs stmts
100+
extractStmtsHint who env globals tops inputs stmts
102101
where
103102
stmts = block ^. blockStmts
104103
inputs = blockInputs block
105104
who = show (blockID block)
106105

106+
-- | Test if a sequence of statements starts with the Crucible representation of
107+
-- a call to the dummy function @heapster.require@
107108
extractStmtsHint ::
108109
forall blocks ret ctx tops.
109110
String ->
@@ -115,20 +116,18 @@ extractStmtsHint ::
115116
CtxRepr ctx ->
116117
-- ^ block arguments
117118
StmtSeq LLVM blocks ret ctx ->
118-
Maybe (SomeHintSpec tops ctx)
119+
ExtractM (Maybe (SomeHintSpec tops ctx))
119120
extractStmtsHint who env globals tops inputs = loop Ctx.zeroSize
120121
where
121122
loop ::
122123
forall rest.
123124
Ctx.Size rest ->
124125
StmtSeq LLVM blocks ret (ctx Ctx.<+> rest) ->
125-
Maybe (SomeHintSpec tops ctx)
126+
ExtractM (Maybe (SomeHintSpec tops ctx))
126127
loop sz_rest s =
127-
case s of
128-
_ | Just p <- extractHintFromSequence who env globals tops inputs sz_rest s ->
129-
Just p
130-
131-
ConsStmt _ s' rest ->
128+
extractHintFromSequence who env globals tops inputs sz_rest s >>= \case
129+
Just p -> return $ Just p
130+
_ | ConsStmt _ s' rest <- s ->
132131
let inc_rest :: forall tp. Ctx.Size (rest Ctx.::> tp)
133132
inc_rest = Ctx.incSize sz_rest in
134133
case s' of
@@ -148,8 +147,7 @@ extractStmtsHint who env globals tops inputs = loop Ctx.zeroSize
148147
DropRefCell {} -> loop sz_rest rest
149148
Assert {} -> loop sz_rest rest
150149
Assume {} -> loop sz_rest rest
151-
152-
TermStmt {} -> Nothing
150+
_ -> return Nothing
153151

154152
-- | Try to recognize the sequence of Crucible instructions leading up to
155153
-- a call to heapster.require. If found, build a hint by parsing the provided
@@ -171,8 +169,8 @@ extractHintFromSequence ::
171169
Ctx.Size rest ->
172170
-- ^ keeps track of how deep we are into the current block
173171
StmtSeq LLVM blocks ret (ctx Ctx.<+> rest) ->
174-
Maybe (SomeHintSpec tops ctx)
175-
extractHintFromSequence who env globals tops blockInputs sz s =
172+
ExtractM (Maybe (SomeHintSpec tops ctx))
173+
extractHintFromSequence who env globals tops blockIns sz s =
176174
case s of
177175
ConsStmt _ (ExtendAssign (LLVM_ResolveGlobal _ _ f))
178176
(ConsStmt _ (ExtendAssign (LLVM_ResolveGlobal _ _ ghosts))
@@ -191,20 +189,20 @@ extractHintFromSequence who env globals tops blockInputs sz s =
191189
-- "demote" the context of each reg to the block input context,
192190
-- proving that each arg is in fact defined in a previous block
193191
-- (and is thus valid for use in this spec)
194-
case sequence (toBlockArg (Ctx.size blockInputs) sizeAtCall <$> args) of
192+
case sequence (toBlockArg (Ctx.size blockIns) sizeAtCall <$> args) of
195193
Just demoted ->
196-
Just $ requireArgsToHint who env blockInputs tops demoted ghosts_str spec_str
194+
Just <$> requireArgsToHint who env blockIns tops demoted ghosts_str spec_str
197195
Nothing ->
198-
error (who ++ ": spec refers to block-defined expressions")
196+
throwError (who ++ ": spec refers to block-defined expressions")
199197

200-
_ -> Nothing
198+
_ -> return Nothing
201199

202200
where
203201
fnPtrReg :: forall a b tp. Reg (ctx Ctx.<+> rest Ctx.::> tp Ctx.::> a Ctx.::> b) tp
204-
fnPtrReg = Reg (Ctx.skipIndex (Ctx.skipIndex (Ctx.nextIndex (Ctx.addSize (Ctx.size blockInputs) sz))))
202+
fnPtrReg = Reg (Ctx.skipIndex (Ctx.skipIndex (Ctx.nextIndex (Ctx.addSize (Ctx.size blockIns) sz))))
205203

206204
fnHdlReg :: forall a b c tp. Reg ((ctx Ctx.<+> rest) Ctx.::> a Ctx.::> b Ctx.::> c Ctx.::> tp) tp
207-
fnHdlReg = Reg (Ctx.lastIndex (Ctx.addSize (Ctx.size blockInputs) sizeAtCall))
205+
fnHdlReg = Reg (Ctx.lastIndex (Ctx.addSize (Ctx.size blockIns) sizeAtCall))
208206

209207
sizeAtCall :: forall a b c d. Ctx.Size (rest Ctx.::> a Ctx.::> b Ctx.::> c Ctx.::> d)
210208
sizeAtCall = Ctx.incSize (Ctx.incSize (Ctx.incSize (Ctx.incSize sz)))
@@ -221,25 +219,28 @@ requireArgsToHint ::
221219
[Some (Reg ctx)] {-^ The actual arguments to the require, demoted to block args -} ->
222220
String {-^ The ghost ctx to parse -} ->
223221
String {-^ The permissions to parse -} ->
224-
SomeHintSpec tops ctx
225-
requireArgsToHint who env blockInputs tops args ghostString specString =
222+
ExtractM (SomeHintSpec tops ctx)
223+
requireArgsToHint who env blockIns tops args ghostString specString =
226224
case parseParsedCtxString who env ghostString of
227225
Just (Some ghost_ctx) ->
228226
let full_ctx = appendParsedCtx (appendParsedCtx top_ctx ctx_rename) ghost_ctx
229-
sub = buildHintSub blockInputs args
230-
ctx = mkArgsParsedCtx (mkCruCtx blockInputs)
227+
sub = buildHintSub blockIns args
228+
ctx = mkArgsParsedCtx (mkCruCtx blockIns)
231229
top_ctx = mkTopParsedCtx tops
232230
ctx_rename = renameParsedCtx sub ctx
233-
in maybe (error (who ++ ": error parsing ghost context"))
234-
(SomeHintSpec (parsedCtxCtx ghost_ctx))
231+
in maybe (throwError (who ++ ": error parsing permissions"))
232+
(return . SomeHintSpec (parsedCtxCtx ghost_ctx))
235233
(parsePermsString who env full_ctx specString)
234+
Nothing ->
235+
throwError (who ++ ": error parsing ghost context")
236236

237237
-- | Apply a substitution to the names in a ParsedCtx
238238
renameParsedCtx :: [(String, String)] -> ParsedCtx ctx -> ParsedCtx ctx
239239
renameParsedCtx sub ctx = ctx { parsedCtxNames = renamed }
240240
where
241-
renamed = mapRAssign (\(Constant x) -> Constant (subst x)) (parsedCtxNames ctx)
242-
subst x = fromMaybe x (lookup x sub)
241+
renamed = mapRAssign (\(Constant x) ->
242+
Constant (substNames x)) (parsedCtxNames ctx)
243+
substNames x = fromMaybe x (lookup x sub)
243244

244245
-- | Build a susbstitution to apply to block arguments based on the actual arguments
245246
-- provided to a `requires` call, i.e. given
@@ -297,4 +298,4 @@ someRegName :: Some (Reg ctx) -> String
297298
someRegName (Some (Reg i)) = argNamei (Ctx.indexVal i)
298299

299300
argNamei :: Int -> String
300-
argNamei i = "arg" ++ show i
301+
argNamei i = "arg" ++ show i

src/SAWScript/HeapsterBuiltins.hs

+3-1
Original file line numberDiff line numberDiff line change
@@ -1150,7 +1150,9 @@ heapster_typecheck_mut_funs_rename _bic _opts henv fn_names_and_perms =
11501150
withKnownNat w $
11511151
parseFunPermStringMaybeRust "permissions" w env args ret perms_string
11521152
let mods = [ modAST m | Some m <- heapsterEnvLLVMModules henv ]
1153-
let hints = extractHints env mods fun_perm cfg
1153+
hints <- case extractHints env mods fun_perm cfg of
1154+
Left err -> fail ("Error parsing LLVM-level hints: " ++ err)
1155+
Right hints -> return hints
11541156
let env' = foldlFC (\e h -> maybe e (permEnvAddHint e) (getConstant h))
11551157
env
11561158
hints

0 commit comments

Comments
 (0)