raaz-0.0.1: The raaz cryptographic library.

Safe HaskellNone
LanguageHaskell98

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 use the type safety of Haskell to catch some common bugs at compile time. As of now we address three kinds of errors

Timing safe equality:
We need a consistent way to build timing safe equality comparisons. The type class Equality plays the role of Eq for us. The comparison result is of type Result and not Bool so as to avoid timing attacks due to short-circuting of the AND-operation. Instance for basic word types are given here and users are expected to build the Equality instances of compound types by combine the results of comparisons using the monoid instance of Result. We also give timing safe equality comparisons for Vector types using the eqVector and oftenCorrectEqVector functions. Once an instance for Equality is defined for a cryptographically sensitive data type, we define the Eq for it indirectly using the Equality instance and the operation ===.
Endianness aware types:
When serialising data, we need to be careful about the endianness of the machine. Instance of the EndianStore type class correctly stores and loads data from memory, irrespective of the endianness of the machine. We define endian aware variants of Word32 and Word64 here and expect other cryptographic types to use such endian explicit types in their definition.
Pointer and Length units:
We have the generic pointer type Pointer and distinguish between different length units at the type level. This helps in to avoid a lot of length conversion errors.

Synopsis

Timing safe equality checking.

class Equality a where Source #

In a cryptographic setting, naive equality checking dangerous. This class is the timing safe way of doing equality checking. The recommended method of defining equality checking for cryptographically sensitive data is as follows.

  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

Minimal complete definition

eq

Methods

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

Instances

Equality Word Source # 

Methods

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

Equality Word8 Source # 

Methods

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

Equality Word16 Source # 

Methods

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

Equality Word32 Source # 

Methods

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

Equality Word64 Source # 

Methods

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

Equality SHA1 Source # 

Methods

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

Equality SHA224 Source # 

Methods

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

Equality SHA256 Source # 

Methods

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

Equality SHA384 Source # 

Methods

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

Equality SHA512 Source # 

Methods

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

Equality a => Equality (BITS a) Source # 

Methods

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

Equality a => Equality (BYTES a) Source # 

Methods

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

Equality w => Equality (BE w) Source # 

Methods

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

Equality w => Equality (LE w) Source # 

Methods

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

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

Methods

eq :: Tuple dim a -> Tuple dim a -> 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.

The result of comparion.

data Result Source #

An opaque type that captures the result of a comparison. The monoid instances allows us to combine the results of two equality comparisons in a timing independent manner. We have the following properties.

isSuccessful mempty            = True
isSuccessful (r `mappend` s)   = isSuccessful r && isSuccessful s

Instances

Monoid Result Source # 
Unbox Result Source # 
Vector Vector Result Source # 
MVector MVector Result Source # 
data Vector Result Source #

Vector of Results.

data MVector s Result Source #

MVector for Results.

isSuccessful :: Result -> Bool Source #

Checks whether a given equality comparison is successful.

Comparing vectors.

oftenCorrectEqVector :: (Vector v a, Equality a, Vector v Result) => v a -> v a -> Bool Source #

Timing independent equality checks for vector of values. Do not use this to check the equality of two general vectors in a timing independent manner (use eqVector instead) because:

  1. They do not work for vectors of unequal lengths,
  2. They do not work for empty vectors.

The use case is for defining equality of data types which have fixed size vector quantities in it. Like for example

import Data.Vector.Unboxed
newtype Sha1 = Sha1 (Vector (BE Word32))

instance Eq Sha1 where
   (==) (Sha1 g) (Sha1 h) = oftenCorrectEqVector g h

eqVector :: (Vector v a, Equality a, Vector v Result) => v a -> v a -> Bool Source #

Timing independent equality checks for vectors. If you know that the vectors are not empty and of equal length, you may use the slightly faster oftenCorrectEqVector

Endianess aware types.

class Storable w => EndianStore w where Source #

This class is the starting point of an endian agnostic interface to basic cryptographic data types. Endianness only matters when we first load the data from the buffer or when we finally write the data out. Any multi-byte type that are meant to be serialised should define and instance of this class. The load and store should takes care of the appropriate endian conversion.

Minimal complete definition

store, load

Methods

store :: Pointer -> w -> IO () Source #

Store the given value at the locating pointed by the pointer

load :: Pointer -> IO w Source #

Load the value from the location pointed by the pointer.

Instances

EndianStore Word8 Source # 

Methods

store :: Pointer -> Word8 -> IO () Source #

load :: Pointer -> IO Word8 Source #

EndianStore SHA1 Source # 

Methods

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

load :: Pointer -> IO SHA1 Source #

EndianStore SHA224 Source # 
EndianStore SHA256 Source # 
EndianStore SHA384 Source # 
EndianStore SHA512 Source # 
EndianStore IV Source # 

Methods

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

load :: Pointer -> IO IV Source #

EndianStore KEY256 Source # 
EndianStore KEY192 Source # 
EndianStore KEY128 Source # 
EndianStore (BE Word32) Source # 

Methods

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

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

EndianStore (BE Word64) Source # 

Methods

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

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

EndianStore (LE Word32) Source # 

Methods

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

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

EndianStore (LE Word64) Source # 

Methods

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

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

EndianStore h => EndianStore (HMAC h) Source # 

Methods

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

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

(Unbox a, EndianStore a, KnownNat dim) => EndianStore (Tuple dim a) Source # 

Methods

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

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

Endian explicit word types.

data LE w Source #

Little endian version of the word type w

Instances

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

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 # 

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 # 

Methods

minBound :: LE w #

maxBound :: LE w #

Enum w => Enum (LE w) Source # 

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 # 

Methods

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

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

Integral w => Integral (LE w) Source # 

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 # 

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 # 

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 # 
Real w => Real (LE w) Source # 

Methods

toRational :: LE w -> Rational #

Show w => Show (LE w) Source # 

Methods

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

show :: LE w -> String #

showList :: [LE w] -> ShowS #

Storable w => Storable (LE w) Source # 

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 # 

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 # 

Methods

rnf :: LE w -> () #

Unbox w => Unbox (LE w) Source # 
Equality w => Equality (LE w) Source # 

Methods

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

EndianStore (LE Word32) Source # 

Methods

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

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

EndianStore (LE Word64) Source # 

Methods

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

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

Encodable (LE Word32) Source # 
Encodable (LE Word64) Source # 
Random w => Random (LE w) Source # 

Methods

random :: PRG prg => prg -> IO (LE w) Source #

data MVector s (LE w) Source # 
data MVector s (LE w) = MV_LE (MVector s w)
data Vector (LE w) Source # 
data Vector (LE w) = V_LE (Vector w)

data BE w Source #

Big endian version of the word type w

Instances

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

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 # 

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 # 

Methods

minBound :: BE w #

maxBound :: BE w #

Enum w => Enum (BE w) Source # 

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 # 

Methods

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

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

Integral w => Integral (BE w) Source # 

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 # 

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 # 

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 # 
Real w => Real (BE w) Source # 

Methods

toRational :: BE w -> Rational #

Show w => Show (BE w) Source # 

Methods

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

show :: BE w -> String #

showList :: [BE w] -> ShowS #

Storable w => Storable (BE w) Source # 

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 # 

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 # 

Methods

rnf :: BE w -> () #

Unbox w => Unbox (BE w) Source # 
Equality w => Equality (BE w) Source # 

Methods

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

EndianStore (BE Word32) Source # 

Methods

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

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

EndianStore (BE Word64) Source # 

Methods

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

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

Encodable (BE Word32) Source # 
Encodable (BE Word64) Source # 
Random w => Random (BE w) Source # 

Methods

random :: PRG prg => prg -> IO (BE w) Source #

data MVector s (BE w) Source # 
data MVector s (BE w) = MV_BE (MVector s w)
data Vector (BE w) Source # 
data 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) 
=> Pointer

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 
=> Pointer

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) 
=> Pointer

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 
=> Pointer

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.

The pointer type and Length offsets.

The pointer type.

type Pointer = Ptr Align Source #

The pointer type used by all cryptographic library.

Type safe length units.

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

In cryptographic settings, we need to measure pointer offsets and buffer sizes in different units. To avoid errors due to unit conversions, we distinguish between different length units at the type level. This type class capturing such types, i.e. types that stand of length units.

Minimal complete definition

inBytes

Methods

inBytes :: u -> BYTES Int Source #

Express the length units in bytes.

newtype BYTES a Source #

Type safe lengths/offsets in units of bytes.

Constructors

BYTES a 

Instances

IsString Write # 

Methods

fromString :: String -> Write #

Encodable Write Source # 
Enum a => Enum (BYTES a) Source # 

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 # 

Methods

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

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

Integral a => Integral (BYTES a) Source # 

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 # 

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 # 

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 # 

Methods

toRational :: BYTES a -> Rational #

Show a => Show (BYTES a) Source # 

Methods

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

show :: BYTES a -> String #

showList :: [BYTES a] -> ShowS #

Storable a => Storable (BYTES a) Source # 

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 # 

Methods

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

LengthUnit (BYTES Int) Source # 
Encodable a => Encodable (BYTES a) Source # 

newtype BITS a Source #

Type safe lengths/offsets in units of bits.

Constructors

BITS a 

Instances

Enum a => Enum (BITS a) Source # 

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 # 

Methods

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

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

Integral a => Integral (BITS a) Source # 

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 # 

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 # 

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 # 

Methods

toRational :: BITS a -> Rational #

Show a => Show (BITS a) Source # 

Methods

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

show :: BITS a -> String #

showList :: [BITS a] -> ShowS #

Storable a => Storable (BITS a) Source # 

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 # 

Methods

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

Encodable a => Encodable (BITS a) Source # 

data ALIGN Source #

Instances

Enum ALIGN Source # 
Eq ALIGN Source # 

Methods

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

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

Integral ALIGN Source # 
Num ALIGN Source # 
Ord ALIGN Source # 

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 # 

Methods

toRational :: ALIGN -> Rational #

Show ALIGN Source # 

Methods

showsPrec :: Int -> ALIGN -> ShowS #

show :: ALIGN -> String #

showList :: [ALIGN] -> ShowS #

Storable ALIGN Source # 

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 # 

Methods

inBytes :: ALIGN -> BYTES Int Source #

data Align Source #

A type whose only purpose in this universe is to provide alignment safe pointers.

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

Express the length units in bits.

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.

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

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

Helper function that uses generalised length units.

allocaBuffer Source #

Arguments

:: LengthUnit l 
=> l

buffer length

-> (Pointer -> IO b)

the action to run

-> IO b 

The expression allocaBuffer l action allocates a local buffer of length l 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 allocaBytes as it does type safe scaling. This function also ensure that the allocated buffer is word aligned.

allocaSecure :: LengthUnit l => 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.

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.

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

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

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

Similar to sizeOf but returns the length in type safe units.

memset Source #

Arguments

:: LengthUnit l 
=> Pointer

Target

-> Word8

Value byte to set

-> l

Number of bytes to set

-> IO () 

Sets the given number of Bytes to the specified value.

memmove Source #

Arguments

:: LengthUnit l 
=> Pointer

Dest

-> Pointer

Src

-> l

Number of Bytes to copy

-> IO () 

Move between pointers.

memcpy Source #

Arguments

:: LengthUnit l 
=> Pointer

Dest

-> Pointer

Src

-> l

Number of Bytes to copy

-> IO () 

Copy between pointers.

Tuples with length encoded in their types.

Length encoded tuples

data Tuple dim 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.

Methods

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

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

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

Methods

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

show :: Tuple dim a -> String #

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

(Unbox a, Storable a, KnownNat dim) => Storable (Tuple dim a) Source # 

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 # 

Methods

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

(Unbox a, EndianStore a, KnownNat dim) => EndianStore (Tuple dim a) Source # 

Methods

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

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

dimension :: (Unbox a, KnownNat dim) => Tuple dim a -> Int 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.

initial :: (Unbox a, KnownNat dim0, KnownNat dim1) => 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.

Unsafe operations

unsafeFromList :: (Unbox a, KnownNat 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.

class Describable d where Source #

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

Minimal complete definition

name, description

Methods

name :: d -> String Source #

Short name that describes the object.

description :: d -> String Source #

Longer description

Instances

Describable (SomeHashI h) Source # 
Describable (SomeCipherI cipher) Source # 
Describable (HashI h m) Source # 

Methods

name :: HashI h m -> String Source #

description :: HashI h m -> String Source #

Describable (CipherI cipher encMem decMem) Source # 

Methods

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

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