raaz-0.2.1: The raaz cryptographic library.

Safe HaskellNone
LanguageHaskell2010

Raaz.Core.Types

Contents

Description

This module exposes some core types used through out the Raaz library. One of the major goals of the raaz cryptographic library is to use the type safety of Haskell to catch some common bugs at compile time.

WARNING: If you are just a user of this library, it is unlikely that you will need to import this module. It is only required if you are a developer and want to define a new cryptographic data type.

Synopsis

Overview.

A lot of cryptographic code is low level and involves quite a bit of boilerplate and are therefore fertile grounds for bugs. This module describes types specific to raaz that are designed to catch bugs in such low level code. The three principles that we follow in the design are:

  1. Define distinct types for semantically different objects. For example, distinguish between buffer length/pointer offset in bytes versus other units (see LengthUnit) or make endian aware variants of standard word types (see BE and LE) etc.
  2. Make sure that the low level functions are sensitive to these types. For example, the function sizeOf exposed here returns BYTES Int instead of just Int and functions like allocaBuffer are generic enough to work with any length units.
  3. Provide obvious instances for some basic type and have and idiom/design pattern to build such interfaces for user defined types. For example, we have a very specific way to build timing safe equality functions for arbitrary types. Most of the time, in our case it just amounts to handling product types.

Role of Monoids.

Monoids play an important role in facilitating the top down approach to type safety that we mentioned above. Some types described here have a natural monoid semantics. For example, when dealing with pointer offsets and buffer sizes, we use type safe length units like BYTES. These length units are instances of monoids where the underlying operation is addition. On the other hand, when it comes to pointer alignment which is captured by the type Alignment, the monoid operation is taking the lowest common multiple.

Timing safe equality checking.

Many cryptographic setting require comparing two secrets and such comparisons should be timing safe, i.e. the time taken to make the comparison should not depend on the actual values that are compared. Unfortunately, the equality comparison of may Haskell types like ByteString, provided via the class Eq is not timing safe. In raaz we take special care in defining the Eq instance of all cryptographically sensitive types which make them timing safe . For example, if we compare two digests dgst1 == dgst2, the Eq instance is defined in such a way that the time taken is constant irrespective of the actual values. We also give a mechanism to build timing safe equality for more complicated types that user might need to define in her use cases as we now describe.

The starting point of defining such timing safe equality is the class Equality which plays the role Eq. The member function eq playing the role of (==) with an important difference. The comparison function eq returns the type type Result instead of Bool and it is timing safe. The Eq instance is then defined by making use of the operator (===). Thus a user of the library can stick to the familiar Eq class and get the benefits of timing safe comparison

Building timing safe equality for Custom types.

For basic types like Word32, Word64 this module defines instances of Equality. The Tuple type inherits the Equality instance from its base type. As a developer, new crypto-primitives or protocols often need to define timing safe equality for types other than those exported here. This is done in two stages.

  1. Define an instance of Equality.
  2. Make use of the above instance to define Eq instance as follows.
data SomeSensitiveType = ...

instance Equality SomeSensitiveType where
         eq a b = ...

instance Eq SomeSensitiveType where
     (==) a b = a === b

Combining multiple comparisons using Monoid operations

The Result type is an opaque type and does not allow inspection via a pattern match or conversion to Bool. However, while defining the Equality instance, we often need to perform an AND of multiple comparison (think of comparing a tuple). This is where the monoid instance of Result is useful. If r1 and r2 are the results of two comparisons then r1 mappend r2 essentially takes the AND of these results. However, unlike in the case of AND-ing in Bool, mappend on the Result type does not short-circuit. In fact, the whole point of using Result type instead of Bool is to avoid this short circuiting.

To illustrate, we have the following code fragment

data Foo = Foo Word32 Word64

instance Equality Foo where
   eq (Foo a b) (Foo c d) = eq a c `mapped` eq b d

instance Eq Foo where
   (=) = (===)

Automatic deriving of Equality instances.

We often find ourselves wrapping existing types in new types keeping in line with the philosophy of distinguishing sematically distinct data with their types. It would be tedious to repeat the above process for each such type. Often, we can get away by just deriving these instances thereby saving a lot of boilerplate. For example, consider a data type that needs to keep a 128-byte secret. A simple deriving class would work in such cases.

newtype Secret = Secret (Tuple 128 Word8) deriving (Equality, Eq)

The Eq instance here would be timing safe because it is essentially the Eq instance of tuples. The deriving Equality is not strictly required here. However, we suggest keeping it so that on can define timing safe equality for other types that contain a component of type Secret.

Beware: deriving clause can be dangerous

The deriving clause that we defined above while convenient, hides a danger when not used properly. For example, consider the following definitions.

data    Bad      = Bad Bar Biz deriving Eq
newtype BadAgain = BadAgain (Bar, Biz) deriving (Eq, Equality)

The comparison for the elements of the type Bad would leak some timing information even when Bar and Biz are instances of Equality and thus have timing safe equalities themselves. This is because the automatic derivation of Eq instances in the above two cases performs a component by component comparison and combines the result using and. Due to boolean short circuiting, this will lead to timing information being leaked.

For product types, we can safely derive the Equality instance and use it to define the Eq instance as follows

newtype Okey2 = Okey (Foo, Bar) deriving Equality

instance Eq Okey2 where
   (=) = (===)

class Equality a where Source #

All types that support timing safe equality are instances of this class.

Methods

eq :: a -> a -> Result Source #

Instances
Equality Word Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: Word -> Word -> Result Source #

Equality Word8 Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: Word8 -> Word8 -> Result Source #

Equality Word16 Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: Word16 -> Word16 -> Result Source #

Equality Word32 Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: Word32 -> Word32 -> Result Source #

Equality Word64 Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: Word64 -> Word64 -> Result Source #

Equality SHA1 Source # 
Instance details

Defined in Raaz.Hash.Sha1.Internal

Methods

eq :: SHA1 -> SHA1 -> Result Source #

Equality SHA224 Source # 
Instance details

Defined in Raaz.Hash.Sha224.Internal

Methods

eq :: SHA224 -> SHA224 -> Result Source #

Equality SHA256 Source # 
Instance details

Defined in Raaz.Hash.Sha256.Internal

Methods

eq :: SHA256 -> SHA256 -> Result Source #

Equality SHA384 Source # 
Instance details

Defined in Raaz.Hash.Sha384.Internal

Methods

eq :: SHA384 -> SHA384 -> Result Source #

Equality SHA512 Source # 
Instance details

Defined in Raaz.Hash.Sha512.Internal

Methods

eq :: SHA512 -> SHA512 -> Result Source #

Equality a => Equality (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

eq :: BITS a -> BITS a -> Result Source #

Equality a => Equality (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

eq :: BYTES a -> BYTES a -> Result Source #

Equality w => Equality (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

eq :: BE w -> BE w -> Result Source #

Equality w => Equality (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

eq :: LE w -> LE w -> Result Source #

(Equality a, Equality b) => Equality (a, b) Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: (a, b) -> (a, b) -> Result Source #

(Unbox a, Equality a) => Equality (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

eq :: Tuple dim a -> Tuple dim a -> Result Source #

(Equality a, Equality b, Equality c) => Equality (a, b, c) Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: (a, b, c) -> (a, b, c) -> Result Source #

(Equality a, Equality b, Equality c, Equality d) => Equality (a, b, c, d) Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: (a, b, c, d) -> (a, b, c, d) -> Result Source #

(Equality a, Equality b, Equality c, Equality d, Equality e) => Equality (a, b, c, d, e) Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: (a, b, c, d, e) -> (a, b, c, d, e) -> Result Source #

(Equality a, Equality b, Equality c, Equality d, Equality e, Equality f) => Equality (a, b, c, d, e, f) Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Result Source #

(Equality a, Equality b, Equality c, Equality d, Equality e, Equality f, Equality g) => Equality (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Methods

eq :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Result Source #

(===) :: Equality a => a -> a -> Bool Source #

Check whether two values are equal using the timing safe eq function. Use this function when defining the Eq instance for a Sensitive data type.

data Result Source #

The result of a comparison. This is an opaque type and the monoid instance essentially takes AND of two comparisons in a timing safe way.

Instances
Semigroup Result Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Monoid Result Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Unbox Result Source # 
Instance details

Defined in Raaz.Core.Types.Equality

Vector Vector Result Source # 
Instance details

Defined in Raaz.Core.Types.Equality

MVector MVector Result Source # 
Instance details

Defined in Raaz.Core.Types.Equality

newtype Vector Result Source #

Vector of Results.

Instance details

Defined in Raaz.Core.Types.Equality

newtype MVector s Result Source #

MVector for Results.

Instance details

Defined in Raaz.Core.Types.Equality

Endianess aware types.

Cryptographic primitives often consider their input as an array of words of a particular endianness. Endianness is only relevant when serialising to (or de-serialising from) their encoding to the outside world. Raaz strives to use types to provide an endian agnostic interface to all data that is relevant to the outside world.

The starting point of an endian agnostic interface is the class EndianStore. Instances of this class support an endian agnostic load and store. Endian adjusted copying is also provided for these types through the helper functions copyFromBytes and copyToBytes.

It is tedious to think about endianness for each new type one might encounter. As before, we have a top down approach to defining such an interface. To start with, the library exposes endian aware variants of Word32 and Word64 and functions littleEndian and bigEndian for conversions. The Tuple type inherits the endianness of its element type, i.e for example Tuple 10 (LE Word32) when loded (or stored) will load (or store) 10 32-bit words assuming that the words are expressed in little endian. Other types are then built out of these endian aware types. For example, cryptographic type SHA512 is defined as.

newtype SHA512 = SHA512 (Tuple 8 (BE Word64))
                     deriving (Equality, Eq, Storable, EndianStore)

class Storable w => EndianStore w where Source #

This class captures types which provides an endian agnostic way of loading from and storing to data buffers. Any multi-byte type that is meant to be serialised to the outside world should be an instance of this class. When defining the load, store, adjustEndian member functions, care should be taken to ensure proper endian conversion.

Methods

store Source #

Arguments

:: Ptr w

the location.

-> w

value to store

-> IO () 

The action store ptr w stores w at the location pointed by ptr. Endianness of the type w is taken care of when storing. For example, irrespective of the endianness of the machine, store ptr (0x01020304 :: BE Word32) will store the bytes 0x01, 0x02, 0x03, 0x04 respectively at locations ptr, ptr +1, ptr+2 and ptr+3. On the other hand store ptr (0x01020304 :: LE Word32) would store 0x04, 0x03, 0x02, 0x01 at the above locations.

load :: Ptr w -> IO w Source #

The action load ptr loads the value stored at the ptr. Like store, it takes care of the endianness of the data type. For example, if ptr points to a buffer containing the bytes 0x01, 0x02, 0x03, 0x04, irrespective of the endianness of the machine, load ptr :: IO (BE Word32) will load the vale 0x01020304 of type BE Word32 and load ptr :: IO (LE Word32) will load 0x04030201 of type LE Word32.

adjustEndian Source #

Arguments

:: Ptr w

buffer pointers,

-> Int

how many w's are present,

-> IO () 

The action adjustEndian ptr n adjusts the encoding of bytes stored at the location ptr to conform with the endianness of the underlying data type. For example, assume that ptr points to a buffer containing the bytes 0x01 0x02 0x03 0x04, and we are on a big endian machine, then adjustEndian (ptr :: Ptr (LE Word32)) 1 will result in ptr pointing to the sequence 0x04 0x03 0x02 0x01. On the other hand if we were on a little endian machine, the sequence should remain the same. In particular, the following equalities should hold.

store ptr w          = poke ptr w >> adjustEndian ptr 1

Similarly the value loaded by load ptr should be same as the value returned by adjustEndian ptr 1 >> peak ptr, although the former does not change the contents stored at ptr where as the latter might does modify the contents pointed by ptr if the endianness of the machine and the time do not agree.

The action adjustEndian ptr n >> adjustEndian ptr n should be equivalent to return ().

Instances
EndianStore Word8 Source # 
Instance details

Defined in Raaz.Core.Types.Endian

EndianStore KEY Source # 
Instance details

Defined in Raaz.Cipher.ChaCha20.Internal

Methods

store :: Ptr KEY -> KEY -> IO () Source #

load :: Ptr KEY -> IO KEY Source #

adjustEndian :: Ptr KEY -> Int -> IO () Source #

EndianStore Counter Source # 
Instance details

Defined in Raaz.Cipher.ChaCha20.Internal

EndianStore IV Source # 
Instance details

Defined in Raaz.Cipher.ChaCha20.Internal

Methods

store :: Ptr IV -> IV -> IO () Source #

load :: Ptr IV -> IO IV Source #

adjustEndian :: Ptr IV -> Int -> IO () Source #

EndianStore SHA1 Source # 
Instance details

Defined in Raaz.Hash.Sha1.Internal

Methods

store :: Ptr SHA1 -> SHA1 -> IO () Source #

load :: Ptr SHA1 -> IO SHA1 Source #

adjustEndian :: Ptr SHA1 -> Int -> IO () Source #

EndianStore SHA224 Source # 
Instance details

Defined in Raaz.Hash.Sha224.Internal

EndianStore SHA256 Source # 
Instance details

Defined in Raaz.Hash.Sha256.Internal

EndianStore SHA384 Source # 
Instance details

Defined in Raaz.Hash.Sha384.Internal

EndianStore SHA512 Source # 
Instance details

Defined in Raaz.Hash.Sha512.Internal

EndianStore IV Source # 
Instance details

Defined in Raaz.Cipher.AES.Internal

Methods

store :: Ptr IV -> IV -> IO () Source #

load :: Ptr IV -> IO IV Source #

adjustEndian :: Ptr IV -> Int -> IO () Source #

EndianStore KEY256 Source # 
Instance details

Defined in Raaz.Cipher.AES.Internal

EndianStore KEY192 Source # 
Instance details

Defined in Raaz.Cipher.AES.Internal

EndianStore KEY128 Source # 
Instance details

Defined in Raaz.Cipher.AES.Internal

EndianStore w => EndianStore (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (BYTES w) -> BYTES w -> IO () Source #

load :: Ptr (BYTES w) -> IO (BYTES w) Source #

adjustEndian :: Ptr (BYTES w) -> Int -> IO () Source #

EndianStore (BE Word32) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (BE Word32) -> BE Word32 -> IO () Source #

load :: Ptr (BE Word32) -> IO (BE Word32) Source #

adjustEndian :: Ptr (BE Word32) -> Int -> IO () Source #

EndianStore (BE Word64) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (BE Word64) -> BE Word64 -> IO () Source #

load :: Ptr (BE Word64) -> IO (BE Word64) Source #

adjustEndian :: Ptr (BE Word64) -> Int -> IO () Source #

EndianStore (LE Word32) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (LE Word32) -> LE Word32 -> IO () Source #

load :: Ptr (LE Word32) -> IO (LE Word32) Source #

adjustEndian :: Ptr (LE Word32) -> Int -> IO () Source #

EndianStore (LE Word64) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (LE Word64) -> LE Word64 -> IO () Source #

load :: Ptr (LE Word64) -> IO (LE Word64) Source #

adjustEndian :: Ptr (LE Word64) -> Int -> IO () Source #

EndianStore h => EndianStore (HMAC h) Source # 
Instance details

Defined in Raaz.Hash.Internal.HMAC

Methods

store :: Ptr (HMAC h) -> HMAC h -> IO () Source #

load :: Ptr (HMAC h) -> IO (HMAC h) Source #

adjustEndian :: Ptr (HMAC h) -> Int -> IO () Source #

(Unbox a, EndianStore a, Dimension dim) => EndianStore (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

store :: Ptr (Tuple dim a) -> Tuple dim a -> IO () Source #

load :: Ptr (Tuple dim a) -> IO (Tuple dim a) Source #

adjustEndian :: Ptr (Tuple dim a) -> Int -> IO () Source #

copyFromBytes Source #

Arguments

:: EndianStore w 
=> Dest (Ptr w) 
-> Src Pointer 
-> Int

How many items.

-> IO () 

For the type w, the action copyFromBytes dest src n copies n-elements from src to dest. Copy performed by this combinator accounts for the endianness of the data in dest and is therefore not a mere copy of n * sizeOf(w) bytes. This action does not modify the src pointer in any way.

copyToBytes :: EndianStore w => Dest Pointer -> Src (Ptr w) -> Int -> IO () Source #

Similar to copyFromBytes but the transfer is done in the other direction. The copy takes care of performing the appropriate endian encoding.

Endian explicit word types.

data LE w Source #

Little endian version of the word type w

Instances
Functor LE Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

fmap :: (a -> b) -> LE a -> LE b #

(<$) :: a -> LE b -> LE a #

Show BLAKE2s Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

Show BLAKE2b Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

IsString BLAKE2s Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

Methods

fromString :: String -> BLAKE2s #

IsString BLAKE2b Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

Methods

fromString :: String -> BLAKE2b #

Encodable BLAKE2s Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

Encodable BLAKE2b Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

Recommendation BLAKE2s Source #

Recommended implementation for balke2s.

Instance details

Defined in Raaz.Hash.Blake2.Recommendation

Recommendation BLAKE2b Source #

Recommended implementation for blake2b.

Instance details

Defined in Raaz.Hash.Blake2.Recommendation

Primitive BLAKE2s Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

Associated Types

type Implementation BLAKE2s :: Type Source #

Primitive BLAKE2b Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

Associated Types

type Implementation BLAKE2b :: Type Source #

Hash BLAKE2s Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

Hash BLAKE2b Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

Unbox w => Vector Vector (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (LE w) -> m (Vector (LE w)) #

basicUnsafeThaw :: PrimMonad m => Vector (LE w) -> m (Mutable Vector (PrimState m) (LE w)) #

basicLength :: Vector (LE w) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (LE w) -> Vector (LE w) #

basicUnsafeIndexM :: Monad m => Vector (LE w) -> Int -> m (LE w) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (LE w) -> Vector (LE w) -> m () #

elemseq :: Vector (LE w) -> LE w -> b -> b #

Unbox w => MVector MVector (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

basicLength :: MVector s (LE w) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (LE w) -> MVector s (LE w) #

basicOverlaps :: MVector s (LE w) -> MVector s (LE w) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (LE w)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (LE w) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> LE w -> m (MVector (PrimState m) (LE w)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (LE w) -> Int -> m (LE w) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (LE w) -> Int -> LE w -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (LE w) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (LE w) -> LE w -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (LE w) -> MVector (PrimState m) (LE w) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (LE w) -> MVector (PrimState m) (LE w) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (LE w) -> Int -> m (MVector (PrimState m) (LE w)) #

Bounded w => Bounded (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

minBound :: LE w #

maxBound :: LE w #

Enum w => Enum (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

succ :: LE w -> LE w #

pred :: LE w -> LE w #

toEnum :: Int -> LE w #

fromEnum :: LE w -> Int #

enumFrom :: LE w -> [LE w] #

enumFromThen :: LE w -> LE w -> [LE w] #

enumFromTo :: LE w -> LE w -> [LE w] #

enumFromThenTo :: LE w -> LE w -> LE w -> [LE w] #

Eq w => Eq (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(==) :: LE w -> LE w -> Bool #

(/=) :: LE w -> LE w -> Bool #

Integral w => Integral (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

quot :: LE w -> LE w -> LE w #

rem :: LE w -> LE w -> LE w #

div :: LE w -> LE w -> LE w #

mod :: LE w -> LE w -> LE w #

quotRem :: LE w -> LE w -> (LE w, LE w) #

divMod :: LE w -> LE w -> (LE w, LE w) #

toInteger :: LE w -> Integer #

Num w => Num (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(+) :: LE w -> LE w -> LE w #

(-) :: LE w -> LE w -> LE w #

(*) :: LE w -> LE w -> LE w #

negate :: LE w -> LE w #

abs :: LE w -> LE w #

signum :: LE w -> LE w #

fromInteger :: Integer -> LE w #

Ord w => Ord (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

compare :: LE w -> LE w -> Ordering #

(<) :: LE w -> LE w -> Bool #

(<=) :: LE w -> LE w -> Bool #

(>) :: LE w -> LE w -> Bool #

(>=) :: LE w -> LE w -> Bool #

max :: LE w -> LE w -> LE w #

min :: LE w -> LE w -> LE w #

Read w => Read (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Real w => Real (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

toRational :: LE w -> Rational #

Show w => Show (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

showsPrec :: Int -> LE w -> ShowS #

show :: LE w -> String #

showList :: [LE w] -> ShowS #

Storable w => Storable (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

sizeOf :: LE w -> Int #

alignment :: LE w -> Int #

peekElemOff :: Ptr (LE w) -> Int -> IO (LE w) #

pokeElemOff :: Ptr (LE w) -> Int -> LE w -> IO () #

peekByteOff :: Ptr b -> Int -> IO (LE w) #

pokeByteOff :: Ptr b -> Int -> LE w -> IO () #

peek :: Ptr (LE w) -> IO (LE w) #

poke :: Ptr (LE w) -> LE w -> IO () #

Bits w => Bits (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(.&.) :: LE w -> LE w -> LE w #

(.|.) :: LE w -> LE w -> LE w #

xor :: LE w -> LE w -> LE w #

complement :: LE w -> LE w #

shift :: LE w -> Int -> LE w #

rotate :: LE w -> Int -> LE w #

zeroBits :: LE w #

bit :: Int -> LE w #

setBit :: LE w -> Int -> LE w #

clearBit :: LE w -> Int -> LE w #

complementBit :: LE w -> Int -> LE w #

testBit :: LE w -> Int -> Bool #

bitSizeMaybe :: LE w -> Maybe Int #

bitSize :: LE w -> Int #

isSigned :: LE w -> Bool #

shiftL :: LE w -> Int -> LE w #

unsafeShiftL :: LE w -> Int -> LE w #

shiftR :: LE w -> Int -> LE w #

unsafeShiftR :: LE w -> Int -> LE w #

rotateL :: LE w -> Int -> LE w #

rotateR :: LE w -> Int -> LE w #

popCount :: LE w -> Int #

NFData w => NFData (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

rnf :: LE w -> () #

Unbox w => Unbox (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Equality w => Equality (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

eq :: LE w -> LE w -> Result Source #

EndianStore (LE Word32) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (LE Word32) -> LE Word32 -> IO () Source #

load :: Ptr (LE Word32) -> IO (LE Word32) Source #

adjustEndian :: Ptr (LE Word32) -> Int -> IO () Source #

EndianStore (LE Word64) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (LE Word64) -> LE Word64 -> IO () Source #

load :: Ptr (LE Word64) -> IO (LE Word64) Source #

adjustEndian :: Ptr (LE Word64) -> Int -> IO () Source #

Encodable (LE Word32) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable (LE Word64) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

RandomStorable w => RandomStorable (LE w) Source # 
Instance details

Defined in Raaz.Random

Methods

fillRandomElements :: Memory mem => Int -> Ptr (LE w) -> RT mem () Source #

type Implementation BLAKE2s Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

type Implementation BLAKE2b Source # 
Instance details

Defined in Raaz.Hash.Blake2.Internal

newtype MVector s (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

newtype MVector s (LE w) = MV_LE (MVector s w)
newtype Vector (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

newtype Vector (LE w) = V_LE (Vector w)

data BE w Source #

Big endian version of the word type w

Instances
Functor BE Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

fmap :: (a -> b) -> BE a -> BE b #

(<$) :: a -> BE b -> BE a #

Unbox w => Vector Vector (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (BE w) -> m (Vector (BE w)) #

basicUnsafeThaw :: PrimMonad m => Vector (BE w) -> m (Mutable Vector (PrimState m) (BE w)) #

basicLength :: Vector (BE w) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (BE w) -> Vector (BE w) #

basicUnsafeIndexM :: Monad m => Vector (BE w) -> Int -> m (BE w) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (BE w) -> Vector (BE w) -> m () #

elemseq :: Vector (BE w) -> BE w -> b -> b #

Unbox w => MVector MVector (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

basicLength :: MVector s (BE w) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (BE w) -> MVector s (BE w) #

basicOverlaps :: MVector s (BE w) -> MVector s (BE w) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (BE w)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (BE w) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> BE w -> m (MVector (PrimState m) (BE w)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (BE w) -> Int -> m (BE w) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (BE w) -> Int -> BE w -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (BE w) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (BE w) -> BE w -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (BE w) -> MVector (PrimState m) (BE w) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (BE w) -> MVector (PrimState m) (BE w) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (BE w) -> Int -> m (MVector (PrimState m) (BE w)) #

Bounded w => Bounded (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

minBound :: BE w #

maxBound :: BE w #

Enum w => Enum (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

succ :: BE w -> BE w #

pred :: BE w -> BE w #

toEnum :: Int -> BE w #

fromEnum :: BE w -> Int #

enumFrom :: BE w -> [BE w] #

enumFromThen :: BE w -> BE w -> [BE w] #

enumFromTo :: BE w -> BE w -> [BE w] #

enumFromThenTo :: BE w -> BE w -> BE w -> [BE w] #

Eq w => Eq (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(==) :: BE w -> BE w -> Bool #

(/=) :: BE w -> BE w -> Bool #

Integral w => Integral (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

quot :: BE w -> BE w -> BE w #

rem :: BE w -> BE w -> BE w #

div :: BE w -> BE w -> BE w #

mod :: BE w -> BE w -> BE w #

quotRem :: BE w -> BE w -> (BE w, BE w) #

divMod :: BE w -> BE w -> (BE w, BE w) #

toInteger :: BE w -> Integer #

Num w => Num (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(+) :: BE w -> BE w -> BE w #

(-) :: BE w -> BE w -> BE w #

(*) :: BE w -> BE w -> BE w #

negate :: BE w -> BE w #

abs :: BE w -> BE w #

signum :: BE w -> BE w #

fromInteger :: Integer -> BE w #

Ord w => Ord (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

compare :: BE w -> BE w -> Ordering #

(<) :: BE w -> BE w -> Bool #

(<=) :: BE w -> BE w -> Bool #

(>) :: BE w -> BE w -> Bool #

(>=) :: BE w -> BE w -> Bool #

max :: BE w -> BE w -> BE w #

min :: BE w -> BE w -> BE w #

Read w => Read (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Real w => Real (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

toRational :: BE w -> Rational #

Show w => Show (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

showsPrec :: Int -> BE w -> ShowS #

show :: BE w -> String #

showList :: [BE w] -> ShowS #

Storable w => Storable (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

sizeOf :: BE w -> Int #

alignment :: BE w -> Int #

peekElemOff :: Ptr (BE w) -> Int -> IO (BE w) #

pokeElemOff :: Ptr (BE w) -> Int -> BE w -> IO () #

peekByteOff :: Ptr b -> Int -> IO (BE w) #

pokeByteOff :: Ptr b -> Int -> BE w -> IO () #

peek :: Ptr (BE w) -> IO (BE w) #

poke :: Ptr (BE w) -> BE w -> IO () #

Bits w => Bits (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(.&.) :: BE w -> BE w -> BE w #

(.|.) :: BE w -> BE w -> BE w #

xor :: BE w -> BE w -> BE w #

complement :: BE w -> BE w #

shift :: BE w -> Int -> BE w #

rotate :: BE w -> Int -> BE w #

zeroBits :: BE w #

bit :: Int -> BE w #

setBit :: BE w -> Int -> BE w #

clearBit :: BE w -> Int -> BE w #

complementBit :: BE w -> Int -> BE w #

testBit :: BE w -> Int -> Bool #

bitSizeMaybe :: BE w -> Maybe Int #

bitSize :: BE w -> Int #

isSigned :: BE w -> Bool #

shiftL :: BE w -> Int -> BE w #

unsafeShiftL :: BE w -> Int -> BE w #

shiftR :: BE w -> Int -> BE w #

unsafeShiftR :: BE w -> Int -> BE w #

rotateL :: BE w -> Int -> BE w #

rotateR :: BE w -> Int -> BE w #

popCount :: BE w -> Int #

NFData w => NFData (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

rnf :: BE w -> () #

Unbox w => Unbox (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Equality w => Equality (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

eq :: BE w -> BE w -> Result Source #

EndianStore (BE Word32) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (BE Word32) -> BE Word32 -> IO () Source #

load :: Ptr (BE Word32) -> IO (BE Word32) Source #

adjustEndian :: Ptr (BE Word32) -> Int -> IO () Source #

EndianStore (BE Word64) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (BE Word64) -> BE Word64 -> IO () Source #

load :: Ptr (BE Word64) -> IO (BE Word64) Source #

adjustEndian :: Ptr (BE Word64) -> Int -> IO () Source #

Encodable (BE Word32) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable (BE Word64) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

RandomStorable w => RandomStorable (BE w) Source # 
Instance details

Defined in Raaz.Random

Methods

fillRandomElements :: Memory mem => Int -> Ptr (BE w) -> RT mem () Source #

newtype MVector s (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

newtype MVector s (BE w) = MV_BE (MVector s w)
newtype Vector (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

newtype Vector (BE w) = V_BE (Vector w)

littleEndian :: w -> LE w Source #

Convert to the little endian variant.

bigEndian :: w -> BE w Source #

Convert to the big endian variants.

Helper functions for endian aware storing and loading.

storeAt Source #

Arguments

:: (EndianStore w, LengthUnit offset) 
=> Ptr w

the pointer

-> offset

the absolute offset in type safe length units.

-> w

value to store

-> IO () 

Store the given value at an offset from the crypto pointer. The offset is given in type safe units.

storeAtIndex Source #

Arguments

:: EndianStore w 
=> Ptr w

the pointer to the first element of the array

-> Int

the index of the array

-> w

the value to store

-> IO () 

Store the given value as the n-th element of the array pointed by the crypto pointer.

loadFrom Source #

Arguments

:: (EndianStore w, LengthUnit offset) 
=> Ptr w

the pointer

-> offset

the offset

-> IO w 

Load from a given offset. The offset is given in type safe units.

loadFromIndex Source #

Arguments

:: EndianStore w 
=> Ptr w

the pointer to the first element of the array

-> Int

the index of the array

-> IO w 

Load the n-th value of an array pointed by the crypto pointer.

Pointers, offsets, and alignment

type Pointer = Ptr Align Source #

The pointer type used by all cryptographic library.

Type safe length units.

class (Enum u, Monoid u) => LengthUnit u where Source #

In cryptographic settings, we need to measure pointer offsets and buffer sizes. The smallest of length/offset that we have is bytes measured using the type BYTES. In various other circumstances, it would be more natural to measure these in multiples of bytes. For example, when allocating buffer to use encrypt using a block cipher it makes sense to measure the buffer size in multiples of block of the cipher. Explicit conversion between these length units, while allocating or moving pointers, involves a lot of low level scaling that is also error prone. To avoid these errors due to unit conversions, we distinguish between different length units at the type level. This type class capturing all such types, i.e. types that stand of length units. Allocation functions and pointer arithmetic are generalised to these length units.

All instances of a LengthUnit are required to be instances of Monoid where the monoid operation gives these types the natural size/offset addition semantics: i.e. shifting a pointer by offset a mappend b is same as shifting it by a and then by b.

Methods

inBytes :: u -> BYTES Int Source #

Express the length units in bytes.

Instances
LengthUnit ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

inBytes :: ALIGN -> BYTES Int Source #

LengthUnit (BYTES Int) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Primitive p => LengthUnit (BLOCKS p) Source # 
Instance details

Defined in Raaz.Core.Primitives

Methods

inBytes :: BLOCKS p -> BYTES Int Source #

newtype BYTES a Source #

Type safe lengths/offsets in units of bytes.

Constructors

BYTES a 
Instances
Bounded a => Bounded (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

minBound :: BYTES a #

maxBound :: BYTES a #

Enum a => Enum (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

succ :: BYTES a -> BYTES a #

pred :: BYTES a -> BYTES a #

toEnum :: Int -> BYTES a #

fromEnum :: BYTES a -> Int #

enumFrom :: BYTES a -> [BYTES a] #

enumFromThen :: BYTES a -> BYTES a -> [BYTES a] #

enumFromTo :: BYTES a -> BYTES a -> [BYTES a] #

enumFromThenTo :: BYTES a -> BYTES a -> BYTES a -> [BYTES a] #

Eq a => Eq (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(==) :: BYTES a -> BYTES a -> Bool #

(/=) :: BYTES a -> BYTES a -> Bool #

Integral a => Integral (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

quot :: BYTES a -> BYTES a -> BYTES a #

rem :: BYTES a -> BYTES a -> BYTES a #

div :: BYTES a -> BYTES a -> BYTES a #

mod :: BYTES a -> BYTES a -> BYTES a #

quotRem :: BYTES a -> BYTES a -> (BYTES a, BYTES a) #

divMod :: BYTES a -> BYTES a -> (BYTES a, BYTES a) #

toInteger :: BYTES a -> Integer #

Num a => Num (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(+) :: BYTES a -> BYTES a -> BYTES a #

(-) :: BYTES a -> BYTES a -> BYTES a #

(*) :: BYTES a -> BYTES a -> BYTES a #

negate :: BYTES a -> BYTES a #

abs :: BYTES a -> BYTES a #

signum :: BYTES a -> BYTES a #

fromInteger :: Integer -> BYTES a #

Ord a => Ord (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

compare :: BYTES a -> BYTES a -> Ordering #

(<) :: BYTES a -> BYTES a -> Bool #

(<=) :: BYTES a -> BYTES a -> Bool #

(>) :: BYTES a -> BYTES a -> Bool #

(>=) :: BYTES a -> BYTES a -> Bool #

max :: BYTES a -> BYTES a -> BYTES a #

min :: BYTES a -> BYTES a -> BYTES a #

Real a => Real (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

toRational :: BYTES a -> Rational #

Show a => Show (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

showsPrec :: Int -> BYTES a -> ShowS #

show :: BYTES a -> String #

showList :: [BYTES a] -> ShowS #

Num a => Semigroup (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(<>) :: BYTES a -> BYTES a -> BYTES a #

sconcat :: NonEmpty (BYTES a) -> BYTES a #

stimes :: Integral b => b -> BYTES a -> BYTES a #

Num a => Monoid (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

mempty :: BYTES a #

mappend :: BYTES a -> BYTES a -> BYTES a #

mconcat :: [BYTES a] -> BYTES a #

Storable a => Storable (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

sizeOf :: BYTES a -> Int #

alignment :: BYTES a -> Int #

peekElemOff :: Ptr (BYTES a) -> Int -> IO (BYTES a) #

pokeElemOff :: Ptr (BYTES a) -> Int -> BYTES a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (BYTES a) #

pokeByteOff :: Ptr b -> Int -> BYTES a -> IO () #

peek :: Ptr (BYTES a) -> IO (BYTES a) #

poke :: Ptr (BYTES a) -> BYTES a -> IO () #

Equality a => Equality (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

eq :: BYTES a -> BYTES a -> Result Source #

LengthUnit (BYTES Int) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

EndianStore w => EndianStore (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (BYTES w) -> BYTES w -> IO () Source #

load :: Ptr (BYTES w) -> IO (BYTES w) Source #

adjustEndian :: Ptr (BYTES w) -> Int -> IO () Source #

Encodable a => Encodable (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

newtype BITS a Source #

Type safe lengths/offsets in units of bits.

Constructors

BITS a 
Instances
Bounded a => Bounded (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

minBound :: BITS a #

maxBound :: BITS a #

Enum a => Enum (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

succ :: BITS a -> BITS a #

pred :: BITS a -> BITS a #

toEnum :: Int -> BITS a #

fromEnum :: BITS a -> Int #

enumFrom :: BITS a -> [BITS a] #

enumFromThen :: BITS a -> BITS a -> [BITS a] #

enumFromTo :: BITS a -> BITS a -> [BITS a] #

enumFromThenTo :: BITS a -> BITS a -> BITS a -> [BITS a] #

Eq a => Eq (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(==) :: BITS a -> BITS a -> Bool #

(/=) :: BITS a -> BITS a -> Bool #

Integral a => Integral (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

quot :: BITS a -> BITS a -> BITS a #

rem :: BITS a -> BITS a -> BITS a #

div :: BITS a -> BITS a -> BITS a #

mod :: BITS a -> BITS a -> BITS a #

quotRem :: BITS a -> BITS a -> (BITS a, BITS a) #

divMod :: BITS a -> BITS a -> (BITS a, BITS a) #

toInteger :: BITS a -> Integer #

Num a => Num (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(+) :: BITS a -> BITS a -> BITS a #

(-) :: BITS a -> BITS a -> BITS a #

(*) :: BITS a -> BITS a -> BITS a #

negate :: BITS a -> BITS a #

abs :: BITS a -> BITS a #

signum :: BITS a -> BITS a #

fromInteger :: Integer -> BITS a #

Ord a => Ord (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

compare :: BITS a -> BITS a -> Ordering #

(<) :: BITS a -> BITS a -> Bool #

(<=) :: BITS a -> BITS a -> Bool #

(>) :: BITS a -> BITS a -> Bool #

(>=) :: BITS a -> BITS a -> Bool #

max :: BITS a -> BITS a -> BITS a #

min :: BITS a -> BITS a -> BITS a #

Real a => Real (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

toRational :: BITS a -> Rational #

Show a => Show (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

showsPrec :: Int -> BITS a -> ShowS #

show :: BITS a -> String #

showList :: [BITS a] -> ShowS #

Storable a => Storable (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

sizeOf :: BITS a -> Int #

alignment :: BITS a -> Int #

peekElemOff :: Ptr (BITS a) -> Int -> IO (BITS a) #

pokeElemOff :: Ptr (BITS a) -> Int -> BITS a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (BITS a) #

pokeByteOff :: Ptr b -> Int -> BITS a -> IO () #

peek :: Ptr (BITS a) -> IO (BITS a) #

poke :: Ptr (BITS a) -> BITS a -> IO () #

Equality a => Equality (BITS a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

eq :: BITS a -> BITS a -> Result Source #

Encodable a => Encodable (BITS a) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

inBits :: LengthUnit u => u -> BITS Word64 Source #

Express the length units in bits.

sizeOf :: Storable a => a -> BYTES Int Source #

Compute the size of a storable element.

Some length arithmetic

bitsQuotRem :: LengthUnit u => BITS Word64 -> (u, BITS Word64) Source #

Function similar to bytesQuotRem but works with bits instead.

bytesQuotRem :: LengthUnit u => BYTES Int -> (u, BYTES Int) Source #

A length unit u is usually a multiple of bytes. The function bytesQuotRem is like quotRem: the value byteQuotRem bytes is a tuple (x,r), where x is bytes expressed in the unit u with r being the reminder.

bitsQuot :: LengthUnit u => BITS Word64 -> u Source #

Function similar to bitsQuotRem but returns only the quotient.

bytesQuot :: LengthUnit u => BYTES Int -> u Source #

Function similar to bytesQuotRem but returns only the quotient.

atLeast :: (LengthUnit src, LengthUnit dest) => src -> dest Source #

Express length unit src in terms of length unit dest rounding upwards.

atLeastAligned :: LengthUnit l => l -> Alignment -> ALIGN Source #

Often we want to allocate a buffer of size l. We also want to make sure that the buffer starts at an alignment boundary a. However, the standard word allocation functions might return a pointer that is not aligned as desired. The atLeastAligned l a returns a length n such the length n is big enough to ensure that there is at least l length of valid buffer starting at the next pointer aligned at boundary a. If the alignment required in a then allocating @l + a - 1 should do the trick.

atMost :: (LengthUnit src, LengthUnit dest) => src -> dest Source #

Express length unit src in terms of length unit dest rounding downwards.

Types measuring alignment

data Alignment Source #

Types to measure alignment in units of bytes.

Instances
Enum Alignment Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Eq Alignment Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Integral Alignment Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Num Alignment Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Ord Alignment Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Real Alignment Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Show Alignment Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Semigroup Alignment Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Monoid Alignment Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

wordAlignment :: Alignment Source #

The default alignment to use is word boundary.

data ALIGN Source #

Type safe length unit that measures offsets in multiples of word length. This length unit can be used if one wants to make sure that all offsets are word aligned.

Instances
Enum ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Eq ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(==) :: ALIGN -> ALIGN -> Bool #

(/=) :: ALIGN -> ALIGN -> Bool #

Integral ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Num ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Ord ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

compare :: ALIGN -> ALIGN -> Ordering #

(<) :: ALIGN -> ALIGN -> Bool #

(<=) :: ALIGN -> ALIGN -> Bool #

(>) :: ALIGN -> ALIGN -> Bool #

(>=) :: ALIGN -> ALIGN -> Bool #

max :: ALIGN -> ALIGN -> ALIGN #

min :: ALIGN -> ALIGN -> ALIGN #

Real ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

toRational :: ALIGN -> Rational #

Show ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

showsPrec :: Int -> ALIGN -> ShowS #

show :: ALIGN -> String #

showList :: [ALIGN] -> ShowS #

Semigroup ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(<>) :: ALIGN -> ALIGN -> ALIGN #

sconcat :: NonEmpty ALIGN -> ALIGN #

stimes :: Integral b => b -> ALIGN -> ALIGN #

Monoid ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

mempty :: ALIGN #

mappend :: ALIGN -> ALIGN -> ALIGN #

mconcat :: [ALIGN] -> ALIGN #

Storable ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

sizeOf :: ALIGN -> Int #

alignment :: ALIGN -> Int #

peekElemOff :: Ptr ALIGN -> Int -> IO ALIGN #

pokeElemOff :: Ptr ALIGN -> Int -> ALIGN -> IO () #

peekByteOff :: Ptr b -> Int -> IO ALIGN #

pokeByteOff :: Ptr b -> Int -> ALIGN -> IO () #

peek :: Ptr ALIGN -> IO ALIGN #

poke :: Ptr ALIGN -> ALIGN -> IO () #

LengthUnit ALIGN Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

inBytes :: ALIGN -> BYTES Int Source #

alignment :: Storable a => a -> Alignment Source #

Compute the alignment for a storable object.

alignPtr :: Ptr a -> Alignment -> Ptr a Source #

Align a pointer to the appropriate alignment.

movePtr :: LengthUnit l => Ptr a -> l -> Ptr a Source #

Move the given pointer with a specific offset.

alignedSizeOf :: Storable a => a -> ALIGN Source #

Size of the buffer to be allocated to store an element of type a so as to guarantee that there exist enough space to store the element after aligning the pointer. If the size of the element is s and its alignment is a then this quantity is essentially equal to s + a - 1. All units measured in word alignment.

nextAlignedPtr :: Storable a => Ptr a -> Ptr a Source #

Compute the next aligned pointer starting from the given pointer location.

peekAligned :: Storable a => Ptr a -> IO a Source #

Peek the element from the next aligned location.

pokeAligned :: Storable a => Ptr a -> a -> IO () Source #

Poke the element from the next aligned location.

Allocation functions.

allocaAligned Source #

Arguments

:: LengthUnit l 
=> Alignment

the alignment of the buffer

-> l

size of the buffer

-> (Pointer -> IO b)

the action to run

-> IO b 

The expression allocaAligned a l action allocates a local buffer of length l and alignment a and passes it on to the IO action action. No explicit freeing of the memory is required as the memory is allocated locally and freed once the action finishes. It is better to use this function than allocaBytesAligned as it does type safe scaling and alignment.

allocaSecureAligned :: LengthUnit l => Alignment -> l -> (Pointer -> IO a) -> IO a Source #

This function allocates a chunk of "secure" memory of a given size and runs the action. The memory (1) exists for the duration of the action (2) will not be swapped during that time and (3) will be wiped clean and deallocated when the action terminates either directly or indirectly via errors. While this is mostly secure, there can be strange situations in multi-threaded application where the memory is not wiped out. For example if you run a crypto-sensitive action inside a child thread and the main thread gets exists, then the child thread is killed (due to the demonic nature of haskell threads) immediately and might not give it chance to wipe the memory clean. This is a problem inherent to how the bracket combinator works inside a child thread.

TODO: File this insecurity in the wiki.

allocaBuffer Source #

Arguments

:: LengthUnit l 
=> l

buffer length

-> (Pointer -> IO b)

the action to run

-> IO b 

A less general version of allocaAligned where the pointer passed is aligned to word boundary.

allocaSecure :: LengthUnit l => l -> (Pointer -> IO b) -> IO b Source #

A less general version of allocaSecureAligned where the pointer passed is aligned to word boundary

mallocBuffer Source #

Arguments

:: LengthUnit l 
=> l

buffer length

-> IO Pointer 

Creates a memory of given size. It is better to use over mallocBytes as it uses typesafe length.

Some buffer operations

memset Source #

Arguments

:: (MonadIO m, LengthUnit l) 
=> Pointer

Target

-> Word8

Value byte to set

-> l

Number of bytes to set

-> m () 

Sets the given number of Bytes to the specified value.

memmove Source #

Arguments

:: (MonadIO m, LengthUnit l) 
=> Dest Pointer

destination

-> Src Pointer

source

-> l

Number of Bytes to copy

-> m () 

Move between pointers.

memcpy Source #

Arguments

:: (MonadIO m, LengthUnit l) 
=> Dest Pointer

destination

-> Src Pointer

src

-> l

Number of Bytes to copy

-> m () 

Copy between pointers.

hFillBuf :: LengthUnit bufSize => Handle -> Pointer -> bufSize -> IO (BYTES Int) Source #

A version of hGetBuf which works for any type safe length units.

Types to force alignment.

data Aligned (align :: Nat) w Source #

A type w forced to be aligned to the alignment boundary alg

Instances
(Storable a, AlignBoundary alg) => Storable (Aligned alg a) Source # 
Instance details

Defined in Raaz.Core.Types.Aligned

Methods

sizeOf :: Aligned alg a -> Int #

alignment :: Aligned alg a -> Int #

peekElemOff :: Ptr (Aligned alg a) -> Int -> IO (Aligned alg a) #

pokeElemOff :: Ptr (Aligned alg a) -> Int -> Aligned alg a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Aligned alg a) #

pokeByteOff :: Ptr b -> Int -> Aligned alg a -> IO () #

peek :: Ptr (Aligned alg a) -> IO (Aligned alg a) #

poke :: Ptr (Aligned alg a) -> Aligned alg a -> IO () #

unAligned :: Aligned align w -> w Source #

The underlying unAligned value.

aligned16Bytes :: w -> Aligned 16 w Source #

Align the value to 16-byte boundary

aligned32Bytes :: w -> Aligned 32 w Source #

Align the value to 32-byte boundary

aligned64Bytes :: w -> Aligned 64 w Source #

Align the value to 64-byte boundary

Length encoded tuples

data Tuple (dim :: Nat) a Source #

Tuples that encode their length in their types. For tuples, we call the length its dimension.

Instances
(Unbox a, Equality a) => Eq (Tuple dim a) Source #

Equality checking is timing safe.

Instance details

Defined in Raaz.Core.Types.Tuple

Methods

(==) :: Tuple dim a -> Tuple dim a -> Bool #

(/=) :: Tuple dim a -> Tuple dim a -> Bool #

(Show a, Unbox a) => Show (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

showsPrec :: Int -> Tuple dim a -> ShowS #

show :: Tuple dim a -> String #

showList :: [Tuple dim a] -> ShowS #

(Unbox a, Storable a, Dimension dim) => Storable (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

sizeOf :: Tuple dim a -> Int #

alignment :: Tuple dim a -> Int #

peekElemOff :: Ptr (Tuple dim a) -> Int -> IO (Tuple dim a) #

pokeElemOff :: Ptr (Tuple dim a) -> Int -> Tuple dim a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Tuple dim a) #

pokeByteOff :: Ptr b -> Int -> Tuple dim a -> IO () #

peek :: Ptr (Tuple dim a) -> IO (Tuple dim a) #

poke :: Ptr (Tuple dim a) -> Tuple dim a -> IO () #

(Unbox a, Equality a) => Equality (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

eq :: Tuple dim a -> Tuple dim a -> Result Source #

(Unbox a, EndianStore a, Dimension dim) => EndianStore (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

store :: Ptr (Tuple dim a) -> Tuple dim a -> IO () Source #

load :: Ptr (Tuple dim a) -> IO (Tuple dim a) Source #

adjustEndian :: Ptr (Tuple dim a) -> Int -> IO () Source #

(Dimension d, Unbox w, RandomStorable w) => RandomStorable (Tuple d w) Source # 
Instance details

Defined in Raaz.Random

Methods

fillRandomElements :: Memory mem => Int -> Ptr (Tuple d w) -> RT mem () Source #

type Dimension (dim :: Nat) = KnownNat dim Source #

Function that returns the dimension of the tuple. The dimension is calculated without inspecting the tuple and hence the term dimension (undefined :: Tuple 5 Int) will evaluate to 5.

The constaint on the dimension of the tuple (since base 4.7.0)

dimension :: Dimension dim => Tuple dim a -> Int Source #

This combinator returns the dimension of the tuple.

initial :: (Unbox a, Dimension dim0) => Tuple dim1 a -> Tuple dim0 a Source #

Computes the initial fragment of a tuple. No length needs to be given as it is infered from the types.

diagonal :: (Unbox a, Dimension dim) => a -> Tuple dim a Source #

The diagonal a gives a tuple, all of whose entries is a.

repeatM :: (Functor m, Monad m, Unbox a, Dimension dim) => m a -> m (Tuple dim a) Source #

Construct a tuple by repeating a monadic action.

zipWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Tuple dim a -> Tuple dim b -> Tuple dim c Source #

A zipwith function for tuples

Unsafe operations

unsafeFromList :: (Unbox a, Dimension dim) => [a] -> Tuple dim a Source #

Construct a tuple out of the list. This function is unsafe and will result in run time error if the list is not of the correct dimension.

data Dest a Source #

The destination of a copy operation.

Note to Developers of Raaz: Since the Dest type inherits the Storable instance of the base type, one can use this type in foreign functions.

Instances
Functor Dest Source # 
Instance details

Defined in Raaz.Core.Types.Copying

Methods

fmap :: (a -> b) -> Dest a -> Dest b #

(<$) :: a -> Dest b -> Dest a #

Storable a => Storable (Dest a) Source # 
Instance details

Defined in Raaz.Core.Types.Copying

Methods

sizeOf :: Dest a -> Int #

alignment :: Dest a -> Int #

peekElemOff :: Ptr (Dest a) -> Int -> IO (Dest a) #

pokeElemOff :: Ptr (Dest a) -> Int -> Dest a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Dest a) #

pokeByteOff :: Ptr b -> Int -> Dest a -> IO () #

peek :: Ptr (Dest a) -> IO (Dest a) #

poke :: Ptr (Dest a) -> Dest a -> IO () #

data Src a Source #

The source of a copy operation.

Instances
Functor Src Source # 
Instance details

Defined in Raaz.Core.Types.Copying

Methods

fmap :: (a -> b) -> Src a -> Src b #

(<$) :: a -> Src b -> Src a #

Storable a => Storable (Src a) Source # 
Instance details

Defined in Raaz.Core.Types.Copying

Methods

sizeOf :: Src a -> Int #

alignment :: Src a -> Int #

peekElemOff :: Ptr (Src a) -> Int -> IO (Src a) #

pokeElemOff :: Ptr (Src a) -> Int -> Src a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Src a) #

pokeByteOff :: Ptr b -> Int -> Src a -> IO () #

peek :: Ptr (Src a) -> IO (Src a) #

poke :: Ptr (Src a) -> Src a -> IO () #

source :: a -> Src a Source #

smart constructor for source

destination :: a -> Dest a Source #

smart constructor for destionation.

class Describable d where Source #

This class captures all types that have some sort of description attached to it.

Methods

name :: d -> String Source #

Short name that describes the object.

description :: d -> String Source #

Longer description

Instances
Describable ChaCha20 Source # 
Instance details

Defined in Raaz.Cipher.ChaCha20.Internal

Describable (SomeCipherI cipher) Source # 
Instance details

Defined in Raaz.Cipher.Internal

Describable (SomeHashI h) Source # 
Instance details

Defined in Raaz.Hash.Internal

Describable (HashI h m) Source # 
Instance details

Defined in Raaz.Hash.Internal

Methods

name :: HashI h m -> String Source #

description :: HashI h m -> String Source #

Describable (AES 128 CBC) Source # 
Instance details

Defined in Raaz.Cipher.AES.Internal

Methods

name :: AES 128 CBC -> String Source #

description :: AES 128 CBC -> String Source #

Describable (AES 192 CBC) Source # 
Instance details

Defined in Raaz.Cipher.AES.Internal

Methods

name :: AES 192 CBC -> String Source #

description :: AES 192 CBC -> String Source #

Describable (AES 256 CBC) Source # 
Instance details

Defined in Raaz.Cipher.AES.Internal

Methods

name :: AES 256 CBC -> String Source #

description :: AES 256 CBC -> String Source #

Describable (CipherI cipher encMem decMem) Source # 
Instance details

Defined in Raaz.Cipher.Internal

Methods

name :: CipherI cipher encMem decMem -> String Source #

description :: CipherI cipher encMem decMem -> String Source #