{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
module Cryptol.Eval.What4
( Value
, primTable
, floatPrims
) where
import qualified Control.Exception as X
import Control.Concurrent.MVar
import Control.Monad (join,foldM)
import Control.Monad.IO.Class
import Data.Bits
import qualified Data.Map as Map
import Data.Map (Map)
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Parameterized.Context
import Data.Parameterized.Some
import Data.Parameterized.TraversableFC
import qualified Data.BitVector.Sized as BV
import qualified What4.Interface as W4
import qualified What4.SWord as SW
import qualified What4.Utils.AbstractDomains as W4
import Cryptol.Backend
import Cryptol.Backend.Monad ( EvalError(..), Unsupported(..) )
import Cryptol.Backend.What4
import qualified Cryptol.Backend.What4.SFloat as W4
import Cryptol.Eval.Generic
import Cryptol.Eval.Type (finNat', TValue(..))
import Cryptol.Eval.Value
import qualified Cryptol.SHA as SHA
import Cryptol.TypeCheck.Solver.InfNat( Nat'(..), widthInteger )
import Cryptol.Utils.Ident
import Cryptol.Utils.Panic
import Cryptol.Utils.RecordMap
type Value sym = GenValue (What4 sym)
primTable :: W4.IsSymExprBuilder sym => What4 sym -> Map.Map PrimIdent (Value sym)
primTable :: What4 sym -> Map PrimIdent (Value sym)
primTable What4 sym
sym =
let w4sym :: sym
w4sym = What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym in
Map PrimIdent (Value sym)
-> Map PrimIdent (Value sym) -> Map PrimIdent (Value sym)
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (What4 sym -> Map PrimIdent (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym -> Map PrimIdent (Value sym)
floatPrims What4 sym
sym) (Map PrimIdent (Value sym) -> Map PrimIdent (Value sym))
-> Map PrimIdent (Value sym) -> Map PrimIdent (Value sym)
forall a b. (a -> b) -> a -> b
$
Map PrimIdent (Value sym)
-> Map PrimIdent (Value sym) -> Map PrimIdent (Value sym)
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (What4 sym -> Map PrimIdent (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym -> Map PrimIdent (Value sym)
suiteBPrims What4 sym
sym) (Map PrimIdent (Value sym) -> Map PrimIdent (Value sym))
-> Map PrimIdent (Value sym) -> Map PrimIdent (Value sym)
forall a b. (a -> b) -> a -> b
$
Map PrimIdent (Value sym)
-> Map PrimIdent (Value sym) -> Map PrimIdent (Value sym)
forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union (What4 sym -> Map PrimIdent (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym -> Map PrimIdent (Value sym)
primeECPrims What4 sym
sym) (Map PrimIdent (Value sym) -> Map PrimIdent (Value sym))
-> Map PrimIdent (Value sym) -> Map PrimIdent (Value sym)
forall a b. (a -> b) -> a -> b
$
[(PrimIdent, Value sym)] -> Map PrimIdent (Value sym)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(PrimIdent, Value sym)] -> Map PrimIdent (Value sym))
-> [(PrimIdent, Value sym)] -> Map PrimIdent (Value sym)
forall a b. (a -> b) -> a -> b
$ ((Text, Value sym) -> (PrimIdent, Value sym))
-> [(Text, Value sym)] -> [(PrimIdent, Value sym)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Text
n, Value sym
v) -> (Text -> PrimIdent
prelPrim Text
n, Value sym
v))
[
(Text
"True" , SBit (What4 sym) -> Value sym
forall sym. SBit sym -> GenValue sym
VBit (What4 sym -> Bool -> SBit (What4 sym)
forall sym. Backend sym => sym -> Bool -> SBit sym
bitLit What4 sym
sym Bool
True))
, (Text
"False" , SBit (What4 sym) -> Value sym
forall sym. SBit sym -> GenValue sym
VBit (What4 sym -> Bool -> SBit (What4 sym)
forall sym. Backend sym => sym -> Bool -> SBit sym
bitLit What4 sym
sym Bool
False))
, (Text
"number" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
ecNumberV What4 sym
sym)
, (Text
"fraction" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
ecFractionV What4 sym
sym)
, (Text
"ratio" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
ratioV What4 sym
sym)
, (Text
"zero" , (TValue -> SEval (What4 sym) (Value sym)) -> Value sym
forall sym. (TValue -> SEval sym (GenValue sym)) -> GenValue sym
VPoly (What4 sym -> TValue -> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym -> TValue -> SEval sym (GenValue sym)
zeroV What4 sym
sym))
, (Text
"&&" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
andV What4 sym
sym))
, (Text
"||" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
orV What4 sym
sym))
, (Text
"^" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
xorV What4 sym
sym))
, (Text
"complement" , Unary (What4 sym) -> Value sym
forall sym. Backend sym => Unary sym -> GenValue sym
unary (What4 sym -> Unary (What4 sym)
forall sym. Backend sym => sym -> Unary sym
complementV What4 sym
sym))
, (Text
"fromInteger" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
fromIntegerV What4 sym
sym)
, (Text
"+" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
addV What4 sym
sym))
, (Text
"-" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
subV What4 sym
sym))
, (Text
"negate" , Unary (What4 sym) -> Value sym
forall sym. Backend sym => Unary sym -> GenValue sym
unary (What4 sym -> Unary (What4 sym)
forall sym. Backend sym => sym -> Unary sym
negateV What4 sym
sym))
, (Text
"*" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
mulV What4 sym
sym))
, (Text
"toInteger" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
toIntegerV What4 sym
sym)
, (Text
"/" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
divV What4 sym
sym))
, (Text
"%" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
modV What4 sym
sym))
, (Text
"^^" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
expV What4 sym
sym)
, (Text
"infFrom" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
infFromV What4 sym
sym)
, (Text
"infFromThen" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
infFromThenV What4 sym
sym)
, (Text
"recip" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
recipV What4 sym
sym)
, (Text
"/." , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
fieldDivideV What4 sym
sym)
, (Text
"floor" , Unary (What4 sym) -> Value sym
forall sym. Backend sym => Unary sym -> GenValue sym
unary (What4 sym -> Unary (What4 sym)
forall sym. Backend sym => sym -> Unary sym
floorV What4 sym
sym))
, (Text
"ceiling" , Unary (What4 sym) -> Value sym
forall sym. Backend sym => Unary sym -> GenValue sym
unary (What4 sym -> Unary (What4 sym)
forall sym. Backend sym => sym -> Unary sym
ceilingV What4 sym
sym))
, (Text
"trunc" , Unary (What4 sym) -> Value sym
forall sym. Backend sym => Unary sym -> GenValue sym
unary (What4 sym -> Unary (What4 sym)
forall sym. Backend sym => sym -> Unary sym
truncV What4 sym
sym))
, (Text
"roundAway" , Unary (What4 sym) -> Value sym
forall sym. Backend sym => Unary sym -> GenValue sym
unary (What4 sym -> Unary (What4 sym)
forall sym. Backend sym => sym -> Unary sym
roundAwayV What4 sym
sym))
, (Text
"roundToEven" , Unary (What4 sym) -> Value sym
forall sym. Backend sym => Unary sym -> GenValue sym
unary (What4 sym -> Unary (What4 sym)
forall sym. Backend sym => sym -> Unary sym
roundToEvenV What4 sym
sym))
, (Text
"/$" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
sdivV What4 sym
sym)
, (Text
"%$" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
smodV What4 sym
sym)
, (Text
"lg2" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
lg2V What4 sym
sym)
, (Text
">>$" , What4 sym -> Value sym
forall sym. IsSymExprBuilder sym => What4 sym -> Value sym
sshrV What4 sym
sym)
, (Text
"<" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
lessThanV What4 sym
sym))
, (Text
">" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
greaterThanV What4 sym
sym))
, (Text
"<=" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
lessThanEqV What4 sym
sym))
, (Text
">=" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
greaterThanEqV What4 sym
sym))
, (Text
"==" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
eqV What4 sym
sym))
, (Text
"!=" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
distinctV What4 sym
sym))
, (Text
"<$" , Binary (What4 sym) -> Value sym
forall sym. Backend sym => Binary sym -> GenValue sym
binary (What4 sym -> Binary (What4 sym)
forall sym. Backend sym => sym -> Binary sym
signedLessThanV What4 sym
sym))
, (Text
"fromTo" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
fromToV What4 sym
sym)
, (Text
"fromThenTo" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
fromThenToV What4 sym
sym)
, (Text
"#" ,
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \ Nat'
front ->
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \ Nat'
back ->
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \ TValue
elty ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \ SEval (What4 sym) (Value sym)
l -> Value sym -> W4Eval sym (Value sym)
forall (m :: * -> *) a. Monad m => a -> m a
return (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \ SEval (What4 sym) (Value sym)
r -> W4Eval sym (W4Eval sym (Value sym)) -> W4Eval sym (Value sym)
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (What4 sym -> Nat' -> Nat' -> Binary (What4 sym)
forall sym.
Backend sym =>
sym
-> Nat'
-> Nat'
-> TValue
-> GenValue sym
-> GenValue sym
-> SEval sym (GenValue sym)
ccatV What4 sym
sym Nat'
front Nat'
back TValue
elty (Value sym -> Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym)
-> W4Eval sym (Value sym -> W4Eval sym (Value sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
l W4Eval sym (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (W4Eval sym (Value sym))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
r))
, (Text
"join" ,
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \ Nat'
parts ->
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \ (Nat' -> Integer
finNat' -> Integer
each) ->
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \ TValue
a ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \ SEval (What4 sym) (Value sym)
x ->
What4 sym -> Nat' -> Integer -> Unary (What4 sym)
forall sym.
Backend sym =>
sym
-> Nat'
-> Integer
-> TValue
-> GenValue sym
-> SEval sym (GenValue sym)
joinV What4 sym
sym Nat'
parts Integer
each TValue
a (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
x)
, (Text
"split" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
ecSplitV What4 sym
sym)
, (Text
"splitAt" ,
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \ Nat'
front ->
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \ Nat'
back ->
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \ TValue
a ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \ SEval (What4 sym) (Value sym)
x ->
What4 sym -> Nat' -> Nat' -> Unary (What4 sym)
forall sym.
Backend sym =>
sym
-> Nat'
-> Nat'
-> TValue
-> GenValue sym
-> SEval sym (GenValue sym)
splitAtV What4 sym
sym Nat'
front Nat'
back TValue
a (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
x)
, (Text
"reverse" , (Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \Nat'
_a ->
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \TValue
_b ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SEval (What4 sym) (Value sym)
xs -> What4 sym -> Value sym -> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym -> GenValue sym -> SEval sym (GenValue sym)
reverseV What4 sym
sym (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
xs)
, (Text
"transpose" , (Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \Nat'
a ->
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \Nat'
b ->
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \TValue
c ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SEval (What4 sym) (Value sym)
xs -> What4 sym -> Nat' -> Nat' -> Unary (What4 sym)
forall sym.
Backend sym =>
sym
-> Nat'
-> Nat'
-> TValue
-> GenValue sym
-> SEval sym (GenValue sym)
transposeV What4 sym
sym Nat'
a Nat'
b TValue
c (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
xs)
, (Text
"<<" , What4 sym
-> String
-> (What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym)))
-> (SWord (What4 sym)
-> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)))
-> (SWord (What4 sym)
-> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)))
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> Value sym
forall sym.
Backend sym =>
sym
-> String
-> (sym
-> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym))
-> (SWord sym -> SWord sym -> SEval sym (SWord sym))
-> (SWord sym -> SWord sym -> SEval sym (SWord sym))
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> GenValue sym
logicShift What4 sym
sym String
"<<" What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym)
shiftShrink
(sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvShl sym
w4sym) (sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvLshr sym
w4sym)
Nat' -> Integer -> Integer -> Maybe Integer
shiftLeftReindex Nat' -> Integer -> Integer -> Maybe Integer
shiftRightReindex)
, (Text
">>" , What4 sym
-> String
-> (What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym)))
-> (SWord (What4 sym)
-> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)))
-> (SWord (What4 sym)
-> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)))
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> Value sym
forall sym.
Backend sym =>
sym
-> String
-> (sym
-> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym))
-> (SWord sym -> SWord sym -> SEval sym (SWord sym))
-> (SWord sym -> SWord sym -> SEval sym (SWord sym))
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> GenValue sym
logicShift What4 sym
sym String
">>" What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym)
shiftShrink
(sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvLshr sym
w4sym) (sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvShl sym
w4sym)
Nat' -> Integer -> Integer -> Maybe Integer
shiftRightReindex Nat' -> Integer -> Integer -> Maybe Integer
shiftLeftReindex)
, (Text
"<<<" , What4 sym
-> String
-> (What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym)))
-> (SWord (What4 sym)
-> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)))
-> (SWord (What4 sym)
-> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)))
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> Value sym
forall sym.
Backend sym =>
sym
-> String
-> (sym
-> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym))
-> (SWord sym -> SWord sym -> SEval sym (SWord sym))
-> (SWord sym -> SWord sym -> SEval sym (SWord sym))
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> GenValue sym
logicShift What4 sym
sym String
"<<<" What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym)
rotateShrink
(sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvRol sym
w4sym) (sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvRor sym
w4sym)
Nat' -> Integer -> Integer -> Maybe Integer
rotateLeftReindex Nat' -> Integer -> Integer -> Maybe Integer
rotateRightReindex)
, (Text
">>>" , What4 sym
-> String
-> (What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym)))
-> (SWord (What4 sym)
-> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)))
-> (SWord (What4 sym)
-> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)))
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> Value sym
forall sym.
Backend sym =>
sym
-> String
-> (sym
-> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym))
-> (SWord sym -> SWord sym -> SEval sym (SWord sym))
-> (SWord sym -> SWord sym -> SEval sym (SWord sym))
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> (Nat' -> Integer -> Integer -> Maybe Integer)
-> GenValue sym
logicShift What4 sym
sym String
">>>" What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym)
rotateShrink
(sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvRor sym
w4sym) (sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvRol sym
w4sym)
Nat' -> Integer -> Integer -> Maybe Integer
rotateRightReindex Nat' -> Integer -> Integer -> Maybe Integer
rotateLeftReindex)
, (Text
"@" , What4 sym
-> (Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym))
-> (Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym))
-> (Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
Backend sym =>
sym
-> (Nat'
-> TValue
-> SeqMap sym
-> TValue
-> SInteger sym
-> SEval sym (GenValue sym))
-> (Nat'
-> TValue
-> SeqMap sym
-> TValue
-> [SBit sym]
-> SEval sym (GenValue sym))
-> (Nat'
-> TValue
-> SeqMap sym
-> TValue
-> SWord sym
-> SEval sym (GenValue sym))
-> GenValue sym
indexPrim What4 sym
sym (What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym)
indexFront_int What4 sym
sym) (What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym)
indexFront_bits What4 sym
sym) (What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym)
indexFront_word What4 sym
sym))
, (Text
"!" , What4 sym
-> (Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym))
-> (Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym))
-> (Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
Backend sym =>
sym
-> (Nat'
-> TValue
-> SeqMap sym
-> TValue
-> SInteger sym
-> SEval sym (GenValue sym))
-> (Nat'
-> TValue
-> SeqMap sym
-> TValue
-> [SBit sym]
-> SEval sym (GenValue sym))
-> (Nat'
-> TValue
-> SeqMap sym
-> TValue
-> SWord sym
-> SEval sym (GenValue sym))
-> GenValue sym
indexPrim What4 sym
sym (What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym)
indexBack_int What4 sym
sym) (What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym)
indexBack_bits What4 sym
sym) (What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym)
indexBack_word What4 sym
sym))
, (Text
"update" , What4 sym
-> (Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (WordValue (What4 sym)))
-> (Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym)))
-> Value sym
forall sym.
Backend sym =>
sym
-> (Nat'
-> TValue
-> WordValue sym
-> Either (SInteger sym) (WordValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (WordValue sym))
-> (Nat'
-> TValue
-> SeqMap sym
-> Either (SInteger sym) (WordValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (SeqMap sym))
-> GenValue sym
updatePrim What4 sym
sym (What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (WordValue (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
updateFrontSym_word What4 sym
sym) (What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
updateFrontSym What4 sym
sym))
, (Text
"updateEnd" , What4 sym
-> (Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (WordValue (What4 sym)))
-> (Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym)))
-> Value sym
forall sym.
Backend sym =>
sym
-> (Nat'
-> TValue
-> WordValue sym
-> Either (SInteger sym) (WordValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (WordValue sym))
-> (Nat'
-> TValue
-> SeqMap sym
-> Either (SInteger sym) (WordValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (SeqMap sym))
-> GenValue sym
updatePrim What4 sym
sym (What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (WordValue (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
updateBackSym_word What4 sym
sym) (What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
updateBackSym What4 sym
sym))
, (Text
"foldl" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
foldlV What4 sym
sym)
, (Text
"foldl'" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
foldl'V What4 sym
sym)
, (Text
"deepseq" ,
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \TValue
_a ->
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \TValue
_b ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SEval (What4 sym) (Value sym)
x -> Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SEval (What4 sym) (Value sym)
y ->
do ()
_ <- Value sym -> W4Eval sym ()
forall sym. Backend sym => GenValue sym -> SEval sym ()
forceValue (Value sym -> W4Eval sym ())
-> W4Eval sym (Value sym) -> W4Eval sym ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
x
SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
y)
, (Text
"parmap" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
parmapV What4 sym
sym)
, (Text
"fromZ" , What4 sym -> Value sym
forall sym. Backend sym => sym -> GenValue sym
fromZV What4 sym
sym)
, (Text
"error" ,
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \TValue
a ->
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \Nat'
_ ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
VFun ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SEval (What4 sym) (Value sym)
s -> What4 sym -> TValue -> String -> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym -> TValue -> String -> SEval sym (GenValue sym)
errorV What4 sym
sym TValue
a (String -> W4Eval sym (Value sym))
-> W4Eval sym String -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (What4 sym -> Value sym -> SEval (What4 sym) String
forall sym. Backend sym => sym -> GenValue sym -> SEval sym String
valueToString What4 sym
sym (Value sym -> W4Eval sym String)
-> W4Eval sym (Value sym) -> W4Eval sym String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
s))
, (Text
"random" ,
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \TValue
a ->
What4 sym
-> (SWord (What4 sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
Backend sym =>
sym -> (SWord sym -> SEval sym (GenValue sym)) -> GenValue sym
wlam What4 sym
sym ((SWord (What4 sym) -> SEval (What4 sym) (Value sym)) -> Value sym)
-> (SWord (What4 sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SWord (What4 sym)
x ->
case What4 sym -> SWord (What4 sym) -> Maybe (Integer, Integer)
forall sym.
Backend sym =>
sym -> SWord sym -> Maybe (Integer, Integer)
wordAsLit What4 sym
sym SWord (What4 sym)
x of
Just (Integer
_,Integer
i) -> What4 sym -> TValue -> Integer -> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym -> TValue -> Integer -> SEval sym (GenValue sym)
randomV What4 sym
sym TValue
a Integer
i
Maybe (Integer, Integer)
Nothing -> What4 sym -> String -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> String -> SEval sym a
cryUserError What4 sym
sym String
"cannot evaluate 'random' with symbolic inputs")
, (Text
"trace",
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \Nat'
_n ->
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \TValue
_a ->
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \TValue
_b ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SEval (What4 sym) (Value sym)
s -> Value sym -> W4Eval sym (Value sym)
forall (m :: * -> *) a. Monad m => a -> m a
return (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SEval (What4 sym) (Value sym)
x -> Value sym -> W4Eval sym (Value sym)
forall (m :: * -> *) a. Monad m => a -> m a
return (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SEval (What4 sym) (Value sym)
y -> do
Value sym
_ <- SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
s
Value sym
_ <- SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
x
SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
y)
]
primeECPrims :: W4.IsSymExprBuilder sym => What4 sym -> Map.Map PrimIdent (Value sym)
primeECPrims :: What4 sym -> Map PrimIdent (Value sym)
primeECPrims What4 sym
sym = [(PrimIdent, Value sym)] -> Map PrimIdent (Value sym)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(PrimIdent, Value sym)] -> Map PrimIdent (Value sym))
-> [(PrimIdent, Value sym)] -> Map PrimIdent (Value sym)
forall a b. (a -> b) -> a -> b
$ [ (Text -> PrimIdent
primeECPrim Text
n, Value sym
v) | (Text
n,Value sym
v) <- [(Text, Value sym)]
prims ]
where
~> :: a -> b -> (a, b)
(~>) = (,)
prims :: [(Text, Value sym)]
prims =
[
Text
"ec_double" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
p ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
s ->
do SymExpr sym BaseIntegerType
p' <- What4 sym -> Integer -> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SEval sym (SInteger sym)
integerLit What4 sym
sym Integer
p
SymExpr sym ProjectivePoint
s' <- What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
toProjectivePoint What4 sym
sym (Value sym -> W4Eval sym (SymExpr sym ProjectivePoint))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
s
What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"Prime ECC"
SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint
fn <- IO
(SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint))
-> IO
(SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint)
forall a b. (a -> b) -> a -> b
$ What4 sym
-> Text
-> Assignment
BaseTypeRepr ((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
-> BaseTypeRepr ProjectivePoint
-> IO
(SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint)
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
What4 sym
-> Text
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
getUninterpFn What4 sym
sym Text
"ec_double"
(Assignment BaseTypeRepr EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment BaseTypeRepr EmptyCtx
-> BaseTypeRepr BaseIntegerType
-> Assignment BaseTypeRepr (EmptyCtx ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr BaseIntegerType
W4.BaseIntegerRepr Assignment BaseTypeRepr (EmptyCtx ::> BaseIntegerType)
-> BaseTypeRepr ProjectivePoint
-> Assignment
BaseTypeRepr ((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr ProjectivePoint
projectivePointRepr) BaseTypeRepr ProjectivePoint
projectivePointRepr
SymExpr sym ProjectivePoint
z <- IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint))
-> IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall a b. (a -> b) -> a -> b
$ sym
-> SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint
-> Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
-> IO (SymExpr sym ProjectivePoint)
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
sym
-> SymFn sym args ret
-> Assignment (SymExpr sym) args
-> IO (SymExpr sym ret)
W4.applySymFn (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymFn
sym
((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
ProjectivePoint
fn (Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym BaseIntegerType
-> Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
p' Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
-> SymExpr sym ProjectivePoint
-> Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ProjectivePoint
s')
What4 sym
-> SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
fromProjectivePoint What4 sym
sym SymExpr sym ProjectivePoint
z
, Text
"ec_add_nonzero" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
p ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
s -> Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
t ->
do SymExpr sym BaseIntegerType
p' <- What4 sym -> Integer -> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SEval sym (SInteger sym)
integerLit What4 sym
sym Integer
p
SymExpr sym ProjectivePoint
s' <- What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
toProjectivePoint What4 sym
sym (Value sym -> W4Eval sym (SymExpr sym ProjectivePoint))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
s
SymExpr sym ProjectivePoint
t' <- What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
toProjectivePoint What4 sym
sym (Value sym -> W4Eval sym (SymExpr sym ProjectivePoint))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
t
What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"Prime ECC"
SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint
fn <- IO
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint))
-> IO
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint)
forall a b. (a -> b) -> a -> b
$ What4 sym
-> Text
-> Assignment
BaseTypeRepr
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
-> BaseTypeRepr ProjectivePoint
-> IO
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint)
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
What4 sym
-> Text
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
getUninterpFn What4 sym
sym Text
"ec_add_nonzero"
(Assignment BaseTypeRepr EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment BaseTypeRepr EmptyCtx
-> BaseTypeRepr BaseIntegerType
-> Assignment BaseTypeRepr (EmptyCtx ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr BaseIntegerType
W4.BaseIntegerRepr Assignment BaseTypeRepr (EmptyCtx ::> BaseIntegerType)
-> BaseTypeRepr ProjectivePoint
-> Assignment
BaseTypeRepr ((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr ProjectivePoint
projectivePointRepr Assignment
BaseTypeRepr ((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
-> BaseTypeRepr ProjectivePoint
-> Assignment
BaseTypeRepr
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr ProjectivePoint
projectivePointRepr) BaseTypeRepr ProjectivePoint
projectivePointRepr
SymExpr sym ProjectivePoint
z <- IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint))
-> IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall a b. (a -> b) -> a -> b
$ sym
-> SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
-> IO (SymExpr sym ProjectivePoint)
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
sym
-> SymFn sym args ret
-> Assignment (SymExpr sym) args
-> IO (SymExpr sym ret)
W4.applySymFn (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
ProjectivePoint
fn (Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym BaseIntegerType
-> Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
p' Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
-> SymExpr sym ProjectivePoint
-> Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ProjectivePoint
s' Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
-> SymExpr sym ProjectivePoint
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseIntegerType) ::> ProjectivePoint)
::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ProjectivePoint
t')
What4 sym
-> SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
fromProjectivePoint What4 sym
sym SymExpr sym ProjectivePoint
z
, Text
"ec_mult" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
p ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
k -> Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
s ->
do SymExpr sym BaseIntegerType
p' <- What4 sym -> Integer -> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SEval sym (SInteger sym)
integerLit What4 sym
sym Integer
p
SymExpr sym BaseIntegerType
k' <- Value sym -> SymExpr sym BaseIntegerType
forall sym. GenValue sym -> SInteger sym
fromVInteger (Value sym -> SymExpr sym BaseIntegerType)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym BaseIntegerType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
k
SymExpr sym ProjectivePoint
s' <- What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
toProjectivePoint What4 sym
sym (Value sym -> W4Eval sym (SymExpr sym ProjectivePoint))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
s
What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"Prime ECC"
SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint
fn <- IO
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint))
-> IO
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
forall a b. (a -> b) -> a -> b
$ What4 sym
-> Text
-> Assignment
BaseTypeRepr
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
-> BaseTypeRepr ProjectivePoint
-> IO
(SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
What4 sym
-> Text
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
getUninterpFn What4 sym
sym Text
"ec_mult"
(Assignment BaseTypeRepr EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment BaseTypeRepr EmptyCtx
-> BaseTypeRepr BaseIntegerType
-> Assignment BaseTypeRepr (EmptyCtx ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr BaseIntegerType
W4.BaseIntegerRepr Assignment BaseTypeRepr (EmptyCtx ::> BaseIntegerType)
-> BaseTypeRepr BaseIntegerType
-> Assignment
BaseTypeRepr ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr BaseIntegerType
W4.BaseIntegerRepr Assignment
BaseTypeRepr ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
-> BaseTypeRepr ProjectivePoint
-> Assignment
BaseTypeRepr
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr ProjectivePoint
projectivePointRepr) BaseTypeRepr ProjectivePoint
projectivePointRepr
SymExpr sym ProjectivePoint
z <- IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint))
-> IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall a b. (a -> b) -> a -> b
$ sym
-> SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
-> IO (SymExpr sym ProjectivePoint)
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
sym
-> SymFn sym args ret
-> Assignment (SymExpr sym) args
-> IO (SymExpr sym ret)
W4.applySymFn (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymFn
sym
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint
fn (Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym BaseIntegerType
-> Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
p' Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
-> SymExpr sym BaseIntegerType
-> Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
k' Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
-> SymExpr sym ProjectivePoint
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ProjectivePoint
s')
What4 sym
-> SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
fromProjectivePoint What4 sym
sym SymExpr sym ProjectivePoint
z
, Text
"ec_twin_mult" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
p ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
j -> Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
s -> Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
k -> Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
t ->
do SymExpr sym BaseIntegerType
p' <- What4 sym -> Integer -> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SEval sym (SInteger sym)
integerLit What4 sym
sym Integer
p
SymExpr sym BaseIntegerType
j' <- Value sym -> SymExpr sym BaseIntegerType
forall sym. GenValue sym -> SInteger sym
fromVInteger (Value sym -> SymExpr sym BaseIntegerType)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym BaseIntegerType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
j
SymExpr sym ProjectivePoint
s' <- What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
toProjectivePoint What4 sym
sym (Value sym -> W4Eval sym (SymExpr sym ProjectivePoint))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
s
SymExpr sym BaseIntegerType
k' <- Value sym -> SymExpr sym BaseIntegerType
forall sym. GenValue sym -> SInteger sym
fromVInteger (Value sym -> SymExpr sym BaseIntegerType)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym BaseIntegerType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
k
SymExpr sym ProjectivePoint
t' <- What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
toProjectivePoint What4 sym
sym (Value sym -> W4Eval sym (SymExpr sym ProjectivePoint))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
t
What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"Prime ECC"
SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint
fn <- IO
(SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint))
-> IO
(SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
-> W4Eval
sym
(SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
forall a b. (a -> b) -> a -> b
$ What4 sym
-> Text
-> Assignment
BaseTypeRepr
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
-> BaseTypeRepr ProjectivePoint
-> IO
(SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint)
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
What4 sym
-> Text
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
getUninterpFn What4 sym
sym Text
"ec_twin_mult"
(Assignment BaseTypeRepr EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment BaseTypeRepr EmptyCtx
-> BaseTypeRepr BaseIntegerType
-> Assignment BaseTypeRepr (EmptyCtx ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr BaseIntegerType
W4.BaseIntegerRepr Assignment BaseTypeRepr (EmptyCtx ::> BaseIntegerType)
-> BaseTypeRepr BaseIntegerType
-> Assignment
BaseTypeRepr ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr BaseIntegerType
W4.BaseIntegerRepr Assignment
BaseTypeRepr ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
-> BaseTypeRepr ProjectivePoint
-> Assignment
BaseTypeRepr
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr ProjectivePoint
projectivePointRepr Assignment
BaseTypeRepr
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
-> BaseTypeRepr BaseIntegerType
-> Assignment
BaseTypeRepr
((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:>
BaseTypeRepr BaseIntegerType
W4.BaseIntegerRepr Assignment
BaseTypeRepr
((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
-> BaseTypeRepr ProjectivePoint
-> Assignment
BaseTypeRepr
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> BaseTypeRepr ProjectivePoint
projectivePointRepr)
BaseTypeRepr ProjectivePoint
projectivePointRepr
SymExpr sym ProjectivePoint
z <- IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint))
-> IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall a b. (a -> b) -> a -> b
$ sym
-> SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint
-> Assignment
(SymExpr sym)
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
-> IO (SymExpr sym ProjectivePoint)
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
sym
-> SymFn sym args ret
-> Assignment (SymExpr sym) args
-> IO (SymExpr sym ret)
W4.applySymFn (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymFn
sym
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
ProjectivePoint
fn (Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym BaseIntegerType
-> Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
p' Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
-> SymExpr sym BaseIntegerType
-> Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
j' Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
-> SymExpr sym ProjectivePoint
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ProjectivePoint
s' Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
-> SymExpr sym BaseIntegerType
-> Assignment
(SymExpr sym)
((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
k' Assignment
(SymExpr sym)
((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
-> SymExpr sym ProjectivePoint
-> Assignment
(SymExpr sym)
(((((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> ProjectivePoint)
::> BaseIntegerType)
::> ProjectivePoint)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ProjectivePoint
t')
What4 sym
-> SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
fromProjectivePoint What4 sym
sym SymExpr sym ProjectivePoint
z
]
type ProjectivePoint = W4.BaseStructType (EmptyCtx ::> W4.BaseIntegerType ::> W4.BaseIntegerType ::> W4.BaseIntegerType)
projectivePointRepr :: W4.BaseTypeRepr ProjectivePoint
projectivePointRepr :: BaseTypeRepr ProjectivePoint
projectivePointRepr = BaseTypeRepr ProjectivePoint
forall k (f :: k -> *) (ctx :: k). KnownRepr f ctx => f ctx
W4.knownRepr
toProjectivePoint :: W4.IsSymExprBuilder sym =>
What4 sym -> Value sym -> SEval (What4 sym) (W4.SymExpr sym ProjectivePoint)
toProjectivePoint :: What4 sym
-> Value sym -> SEval (What4 sym) (SymExpr sym ProjectivePoint)
toProjectivePoint What4 sym
sym Value sym
v =
do SymExpr sym BaseIntegerType
x <- Value sym -> SymExpr sym BaseIntegerType
forall sym. GenValue sym -> SInteger sym
fromVInteger (Value sym -> SymExpr sym BaseIntegerType)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym BaseIntegerType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ident -> Value sym -> SEval (What4 sym) (Value sym)
forall sym. Ident -> GenValue sym -> SEval sym (GenValue sym)
lookupRecord Ident
"x" Value sym
v
SymExpr sym BaseIntegerType
y <- Value sym -> SymExpr sym BaseIntegerType
forall sym. GenValue sym -> SInteger sym
fromVInteger (Value sym -> SymExpr sym BaseIntegerType)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym BaseIntegerType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ident -> Value sym -> SEval (What4 sym) (Value sym)
forall sym. Ident -> GenValue sym -> SEval sym (GenValue sym)
lookupRecord Ident
"y" Value sym
v
SymExpr sym BaseIntegerType
z <- Value sym -> SymExpr sym BaseIntegerType
forall sym. GenValue sym -> SInteger sym
fromVInteger (Value sym -> SymExpr sym BaseIntegerType)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym BaseIntegerType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ident -> Value sym -> SEval (What4 sym) (Value sym)
forall sym. Ident -> GenValue sym -> SEval sym (GenValue sym)
lookupRecord Ident
"z" Value sym
v
IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint))
-> IO (SymExpr sym ProjectivePoint)
-> W4Eval sym (SymExpr sym ProjectivePoint)
forall a b. (a -> b) -> a -> b
$ sym
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> BaseIntegerType)
-> IO (SymExpr sym ProjectivePoint)
forall sym (flds :: Ctx BaseType).
IsExprBuilder sym =>
sym -> Assignment (SymExpr sym) flds -> IO (SymStruct sym flds)
W4.mkStruct (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) (Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym BaseIntegerType
-> Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
x Assignment (SymExpr sym) (EmptyCtx ::> BaseIntegerType)
-> SymExpr sym BaseIntegerType
-> Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
y Assignment
(SymExpr sym) ((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
-> SymExpr sym BaseIntegerType
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> BaseIntegerType)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym BaseIntegerType
z)
fromProjectivePoint :: W4.IsSymExprBuilder sym =>
What4 sym -> W4.SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
fromProjectivePoint :: What4 sym
-> SymExpr sym ProjectivePoint -> SEval (What4 sym) (Value sym)
fromProjectivePoint What4 sym
sym SymExpr sym ProjectivePoint
p = IO (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Value sym) -> W4Eval sym (Value sym))
-> IO (Value sym) -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
do Value sym
x <- SymExpr sym BaseIntegerType -> Value sym
forall sym. SInteger sym -> GenValue sym
VInteger (SymExpr sym BaseIntegerType -> Value sym)
-> IO (SymExpr sym BaseIntegerType) -> IO (Value sym)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> sym
-> SymExpr sym ProjectivePoint
-> Index
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> BaseIntegerType)
BaseIntegerType
-> IO (SymExpr sym BaseIntegerType)
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr sym ProjectivePoint
p (forall k (n :: Nat) (ctx :: Ctx k) (r :: k).
Idx n ctx r =>
Index ctx r
forall (ctx :: Ctx BaseType) (r :: BaseType).
Idx 0 ctx r =>
Index ctx r
natIndex @0)
Value sym
y <- SymExpr sym BaseIntegerType -> Value sym
forall sym. SInteger sym -> GenValue sym
VInteger (SymExpr sym BaseIntegerType -> Value sym)
-> IO (SymExpr sym BaseIntegerType) -> IO (Value sym)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> sym
-> SymExpr sym ProjectivePoint
-> Index
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> BaseIntegerType)
BaseIntegerType
-> IO (SymExpr sym BaseIntegerType)
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr sym ProjectivePoint
p (forall k (n :: Nat) (ctx :: Ctx k) (r :: k).
Idx n ctx r =>
Index ctx r
forall (ctx :: Ctx BaseType) (r :: BaseType).
Idx 1 ctx r =>
Index ctx r
natIndex @1)
Value sym
z <- SymExpr sym BaseIntegerType -> Value sym
forall sym. SInteger sym -> GenValue sym
VInteger (SymExpr sym BaseIntegerType -> Value sym)
-> IO (SymExpr sym BaseIntegerType) -> IO (Value sym)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> sym
-> SymExpr sym ProjectivePoint
-> Index
(((EmptyCtx ::> BaseIntegerType) ::> BaseIntegerType)
::> BaseIntegerType)
BaseIntegerType
-> IO (SymExpr sym BaseIntegerType)
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr sym ProjectivePoint
p (forall k (n :: Nat) (ctx :: Ctx k) (r :: k).
Idx n ctx r =>
Index ctx r
forall (ctx :: Ctx BaseType) (r :: BaseType).
Idx 2 ctx r =>
Index ctx r
natIndex @2)
Value sym -> IO (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> IO (Value sym)) -> Value sym -> IO (Value sym)
forall a b. (a -> b) -> a -> b
$ RecordMap Ident (SEval (What4 sym) (Value sym)) -> Value sym
forall sym.
RecordMap Ident (SEval sym (GenValue sym)) -> GenValue sym
VRecord (RecordMap Ident (SEval (What4 sym) (Value sym)) -> Value sym)
-> RecordMap Ident (SEval (What4 sym) (Value sym)) -> Value sym
forall a b. (a -> b) -> a -> b
$ [(Ident, W4Eval sym (Value sym))]
-> RecordMap Ident (W4Eval sym (Value sym))
forall a b. (Show a, Ord a) => [(a, b)] -> RecordMap a b
recordFromFields [ (String -> Ident
packIdent String
"x",Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value sym
x), (String -> Ident
packIdent String
"y",Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value sym
y),(String -> Ident
packIdent String
"z",Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value sym
z) ]
suiteBPrims :: W4.IsSymExprBuilder sym => What4 sym -> Map.Map PrimIdent (Value sym)
suiteBPrims :: What4 sym -> Map PrimIdent (Value sym)
suiteBPrims What4 sym
sym = [(PrimIdent, Value sym)] -> Map PrimIdent (Value sym)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(PrimIdent, Value sym)] -> Map PrimIdent (Value sym))
-> [(PrimIdent, Value sym)] -> Map PrimIdent (Value sym)
forall a b. (a -> b) -> a -> b
$ [ (Text -> PrimIdent
suiteBPrim Text
n, Value sym
v) | (Text
n,Value sym
v) <- [(Text, Value sym)]
prims ]
where
~> :: a -> b -> (a, b)
(~>) = (,)
prims :: [(Text, Value sym)]
prims =
[ Text
"AESEncRound" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
st ->
do What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"AES encryption"
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
applyAESStateFunc What4 sym
sym Text
"AESEncRound" (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
st
, Text
"AESEncFinalRound" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
st ->
do What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"AES encryption"
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
applyAESStateFunc What4 sym
sym Text
"AESEncFinalRound" (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
st
, Text
"AESDecRound" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
st ->
do What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"AES decryption"
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
applyAESStateFunc What4 sym
sym Text
"AESDecRound" (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
st
, Text
"AESDecFinalRound" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
st ->
do What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"AES decryption"
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
applyAESStateFunc What4 sym
sym Text
"AESDecFinalRound" (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
st
, Text
"AESInvMixColumns" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
st ->
do What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"AES key expansion"
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
applyAESStateFunc What4 sym
sym Text
"AESInvMixColumns" (Value sym -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
st
, Text
"AESKeyExpand" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
k ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
st ->
do SeqMap (What4 sym)
ss <- Value sym -> SeqMap (What4 sym)
forall sym. GenValue sym -> SeqMap sym
fromVSeq (Value sym -> SeqMap (What4 sym))
-> W4Eval sym (Value sym) -> W4Eval sym (SeqMap (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
st
Some Assignment (SymExpr sym) x
ws <- Int
-> (Int -> W4Eval sym (Some (SymExpr sym)))
-> W4Eval sym (Some (Assignment (SymExpr sym)))
forall k (m :: * -> *) (f :: k -> *).
Applicative m =>
Int -> (Int -> m (Some f)) -> m (Some (Assignment f))
generateSomeM (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
k) (\Int
i -> SymExpr sym ('BaseBVType 32) -> Some (SymExpr sym)
forall k (f :: k -> *) (x :: k). f x -> Some f
Some (SymExpr sym ('BaseBVType 32) -> Some (SymExpr sym))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (Some (SymExpr sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"AESKeyExpand" SeqMap (What4 sym)
ss (Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
i))
let args :: Assignment BaseTypeRepr x
args = (forall (x :: BaseType). SymExpr sym x -> BaseTypeRepr x)
-> Assignment (SymExpr sym) x -> Assignment BaseTypeRepr x
forall k l (t :: (k -> *) -> l -> *) (f :: k -> *) (g :: k -> *).
FunctorFC t =>
(forall (x :: k). f x -> g x) -> forall (x :: l). t f x -> t g x
fmapFC forall (x :: BaseType). SymExpr sym x -> BaseTypeRepr x
forall (e :: BaseType -> *) (tp :: BaseType).
IsExpr e =>
e tp -> BaseTypeRepr tp
W4.exprType Assignment (SymExpr sym) x
ws
Some Assignment BaseTypeRepr x
ret <- Some (Assignment BaseTypeRepr)
-> W4Eval sym (Some (Assignment BaseTypeRepr))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Some (Assignment BaseTypeRepr)
-> W4Eval sym (Some (Assignment BaseTypeRepr)))
-> Some (Assignment BaseTypeRepr)
-> W4Eval sym (Some (Assignment BaseTypeRepr))
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> Some BaseTypeRepr) -> Some (Assignment BaseTypeRepr)
forall k (f :: k -> *).
Int -> (Int -> Some f) -> Some (Assignment f)
generateSome (Int
4Int -> Int -> Int
forall a. Num a => a -> a -> a
*(Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
7)) (\Int
_ -> BaseTypeRepr ('BaseBVType 32) -> Some BaseTypeRepr
forall k (f :: k -> *) (x :: k). f x -> Some f
Some (NatRepr 32 -> BaseTypeRepr ('BaseBVType 32)
forall (w :: Nat).
(1 <= w) =>
NatRepr w -> BaseTypeRepr ('BaseBVType w)
W4.BaseBVRepr (KnownNat 32 => NatRepr 32
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @32)))
What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"AES key expansion"
SymFn sym x ('BaseStructType x)
fn <- IO (SymFn sym x ('BaseStructType x))
-> W4Eval sym (SymFn sym x ('BaseStructType x))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymFn sym x ('BaseStructType x))
-> W4Eval sym (SymFn sym x ('BaseStructType x)))
-> IO (SymFn sym x ('BaseStructType x))
-> W4Eval sym (SymFn sym x ('BaseStructType x))
forall a b. (a -> b) -> a -> b
$ What4 sym
-> Text
-> Assignment BaseTypeRepr x
-> BaseTypeRepr ('BaseStructType x)
-> IO (SymFn sym x ('BaseStructType x))
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
What4 sym
-> Text
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
getUninterpFn What4 sym
sym (Text
"AESKeyExpand" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (Integer -> String
forall a. Show a => a -> String
show Integer
k)) Assignment BaseTypeRepr x
args (Assignment BaseTypeRepr x -> BaseTypeRepr ('BaseStructType x)
forall (ctx :: Ctx BaseType).
Assignment BaseTypeRepr ctx -> BaseTypeRepr ('BaseStructType ctx)
W4.BaseStructRepr Assignment BaseTypeRepr x
ret)
SymExpr sym ('BaseStructType x)
z <- IO (SymExpr sym ('BaseStructType x))
-> W4Eval sym (SymExpr sym ('BaseStructType x))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym ('BaseStructType x))
-> W4Eval sym (SymExpr sym ('BaseStructType x)))
-> IO (SymExpr sym ('BaseStructType x))
-> W4Eval sym (SymExpr sym ('BaseStructType x))
forall a b. (a -> b) -> a -> b
$ sym
-> SymFn sym x ('BaseStructType x)
-> Assignment (SymExpr sym) x
-> IO (SymExpr sym ('BaseStructType x))
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
sym
-> SymFn sym args ret
-> Assignment (SymExpr sym) args
-> IO (SymExpr sym ret)
W4.applySymFn (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymFn sym x ('BaseStructType x)
fn Assignment (SymExpr sym) x
ws
Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$ Integer -> SeqMap (What4 sym) -> Value sym
forall sym. Integer -> SeqMap sym -> GenValue sym
VSeq (Integer
4Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*(Integer
kInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
7)) (SeqMap (What4 sym) -> Value sym)
-> SeqMap (What4 sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap ((Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym))
-> (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall a b. (a -> b) -> a -> b
$ \Integer
i ->
case Int -> Size x -> Maybe (Some (Index x))
forall k (ctx :: Ctx k).
Int -> Size ctx -> Maybe (Some (Index ctx))
intIndex (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
i) (Assignment BaseTypeRepr x -> Size x
forall k (f :: k -> *) (ctx :: Ctx k). Assignment f ctx -> Size ctx
size Assignment BaseTypeRepr x
ret) of
Just (Some Index x x
idx) | Just x :~: 'BaseBVType 32
W4.Refl <- BaseTypeRepr x
-> BaseTypeRepr ('BaseBVType 32) -> Maybe (x :~: 'BaseBVType 32)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
W4.testEquality (Assignment BaseTypeRepr x
retAssignment BaseTypeRepr x -> Index x x -> BaseTypeRepr x
forall k (f :: k -> *) (ctx :: Ctx k) (tp :: k).
Assignment f ctx -> Index ctx tp -> f tp
!Index x x
idx) (NatRepr 32 -> BaseTypeRepr ('BaseBVType 32)
forall (w :: Nat).
(1 <= w) =>
NatRepr w -> BaseTypeRepr ('BaseBVType w)
W4.BaseBVRepr (KnownNat 32 => NatRepr 32
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @32)) ->
SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym)
forall sym.
IsSymExprBuilder sym =>
SymBV sym 32 -> SEval (What4 sym) (Value sym)
fromWord32 (SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym
-> SymExpr sym ('BaseStructType x)
-> Index x x
-> IO (SymExpr sym x)
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr sym ('BaseStructType x)
z Index x x
idx)
Maybe (Some (Index x))
_ -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
, Text
"processSHA2_224" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
n ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
xs ->
do [W4Eval sym (Value sym)]
blks <- Integer -> SeqMap (What4 sym) -> [SEval (What4 sym) (Value sym)]
forall n sym.
Integral n =>
n -> SeqMap sym -> [SEval sym (GenValue sym)]
enumerateSeqMap Integer
n (SeqMap (What4 sym) -> [W4Eval sym (Value sym)])
-> (Value sym -> SeqMap (What4 sym))
-> Value sym
-> [W4Eval sym (Value sym)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value sym -> SeqMap (What4 sym)
forall sym. GenValue sym -> SeqMap sym
fromVSeq (Value sym -> [W4Eval sym (Value sym)])
-> W4Eval sym (Value sym) -> W4Eval sym [W4Eval sym (Value sym)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
xs
What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"SHA-224"
SymExpr sym (BaseStructType SHA256State)
initSt <- IO (SymExpr sym (BaseStructType SHA256State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (What4 sym
-> SHA256State -> IO (SymExpr sym (BaseStructType SHA256State))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SHA256State -> IO (SymExpr sym (BaseStructType SHA256State))
mkSHA256InitialState What4 sym
sym SHA256State
SHA.initialSHA224State)
SymExpr sym (BaseStructType SHA256State)
finalSt <- (SymExpr sym (BaseStructType SHA256State)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State)))
-> SymExpr sym (BaseStructType SHA256State)
-> [W4Eval sym (Value sym)]
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State))
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\SymExpr sym (BaseStructType SHA256State)
st W4Eval sym (Value sym)
blk -> What4 sym
-> SymExpr sym (BaseStructType SHA256State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA256State))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SymExpr sym (BaseStructType SHA256State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA256State))
processSHA256Block What4 sym
sym SymExpr sym (BaseStructType SHA256State)
st (Value sym
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State)))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< W4Eval sym (Value sym)
blk) SymExpr sym (BaseStructType SHA256State)
initSt [W4Eval sym (Value sym)]
blks
Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$ Integer -> SeqMap (What4 sym) -> Value sym
forall sym. Integer -> SeqMap sym -> GenValue sym
VSeq Integer
7 (SeqMap (What4 sym) -> Value sym)
-> SeqMap (What4 sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap \Integer
i ->
case Int -> Size SHA256State -> Maybe (Some (Index SHA256State))
forall k (ctx :: Ctx k).
Int -> Size ctx -> Maybe (Some (Index ctx))
intIndex (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
i) (Size SHA256State
forall k (ctx :: Ctx k). KnownContext ctx => Size ctx
knownSize :: Size SHA256State) of
Just (Some Index SHA256State x
idx) ->
do SymExpr sym x
z <- IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x))
-> IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x)
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym (BaseStructType SHA256State)
-> Index SHA256State x
-> IO (SymExpr sym x)
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr sym (BaseStructType SHA256State)
finalSt Index SHA256State x
idx
case BaseTypeRepr x
-> BaseTypeRepr ('BaseBVType 32) -> Maybe (x :~: 'BaseBVType 32)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
W4.testEquality (SymExpr sym x -> BaseTypeRepr x
forall (e :: BaseType -> *) (tp :: BaseType).
IsExpr e =>
e tp -> BaseTypeRepr tp
W4.exprType SymExpr sym x
z) (NatRepr 32 -> BaseTypeRepr ('BaseBVType 32)
forall (w :: Nat).
(1 <= w) =>
NatRepr w -> BaseTypeRepr ('BaseBVType w)
W4.BaseBVRepr (KnownNat 32 => NatRepr 32
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @32)) of
Just x :~: 'BaseBVType 32
W4.Refl -> SymExpr sym ('BaseBVType 32) -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
SymBV sym 32 -> SEval (What4 sym) (Value sym)
fromWord32 SymExpr sym x
SymExpr sym ('BaseBVType 32)
z
Maybe (x :~: 'BaseBVType 32)
Nothing -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
Maybe (Some (Index SHA256State))
Nothing -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
, Text
"processSHA2_256" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
n ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
xs ->
do [W4Eval sym (Value sym)]
blks <- Integer -> SeqMap (What4 sym) -> [SEval (What4 sym) (Value sym)]
forall n sym.
Integral n =>
n -> SeqMap sym -> [SEval sym (GenValue sym)]
enumerateSeqMap Integer
n (SeqMap (What4 sym) -> [W4Eval sym (Value sym)])
-> (Value sym -> SeqMap (What4 sym))
-> Value sym
-> [W4Eval sym (Value sym)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value sym -> SeqMap (What4 sym)
forall sym. GenValue sym -> SeqMap sym
fromVSeq (Value sym -> [W4Eval sym (Value sym)])
-> W4Eval sym (Value sym) -> W4Eval sym [W4Eval sym (Value sym)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
xs
What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"SHA-256"
SymExpr sym (BaseStructType SHA256State)
initSt <- IO (SymExpr sym (BaseStructType SHA256State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (What4 sym
-> SHA256State -> IO (SymExpr sym (BaseStructType SHA256State))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SHA256State -> IO (SymExpr sym (BaseStructType SHA256State))
mkSHA256InitialState What4 sym
sym SHA256State
SHA.initialSHA256State)
SymExpr sym (BaseStructType SHA256State)
finalSt <- (SymExpr sym (BaseStructType SHA256State)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State)))
-> SymExpr sym (BaseStructType SHA256State)
-> [W4Eval sym (Value sym)]
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State))
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\SymExpr sym (BaseStructType SHA256State)
st W4Eval sym (Value sym)
blk -> What4 sym
-> SymExpr sym (BaseStructType SHA256State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA256State))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SymExpr sym (BaseStructType SHA256State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA256State))
processSHA256Block What4 sym
sym SymExpr sym (BaseStructType SHA256State)
st (Value sym
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State)))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< W4Eval sym (Value sym)
blk) SymExpr sym (BaseStructType SHA256State)
initSt [W4Eval sym (Value sym)]
blks
Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$ Integer -> SeqMap (What4 sym) -> Value sym
forall sym. Integer -> SeqMap sym -> GenValue sym
VSeq Integer
8 (SeqMap (What4 sym) -> Value sym)
-> SeqMap (What4 sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap \Integer
i ->
case Int -> Size SHA256State -> Maybe (Some (Index SHA256State))
forall k (ctx :: Ctx k).
Int -> Size ctx -> Maybe (Some (Index ctx))
intIndex (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
i) (Size SHA256State
forall k (ctx :: Ctx k). KnownContext ctx => Size ctx
knownSize :: Size SHA256State) of
Just (Some Index SHA256State x
idx) ->
do SymExpr sym x
z <- IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x))
-> IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x)
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym (BaseStructType SHA256State)
-> Index SHA256State x
-> IO (SymExpr sym x)
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr sym (BaseStructType SHA256State)
finalSt Index SHA256State x
idx
case BaseTypeRepr x
-> BaseTypeRepr ('BaseBVType 32) -> Maybe (x :~: 'BaseBVType 32)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
W4.testEquality (SymExpr sym x -> BaseTypeRepr x
forall (e :: BaseType -> *) (tp :: BaseType).
IsExpr e =>
e tp -> BaseTypeRepr tp
W4.exprType SymExpr sym x
z) (NatRepr 32 -> BaseTypeRepr ('BaseBVType 32)
forall (w :: Nat).
(1 <= w) =>
NatRepr w -> BaseTypeRepr ('BaseBVType w)
W4.BaseBVRepr (KnownNat 32 => NatRepr 32
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @32)) of
Just x :~: 'BaseBVType 32
W4.Refl -> SymExpr sym ('BaseBVType 32) -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
SymBV sym 32 -> SEval (What4 sym) (Value sym)
fromWord32 SymExpr sym x
SymExpr sym ('BaseBVType 32)
z
Maybe (x :~: 'BaseBVType 32)
Nothing -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
Maybe (Some (Index SHA256State))
Nothing -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
, Text
"processSHA2_384" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
n ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
xs ->
do [W4Eval sym (Value sym)]
blks <- Integer -> SeqMap (What4 sym) -> [SEval (What4 sym) (Value sym)]
forall n sym.
Integral n =>
n -> SeqMap sym -> [SEval sym (GenValue sym)]
enumerateSeqMap Integer
n (SeqMap (What4 sym) -> [W4Eval sym (Value sym)])
-> (Value sym -> SeqMap (What4 sym))
-> Value sym
-> [W4Eval sym (Value sym)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value sym -> SeqMap (What4 sym)
forall sym. GenValue sym -> SeqMap sym
fromVSeq (Value sym -> [W4Eval sym (Value sym)])
-> W4Eval sym (Value sym) -> W4Eval sym [W4Eval sym (Value sym)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
xs
What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"SHA-384"
SymExpr sym (BaseStructType SHA512State)
initSt <- IO (SymExpr sym (BaseStructType SHA512State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (What4 sym
-> SHA512State -> IO (SymExpr sym (BaseStructType SHA512State))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SHA512State -> IO (SymExpr sym (BaseStructType SHA512State))
mkSHA512InitialState What4 sym
sym SHA512State
SHA.initialSHA384State)
SymExpr sym (BaseStructType SHA512State)
finalSt <- (SymExpr sym (BaseStructType SHA512State)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State)))
-> SymExpr sym (BaseStructType SHA512State)
-> [W4Eval sym (Value sym)]
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State))
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\SymExpr sym (BaseStructType SHA512State)
st W4Eval sym (Value sym)
blk -> What4 sym
-> SymExpr sym (BaseStructType SHA512State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA512State))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SymExpr sym (BaseStructType SHA512State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA512State))
processSHA512Block What4 sym
sym SymExpr sym (BaseStructType SHA512State)
st (Value sym
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State)))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< W4Eval sym (Value sym)
blk) SymExpr sym (BaseStructType SHA512State)
initSt [W4Eval sym (Value sym)]
blks
Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$ Integer -> SeqMap (What4 sym) -> Value sym
forall sym. Integer -> SeqMap sym -> GenValue sym
VSeq Integer
6 (SeqMap (What4 sym) -> Value sym)
-> SeqMap (What4 sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap \Integer
i ->
case Int -> Size SHA512State -> Maybe (Some (Index SHA512State))
forall k (ctx :: Ctx k).
Int -> Size ctx -> Maybe (Some (Index ctx))
intIndex (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
i) (Size SHA512State
forall k (ctx :: Ctx k). KnownContext ctx => Size ctx
knownSize :: Size SHA512State) of
Just (Some Index SHA512State x
idx) ->
do SymExpr sym x
z <- IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x))
-> IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x)
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym (BaseStructType SHA512State)
-> Index SHA512State x
-> IO (SymExpr sym x)
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr sym (BaseStructType SHA512State)
finalSt Index SHA512State x
idx
case BaseTypeRepr x
-> BaseTypeRepr ('BaseBVType 64) -> Maybe (x :~: 'BaseBVType 64)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
W4.testEquality (SymExpr sym x -> BaseTypeRepr x
forall (e :: BaseType -> *) (tp :: BaseType).
IsExpr e =>
e tp -> BaseTypeRepr tp
W4.exprType SymExpr sym x
z) (NatRepr 64 -> BaseTypeRepr ('BaseBVType 64)
forall (w :: Nat).
(1 <= w) =>
NatRepr w -> BaseTypeRepr ('BaseBVType w)
W4.BaseBVRepr (KnownNat 64 => NatRepr 64
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @64)) of
Just x :~: 'BaseBVType 64
W4.Refl -> SymBV sym 64 -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
SymBV sym 64 -> SEval (What4 sym) (Value sym)
fromWord64 SymExpr sym x
SymBV sym 64
z
Maybe (x :~: 'BaseBVType 64)
Nothing -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
Maybe (Some (Index SHA512State))
Nothing -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
, Text
"processSHA2_512" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
n ->
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
xs ->
do [W4Eval sym (Value sym)]
blks <- Integer -> SeqMap (What4 sym) -> [SEval (What4 sym) (Value sym)]
forall n sym.
Integral n =>
n -> SeqMap sym -> [SEval sym (GenValue sym)]
enumerateSeqMap Integer
n (SeqMap (What4 sym) -> [W4Eval sym (Value sym)])
-> (Value sym -> SeqMap (What4 sym))
-> Value sym
-> [W4Eval sym (Value sym)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value sym -> SeqMap (What4 sym)
forall sym. GenValue sym -> SeqMap sym
fromVSeq (Value sym -> [W4Eval sym (Value sym)])
-> W4Eval sym (Value sym) -> W4Eval sym [W4Eval sym (Value sym)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
xs
What4 sym -> Text -> W4Eval sym ()
forall (m :: * -> *) sym. MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
"SHA-512"
SymExpr sym (BaseStructType SHA512State)
initSt <- IO (SymExpr sym (BaseStructType SHA512State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (What4 sym
-> SHA512State -> IO (SymExpr sym (BaseStructType SHA512State))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SHA512State -> IO (SymExpr sym (BaseStructType SHA512State))
mkSHA512InitialState What4 sym
sym SHA512State
SHA.initialSHA512State)
SymExpr sym (BaseStructType SHA512State)
finalSt <- (SymExpr sym (BaseStructType SHA512State)
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State)))
-> SymExpr sym (BaseStructType SHA512State)
-> [W4Eval sym (Value sym)]
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State))
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\SymExpr sym (BaseStructType SHA512State)
st W4Eval sym (Value sym)
blk -> What4 sym
-> SymExpr sym (BaseStructType SHA512State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA512State))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> SymExpr sym (BaseStructType SHA512State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA512State))
processSHA512Block What4 sym
sym SymExpr sym (BaseStructType SHA512State)
st (Value sym
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State)))
-> W4Eval sym (Value sym)
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< W4Eval sym (Value sym)
blk) SymExpr sym (BaseStructType SHA512State)
initSt [W4Eval sym (Value sym)]
blks
Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$ Integer -> SeqMap (What4 sym) -> Value sym
forall sym. Integer -> SeqMap sym -> GenValue sym
VSeq Integer
8 (SeqMap (What4 sym) -> Value sym)
-> SeqMap (What4 sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap \Integer
i ->
case Int -> Size SHA512State -> Maybe (Some (Index SHA512State))
forall k (ctx :: Ctx k).
Int -> Size ctx -> Maybe (Some (Index ctx))
intIndex (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
i) (Size SHA512State
forall k (ctx :: Ctx k). KnownContext ctx => Size ctx
knownSize :: Size SHA512State) of
Just (Some Index SHA512State x
idx) ->
do SymExpr sym x
z <- IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x))
-> IO (SymExpr sym x) -> W4Eval sym (SymExpr sym x)
forall a b. (a -> b) -> a -> b
$ sym
-> SymExpr sym (BaseStructType SHA512State)
-> Index SHA512State x
-> IO (SymExpr sym x)
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr sym (BaseStructType SHA512State)
finalSt Index SHA512State x
idx
case BaseTypeRepr x
-> BaseTypeRepr ('BaseBVType 64) -> Maybe (x :~: 'BaseBVType 64)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
W4.testEquality (SymExpr sym x -> BaseTypeRepr x
forall (e :: BaseType -> *) (tp :: BaseType).
IsExpr e =>
e tp -> BaseTypeRepr tp
W4.exprType SymExpr sym x
z) (NatRepr 64 -> BaseTypeRepr ('BaseBVType 64)
forall (w :: Nat).
(1 <= w) =>
NatRepr w -> BaseTypeRepr ('BaseBVType w)
W4.BaseBVRepr (KnownNat 64 => NatRepr 64
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @64)) of
Just x :~: 'BaseBVType 64
W4.Refl -> SymBV sym 64 -> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
SymBV sym 64 -> SEval (What4 sym) (Value sym)
fromWord64 SymExpr sym x
SymBV sym 64
z
Maybe (x :~: 'BaseBVType 64)
Nothing -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
Maybe (Some (Index SHA512State))
Nothing -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
]
type SHA256State =
EmptyCtx ::>
W4.BaseBVType 32 ::> W4.BaseBVType 32 ::> W4.BaseBVType 32 ::> W4.BaseBVType 32 ::>
W4.BaseBVType 32 ::> W4.BaseBVType 32 ::> W4.BaseBVType 32 ::> W4.BaseBVType 32
type SHA512State =
EmptyCtx ::>
W4.BaseBVType 64 ::> W4.BaseBVType 64 ::> W4.BaseBVType 64 ::> W4.BaseBVType 64 ::>
W4.BaseBVType 64 ::> W4.BaseBVType 64 ::> W4.BaseBVType 64 ::> W4.BaseBVType 64
mkSHA256InitialState :: W4.IsSymExprBuilder sym =>
What4 sym ->
SHA.SHA256State ->
IO (W4.SymExpr sym (W4.BaseStructType SHA256State))
mkSHA256InitialState :: What4 sym
-> SHA256State -> IO (SymExpr sym (BaseStructType SHA256State))
mkSHA256InitialState What4 sym
sym (SHA.SHA256S Word32
s0 Word32
s1 Word32
s2 Word32
s3 Word32
s4 Word32
s5 Word32
s6 Word32
s7) =
do SymExpr sym ('BaseBVType 32)
z0 <- Word32 -> IO (SymExpr sym ('BaseBVType 32))
lit Word32
s0
SymExpr sym ('BaseBVType 32)
z1 <- Word32 -> IO (SymExpr sym ('BaseBVType 32))
lit Word32
s1
SymExpr sym ('BaseBVType 32)
z2 <- Word32 -> IO (SymExpr sym ('BaseBVType 32))
lit Word32
s2
SymExpr sym ('BaseBVType 32)
z3 <- Word32 -> IO (SymExpr sym ('BaseBVType 32))
lit Word32
s3
SymExpr sym ('BaseBVType 32)
z4 <- Word32 -> IO (SymExpr sym ('BaseBVType 32))
lit Word32
s4
SymExpr sym ('BaseBVType 32)
z5 <- Word32 -> IO (SymExpr sym ('BaseBVType 32))
lit Word32
s5
SymExpr sym ('BaseBVType 32)
z6 <- Word32 -> IO (SymExpr sym ('BaseBVType 32))
lit Word32
s6
SymExpr sym ('BaseBVType 32)
z7 <- Word32 -> IO (SymExpr sym ('BaseBVType 32))
lit Word32
s7
sym
-> Assignment (SymExpr sym) SHA256State
-> IO (SymExpr sym (BaseStructType SHA256State))
forall sym (flds :: Ctx BaseType).
IsExprBuilder sym =>
sym -> Assignment (SymExpr sym) flds -> IO (SymStruct sym flds)
W4.mkStruct (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) (Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym ('BaseBVType 32)
-> Assignment (SymExpr sym) (EmptyCtx ::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
z0 Assignment (SymExpr sym) (EmptyCtx ::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym) ((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
z1 Assignment
(SymExpr sym) ((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
z2 Assignment
(SymExpr sym)
(((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
z3 Assignment
(SymExpr sym)
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
z4 Assignment
(SymExpr sym)
(((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
z5 Assignment
(SymExpr sym)
((((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
z6 Assignment
(SymExpr sym)
(((((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment (SymExpr sym) SHA256State
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
z7)
where lit :: Word32 -> IO (SymExpr sym ('BaseBVType 32))
lit Word32
w = sym -> NatRepr 32 -> BV 32 -> IO (SymExpr sym ('BaseBVType 32))
forall sym (w :: Nat).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
W4.bvLit (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) (KnownNat 32 => NatRepr 32
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @32) (Word32 -> BV 32
BV.word32 Word32
w)
mkSHA512InitialState :: W4.IsSymExprBuilder sym =>
What4 sym ->
SHA.SHA512State ->
IO (W4.SymExpr sym (W4.BaseStructType SHA512State))
mkSHA512InitialState :: What4 sym
-> SHA512State -> IO (SymExpr sym (BaseStructType SHA512State))
mkSHA512InitialState What4 sym
sym (SHA.SHA512S Word64
s0 Word64
s1 Word64
s2 Word64
s3 Word64
s4 Word64
s5 Word64
s6 Word64
s7) =
do SymExpr sym ('BaseBVType 64)
z0 <- Word64 -> IO (SymExpr sym ('BaseBVType 64))
lit Word64
s0
SymExpr sym ('BaseBVType 64)
z1 <- Word64 -> IO (SymExpr sym ('BaseBVType 64))
lit Word64
s1
SymExpr sym ('BaseBVType 64)
z2 <- Word64 -> IO (SymExpr sym ('BaseBVType 64))
lit Word64
s2
SymExpr sym ('BaseBVType 64)
z3 <- Word64 -> IO (SymExpr sym ('BaseBVType 64))
lit Word64
s3
SymExpr sym ('BaseBVType 64)
z4 <- Word64 -> IO (SymExpr sym ('BaseBVType 64))
lit Word64
s4
SymExpr sym ('BaseBVType 64)
z5 <- Word64 -> IO (SymExpr sym ('BaseBVType 64))
lit Word64
s5
SymExpr sym ('BaseBVType 64)
z6 <- Word64 -> IO (SymExpr sym ('BaseBVType 64))
lit Word64
s6
SymExpr sym ('BaseBVType 64)
z7 <- Word64 -> IO (SymExpr sym ('BaseBVType 64))
lit Word64
s7
sym
-> Assignment (SymExpr sym) SHA512State
-> IO (SymExpr sym (BaseStructType SHA512State))
forall sym (flds :: Ctx BaseType).
IsExprBuilder sym =>
sym -> Assignment (SymExpr sym) flds -> IO (SymStruct sym flds)
W4.mkStruct (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) (Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym ('BaseBVType 64)
-> Assignment (SymExpr sym) (EmptyCtx ::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
z0 Assignment (SymExpr sym) (EmptyCtx ::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym) ((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
z1 Assignment
(SymExpr sym) ((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
z2 Assignment
(SymExpr sym)
(((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
z3 Assignment
(SymExpr sym)
((((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
z4 Assignment
(SymExpr sym)
(((((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((((((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
z5 Assignment
(SymExpr sym)
((((((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((((((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
z6 Assignment
(SymExpr sym)
(((((((EmptyCtx ::> 'BaseBVType 64) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment (SymExpr sym) SHA512State
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
z7)
where lit :: Word64 -> IO (SymExpr sym ('BaseBVType 64))
lit Word64
w = sym -> NatRepr 64 -> BV 64 -> IO (SymExpr sym ('BaseBVType 64))
forall sym (w :: Nat).
(IsExprBuilder sym, 1 <= w) =>
sym -> NatRepr w -> BV w -> IO (SymBV sym w)
W4.bvLit (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) (KnownNat 64 => NatRepr 64
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @64) (Word64 -> BV 64
BV.word64 Word64
w)
processSHA256Block :: W4.IsSymExprBuilder sym =>
What4 sym ->
W4.SymExpr sym (W4.BaseStructType SHA256State) ->
Value sym ->
SEval (What4 sym) (W4.SymExpr sym (W4.BaseStructType SHA256State))
processSHA256Block :: What4 sym
-> SymExpr sym (BaseStructType SHA256State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA256State))
processSHA256Block What4 sym
sym SymExpr sym (BaseStructType SHA256State)
st Value sym
blk =
do let ss :: SeqMap (What4 sym)
ss = Value sym -> SeqMap (What4 sym)
forall sym. GenValue sym -> SeqMap sym
fromVSeq Value sym
blk
SymExpr sym ('BaseBVType 32)
b0 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
0
SymExpr sym ('BaseBVType 32)
b1 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
1
SymExpr sym ('BaseBVType 32)
b2 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
2
SymExpr sym ('BaseBVType 32)
b3 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
3
SymExpr sym ('BaseBVType 32)
b4 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
4
SymExpr sym ('BaseBVType 32)
b5 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
5
SymExpr sym ('BaseBVType 32)
b6 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
6
SymExpr sym ('BaseBVType 32)
b7 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
7
SymExpr sym ('BaseBVType 32)
b8 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
8
SymExpr sym ('BaseBVType 32)
b9 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
9
SymExpr sym ('BaseBVType 32)
b10 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
10
SymExpr sym ('BaseBVType 32)
b11 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
11
SymExpr sym ('BaseBVType 32)
b12 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
12
SymExpr sym ('BaseBVType 32)
b13 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
13
SymExpr sym ('BaseBVType 32)
b14 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
14
SymExpr sym ('BaseBVType 32)
b15 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
"processSHA256Block" SeqMap (What4 sym)
ss Integer
15
let args :: Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
args = Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym (BaseStructType SHA256State)
-> Assignment
(SymExpr sym) (EmptyCtx ::> BaseStructType SHA256State)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym (BaseStructType SHA256State)
st Assignment (SymExpr sym) (EmptyCtx ::> BaseStructType SHA256State)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:>
SymExpr sym ('BaseBVType 32)
b0 Assignment
(SymExpr sym)
((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b1 Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b2 Assignment
(SymExpr sym)
((((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b3 Assignment
(SymExpr sym)
(((((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:>
SymExpr sym ('BaseBVType 32)
b4 Assignment
(SymExpr sym)
((((((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((((((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b5 Assignment
(SymExpr sym)
(((((((EmptyCtx ::> BaseStructType SHA256State) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b6 Assignment
(SymExpr sym)
((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b7 Assignment
(SymExpr sym)
(((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:>
SymExpr sym ('BaseBVType 32)
b8 Assignment
(SymExpr sym)
((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b9 Assignment
(SymExpr sym)
(((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b10 Assignment
(SymExpr sym)
((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b11 Assignment
(SymExpr sym)
(((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:>
SymExpr sym ('BaseBVType 32)
b12 Assignment
(SymExpr sym)
((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b13 Assignment
(SymExpr sym)
(((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b14 Assignment
(SymExpr sym)
((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
b15
let ret :: BaseTypeRepr (BaseStructType SHA256State)
ret = SymExpr sym (BaseStructType SHA256State)
-> BaseTypeRepr (BaseStructType SHA256State)
forall (e :: BaseType -> *) (tp :: BaseType).
IsExpr e =>
e tp -> BaseTypeRepr tp
W4.exprType SymExpr sym (BaseStructType SHA256State)
st
SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State)
fn <- IO
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State))
-> W4Eval
sym
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State))
-> W4Eval
sym
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State)))
-> IO
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State))
-> W4Eval
sym
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State))
forall a b. (a -> b) -> a -> b
$ What4 sym
-> Text
-> Assignment
BaseTypeRepr
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> BaseTypeRepr (BaseStructType SHA256State)
-> IO
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State))
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
What4 sym
-> Text
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
getUninterpFn What4 sym
sym Text
"processSHA256Block" ((forall (x :: BaseType). SymExpr sym x -> BaseTypeRepr x)
-> Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> Assignment
BaseTypeRepr
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k l (t :: (k -> *) -> l -> *) (f :: k -> *) (g :: k -> *).
FunctorFC t =>
(forall (x :: k). f x -> g x) -> forall (x :: l). t f x -> t g x
fmapFC forall (x :: BaseType). SymExpr sym x -> BaseTypeRepr x
forall (e :: BaseType -> *) (tp :: BaseType).
IsExpr e =>
e tp -> BaseTypeRepr tp
W4.exprType Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
args) BaseTypeRepr (BaseStructType SHA256State)
ret
IO (SymExpr sym (BaseStructType SHA256State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseStructType SHA256State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State)))
-> IO (SymExpr sym (BaseStructType SHA256State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA256State))
forall a b. (a -> b) -> a -> b
$ sym
-> SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State)
-> Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> IO (SymExpr sym (BaseStructType SHA256State))
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
sym
-> SymFn sym args ret
-> Assignment (SymExpr sym) args
-> IO (SymExpr sym ret)
W4.applySymFn (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
(BaseStructType SHA256State)
fn Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA256State)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
args
processSHA512Block :: W4.IsSymExprBuilder sym =>
What4 sym ->
W4.SymExpr sym (W4.BaseStructType SHA512State) ->
Value sym ->
SEval (What4 sym) (W4.SymExpr sym (W4.BaseStructType SHA512State))
processSHA512Block :: What4 sym
-> SymExpr sym (BaseStructType SHA512State)
-> Value sym
-> SEval (What4 sym) (SymExpr sym (BaseStructType SHA512State))
processSHA512Block What4 sym
sym SymExpr sym (BaseStructType SHA512State)
st Value sym
blk =
do let ss :: SeqMap (What4 sym)
ss = Value sym -> SeqMap (What4 sym)
forall sym. GenValue sym -> SeqMap sym
fromVSeq Value sym
blk
SymExpr sym ('BaseBVType 64)
b0 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
0
SymExpr sym ('BaseBVType 64)
b1 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
1
SymExpr sym ('BaseBVType 64)
b2 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
2
SymExpr sym ('BaseBVType 64)
b3 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
3
SymExpr sym ('BaseBVType 64)
b4 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
4
SymExpr sym ('BaseBVType 64)
b5 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
5
SymExpr sym ('BaseBVType 64)
b6 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
6
SymExpr sym ('BaseBVType 64)
b7 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
7
SymExpr sym ('BaseBVType 64)
b8 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
8
SymExpr sym ('BaseBVType 64)
b9 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
9
SymExpr sym ('BaseBVType 64)
b10 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
10
SymExpr sym ('BaseBVType 64)
b11 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
11
SymExpr sym ('BaseBVType 64)
b12 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
12
SymExpr sym ('BaseBVType 64)
b13 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
13
SymExpr sym ('BaseBVType 64)
b14 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
14
SymExpr sym ('BaseBVType 64)
b15 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 64))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
"processSHA512Block" SeqMap (What4 sym)
ss Integer
15
let args :: Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
args = Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym (BaseStructType SHA512State)
-> Assignment
(SymExpr sym) (EmptyCtx ::> BaseStructType SHA512State)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym (BaseStructType SHA512State)
st Assignment (SymExpr sym) (EmptyCtx ::> BaseStructType SHA512State)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:>
SymExpr sym ('BaseBVType 64)
b0 Assignment
(SymExpr sym)
((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b1 Assignment
(SymExpr sym)
(((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b2 Assignment
(SymExpr sym)
((((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b3 Assignment
(SymExpr sym)
(((((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((((((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:>
SymExpr sym ('BaseBVType 64)
b4 Assignment
(SymExpr sym)
((((((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((((((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b5 Assignment
(SymExpr sym)
(((((((EmptyCtx ::> BaseStructType SHA512State) ::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b6 Assignment
(SymExpr sym)
((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b7 Assignment
(SymExpr sym)
(((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:>
SymExpr sym ('BaseBVType 64)
b8 Assignment
(SymExpr sym)
((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b9 Assignment
(SymExpr sym)
(((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b10 Assignment
(SymExpr sym)
((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b11 Assignment
(SymExpr sym)
(((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:>
SymExpr sym ('BaseBVType 64)
b12 Assignment
(SymExpr sym)
((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b13 Assignment
(SymExpr sym)
(((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b14 Assignment
(SymExpr sym)
((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> SymExpr sym ('BaseBVType 64)
-> Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 64)
b15
let ret :: BaseTypeRepr (BaseStructType SHA512State)
ret = SymExpr sym (BaseStructType SHA512State)
-> BaseTypeRepr (BaseStructType SHA512State)
forall (e :: BaseType -> *) (tp :: BaseType).
IsExpr e =>
e tp -> BaseTypeRepr tp
W4.exprType SymExpr sym (BaseStructType SHA512State)
st
SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State)
fn <- IO
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State))
-> W4Eval
sym
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State))
-> W4Eval
sym
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State)))
-> IO
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State))
-> W4Eval
sym
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State))
forall a b. (a -> b) -> a -> b
$ What4 sym
-> Text
-> Assignment
BaseTypeRepr
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> BaseTypeRepr (BaseStructType SHA512State)
-> IO
(SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State))
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
What4 sym
-> Text
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
getUninterpFn What4 sym
sym Text
"processSHA512Block" ((forall (x :: BaseType). SymExpr sym x -> BaseTypeRepr x)
-> Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> Assignment
BaseTypeRepr
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
forall k l (t :: (k -> *) -> l -> *) (f :: k -> *) (g :: k -> *).
FunctorFC t =>
(forall (x :: k). f x -> g x) -> forall (x :: l). t f x -> t g x
fmapFC forall (x :: BaseType). SymExpr sym x -> BaseTypeRepr x
forall (e :: BaseType -> *) (tp :: BaseType).
IsExpr e =>
e tp -> BaseTypeRepr tp
W4.exprType Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
args) BaseTypeRepr (BaseStructType SHA512State)
ret
IO (SymExpr sym (BaseStructType SHA512State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SymExpr sym (BaseStructType SHA512State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State)))
-> IO (SymExpr sym (BaseStructType SHA512State))
-> W4Eval sym (SymExpr sym (BaseStructType SHA512State))
forall a b. (a -> b) -> a -> b
$ sym
-> SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State)
-> Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
-> IO (SymExpr sym (BaseStructType SHA512State))
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
sym
-> SymFn sym args ret
-> Assignment (SymExpr sym) args
-> IO (SymExpr sym ret)
W4.applySymFn (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymFn
sym
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
(BaseStructType SHA512State)
fn Assignment
(SymExpr sym)
(((((((((((((((((EmptyCtx ::> BaseStructType SHA512State)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
::> 'BaseBVType 64)
args
addUninterpWarning :: MonadIO m => What4 sym -> Text -> m ()
addUninterpWarning :: What4 sym -> Text -> m ()
addUninterpWarning What4 sym
sym Text
nm = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MVar (Set Text) -> (Set Text -> IO (Set Text)) -> IO ()
forall a. MVar a -> (a -> IO a) -> IO ()
modifyMVar_ (What4 sym -> MVar (Set Text)
forall sym. What4 sym -> MVar (Set Text)
w4uninterpWarns What4 sym
sym) (Set Text -> IO (Set Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Set Text -> IO (Set Text))
-> (Set Text -> Set Text) -> Set Text -> IO (Set Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Set Text -> Set Text
forall a. Ord a => a -> Set a -> Set a
Set.insert Text
nm))
getUninterpFn :: W4.IsSymExprBuilder sym =>
What4 sym ->
Text ->
Assignment W4.BaseTypeRepr args ->
W4.BaseTypeRepr ret ->
IO (W4.SymFn sym args ret)
getUninterpFn :: What4 sym
-> Text
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
getUninterpFn What4 sym
sym Text
funNm Assignment BaseTypeRepr args
args BaseTypeRepr ret
ret =
MVar (What4FunCache sym)
-> (What4FunCache sym
-> IO (What4FunCache sym, SymFn sym args ret))
-> IO (SymFn sym args ret)
forall a b. MVar a -> (a -> IO (a, b)) -> IO b
modifyMVar (What4 sym -> MVar (What4FunCache sym)
forall sym. What4 sym -> MVar (What4FunCache sym)
w4funs What4 sym
sym) ((What4FunCache sym -> IO (What4FunCache sym, SymFn sym args ret))
-> IO (SymFn sym args ret))
-> (What4FunCache sym
-> IO (What4FunCache sym, SymFn sym args ret))
-> IO (SymFn sym args ret)
forall a b. (a -> b) -> a -> b
$ \What4FunCache sym
m ->
case Text -> What4FunCache sym -> Maybe (SomeSymFn sym)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
funNm What4FunCache sym
m of
Maybe (SomeSymFn sym)
Nothing ->
do SymFn sym args ret
fn <- sym
-> SolverSymbol
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
sym
-> SolverSymbol
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
W4.freshTotalUninterpFn (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) (String -> SolverSymbol
W4.safeSymbol (Text -> String
Text.unpack Text
funNm)) Assignment BaseTypeRepr args
args BaseTypeRepr ret
ret
let m' :: What4FunCache sym
m' = Text -> SomeSymFn sym -> What4FunCache sym -> What4FunCache sym
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Text
funNm (SymFn sym args ret -> SomeSymFn sym
forall sym (args :: Ctx BaseType) (ret :: BaseType).
SymFn sym args ret -> SomeSymFn sym
SomeSymFn SymFn sym args ret
fn) What4FunCache sym
m
(What4FunCache sym, SymFn sym args ret)
-> IO (What4FunCache sym, SymFn sym args ret)
forall (m :: * -> *) a. Monad m => a -> m a
return (What4FunCache sym
m', SymFn sym args ret
fn)
Just (SomeSymFn SymFn sym args ret
fn)
| Just args :~: args
W4.Refl <- Assignment BaseTypeRepr args
-> Assignment BaseTypeRepr args -> Maybe (args :~: args)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
W4.testEquality Assignment BaseTypeRepr args
args (SymFn sym args ret -> Assignment BaseTypeRepr args
forall (fn :: Ctx BaseType -> BaseType -> *) (args :: Ctx BaseType)
(ret :: BaseType).
IsSymFn fn =>
fn args ret -> Assignment BaseTypeRepr args
W4.fnArgTypes SymFn sym args ret
fn)
, Just ret :~: ret
W4.Refl <- BaseTypeRepr ret -> BaseTypeRepr ret -> Maybe (ret :~: ret)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
W4.testEquality BaseTypeRepr ret
ret (SymFn sym args ret -> BaseTypeRepr ret
forall (fn :: Ctx BaseType -> BaseType -> *) (args :: Ctx BaseType)
(ret :: BaseType).
IsSymFn fn =>
fn args ret -> BaseTypeRepr ret
W4.fnReturnType SymFn sym args ret
SymFn sym args ret
fn)
-> (What4FunCache sym, SymFn sym args ret)
-> IO (What4FunCache sym, SymFn sym args ret)
forall (m :: * -> *) a. Monad m => a -> m a
return (What4FunCache sym
m, SymFn sym args ret
SymFn sym args ret
fn)
| Bool
otherwise -> String -> [String] -> IO (What4FunCache sym, SymFn sym args ret)
forall a. HasCallStack => String -> [String] -> a
panic String
"getUninterpFn"
[ String
"Function" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
funNm String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"used at incompatible types"
, String
"Created with types:"
, Assignment BaseTypeRepr args -> String
forall a. Show a => a -> String
show (SymFn sym args ret -> Assignment BaseTypeRepr args
forall (fn :: Ctx BaseType -> BaseType -> *) (args :: Ctx BaseType)
(ret :: BaseType).
IsSymFn fn =>
fn args ret -> Assignment BaseTypeRepr args
W4.fnArgTypes SymFn sym args ret
fn) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" -> " String -> String -> String
forall a. [a] -> [a] -> [a]
++ BaseTypeRepr ret -> String
forall a. Show a => a -> String
show (SymFn sym args ret -> BaseTypeRepr ret
forall (fn :: Ctx BaseType -> BaseType -> *) (args :: Ctx BaseType)
(ret :: BaseType).
IsSymFn fn =>
fn args ret -> BaseTypeRepr ret
W4.fnReturnType SymFn sym args ret
fn)
, String
"Requested at types:"
, Assignment BaseTypeRepr args -> String
forall a. Show a => a -> String
show Assignment BaseTypeRepr args
args String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" -> " String -> String -> String
forall a. [a] -> [a] -> [a]
++ BaseTypeRepr ret -> String
forall a. Show a => a -> String
show BaseTypeRepr ret
ret
]
toWord32 :: W4.IsSymExprBuilder sym =>
What4 sym -> String -> SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (W4.SymBV sym 32)
toWord32 :: What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
nm SeqMap (What4 sym)
ss Integer
i =
do SWord sym
x <- What4 sym
-> String
-> GenValue (What4 sym)
-> SEval (What4 sym) (SWord (What4 sym))
forall sym.
Backend sym =>
sym -> String -> GenValue sym -> SEval sym (SWord sym)
fromVWord What4 sym
sym String
nm (GenValue (What4 sym) -> W4Eval sym (SWord sym))
-> W4Eval sym (GenValue (What4 sym)) -> W4Eval sym (SWord sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SeqMap (What4 sym)
-> Integer -> SEval (What4 sym) (GenValue (What4 sym))
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
ss Integer
i
case SWord sym
x of
SW.DBV SymBV sym w
x' | Just w :~: 32
W4.Refl <- NatRepr w -> NatRepr 32 -> Maybe (w :~: 32)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
W4.testEquality (SymBV sym w -> NatRepr w
forall (e :: BaseType -> *) (w :: Nat).
IsExpr e =>
e (BaseBVType w) -> NatRepr w
W4.bvWidth SymBV sym w
x') (KnownNat 32 => NatRepr 32
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @32) -> SymBV sym 32 -> W4Eval sym (SymBV sym 32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure SymBV sym w
SymBV sym 32
x'
SWord sym
_ -> String -> [String] -> W4Eval sym (SymBV sym 32)
forall a. HasCallStack => String -> [String] -> a
panic String
nm [String
"Unexpected word size", Integer -> String
forall a. Show a => a -> String
show (SWord sym -> Integer
forall sym. SWord sym -> Integer
SW.bvWidth SWord sym
x)]
fromWord32 :: W4.IsSymExprBuilder sym => W4.SymBV sym 32 -> SEval (What4 sym) (Value sym)
fromWord32 :: SymBV sym 32 -> SEval (What4 sym) (Value sym)
fromWord32 = Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> (SymBV sym 32 -> Value sym)
-> SymBV sym 32
-> W4Eval sym (Value sym)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> SEval (What4 sym) (WordValue (What4 sym)) -> Value sym
forall sym. Integer -> SEval sym (WordValue sym) -> GenValue sym
VWord Integer
32 (W4Eval sym (WordValue (What4 sym)) -> Value sym)
-> (SymBV sym 32 -> W4Eval sym (WordValue (What4 sym)))
-> SymBV sym 32
-> Value sym
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WordValue (What4 sym) -> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WordValue (What4 sym) -> W4Eval sym (WordValue (What4 sym)))
-> (SymBV sym 32 -> WordValue (What4 sym))
-> SymBV sym 32
-> W4Eval sym (WordValue (What4 sym))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SWord sym -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal (SWord sym -> WordValue (What4 sym))
-> (SymBV sym 32 -> SWord sym)
-> SymBV sym 32
-> WordValue (What4 sym)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SymBV sym 32 -> SWord sym
forall sym (w :: Nat).
(IsExpr (SymExpr sym), 1 <= w) =>
SymBV sym w -> SWord sym
SW.DBV
toWord64 :: W4.IsSymExprBuilder sym =>
What4 sym -> String -> SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (W4.SymBV sym 64)
toWord64 :: What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 64)
toWord64 What4 sym
sym String
nm SeqMap (What4 sym)
ss Integer
i =
do SWord sym
x <- What4 sym
-> String
-> GenValue (What4 sym)
-> SEval (What4 sym) (SWord (What4 sym))
forall sym.
Backend sym =>
sym -> String -> GenValue sym -> SEval sym (SWord sym)
fromVWord What4 sym
sym String
nm (GenValue (What4 sym) -> W4Eval sym (SWord sym))
-> W4Eval sym (GenValue (What4 sym)) -> W4Eval sym (SWord sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< SeqMap (What4 sym)
-> Integer -> SEval (What4 sym) (GenValue (What4 sym))
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
ss Integer
i
case SWord sym
x of
SW.DBV SymBV sym w
x' | Just w :~: 64
W4.Refl <- NatRepr w -> NatRepr 64 -> Maybe (w :~: 64)
forall k (f :: k -> *) (a :: k) (b :: k).
TestEquality f =>
f a -> f b -> Maybe (a :~: b)
W4.testEquality (SymBV sym w -> NatRepr w
forall (e :: BaseType -> *) (w :: Nat).
IsExpr e =>
e (BaseBVType w) -> NatRepr w
W4.bvWidth SymBV sym w
x') (KnownNat 64 => NatRepr 64
forall (n :: Nat). KnownNat n => NatRepr n
W4.knownNat @64) -> SymBV sym 64 -> W4Eval sym (SymBV sym 64)
forall (f :: * -> *) a. Applicative f => a -> f a
pure SymBV sym w
SymBV sym 64
x'
SWord sym
_ -> String -> [String] -> W4Eval sym (SymBV sym 64)
forall a. HasCallStack => String -> [String] -> a
panic String
nm [String
"Unexpected word size", Integer -> String
forall a. Show a => a -> String
show (SWord sym -> Integer
forall sym. SWord sym -> Integer
SW.bvWidth SWord sym
x)]
fromWord64 :: W4.IsSymExprBuilder sym => W4.SymBV sym 64 -> SEval (What4 sym) (Value sym)
fromWord64 :: SymBV sym 64 -> SEval (What4 sym) (Value sym)
fromWord64 = Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> (SymBV sym 64 -> Value sym)
-> SymBV sym 64
-> W4Eval sym (Value sym)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> SEval (What4 sym) (WordValue (What4 sym)) -> Value sym
forall sym. Integer -> SEval sym (WordValue sym) -> GenValue sym
VWord Integer
64 (W4Eval sym (WordValue (What4 sym)) -> Value sym)
-> (SymBV sym 64 -> W4Eval sym (WordValue (What4 sym)))
-> SymBV sym 64
-> Value sym
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WordValue (What4 sym) -> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WordValue (What4 sym) -> W4Eval sym (WordValue (What4 sym)))
-> (SymBV sym 64 -> WordValue (What4 sym))
-> SymBV sym 64
-> W4Eval sym (WordValue (What4 sym))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SWord sym -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal (SWord sym -> WordValue (What4 sym))
-> (SymBV sym 64 -> SWord sym)
-> SymBV sym 64
-> WordValue (What4 sym)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SymBV sym 64 -> SWord sym
forall sym (w :: Nat).
(IsExpr (SymExpr sym), 1 <= w) =>
SymBV sym w -> SWord sym
SW.DBV
applyAESStateFunc :: forall sym. W4.IsSymExprBuilder sym =>
What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
applyAESStateFunc :: What4 sym -> Text -> Value sym -> SEval (What4 sym) (Value sym)
applyAESStateFunc What4 sym
sym Text
funNm Value sym
x =
do let ss :: SeqMap (What4 sym)
ss = Value sym -> SeqMap (What4 sym)
forall sym. GenValue sym -> SeqMap sym
fromVSeq Value sym
x
SymExpr sym ('BaseBVType 32)
w0 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
nm SeqMap (What4 sym)
ss Integer
0
SymExpr sym ('BaseBVType 32)
w1 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
nm SeqMap (What4 sym)
ss Integer
1
SymExpr sym ('BaseBVType 32)
w2 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
nm SeqMap (What4 sym)
ss Integer
2
SymExpr sym ('BaseBVType 32)
w3 <- What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymExpr sym ('BaseBVType 32))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> String
-> SeqMap (What4 sym)
-> Integer
-> SEval (What4 sym) (SymBV sym 32)
toWord32 What4 sym
sym String
nm SeqMap (What4 sym)
ss Integer
3
SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
fn <- IO
(SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
-> W4Eval
sym
(SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
-> W4Eval
sym
(SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))))
-> IO
(SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
-> W4Eval
sym
(SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
forall a b. (a -> b) -> a -> b
$ What4 sym
-> Text
-> Assignment
BaseTypeRepr
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> BaseTypeRepr
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
-> IO
(SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
What4 sym
-> Text
-> Assignment BaseTypeRepr args
-> BaseTypeRepr ret
-> IO (SymFn sym args ret)
getUninterpFn What4 sym
sym Text
funNm Assignment
BaseTypeRepr
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
argCtx (Assignment
BaseTypeRepr
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> BaseTypeRepr
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
forall (ctx :: Ctx BaseType).
Assignment BaseTypeRepr ctx -> BaseTypeRepr ('BaseStructType ctx)
W4.BaseStructRepr Assignment
BaseTypeRepr
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
argCtx)
SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
z <- IO
(SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
-> W4Eval
sym
(SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
(SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
-> W4Eval
sym
(SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))))
-> IO
(SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
-> W4Eval
sym
(SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
forall a b. (a -> b) -> a -> b
$ sym
-> SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
-> Assignment
(SymExpr sym)
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> IO
(SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)))
forall sym (args :: Ctx BaseType) (ret :: BaseType).
IsSymExprBuilder sym =>
sym
-> SymFn sym args ret
-> Assignment (SymExpr sym) args
-> IO (SymExpr sym ret)
W4.applySymFn (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymFn
sym
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
fn (Assignment (SymExpr sym) EmptyCtx
forall k (ctx :: Ctx k) (f :: k -> *).
(ctx ~ EmptyCtx) =>
Assignment f ctx
Empty Assignment (SymExpr sym) EmptyCtx
-> SymExpr sym ('BaseBVType 32)
-> Assignment (SymExpr sym) (EmptyCtx ::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
w0 Assignment (SymExpr sym) (EmptyCtx ::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym) ((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
w1 Assignment
(SymExpr sym) ((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
(((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
w2 Assignment
(SymExpr sym)
(((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
-> SymExpr sym ('BaseBVType 32)
-> Assignment
(SymExpr sym)
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (ctx' :: Ctx k) (f :: k -> *) (ctx :: Ctx k) (tp :: k).
(ctx' ~ (ctx ::> tp)) =>
Assignment f ctx -> f tp -> Assignment f ctx'
:> SymExpr sym ('BaseBVType 32)
w3)
Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$ Integer -> SeqMap (What4 sym) -> Value sym
forall sym. Integer -> SeqMap sym -> GenValue sym
VSeq Integer
4 (SeqMap (What4 sym) -> Value sym)
-> SeqMap (What4 sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap \Integer
i ->
if | Integer
i Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 -> SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym)
forall sym.
IsSymExprBuilder sym =>
SymBV sym 32 -> SEval (What4 sym) (Value sym)
fromWord32 (SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym
-> SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
-> Index
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseBVType 32)
-> IO (SymExpr sym ('BaseBVType 32))
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
z (forall k (n :: Nat) (ctx :: Ctx k) (r :: k).
Idx n ctx r =>
Index ctx r
forall (ctx :: Ctx BaseType) (r :: BaseType).
Idx 0 ctx r =>
Index ctx r
natIndex @0))
| Integer
i Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
1 -> SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym)
forall sym.
IsSymExprBuilder sym =>
SymBV sym 32 -> SEval (What4 sym) (Value sym)
fromWord32 (SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym
-> SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
-> Index
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseBVType 32)
-> IO (SymExpr sym ('BaseBVType 32))
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
z (forall k (n :: Nat) (ctx :: Ctx k) (r :: k).
Idx n ctx r =>
Index ctx r
forall (ctx :: Ctx BaseType) (r :: BaseType).
Idx 1 ctx r =>
Index ctx r
natIndex @1))
| Integer
i Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
2 -> SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym)
forall sym.
IsSymExprBuilder sym =>
SymBV sym 32 -> SEval (What4 sym) (Value sym)
fromWord32 (SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym
-> SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
-> Index
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseBVType 32)
-> IO (SymExpr sym ('BaseBVType 32))
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
z (forall k (n :: Nat) (ctx :: Ctx k) (r :: k).
Idx n ctx r =>
Index ctx r
forall (ctx :: Ctx BaseType) (r :: BaseType).
Idx 2 ctx r =>
Index ctx r
natIndex @2))
| Integer
i Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
3 -> SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym)
forall sym.
IsSymExprBuilder sym =>
SymBV sym 32 -> SEval (What4 sym) (Value sym)
fromWord32 (SymExpr sym ('BaseBVType 32) -> W4Eval sym (Value sym))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (SymExpr sym ('BaseBVType 32))
-> W4Eval sym (SymExpr sym ('BaseBVType 32))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym
-> SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
-> Index
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
('BaseBVType 32)
-> IO (SymExpr sym ('BaseBVType 32))
forall sym (flds :: Ctx BaseType) (tp :: BaseType).
IsExprBuilder sym =>
sym -> SymStruct sym flds -> Index flds tp -> IO (SymExpr sym tp)
W4.structField (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SymExpr
sym
('BaseStructType
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32))
z (forall k (n :: Nat) (ctx :: Ctx k) (r :: k).
Idx n ctx r =>
Index ctx r
forall (ctx :: Ctx BaseType) (r :: BaseType).
Idx 3 ctx r =>
Index ctx r
natIndex @3))
| Bool
otherwise -> What4 sym -> Integer -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> Integer -> SEval sym a
invalidIndex What4 sym
sym Integer
i
where
nm :: String
nm = Text -> String
Text.unpack Text
funNm
argCtx :: Assignment W4.BaseTypeRepr
(EmptyCtx ::> W4.BaseBVType 32 ::> W4.BaseBVType 32 ::> W4.BaseBVType 32 ::> W4.BaseBVType 32)
argCtx :: Assignment
BaseTypeRepr
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
argCtx = Assignment
BaseTypeRepr
((((EmptyCtx ::> 'BaseBVType 32) ::> 'BaseBVType 32)
::> 'BaseBVType 32)
::> 'BaseBVType 32)
forall k (f :: k -> *) (ctx :: k). KnownRepr f ctx => f ctx
W4.knownRepr
sshrV :: W4.IsSymExprBuilder sym => What4 sym -> Value sym
sshrV :: What4 sym -> Value sym
sshrV What4 sym
sym =
(Nat' -> Value sym) -> Value sym
forall sym. Backend sym => (Nat' -> GenValue sym) -> GenValue sym
nlam ((Nat' -> Value sym) -> Value sym)
-> (Nat' -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \(Nat Integer
n) ->
(TValue -> Value sym) -> Value sym
forall sym. Backend sym => (TValue -> GenValue sym) -> GenValue sym
tlam ((TValue -> Value sym) -> Value sym)
-> (TValue -> Value sym) -> Value sym
forall a b. (a -> b) -> a -> b
$ \TValue
ix ->
What4 sym
-> (SWord (What4 sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
Backend sym =>
sym -> (SWord sym -> SEval sym (GenValue sym)) -> GenValue sym
wlam What4 sym
sym ((SWord (What4 sym) -> SEval (What4 sym) (Value sym)) -> Value sym)
-> (SWord (What4 sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SWord (What4 sym)
x -> Value sym -> W4Eval sym (Value sym)
forall (m :: * -> *) a. Monad m => a -> m a
return (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$
(SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam ((SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym)
-> (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall a b. (a -> b) -> a -> b
$ \SEval (What4 sym) (Value sym)
y ->
SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
y W4Eval sym (Value sym)
-> (Value sym
-> W4Eval
sym (Either (SymExpr sym BaseIntegerType) (WordValue (What4 sym))))
-> W4Eval
sym (Either (SymExpr sym BaseIntegerType) (WordValue (What4 sym)))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= What4 sym
-> String
-> TValue
-> Value sym
-> SEval
(What4 sym) (Either (SInteger (What4 sym)) (WordValue (What4 sym)))
forall sym.
Backend sym =>
sym
-> String
-> TValue
-> GenValue sym
-> SEval sym (Either (SInteger sym) (WordValue sym))
asIndex What4 sym
sym String
">>$" TValue
ix W4Eval
sym (Either (SymExpr sym BaseIntegerType) (WordValue (What4 sym)))
-> (Either (SymExpr sym BaseIntegerType) (WordValue (What4 sym))
-> W4Eval sym (Value sym))
-> W4Eval sym (Value sym)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left SymExpr sym BaseIntegerType
i ->
do SymExpr sym BaseBoolType
pneg <- What4 sym
-> SInteger (What4 sym)
-> SInteger (What4 sym)
-> SEval (What4 sym) (SBit (What4 sym))
forall sym.
Backend sym =>
sym -> SInteger sym -> SInteger sym -> SEval sym (SBit sym)
intLessThan What4 sym
sym SymExpr sym BaseIntegerType
SInteger (What4 sym)
i (SymExpr sym BaseIntegerType
-> W4Eval sym (SymExpr sym BaseBoolType))
-> W4Eval sym (SymExpr sym BaseIntegerType)
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< What4 sym -> Integer -> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SEval sym (SInteger sym)
integerLit What4 sym
sym Integer
0
SWord sym
zneg <- do SymExpr sym BaseIntegerType
i' <- What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym)
shiftShrink What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
ix (SymExpr sym BaseIntegerType
-> W4Eval sym (SymExpr sym BaseIntegerType))
-> W4Eval sym (SymExpr sym BaseIntegerType)
-> W4Eval sym (SymExpr sym BaseIntegerType)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< What4 sym
-> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> SInteger sym -> SEval sym (SInteger sym)
intNegate What4 sym
sym SymExpr sym BaseIntegerType
SInteger (What4 sym)
i
SWord sym
amt <- What4 sym
-> Integer
-> SInteger (What4 sym)
-> SEval (What4 sym) (SWord (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SInteger sym -> SEval sym (SWord sym)
wordFromInt What4 sym
sym Integer
n SymExpr sym BaseIntegerType
SInteger (What4 sym)
i'
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvShl (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
SWord (What4 sym)
x SWord sym
amt
SWord sym
zpos <- do SymExpr sym BaseIntegerType
i' <- What4 sym
-> Nat'
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Nat' -> TValue -> SInteger sym -> SEval sym (SInteger sym)
shiftShrink What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
ix SymExpr sym BaseIntegerType
SInteger (What4 sym)
i
SWord sym
amt <- What4 sym
-> Integer
-> SInteger (What4 sym)
-> SEval (What4 sym) (SWord (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SInteger sym -> SEval sym (SWord sym)
wordFromInt What4 sym
sym Integer
n SymExpr sym BaseIntegerType
SInteger (What4 sym)
i'
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvAshr (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
SWord (What4 sym)
x SWord sym
amt
Value sym -> W4Eval sym (Value sym)
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> SEval (What4 sym) (WordValue (What4 sym)) -> Value sym
forall sym. Integer -> SEval sym (WordValue sym) -> GenValue sym
VWord (SWord sym -> Integer
forall sym. SWord sym -> Integer
SW.bvWidth SWord sym
SWord (What4 sym)
x) (SWord sym -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal (SWord sym -> WordValue (What4 sym))
-> W4Eval sym (SWord sym) -> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> What4 sym
-> SBit (What4 sym)
-> SWord (What4 sym)
-> SWord (What4 sym)
-> SEval (What4 sym) (SWord (What4 sym))
forall sym.
Backend sym =>
sym -> SBit sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
iteWord What4 sym
sym SymExpr sym BaseBoolType
SBit (What4 sym)
pneg SWord sym
SWord (What4 sym)
zneg SWord sym
SWord (What4 sym)
zpos))
Right WordValue (What4 sym)
wv ->
do SWord sym
amt <- What4 sym
-> WordValue (What4 sym) -> SEval (What4 sym) (SWord (What4 sym))
forall sym.
Backend sym =>
sym -> WordValue sym -> SEval sym (SWord sym)
asWordVal What4 sym
sym WordValue (What4 sym)
wv
Value sym -> W4Eval sym (Value sym)
forall (m :: * -> *) a. Monad m => a -> m a
return (Integer -> SEval (What4 sym) (WordValue (What4 sym)) -> Value sym
forall sym. Integer -> SEval sym (WordValue sym) -> GenValue sym
VWord (SWord sym -> Integer
forall sym. SWord sym -> Integer
SW.bvWidth SWord sym
SWord (What4 sym)
x) (SWord sym -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal (SWord sym -> WordValue (What4 sym))
-> W4Eval sym (SWord sym) -> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvAshr (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
SWord (What4 sym)
x SWord sym
amt))
indexFront_int ::
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
SeqMap (What4 sym) ->
TValue ->
SInteger (What4 sym) ->
SEval (What4 sym) (Value sym)
indexFront_int :: What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym)
indexFront_int What4 sym
sym Nat'
mblen TValue
_a SeqMap (What4 sym)
xs TValue
ix SInteger (What4 sym)
idx
| Just Integer
i <- SymExpr sym BaseIntegerType -> Maybe Integer
forall (e :: BaseType -> *).
IsExpr e =>
e BaseIntegerType -> Maybe Integer
W4.asInteger SymExpr sym BaseIntegerType
SInteger (What4 sym)
idx
= SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (Value sym)
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
xs Integer
i
| (Integer
lo, Just Integer
hi) <- (Integer, Maybe Integer)
bounds
= (Integer -> W4Eval sym (Value sym) -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> [Integer] -> W4Eval sym (Value sym)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Integer -> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
f SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
def [Integer
lo .. Integer
hi]
| Bool
otherwise
= IO (Value sym) -> W4Eval sym (Value sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Unsupported -> IO (Value sym)
forall a e. Exception e => e -> a
X.throw (String -> Unsupported
UnsupportedSymbolicOp String
"unbounded integer indexing"))
where
w4sym :: sym
w4sym = What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym
def :: SEval (What4 sym) (Value sym)
def = What4 sym -> EvalError -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> EvalError -> SEval sym a
raiseError What4 sym
sym (Maybe Integer -> EvalError
InvalidIndex Maybe Integer
forall a. Maybe a
Nothing)
f :: Integer -> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
f Integer
n W4Eval sym (Value sym)
y =
do SymExpr sym BaseBoolType
p <- IO (SymExpr sym BaseBoolType)
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym
-> SymExpr sym BaseIntegerType
-> SymExpr sym BaseIntegerType
-> IO (SymExpr sym BaseBoolType)
forall sym.
IsExprBuilder sym =>
sym -> SymInteger sym -> SymInteger sym -> IO (Pred sym)
W4.intEq sym
w4sym SymExpr sym BaseIntegerType
SInteger (What4 sym)
idx (SymExpr sym BaseIntegerType -> IO (SymExpr sym BaseBoolType))
-> IO (SymExpr sym BaseIntegerType)
-> IO (SymExpr sym BaseBoolType)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> Integer -> IO (SymExpr sym BaseIntegerType)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> IO (SymInteger sym)
W4.intLit sym
w4sym Integer
n)
What4 sym
-> SBit (What4 sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym
-> SBit sym
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
iteValue What4 sym
sym SymExpr sym BaseBoolType
SBit (What4 sym)
p (SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (Value sym)
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
xs Integer
n) SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
y
bounds :: (Integer, Maybe Integer)
bounds =
(case ValueRange Integer -> ValueBound Integer
forall tp. ValueRange tp -> ValueBound tp
W4.rangeLowBound (SymExpr sym BaseIntegerType -> ValueRange Integer
forall (e :: BaseType -> *).
IsExpr e =>
e BaseIntegerType -> ValueRange Integer
W4.integerBounds SymExpr sym BaseIntegerType
SInteger (What4 sym)
idx) of
W4.Inclusive Integer
l -> Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
max Integer
l Integer
0
ValueBound Integer
_ -> Integer
0
, case (Maybe Integer
maxIdx, ValueRange Integer -> ValueBound Integer
forall tp. ValueRange tp -> ValueBound tp
W4.rangeHiBound (SymExpr sym BaseIntegerType -> ValueRange Integer
forall (e :: BaseType -> *).
IsExpr e =>
e BaseIntegerType -> ValueRange Integer
W4.integerBounds SymExpr sym BaseIntegerType
SInteger (What4 sym)
idx)) of
(Just Integer
n, W4.Inclusive Integer
h) -> Integer -> Maybe Integer
forall a. a -> Maybe a
Just (Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
min Integer
n Integer
h)
(Just Integer
n, ValueBound Integer
_) -> Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
n
(Maybe Integer, ValueBound Integer)
_ -> Maybe Integer
forall a. Maybe a
Nothing
)
maxIdx :: Maybe Integer
maxIdx =
case (Nat'
mblen, TValue
ix) of
(Nat Integer
n, TVIntMod Integer
m) -> Integer -> Maybe Integer
forall a. a -> Maybe a
Just (Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
min (Integer -> Integer
forall a. Integral a => a -> Integer
toInteger Integer
n) (Integer -> Integer
forall a. Integral a => a -> Integer
toInteger Integer
m))
(Nat Integer
n, TValue
_) -> Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
n
(Nat'
_ , TVIntMod Integer
m) -> Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
m
(Nat', TValue)
_ -> Maybe Integer
forall a. Maybe a
Nothing
indexBack_int ::
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
SeqMap (What4 sym) ->
TValue ->
SInteger (What4 sym) ->
SEval (What4 sym) (Value sym)
indexBack_int :: What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym)
indexBack_int What4 sym
sym (Nat Integer
n) TValue
a SeqMap (What4 sym)
xs TValue
ix SInteger (What4 sym)
idx = What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SInteger (What4 sym)
-> SEval (What4 sym) (Value sym)
indexFront_int What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
a (Integer -> SeqMap (What4 sym) -> SeqMap (What4 sym)
forall sym. Integer -> SeqMap sym -> SeqMap sym
reverseSeqMap Integer
n SeqMap (What4 sym)
xs) TValue
ix SInteger (What4 sym)
idx
indexBack_int What4 sym
_ Nat'
Inf TValue
_ SeqMap (What4 sym)
_ TValue
_ SInteger (What4 sym)
_ = String -> [String] -> W4Eval sym (Value sym)
forall a. String -> [String] -> a
evalPanic String
"Expected finite sequence" [String
"indexBack_int"]
indexFront_word ::
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
SeqMap (What4 sym) ->
TValue ->
SWord (What4 sym) ->
SEval (What4 sym) (Value sym)
indexFront_word :: What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym)
indexFront_word What4 sym
sym Nat'
mblen TValue
_a SeqMap (What4 sym)
xs TValue
_ix SWord (What4 sym)
idx
| Just Integer
i <- SWord sym -> Maybe Integer
forall sym. IsExprBuilder sym => SWord sym -> Maybe Integer
SW.bvAsUnsignedInteger SWord sym
SWord (What4 sym)
idx
= SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (Value sym)
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
xs Integer
i
| Bool
otherwise
= (Integer -> W4Eval sym (Value sym) -> W4Eval sym (Value sym))
-> W4Eval sym (Value sym) -> [Integer] -> W4Eval sym (Value sym)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Integer -> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
f SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
def [Integer]
idxs
where
w4sym :: sym
w4sym = What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym
w :: Integer
w = SWord sym -> Integer
forall sym. SWord sym -> Integer
SW.bvWidth SWord sym
SWord (What4 sym)
idx
def :: SEval (What4 sym) (Value sym)
def = What4 sym -> EvalError -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> EvalError -> SEval sym a
raiseError What4 sym
sym (Maybe Integer -> EvalError
InvalidIndex Maybe Integer
forall a. Maybe a
Nothing)
f :: Integer -> W4Eval sym (Value sym) -> W4Eval sym (Value sym)
f Integer
n W4Eval sym (Value sym)
y =
do SymExpr sym BaseBoolType
p <- IO (SymExpr sym BaseBoolType)
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym -> SWord sym -> SWord sym -> IO (SymExpr sym BaseBoolType)
PredBin
SW.bvEq sym
w4sym SWord sym
SWord (What4 sym)
idx (SWord sym -> IO (SymExpr sym BaseBoolType))
-> IO (SWord sym) -> IO (SymExpr sym BaseBoolType)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> Integer -> Integer -> IO (SWord sym)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> Integer -> IO (SWord sym)
SW.bvLit sym
w4sym Integer
w Integer
n)
What4 sym
-> SBit (What4 sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym
-> SBit sym
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
iteValue What4 sym
sym SymExpr sym BaseBoolType
SBit (What4 sym)
p (SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (Value sym)
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
xs Integer
n) SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
y
maxIdx :: Integer
maxIdx =
case Nat'
mblen of
Nat Integer
n | Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
2Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
w -> Integer
nInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
1
Nat'
_ -> Integer
2Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
w Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1
idxs :: [Integer]
idxs =
case SWord sym -> Maybe (Integer, Integer)
forall sym.
IsExprBuilder sym =>
SWord sym -> Maybe (Integer, Integer)
SW.unsignedBVBounds SWord sym
SWord (What4 sym)
idx of
Just (Integer
lo, Integer
hi) -> [Integer
lo .. Integer -> Integer -> Integer
forall a. Ord a => a -> a -> a
min Integer
hi Integer
maxIdx]
Maybe (Integer, Integer)
_ -> [Integer
0 .. Integer
maxIdx]
indexBack_word ::
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
SeqMap (What4 sym) ->
TValue ->
SWord (What4 sym) ->
SEval (What4 sym) (Value sym)
indexBack_word :: What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym)
indexBack_word What4 sym
sym (Nat Integer
n) TValue
a SeqMap (What4 sym)
xs TValue
ix SWord (What4 sym)
idx = What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> SWord (What4 sym)
-> SEval (What4 sym) (Value sym)
indexFront_word What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
a (Integer -> SeqMap (What4 sym) -> SeqMap (What4 sym)
forall sym. Integer -> SeqMap sym -> SeqMap sym
reverseSeqMap Integer
n SeqMap (What4 sym)
xs) TValue
ix SWord (What4 sym)
idx
indexBack_word What4 sym
_ Nat'
Inf TValue
_ SeqMap (What4 sym)
_ TValue
_ SWord (What4 sym)
_ = String -> [String] -> W4Eval sym (Value sym)
forall a. String -> [String] -> a
evalPanic String
"Expected finite sequence" [String
"indexBack_word"]
indexFront_bits :: forall sym.
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
SeqMap (What4 sym) ->
TValue ->
[SBit (What4 sym)] ->
SEval (What4 sym) (Value sym)
indexFront_bits :: What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym)
indexFront_bits What4 sym
sym Nat'
mblen TValue
_a SeqMap (What4 sym)
xs TValue
_ix [SBit (What4 sym)]
bits0 = Integer -> Int -> [Pred sym] -> W4Eval sym (Value sym)
go Integer
0 ([Pred sym] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Pred sym]
[SBit (What4 sym)]
bits0) [Pred sym]
[SBit (What4 sym)]
bits0
where
go :: Integer -> Int -> [W4.Pred sym] -> W4Eval sym (Value sym)
go :: Integer -> Int -> [Pred sym] -> W4Eval sym (Value sym)
go Integer
i Int
_k []
| Nat Integer
n <- Nat'
mblen
, Integer
i Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
n
= What4 sym -> EvalError -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> EvalError -> SEval sym a
raiseError What4 sym
sym (Maybe Integer -> EvalError
InvalidIndex (Integer -> Maybe Integer
forall a. a -> Maybe a
Just Integer
i))
| Bool
otherwise
= SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (Value sym)
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
xs Integer
i
go Integer
i Int
k (Pred sym
b:[Pred sym]
bs)
| Nat Integer
n <- Nat'
mblen
, (Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` Int
k) Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
n
= What4 sym -> EvalError -> SEval (What4 sym) (Value sym)
forall sym a. Backend sym => sym -> EvalError -> SEval sym a
raiseError What4 sym
sym (Maybe Integer -> EvalError
InvalidIndex Maybe Integer
forall a. Maybe a
Nothing)
| Bool
otherwise
= What4 sym
-> SBit (What4 sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym
-> SBit sym
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
iteValue What4 sym
sym Pred sym
SBit (What4 sym)
b
(Integer -> Int -> [Pred sym] -> W4Eval sym (Value sym)
go ((Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` Int
1) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1) (Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) [Pred sym]
bs)
(Integer -> Int -> [Pred sym] -> W4Eval sym (Value sym)
go (Integer
i Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftL` Int
1) (Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) [Pred sym]
bs)
indexBack_bits ::
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
SeqMap (What4 sym) ->
TValue ->
[SBit (What4 sym)] ->
SEval (What4 sym) (Value sym)
indexBack_bits :: What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym)
indexBack_bits What4 sym
sym (Nat Integer
n) TValue
a SeqMap (What4 sym)
xs TValue
ix [SBit (What4 sym)]
idx = What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> TValue
-> [SBit (What4 sym)]
-> SEval (What4 sym) (Value sym)
indexFront_bits What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
a (Integer -> SeqMap (What4 sym) -> SeqMap (What4 sym)
forall sym. Integer -> SeqMap sym -> SeqMap sym
reverseSeqMap Integer
n SeqMap (What4 sym)
xs) TValue
ix [SBit (What4 sym)]
idx
indexBack_bits What4 sym
_ Nat'
Inf TValue
_ SeqMap (What4 sym)
_ TValue
_ [SBit (What4 sym)]
_ = String -> [String] -> W4Eval sym (Value sym)
forall a. String -> [String] -> a
evalPanic String
"Expected finite sequence" [String
"indexBack_bits"]
wordValueEqualsInteger :: forall sym.
W4.IsSymExprBuilder sym =>
What4 sym ->
WordValue (What4 sym) ->
Integer ->
W4Eval sym (W4.Pred sym)
wordValueEqualsInteger :: What4 sym
-> WordValue (What4 sym) -> Integer -> W4Eval sym (Pred sym)
wordValueEqualsInteger What4 sym
sym WordValue (What4 sym)
wv Integer
i
| What4 sym -> WordValue (What4 sym) -> Integer
forall sym. Backend sym => sym -> WordValue sym -> Integer
wordValueSize What4 sym
sym WordValue (What4 sym)
wv Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer -> Integer
widthInteger Integer
i = Pred sym -> W4Eval sym (Pred sym)
forall (m :: * -> *) a. Monad m => a -> m a
return (sym -> Pred sym
forall sym. IsExprBuilder sym => sym -> Pred sym
W4.falsePred sym
w4sym)
| Bool
otherwise =
case WordValue (What4 sym)
wv of
WordVal SWord (What4 sym)
w -> IO (Pred sym) -> W4Eval sym (Pred sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym -> SWord sym -> SWord sym -> IO (Pred sym)
PredBin
SW.bvEq sym
w4sym SWord sym
SWord (What4 sym)
w (SWord sym -> IO (Pred sym)) -> IO (SWord sym) -> IO (Pred sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> Integer -> Integer -> IO (SWord sym)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> Integer -> IO (SWord sym)
SW.bvLit sym
w4sym (SWord sym -> Integer
forall sym. SWord sym -> Integer
SW.bvWidth SWord sym
SWord (What4 sym)
w) Integer
i)
WordValue (What4 sym)
_ -> IO (Pred sym) -> W4Eval sym (Pred sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Pred sym) -> W4Eval sym (Pred sym))
-> ([Pred sym] -> IO (Pred sym))
-> [Pred sym]
-> W4Eval sym (Pred sym)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> [Pred sym] -> IO (Pred sym)
bitsAre Integer
i ([Pred sym] -> W4Eval sym (Pred sym))
-> W4Eval sym [Pred sym] -> W4Eval sym (Pred sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< What4 sym
-> WordValue (What4 sym) -> SEval (What4 sym) [SBit (What4 sym)]
forall sym.
Backend sym =>
sym -> WordValue sym -> SEval sym [SBit sym]
enumerateWordValueRev What4 sym
sym WordValue (What4 sym)
wv
where
w4sym :: sym
w4sym = What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym
bitsAre :: Integer -> [W4.Pred sym] -> IO (W4.Pred sym)
bitsAre :: Integer -> [Pred sym] -> IO (Pred sym)
bitsAre Integer
n [] = Pred sym -> IO (Pred sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (sym -> Bool -> Pred sym
forall sym. IsExprBuilder sym => sym -> Bool -> Pred sym
W4.backendPred sym
w4sym (Integer
n Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0))
bitsAre Integer
n (Pred sym
b : [Pred sym]
bs) =
do Pred sym
pb <- Bool -> Pred sym -> IO (Pred sym)
bitIs (Integer -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
testBit Integer
n Int
0) Pred sym
b
Pred sym
pbs <- Integer -> [Pred sym] -> IO (Pred sym)
bitsAre (Integer
n Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
`shiftR` Int
1) [Pred sym]
bs
sym -> Pred sym -> Pred sym -> IO (Pred sym)
forall sym.
IsExprBuilder sym =>
sym -> Pred sym -> Pred sym -> IO (Pred sym)
W4.andPred sym
w4sym Pred sym
pb Pred sym
pbs
bitIs :: Bool -> W4.Pred sym -> IO (W4.Pred sym)
bitIs :: Bool -> Pred sym -> IO (Pred sym)
bitIs Bool
b Pred sym
x = if Bool
b then Pred sym -> IO (Pred sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Pred sym
x else sym -> Pred sym -> IO (Pred sym)
forall sym. IsExprBuilder sym => sym -> Pred sym -> IO (Pred sym)
W4.notPred sym
w4sym Pred sym
x
updateFrontSym ::
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
SeqMap (What4 sym) ->
Either (SInteger (What4 sym)) (WordValue (What4 sym)) ->
SEval (What4 sym) (Value sym) ->
SEval (What4 sym) (SeqMap (What4 sym))
updateFrontSym :: What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
updateFrontSym What4 sym
sym Nat'
_len TValue
_eltTy SeqMap (What4 sym)
vs (Left SInteger (What4 sym)
idx) SEval (What4 sym) (Value sym)
val =
case SymExpr sym BaseIntegerType -> Maybe Integer
forall (e :: BaseType -> *).
IsExpr e =>
e BaseIntegerType -> Maybe Integer
W4.asInteger SymExpr sym BaseIntegerType
SInteger (What4 sym)
idx of
Just Integer
i -> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall (m :: * -> *) a. Monad m => a -> m a
return (SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym)))
-> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall a b. (a -> b) -> a -> b
$ SeqMap (What4 sym)
-> Integer -> SEval (What4 sym) (Value sym) -> SeqMap (What4 sym)
forall sym.
SeqMap sym -> Integer -> SEval sym (GenValue sym) -> SeqMap sym
updateSeqMap SeqMap (What4 sym)
vs Integer
i SEval (What4 sym) (Value sym)
val
Maybe Integer
Nothing -> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall (m :: * -> *) a. Monad m => a -> m a
return (SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym)))
-> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap ((Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym))
-> (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall a b. (a -> b) -> a -> b
$ \Integer
i ->
do SymExpr sym BaseBoolType
b <- What4 sym
-> SInteger (What4 sym)
-> SInteger (What4 sym)
-> SEval (What4 sym) (SBit (What4 sym))
forall sym.
Backend sym =>
sym -> SInteger sym -> SInteger sym -> SEval sym (SBit sym)
intEq What4 sym
sym SInteger (What4 sym)
idx (SymExpr sym BaseIntegerType
-> W4Eval sym (SymExpr sym BaseBoolType))
-> W4Eval sym (SymExpr sym BaseIntegerType)
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< What4 sym -> Integer -> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SEval sym (SInteger sym)
integerLit What4 sym
sym Integer
i
What4 sym
-> SBit (What4 sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym
-> SBit sym
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
iteValue What4 sym
sym SymExpr sym BaseBoolType
SBit (What4 sym)
b SEval (What4 sym) (Value sym)
val (SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (Value sym)
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
vs Integer
i)
updateFrontSym What4 sym
sym Nat'
_len TValue
_eltTy SeqMap (What4 sym)
vs (Right WordValue (What4 sym)
wv) SEval (What4 sym) (Value sym)
val =
case WordValue (What4 sym)
wv of
WordVal SWord (What4 sym)
w | Just Integer
j <- SWord sym -> Maybe Integer
forall sym. IsExprBuilder sym => SWord sym -> Maybe Integer
SW.bvAsUnsignedInteger SWord sym
SWord (What4 sym)
w ->
SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall (m :: * -> *) a. Monad m => a -> m a
return (SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym)))
-> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall a b. (a -> b) -> a -> b
$ SeqMap (What4 sym)
-> Integer -> SEval (What4 sym) (Value sym) -> SeqMap (What4 sym)
forall sym.
SeqMap sym -> Integer -> SEval sym (GenValue sym) -> SeqMap sym
updateSeqMap SeqMap (What4 sym)
vs Integer
j SEval (What4 sym) (Value sym)
val
WordValue (What4 sym)
_ ->
SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall (m :: * -> *) sym.
(MonadIO m, Backend sym) =>
SeqMap sym -> m (SeqMap sym)
memoMap (SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym)))
-> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap ((Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym))
-> (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall a b. (a -> b) -> a -> b
$ \Integer
i ->
do SymExpr sym BaseBoolType
b <- What4 sym
-> WordValue (What4 sym)
-> Integer
-> W4Eval sym (SymExpr sym BaseBoolType)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> WordValue (What4 sym) -> Integer -> W4Eval sym (Pred sym)
wordValueEqualsInteger What4 sym
sym WordValue (What4 sym)
wv Integer
i
What4 sym
-> SBit (What4 sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym
-> SBit sym
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
iteValue What4 sym
sym SymExpr sym BaseBoolType
SBit (What4 sym)
b SEval (What4 sym) (Value sym)
val (SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (Value sym)
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
vs Integer
i)
updateBackSym ::
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
SeqMap (What4 sym) ->
Either (SInteger (What4 sym)) (WordValue (What4 sym)) ->
SEval (What4 sym) (Value sym) ->
SEval (What4 sym) (SeqMap (What4 sym))
updateBackSym :: What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
updateBackSym What4 sym
_ Nat'
Inf TValue
_ SeqMap (What4 sym)
_ Either (SInteger (What4 sym)) (WordValue (What4 sym))
_ SEval (What4 sym) (Value sym)
_ = String -> [String] -> W4Eval sym (SeqMap (What4 sym))
forall a. String -> [String] -> a
evalPanic String
"Expected finite sequence" [String
"updateBackSym"]
updateBackSym What4 sym
sym (Nat Integer
n) TValue
_eltTy SeqMap (What4 sym)
vs (Left SInteger (What4 sym)
idx) SEval (What4 sym) (Value sym)
val =
case SymExpr sym BaseIntegerType -> Maybe Integer
forall (e :: BaseType -> *).
IsExpr e =>
e BaseIntegerType -> Maybe Integer
W4.asInteger SymExpr sym BaseIntegerType
SInteger (What4 sym)
idx of
Just Integer
i -> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall (m :: * -> *) a. Monad m => a -> m a
return (SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym)))
-> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall a b. (a -> b) -> a -> b
$ SeqMap (What4 sym)
-> Integer -> SEval (What4 sym) (Value sym) -> SeqMap (What4 sym)
forall sym.
SeqMap sym -> Integer -> SEval sym (GenValue sym) -> SeqMap sym
updateSeqMap SeqMap (What4 sym)
vs (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
i) SEval (What4 sym) (Value sym)
val
Maybe Integer
Nothing -> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall (m :: * -> *) a. Monad m => a -> m a
return (SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym)))
-> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap ((Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym))
-> (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall a b. (a -> b) -> a -> b
$ \Integer
i ->
do SymExpr sym BaseBoolType
b <- What4 sym
-> SInteger (What4 sym)
-> SInteger (What4 sym)
-> SEval (What4 sym) (SBit (What4 sym))
forall sym.
Backend sym =>
sym -> SInteger sym -> SInteger sym -> SEval sym (SBit sym)
intEq What4 sym
sym SInteger (What4 sym)
idx (SymExpr sym BaseIntegerType
-> W4Eval sym (SymExpr sym BaseBoolType))
-> W4Eval sym (SymExpr sym BaseIntegerType)
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< What4 sym -> Integer -> SEval (What4 sym) (SInteger (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SEval sym (SInteger sym)
integerLit What4 sym
sym (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
i)
What4 sym
-> SBit (What4 sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym
-> SBit sym
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
iteValue What4 sym
sym SymExpr sym BaseBoolType
SBit (What4 sym)
b SEval (What4 sym) (Value sym)
val (SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (Value sym)
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
vs Integer
i)
updateBackSym What4 sym
sym (Nat Integer
n) TValue
_eltTy SeqMap (What4 sym)
vs (Right WordValue (What4 sym)
wv) SEval (What4 sym) (Value sym)
val =
case WordValue (What4 sym)
wv of
WordVal SWord (What4 sym)
w | Just Integer
j <- SWord sym -> Maybe Integer
forall sym. IsExprBuilder sym => SWord sym -> Maybe Integer
SW.bvAsUnsignedInteger SWord sym
SWord (What4 sym)
w ->
SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall (m :: * -> *) a. Monad m => a -> m a
return (SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym)))
-> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall a b. (a -> b) -> a -> b
$ SeqMap (What4 sym)
-> Integer -> SEval (What4 sym) (Value sym) -> SeqMap (What4 sym)
forall sym.
SeqMap sym -> Integer -> SEval sym (GenValue sym) -> SeqMap sym
updateSeqMap SeqMap (What4 sym)
vs (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
j) SEval (What4 sym) (Value sym)
val
WordValue (What4 sym)
_ ->
SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall (m :: * -> *) sym.
(MonadIO m, Backend sym) =>
SeqMap sym -> m (SeqMap sym)
memoMap (SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym)))
-> SeqMap (What4 sym) -> W4Eval sym (SeqMap (What4 sym))
forall a b. (a -> b) -> a -> b
$ (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall sym. (Integer -> SEval sym (GenValue sym)) -> SeqMap sym
IndexSeqMap ((Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym))
-> (Integer -> SEval (What4 sym) (Value sym)) -> SeqMap (What4 sym)
forall a b. (a -> b) -> a -> b
$ \Integer
i ->
do SymExpr sym BaseBoolType
b <- What4 sym
-> WordValue (What4 sym)
-> Integer
-> W4Eval sym (SymExpr sym BaseBoolType)
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> WordValue (What4 sym) -> Integer -> W4Eval sym (Pred sym)
wordValueEqualsInteger What4 sym
sym WordValue (What4 sym)
wv (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
i)
What4 sym
-> SBit (What4 sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (Value sym)
forall sym.
Backend sym =>
sym
-> SBit sym
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
-> SEval sym (GenValue sym)
iteValue What4 sym
sym SymExpr sym BaseBoolType
SBit (What4 sym)
b SEval (What4 sym) (Value sym)
val (SeqMap (What4 sym) -> Integer -> SEval (What4 sym) (Value sym)
forall sym. SeqMap sym -> Integer -> SEval sym (GenValue sym)
lookupSeqMap SeqMap (What4 sym)
vs Integer
i)
updateFrontSym_word ::
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
WordValue (What4 sym) ->
Either (SInteger (What4 sym)) (WordValue (What4 sym)) ->
SEval (What4 sym) (GenValue (What4 sym)) ->
SEval (What4 sym) (WordValue (What4 sym))
updateFrontSym_word :: What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
updateFrontSym_word What4 sym
_ Nat'
Inf TValue
_ WordValue (What4 sym)
_ Either (SInteger (What4 sym)) (WordValue (What4 sym))
_ SEval (What4 sym) (GenValue (What4 sym))
_ = String -> [String] -> W4Eval sym (WordValue (What4 sym))
forall a. String -> [String] -> a
evalPanic String
"Expected finite sequence" [String
"updateFrontSym_word"]
updateFrontSym_word What4 sym
sym (Nat Integer
_) TValue
eltTy (LargeBitsVal Integer
n SeqMap (What4 sym)
bv) Either (SInteger (What4 sym)) (WordValue (What4 sym))
idx SEval (What4 sym) (GenValue (What4 sym))
val =
Integer -> SeqMap (What4 sym) -> WordValue (What4 sym)
forall sym. Integer -> SeqMap sym -> WordValue sym
LargeBitsVal Integer
n (SeqMap (What4 sym) -> WordValue (What4 sym))
-> W4Eval sym (SeqMap (What4 sym))
-> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (SeqMap (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
updateFrontSym What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
eltTy SeqMap (What4 sym)
bv Either (SInteger (What4 sym)) (WordValue (What4 sym))
idx SEval (What4 sym) (GenValue (What4 sym))
val
updateFrontSym_word What4 sym
sym (Nat Integer
n) TValue
eltTy (WordVal SWord (What4 sym)
bv) (Left SInteger (What4 sym)
idx) SEval (What4 sym) (GenValue (What4 sym))
val =
do SWord sym
idx' <- What4 sym
-> Integer
-> SInteger (What4 sym)
-> SEval (What4 sym) (SWord (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SInteger sym -> SEval sym (SWord sym)
wordFromInt What4 sym
sym Integer
n SInteger (What4 sym)
idx
What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
updateFrontSym_word What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
eltTy (SWord (What4 sym) -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal SWord (What4 sym)
bv) (WordValue (What4 sym)
-> Either (SymExpr sym BaseIntegerType) (WordValue (What4 sym))
forall a b. b -> Either a b
Right (SWord (What4 sym) -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal SWord sym
SWord (What4 sym)
idx')) SEval (What4 sym) (GenValue (What4 sym))
val
updateFrontSym_word What4 sym
sym (Nat Integer
n) TValue
eltTy WordValue (What4 sym)
bv (Right WordValue (What4 sym)
wv) SEval (What4 sym) (GenValue (What4 sym))
val =
case WordValue (What4 sym)
wv of
WordVal SWord (What4 sym)
idx
| Just Integer
j <- SWord sym -> Maybe Integer
forall sym. IsExprBuilder sym => SWord sym -> Maybe Integer
SW.bvAsUnsignedInteger SWord sym
SWord (What4 sym)
idx ->
What4 sym
-> WordValue (What4 sym)
-> Integer
-> SEval (What4 sym) (SBit (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
forall sym.
Backend sym =>
sym
-> WordValue sym
-> Integer
-> SEval sym (SBit sym)
-> SEval sym (WordValue sym)
updateWordValue What4 sym
sym WordValue (What4 sym)
bv Integer
j (GenValue (What4 sym) -> SymExpr sym BaseBoolType
forall sym. GenValue sym -> SBit sym
fromVBit (GenValue (What4 sym) -> SymExpr sym BaseBoolType)
-> W4Eval sym (GenValue (What4 sym))
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (GenValue (What4 sym))
W4Eval sym (GenValue (What4 sym))
val)
| WordVal SWord (What4 sym)
bw <- WordValue (What4 sym)
bv ->
SWord sym -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal (SWord sym -> WordValue (What4 sym))
-> W4Eval sym (SWord sym) -> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
do SymExpr sym BaseBoolType
b <- GenValue (What4 sym) -> SymExpr sym BaseBoolType
forall sym. GenValue sym -> SBit sym
fromVBit (GenValue (What4 sym) -> SymExpr sym BaseBoolType)
-> W4Eval sym (GenValue (What4 sym))
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (GenValue (What4 sym))
W4Eval sym (GenValue (What4 sym))
val
let sz :: Integer
sz = SWord sym -> Integer
forall sym. SWord sym -> Integer
SW.bvWidth SWord sym
SWord (What4 sym)
bw
SWord sym
highbit <- IO (SWord sym) -> W4Eval sym (SWord sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym -> Integer -> Integer -> IO (SWord sym)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> Integer -> IO (SWord sym)
SW.bvLit (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) Integer
sz (Int -> Integer
forall a. Bits a => Int -> a
bit (Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer
szInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
1))))
SWord sym
msk <- sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvLshr (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
highbit SWord sym
SWord (What4 sym)
idx
IO (SWord sym) -> W4Eval sym (SWord sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SWord sym) -> W4Eval sym (SWord sym))
-> IO (SWord sym) -> W4Eval sym (SWord sym)
forall a b. (a -> b) -> a -> b
$
case SymExpr sym BaseBoolType -> Maybe Bool
forall (e :: BaseType -> *).
IsExpr e =>
e BaseBoolType -> Maybe Bool
W4.asConstantPred SymExpr sym BaseBoolType
b of
Just Bool
True -> sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvOr (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
SWord (What4 sym)
bw SWord sym
msk
Just Bool
False -> sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvAnd (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
SWord (What4 sym)
bw (SWord sym -> IO (SWord sym)) -> IO (SWord sym) -> IO (SWord sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> SWord sym -> IO (SWord sym)
SWordUn
SW.bvNot (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
msk
Maybe Bool
Nothing ->
do SWord sym
q <- sym -> Integer -> SymExpr sym BaseBoolType -> IO (SWord sym)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> Pred sym -> IO (SWord sym)
SW.bvFill (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) Integer
sz SymExpr sym BaseBoolType
b
SWord sym
bw' <- sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvAnd (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
SWord (What4 sym)
bw (SWord sym -> IO (SWord sym)) -> IO (SWord sym) -> IO (SWord sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> SWord sym -> IO (SWord sym)
SWordUn
SW.bvNot (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
msk
sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvXor (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
bw' (SWord sym -> IO (SWord sym)) -> IO (SWord sym) -> IO (SWord sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvAnd (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
q SWord sym
msk
WordValue (What4 sym)
_ -> Integer -> SeqMap (What4 sym) -> WordValue (What4 sym)
forall sym. Integer -> SeqMap sym -> WordValue sym
LargeBitsVal (What4 sym -> WordValue (What4 sym) -> Integer
forall sym. Backend sym => sym -> WordValue sym -> Integer
wordValueSize What4 sym
sym WordValue (What4 sym)
wv) (SeqMap (What4 sym) -> WordValue (What4 sym))
-> W4Eval sym (SeqMap (What4 sym))
-> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (SeqMap (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
updateFrontSym What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
eltTy (What4 sym -> WordValue (What4 sym) -> SeqMap (What4 sym)
forall sym. Backend sym => sym -> WordValue sym -> SeqMap sym
asBitsMap What4 sym
sym WordValue (What4 sym)
bv) (WordValue (What4 sym)
-> Either (SymExpr sym BaseIntegerType) (WordValue (What4 sym))
forall a b. b -> Either a b
Right WordValue (What4 sym)
wv) SEval (What4 sym) (GenValue (What4 sym))
val
updateBackSym_word ::
W4.IsSymExprBuilder sym =>
What4 sym ->
Nat' ->
TValue ->
WordValue (What4 sym) ->
Either (SInteger (What4 sym)) (WordValue (What4 sym)) ->
SEval (What4 sym) (GenValue (What4 sym)) ->
SEval (What4 sym) (WordValue (What4 sym))
updateBackSym_word :: What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
updateBackSym_word What4 sym
_ Nat'
Inf TValue
_ WordValue (What4 sym)
_ Either (SInteger (What4 sym)) (WordValue (What4 sym))
_ SEval (What4 sym) (GenValue (What4 sym))
_ = String -> [String] -> W4Eval sym (WordValue (What4 sym))
forall a. String -> [String] -> a
evalPanic String
"Expected finite sequence" [String
"updateBackSym_word"]
updateBackSym_word What4 sym
sym (Nat Integer
_) TValue
eltTy (LargeBitsVal Integer
n SeqMap (What4 sym)
bv) Either (SInteger (What4 sym)) (WordValue (What4 sym))
idx SEval (What4 sym) (GenValue (What4 sym))
val =
Integer -> SeqMap (What4 sym) -> WordValue (What4 sym)
forall sym. Integer -> SeqMap sym -> WordValue sym
LargeBitsVal Integer
n (SeqMap (What4 sym) -> WordValue (What4 sym))
-> W4Eval sym (SeqMap (What4 sym))
-> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (SeqMap (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
updateBackSym What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
eltTy SeqMap (What4 sym)
bv Either (SInteger (What4 sym)) (WordValue (What4 sym))
idx SEval (What4 sym) (GenValue (What4 sym))
val
updateBackSym_word What4 sym
sym (Nat Integer
n) TValue
eltTy (WordVal SWord (What4 sym)
bv) (Left SInteger (What4 sym)
idx) SEval (What4 sym) (GenValue (What4 sym))
val =
do SWord sym
idx' <- What4 sym
-> Integer
-> SInteger (What4 sym)
-> SEval (What4 sym) (SWord (What4 sym))
forall sym.
Backend sym =>
sym -> Integer -> SInteger sym -> SEval sym (SWord sym)
wordFromInt What4 sym
sym Integer
n SInteger (What4 sym)
idx
What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> WordValue (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
updateBackSym_word What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
eltTy (SWord (What4 sym) -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal SWord (What4 sym)
bv) (WordValue (What4 sym)
-> Either (SymExpr sym BaseIntegerType) (WordValue (What4 sym))
forall a b. b -> Either a b
Right (SWord (What4 sym) -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal SWord sym
SWord (What4 sym)
idx')) SEval (What4 sym) (GenValue (What4 sym))
val
updateBackSym_word What4 sym
sym (Nat Integer
n) TValue
eltTy WordValue (What4 sym)
bv (Right WordValue (What4 sym)
wv) SEval (What4 sym) (GenValue (What4 sym))
val =
case WordValue (What4 sym)
wv of
WordVal SWord (What4 sym)
idx
| Just Integer
j <- SWord sym -> Maybe Integer
forall sym. IsExprBuilder sym => SWord sym -> Maybe Integer
SW.bvAsUnsignedInteger SWord sym
SWord (What4 sym)
idx ->
What4 sym
-> WordValue (What4 sym)
-> Integer
-> SEval (What4 sym) (SBit (What4 sym))
-> SEval (What4 sym) (WordValue (What4 sym))
forall sym.
Backend sym =>
sym
-> WordValue sym
-> Integer
-> SEval sym (SBit sym)
-> SEval sym (WordValue sym)
updateWordValue What4 sym
sym WordValue (What4 sym)
bv (Integer
n Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
j) (GenValue (What4 sym) -> SymExpr sym BaseBoolType
forall sym. GenValue sym -> SBit sym
fromVBit (GenValue (What4 sym) -> SymExpr sym BaseBoolType)
-> W4Eval sym (GenValue (What4 sym))
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (GenValue (What4 sym))
W4Eval sym (GenValue (What4 sym))
val)
| WordVal SWord (What4 sym)
bw <- WordValue (What4 sym)
bv ->
SWord sym -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal (SWord sym -> WordValue (What4 sym))
-> W4Eval sym (SWord sym) -> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
do SymExpr sym BaseBoolType
b <- GenValue (What4 sym) -> SymExpr sym BaseBoolType
forall sym. GenValue sym -> SBit sym
fromVBit (GenValue (What4 sym) -> SymExpr sym BaseBoolType)
-> W4Eval sym (GenValue (What4 sym))
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (GenValue (What4 sym))
W4Eval sym (GenValue (What4 sym))
val
let sz :: Integer
sz = SWord sym -> Integer
forall sym. SWord sym -> Integer
SW.bvWidth SWord sym
SWord (What4 sym)
bw
SWord sym
lowbit <- IO (SWord sym) -> W4Eval sym (SWord sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym -> Integer -> Integer -> IO (SWord sym)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> Integer -> IO (SWord sym)
SW.bvLit (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) Integer
sz Integer
1)
SWord sym
msk <- sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
forall sym.
IsSymExprBuilder sym =>
sym -> SWord sym -> SWord sym -> W4Eval sym (SWord sym)
w4bvShl (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
lowbit SWord sym
SWord (What4 sym)
idx
IO (SWord sym) -> W4Eval sym (SWord sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (SWord sym) -> W4Eval sym (SWord sym))
-> IO (SWord sym) -> W4Eval sym (SWord sym)
forall a b. (a -> b) -> a -> b
$
case SymExpr sym BaseBoolType -> Maybe Bool
forall (e :: BaseType -> *).
IsExpr e =>
e BaseBoolType -> Maybe Bool
W4.asConstantPred SymExpr sym BaseBoolType
b of
Just Bool
True -> sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvOr (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
SWord (What4 sym)
bw SWord sym
msk
Just Bool
False -> sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvAnd (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
SWord (What4 sym)
bw (SWord sym -> IO (SWord sym)) -> IO (SWord sym) -> IO (SWord sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> SWord sym -> IO (SWord sym)
SWordUn
SW.bvNot (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
msk
Maybe Bool
Nothing ->
do SWord sym
q <- sym -> Integer -> SymExpr sym BaseBoolType -> IO (SWord sym)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> Pred sym -> IO (SWord sym)
SW.bvFill (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) Integer
sz SymExpr sym BaseBoolType
b
SWord sym
bw' <- sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvAnd (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
SWord (What4 sym)
bw (SWord sym -> IO (SWord sym)) -> IO (SWord sym) -> IO (SWord sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> SWord sym -> IO (SWord sym)
SWordUn
SW.bvNot (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
msk
sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvXor (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
bw' (SWord sym -> IO (SWord sym)) -> IO (SWord sym) -> IO (SWord sym)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< sym -> SWord sym -> SWord sym -> IO (SWord sym)
SWordBin
SW.bvAnd (What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym) SWord sym
q SWord sym
msk
WordValue (What4 sym)
_ -> Integer -> SeqMap (What4 sym) -> WordValue (What4 sym)
forall sym. Integer -> SeqMap sym -> WordValue sym
LargeBitsVal (What4 sym -> WordValue (What4 sym) -> Integer
forall sym. Backend sym => sym -> WordValue sym -> Integer
wordValueSize What4 sym
sym WordValue (What4 sym)
wv) (SeqMap (What4 sym) -> WordValue (What4 sym))
-> W4Eval sym (SeqMap (What4 sym))
-> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (GenValue (What4 sym))
-> SEval (What4 sym) (SeqMap (What4 sym))
forall sym.
IsSymExprBuilder sym =>
What4 sym
-> Nat'
-> TValue
-> SeqMap (What4 sym)
-> Either (SInteger (What4 sym)) (WordValue (What4 sym))
-> SEval (What4 sym) (Value sym)
-> SEval (What4 sym) (SeqMap (What4 sym))
updateBackSym What4 sym
sym (Integer -> Nat'
Nat Integer
n) TValue
eltTy (What4 sym -> WordValue (What4 sym) -> SeqMap (What4 sym)
forall sym. Backend sym => sym -> WordValue sym -> SeqMap sym
asBitsMap What4 sym
sym WordValue (What4 sym)
bv) (WordValue (What4 sym)
-> Either (SymExpr sym BaseIntegerType) (WordValue (What4 sym))
forall a b. b -> Either a b
Right WordValue (What4 sym)
wv) SEval (What4 sym) (GenValue (What4 sym))
val
floatPrims :: W4.IsSymExprBuilder sym => What4 sym -> Map PrimIdent (Value sym)
floatPrims :: What4 sym -> Map PrimIdent (Value sym)
floatPrims What4 sym
sym =
[(PrimIdent, Value sym)] -> Map PrimIdent (Value sym)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [ (Text -> PrimIdent
floatPrim Text
i,Value sym
v) | (Text
i,Value sym
v) <- [(Text, Value sym)]
nonInfixTable ]
where
w4sym :: sym
w4sym = What4 sym -> sym
forall sym. What4 sym -> sym
w4 What4 sym
sym
~> :: a -> b -> (a, b)
(~>) = (,)
nonInfixTable :: [(Text, Value sym)]
nonInfixTable =
[ Text
"fpNaN" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> (Integer -> Integer -> IO (SFloat sym)) -> Value sym
forall sym.
IsSymExprBuilder sym =>
(Integer -> Integer -> IO (SFloat sym)) -> Value sym
fpConst (sym -> Integer -> Integer -> IO (SFloat sym)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> Integer -> IO (SFloat sym)
W4.fpNaN sym
w4sym)
, Text
"fpPosInf" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> (Integer -> Integer -> IO (SFloat sym)) -> Value sym
forall sym.
IsSymExprBuilder sym =>
(Integer -> Integer -> IO (SFloat sym)) -> Value sym
fpConst (sym -> Integer -> Integer -> IO (SFloat sym)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> Integer -> IO (SFloat sym)
W4.fpPosInf sym
w4sym)
, Text
"fpFromBits" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
e -> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
p -> What4 sym
-> (SWord (What4 sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
Backend sym =>
sym -> (SWord sym -> SEval sym (GenValue sym)) -> GenValue sym
wlam What4 sym
sym \SWord (What4 sym)
w ->
SFloat sym -> Value sym
forall sym. SFloat sym -> GenValue sym
VFloat (SFloat sym -> Value sym)
-> W4Eval sym (SFloat sym) -> W4Eval sym (Value sym)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (SFloat sym) -> W4Eval sym (SFloat sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym -> Integer -> Integer -> SWord sym -> IO (SFloat sym)
forall sym.
IsExprBuilder sym =>
sym -> Integer -> Integer -> SWord sym -> IO (SFloat sym)
W4.fpFromBinary sym
w4sym Integer
e Integer
p SWord sym
SWord (What4 sym)
w)
, Text
"fpToBits" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
e -> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
p -> (SFloat (What4 sym) -> SEval (What4 sym) (Value sym)) -> Value sym
forall sym.
Backend sym =>
(SFloat sym -> SEval sym (GenValue sym)) -> GenValue sym
flam \SFloat (What4 sym)
x ->
Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$ Integer -> SEval (What4 sym) (WordValue (What4 sym)) -> Value sym
forall sym. Integer -> SEval sym (WordValue sym) -> GenValue sym
VWord (Integer
eInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
p)
(SEval (What4 sym) (WordValue (What4 sym)) -> Value sym)
-> SEval (What4 sym) (WordValue (What4 sym)) -> Value sym
forall a b. (a -> b) -> a -> b
$ SWord sym -> WordValue (What4 sym)
forall sym. SWord sym -> WordValue sym
WordVal (SWord sym -> WordValue (What4 sym))
-> W4Eval sym (SWord sym) -> W4Eval sym (WordValue (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (SWord sym) -> W4Eval sym (SWord sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (sym -> SFloat sym -> IO (SWord sym)
forall sym.
IsExprBuilder sym =>
sym -> SFloat sym -> IO (SWord sym)
W4.fpToBinary sym
w4sym SFloat sym
SFloat (What4 sym)
x)
, Text
"=.=" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
_ -> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
_ -> (SFloat (What4 sym) -> SEval (What4 sym) (Value sym)) -> Value sym
forall sym.
Backend sym =>
(SFloat sym -> SEval sym (GenValue sym)) -> GenValue sym
flam \SFloat (What4 sym)
x -> Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$ (SFloat (What4 sym) -> SEval (What4 sym) (Value sym)) -> Value sym
forall sym.
Backend sym =>
(SFloat sym -> SEval sym (GenValue sym)) -> GenValue sym
flam \SFloat (What4 sym)
y ->
SymExpr sym BaseBoolType -> Value sym
forall sym. SBit sym -> GenValue sym
VBit (SymExpr sym BaseBoolType -> Value sym)
-> W4Eval sym (SymExpr sym BaseBoolType) -> W4Eval sym (Value sym)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (SymExpr sym BaseBoolType)
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (SFloatRel sym
forall sym. IsExprBuilder sym => SFloatRel sym
W4.fpEq sym
w4sym SFloat sym
SFloat (What4 sym)
x SFloat sym
SFloat (What4 sym)
y)
, Text
"fpIsFinite" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
_ -> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
_ -> (SFloat (What4 sym) -> SEval (What4 sym) (Value sym)) -> Value sym
forall sym.
Backend sym =>
(SFloat sym -> SEval sym (GenValue sym)) -> GenValue sym
flam \SFloat (What4 sym)
x ->
SymExpr sym BaseBoolType -> Value sym
forall sym. SBit sym -> GenValue sym
VBit (SymExpr sym BaseBoolType -> Value sym)
-> W4Eval sym (SymExpr sym BaseBoolType) -> W4Eval sym (Value sym)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (SymExpr sym BaseBoolType)
-> W4Eval sym (SymExpr sym BaseBoolType)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO do SymExpr sym BaseBoolType
inf <- sym -> SFloat sym -> IO (SymExpr sym BaseBoolType)
forall sym. IsExprBuilder sym => sym -> SFloat sym -> IO (Pred sym)
W4.fpIsInf sym
w4sym SFloat sym
SFloat (What4 sym)
x
SymExpr sym BaseBoolType
nan <- sym -> SFloat sym -> IO (SymExpr sym BaseBoolType)
forall sym. IsExprBuilder sym => sym -> SFloat sym -> IO (Pred sym)
W4.fpIsNaN sym
w4sym SFloat sym
SFloat (What4 sym)
x
SymExpr sym BaseBoolType
weird <- sym
-> SymExpr sym BaseBoolType
-> SymExpr sym BaseBoolType
-> IO (SymExpr sym BaseBoolType)
forall sym.
IsExprBuilder sym =>
sym -> Pred sym -> Pred sym -> IO (Pred sym)
W4.orPred sym
w4sym SymExpr sym BaseBoolType
inf SymExpr sym BaseBoolType
nan
sym -> SymExpr sym BaseBoolType -> IO (SymExpr sym BaseBoolType)
forall sym. IsExprBuilder sym => sym -> Pred sym -> IO (Pred sym)
W4.notPred sym
w4sym SymExpr sym BaseBoolType
weird
, Text
"fpAdd" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> What4 sym -> FPArith2 (What4 sym) -> Value sym
forall sym. Backend sym => sym -> FPArith2 sym -> GenValue sym
fpBinArithV What4 sym
sym FPArith2 (What4 sym)
forall sym. Backend sym => FPArith2 sym
fpPlus
, Text
"fpSub" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> What4 sym -> FPArith2 (What4 sym) -> Value sym
forall sym. Backend sym => sym -> FPArith2 sym -> GenValue sym
fpBinArithV What4 sym
sym FPArith2 (What4 sym)
forall sym. Backend sym => FPArith2 sym
fpMinus
, Text
"fpMul" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> What4 sym -> FPArith2 (What4 sym) -> Value sym
forall sym. Backend sym => sym -> FPArith2 sym -> GenValue sym
fpBinArithV What4 sym
sym FPArith2 (What4 sym)
forall sym. Backend sym => FPArith2 sym
fpMult
, Text
"fpDiv" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~> What4 sym -> FPArith2 (What4 sym) -> Value sym
forall sym. Backend sym => sym -> FPArith2 sym -> GenValue sym
fpBinArithV What4 sym
sym FPArith2 (What4 sym)
forall sym. Backend sym => FPArith2 sym
fpDiv
, Text
"fpFromRational" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
e -> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
p -> What4 sym
-> (SWord (What4 sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
Backend sym =>
sym -> (SWord sym -> SEval sym (GenValue sym)) -> GenValue sym
wlam What4 sym
sym \SWord (What4 sym)
r -> Value sym -> W4Eval sym (Value sym)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Value sym -> W4Eval sym (Value sym))
-> Value sym -> W4Eval sym (Value sym)
forall a b. (a -> b) -> a -> b
$ (SEval (What4 sym) (Value sym) -> SEval (What4 sym) (Value sym))
-> Value sym
forall sym.
(SEval sym (GenValue sym) -> SEval sym (GenValue sym))
-> GenValue sym
lam \SEval (What4 sym) (Value sym)
x ->
do SRational (What4 sym)
rat <- Value sym -> SRational (What4 sym)
forall sym. GenValue sym -> SRational sym
fromVRational (Value sym -> SRational (What4 sym))
-> W4Eval sym (Value sym) -> W4Eval sym (SRational (What4 sym))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SEval (What4 sym) (Value sym)
W4Eval sym (Value sym)
x
SFloat sym -> Value sym
forall sym. SFloat sym -> GenValue sym
VFloat (SFloat sym -> Value sym)
-> W4Eval sym (SFloat sym) -> W4Eval sym (Value sym)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> What4 sym
-> Integer
-> Integer
-> SWord (What4 sym)
-> SRational (What4 sym)
-> SEval (What4 sym) (SFloat (What4 sym))
forall sy sym.
(IsSymExprBuilder sy, sym ~ What4 sy) =>
sym
-> Integer
-> Integer
-> SWord sym
-> SRational sym
-> SEval sym (SFloat sym)
fpCvtFromRational What4 sym
sym Integer
e Integer
p SWord (What4 sym)
r SRational (What4 sym)
rat
, Text
"fpToRational" Text -> Value sym -> (Text, Value sym)
forall a b. a -> b -> (a, b)
~>
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
_e -> (Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \Integer
_p -> (SFloat (What4 sym) -> SEval (What4 sym) (Value sym)) -> Value sym
forall sym.
Backend sym =>
(SFloat sym -> SEval sym (GenValue sym)) -> GenValue sym
flam \SFloat (What4 sym)
fp ->
SRational (What4 sym) -> Value sym
forall sym. SRational sym -> GenValue sym
VRational (SRational (What4 sym) -> Value sym)
-> W4Eval sym (SRational (What4 sym)) -> W4Eval sym (Value sym)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> What4 sym
-> SFloat (What4 sym) -> SEval (What4 sym) (SRational (What4 sym))
forall sy sym.
(IsSymExprBuilder sy, sym ~ What4 sy) =>
sym -> SFloat sym -> SEval sym (SRational sym)
fpCvtToRational What4 sym
sym SFloat (What4 sym)
fp
]
fpConst ::
W4.IsSymExprBuilder sym =>
(Integer -> Integer -> IO (W4.SFloat sym)) ->
Value sym
fpConst :: (Integer -> Integer -> IO (SFloat sym)) -> Value sym
fpConst Integer -> Integer -> IO (SFloat sym)
mk =
(Integer -> Value sym) -> Value sym
forall sym.
Backend sym =>
(Integer -> GenValue sym) -> GenValue sym
ilam \ Integer
e ->
(Nat' -> SEval (What4 sym) (Value sym)) -> Value sym
forall sym. (Nat' -> SEval sym (GenValue sym)) -> GenValue sym
VNumPoly \ ~(Nat Integer
p) ->
SFloat sym -> Value sym
forall sym. SFloat sym -> GenValue sym
VFloat (SFloat sym -> Value sym)
-> W4Eval sym (SFloat sym) -> W4Eval sym (Value sym)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO (SFloat sym) -> W4Eval sym (SFloat sym)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Integer -> Integer -> IO (SFloat sym)
mk Integer
e Integer
p)