raaz-0.0.2: The raaz cryptographic library.

Safe HaskellNone

Raaz.Core.Memory

Contents

Description

The memory subsystem associated with raaz.

Synopsis

The Memory subsystem.

The memory subsystem consists of two main components.

The Memory type class
A memory element is some type that holds an internal buffer inside it. The operations that are allowed on the element is controlled by the associated type. Certain memory element have a default way in which it can be initialised by values of type a. An instance declaration Initialisable mem a for the memory type mem is done in such case. Similary, if values of type b can be extracted out of a memory element mem, we can indicate it with an instance of Extractable mem a.
The Alloc type and memory allocation
The most important and often error prone operation while using low level memory buffers is its allocation. The Alloc types gives the allocation strategy for a memory element keeping track of the necessary book keeping involved in it. The Alloc type is an instance of Applicative which helps build the allocation strategy for a compound memory type from its components in a modular fashion without any explicit size calculation or offset computation.
The MonadMemory class
Instances of these classes are actions that use some kind of memory elements, i.e. instances of the class Memory, inside it. Any such monad can either be run using the combinator securely or the combinator insecurely. If one use the combinator securely, then all allocations done during the run is from a locked memory pool which is wiped clean before de-allocation. The types MT and MemoryM are two instances that we expose from this library.

class Memory m whereSource

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

    underlyingPtr (ma, _) =  underlyingPtr ma

Methods

memoryAlloc :: Alloc mSource

Returns an allocator for this memory.

underlyingPtr :: m -> PointerSource

Returns the pointer to the underlying buffer.

Instances

Storable a => Memory (MemoryCell a) 
Storable h => Memory (HashMemory h) 
(Memory ma, Memory mb) => Memory (ma, mb) 
(Memory ma, Memory mb, Memory mc) => Memory (ma, mb, mc) 
(Memory ma, Memory mb, Memory mc, Memory md) => Memory (ma, mb, mc, md) 

copyMemorySource

Arguments

:: Memory m 
=> m

Destination

-> m

Source

-> IO () 

Copy data from a given memory location to the other. The first argument is destionation and the second argument is source to match with the convention followed in memcpy.

A basic memory cell.

data MemoryCell a Source

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

Initialising and extracting.

class Memory m => Extractable m v whereSource

Methods

extract :: MT m vSource

Instances

Actions on memory elements.

data MT mem a Source

An action of type MT mem a is an action that uses internally a a single memory object of type mem and returns a result of type a. All the actions are performed on a single memory element and hence the side effects persist. It is analogues to the ST monad.

Instances

Monad (MT mem) 
Functor (MT mem) 
Applicative (MT mem) 
MonadIO (MT mem) 
Memory mem => MonadMemory (MT mem) 

execute :: (mem -> IO a) -> MT mem aSource

Run a given memory action in the memory thread.

getMemory :: MT mem memSource

liftSubMTSource

Arguments

:: (mem -> mem')

Projection from the compound element to sub-element

-> MT mem' a

Memory thread of the sub-element.

-> MT mem a 

Compound memory elements might intern be composed of sub-elements. Often one might want to lift the memory thread for a sub-element to the compound element. Given a sub-element of type mem' which can be obtained from the compound memory element of type mem using the projection proj, liftSubMT proj lifts the a memory thread of the sub element to the compound element.

modify :: (Initialisable m a, Extractable m b) => (b -> a) -> MT m ()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.

 modify f = do b          <- extract
               initialise $  f b

Some low level MT actions.

getMemoryPointer :: Memory mem => MT mem PointerSource

Get the pointer associated with the given memory.

withPointer :: Memory mem => (Pointer -> IO b) -> MT mem bSource

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

allocate :: LengthUnit bufSize => bufSize -> (Pointer -> MT mem a) -> MT mem aSource

Given an memory thread

Generic memory monads.

class (Monad m, MonadIO m) => MonadMemory m whereSource

A class that captures monads that use an internal memory element.

Any instance of MonadMemory can be executed securely in which case all allocations are performed from a locked pool of memory. which at the end of the operation is also wiped clean before deallocation.

Systems often put tight restriction on the amount of memory a process can lock. Therefore, secure memory is often to be used judiciously. Instances of this class should also implement the the combinator insecurely which allocates all memory from an unlocked memory pool.

This library exposes two instances of MonadMemory

  1. Memory threads captured by the type MT, which are a sequence of actions that use the same memory element and
  2. Memory actions captured by the type MemoryM.

WARNING: Be careful with liftIO.

The rule of thumb to follow is that the action being lifted should itself never unlock any memory. In particular, the following code is bad because the securely action unlocks some portion of the memory after foo is executed.

  liftIO $ securely $ foo

On the other hand the following code is fine

 liftIO $ insecurely $ someMemoryAction

Whether an IO action unlocks memory is difficult to keep track of; for all you know, it might be a FFI call that does an memunlock.

As to why this is dangerous, it has got to do with the fact that mlock and munlock do not nest correctly. A single munlock can unlock multiple calls of mlock on the same page.

Methods

securely :: m a -> IO aSource

Perform the memory action where all memory elements are allocated locked memory. All memory allocated will be locked and hence will never be swapped out by the operating system. It will also be wiped clean before releasing.

Memory locking is an expensive operation and usually there would be a limit to how much locked memory can be allocated. Nonetheless, actions that work with sensitive information like passwords should use this to run an memory action.

insecurely :: m a -> IO aSource

Perform the memory action where all memory elements are allocated unlocked memory. Use this function when you work with data that is not sensitive to security considerations (for example, when you want to verify checksums of files).

Instances

data MemoryM a Source

A memory action that uses some sort of memory element internally.

runMT :: Memory mem => MT mem a -> MemoryM aSource

Run the memory thread to obtain a memory action.

Memory allocation

type Alloc mem = TwistRF AllocField ALIGNMonoid memSource

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.

pointerAlloc :: LengthUnit l => l -> Alloc PointerSource

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