Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data Eval a
- 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
- asciiMode :: PPOpts -> Integer -> Bool
- data PPFloatFormat
- data PPFloatExp
- defaultPPOpts :: PPOpts
- io :: IO a -> Eval a
- delayFill :: Eval a -> Eval a -> Eval (Eval a)
- ready :: a -> Eval a
- blackhole :: String -> Eval (Eval a, Eval a -> Eval ())
- evalSpark :: Eval a -> Eval (Eval a)
- maybeReady :: Eval a -> Eval (Maybe a)
- data Unsupported = UnsupportedSymbolicOp String
- data EvalError
- evalPanic :: HasCallStack => String -> [String] -> a
- wordTooWide :: Integer -> a
- typeCannotBeDemoted :: Type -> a
Evaluation monad
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.
Some options for evalutaion
EvalOpts | |
|
How to pretty print things when evaluating
PPOpts | |
|
data PPFloatFormat Source #
FloatFixed Int PPFloatExp | Use this many significant digis |
FloatFrac Int | Show this many digits after floating point |
FloatFree PPFloatExp | Use the correct number of digits |
data PPFloatExp Source #
ForceExponent | Always show an exponent |
AutoExponent | Only show exponent when needed |
:: Eval a | Computation to delay |
-> Eval a | Backup computation to run if a tight loop is detected |
-> Eval (Eval a) |
Delay the given evaluation computation, returning a thunk
which will run the computation when forced. Run the retry
computation instead if the resulting thunk is forced during
its own evaluation.
Produce a thunk value which can be filled with its associated computation after the fact. A preallocated thunk is returned, along with an operation to fill the thunk with the associated computation. This is used to implement recursive declaration groups.
evalSpark :: Eval a -> Eval (Eval a) Source #
Begin executing the given operation in a separate thread, returning a thunk which will await the completion of the computation when forced.
maybeReady :: Eval a -> Eval (Maybe a) Source #
Test if a value is "ready", which means that it requires no computation to return.
Error reporting
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 |
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 # | |
wordTooWide :: Integer -> a Source #
For when we know that a word is too wide and will exceed gmp's limits (though words approaching this size will probably cause the system to crash anyway due to lack of memory).
typeCannotBeDemoted :: Type -> a Source #
For things like `(inf)
or `(0-1)
.