5
5
{-# Language ScopedTypeVariables #-}
6
6
{-# LANGUAGE GADTs #-}
7
7
{-# LANGUAGE ParallelListComp #-}
8
+ {-# LANGUAGE LambdaCase #-}
8
9
9
10
module Verifier.SAW.Heapster.HintExtract ( heapsterRequireName , extractHints ) where
10
11
11
- import Control.Applicative ((<|>) )
12
12
import Data.String (fromString )
13
13
import Data.Functor.Constant (Constant (.. ))
14
14
import Control.Lens ((^.) )
15
+ import Control.Monad.Except
15
16
import Data.Maybe (fromMaybe , maybeToList )
16
17
import qualified Data.Map as Map
17
18
import Data.Char (chr )
18
19
import Text.LLVM.AST as L
19
20
20
- import Data.Binding.Hobbits (RAssign ((:>:) ))
21
- import Data.Type.RList (mapRAssign , type (:++: ), RAssign (MNil ))
22
21
import Data.Parameterized (toListFC , fmapFC , (:~:) (.. ), testEquality )
23
22
import qualified Data.Parameterized.Context as Ctx
23
+ import Data.Parameterized.TraversableFC (traverseFC )
24
24
25
+ import Data.Type.RList (mapRAssign , (:++:) )
25
26
import Lang.Crucible.LLVM.Extension ( LLVM , LLVMStmt (.. ))
26
27
import Lang.Crucible.CFG.Core ( Some (Some )
27
28
, CtxRepr
@@ -33,14 +34,17 @@ import Lang.Crucible.CFG.Core ( Some(Some)
33
34
, StmtSeq (.. )
34
35
, Stmt (.. ), BlockID )
35
36
36
- import Verifier.SAW.Heapster.CruUtil ( globalSymbolName , mkCruCtx , CruCtx ( .. ), CtxToRList , cruCtxLen )
37
+ import Verifier.SAW.Heapster.CruUtil
37
38
import Verifier.SAW.Heapster.ParsedCtx
38
- import Verifier.SAW.Heapster.Permissions ( PermEnv , Hint ( .. ), BlockHintSort ( .. ), BlockHint ( .. ), MbValuePerms , funPermTops , FunPerm )
39
+ import Verifier.SAW.Heapster.Permissions
39
40
import Verifier.SAW.Heapster.PermParser
40
41
41
42
heapsterRequireName :: String
42
43
heapsterRequireName = " heapster.require"
43
44
45
+ -- | The monad we use for extracting hints, which just has 'String' errors
46
+ type ExtractM = Except String
47
+
44
48
-- | Extract block hints from calls to `heapster.require` in the Crucible CFG.
45
49
extractHints ::
46
50
forall ghosts args outs blocks init ret .
@@ -51,34 +55,29 @@ extractHints ::
51
55
-- ^ The FunPerm corresponding to the CFG we are scanning
52
56
CFG LLVM blocks init ret ->
53
57
-- ^ 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)
56
61
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 ]
65
68
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
82
81
83
82
-- | Packs up the ghosts in a parsed hint permission spec
84
83
data SomeHintSpec tops ctx where
@@ -96,14 +95,16 @@ extractBlockHints ::
96
95
CruCtx tops ->
97
96
-- ^ top context derived from current function's perm
98
97
Block LLVM blocks ret ctx ->
99
- Constant (Maybe (SomeHintSpec tops ctx )) blocks
98
+ ExtractM (Maybe (SomeHintSpec tops ctx ))
100
99
extractBlockHints env globals tops block =
101
- Constant $ extractStmtsHint who env globals tops inputs stmts
100
+ extractStmtsHint who env globals tops inputs stmts
102
101
where
103
102
stmts = block ^. blockStmts
104
103
inputs = blockInputs block
105
104
who = show (blockID block)
106
105
106
+ -- | Test if a sequence of statements starts with the Crucible representation of
107
+ -- a call to the dummy function @heapster.require@
107
108
extractStmtsHint ::
108
109
forall blocks ret ctx tops .
109
110
String ->
@@ -115,20 +116,18 @@ extractStmtsHint ::
115
116
CtxRepr ctx ->
116
117
-- ^ block arguments
117
118
StmtSeq LLVM blocks ret ctx ->
118
- Maybe (SomeHintSpec tops ctx )
119
+ ExtractM ( Maybe (SomeHintSpec tops ctx ) )
119
120
extractStmtsHint who env globals tops inputs = loop Ctx. zeroSize
120
121
where
121
122
loop ::
122
123
forall rest .
123
124
Ctx. Size rest ->
124
125
StmtSeq LLVM blocks ret (ctx Ctx. <+> rest ) ->
125
- Maybe (SomeHintSpec tops ctx )
126
+ ExtractM ( Maybe (SomeHintSpec tops ctx ) )
126
127
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 ->
132
131
let inc_rest :: forall tp . Ctx. Size (rest Ctx. ::> tp )
133
132
inc_rest = Ctx. incSize sz_rest in
134
133
case s' of
@@ -148,8 +147,7 @@ extractStmtsHint who env globals tops inputs = loop Ctx.zeroSize
148
147
DropRefCell {} -> loop sz_rest rest
149
148
Assert {} -> loop sz_rest rest
150
149
Assume {} -> loop sz_rest rest
151
-
152
- TermStmt {} -> Nothing
150
+ _ -> return Nothing
153
151
154
152
-- | Try to recognize the sequence of Crucible instructions leading up to
155
153
-- a call to heapster.require. If found, build a hint by parsing the provided
@@ -171,8 +169,8 @@ extractHintFromSequence ::
171
169
Ctx. Size rest ->
172
170
-- ^ keeps track of how deep we are into the current block
173
171
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 =
176
174
case s of
177
175
ConsStmt _ (ExtendAssign (LLVM_ResolveGlobal _ _ f))
178
176
(ConsStmt _ (ExtendAssign (LLVM_ResolveGlobal _ _ ghosts))
@@ -191,20 +189,20 @@ extractHintFromSequence who env globals tops blockInputs sz s =
191
189
-- "demote" the context of each reg to the block input context,
192
190
-- proving that each arg is in fact defined in a previous block
193
191
-- (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
195
193
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
197
195
Nothing ->
198
- error (who ++ " : spec refers to block-defined expressions" )
196
+ throwError (who ++ " : spec refers to block-defined expressions" )
199
197
200
- _ -> Nothing
198
+ _ -> return Nothing
201
199
202
200
where
203
201
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))))
205
203
206
204
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))
208
206
209
207
sizeAtCall :: forall a b c d . Ctx. Size (rest Ctx. ::> a Ctx. ::> b Ctx. ::> c Ctx. ::> d )
210
208
sizeAtCall = Ctx. incSize (Ctx. incSize (Ctx. incSize (Ctx. incSize sz)))
@@ -221,25 +219,28 @@ requireArgsToHint ::
221
219
[Some (Reg ctx )] {-^ The actual arguments to the require, demoted to block args -} ->
222
220
String {-^ The ghost ctx to parse -} ->
223
221
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 =
226
224
case parseParsedCtxString who env ghostString of
227
225
Just (Some ghost_ctx) ->
228
226
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 )
231
229
top_ctx = mkTopParsedCtx tops
232
230
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))
235
233
(parsePermsString who env full_ctx specString)
234
+ Nothing ->
235
+ throwError (who ++ " : error parsing ghost context" )
236
236
237
237
-- | Apply a substitution to the names in a ParsedCtx
238
238
renameParsedCtx :: [(String , String )] -> ParsedCtx ctx -> ParsedCtx ctx
239
239
renameParsedCtx sub ctx = ctx { parsedCtxNames = renamed }
240
240
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)
243
244
244
245
-- | Build a susbstitution to apply to block arguments based on the actual arguments
245
246
-- provided to a `requires` call, i.e. given
@@ -297,4 +298,4 @@ someRegName :: Some (Reg ctx) -> String
297
298
someRegName (Some (Reg i)) = argNamei (Ctx. indexVal i)
298
299
299
300
argNamei :: Int -> String
300
- argNamei i = " arg" ++ show i
301
+ argNamei i = " arg" ++ show i
0 commit comments