raaz-0.3.3: 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

Description

 
Synopsis

Documentation

length :: ByteString -> BYTES Int Source #

A typesafe length for Bytestring

replicate :: LengthUnit l => l -> Word8 -> ByteString Source #

A type safe version of replicate

create :: LengthUnit l => l -> (Ptr a -> IO ()) -> IO ByteString Source #

The action create l act creates a length l bytestring where the contents are filled using the the act to fill the buffer.

createFrom :: LengthUnit l => l -> Ptr a -> IO ByteString Source #

The IO action createFrom n cptr creates a bytestring by copying n bytes from the pointer cptr.

withByteString :: ByteString -> (Ptr something -> IO a) -> IO a Source #

Works directly on the pointer associated with the ByteString. This function should only read and not modify the contents of the pointer.

unsafeCopyToPointer Source #

Arguments

:: Pointer ptr 
=> ByteString

The source.

-> ptr a

The destination.

-> IO () 

Copy the bytestring to the crypto buffer. This operation leads to undefined behaviour if the crypto pointer points to an area smaller than the size of the byte string.

unsafeNCopyToPointer Source #

Arguments

:: LengthUnit n 
=> n

length of data to be copied

-> ByteString

The source byte string

-> Ptr a

The buffer

-> IO () 

Similar to unsafeCopyToPointer but takes an additional input n which is the number of bytes (expressed in type safe length units) to transfer. This operation leads to undefined behaviour if either the bytestring is shorter than n or the crypto pointer points to an area smaller than n.

Cryptographic Primtives

class (Unbox (WordType p), EndianStore (WordType p), KnownNat (WordsPerBlock p)) => Primitive p Source #

Cryptographic primitives that process bulk data (like ciphers, cryptographic hashes) process data in blocks. For data that is not a multiple of the block size they may have some padding strategy. The type class that captures an abstract block cryptographic primitive.

Associated Types

type WordType p :: Type Source #

The block which is the smallest unit of data that the primitive processes, is typically considered as an array of a particular word which is captured by the following associated type.

type WordsPerBlock p :: Nat Source #

The size of the array that forms the block. In particular, the block can be seen as an array of size `BlockArraySize p` of type `WORD p`.

Instances

Instances details
Primitive XChaCha20 Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Primitive ChaCha20 Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Associated Types

type WordType ChaCha20 Source #

type WordsPerBlock ChaCha20 :: Nat Source #

Primitive Poly1305 Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Associated Types

type WordType Poly1305 Source #

type WordsPerBlock Poly1305 :: Nat Source #

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

Defined in Raaz.Primitive.Keyed.Internal

Associated Types

type WordType (Keyed prim) Source #

type WordsPerBlock (Keyed prim) :: Nat Source #

data family Key p :: Type Source #

The type family that captures the key of a keyed primitive.

Instances

Instances details
Initialisable ChaCha20Mem (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Eq (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Show (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Show (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Show (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

showsPrec :: Int -> Key (Keyed prim) -> ShowS #

show :: Key (Keyed prim) -> String #

showList :: [Key (Keyed prim)] -> ShowS #

Show (Key Poly1305) Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

IsString (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

IsString (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

IsString (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

fromString :: String -> Key (Keyed prim) #

Storable (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Storable (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Equality (Key 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

Encodable (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Initialisable (MemoryCell (Key ChaCha20)) (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Key XChaCha20 Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Key XChaCha20 = XKey KEY
newtype Key ChaCha20 Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Key ChaCha20 = Key KEY
data Key Poly1305 Source # 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

data Key Poly1305 = Key R S
newtype Key (Keyed prim) Source # 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

newtype Key (Keyed prim) = Key ByteString

data family Nounce p :: Type Source #

In addition to keys, certain primitives require nounces that can be public but needs to be distinct across different uses when sharing the key. The type family that captures the nounce for a primitive (if it requires one).

Instances

Instances details
Initialisable ChaCha20Mem (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Eq (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Show (Nounce XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Show (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

IsString (Nounce XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

IsString (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Storable (Nounce XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Storable (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Equality (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore (Nounce XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Nounce XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Nounce XChaCha20 Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Nounce XChaCha20 = XNounce (Tuple 6 WORD)
newtype Nounce ChaCha20 Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Nounce ChaCha20 = Nounce (Tuple 3 WORD)

type Block p = Tuple (WordsPerBlock p) (WordType p) Source #

A block of the primitive.

type BlockPtr p = Ptr (Block p) Source #

Pointer to a block of the primitive.

type AlignedBlockPtr n p = AlignedPtr n (Block p) Source #

Aligned version of block pointers.

newtype 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.

Constructors

BlockCount 

Fields

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

blocksOf :: Int -> Proxy p -> BlockCount p Source #

The expression n blocksOf primProxy specifies the message lengths in units of the block length of the primitive whose proxy is primProxy. This expression is sometimes required to make the type checker happy.

l1Cache :: BYTES Int Source #

Typical size of L1 cache. Used for selecting buffer size etc in crypto operations.

Byte sources.

Cryptographic input come from various sources; they can come from network sockets or might be just a string in the Haskell. To give a uniform interfaces for all such inputs, we define the abstract concept of a byte source. Essentially a byte source is one from which we can fill a buffer with bytes.

Among instances of ByteSource, some like for example ByteString are pure in the sense filling a buffer with bytes from such a source has no other side-effects. This is in contrast to a source like a sockets. The type class PureByteSource captures such byte sources.

class ByteSource src where Source #

Abstract byte sources. A bytesource is something that you can use to fill a buffer.

WARNING: The source is required to return Exhausted in the boundary case where it has exactly the number of bytes requested. In other words, if the source returns Remaining on any particular request, there should be at least 1 additional byte left on the source for the next request. Cryptographic block primitives perform certain special processing, like padding for example, for the last block and it is required to know whether the last block has been read or not.

Methods

fillBytes Source #

Arguments

:: BYTES Int

Buffer size

-> src

The source to fill.

-> Ptr a

Buffer pointer

-> IO (FillResult src) 

Fills a buffer from the source.

Instances

Instances details
ByteSource Handle Source #

WARNING: The fillBytes may block.

Instance details

Defined in Raaz.Core.ByteSource

ByteSource ByteString Source # 
Instance details

Defined in Raaz.Core.ByteSource

ByteSource ByteString Source # 
Instance details

Defined in Raaz.Core.ByteSource

ByteSource src => ByteSource [src] Source # 
Instance details

Defined in Raaz.Core.ByteSource

Methods

fillBytes :: BYTES Int -> [src] -> Ptr a -> IO (FillResult [src]) Source #

ByteSource src => ByteSource (Maybe src) Source # 
Instance details

Defined in Raaz.Core.ByteSource

Methods

fillBytes :: BYTES Int -> Maybe src -> Ptr a -> IO (FillResult (Maybe src)) Source #

class ByteSource src => PureByteSource src Source #

A byte source src is pure if filling from it does not have any other side effect on the state of the byte source. Formally, two different fills form the same source should fill the buffer with the same bytes. This additional constraint on the source helps to purify certain crypto computations like computing the hash or mac of the source. Usualy sources like ByteString etc are pure byte sources. A file handle is a byte source that is not a pure source.

Instances

Instances details
PureByteSource ByteString Source # 
Instance details

Defined in Raaz.Core.ByteSource

PureByteSource ByteString Source # 
Instance details

Defined in Raaz.Core.ByteSource

PureByteSource src => PureByteSource [src] Source # 
Instance details

Defined in Raaz.Core.ByteSource

PureByteSource src => PureByteSource (Maybe src) Source # 
Instance details

Defined in Raaz.Core.ByteSource

data FillResult a Source #

This type captures the result of a fill operation.

Constructors

Remaining a

There is still bytes left.

Exhausted (BYTES Int)

source exhausted with so much bytes read.

Instances

Instances details
Functor FillResult Source # 
Instance details

Defined in Raaz.Core.ByteSource

Methods

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

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

Eq a => Eq (FillResult a) Source # 
Instance details

Defined in Raaz.Core.ByteSource

Methods

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

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

Show a => Show (FillResult a) Source # 
Instance details

Defined in Raaz.Core.ByteSource

fill :: (Pointer ptr, LengthUnit len, ByteSource src) => len -> src -> ptr a -> IO (FillResult src) Source #

A version of fillBytes that takes type safe lengths as input.

processChunks Source #

Arguments

:: (Pointer ptr, MonadIO m, LengthUnit chunkSize, ByteSource src) 
=> m a

action on a complete chunk,

-> (BYTES Int -> m b)

action on the last partial chunk,

-> src

the source

-> ptr something

buffer to fill the chunk in

-> chunkSize

size of the chunksize

-> m b 

Process data from a source in chunks of a particular size.

withFillResult Source #

Arguments

:: (a -> b)

stuff to do when filled

-> (BYTES Int -> b)

stuff to do when exhausted

-> FillResult a

the fill result to process

-> b 

Combinator to handle a fill result.

data MemoryCell a Source #

A memory location to store a value of type having Storable instance.

Instances

Instances details
EndianStore a => WriteAccessible (MemoryCell a) Source # 
Instance details

Defined in Raaz.Core.Memory

EndianStore a => ReadAccessible (MemoryCell a) Source # 
Instance details

Defined in Raaz.Core.Memory

Storable a => Memory (MemoryCell a) Source # 
Instance details

Defined in Raaz.Core.Memory

Storable a => Extractable (MemoryCell a) a Source # 
Instance details

Defined in Raaz.Core.Memory

Methods

extract :: MemoryCell a -> IO a Source #

Storable a => Initialisable (MemoryCell a) a Source # 
Instance details

Defined in Raaz.Core.Memory

Methods

initialise :: a -> MemoryCell a -> IO () Source #

Initialisable (MemoryCell (Key ChaCha20)) (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

class Memory mem => WriteAccessible mem where Source #

This class captures memories that can be initialised by writing bytes to (portions of) its buffer.

Methods

writeAccess :: mem -> [Access] Source #

The ordered access to buffers through which bytes may be written into the memory.

afterWriteAdjustment :: mem -> IO () Source #

After writing data into the buffer, the memory might need further adjustments before it is considered "initialised" with the sensitive data.

Instances

Instances details
WriteAccessible ChaCha20Mem Source #

Writes into the key portion.

Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore a => WriteAccessible (MemoryCell a) Source # 
Instance details

Defined in Raaz.Core.Memory

class Memory mem => ReadAccessible mem where Source #

This class captures memories from which bytes can be extracted directly from (portions of) its buffer.

Methods

beforeReadAdjustment :: mem -> IO () Source #

Internal organisation of the data might need adjustment due to host machine having a different endian than the standard byte order of the associated type. This action perform the necessary adjustment before the bytes can be read-off from the associated readAccess adjustments.

readAccess :: mem -> [Access] Source #

The ordered access buffers for the memory through which bytes may be read off (after running beforeReadAdjustment of course)

Instances

Instances details
EndianStore a => ReadAccessible (MemoryCell a) Source # 
Instance details

Defined in Raaz.Core.Memory

data Access Source #

Data type that gives an access buffer to portion of the memory.

class Memory m => Extractable m v where Source #

Memories from which pure values can be extracted. Much like the case of the Initialisable class, avoid using this interface if you do not want the data extracted to be swapped. Use the ReadAccessible class instead.

Methods

extract :: m -> IO v Source #

Instances

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

Defined in Raaz.Primitive.ChaCha20.Internal

Storable a => Extractable (MemoryCell a) a Source # 
Instance details

Defined in Raaz.Core.Memory

Methods

extract :: MemoryCell a -> IO a Source #

Storable h => Extractable (HashMemory128 h) h Source # 
Instance details

Defined in Raaz.Primitive.HashMemory

Methods

extract :: HashMemory128 h -> IO h Source #

Storable h => Extractable (HashMemory64 h) h Source # 
Instance details

Defined in Raaz.Primitive.HashMemory

Methods

extract :: HashMemory64 h -> IO h Source #

class Memory m => Initialisable m v where Source #

Memories that can be initialised with a pure value. The pure value resides in the Haskell heap and hence can potentially be swapped. Therefore, this class should be avoided if compromising the initialisation value can be dangerous. Look into the type class WriteAccessible instead.

Methods

initialise :: v -> m -> IO () Source #

Instances

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

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 #

Initialisable ChaCha20Mem (BlockCount ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Initialisable ChaCha20Mem (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Initialisable ChaCha20Mem (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Storable a => Initialisable (MemoryCell a) a Source # 
Instance details

Defined in Raaz.Core.Memory

Methods

initialise :: a -> MemoryCell a -> IO () Source #

Storable h => Initialisable (HashMemory128 h) h Source # 
Instance details

Defined in Raaz.Primitive.HashMemory

Methods

initialise :: h -> HashMemory128 h -> IO () Source #

Storable h => Initialisable (HashMemory64 h) h Source # 
Instance details

Defined in Raaz.Primitive.HashMemory

Methods

initialise :: h -> HashMemory64 h -> IO () Source #

Initialisable (MemoryCell (Key ChaCha20)) (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

data VoidMemory Source #

A memory element that holds nothing.

Instances

Instances details
Memory VoidMemory Source # 
Instance details

Defined in Raaz.Core.Memory

class Memory m where Source #

Any cryptographic primitives use memory to store stuff. This class abstracts all types that hold some memory. Cryptographic application often requires securing the memory from being swapped out (think of memory used to store private keys or passwords). This abstraction supports memory securing. If your platform supports memory locking, then securing a memory will prevent the memory from being swapped to the disk. Once secured the memory location is overwritten by nonsense before being freed.

While some basic memory elements like MemoryCell are exposed from the library, often we require compound memory objects built out of simpler ones. The Applicative instance of the Alloc can be made use of in such situation to simplify such instance declaration as illustrated in the instance declaration for a pair of memory elements.

instance (Memory ma, Memory mb) => Memory (ma, mb) where

   memoryAlloc             = (,) <$> memoryAlloc <*> memoryAlloc

   unsafeToPointer (ma, _) =  unsafeToPointer ma

Methods

memoryAlloc :: Alloc m Source #

Returns an allocator for this memory.

unsafeToPointer :: m -> Ptr Word8 Source #

Returns the pointer to the underlying buffer.

Instances

Instances details
Memory VoidMemory Source # 
Instance details

Defined in Raaz.Core.Memory

Memory ChaCha20Mem Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Storable a => Memory (MemoryCell a) Source # 
Instance details

Defined in Raaz.Core.Memory

Storable h => Memory (HashMemory128 h) Source # 
Instance details

Defined in Raaz.Primitive.HashMemory

Storable h => Memory (HashMemory64 h) Source # 
Instance details

Defined in Raaz.Primitive.HashMemory

(Memory ma, Memory mb) => Memory (ma, mb) Source # 
Instance details

Defined in Raaz.Core.Memory

Methods

memoryAlloc :: Alloc (ma, mb) Source #

unsafeToPointer :: (ma, mb) -> Ptr Word8 Source #

(Memory ma, Memory mb, Memory mc) => Memory (ma, mb, mc) Source # 
Instance details

Defined in Raaz.Core.Memory

Methods

memoryAlloc :: Alloc (ma, mb, mc) Source #

unsafeToPointer :: (ma, mb, mc) -> Ptr Word8 Source #

(Memory ma, Memory mb, Memory mc, Memory md) => Memory (ma, mb, mc, md) Source # 
Instance details

Defined in Raaz.Core.Memory

Methods

memoryAlloc :: Alloc (ma, mb, mc, md) Source #

unsafeToPointer :: (ma, mb, mc, md) -> Ptr Word8 Source #

type Alloc mem = TwistRF AllocField (BYTES Int) mem Source #

A memory allocator for the memory type mem. The Applicative instance of Alloc can be used to build allocations for complicated memory elements from simpler ones and takes care of handling the size/offset calculations involved.

pointerAlloc :: LengthUnit l => l -> Alloc (Ptr Word8) Source #

Allocates a buffer of size l and returns the pointer to it pointer.

withMemoryPtr :: Memory m => (BYTES Int -> Ptr Word8 -> IO a) -> m -> IO a Source #

Apply some low level action on the underlying buffer of the memory.

withMemory :: Memory mem => (mem -> IO a) -> IO a Source #

Perform an action which makes use of this memory. The memory allocated will automatically be freed when the action finishes either gracefully or with some exception. Besides being safer, this method might be more efficient as the memory might be allocated from the stack directly and will have very little GC overhead.

withSecureMemory :: Memory mem => (mem -> IO a) -> IO a Source #

Similar to withMemory but allocates a secure memory for the action. Secure memories are never swapped on to disk and will be wiped clean of sensitive data after use. However, be careful when using this function in a child thread. Due to the daemonic nature of Haskell threads, if the main thread exists before the child thread is done with its job, sensitive data can leak. This is essentially a limitation of the bracket which is used internally.

modifyMem :: (Initialisable mem a, Extractable mem b) => (b -> a) -> mem -> IO () Source #

Apply the given function to the value in the cell. For a function f :: b -> a, the action modify f first extracts a value of type b from the memory element, applies f to it and puts the result back into the memory.

modifyMem f mem = do b <- extract mem
                     initialise (f b) mem

memTransfer :: (ReadAccessible src, WriteAccessible dest) => Dest dest -> Src src -> IO () Source #

Transfer the bytes from the source memory to the destination memory. The total bytes transferred is the minimum of the bytes available at the source and the space available at the destination.

unsafeGetCellPointer :: Storable a => MemoryCell a -> Ptr a Source #

The location where the actual storing of element happens. This pointer is guaranteed to be aligned to the alignment restriction of a

withCellPointer :: Storable a => (Ptr a -> IO b) -> MemoryCell a -> IO b Source #

Work with the underlying pointer of the memory cell. Useful while working with ffi functions.

copyCell :: Storable a => Dest (MemoryCell a) -> Src (MemoryCell a) -> IO () Source #

Copy the contents of one memory cell to another.