Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class MonadIO (SEval sym) => Backend sym where
- type SBit sym :: Type
- type SWord sym :: Type
- type SInteger sym :: Type
- type SFloat sym :: Type
- type SEval sym :: Type -> Type
- isReady :: sym -> SEval sym a -> Bool
- sDeclareHole :: sym -> String -> SEval sym (SEval sym a, SEval sym a -> SEval sym ())
- sDelayFill :: sym -> SEval sym a -> SEval sym a -> SEval sym (SEval sym a)
- sSpark :: sym -> SEval sym a -> SEval sym (SEval sym a)
- mergeEval :: sym -> (SBit sym -> a -> a -> SEval sym a) -> SBit sym -> SEval sym a -> SEval sym a -> SEval sym a
- assertSideCondition :: sym -> SBit sym -> EvalError -> SEval sym ()
- raiseError :: sym -> EvalError -> SEval sym a
- ppBit :: sym -> SBit sym -> Doc
- ppWord :: sym -> PPOpts -> SWord sym -> Doc
- ppInteger :: sym -> PPOpts -> SInteger sym -> Doc
- ppFloat :: sym -> PPOpts -> SFloat sym -> Doc
- bitAsLit :: sym -> SBit sym -> Maybe Bool
- wordLen :: sym -> SWord sym -> Integer
- wordAsLit :: sym -> SWord sym -> Maybe (Integer, Integer)
- wordAsChar :: sym -> SWord sym -> Maybe Char
- integerAsLit :: sym -> SInteger sym -> Maybe Integer
- bitLit :: sym -> Bool -> SBit sym
- wordLit :: sym -> Integer -> Integer -> SEval sym (SWord sym)
- integerLit :: sym -> Integer -> SEval sym (SInteger sym)
- fpLit :: sym -> Integer -> Integer -> Rational -> SEval sym (SFloat sym)
- fpExactLit :: sym -> BF -> SEval sym (SFloat sym)
- iteBit :: sym -> SBit sym -> SBit sym -> SBit sym -> SEval sym (SBit sym)
- iteWord :: sym -> SBit sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- iteInteger :: sym -> SBit sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym)
- bitEq :: sym -> SBit sym -> SBit sym -> SEval sym (SBit sym)
- bitOr :: sym -> SBit sym -> SBit sym -> SEval sym (SBit sym)
- bitAnd :: sym -> SBit sym -> SBit sym -> SEval sym (SBit sym)
- bitXor :: sym -> SBit sym -> SBit sym -> SEval sym (SBit sym)
- bitComplement :: sym -> SBit sym -> SEval sym (SBit sym)
- wordBit :: sym -> SWord sym -> Integer -> SEval sym (SBit sym)
- wordUpdate :: sym -> SWord sym -> Integer -> SBit sym -> SEval sym (SWord sym)
- packWord :: sym -> [SBit sym] -> SEval sym (SWord sym)
- unpackWord :: sym -> SWord sym -> SEval sym [SBit sym]
- wordFromInt :: sym -> Integer -> SInteger sym -> SEval sym (SWord sym)
- joinWord :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- splitWord :: sym -> Integer -> Integer -> SWord sym -> SEval sym (SWord sym, SWord sym)
- extractWord :: sym -> Integer -> Integer -> SWord sym -> SEval sym (SWord sym)
- wordOr :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordAnd :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordXor :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordComplement :: sym -> SWord sym -> SEval sym (SWord sym)
- wordPlus :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordMinus :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordMult :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordDiv :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordMod :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordSignedDiv :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordSignedMod :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym)
- wordNegate :: sym -> SWord sym -> SEval sym (SWord sym)
- wordLg2 :: sym -> SWord sym -> SEval sym (SWord sym)
- wordEq :: sym -> SWord sym -> SWord sym -> SEval sym (SBit sym)
- wordSignedLessThan :: sym -> SWord sym -> SWord sym -> SEval sym (SBit sym)
- wordLessThan :: sym -> SWord sym -> SWord sym -> SEval sym (SBit sym)
- wordGreaterThan :: sym -> SWord sym -> SWord sym -> SEval sym (SBit sym)
- wordToInt :: sym -> SWord sym -> SEval sym (SInteger sym)
- intPlus :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym)
- intNegate :: sym -> SInteger sym -> SEval sym (SInteger sym)
- intMinus :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym)
- intMult :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym)
- intDiv :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym)
- intMod :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym)
- intEq :: sym -> SInteger sym -> SInteger sym -> SEval sym (SBit sym)
- intLessThan :: sym -> SInteger sym -> SInteger sym -> SEval sym (SBit sym)
- intGreaterThan :: sym -> SInteger sym -> SInteger sym -> SEval sym (SBit sym)
- intToZn :: sym -> Integer -> SInteger sym -> SEval sym (SInteger sym)
- znToInt :: sym -> Integer -> SInteger sym -> SEval sym (SInteger sym)
- znPlus :: sym -> Integer -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym)
- znNegate :: sym -> Integer -> SInteger sym -> SEval sym (SInteger sym)
- znMinus :: sym -> Integer -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym)
- znMult :: sym -> Integer -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym)
- znEq :: sym -> Integer -> SInteger sym -> SInteger sym -> SEval sym (SBit sym)
- znRecip :: sym -> Integer -> SInteger sym -> SEval sym (SInteger sym)
- fpEq :: sym -> SFloat sym -> SFloat sym -> SEval sym (SBit sym)
- fpLessThan :: sym -> SFloat sym -> SFloat sym -> SEval sym (SBit sym)
- fpGreaterThan :: sym -> SFloat sym -> SFloat sym -> SEval sym (SBit sym)
- fpLogicalEq :: sym -> SFloat sym -> SFloat sym -> SEval sym (SBit sym)
- fpPlus, fpMinus, fpMult, fpDiv :: FPArith2 sym
- fpNeg :: sym -> SFloat sym -> SEval sym (SFloat sym)
- fpToInteger :: sym -> String -> SWord sym -> SFloat sym -> SEval sym (SInteger sym)
- fpFromInteger :: sym -> Integer -> Integer -> SWord sym -> SInteger sym -> SEval sym (SFloat sym)
- sDelay :: Backend sym => sym -> Maybe String -> SEval sym a -> SEval sym (SEval sym a)
- invalidIndex :: Backend sym => sym -> Integer -> SEval sym a
- cryUserError :: Backend sym => sym -> String -> SEval sym a
- cryNoPrimError :: Backend sym => sym -> Name -> SEval sym a
- type FPArith2 sym = sym -> SWord sym -> SFloat sym -> SFloat sym -> SEval sym (SFloat sym)
- data SRational sym = SRational {}
- intToRational :: Backend sym => sym -> SInteger sym -> SEval sym (SRational sym)
- ratio :: Backend sym => sym -> SInteger sym -> SInteger sym -> SEval sym (SRational sym)
- rationalAdd :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym)
- rationalSub :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym)
- rationalNegate :: Backend sym => sym -> SRational sym -> SEval sym (SRational sym)
- rationalMul :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym)
- rationalRecip :: Backend sym => sym -> SRational sym -> SEval sym (SRational sym)
- rationalDivide :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym)
- rationalFloor :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym)
- rationalCeiling :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym)
- rationalTrunc :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym)
- rationalRoundAway :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym)
- rationalRoundToEven :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym)
- rationalEq :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SBit sym)
- rationalLessThan :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SBit sym)
- rationalGreaterThan :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SBit sym)
- iteRational :: Backend sym => sym -> SBit sym -> SRational sym -> SRational sym -> SEval sym (SRational sym)
- ppRational :: Backend sym => sym -> PPOpts -> SRational sym -> Doc
Documentation
class MonadIO (SEval sym) => Backend sym where Source #
This type class defines a collection of operations on bits, words and integers that are necessary to define generic evaluator primitives that operate on both concrete and symbolic values uniformly.
type SBit sym :: Type Source #
type SWord sym :: Type Source #
type SInteger sym :: Type Source #
isReady :: sym -> SEval sym a -> Bool Source #
Check if an operation is "ready", which means its evaluation will be trivial.
sDeclareHole :: sym -> String -> SEval sym (SEval sym a, SEval sym a -> SEval sym ()) Source #
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.
sDelayFill :: sym -> SEval sym a -> SEval sym a -> SEval sym (SEval sym a) Source #
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.
sSpark :: sym -> SEval sym a -> SEval sym (SEval sym a) Source #
Begin evaluating the given computation eagerly in a separate thread and return a thunk which will await the completion of the given computation when forced.
:: sym | |
-> (SBit sym -> a -> a -> SEval sym a) | A merge operation on values |
-> SBit sym | The condition |
-> SEval sym a | The "then" computation |
-> SEval sym a | The "else" computation |
-> SEval sym a |
Merge the two given computations according to the predicate.
assertSideCondition :: sym -> SBit sym -> EvalError -> SEval sym () Source #
Assert that a condition must hold, and indicate what sort of error is indicated if the condition fails.
raiseError :: sym -> EvalError -> SEval sym a Source #
Indiciate that an error condition exists
ppBit :: sym -> SBit sym -> Doc Source #
Pretty-print an individual bit
ppWord :: sym -> PPOpts -> SWord sym -> Doc Source #
Pretty-print a word value
ppInteger :: sym -> PPOpts -> SInteger sym -> Doc Source #
Pretty-print an integer value
ppFloat :: sym -> PPOpts -> SFloat sym -> Doc Source #
Pretty-print a floating-point value
bitAsLit :: sym -> SBit sym -> Maybe Bool Source #
Determine if this symbolic bit is a boolean literal
wordLen :: sym -> SWord sym -> Integer Source #
The number of bits in a word value.
wordAsLit :: sym -> SWord sym -> Maybe (Integer, Integer) Source #
Determine if this symbolic word is a literal. If so, return the bit width and value.
wordAsChar :: sym -> SWord sym -> Maybe Char Source #
Attempt to render a word value as an ASCII character. Return Nothing
if the character value is unknown (e.g., for symbolic values).
integerAsLit :: sym -> SInteger sym -> Maybe Integer Source #
Determine if this symbolic integer is a literal
bitLit :: sym -> Bool -> SBit sym Source #
Construct a literal bit value from a boolean.
Construct a literal word value given a bit width and a value.
Construct a literal integer value from the given integer.
:: sym | |
-> Integer | exponent bits |
-> Integer | precision bits |
-> Rational | The rational |
-> SEval sym (SFloat sym) |
Construct a floating point value from the given rational.
fpExactLit :: sym -> BF -> SEval sym (SFloat sym) Source #
Construct a floating point value from the given bit-precise floating-point representation.
iteBit :: sym -> SBit sym -> SBit sym -> SBit sym -> SEval sym (SBit sym) Source #
iteWord :: sym -> SBit sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
iteInteger :: sym -> SBit sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym) Source #
bitEq :: sym -> SBit sym -> SBit sym -> SEval sym (SBit sym) Source #
bitOr :: sym -> SBit sym -> SBit sym -> SEval sym (SBit sym) Source #
bitAnd :: sym -> SBit sym -> SBit sym -> SEval sym (SBit sym) Source #
bitXor :: sym -> SBit sym -> SBit sym -> SEval sym (SBit sym) Source #
bitComplement :: sym -> SBit sym -> SEval sym (SBit sym) Source #
Extract the numbered bit from the word.
NOTE: this assumes that the sequence of bits is big-endian and finite, so the bit numbered 0 is the most significant bit.
Update the numbered bit in the word.
NOTE: this assumes that the sequence of bits is big-endian and finite, so the bit numbered 0 is the most significant bit.
packWord :: sym -> [SBit sym] -> SEval sym (SWord sym) Source #
Construct a word value from a finite sequence of bits. NOTE: this assumes that the sequence of bits is big-endian and finite, so the first element of the list will be the most significant bit.
unpackWord :: sym -> SWord sym -> SEval sym [SBit sym] Source #
Deconstruct a packed word value in to a finite sequence of bits. NOTE: this produces a list of bits that represent a big-endian word, so the most significant bit is the first element of the list.
Construct a packed word of the specified width from an integer value.
joinWord :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
Concatenate the two given word values. NOTE: the first argument represents the more-significant bits
Take the most-significant bits, and return those bits and the remainder. The first element of the pair is the most significant bits. The two integer sizes must sum to the length of the given word value.
:: sym | |
-> Integer | Number of bits to take |
-> Integer | starting bit |
-> SWord sym | |
-> SEval sym (SWord sym) |
Extract a subsequence of bits from a packed word value.
The first integer argument is the number of bits in the
resulting word. The second integer argument is the
number of less-significant digits to discard. Stated another
way, the operation extractWord n i w
is equivalent to
first shifting w
right by i
bits, and then truncating to
n
bits.
wordOr :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
Bitwise OR
wordAnd :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
Bitwise AND
wordXor :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
Bitwise XOR
wordComplement :: sym -> SWord sym -> SEval sym (SWord sym) Source #
Bitwise complement
wordPlus :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
2's complement addition of packed words. The arguments must have equal bit width, and the result is of the same width. Overflow is silently discarded.
wordMinus :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
2's complement subtraction of packed words. The arguments must have equal bit width, and the result is of the same width. Overflow is silently discarded.
wordMult :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
2's complement multiplication of packed words. The arguments must have equal bit width, and the result is of the same width. The high bits of the multiplication are silently discarded.
wordDiv :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
2's complement unsigned division of packed words. The arguments must have equal bit width, and the result is of the same width. It is illegal to call with a second argument concretely equal to 0.
wordMod :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
2's complement unsigned modulus of packed words. The arguments must have equal bit width, and the result is of the same width. It is illegal to call with a second argument concretely equal to 0.
wordSignedDiv :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
2's complement signed division of packed words. The arguments must have equal bit width, and the result is of the same width. It is illegal to call with a second argument concretely equal to 0.
wordSignedMod :: sym -> SWord sym -> SWord sym -> SEval sym (SWord sym) Source #
2's complement signed modulus of packed words. The arguments must have equal bit width, and the result is of the same width. It is illegal to call with a second argument concretely equal to 0.
wordNegate :: sym -> SWord sym -> SEval sym (SWord sym) Source #
2's complement negation of bitvectors
wordLg2 :: sym -> SWord sym -> SEval sym (SWord sym) Source #
Compute rounded-up log-2 of the input
wordEq :: sym -> SWord sym -> SWord sym -> SEval sym (SBit sym) Source #
Test if two words are equal. Arguments must have the same width.
wordSignedLessThan :: sym -> SWord sym -> SWord sym -> SEval sym (SBit sym) Source #
Signed less-than comparison on words. Arguments must have the same width.
wordLessThan :: sym -> SWord sym -> SWord sym -> SEval sym (SBit sym) Source #
Unsigned less-than comparison on words. Arguments must have the same width.
wordGreaterThan :: sym -> SWord sym -> SWord sym -> SEval sym (SBit sym) Source #
Unsigned greater-than comparison on words. Arguments must have the same width.
wordToInt :: sym -> SWord sym -> SEval sym (SInteger sym) Source #
Construct an integer value from the given packed word.
intPlus :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym) Source #
Addition of unbounded integers.
intNegate :: sym -> SInteger sym -> SEval sym (SInteger sym) Source #
Negation of unbounded integers
intMinus :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym) Source #
Subtraction of unbounded integers.
intMult :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym) Source #
Multiplication of unbounded integers.
intDiv :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym) Source #
Integer division, rounding down. It is illegal to
call with a second argument concretely equal to 0.
Same semantics as Haskell's div
operation.
intMod :: sym -> SInteger sym -> SInteger sym -> SEval sym (SInteger sym) Source #
Integer modulus, with division rounding down. It is illegal to
call with a second argument concretely equal to 0.
Same semantics as Haskell's mod
operation.
intEq :: sym -> SInteger sym -> SInteger sym -> SEval sym (SBit sym) Source #
Equality comparison on integers
intLessThan :: sym -> SInteger sym -> SInteger sym -> SEval sym (SBit sym) Source #
Less-than comparison on integers
intGreaterThan :: sym -> SInteger sym -> SInteger sym -> SEval sym (SBit sym) Source #
Greater-than comparison on integers
Turn an integer into a value in Z_n
Transform a Z_n value into an integer, ensuring the value is properly reduced modulo n
Addition of integers modulo n, for a concrete positive integer n.
Additive inverse of integers modulo n
Subtraction of integers modulo n, for a concrete positive integer n.
Multiplication of integers modulo n, for a concrete positive integer n.
Equality test of integers modulo n
Multiplicitive inverse in (Z n). PRECONDITION: the modulus is a prime
fpEq :: sym -> SFloat sym -> SFloat sym -> SEval sym (SBit sym) Source #
fpLessThan :: sym -> SFloat sym -> SFloat sym -> SEval sym (SBit sym) Source #
fpGreaterThan :: sym -> SFloat sym -> SFloat sym -> SEval sym (SBit sym) Source #
fpLogicalEq :: sym -> SFloat sym -> SFloat sym -> SEval sym (SBit sym) Source #
fpPlus :: FPArith2 sym Source #
fpMinus :: FPArith2 sym Source #
fpMult :: FPArith2 sym Source #
fpDiv :: FPArith2 sym Source #
fpNeg :: sym -> SFloat sym -> SEval sym (SFloat sym) Source #
Instances
sDelay :: Backend sym => sym -> Maybe String -> SEval sym a -> SEval sym (SEval sym a) Source #
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.
Rationals
Representation of rational numbers. Invariant: denominator is not 0
rationalAdd :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym) Source #
rationalSub :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym) Source #
rationalMul :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym) Source #
rationalDivide :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym) Source #
rationalLessThan :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SBit sym) Source #
rationalGreaterThan :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SBit sym) Source #