raaz-0.0.1: The raaz cryptographic library.

Safe HaskellNone
LanguageHaskell98

Raaz.Core.Memory

Contents

Description

The memory subsystem associated with raaz.

Synopsis

The Memory subsystem

The memory subsystem consists of two main components.

  1. Abstract elements captured by the Memory type class.
  2. Abstract memory actions captured by the type class MonadMemory.

Memory monads

class (Monad m, MonadIO m) => MonadMemory m where Source #

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.

Minimal complete definition

securely, insecurely

Methods

securely :: m a -> IO a Source #

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 a Source #

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

MonadMemory MemoryM Source # 

Methods

securely :: MemoryM a -> IO a Source #

insecurely :: MemoryM a -> IO a Source #

Memory mem => MonadMemory (MT mem) Source # 

Methods

securely :: MT mem a -> IO a Source #

insecurely :: MT mem a -> IO a Source #

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) Source # 

Methods

(>>=) :: MT mem a -> (a -> MT mem b) -> MT mem b #

(>>) :: MT mem a -> MT mem b -> MT mem b #

return :: a -> MT mem a #

fail :: String -> MT mem a #

Functor (MT mem) Source # 

Methods

fmap :: (a -> b) -> MT mem a -> MT mem b #

(<$) :: a -> MT mem b -> MT mem a #

Applicative (MT mem) Source # 

Methods

pure :: a -> MT mem a #

(<*>) :: MT mem (a -> b) -> MT mem a -> MT mem b #

(*>) :: MT mem a -> MT mem b -> MT mem b #

(<*) :: MT mem a -> MT mem b -> MT mem a #

MonadIO (MT mem) Source # 

Methods

liftIO :: IO a -> MT mem a #

Memory mem => MonadMemory (MT mem) Source # 

Methods

securely :: MT mem a -> IO a Source #

insecurely :: MT mem a -> IO a Source #

execute :: (mem -> IO a) -> MT mem a Source #

Run a given memory action in the memory thread.

getMemory :: MT mem mem Source #

liftSubMT Source #

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.

data MemoryM a Source #

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

Instances

Monad MemoryM Source # 

Methods

(>>=) :: MemoryM a -> (a -> MemoryM b) -> MemoryM b #

(>>) :: MemoryM a -> MemoryM b -> MemoryM b #

return :: a -> MemoryM a #

fail :: String -> MemoryM a #

Functor MemoryM Source # 

Methods

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

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

Applicative MemoryM Source # 

Methods

pure :: a -> MemoryM a #

(<*>) :: MemoryM (a -> b) -> MemoryM a -> MemoryM b #

(*>) :: MemoryM a -> MemoryM b -> MemoryM b #

(<*) :: MemoryM a -> MemoryM b -> MemoryM a #

MonadIO MemoryM Source # 

Methods

liftIO :: IO a -> MemoryM a #

MonadMemory MemoryM Source # 

Methods

securely :: MemoryM a -> IO a Source #

insecurely :: MemoryM a -> IO a Source #

runMT :: Memory mem => MT mem a -> MemoryM a Source #

Run the memory thread to obtain a memory action.

Some low level functions.

getMemoryPointer :: Memory mem => MT mem Pointer Source #

Get the pointer associated with the given memory.

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

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 a Source #

Given an memory thread

Memory elements.

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

   underlyingPtr (ma, _) =  underlyingPtr ma

Minimal complete definition

memoryAlloc, underlyingPtr

Methods

memoryAlloc :: Alloc m Source #

Returns an allocator for this memory.

underlyingPtr :: m -> Pointer Source #

Returns the pointer to the underlying buffer.

Instances

Storable a => Memory (MemoryCell a) Source # 
Storable h => Memory (HashMemory h) Source # 
(Memory ma, Memory mb) => Memory (ma, mb) Source # 

Methods

memoryAlloc :: Alloc (ma, mb) Source #

underlyingPtr :: (ma, mb) -> Pointer Source #

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

Methods

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

underlyingPtr :: (ma, mb, mc) -> Pointer Source #

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

Methods

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

underlyingPtr :: (ma, mb, mc, md) -> Pointer Source #

copyMemory Source #

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.

class Memory m => Initialisable m v where Source #

Minimal complete definition

initialise

Methods

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

class Memory m => Extractable m v where Source #

Minimal complete definition

extract

Methods

extract :: MT m v Source #

Instances

modify :: (Initialisable m a, Extractable m b) => (b -> a) -> MT m () Source #

Apply the given function to the value in the cell.

Some basic memory elements.

data MemoryCell a Source #

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

Memory allocation

type Alloc mem = TwistRF AllocField ALIGNMonoid 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.

pointerAlloc :: LengthUnit l => l -> Alloc Pointer Source #

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