Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- class Equality a where
- (===) :: Equality a => a -> a -> Bool
- data Result
- class Storable w => EndianStore w where
- copyFromBytes :: EndianStore w => Dest (Ptr w) -> Src Pointer -> Int -> IO ()
- copyToBytes :: EndianStore w => Dest Pointer -> Src (Ptr w) -> Int -> IO ()
- data LE w
- data BE w
- littleEndian :: w -> LE w
- bigEndian :: w -> BE w
- storeAt :: (EndianStore w, LengthUnit offset) => Ptr w -> offset -> w -> IO ()
- storeAtIndex :: EndianStore w => Ptr w -> Int -> w -> IO ()
- loadFrom :: (EndianStore w, LengthUnit offset) => Ptr w -> offset -> IO w
- loadFromIndex :: EndianStore w => Ptr w -> Int -> IO w
- type Pointer = Ptr Align
- class (Enum u, Monoid u) => LengthUnit u where
- newtype BYTES a = BYTES a
- newtype BITS a = BITS a
- inBits :: LengthUnit u => u -> BITS Word64
- sizeOf :: Storable a => a -> BYTES Int
- bitsQuotRem :: LengthUnit u => BITS Word64 -> (u, BITS Word64)
- bytesQuotRem :: LengthUnit u => BYTES Int -> (u, BYTES Int)
- bitsQuot :: LengthUnit u => BITS Word64 -> u
- bytesQuot :: LengthUnit u => BYTES Int -> u
- atLeast :: (LengthUnit src, LengthUnit dest) => src -> dest
- atLeastAligned :: LengthUnit l => l -> Alignment -> ALIGN
- atMost :: (LengthUnit src, LengthUnit dest) => src -> dest
- data Alignment
- wordAlignment :: Alignment
- data ALIGN
- alignment :: Storable a => a -> Alignment
- alignPtr :: Ptr a -> Alignment -> Ptr a
- movePtr :: LengthUnit l => Ptr a -> l -> Ptr a
- alignedSizeOf :: Storable a => a -> ALIGN
- nextAlignedPtr :: Storable a => Ptr a -> Ptr a
- peekAligned :: Storable a => Ptr a -> IO a
- pokeAligned :: Storable a => Ptr a -> a -> IO ()
- allocaAligned :: LengthUnit l => Alignment -> l -> (Pointer -> IO b) -> IO b
- allocaSecureAligned :: LengthUnit l => Alignment -> l -> (Pointer -> IO a) -> IO a
- allocaBuffer :: LengthUnit l => l -> (Pointer -> IO b) -> IO b
- allocaSecure :: LengthUnit l => l -> (Pointer -> IO b) -> IO b
- mallocBuffer :: LengthUnit l => l -> IO Pointer
- memset :: (MonadIO m, LengthUnit l) => Pointer -> Word8 -> l -> m ()
- memmove :: (MonadIO m, LengthUnit l) => Dest Pointer -> Src Pointer -> l -> m ()
- memcpy :: (MonadIO m, LengthUnit l) => Dest Pointer -> Src Pointer -> l -> m ()
- hFillBuf :: LengthUnit bufSize => Handle -> Pointer -> bufSize -> IO (BYTES Int)
- data Aligned align w
- unAligned :: Aligned align w -> w
- aligned16Bytes :: w -> Aligned 16 w
- aligned32Bytes :: w -> Aligned 32 w
- aligned64Bytes :: w -> Aligned 64 w
- data Tuple dim a
- type Dimension dim = KnownNat dim
- dimension :: Dimension dim => Tuple dim a -> Int
- initial :: (Unbox a, Dimension dim0) => Tuple dim1 a -> Tuple dim0 a
- diagonal :: (Unbox a, Dimension dim) => a -> Tuple dim a
- repeatM :: (Functor m, Monad m, Unbox a, Dimension dim) => m a -> m (Tuple dim a)
- zipWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Tuple dim a -> Tuple dim b -> Tuple dim c
- unsafeFromList :: (Unbox a, Dimension dim) => [a] -> Tuple dim a
- newtype Src a = Src {
- unSrc :: a
- newtype Dest a = Dest {
- unDest :: a
- source :: a -> Src a
- destination :: a -> Dest a
- class Describable d where
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:
- 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 (seeBE
andLE
) etc. - Make sure that the low level functions are sensitive to these
types. For example, the function
sizeOf
exposed here returns
instead of justBYTES
Int
Int
and functions likeallocaBuffer
are generic enough to work with any length units. - 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.
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
essentially takes
the AND of these results. However, unlike in the case of AND-ing in
mappend
r2Bool
, 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
. Due to boolean short circuiting, this
will lead to timing information being leaked.and
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.
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.
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.
store :: Ptr w -> w -> IO () Source #
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 :: Ptr w -> Int -> IO () Source #
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 ()
.
EndianStore Word8 Source # | |
EndianStore SHA1 Source # | |
EndianStore SHA256 Source # | |
EndianStore SHA224 Source # | |
EndianStore SHA384 Source # | |
EndianStore SHA512 Source # | |
EndianStore KEY Source # | |
EndianStore Counter Source # | |
EndianStore IV Source # | |
EndianStore IV Source # | |
EndianStore KEY256 Source # | |
EndianStore KEY192 Source # | |
EndianStore KEY128 Source # | |
EndianStore w => EndianStore (BYTES w) Source # | |
EndianStore (BE Word32) Source # | |
EndianStore (BE Word64) Source # | |
EndianStore (LE Word32) Source # | |
EndianStore (LE Word64) Source # | |
EndianStore h => EndianStore (HMAC h) Source # | |
(Unbox a, EndianStore a, Dimension dim) => EndianStore (Tuple dim a) Source # | |
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.
Little endian version of the word type w
Big endian version of the word type w
Functor BE Source # | |
Unbox w => MVector MVector (BE w) Source # | |
Unbox w => Vector Vector (BE w) Source # | |
Bounded w => Bounded (BE w) Source # | |
Enum w => Enum (BE w) Source # | |
Eq w => Eq (BE w) Source # | |
Integral w => Integral (BE w) Source # | |
Num w => Num (BE w) Source # | |
Ord w => Ord (BE w) Source # | |
Read w => Read (BE w) Source # | |
Real w => Real (BE w) Source # | |
Show w => Show (BE w) Source # | |
Storable w => Storable (BE w) Source # | |
Bits w => Bits (BE w) Source # | |
NFData w => NFData (BE w) Source # | |
Unbox w => Unbox (BE w) Source # | |
Equality w => Equality (BE w) Source # | |
EndianStore (BE Word32) Source # | |
EndianStore (BE Word64) Source # | |
Encodable (BE Word32) Source # | |
Encodable (BE Word64) Source # | |
RandomStorable w => RandomStorable (BE w) Source # | |
data MVector s (BE w) Source # | |
data Vector (BE w) Source # | |
littleEndian :: w -> LE w Source #
Convert to the little endian variant.
Helper functions for endian aware storing and loading.
:: (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.
:: 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.
:: (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.
:: 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 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
is same as shifting it by mappend
ba
and then by b
.
LengthUnit ALIGN Source # | |
LengthUnit (BYTES Int) Source # | |
Primitive p => LengthUnit (BLOCKS p) Source # | |
Type safe lengths/offsets in units of bytes.
BYTES a |
Bounded a => Bounded (BYTES a) Source # | |
Enum a => Enum (BYTES a) Source # | |
Eq a => Eq (BYTES a) Source # | |
Integral a => Integral (BYTES a) Source # | |
Num a => Num (BYTES a) Source # | |
Ord a => Ord (BYTES a) Source # | |
Real a => Real (BYTES a) Source # | |
Show a => Show (BYTES a) Source # | |
Num a => Monoid (BYTES a) Source # | |
Storable a => Storable (BYTES a) Source # | |
Equality a => Equality (BYTES a) Source # | |
LengthUnit (BYTES Int) Source # | |
EndianStore w => EndianStore (BYTES w) Source # | |
Encodable a => Encodable (BYTES a) Source # | |
Type safe lengths/offsets in units of bits.
BITS a |
Bounded a => Bounded (BITS a) Source # | |
Enum a => Enum (BITS a) Source # | |
Eq a => Eq (BITS a) Source # | |
Integral a => Integral (BITS a) Source # | |
Num a => Num (BITS a) Source # | |
Ord a => Ord (BITS a) Source # | |
Real a => Real (BITS a) Source # | |
Show a => Show (BITS a) Source # | |
Storable a => Storable (BITS a) Source # | |
Equality a => Equality (BITS a) Source # | |
Encodable a => Encodable (BITS a) Source # | |
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
Types to measure alignment in units of bytes.
wordAlignment :: Alignment Source #
The default alignment to use is word boundary.
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.
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.
pokeAligned :: Storable a => Ptr a -> a -> IO () Source #
Poke the element from the next aligned location.
Allocation functions.
:: 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
as it does type safe scaling and alignment.allocaBytesAligned
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.
:: 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
:: LengthUnit l | |
=> l | buffer length |
-> IO Pointer |
Creates a memory of given size. It is better to use over
as it uses typesafe length.mallocBytes
Some buffer operations
:: (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.
:: (MonadIO m, LengthUnit l) | |
=> Dest Pointer | destination |
-> Src Pointer | source |
-> l | Number of Bytes to copy |
-> m () |
Move between pointers.
:: (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.
A type w
forced to be aligned to the alignment boundary alg
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
Tuples that encode their length in their types. For tuples, we call the length its dimension.
(Unbox a, Equality a) => Eq (Tuple dim a) Source # | Equality checking is timing safe. |
(Show a, Unbox a) => Show (Tuple dim a) Source # | |
(Unbox a, Storable a, Dimension dim) => Storable (Tuple dim a) Source # | |
(Unbox a, Equality a) => Equality (Tuple dim a) Source # | |
(Unbox a, EndianStore a, Dimension dim) => EndianStore (Tuple dim a) Source # | |
(Dimension d, Unbox w, RandomStorable w) => RandomStorable (Tuple d w) Source # | |
type Dimension dim = KnownNat dim Source #
Function that returns the dimension of the tuple. The dimension
is calculated without inspecting the tuple and hence the term
will evaluate to 5.dimension
(undefined :: Tuple 5 Int)
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.
Copying.
Consider a copy operation that involves copying data between two
entities of the same type. If the source and target is confused
this can lead to bugs. The types Src
and Dest
helps in avoiding
this confusion. The convention that we follow is that copy function
mark its destination and source explicitly at the type level. The
actual constructors for the type Src
and Dest
are not available
to users of the library. Instead they use the smart constructors
source
and destination
when passing arguments to these
functions.
The developers of the raaz library do have access to the
constructors. However, it is unlikely one would need it. Since both
Src
and Dest
derive the underlying Storable
instance, one can
mark Src
and Dest
in calls to FFI
functions as well.
The source of a copy operation.
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.
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.
Describable ChaCha20 Source # | |
Describable (SomeHashI h) Source # | |
Describable (SomeCipherI cipher) Source # | |
Describable (HashI h m) Source # | |
Describable (AES 128 CBC) Source # | |
Describable (AES 192 CBC) Source # | |
Describable (AES 256 CBC) Source # | |
Describable (CipherI cipher encMem decMem) Source # | |