raaz-0.1.0: The raaz cryptographic library.

Safe HaskellNone
LanguageHaskell2010

Raaz.Random

Contents

Description

Interface for cryptographically secure random byte generators.

Synopsis

Cryptographically secure randomness.

The raaz library gives a relatively high level interface to randomness. The monad RandM captures a batch of actions that generate/use cryptographically secure random bytes. In particular, you can use the functions random and randomByteString to actually generate random elements.

The monad RandM is an an instance of MonadMemory and hence can be run either securely or insecurely. Here are some examples.

-- Generate a pair of random Word8's
import Raaz
import Data.Word

main :: IO ()
main = insecurely rPair >>= print
   where rPair :: RandM (Word8, Word8)
         rPair = (,) <$> random <$> random
-- A version of hello world that has gone nuts. Printed in base16
-- to save some terminal grief.

main = insecurely who >>= \ w -> putStrLn $ "hello " ++ showBase16 w
  where who :: RandM ByteString
        who = randomByteString 10

Some times you need additional memory to keep track of other stuff. The monad RT mem is meant for such uses. It should be seen as the analogue of the monad MT mem which in addition allows you to pick cryptographically secure random data. In fact, the combinator liftMT allows you to lift an MT action to the corresponding RT action.

Internal details

Generating unpredictable stream of bytes is one task that has burnt the fingers of a lot of programmers. Unfortunately, getting it correct is something of a black art. Raaz uses a stream cipher (chacha20), initialised with a starting random key/iv. The starting seed is then drawn from the system entropy pool.

TODO: For system entropy we use /dev/urandom on a posix systems (no windows support yet). Even on posix systems, depending on underlying operating system, there are better options. The recommended way to generate randomness on an OpenBSD system is through the function arc4random (note that arc4random does not use rc4 cipher anymore). Recent Linux kernels support the getrandom system call which unfortunately is not yet popular. These system specific calls are better because they take into consideration many edge cases like for example /dev/urandom not being accessible or protection from interrupts Eventually we will be supporting these calls.

type RandM = RT VoidMemory Source #

The monad for generating cryptographically secure random data.

data RT mem a Source #

A batch of actions on the memory element mem that uses some randomness.

Instances

Monad (RT mem) Source # 

Methods

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

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

return :: a -> RT mem a #

fail :: String -> RT mem a #

Functor (RT mem) Source # 

Methods

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

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

Applicative (RT mem) Source # 

Methods

pure :: a -> RT mem a #

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

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

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

MonadIO (RT mem) Source # 

Methods

liftIO :: IO a -> RT mem a #

Memory mem => MonadMemory (RT mem) Source # 

Methods

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

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

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

Lift a memory action to the corresponding RT action.

randomByteString :: (Memory mem, LengthUnit l) => l -> RT mem ByteString Source #

Generate a random byteString.

Types that can be generated randomly

class Random a where Source #

Types that can be generated at random. It might appear that all storables should be an instance of this class, after all we know the size of the element why not write that many random bytes. In fact, this module provides an unsafeStorableRandom which does exactly that. However, we do not give a blanket definition for all storables because for certain refinements of a given type, like for example, Word8's modulo 10, unsafeStorableRandom introduces unacceptable skews.

Minimal complete definition

random

Methods

random :: Memory mem => RT mem a Source #

Instances

Random Int Source # 

Methods

random :: Memory mem => RT mem Int Source #

Random Int8 Source # 

Methods

random :: Memory mem => RT mem Int8 Source #

Random Int16 Source # 

Methods

random :: Memory mem => RT mem Int16 Source #

Random Int32 Source # 

Methods

random :: Memory mem => RT mem Int32 Source #

Random Int64 Source # 

Methods

random :: Memory mem => RT mem Int64 Source #

Random Word Source # 

Methods

random :: Memory mem => RT mem Word Source #

Random Word8 Source # 

Methods

random :: Memory mem => RT mem Word8 Source #

Random Word16 Source # 

Methods

random :: Memory mem => RT mem Word16 Source #

Random Word32 Source # 

Methods

random :: Memory mem => RT mem Word32 Source #

Random Word64 Source # 

Methods

random :: Memory mem => RT mem Word64 Source #

Random KEY Source # 

Methods

random :: Memory mem => RT mem KEY Source #

Random IV Source # 

Methods

random :: Memory mem => RT mem IV Source #

Random IV Source # 

Methods

random :: Memory mem => RT mem IV Source #

Random KEY256 Source # 

Methods

random :: Memory mem => RT mem KEY256 Source #

Random KEY192 Source # 

Methods

random :: Memory mem => RT mem KEY192 Source #

Random KEY128 Source # 

Methods

random :: Memory mem => RT mem KEY128 Source #

Random w => Random (BE w) Source # 

Methods

random :: Memory mem => RT mem (BE w) Source #

Random w => Random (LE w) Source # 

Methods

random :: Memory mem => RT mem (LE w) Source #

(Random a, Random b) => Random (a, b) Source # 

Methods

random :: Memory mem => RT mem (a, b) Source #

(Dimension d, Unbox w, Random w) => Random (Tuple d w) Source # 

Methods

random :: Memory mem => RT mem (Tuple d w) Source #

(Random a, Random b, Random c) => Random (a, b, c) Source # 

Methods

random :: Memory mem => RT mem (a, b, c) Source #

(Random a, Random b, Random c, Random d) => Random (a, b, c, d) Source # 

Methods

random :: Memory mem => RT mem (a, b, c, d) Source #

(Random a, Random b, Random c, Random d, Random e) => Random (a, b, c, d, e) Source # 

Methods

random :: Memory mem => RT mem (a, b, c, d, e) Source #

Low level access to randomness.

fillRandomBytes :: LengthUnit l => l -> Pointer -> RT mem () Source #

Fill the given input pointer with random bytes.

unsafeStorableRandom :: (Memory mem, Storable a) => RT mem a Source #

Generate a random element. The element picked is crypto-graphically pseudo-random.

This is a helper function that has been exported to simplify the definition of a Random instance for Storable types. However, there is a reason why we do not give a blanket instance for all instances Storable and why this function is unsafe? This function generates a random element of type a by generating n random bytes where n is the size of the elements of a. For instances that range the entire n byte space this is fine. However, if the type is actually a refinement of such a type --- consider for example, Word8 modulo 10 -- this function generates an unacceptable skew in the distribution. Hence this function is prefixed unsafe.

reseed :: RT mem () Source #

Reseed from the system entropy pool. There is never a need to explicitly seed your generator. The insecurely and securely calls makes sure that your generator is seed before starting. Furthermore, the generator also reseeds after every few GB of random bytes generates. Generating random data from the system entropy is usually an order of magnitude slower than using a fast stream cipher. Reseeding often can slow your program considerably without any additional security advantage.