cryptol-2.8.0: Cryptol: The Language of Cryptography

Copyright(c) 2013-2016 Galois Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Cryptol.Prims.Eval

Contents

Description

 
Synopsis

Documentation

mkLit :: BitWord b w i => TValue -> Integer -> GenValue b w i Source #

Make a numeric literal value at the given type.

ecNumberV :: BitWord b w i => GenValue b w i Source #

Make a numeric constant.

ecToIntegerV :: BitWord b w i => GenValue b w i Source #

Convert a word to a non-negative integer.

ecFromIntegerV :: BitWord b w i => (Integer -> i -> i) -> GenValue b w i Source #

Convert an unbounded integer to a packed bitvector.

modExp Source #

Arguments

:: Integer

bit size of the resulting word

-> BV

base

-> BV

exponent

-> Eval BV 

Create a packed word

doubleAndAdd Source #

Arguments

:: Integer

base

-> Integer

exponent mask

-> Integer

modulus

-> Integer 

type Binary b w i = TValue -> GenValue b w i -> GenValue b w i -> Eval (GenValue b w i) Source #

binary :: Binary b w i -> GenValue b w i Source #

type Unary b w i = TValue -> GenValue b w i -> Eval (GenValue b w i) Source #

unary :: Unary b w i -> GenValue b w i Source #

liftBinArith :: (Integer -> Integer -> Integer) -> BinArith BV Source #

Turn a normal binop on Integers into one that can also deal with a bitsize. However, if the bitvector size is 0, always return the 0 bitvector.

liftDivArith :: (Integer -> Integer -> Integer) -> BinArith BV Source #

Turn a normal binop on Integers into one that can also deal with a bitsize. Generate a thunk that throws a divide by 0 error when forced if the second argument is 0. However, if the bitvector size is 0, always return the 0 bitvector.

type BinArith w = Integer -> w -> w -> Eval w Source #

modWrap :: Integral a => a -> a -> Eval a Source #

arithBinary :: forall b w i. BitWord b w i => BinArith w -> (i -> i -> Eval i) -> (Integer -> i -> i -> Eval i) -> Binary b w i Source #

type UnaryArith w = Integer -> w -> Eval w Source #

arithUnary :: forall b w i. BitWord b w i => UnaryArith w -> (i -> Eval i) -> (Integer -> i -> Eval i) -> Unary b w i Source #

arithNullary :: forall b w i. BitWord b w i => (Integer -> w) -> i -> (Integer -> i) -> TValue -> GenValue b w i Source #

addV :: BitWord b w i => Binary b w i Source #

subV :: BitWord b w i => Binary b w i Source #

mulV :: BitWord b w i => Binary b w i Source #

intV :: BitWord b w i => i -> TValue -> GenValue b w i Source #

cmpValue :: BitWord b w i => (b -> b -> Eval a -> Eval a) -> (w -> w -> Eval a -> Eval a) -> (i -> i -> Eval a -> Eval a) -> (Integer -> i -> i -> Eval a -> Eval a) -> TValue -> GenValue b w i -> GenValue b w i -> Eval a -> Eval a Source #

cmpOrder :: String -> (Ordering -> Bool) -> Binary Bool BV Integer Source #

Process two elements based on their lexicographic ordering.

signedCmpOrder :: String -> (Ordering -> Bool) -> Binary Bool BV Integer Source #

Process two elements based on their lexicographic ordering, using signed comparisons

liftWord :: BitWord b w i => (w -> w -> Eval (GenValue b w i)) -> GenValue b w i Source #

Lifted operation on finite bitsequences. Used for signed comparisons and arithemtic.

scarryV :: Value Source #

Signed carry bit.

carryV :: Value Source #

Unsigned carry bit.

zeroV :: forall b w i. BitWord b w i => TValue -> GenValue b w i Source #

joinWordVal :: BitWord b w i => WordValue b w i -> WordValue b w i -> WordValue b w i Source #

joinWords :: forall b w i. BitWord b w i => Integer -> Integer -> SeqMap b w i -> Eval (GenValue b w i) Source #

joinSeq :: BitWord b w i => Nat' -> Integer -> TValue -> SeqMap b w i -> Eval (GenValue b w i) Source #

joinV :: BitWord b w i => Nat' -> Integer -> TValue -> GenValue b w i -> Eval (GenValue b w i) Source #

Join a sequence of sequences into a single sequence.

splitWordVal :: BitWord b w i => Integer -> Integer -> WordValue b w i -> (WordValue b w i, WordValue b w i) Source #

splitAtV :: BitWord b w i => Nat' -> Nat' -> TValue -> GenValue b w i -> Eval (GenValue b w i) Source #

extractWordVal :: BitWord b w i => Integer -> Integer -> WordValue b w i -> WordValue b w i Source #

ecSplitV :: BitWord b w i => GenValue b w i Source #

Split implementation.

reverseV :: forall b w i. BitWord b w i => GenValue b w i -> Eval (GenValue b w i) Source #

transposeV :: BitWord b w i => Nat' -> Nat' -> TValue -> GenValue b w i -> Eval (GenValue b w i) Source #

ccatV :: (Show b, Show w, BitWord b w i) => Nat' -> Nat' -> TValue -> GenValue b w i -> GenValue b w i -> Eval (GenValue b w i) Source #

wordValLogicOp :: BitWord b w i => (b -> b -> b) -> (w -> w -> w) -> WordValue b w i -> WordValue b w i -> Eval (WordValue b w i) Source #

logicBinary :: forall b w i. BitWord b w i => (b -> b -> b) -> (w -> w -> w) -> Binary b w i Source #

Merge two values given a binop. This is used for and, or and xor.

wordValUnaryOp :: BitWord b w i => (b -> b) -> (w -> w) -> WordValue b w i -> Eval (WordValue b w i) Source #

logicUnary :: forall b w i. BitWord b w i => (b -> b) -> (w -> w) -> Unary b w i Source #

logicShift Source #

Arguments

:: (Integer -> Integer -> Integer -> Integer)

The function may assume its arguments are masked. It is responsible for masking its result if needed.

-> (Integer -> Seq (Eval Bool) -> Integer -> Seq (Eval Bool)) 
-> (Nat' -> TValue -> SeqValMap -> Integer -> SeqValMap) 
-> Value 

indexPrim :: BitWord b w i => (Maybe Integer -> TValue -> SeqMap b w i -> Seq b -> Eval (GenValue b w i)) -> (Maybe Integer -> TValue -> SeqMap b w i -> w -> Eval (GenValue b w i)) -> GenValue b w i Source #

Indexing operations.

updatePrim :: BitWord b w i => (Nat' -> TValue -> WordValue b w i -> WordValue b w i -> Eval (GenValue b w i) -> Eval (WordValue b w i)) -> (Nat' -> TValue -> SeqMap b w i -> WordValue b w i -> Eval (GenValue b w i) -> Eval (SeqMap b w i)) -> GenValue b w i Source #

fromToV :: BitWord b w i => GenValue b w i Source #

fromThenToV :: BitWord b w i => GenValue b w i Source #

infFromV :: BitWord b w i => GenValue b w i Source #

randomV :: BitWord b w i => TValue -> Integer -> GenValue b w i Source #

Produce a random value with the given seed. If we do not support making values of the given type, return zero of that type. TODO: do better than returning zero

errorV :: forall b w i. BitWord b w i => TValue -> String -> Eval (GenValue b w i) Source #

Orphan instances