raaz-0.3.5: Fast and type safe cryptography.
Copyright(c) Piyush P Kurur 2019
LicenseApache-2.0 OR BSD-3-Clause
MaintainerPiyush P Kurur <ppk@iitpkd.ac.in>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Raaz.Core.Types

Description

 
Synopsis

Overview.

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.

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.

data BlockCount p Source #

Type safe message length in units of blocks of the primitive. When dealing with buffer lengths for a primitive, it is often better to use the type safe units BlockCount. Functions in the raaz package that take lengths usually allow any type safe length as long as they can be converted to bytes. This can avoid a lot of tedious and error prone length calculations.

Instances

Instances details
Extractable ChaCha20Mem (BlockCount ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Initialisable ChaCha20Mem (BlockCount ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Enum (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Eq (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Methods

(==) :: BlockCount p -> BlockCount p -> Bool #

(/=) :: BlockCount p -> BlockCount p -> Bool #

Ord (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Show (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Semigroup (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Monoid (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Storable (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Methods

sizeOf :: BlockCount p -> Int #

alignment :: BlockCount p -> Int #

peekElemOff :: Ptr (BlockCount p) -> Int -> IO (BlockCount p) #

pokeElemOff :: Ptr (BlockCount p) -> Int -> BlockCount p -> IO () #

peekByteOff :: Ptr b -> Int -> IO (BlockCount p) #

pokeByteOff :: Ptr b -> Int -> BlockCount p -> IO () #

peek :: Ptr (BlockCount p) -> IO (BlockCount p) #

poke :: Ptr (BlockCount p) -> BlockCount p -> IO () #

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

Defined in Raaz.Core.Primitive

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

Instances details
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 S Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Methods

eq :: S -> S -> Result Source #

Equality R Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Methods

eq :: R -> R -> Result Source #

Equality Poly1305 Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Methods

eq :: Poly1305 -> Poly1305 -> 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 (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Equality (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Equality prim => Equality (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

eq :: Keyed prim -> Keyed prim -> 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

Instances details
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

data BE w Source #

Big endian version of the word type w

Instances

Instances details
Functor BE Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

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

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

Initialisable Sha256Mem () Source # 
Instance details

Defined in Raaz.Primitive.Sha2.Internal

Methods

initialise :: () -> Sha256Mem -> IO () Source #

Initialisable Sha512Mem () Source # 
Instance details

Defined in Raaz.Primitive.Sha2.Internal

Methods

initialise :: () -> Sha512Mem -> IO () Source #

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

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)

data LE w Source #

Little endian version of the word type w

Instances

Instances details
Functor LE Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

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

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

KeyedHash Blake2s Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

KeyedHash Blake2b Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

Initialisable Blake2sMem () Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

Methods

initialise :: () -> Blake2sMem -> IO () Source #

Initialisable Blake2bMem () Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

Methods

initialise :: () -> Blake2bMem -> IO () Source #

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

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)

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

Instances details
EndianStore Word8 Source # 
Instance details

Defined in Raaz.Core.Types.Endian

EndianStore () Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

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

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

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

EndianStore S Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Methods

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

load :: Ptr S -> IO S Source #

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

EndianStore R Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Methods

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

load :: Ptr R -> IO R Source #

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

EndianStore Poly1305 Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.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 (Nounce XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore prim => EndianStore (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

store :: Ptr (Keyed prim) -> Keyed prim -> IO () Source #

load :: Ptr (Keyed prim) -> IO (Keyed prim) Source #

adjustEndian :: Ptr (Keyed prim) -> 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 #

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.

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.

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.

copyFromBytes Source #

Arguments

:: EndianStore w 
=> Dest (Ptr w) 
-> Src (Ptr Word8) 
-> 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 (Ptr Word8) -> 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.

littleEndian :: w -> LE w Source #

Convert to the little endian variant.

bigEndian :: w -> BE w Source #

Convert to the big endian variants.

data Ptr a #

A value of type Ptr a represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of type a.

The type a will often be an instance of class Storable which provides the marshalling operations. However this is not essential, and you can provide your own operations to access the pointer. For example you might write small foreign functions to get or set the fields of a C struct.

Instances

Instances details
IsString WriteTo Source # 
Instance details

Defined in Raaz.Core.Transfer.Unsafe

Methods

fromString :: String -> WriteTo #

NFData1 Ptr

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Ptr a -> () #

Pointer Ptr Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

castPointer :: Ptr a -> Ptr b Source #

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

unsafeRawPtr :: Ptr a -> Ptr a Source #

Encodable WriteTo Source # 
Instance details

Defined in Raaz.Core.Transfer.Unsafe

Generic1 (URec (Ptr ()) :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec (Ptr ())) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a #

to1 :: forall (a :: k0). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a #

Eq (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

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

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

Data a => Data (Ptr a)

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) #

toConstr :: Ptr a -> Constr #

dataTypeOf :: Ptr a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) #

gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) #

Ord (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

compare :: Ptr a -> Ptr a -> Ordering #

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

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

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

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

max :: Ptr a -> Ptr a -> Ptr a #

min :: Ptr a -> Ptr a -> Ptr a #

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

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

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Foldable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UAddr m -> m #

foldMap :: Monoid m => (a -> m) -> UAddr a -> m #

foldMap' :: Monoid m => (a -> m) -> UAddr a -> m #

foldr :: (a -> b -> b) -> b -> UAddr a -> b #

foldr' :: (a -> b -> b) -> b -> UAddr a -> b #

foldl :: (b -> a -> b) -> b -> UAddr a -> b #

foldl' :: (b -> a -> b) -> b -> UAddr a -> b #

foldr1 :: (a -> a -> a) -> UAddr a -> a #

foldl1 :: (a -> a -> a) -> UAddr a -> a #

toList :: UAddr a -> [a] #

null :: UAddr a -> Bool #

length :: UAddr a -> Int #

elem :: Eq a => a -> UAddr a -> Bool #

maximum :: Ord a => UAddr a -> a #

minimum :: Ord a => UAddr a -> a #

sum :: Num a => UAddr a -> a #

product :: Num a => UAddr a -> a #

Traversable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) #

Storable (Ptr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int #

alignment :: Ptr a -> Int #

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

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

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

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

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

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

NFData (Ptr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ptr a -> () #

Prim (Ptr a) 
Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Ptr a -> Int# #

alignment# :: Ptr a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Ptr a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Ptr a #) #

writeByteArray# :: MutableByteArray# s -> Int# -> Ptr a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Ptr a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Ptr a #

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Ptr a #) #

writeOffAddr# :: Addr# -> Int# -> Ptr a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Ptr a -> State# s -> State# s #

Functor (URec (Ptr ()) :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a #

Eq (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

Ord (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

Generic (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

data URec (Ptr ()) (p :: k)

Used for marking occurrences of Addr#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec (Ptr ()) (p :: k) = UAddr {}
type Rep1 (URec (Ptr ()) :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))
type Rep (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

data AlignedPtr (n :: Nat) a Source #

The type AlignedPtr n that captures pointers that are aligned to n byte boundary.

Instances

Instances details
KnownNat n => Pointer (AlignedPtr n) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

class Pointer (ptr :: Type -> Type) where Source #

Depending on the constraints of various pointers, raaz expose a variety of pointer types. This type class capturing such types. The main operation of interest to use is casting and allocation. All of these types have an underlying pointer which you can also be accessed.

Methods

castPointer :: ptr a -> ptr b Source #

Convert pointers of one type to another.

allocaPointer :: BYTES Int -> (ptr a -> IO b) -> IO b Source #

The alloca variant for this pointer type. The action allocaPointer l action allocates a buffer of size l and passes it on to action. No explicit de-allocation is required just like in the case of alloca

unsafeRawPtr :: ptr a -> Ptr a Source #

Recover the underlying raw pointer.

Instances

Instances details
Pointer Ptr Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

castPointer :: Ptr a -> Ptr b Source #

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

unsafeRawPtr :: Ptr a -> Ptr a Source #

KnownNat n => Pointer (AlignedPtr n) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

data BYTES a Source #

Type safe lengths/offsets in units of bytes.

Instances

Instances details
Functor BYTES Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

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

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

IsString WriteTo Source # 
Instance details

Defined in Raaz.Core.Transfer.Unsafe

Methods

fromString :: String -> WriteTo #

Encodable WriteTo Source # 
Instance details

Defined in Raaz.Core.Transfer.Unsafe

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

Defined in Raaz.Core.Types.Pointer

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

Defined in Raaz.Core.Types.Pointer

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 () #

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

Defined in Raaz.Core.Types.Pointer

Methods

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

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

xor :: BYTES a -> BYTES a -> BYTES a #

complement :: BYTES a -> BYTES a #

shift :: BYTES a -> Int -> BYTES a #

rotate :: BYTES a -> Int -> BYTES a #

zeroBits :: BYTES a #

bit :: Int -> BYTES a #

setBit :: BYTES a -> Int -> BYTES a #

clearBit :: BYTES a -> Int -> BYTES a #

complementBit :: BYTES a -> Int -> BYTES a #

testBit :: BYTES a -> Int -> Bool #

bitSizeMaybe :: BYTES a -> Maybe Int #

bitSize :: BYTES a -> Int #

isSigned :: BYTES a -> Bool #

shiftL :: BYTES a -> Int -> BYTES a #

unsafeShiftL :: BYTES a -> Int -> BYTES a #

shiftR :: BYTES a -> Int -> BYTES a #

unsafeShiftR :: BYTES a -> Int -> BYTES a #

rotateL :: BYTES a -> Int -> BYTES a #

rotateR :: BYTES a -> Int -> BYTES a #

popCount :: BYTES a -> Int #

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

Defined in Raaz.Core.Types.Pointer

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 MVector s (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

newtype MVector s (BYTES w) = MV_BYTES (MVector s w)
newtype Vector (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

newtype Vector (BYTES w) = V_BYTES (Vector w)

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

Instances details
LengthUnit (BYTES Int) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

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

Defined in Raaz.Core.Primitive

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

Compute the size of a storable element.

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

Compute the alignment for a storable object.

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

Move the given pointer with a specific offset.

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

Align pointer to the next alignment

alignedSizeOf :: Storable a => Proxy a -> BYTES Int 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.

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

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 -> BYTES Int 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 should do the trick.

NOTE: Let us say that the next allocation happens at a pointer ptr whose address is r mod a. Then if we allocate a buffer of size s, the buffer will be spanning the address ptr, ptr + 1, ... ptr + s -1. Assume that r ≠ 0, then the next address at which our buffer can start is at ptr + a - r. Therefore the size of the buffer available at this location is (ptr + s - 1) - (ptr + a - r ) + 1 = s - a + r, which should at least l. Therefore, we have s - a - r = l, which means s >= l + a - r. This is maximised when r = 1. This analysis means that we need to allocate only l + a - 1 bytes but that seems to be creating problems for our copy. May be it is a memcpy vs memmove problem.

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

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

unsafeWithPointer :: Pointer ptr => (Ptr a -> b) -> ptr a -> b Source #

Lifts raw pointer actions to the given pointer type.

unsafeWithPointerCast :: Pointer ptr => (Ptr a -> b) -> ptr something -> b Source #

Lifts raw pointer actions to a pointer action of a different type.

allocaBuffer Source #

Arguments

:: (LengthUnit l, Pointer ptr) 
=> l

buffer length

-> (ptr something -> IO b)

the action to run

-> IO b 

Allocate a buffer for an action that expects a generic pointer. Length can be specified in any length units.

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

Variant of allocaBuffer that allocates a locked buffer of a given size and runs the action. The associated memory (1) exists for the duration of the action (2) will not be swapped during the action as guaranteed by the memlock function of the operating system and (3) will be wiped clean and deallocated when the action terminates either directly or indirectly via errors. While this is mostly secure, there are still edge cases in multi-threaded applications where the memory will not be cleaned. 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 threads in GHC haskell) immediately and might not give it chance to wipe the memory clean. See https://ghc.haskell.org/trac/ghc/ticket/13891 on this problem and possible workarounds.

wipeMemory Source #

Arguments

:: (LengthUnit l, Pointer ptr) 
=> ptr a

buffer to wipe

-> l

buffer length

-> IO () 

Cleanup the given pointer of any sensitive data. This is a tricky function to write as compilers are known to optimise this away. In our case we try to use the platform specific one if it exists.

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

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

memcpy Source #

Arguments

:: (LengthUnit l, Pointer ptrS, Pointer ptrD) 
=> Dest (ptrD dest)

destination

-> Src (ptrS src)

src

-> l

Number of Bytes to copy

-> IO () 

Copy between pointers.

memset Source #

Arguments

:: (LengthUnit l, Pointer ptr) 
=> ptr a

Target

-> Word8

Value byte to set

-> l

Number of bytes to set

-> IO () 

Sets the given number of Bytes to the specified value.

nextAlignedPtr :: (Storable a, KnownNat n) => Ptr a -> AlignedPtr n a Source #

Given a raw pointer (i.e. element of type Ptr), returns the next pointer aligned to n-bytes boundary.

ptrAlignment :: KnownNat n => Proxy (AlignedPtr n a) -> Alignment Source #

Compute the alignment restriction.

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

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

data Tuple (dim :: Nat) a Source #

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

Instances

Instances details
(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 #

unsafeToVector :: Tuple dim a -> Vector a Source #

Convert the tuple to vector.

unsafeFromVector :: Vector a -> Tuple dim a Source #

Convert vector to tuple. This function is unsafe because it does not check whether length of the vector matches with the tuple dimension.

dimension :: Dimension 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.

dimension' :: Dimension dim => Proxy (Tuple dim a) -> Int Source #

Function that returns the dimension from the proxy of the tuple. This is useful when we only have a proxy of the tuple at hand. This is clearly possible because the dimension calculation works at the type level and does not require looking at the value of the tuple.

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

Construct a tuple by repeating a monadic action.

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.

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.

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

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

Generate using the given action.

data Dest a Source #

The destination of a copy operation. Besides the destination smart constructor, the functor instance allows to transform the internal type using the fmap (e.g. given an dptr :: Dest (Ptr Word8) shift it by an offset).

For FFI use: One can use this type directly in FFI interface by importing Raaz.Core.Types.Internal to get access to the constructor.

Instances

Instances details
Functor Dest Source # 
Instance details

Defined in Raaz.Core.Types.Copying

Methods

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

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

data Src a Source #

The source of a copy operation. Besides the source smart constructor, the functor instance allows to transform the internal type using the fmap (e.g. given an sptr :: Src (Ptr Word8) shift it by an offset).

For FFI use: One can use this type directly in FFI interface by importing Raaz.Core.Types.Internal to get access to the constructor.

Instances

Instances details
Functor Src Source # 
Instance details

Defined in Raaz.Core.Types.Copying

Methods

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

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

source :: a -> Src a Source #

Smart constructor for Src. Copying functions

destination :: a -> Dest a Source #

Smart constructor for Dest.