| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Raaz.Core.Transfer
Description
Module to reading from and writing into buffers.
Synopsis
- data ReadM m
- type ReadIO = ReadM IO
- bytesToRead :: ReadM m -> BYTES Int
- unsafeRead :: ReadM m -> Pointer -> m ()
- readBytes :: (LengthUnit sz, MonadIO m) => sz -> Dest Pointer -> ReadM m
- readInto :: (EndianStore a, MonadIO m) => Int -> Dest (Ptr a) -> ReadM m
- data WriteM m
- type WriteIO = WriteM IO
- bytesToWrite :: WriteM m -> BYTES Int
- unsafeWrite :: WriteM m -> Pointer -> m ()
- write :: (MonadIO m, EndianStore a) => a -> WriteM m
- writeStorable :: (MonadIO m, Storable a) => a -> WriteM m
- writeVector :: (EndianStore a, Vector v a, MonadIO m) => v a -> WriteM m
- writeStorableVector :: (Storable a, Vector v a, MonadIO m) => v a -> WriteM m
- writeFrom :: (MonadIO m, EndianStore a) => Int -> Src (Ptr a) -> WriteM m
- writeBytes :: (LengthUnit n, MonadIO m) => Word8 -> n -> WriteM m
- padWrite :: (LengthUnit n, MonadIO m) => Word8 -> n -> WriteM m -> WriteM m
- prependWrite :: (LengthUnit n, MonadIO m) => Word8 -> n -> WriteM m -> WriteM m
- glueWrites :: (LengthUnit n, MonadIO m) => Word8 -> n -> WriteM m -> WriteM m -> WriteM m
- writeByteString :: MonadIO m => ByteString -> WriteM m
- skipWrite :: (LengthUnit u, Monad m) => u -> WriteM m
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
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  first reads the
 data associated from <> r2r1 and then the read associated with the
 data r2.
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.
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.
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.
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.
An element of type `WriteM m` is an action which when executed transfers bytes
 into its input buffer.  The type WriteM m<> operator.
Instances
| MonadIO m => IsString (WriteM m) Source # | |
| Defined in Raaz.Core.Transfer Methods fromString :: String -> WriteM m # | |
| Monad m => Semigroup (WriteM m) Source # | |
| Monad m => Monoid (WriteM m) Source # | |
| Encodable (WriteM IO) Source # | |
| Defined in Raaz.Core.Transfer Methods toByteString :: WriteM IO -> ByteString Source # fromByteString :: ByteString -> Maybe (WriteM IO) Source # | |
bytesToWrite :: WriteM m -> BYTES Int Source #
Returns the bytes that will be written when the write action is performed.
Perform the write action without any checks of the buffer
write :: (MonadIO m, EndianStore a) => a -> WriteM m Source #
The expression write aa. 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 aa 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.
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.
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.
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.