Skip to content

Commit cfaba80

Browse files
authored
Merge pull request #2121 from GaloisInc/2120-function-arrays
Don't fail when What4 sends us a function-based array in a result.
2 parents 2684385 + d489ee3 commit cfaba80

File tree

3 files changed

+85
-10
lines changed

3 files changed

+85
-10
lines changed

saw-core-what4/src/Verifier/SAW/Simulator/What4/FirstOrder.hs

+26-4
Original file line numberDiff line numberDiff line change
@@ -114,10 +114,32 @@ groundToFOV BaseRealRepr _ = Left "Real is not FOV"
114114
groundToFOV BaseComplexRepr _ = Left "Complex is not FOV"
115115
groundToFOV (BaseStringRepr _) _ = Left "String is not FOV"
116116
groundToFOV (BaseFloatRepr _) _ = Left "Floating point is not FOV"
117-
groundToFOV (BaseArrayRepr _ _) (ArrayMapping _) =
118-
-- We don't have a way to represent ArrayMapping in FirstOrderValue
119-
-- (see note in FiniteValue.hs where FirstOrderValue's defined)
120-
Left "Unsupported FOV Array (values only available by lookup)"
117+
groundToFOV (BaseArrayRepr (Empty :> ty_idx) ty_val) (ArrayMapping _) = do
118+
-- ArrayMapping is an array represented as a function call we can
119+
-- use to extract values. We can't do anything useful with this
120+
-- because we don't have any clue what key values to look at and
121+
-- no good way to figure that out either. So return a placeholder
122+
-- value in FirstOrderValue.
123+
--
124+
-- (The frustrating part is that in many cases the _user_ will
125+
-- know what key values to look at, but has no way to tell us.)
126+
--
127+
-- In principle we could change groundToFOV to return any of an
128+
-- error, a FirstOrderValue, or a separate FunctionArrayValue
129+
-- type, and use that channel to return the actual function
130+
-- handle. (Including the function handle in a FirstOrderValue
131+
-- value is problematic as things stand.) However, there's nothing
132+
-- to be gained by doing this without a way to figure out what
133+
-- key values to look at. And realistically, if we ever _do_
134+
-- come up with a way to figure out what key values to look at,
135+
-- it should be implemented in What4 so What4 never returns
136+
-- ArrayMapping.
137+
--
138+
-- (See Note [FOVArray] in in saw-core:Verifier.SAW.FiniteValue
139+
-- where FirstOrderValue is defined.)
140+
ty_idx' <- typeReprToFOT ty_idx
141+
ty_val' <- typeReprToFOT ty_val
142+
pure $ FOVOpaqueArray ty_idx' ty_val'
121143
groundToFOV (BaseArrayRepr (Empty :> ty_idx) ty_val) (ArrayConcrete dfl values) = do
122144
ty_idx' <- typeReprToFOT ty_idx
123145
dfl' <- groundToFOV ty_val dfl

saw-core/src/Verifier/SAW/FiniteValue.hs

+57-5
Original file line numberDiff line numberDiff line change
@@ -78,13 +78,20 @@ data FirstOrderType
7878
-- The type argument of FOVArray is the key type; the value type is
7979
-- derivable from the default value, which is the second argument. The third
8080
-- argument is an assignment for all the entries that have non-default values.
81+
--
82+
-- FOVOpaqueArray is for arrays we get back from the solver only as a
83+
-- function call that one can use for lookups. We can't do anything
84+
-- with that (see Note [FOVArray] below) so we just treat it as an
85+
-- opaque blob. The arguments are the key and value types, since we
86+
-- do at least have that info.
8187
data FirstOrderValue
8288
= FOVBit Bool
8389
| FOVInt Integer
8490
| FOVIntMod Natural Integer
8591
| FOVWord Natural Integer -- ^ a more efficient special case for 'FOVVec FOTBit _'.
8692
| FOVVec FirstOrderType [FirstOrderValue]
8793
| FOVArray FirstOrderType FirstOrderValue (Map FirstOrderValue FirstOrderValue)
94+
| FOVOpaqueArray FirstOrderType FirstOrderType
8895
| FOVTuple [FirstOrderValue]
8996
| FOVRec (Map FieldName FirstOrderValue)
9097
deriving (Eq, Ord, Generic)
@@ -107,11 +114,49 @@ data FirstOrderValue
107114
-- clear how we'd use this, since the primary thing we do with array
108115
-- values that come back from the solver is print them as part of
109116
-- models and without a way to know what keys are present a function
110-
-- that just extracts values is fairly useless. For the moment, if one
111-
-- of these pops up, it fails during conversion to FOVArray.
112-
--
113-
-- Furthermore, restrictions in What4 mean that array values coming
114-
-- back from the solver via that interface are indexed only by
117+
-- that just extracts values is fairly useless. If one of these pops
118+
-- up, it comes back as FOVOpaqueArray and we treat it as an opaque
119+
-- blob. Unfortuately this does happen (maybe we can improve What4 so
120+
-- it happens less or maybe not at all, but that's not happening right
121+
-- away) so we need to be able to handle it rather than erroring out
122+
-- or crashing.
123+
--
124+
-- Note that trying to retain the function at this level is
125+
-- problematic for a number of reasons:
126+
--
127+
-- 1. It's not actually a first-order value, and calling it one is
128+
-- borrowing trouble.
129+
--
130+
-- 2. We need ToJSON and FromJSON instances for solver caching, and
131+
-- there's no way to do that. Now, trying to stick one of these
132+
-- objects in the solver cache is just not going to work no
133+
-- matter how we handle it; but things are not structured so
134+
-- that we can e.g. decline to cache values that contain
135+
-- function-based arrays so that it's safe to stub out the
136+
-- ToJSON and FromJSON instances with an error invocation. That
137+
-- could doubtless be arranged, but it'll take work, possibly a
138+
-- lot of work. As things stand, we _can_ stuff FOVOpaqueArray
139+
-- into the solver cache, and it won't do anything useful when
140+
-- we unstuff it later, but it won't crash.
141+
--
142+
-- 3. FirstOrderValue needs Eq and Ord instances, at least but not
143+
-- necessarily only for use by maps. At least one of those maps
144+
-- (the one used in FOVArray) is restricted to not have array
145+
-- values as keys; however, that's not an _explicit_ restriction
146+
-- (e.g. in typechecking), it's a consequence of the things
147+
-- What4 allows as array keys. To be halfway safe we'd need to
148+
-- make it an explicit restriction, and in the current state of
149+
-- SAW maintenance it's not really clear enough where we'd need
150+
-- to enforce that to keep it safe. Also, there may be other
151+
-- such maps about where arrays _can_ be keys, or for that
152+
-- matter other comparisons. In principle you could have the
153+
-- compiler find you all the uses by disabling the Eq and Ord
154+
-- instances. But that doesn't work because the ToJSON and
155+
-- FromJSON classes need them. The compiler then just fails on
156+
-- those before telling you anything else.
157+
--
158+
-- Besides all the above, restrictions in What4 mean that array values
159+
-- coming back from the solver via that interface are indexed only by
115160
-- integers or bitvectors. At this layer, though, we can support any
116161
-- FirstOrderValue.
117162
--
@@ -159,6 +204,8 @@ instance Show FirstOrderValue where
159204
d' = showEntry ("<default>", d)
160205
in
161206
showString "[" . commaSep (vs' ++ [d']) . showString "]"
207+
FOVOpaqueArray _kty _vty ->
208+
showString "[ opaque array, sorry ]"
162209
FOVTuple vs -> showString "(" . commaSep (map shows vs) . showString ")"
163210
FOVRec vm -> showString "{" . commaSep (map showField (Map.assocs vm)) . showString "}"
164211
where
@@ -187,6 +234,8 @@ ppFirstOrderValue opts = loop
187234
vs' = map ppEntry $ Map.toAscList vs
188235
in
189236
brackets (nest 4 (sep (punctuate comma (vs' ++ [d']))))
237+
FOVOpaqueArray _kty _vty ->
238+
pretty "[ opaque array, sorry ]"
190239
FOVTuple xs -> parens (nest 4 (sep (punctuate comma (map loop xs))))
191240
FOVRec xs -> braces (sep (punctuate comma (map ppField (Map.toList xs))))
192241
where ppField (f,x) = pretty f <+> pretty '=' <+> loop x
@@ -264,6 +313,7 @@ firstOrderTypeOf fv =
264313
FOVWord n _ -> FOTVec n FOTBit
265314
FOVVec t vs -> FOTVec (fromIntegral (length vs)) t
266315
FOVArray tk d _vs -> FOTArray tk (firstOrderTypeOf d)
316+
FOVOpaqueArray tk tv -> FOTArray tk tv
267317
FOVTuple vs -> FOTTuple (map firstOrderTypeOf vs)
268318
FOVRec vm -> FOTRec (fmap firstOrderTypeOf vm)
269319

@@ -391,6 +441,8 @@ scFirstOrderValue sc fv =
391441
v' <- scFirstOrderValue sc v
392442
scArrayUpdate sc tk' tv' arr k' v'
393443
ifoldrM visit arr0 vs
444+
FOVOpaqueArray _tk _tv -> do
445+
fail "Cannot convert opaque array to SharedTerm"
394446
FOVTuple vs -> scTuple sc =<< traverse (scFirstOrderValue sc) vs
395447
FOVRec vm -> scRecord sc =<< traverse (scFirstOrderValue sc) vm
396448

saw-remote-api/src/SAWServer/ProofScript.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -231,7 +231,8 @@ exportFirstOrderExpression fv =
231231
FOVIntMod m i -> return $ IntegerModulo i (toInteger m)
232232
FOVWord w x -> return $ Num Hex (pack (showHex x "")) (toInteger w)
233233
FOVVec _t vs -> Sequence <$> mapM exportFirstOrderExpression vs
234-
FOVArray{} -> Left "exportFirstOrderExpression: unsupported type: Array"
234+
FOVArray{} -> Left "exportFirstOrderExpression: unsupported type: Array (concrete case)"
235+
FOVOpaqueArray{} -> Left "exportFirstOrderExpression: unsupported type: Array (opaque case)"
235236
FOVTuple vs -> Tuple <$> mapM exportFirstOrderExpression vs
236237
FOVRec _vm -> Left "exportFirstOrderExpression: unsupported type: Record"
237238

0 commit comments

Comments
 (0)