Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- moduleEnv :: EvalPrims sym => sym -> Module -> GenEvalEnv sym -> SEval sym (GenEvalEnv sym)
- runEval :: Eval a -> IO a
- data EvalOpts = EvalOpts {
- evalLogger :: Logger
- evalPPOpts :: PPOpts
- data PPOpts = PPOpts {
- useAscii :: Bool
- useBase :: Int
- useInfLength :: Int
- useFPBase :: Int
- useFPFormat :: PPFloatFormat
- defaultPPOpts :: PPOpts
- data Eval a
- type EvalEnv = GenEvalEnv Concrete
- emptyEnv :: GenEvalEnv sym
- evalExpr :: EvalPrims sym => sym -> GenEvalEnv sym -> Expr -> SEval sym (GenValue sym)
- evalDecls :: EvalPrims sym => sym -> [DeclGroup] -> GenEvalEnv sym -> SEval sym (GenEvalEnv sym)
- evalSel :: EvalPrims sym => sym -> GenValue sym -> Selector -> SEval sym (GenValue sym)
- evalSetSel :: forall sym. EvalPrims sym => sym -> TValue -> GenValue sym -> Selector -> SEval sym (GenValue sym) -> SEval sym (GenValue sym)
- data EvalError
- data Unsupported = UnsupportedSymbolicOp String
- forceValue :: Backend sym => GenValue sym -> SEval sym ()
Documentation
:: EvalPrims sym | |
=> sym | |
-> Module | Module containing declarations to evaluate |
-> GenEvalEnv sym | Environment to extend |
-> SEval sym (GenEvalEnv sym) |
Extend the given evaluation environment with all the declarations contained in the given module.
Some options for evalutaion
EvalOpts | |
|
How to pretty print things when evaluating
PPOpts | |
|
The monad for Cryptol evaluation. A computation is either "ready", which means it represents only trivial computation, or is an "eval" action which must be computed to get the answer, or it is a "thunk", which represents a delayed, shared computation.
type EvalEnv = GenEvalEnv Concrete Source #
emptyEnv :: GenEvalEnv sym Source #
Evaluation environment with no bindings
:: EvalPrims sym | |
=> sym | |
-> GenEvalEnv sym | Evaluation environment |
-> Expr | Expression to evaluate |
-> SEval sym (GenValue sym) |
Evaluate a Cryptol expression to a value. This evaluator is parameterized
by the EvalPrims
class, which defines the behavior of bits and words, in
addition to providing implementations for all the primitives.
:: EvalPrims sym | |
=> sym | |
-> [DeclGroup] | Declaration groups to evaluate |
-> GenEvalEnv sym | Environment to extend |
-> SEval sym (GenEvalEnv sym) |
Extend the given evaluation environment with the result of evaluating the given collection of declaration groups.
evalSel :: EvalPrims sym => sym -> GenValue sym -> Selector -> SEval sym (GenValue sym) Source #
Apply the the given "selector" form to the given value. This function pushes tuple and record selections pointwise down into other value constructs (e.g., streams and functions).
evalSetSel :: forall sym. EvalPrims sym => sym -> TValue -> GenValue sym -> Selector -> SEval sym (GenValue sym) -> SEval sym (GenValue sym) Source #
Data type describing errors that can occur during evaluation.
InvalidIndex (Maybe Integer) | Out-of-bounds index |
TypeCannotBeDemoted Type | Non-numeric type passed to |
DivideByZero | Division or modulus by 0 |
NegativeExponent | Exponentiation by negative integer |
LogNegative | Logarithm of a negative integer |
WordTooWide Integer | Bitvector too large |
UserError String | Call to the Cryptol |
LoopError String | Detectable nontermination |
NoPrim Name | Primitive with no implementation |
BadRoundingMode Integer | Invalid rounding mode |
BadValue String | Value outside the domain of a partial function. |
Instances
Show EvalError Source # | |
Exception EvalError Source # | |
Defined in Cryptol.Backend.Monad toException :: EvalError -> SomeException # fromException :: SomeException -> Maybe EvalError # displayException :: EvalError -> String # | |
PP EvalError Source # | |
data Unsupported Source #
UnsupportedSymbolicOp String | Operation cannot be supported in the symbolic simulator |
Instances
Show Unsupported Source # | |
Defined in Cryptol.Backend.Monad showsPrec :: Int -> Unsupported -> ShowS # show :: Unsupported -> String # showList :: [Unsupported] -> ShowS # | |
Exception Unsupported Source # | |
Defined in Cryptol.Backend.Monad | |
PP Unsupported Source # | |
Defined in Cryptol.Backend.Monad |