cryptol-2.11.0: Cryptol: The Language of Cryptography
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cryptol.Backend

Contents

Synopsis

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.

Associated Types

type SBit sym :: Type Source #

type SWord sym :: Type Source #

type SInteger sym :: Type Source #

type SFloat sym :: Type Source #

type SEval sym :: Type -> Type Source #

Methods

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 -> Maybe (SEval sym a) -> String -> 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.

sPushFrame :: sym -> Name -> Range -> SEval sym a -> SEval sym a Source #

Push a call frame on to the current call stack while evaluating the given action

sWithCallStack :: sym -> CallStack -> SEval sym a -> SEval sym a Source #

Use the given call stack while evaluating the given action

sModifyCallStack :: sym -> (CallStack -> CallStack) -> SEval sym a -> SEval sym a Source #

Apply the given function to the current call stack while evaluating the given action

sGetCallStack :: sym -> SEval sym CallStack Source #

Retrieve the current evaluation call stack

mergeEval Source #

Arguments

:: 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

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

fpAsLit :: sym -> SFloat sym -> Maybe BF Source #

Determine if this symbolic floating-point value is a literal

bitLit :: sym -> Bool -> SBit sym Source #

Construct a literal bit value from a boolean.

wordLit Source #

Arguments

:: sym 
-> Integer

Width

-> Integer

Value

-> SEval sym (SWord sym) 

Construct a literal word value given a bit width and a value.

integerLit Source #

Arguments

:: sym 
-> Integer

Value

-> SEval sym (SInteger sym) 

Construct a literal integer value from the given integer.

fpLit Source #

Arguments

:: 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 #

iteFloat :: sym -> SBit sym -> SFloat sym -> SFloat sym -> SEval sym (SFloat 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 #

wordBit Source #

Arguments

:: sym 
-> SWord sym 
-> Integer

Bit position to extract

-> SEval sym (SBit sym) 

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.

wordUpdate Source #

Arguments

:: sym 
-> SWord sym 
-> Integer

Bit position to update

-> SBit sym 
-> SEval sym (SWord sym) 

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.

wordFromInt Source #

Arguments

:: sym 
-> Integer

bit-width

-> SInteger sym 
-> SEval sym (SWord sym) 

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

splitWord Source #

Arguments

:: sym 
-> Integer

left width

-> Integer

right width

-> SWord sym 
-> SEval sym (SWord sym, SWord sym) 

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.

extractWord Source #

Arguments

:: 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

intToZn Source #

Arguments

:: sym 
-> Integer

modulus

-> SInteger sym 
-> SEval sym (SInteger sym) 

Turn an integer into a value in Z_n

znToInt Source #

Arguments

:: sym 
-> Integer

modulus

-> SInteger sym 
-> SEval sym (SInteger sym) 

Transform a Z_n value into an integer, ensuring the value is properly reduced modulo n

znPlus Source #

Arguments

:: sym 
-> Integer

modulus

-> SInteger sym 
-> SInteger sym 
-> SEval sym (SInteger sym) 

Addition of integers modulo n, for a concrete positive integer n.

znNegate Source #

Arguments

:: sym 
-> Integer

modulus

-> SInteger sym 
-> SEval sym (SInteger sym) 

Additive inverse of integers modulo n

znMinus Source #

Arguments

:: sym 
-> Integer

modulus

-> SInteger sym 
-> SInteger sym 
-> SEval sym (SInteger sym) 

Subtraction of integers modulo n, for a concrete positive integer n.

znMult Source #

Arguments

:: sym 
-> Integer

modulus

-> SInteger sym 
-> SInteger sym 
-> SEval sym (SInteger sym) 

Multiplication of integers modulo n, for a concrete positive integer n.

znEq Source #

Arguments

:: sym 
-> Integer

modulus

-> SInteger sym 
-> SInteger sym 
-> SEval sym (SBit sym) 

Equality test of integers modulo n

znRecip Source #

Arguments

:: sym 
-> Integer

modulus

-> SInteger sym 
-> SEval sym (SInteger sym) 

Multiplicative 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 #

fpNaN Source #

Arguments

:: sym 
-> Integer

exponent bits

-> Integer

precision bits

-> SEval sym (SFloat sym) 

fpPosInf Source #

Arguments

:: sym 
-> Integer

exponent bits

-> Integer

precision bits

-> SEval sym (SFloat sym) 

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 #

fpAbs :: sym -> SFloat sym -> SEval sym (SFloat sym) Source #

fpSqrt :: sym -> SWord sym -> SFloat sym -> SEval sym (SFloat sym) Source #

fpFMA :: sym -> SWord sym -> SFloat sym -> SFloat sym -> SFloat sym -> SEval sym (SFloat sym) Source #

fpIsZero :: sym -> SFloat sym -> SEval sym (SBit sym) Source #

fpIsNeg :: sym -> SFloat sym -> SEval sym (SBit sym) Source #

fpIsNaN :: sym -> SFloat sym -> SEval sym (SBit sym) Source #

fpIsInf :: sym -> SFloat sym -> SEval sym (SBit sym) Source #

fpIsNorm :: sym -> SFloat sym -> SEval sym (SBit sym) Source #

fpIsSubnorm :: sym -> SFloat sym -> SEval sym (SBit sym) Source #

fpToBits :: sym -> SFloat sym -> SEval sym (SWord sym) Source #

fpFromBits Source #

Arguments

:: sym 
-> Integer

exponent bits

-> Integer

precision bits

-> SWord sym 
-> SEval sym (SFloat sym) 

fpToInteger Source #

Arguments

:: sym 
-> String

Name of the function for error reporting

-> SWord sym

Rounding mode

-> SFloat sym 
-> SEval sym (SInteger sym) 

fpFromInteger Source #

Arguments

:: sym 
-> Integer

exp width

-> Integer

prec width

-> SWord sym

rounding mode

-> SInteger sym

the integer to use

-> SEval sym (SFloat sym) 

fpToRational :: sym -> SFloat sym -> SEval sym (SRational sym) Source #

fpFromRational Source #

Arguments

:: sym 
-> Integer

exp width

-> Integer

prec width

-> SWord sym

rounding mode

-> SRational sym 
-> SEval sym (SFloat sym) 

Instances

Instances details
Backend Concrete Source # 
Instance details

Defined in Cryptol.Backend.Concrete

Methods

isReady :: Concrete -> SEval Concrete a -> Bool Source #

sDeclareHole :: Concrete -> String -> SEval Concrete (SEval Concrete a, SEval Concrete a -> SEval Concrete ()) Source #

sDelayFill :: Concrete -> SEval Concrete a -> Maybe (SEval Concrete a) -> String -> SEval Concrete (SEval Concrete a) Source #

sSpark :: Concrete -> SEval Concrete a -> SEval Concrete (SEval Concrete a) Source #

sPushFrame :: Concrete -> Name -> Range -> SEval Concrete a -> SEval Concrete a Source #

sWithCallStack :: Concrete -> CallStack -> SEval Concrete a -> SEval Concrete a Source #

sModifyCallStack :: Concrete -> (CallStack -> CallStack) -> SEval Concrete a -> SEval Concrete a Source #

sGetCallStack :: Concrete -> SEval Concrete CallStack Source #

mergeEval :: Concrete -> (SBit Concrete -> a -> a -> SEval Concrete a) -> SBit Concrete -> SEval Concrete a -> SEval Concrete a -> SEval Concrete a Source #

assertSideCondition :: Concrete -> SBit Concrete -> EvalError -> SEval Concrete () Source #

raiseError :: Concrete -> EvalError -> SEval Concrete a Source #

bitAsLit :: Concrete -> SBit Concrete -> Maybe Bool Source #

wordLen :: Concrete -> SWord Concrete -> Integer Source #

wordAsLit :: Concrete -> SWord Concrete -> Maybe (Integer, Integer) Source #

wordAsChar :: Concrete -> SWord Concrete -> Maybe Char Source #

integerAsLit :: Concrete -> SInteger Concrete -> Maybe Integer Source #

fpAsLit :: Concrete -> SFloat Concrete -> Maybe BF Source #

bitLit :: Concrete -> Bool -> SBit Concrete Source #

wordLit :: Concrete -> Integer -> Integer -> SEval Concrete (SWord Concrete) Source #

integerLit :: Concrete -> Integer -> SEval Concrete (SInteger Concrete) Source #

fpLit :: Concrete -> Integer -> Integer -> Rational -> SEval Concrete (SFloat Concrete) Source #

fpExactLit :: Concrete -> BF -> SEval Concrete (SFloat Concrete) Source #

iteBit :: Concrete -> SBit Concrete -> SBit Concrete -> SBit Concrete -> SEval Concrete (SBit Concrete) Source #

iteWord :: Concrete -> SBit Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

iteInteger :: Concrete -> SBit Concrete -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

iteFloat :: Concrete -> SBit Concrete -> SFloat Concrete -> SFloat Concrete -> SEval Concrete (SFloat Concrete) Source #

bitEq :: Concrete -> SBit Concrete -> SBit Concrete -> SEval Concrete (SBit Concrete) Source #

bitOr :: Concrete -> SBit Concrete -> SBit Concrete -> SEval Concrete (SBit Concrete) Source #

bitAnd :: Concrete -> SBit Concrete -> SBit Concrete -> SEval Concrete (SBit Concrete) Source #

bitXor :: Concrete -> SBit Concrete -> SBit Concrete -> SEval Concrete (SBit Concrete) Source #

bitComplement :: Concrete -> SBit Concrete -> SEval Concrete (SBit Concrete) Source #

wordBit :: Concrete -> SWord Concrete -> Integer -> SEval Concrete (SBit Concrete) Source #

wordUpdate :: Concrete -> SWord Concrete -> Integer -> SBit Concrete -> SEval Concrete (SWord Concrete) Source #

packWord :: Concrete -> [SBit Concrete] -> SEval Concrete (SWord Concrete) Source #

unpackWord :: Concrete -> SWord Concrete -> SEval Concrete [SBit Concrete] Source #

wordFromInt :: Concrete -> Integer -> SInteger Concrete -> SEval Concrete (SWord Concrete) Source #

joinWord :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

splitWord :: Concrete -> Integer -> Integer -> SWord Concrete -> SEval Concrete (SWord Concrete, SWord Concrete) Source #

extractWord :: Concrete -> Integer -> Integer -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordOr :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordAnd :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordXor :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordComplement :: Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordPlus :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordMinus :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordMult :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordDiv :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordMod :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordSignedDiv :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordSignedMod :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordNegate :: Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordLg2 :: Concrete -> SWord Concrete -> SEval Concrete (SWord Concrete) Source #

wordEq :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SBit Concrete) Source #

wordSignedLessThan :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SBit Concrete) Source #

wordLessThan :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SBit Concrete) Source #

wordGreaterThan :: Concrete -> SWord Concrete -> SWord Concrete -> SEval Concrete (SBit Concrete) Source #

wordToInt :: Concrete -> SWord Concrete -> SEval Concrete (SInteger Concrete) Source #

intPlus :: Concrete -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

intNegate :: Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

intMinus :: Concrete -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

intMult :: Concrete -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

intDiv :: Concrete -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

intMod :: Concrete -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

intEq :: Concrete -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SBit Concrete) Source #

intLessThan :: Concrete -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SBit Concrete) Source #

intGreaterThan :: Concrete -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SBit Concrete) Source #

intToZn :: Concrete -> Integer -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

znToInt :: Concrete -> Integer -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

znPlus :: Concrete -> Integer -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

znNegate :: Concrete -> Integer -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

znMinus :: Concrete -> Integer -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

znMult :: Concrete -> Integer -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

znEq :: Concrete -> Integer -> SInteger Concrete -> SInteger Concrete -> SEval Concrete (SBit Concrete) Source #

znRecip :: Concrete -> Integer -> SInteger Concrete -> SEval Concrete (SInteger Concrete) Source #

fpEq :: Concrete -> SFloat Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpLessThan :: Concrete -> SFloat Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpGreaterThan :: Concrete -> SFloat Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpLogicalEq :: Concrete -> SFloat Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpNaN :: Concrete -> Integer -> Integer -> SEval Concrete (SFloat Concrete) Source #

fpPosInf :: Concrete -> Integer -> Integer -> SEval Concrete (SFloat Concrete) Source #

fpPlus :: FPArith2 Concrete Source #

fpMinus :: FPArith2 Concrete Source #

fpMult :: FPArith2 Concrete Source #

fpDiv :: FPArith2 Concrete Source #

fpNeg :: Concrete -> SFloat Concrete -> SEval Concrete (SFloat Concrete) Source #

fpAbs :: Concrete -> SFloat Concrete -> SEval Concrete (SFloat Concrete) Source #

fpSqrt :: Concrete -> SWord Concrete -> SFloat Concrete -> SEval Concrete (SFloat Concrete) Source #

fpFMA :: Concrete -> SWord Concrete -> SFloat Concrete -> SFloat Concrete -> SFloat Concrete -> SEval Concrete (SFloat Concrete) Source #

fpIsZero :: Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpIsNeg :: Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpIsNaN :: Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpIsInf :: Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpIsNorm :: Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpIsSubnorm :: Concrete -> SFloat Concrete -> SEval Concrete (SBit Concrete) Source #

fpToBits :: Concrete -> SFloat Concrete -> SEval Concrete (SWord Concrete) Source #

fpFromBits :: Concrete -> Integer -> Integer -> SWord Concrete -> SEval Concrete (SFloat Concrete) Source #

fpToInteger :: Concrete -> String -> SWord Concrete -> SFloat Concrete -> SEval Concrete (SInteger Concrete) Source #

fpFromInteger :: Concrete -> Integer -> Integer -> SWord Concrete -> SInteger Concrete -> SEval Concrete (SFloat Concrete) Source #

fpToRational :: Concrete -> SFloat Concrete -> SEval Concrete (SRational Concrete) Source #

fpFromRational :: Concrete -> Integer -> Integer -> SWord Concrete -> SRational Concrete -> SEval Concrete (SFloat Concrete) Source #

Backend SBV Source # 
Instance details

Defined in Cryptol.Backend.SBV

Associated Types

type SBit SBV Source #

type SWord SBV Source #

type SInteger SBV Source #

type SFloat SBV Source #

type SEval SBV :: Type -> Type Source #

Methods

isReady :: SBV -> SEval SBV a -> Bool Source #

sDeclareHole :: SBV -> String -> SEval SBV (SEval SBV a, SEval SBV a -> SEval SBV ()) Source #

sDelayFill :: SBV -> SEval SBV a -> Maybe (SEval SBV a) -> String -> SEval SBV (SEval SBV a) Source #

sSpark :: SBV -> SEval SBV a -> SEval SBV (SEval SBV a) Source #

sPushFrame :: SBV -> Name -> Range -> SEval SBV a -> SEval SBV a Source #

sWithCallStack :: SBV -> CallStack -> SEval SBV a -> SEval SBV a Source #

sModifyCallStack :: SBV -> (CallStack -> CallStack) -> SEval SBV a -> SEval SBV a Source #

sGetCallStack :: SBV -> SEval SBV CallStack Source #

mergeEval :: SBV -> (SBit SBV -> a -> a -> SEval SBV a) -> SBit SBV -> SEval SBV a -> SEval SBV a -> SEval SBV a Source #

assertSideCondition :: SBV -> SBit SBV -> EvalError -> SEval SBV () Source #

raiseError :: SBV -> EvalError -> SEval SBV a Source #

bitAsLit :: SBV -> SBit SBV -> Maybe Bool Source #

wordLen :: SBV -> SWord SBV -> Integer Source #

wordAsLit :: SBV -> SWord SBV -> Maybe (Integer, Integer) Source #

wordAsChar :: SBV -> SWord SBV -> Maybe Char Source #

integerAsLit :: SBV -> SInteger SBV -> Maybe Integer Source #

fpAsLit :: SBV -> SFloat SBV -> Maybe BF Source #

bitLit :: SBV -> Bool -> SBit SBV Source #

wordLit :: SBV -> Integer -> Integer -> SEval SBV (SWord SBV) Source #

integerLit :: SBV -> Integer -> SEval SBV (SInteger SBV) Source #

fpLit :: SBV -> Integer -> Integer -> Rational -> SEval SBV (SFloat SBV) Source #

fpExactLit :: SBV -> BF -> SEval SBV (SFloat SBV) Source #

iteBit :: SBV -> SBit SBV -> SBit SBV -> SBit SBV -> SEval SBV (SBit SBV) Source #

iteWord :: SBV -> SBit SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

iteInteger :: SBV -> SBit SBV -> SInteger SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

iteFloat :: SBV -> SBit SBV -> SFloat SBV -> SFloat SBV -> SEval SBV (SFloat SBV) Source #

bitEq :: SBV -> SBit SBV -> SBit SBV -> SEval SBV (SBit SBV) Source #

bitOr :: SBV -> SBit SBV -> SBit SBV -> SEval SBV (SBit SBV) Source #

bitAnd :: SBV -> SBit SBV -> SBit SBV -> SEval SBV (SBit SBV) Source #

bitXor :: SBV -> SBit SBV -> SBit SBV -> SEval SBV (SBit SBV) Source #

bitComplement :: SBV -> SBit SBV -> SEval SBV (SBit SBV) Source #

wordBit :: SBV -> SWord SBV -> Integer -> SEval SBV (SBit SBV) Source #

wordUpdate :: SBV -> SWord SBV -> Integer -> SBit SBV -> SEval SBV (SWord SBV) Source #

packWord :: SBV -> [SBit SBV] -> SEval SBV (SWord SBV) Source #

unpackWord :: SBV -> SWord SBV -> SEval SBV [SBit SBV] Source #

wordFromInt :: SBV -> Integer -> SInteger SBV -> SEval SBV (SWord SBV) Source #

joinWord :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

splitWord :: SBV -> Integer -> Integer -> SWord SBV -> SEval SBV (SWord SBV, SWord SBV) Source #

extractWord :: SBV -> Integer -> Integer -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordOr :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordAnd :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordXor :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordComplement :: SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordPlus :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordMinus :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordMult :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordDiv :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordMod :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordSignedDiv :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordSignedMod :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordNegate :: SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordLg2 :: SBV -> SWord SBV -> SEval SBV (SWord SBV) Source #

wordEq :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SBit SBV) Source #

wordSignedLessThan :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SBit SBV) Source #

wordLessThan :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SBit SBV) Source #

wordGreaterThan :: SBV -> SWord SBV -> SWord SBV -> SEval SBV (SBit SBV) Source #

wordToInt :: SBV -> SWord SBV -> SEval SBV (SInteger SBV) Source #

intPlus :: SBV -> SInteger SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

intNegate :: SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

intMinus :: SBV -> SInteger SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

intMult :: SBV -> SInteger SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

intDiv :: SBV -> SInteger SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

intMod :: SBV -> SInteger SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

intEq :: SBV -> SInteger SBV -> SInteger SBV -> SEval SBV (SBit SBV) Source #

intLessThan :: SBV -> SInteger SBV -> SInteger SBV -> SEval SBV (SBit SBV) Source #

intGreaterThan :: SBV -> SInteger SBV -> SInteger SBV -> SEval SBV (SBit SBV) Source #

intToZn :: SBV -> Integer -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

znToInt :: SBV -> Integer -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

znPlus :: SBV -> Integer -> SInteger SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

znNegate :: SBV -> Integer -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

znMinus :: SBV -> Integer -> SInteger SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

znMult :: SBV -> Integer -> SInteger SBV -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

znEq :: SBV -> Integer -> SInteger SBV -> SInteger SBV -> SEval SBV (SBit SBV) Source #

znRecip :: SBV -> Integer -> SInteger SBV -> SEval SBV (SInteger SBV) Source #

fpEq :: SBV -> SFloat SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpLessThan :: SBV -> SFloat SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpGreaterThan :: SBV -> SFloat SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpLogicalEq :: SBV -> SFloat SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpNaN :: SBV -> Integer -> Integer -> SEval SBV (SFloat SBV) Source #

fpPosInf :: SBV -> Integer -> Integer -> SEval SBV (SFloat SBV) Source #

fpPlus :: FPArith2 SBV Source #

fpMinus :: FPArith2 SBV Source #

fpMult :: FPArith2 SBV Source #

fpDiv :: FPArith2 SBV Source #

fpNeg :: SBV -> SFloat SBV -> SEval SBV (SFloat SBV) Source #

fpAbs :: SBV -> SFloat SBV -> SEval SBV (SFloat SBV) Source #

fpSqrt :: SBV -> SWord SBV -> SFloat SBV -> SEval SBV (SFloat SBV) Source #

fpFMA :: SBV -> SWord SBV -> SFloat SBV -> SFloat SBV -> SFloat SBV -> SEval SBV (SFloat SBV) Source #

fpIsZero :: SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpIsNeg :: SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpIsNaN :: SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpIsInf :: SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpIsNorm :: SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpIsSubnorm :: SBV -> SFloat SBV -> SEval SBV (SBit SBV) Source #

fpToBits :: SBV -> SFloat SBV -> SEval SBV (SWord SBV) Source #

fpFromBits :: SBV -> Integer -> Integer -> SWord SBV -> SEval SBV (SFloat SBV) Source #

fpToInteger :: SBV -> String -> SWord SBV -> SFloat SBV -> SEval SBV (SInteger SBV) Source #

fpFromInteger :: SBV -> Integer -> Integer -> SWord SBV -> SInteger SBV -> SEval SBV (SFloat SBV) Source #

fpToRational :: SBV -> SFloat SBV -> SEval SBV (SRational SBV) Source #

fpFromRational :: SBV -> Integer -> Integer -> SWord SBV -> SRational SBV -> SEval SBV (SFloat SBV) Source #

IsSymExprBuilder sym => Backend (What4 sym) Source # 
Instance details

Defined in Cryptol.Backend.What4

Associated Types

type SBit (What4 sym) Source #

type SWord (What4 sym) Source #

type SInteger (What4 sym) Source #

type SFloat (What4 sym) Source #

type SEval (What4 sym) :: Type -> Type Source #

Methods

isReady :: What4 sym -> SEval (What4 sym) a -> Bool Source #

sDeclareHole :: What4 sym -> String -> SEval (What4 sym) (SEval (What4 sym) a, SEval (What4 sym) a -> SEval (What4 sym) ()) Source #

sDelayFill :: What4 sym -> SEval (What4 sym) a -> Maybe (SEval (What4 sym) a) -> String -> SEval (What4 sym) (SEval (What4 sym) a) Source #

sSpark :: What4 sym -> SEval (What4 sym) a -> SEval (What4 sym) (SEval (What4 sym) a) Source #

sPushFrame :: What4 sym -> Name -> Range -> SEval (What4 sym) a -> SEval (What4 sym) a Source #

sWithCallStack :: What4 sym -> CallStack -> SEval (What4 sym) a -> SEval (What4 sym) a Source #

sModifyCallStack :: What4 sym -> (CallStack -> CallStack) -> SEval (What4 sym) a -> SEval (What4 sym) a Source #

sGetCallStack :: What4 sym -> SEval (What4 sym) CallStack Source #

mergeEval :: What4 sym -> (SBit (What4 sym) -> a -> a -> SEval (What4 sym) a) -> SBit (What4 sym) -> SEval (What4 sym) a -> SEval (What4 sym) a -> SEval (What4 sym) a Source #

assertSideCondition :: What4 sym -> SBit (What4 sym) -> EvalError -> SEval (What4 sym) () Source #

raiseError :: What4 sym -> EvalError -> SEval (What4 sym) a Source #

bitAsLit :: What4 sym -> SBit (What4 sym) -> Maybe Bool Source #

wordLen :: What4 sym -> SWord (What4 sym) -> Integer Source #

wordAsLit :: What4 sym -> SWord (What4 sym) -> Maybe (Integer, Integer) Source #

wordAsChar :: What4 sym -> SWord (What4 sym) -> Maybe Char Source #

integerAsLit :: What4 sym -> SInteger (What4 sym) -> Maybe Integer Source #

fpAsLit :: What4 sym -> SFloat (What4 sym) -> Maybe BF Source #

bitLit :: What4 sym -> Bool -> SBit (What4 sym) Source #

wordLit :: What4 sym -> Integer -> Integer -> SEval (What4 sym) (SWord (What4 sym)) Source #

integerLit :: What4 sym -> Integer -> SEval (What4 sym) (SInteger (What4 sym)) Source #

fpLit :: What4 sym -> Integer -> Integer -> Rational -> SEval (What4 sym) (SFloat (What4 sym)) Source #

fpExactLit :: What4 sym -> BF -> SEval (What4 sym) (SFloat (What4 sym)) Source #

iteBit :: What4 sym -> SBit (What4 sym) -> SBit (What4 sym) -> SBit (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

iteWord :: What4 sym -> SBit (What4 sym) -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

iteInteger :: What4 sym -> SBit (What4 sym) -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

iteFloat :: What4 sym -> SBit (What4 sym) -> SFloat (What4 sym) -> SFloat (What4 sym) -> SEval (What4 sym) (SFloat (What4 sym)) Source #

bitEq :: What4 sym -> SBit (What4 sym) -> SBit (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

bitOr :: What4 sym -> SBit (What4 sym) -> SBit (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

bitAnd :: What4 sym -> SBit (What4 sym) -> SBit (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

bitXor :: What4 sym -> SBit (What4 sym) -> SBit (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

bitComplement :: What4 sym -> SBit (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

wordBit :: What4 sym -> SWord (What4 sym) -> Integer -> SEval (What4 sym) (SBit (What4 sym)) Source #

wordUpdate :: What4 sym -> SWord (What4 sym) -> Integer -> SBit (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

packWord :: What4 sym -> [SBit (What4 sym)] -> SEval (What4 sym) (SWord (What4 sym)) Source #

unpackWord :: What4 sym -> SWord (What4 sym) -> SEval (What4 sym) [SBit (What4 sym)] Source #

wordFromInt :: What4 sym -> Integer -> SInteger (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

joinWord :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

splitWord :: What4 sym -> Integer -> Integer -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym), SWord (What4 sym)) Source #

extractWord :: What4 sym -> Integer -> Integer -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordOr :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordAnd :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordXor :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordComplement :: What4 sym -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordPlus :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordMinus :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordMult :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordDiv :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordMod :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordSignedDiv :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordSignedMod :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordNegate :: What4 sym -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordLg2 :: What4 sym -> SWord (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

wordEq :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

wordSignedLessThan :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

wordLessThan :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

wordGreaterThan :: What4 sym -> SWord (What4 sym) -> SWord (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

wordToInt :: What4 sym -> SWord (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

intPlus :: What4 sym -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

intNegate :: What4 sym -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

intMinus :: What4 sym -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

intMult :: What4 sym -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

intDiv :: What4 sym -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

intMod :: What4 sym -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

intEq :: What4 sym -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

intLessThan :: What4 sym -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

intGreaterThan :: What4 sym -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

intToZn :: What4 sym -> Integer -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

znToInt :: What4 sym -> Integer -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

znPlus :: What4 sym -> Integer -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

znNegate :: What4 sym -> Integer -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

znMinus :: What4 sym -> Integer -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

znMult :: What4 sym -> Integer -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

znEq :: What4 sym -> Integer -> SInteger (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

znRecip :: What4 sym -> Integer -> SInteger (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

fpEq :: What4 sym -> SFloat (What4 sym) -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpLessThan :: What4 sym -> SFloat (What4 sym) -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpGreaterThan :: What4 sym -> SFloat (What4 sym) -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpLogicalEq :: What4 sym -> SFloat (What4 sym) -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpNaN :: What4 sym -> Integer -> Integer -> SEval (What4 sym) (SFloat (What4 sym)) Source #

fpPosInf :: What4 sym -> Integer -> Integer -> SEval (What4 sym) (SFloat (What4 sym)) Source #

fpPlus :: FPArith2 (What4 sym) Source #

fpMinus :: FPArith2 (What4 sym) Source #

fpMult :: FPArith2 (What4 sym) Source #

fpDiv :: FPArith2 (What4 sym) Source #

fpNeg :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SFloat (What4 sym)) Source #

fpAbs :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SFloat (What4 sym)) Source #

fpSqrt :: What4 sym -> SWord (What4 sym) -> SFloat (What4 sym) -> SEval (What4 sym) (SFloat (What4 sym)) Source #

fpFMA :: What4 sym -> SWord (What4 sym) -> SFloat (What4 sym) -> SFloat (What4 sym) -> SFloat (What4 sym) -> SEval (What4 sym) (SFloat (What4 sym)) Source #

fpIsZero :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpIsNeg :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpIsNaN :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpIsInf :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpIsNorm :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpIsSubnorm :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SBit (What4 sym)) Source #

fpToBits :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SWord (What4 sym)) Source #

fpFromBits :: What4 sym -> Integer -> Integer -> SWord (What4 sym) -> SEval (What4 sym) (SFloat (What4 sym)) Source #

fpToInteger :: What4 sym -> String -> SWord (What4 sym) -> SFloat (What4 sym) -> SEval (What4 sym) (SInteger (What4 sym)) Source #

fpFromInteger :: What4 sym -> Integer -> Integer -> SWord (What4 sym) -> SInteger (What4 sym) -> SEval (What4 sym) (SFloat (What4 sym)) Source #

fpToRational :: What4 sym -> SFloat (What4 sym) -> SEval (What4 sym) (SRational (What4 sym)) Source #

fpFromRational :: What4 sym -> Integer -> Integer -> SWord (What4 sym) -> SRational (What4 sym) -> SEval (What4 sym) (SFloat (What4 sym)) Source #

sDelay :: Backend sym => sym -> 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.

invalidIndex :: Backend sym => sym -> Integer -> SEval sym a Source #

cryUserError :: Backend sym => sym -> String -> SEval sym a Source #

cryNoPrimError :: Backend sym => sym -> Name -> SEval sym a Source #

type FPArith2 sym = sym -> SWord sym -> SFloat sym -> SFloat sym -> SEval sym (SFloat sym) Source #

Rationals

data SRational sym Source #

Representation of rational numbers. Invariant: denominator is not 0

Constructors

SRational 

Fields

intToRational :: Backend sym => sym -> SInteger sym -> SEval sym (SRational sym) Source #

ratio :: Backend sym => sym -> SInteger sym -> SInteger sym -> SEval sym (SRational sym) Source #

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 #

rationalNegate :: Backend sym => sym -> SRational sym -> SEval sym (SRational sym) Source #

rationalMul :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym) Source #

rationalRecip :: Backend sym => sym -> SRational sym -> SEval sym (SRational sym) Source #

rationalDivide :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SRational sym) Source #

rationalFloor :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym) Source #

rationalCeiling :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym) Source #

rationalTrunc :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym) Source #

rationalRoundAway :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym) Source #

rationalRoundToEven :: Backend sym => sym -> SRational sym -> SEval sym (SInteger sym) Source #

rationalEq :: Backend sym => sym -> SRational sym -> SRational sym -> SEval sym (SBit 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 #

iteRational :: Backend sym => sym -> SBit sym -> SRational sym -> SRational sym -> SEval sym (SRational sym) Source #