raaz-0.2.0: The raaz cryptographic library.

Safe HaskellNone
LanguageHaskell2010

Raaz.Core.Memory

Contents

Description

The memory subsystem associated with 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.

Synopsis

The Memory subsystem.

Cryptographic operations often need to keep sensitive information like private keys in its memory space. Such sensitive information can leak to the external would if the memory where the data is stored is swapped out to a disk. What makes this particularly dangerous is that the data can reside on the disk almost permanently and might even survive when the hardware is scrapped. The primary purpose of the memory subsystem is to provide a way to allocate and manage secure memory, i.e. memory that will not be swapped out as long as the memory is used and will be wiped clean after use. It consists of the following components:

The Memory type class:
A memory element is some type that holds an internal buffer inside it.
The Alloc type:
Memory elements need to be allocated and this is involves a lot of low lever pointer arithmetic. The Alloc types gives a high level interface for memory allocation. For a memory type mem, the type `Alloc mem` can be seen as the _allocation strategy_ for mem. For example, one of the things that it keeps track of is the space required to create an memory element of type mem. There is a natural applicative instance for Alloc which helps build the allocation strategy for a compound memory type from its components in a modular fashion _without_ explicit size calculation or offset computation.
MemoryThreads:
Instances of this class are actions that use some kind of memory elements inside it. Such a thread can be run using the combinator securely or the combinator insecurely. If one use the combinator securely, then the allocation of the memory element to be used by the action is done using a locked memory pool which is wiped clean before de-allocation.

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

   unsafeToPointer (ma, _) =  unsafeToPointer ma

Minimal complete definition

memoryAlloc, unsafeToPointer

Methods

memoryAlloc :: Alloc m Source #

Returns an allocator for this memory.

unsafeToPointer :: m -> Pointer Source #

Returns the pointer to the underlying buffer.

Instances

Memory VoidMemory Source # 
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 #

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

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

Methods

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

unsafeToPointer :: (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 #

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

data VoidMemory Source #

A memory element that holds nothing.

copyMemory Source #

Arguments

:: Memory m 
=> Dest m

Destination

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

Initialisation and Extraction.

Memory elements often needs to be initialised. Similarly data needs to be extracted out of memory. An instance declaration Initialisable mem a for the memory type mem indicates that it can be initialised with the pure value a. 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.

There is an inherent danger in initialising and extracting pure values out of memory. Pure values are stored on the Haskell heap and hence can be swapped out. Consider a memory element mem that stores some sensitive information, say for example the unencrypted private key. Suppose we extract this key out of the memory element as a pure value before its encryption and storage into the key file. It is likely that the key is swapped out to the disk as the extracted key is part of the the haskell heap.

The InitialiseFromBuffer (ExtractableToBuffer) class gives an interface for reading from (writing to) buffers directly minimising the chances of inadvertent exposure of sensitive information from the Haskell heap due to swapping.

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. Consider using InitialiseableFromBuffer

Minimal complete definition

initialise

Methods

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

class Memory m => Extractable m v where Source #

Memories from which pure values can be extracted. Once a pure value is extracted,

Minimal complete definition

extract

Methods

extract :: MT m v Source #

Instances

class Memory m => InitialisableFromBuffer m where Source #

A memory type that can be initialised from a pointer buffer. The initialisation performs a direct copy from the input buffer and hence the chances of the initialisation value ending up in the swap is minimised.

Minimal complete definition

initialiser

Methods

initialiser :: m -> ReadM (MT m) Source #

class Memory m => ExtractableToBuffer m where Source #

A memory type that can extract bytes into a buffer. The extraction will perform a direct copy and hence the chances of the extracted value ending up in the swap space is minimised.

Minimal complete definition

extractor

Methods

extractor :: m -> WriteM (MT m) Source #

A basic memory cell.

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

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

getCellPointer :: (MemoryThread mT, Storable a) => mT (MemoryCell a) (Ptr a) Source #

Get the pointer associated with the given memory cell.

Memory threads.

class MemoryThread mT where Source #

A class that captures abstract "memory threads". A memory thread can either be run securely or insecurely. Pure IO actions can be run inside a memory thread using the runIO. However, the IO action that is being run must not directly or indirectly run a secure action ever. In particular, the following code is bad.

-- BAD EXAMPLE: DO NOT USE.
runIO $ securely $ foo

On the other hand the following code is fine

runIO $ insecurely $ someMemoryAction

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. Whether a given IO action unlocks memory is difficult to keep track of; for all you know, it might be a FFI call that does an memunlock. Hence, currently there is no easy way to enforce this.

Minimal complete definition

securely, insecurely, liftMT, onSubMemory

Methods

securely :: Memory mem => mT mem a -> IO a Source #

Run a memory action with the internal memory allocated from a locked memory buffer. This memory buffer will never be swapped out by the operating system and will 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 :: Memory mem => mT mem a -> IO a Source #

Run a memory action with the internal memory used by the action being allocated from 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).

liftMT :: MT mem a -> mT mem a Source #

Lift an actual memory thread.

onSubMemory :: (mem -> submem) -> mT submem a -> mT mem a Source #

Combinator that allows us to run a memory action on a sub-memory element. A sub-memory of submem of a memory element mem is given by a projection proj : mem -> submem. The action onSubMemory proj lifts the a memory thread on the sub element to the compound element.

Instances

MemoryThread MT Source # 

Methods

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

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

liftMT :: MT mem a -> MT mem a Source #

onSubMemory :: (mem -> submem) -> MT submem a -> MT mem a Source #

MemoryThread RT Source # 

Methods

securely :: Memory mem => RT mem a -> IO a Source #

insecurely :: Memory mem => RT mem a -> IO a Source #

liftMT :: MT mem a -> RT mem a Source #

onSubMemory :: (mem -> submem) -> RT submem a -> RT mem a Source #

doIO :: MemoryThread mT => IO a -> mT mem a Source #

Perform an IO action inside the memory thread.

getMemory :: MemoryThread mT => mT mem mem Source #

Get the underlying memory element of the memory thread.

modify :: (Initialisable mem a, Extractable mem b, MemoryThread mT) => (b -> a) -> mT mem () 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

execute :: MemoryThread mT => (mem -> IO a) -> mT mem a Source #

Run a given memory action in the memory thread.

data MT mem a Source #

An action of type MT mem a is an action that uses internally 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

MemoryThread MT Source # 

Methods

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

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

liftMT :: MT mem a -> MT mem a Source #

onSubMemory :: (mem -> submem) -> MT submem a -> MT mem a Source #

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 #

WARNING: do not lift a secure memory action.

Methods

liftIO :: IO a -> MT mem a #

Some low level MT actions.

liftPointerAction :: PointerAction IO a b -> PointerAction (MT mem) a b Source #

An IO allocator can be lifted to the memory thread level as follows.

Memory allocation

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.

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

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