Skip to content

Commit b2fd263

Browse files
author
Brian Huffman
committed
Update saw-core submodule and adapt to GaloisInc/saw-core#93.
The What4 prover interface now uses `getLabelValues` from the saw-core-what4 package.
1 parent 918a7d2 commit b2fd263

File tree

2 files changed

+2
-26
lines changed

2 files changed

+2
-26
lines changed

src/SAWScript/Prover/What4.hs

+1-25
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ module SAWScript.Prover.What4 where
88

99
import System.IO
1010

11-
import qualified Data.Vector as V
1211
import Control.Monad(filterM)
1312
import Data.Maybe (catMaybes)
1413

@@ -187,33 +186,10 @@ getValues :: forall sym gt. (SymExpr sym ~ B.Expr gt) => GroundEvalFn gt ->
187186
(Maybe (W.Labeler sym), String) -> IO (Maybe (String, FirstOrderValue))
188187
getValues _ (Nothing, _) = return Nothing
189188
getValues f (Just labeler, orig) = do
190-
fov <- getLabelValues f labeler
189+
fov <- W.getLabelValues f labeler
191190
return $ Just (orig,fov)
192191

193192

194-
getLabelValues :: forall sym gt. (SymExpr sym ~ B.Expr gt) => GroundEvalFn gt ->
195-
W.Labeler sym -> IO FirstOrderValue
196-
197-
getLabelValues f (W.TupleLabel labels) = do
198-
vals <- mapM (getLabelValues f) (V.toList labels)
199-
return (FOVTuple vals)
200-
201-
getLabelValues f (W.VecLabel labels) = do
202-
let vty = error "TODO: compute vector type, or just store it"
203-
vals <- mapM (getLabelValues f) (V.toList labels)
204-
return (FOVVec vty vals)
205-
206-
getLabelValues f (W.RecLabel m) = do
207-
m' <- mapM (getLabelValues f) m
208-
return (FOVRec m')
209-
210-
getLabelValues f (W.BaseLabel (W.TypedExpr ty bv)) = do
211-
gv <- groundEval f bv
212-
case (groundToFOV ty gv) of
213-
Left err -> fail err
214-
Right fov -> return fov
215-
216-
217193
-- | For debugging
218194
printValue :: (B.ExprBuilder t st ff) -> GroundEvalFn t ->
219195
(Maybe (W.TypedExpr (B.ExprBuilder t st ff)), String) -> IO ()

0 commit comments

Comments
 (0)