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 :: EvalOpts -> Eval a -> IO a
- data EvalOpts = EvalOpts {
- evalLogger :: Logger
- evalPPOpts :: PPOpts
- getEvalOpts :: Eval EvalOpts
- data PPOpts = PPOpts {}
- io :: IO a -> Eval a
- delay :: Maybe String -> Eval a -> Eval (Eval a)
- delayFill :: Eval a -> Eval a -> Eval (Eval a)
- ready :: a -> Eval a
- blackhole :: String -> Eval (Eval a, Eval a -> Eval ())
- data EvalError
- evalPanic :: HasCallStack => String -> [String] -> a
- typeCannotBeDemoted :: Type -> a
- divideByZero :: Eval a
- negativeExponent :: Eval a
- logNegative :: Eval a
- wordTooWide :: Integer -> a
- cryUserError :: String -> Eval a
- cryLoopError :: String -> Eval a
- cryNoPrimError :: Name -> Eval a
- invalidIndex :: Integer -> Eval a
Evaluation monad
The monad for Cryptol evaluation.
Some options for evalutaion
EvalOpts | |
|
getEvalOpts :: Eval EvalOpts Source #
Access the evaluation options.
How to pretty print things when evaluating
:: Maybe String | Optional name to print if a loop is detected |
-> Eval a | Computation to delay |
-> Eval (Eval a) |
Delay the given evaluation computation, returning a thunk which will run the computation when forced. Raise a loop error if the resulting thunk is forced during its own evaluation.
:: 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.
Error reporting
Data type describing errors that can occur during evaluation.
InvalidIndex 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 |
Instances
Show EvalError Source # | |
Exception EvalError Source # | |
Defined in Cryptol.Eval.Monad toException :: EvalError -> SomeException # fromException :: SomeException -> Maybe EvalError # displayException :: EvalError -> String # | |
PP EvalError Source # | |
typeCannotBeDemoted :: Type -> a Source #
For things like `(inf)
or `(0-1)
.
divideByZero :: Eval a Source #
For division by 0.
negativeExponent :: Eval a Source #
For exponentiation by a negative integer.
logNegative :: Eval a Source #
For logarithm of a negative integer.
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).
cryUserError :: String -> Eval a Source #
For the Cryptol error
function.
cryLoopError :: String -> Eval a Source #
For cases where we can detect tight loops.
cryNoPrimError :: Name -> Eval a Source #
invalidIndex :: Integer -> Eval a Source #
A sequencing operation has gotten an invalid index.