raaz-0.2.0: The raaz cryptographic library.

Safe HaskellNone
LanguageHaskell2010

Raaz.Core.Transfer

Contents

Description

Module to reading from and writing into buffers.

Synopsis

Transfer actions.

Low level buffer operations are problematic portions of any crypto-library. Buffers are usually represented by the starting pointer and one needs to keep track of the buffer sizes carefully. An operation that writes into a buffer, if it writes beyond the actual size of the buffer, can lead to a possible remote code execution. On the other hand, when reading from a buffer, if we read beyond the buffer it can leak private data to the attacker (as in the case of Heart bleed bug). This module is indented to give a relatively high level interface to this problem. We expose two types, the ReadM and the WriteM type which deals with these two aspects. Both these actions keep track of the number of bytes that they transfer.

Read action

data ReadM m Source #

The ReadM is the type that captures the act of reading from a buffer and possibly doing some action on the bytes read. Although inaccurate, it is helpful to think of elements of ReadM as action that on an input buffer transfers data from it to some unspecified source.

Read actions form a monoid with the following semantics: if r1 and r2 are two read actions then r1 <> r2 first reads the data associated from r1 and then the read associated with the data r2.

Instances

Monad m => Monoid (ReadM m) Source # 

Methods

mempty :: ReadM m #

mappend :: ReadM m -> ReadM m -> ReadM m #

mconcat :: [ReadM m] -> ReadM m #

type ReadIO = ReadM IO Source #

A read io-action.

bytesToRead :: ReadM m -> BYTES Int Source #

The expression bytesToRead r gives the total number of bytes that would be read from the input buffer if the action r is performed.

unsafeRead Source #

Arguments

:: ReadM m 
-> Pointer

The pointer for the buffer to be written into.

-> m () 

The action unsafeRead r ptr results in reading bytesToRead r bytes from the buffer pointed by ptr. This action is unsafe as it will not (and cannot) check if the action reads beyond what is legally stored at ptr.

readBytes Source #

Arguments

:: (LengthUnit sz, MonadIO m) 
=> sz

how much to read.

-> Dest Pointer

buffer to read the bytes into

-> ReadM m 

The action readBytes sz dptr gives a read action, which if run on an input buffer, will transfers sz to the destination buffer pointed by dptr. Note that it is the responsibility of the user to make sure that dptr has enough space to receive sz units of data if and when the read action is executed.

readInto Source #

Arguments

:: (EndianStore a, MonadIO m) 
=> Int

how many elements to read.

-> Dest (Ptr a)

buffer to read the elements into

-> ReadM m 

The action readInto n dptr gives a read action which if run on an input buffer, will transfers n elements of type a into the buffer pointed by dptr. In particular, the read action readInto n dptr is the same as readBytes (fromIntegral n :: BYTES Int) dptr when the type a is Word8.

Write action.

data WriteM m Source #

An element of type `WriteM m` is an action which when executed transfers bytes into its input buffer. The type WriteM m forms a monoid and hence can be concatnated using the <> operator.

type WriteIO = WriteM IO Source #

A write io-action.

bytesToWrite :: WriteM m -> BYTES Int Source #

Returns the bytes that will be written when the write action is performed.

unsafeWrite Source #

Arguments

:: WriteM m 
-> Pointer

The pointer for the buffer to be written into.

-> m () 

Perform the write action without any checks of the buffer

write :: (MonadIO m, EndianStore a) => a -> WriteM m Source #

The expression write a gives a write action that stores a value a. One needs the type of the value a to be an instance of EndianStore. Proper endian conversion is done irrespective of what the machine endianness is. The man use of this write is to serialize data for the consumption of the outside world.

writeStorable :: (MonadIO m, Storable a) => a -> WriteM m Source #

The expression writeStorable a gives a write action that stores a value a in machine endian. The type of the value a has to be an instance of Storable. This should be used when we want to talk with C functions and not when talking to the outside world (otherwise this could lead to endian confusion). To take care of endianness use the write combinator.

writeVector :: (EndianStore a, Vector v a, MonadIO m) => v a -> WriteM m Source #

The vector version of write.

writeStorableVector :: (Storable a, Vector v a, MonadIO m) => v a -> WriteM m Source #

The vector version of writeStorable.

writeFrom :: (MonadIO m, EndianStore a) => Int -> Src (Ptr a) -> WriteM m Source #

Write many elements from the given buffer

writeBytes :: (LengthUnit n, MonadIO m) => Word8 -> n -> WriteM m Source #

The combinator writeBytes n b writes b as the next n consecutive bytes.

padWrite Source #

Arguments

:: (LengthUnit n, MonadIO m) 
=> Word8

the padding byte to use

-> n

the length to align message to

-> WriteM m

the message that needs padding

-> WriteM m 

The write action padWrite w n wr is wr padded with the byte w so that the total length ends at a multiple of n.

prependWrite Source #

Arguments

:: (LengthUnit n, MonadIO m) 
=> Word8

the byte to pre-pend with.

-> n

the length to align the message to

-> WriteM m

the message that needs pre-pending

-> WriteM m 

The write action prependWrite w n wr is wr pre-pended with the byte w so that the total length ends at a multiple of n.

glueWrites Source #

Arguments

:: (LengthUnit n, MonadIO m) 
=> Word8

The bytes to use in the glue

-> n

The length boundary to align to.

-> WriteM m

The header write

-> WriteM m

The footer write

-> WriteM m 

The combinator glueWrites w n hdr ftr is equivalent to hdr <> glue <> ftr where the write glue writes as many bytes w so that the total length is aligned to the boundary n.

writeByteString :: MonadIO m => ByteString -> WriteM m Source #

Writes a strict bytestring.

skipWrite :: (LengthUnit u, Monad m) => u -> WriteM m Source #

A write action that just skips over the given bytes.