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

Description

 
Synopsis

Low level memory management in raaz.

Warning: This module is pretty low level and should not be needed in typical use cases. Only developers of protocols and primitives might have a reason to look into this module.

The memory subsytem of raaz gives a relatively abstract and type safe interface for performing low level size calculations and pointer arithmetic. The two main components of this subsystem is the class Memory whose instances are essentially memory buffers that are distinguished at the type level, and the type Alloc that captures the allocation strategies for these types.

The memory class

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 #

data VoidMemory Source #

A memory element that holds nothing.

Instances

Instances details
Memory VoidMemory Source # 
Instance details

Defined in Raaz.Core.Memory

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.

The allocator

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.

Initialisation and Extraction.

Memories often allow initialisation with and extraction of values in the Haskell world. The Initialisable and Extractable class captures this interface.

Explicit Pointer

Using the Initialisable and Extractable for sensitive data interface defeats one important purpose of the memory subsystem namely providing memory locking. Using these interfaces means keeping the sensitive information as pure values in the Haskell heap which impossible to lock. Worse still, the GC often move the data around spreading it all around the memory. One should use direct byte transfer via memcpy for effecting these initialisation. An interface to facilitate these is the type classes ReadAccessible and WriteAccessble where direct access is given (via the Access buffer) to the portions of the internal memory where sensitive data is kept.

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

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 #

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

Accessing the bytes directly

To avoid the problems associated with the Initialisable and Extractable interface, certain memory types give access to the associated buffers directly via the Access buffer. Data then needs to be transferred between these memories directly via memcpy making use of the Access buffers thereby avoiding a copy in the Haskell heap where it is prone to leak.

ReadAccessible:
Instances of these class are memories that are on the source side of the transfer. Examples include the memory element that is used to implement a Diffie-Hellman key exchange. The exchanged key is in the memory which can then be used to initialise a cipher for the actual transfer of encrypted data .
WriteAccessible:
Instances of these classes are memories that are on the destination side of the transfer. The memory element that stores the key for a cipher is an example of such a element.

data Access Source #

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

Constructors

Access 

Fields

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

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

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.

A basic memory cell.

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

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

Copy the contents of one memory cell to another.

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.

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