Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- class Memory m where
- data VoidMemory
- copyMemory :: Memory m => Dest m -> Src m -> IO ()
- class Memory m => Initialisable m v where
- class Memory m => Extractable m v where
- class Memory m => InitialisableFromBuffer m where
- class Memory m => ExtractableToBuffer m where
- data MemoryCell a
- withCellPointer :: Storable a => (Ptr a -> IO b) -> MT (MemoryCell a) b
- getCellPointer :: Storable a => MT (MemoryCell a) (Ptr a)
- data MT mem a
- execute :: (mem -> IO a) -> MT mem a
- getMemory :: MT mem mem
- onSubMemory :: (mem -> submem) -> MT submem a -> MT mem a
- liftSubMT :: (mem -> submem) -> MT submem a -> MT mem a
- modify :: (Initialisable m a, Extractable m b) => (b -> a) -> MT m ()
- liftAllocator :: Allocator IO a -> Allocator (MT mem) a
- class (Monad m, MonadIO m) => MonadMemory m where
- data MemoryM a
- runMT :: Memory mem => MT mem a -> MemoryM a
- type Alloc mem = TwistRF AllocField (BYTES Int) mem
- pointerAlloc :: LengthUnit l => l -> Alloc Pointer
The Memory subsystem.
Cryptographic operations often need to keep sensitive information in its memory space. If this memory is swapped out to the disk, this can be dangerous. The primary purpose of the memory subsystem in raaz provides a way to allocate and manage _secure memory_, i.e. memory that will not be swapped out during the execution of the process and will be wiped clean after use. There are there important parts to the memory subsystem:
- 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 typemem
, the type `Alloc mem` can be seen as the _allocation strategy_ for mem. For example, one of the things that it keeps track of the space required to create an memory element of typemem
. There is a natural applicative instance forAlloc
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. - 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 combinatorsecurely
or the combinatorinsecurely
. If one use the combinatorsecurely
, then all allocations done during the run is from a locked memory pool which is wiped clean before de-allocation. The typesMT
andMemoryM
are two instances that we expose from this library.
Initialisation and Extraction.
Memory elements often needs to be initialised. Similarly data needs
to be extracted out of memory. An instance declaration
for the memory type Initialisable
mem amem
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 stack
and hence can be swapped out. Consider a memory element mem
that
stores some sensitive information, say for example the unencrypted
private key. Now suppose that we need to extracting out the key 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 part of 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.
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
memoryAlloc :: Alloc m Source #
Returns an allocator for this memory.
unsafeToPointer :: m -> Pointer Source #
Returns the pointer to the underlying buffer.
Memory VoidMemory Source # | |
Storable a => Memory (MemoryCell a) Source # | |
Storable h => Memory (HashMemory h) Source # | |
(Memory ma, Memory mb) => Memory (ma, mb) Source # | |
(Memory ma, Memory mb, Memory mc) => Memory (ma, mb, mc) Source # | |
(Memory ma, Memory mb, Memory mc, Memory md) => Memory (ma, mb, mc, md) Source # | |
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 #
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
initialise :: v -> MT m () Source #
Storable a => Initialisable (MemoryCell a) a Source # | |
Storable h => Initialisable (HashMemory h) h Source # | |
Initialisable (HashMemory SHA1) () Source # | |
Initialisable (HashMemory SHA256) () Source # | |
Initialisable (HashMemory SHA512) () Source # | |
class Memory m => Extractable m v where Source #
Memories from which pure values can be extracted. Once a pure value is extracted,
Storable a => Extractable (MemoryCell a) a Source # | |
Storable h => Extractable (HashMemory h) h Source # | |
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.
initialiser :: m -> ReadM (MT m) Source #
EndianStore a => InitialisableFromBuffer (MemoryCell a) 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.
EndianStore a => ExtractableToBuffer (MemoryCell a) Source # | |
A basic memory cell.
data MemoryCell a Source #
A memory location to store a value of type having Storable
instance.
EndianStore a => ExtractableToBuffer (MemoryCell a) Source # | |
EndianStore a => InitialisableFromBuffer (MemoryCell a) Source # | |
Storable a => Memory (MemoryCell a) Source # | |
Storable a => Extractable (MemoryCell a) a Source # | |
Storable a => Initialisable (MemoryCell a) a Source # | |
withCellPointer :: 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 :: Storable a => MT (MemoryCell a) (Ptr a) Source #
Get the pointer associated with the given memory cell.
Actions on memory elements.
An action of type
is an action that uses internally
a a single memory object of type MT
mem amem
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.
:: (mem -> submem) | Projection from the compound element to sub memory element. |
-> MT submem a | Memory thread of the sub-element. |
-> MT mem a |
The combinator onSubMemory
allows us to run a memory action on a
sub-memory element. Given a memory element of type mem
and a
sub-element of type submem
which can be obtained from the
compound memory element of type mem
using the projection proj
,
then onSubMemory proj
lifts the a memory thread of the sub
element to the compound element.
liftSubMT :: (mem -> submem) -> MT submem a -> MT mem a Source #
Deprecated: use onSubMemory instead
Alternate name for onSubMemory.
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.
liftAllocator :: Allocator IO a -> Allocator (MT mem) a Source #
An IO allocator can be lifted to the memory thread level as follows.
Generic 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
- Memory threads captured by the type
MT
, which are a sequence of actions that use the same memory element and - 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.
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).
MonadMemory MemoryM Source # | |
Memory mem => MonadMemory (MT mem) Source # | |
Memory mem => MonadMemory (RT mem) Source # | |
A memory action that uses some sort of memory element internally.
runMT :: Memory mem => MT mem a -> MemoryM a Source #
Run the memory thread to obtain a memory action.
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.