raaz-0.3.5: Fast and type safe cryptography.
Copyright(c) Piyush P Kurur 2016
LicenseApache-2.0 OR BSD-3-Clause
MaintainerPiyush P Kurur <ppk@iitpkd.ac.in>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Raaz

Description

 
Synopsis

Getting started

Raaz is a cryptographic library that provides an easy to use, type safe interface for cryptographic applications. Applications can get their cryptography wrong and this can have disastrous consequences. This can be due to the wrong choices of the underlying cryptographic primitives, or due to ignoring certain implementation details (reusing the key, nounce pair). To prevent this kind of issues, raaz, like other modern libraries, give a very high level interface with the library taking the responsibility of selecting sane primitives and their correct usages. The recommended usage there is to import the top level module and get going.

module Main where

import Raaz

In addition, raaz makes use of the type system of Haskell to give additional guarantees:

Type safety:
Instead of representing cryptographic data as plain strings, raaz uses distinct types for semantically distinct cryptographic data. If the user inadvertently compares a Sha512 digest with a Blake2b digest, the compiler will flag this as an error. Compare this with the situation in many libraries where both these are just 512-bit quantities.
Timing safe equality:
All cryptographically sensitive data have timing safe equality operation ==. The default comparison is therefore safe and we encourage its use. Compare this with many other libraries where one has to remember to use specific functions sanitised timing safe comparisons.
Locked memory:
The interface to locked memory is provided through the combinators withMemory and withSecureMemory. These combinators take any IO action that expects a memory element (captured by the class Memory) and runs it by providing such an element. The underlying memory buffer is zeroed at the end of the action. In addition, withSecureMeory ensures that the memory allocated for the memory element is locked (and hence not swapped out). This gives a relatively higher level interface for locked memory. A word of caution though. Interfaces that directly deal with memory elements should be considered low-level code and should better be left to advanced users. Furthermore certain usages, particularly those that involve reading pure values out of the memory element, are problematic and a lot of caution needs to be employed when using this interface.

Supported Cryptographic operations

The raaz library provides the following cryptographic operations.

Message Digest:
Compute a short summary of a message that can act as an integrity check for the message. A computationally bound adversary cannot create two distinct messages with the same digest. It does not ensure authentication.
Message Authentication:
In addition to integrity, we often want to ensure that a particular message has indeed come from a know peer (with whom we share a secret). Message authentication is for this purpose. It however, does not ensure privacy
Message Locking:
In addition to authentication, often we want to ensure that the message is private, i.e. no one other than the originator (with whom we share a secret) should be able to know the contents of our communication. Message lock (via authenticated encryption) is for this purpose.
Cryptographically secure random data:
We also have an interface to provide cryptographically secure bytes/data.

For detailed information on the api supported, please consult the documentation of the individual modules.

module Raaz.Auth

Textual and Binary representation

Many cryptographic types exposed from this library like hashes, message authentication, keys and nounces can be converted from/to their textual representation (via the Show, IsString instances) as well as binary representation (via their Encodable instance).

WARNING: textual/binary encoding are not type safe

A user of the raaz library should use the explicit data types instead of their encodings. There are a few security consequences of violating this principle

  1. The IsString instance means that we represent values as string within program source (via OverloadedStrings). Do not do this unless it is to write unit tests as this can result in runtime bugs.
  2. Timing safe comparison will get compromised if one compares the encodings (bytestring) instead of the types themselves

Core types and operations of raaz

data family Key p #

Instances

Instances details
Initialisable ChaCha20Mem (Key ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

initialise :: Key ChaCha20 -> ChaCha20Mem -> IO ()

Initialisable Internals (Key (Keyed Prim)) 
Instance details

Defined in Mac.Implementation

Methods

initialise :: Key (Keyed Prim) -> Internals -> IO ()

Initialisable AEADMem (Key Cipher) 
Instance details

Defined in Interface

Methods

initialise :: Key Cipher -> AEADMem -> IO ()

Initialisable Internals (Key XChaCha20) 
Instance details

Defined in XChaCha20.Implementation

Methods

initialise :: Key XChaCha20 -> Internals -> IO ()

Eq (Key ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

(==) :: Key ChaCha20 -> Key ChaCha20 -> Bool #

(/=) :: Key ChaCha20 -> Key ChaCha20 -> Bool #

Show (Key ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

showsPrec :: Int -> Key ChaCha20 -> ShowS #

show :: Key ChaCha20 -> String #

showList :: [Key ChaCha20] -> ShowS #

Show (Key XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

showsPrec :: Int -> Key XChaCha20 -> ShowS #

show :: Key XChaCha20 -> String #

showList :: [Key XChaCha20] -> ShowS #

Show (Key Poly1305) 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

Methods

showsPrec :: Int -> Key Poly1305 -> ShowS #

show :: Key Poly1305 -> String #

showList :: [Key Poly1305] -> ShowS #

Show (Key (Keyed prim)) 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

showsPrec :: Int -> Key (Keyed prim) -> ShowS #

show :: Key (Keyed prim) -> String #

showList :: [Key (Keyed prim)] -> ShowS #

IsString (Key ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

fromString :: String -> Key ChaCha20 #

IsString (Key XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

fromString :: String -> Key XChaCha20 #

IsString (Key (Keyed prim)) 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

fromString :: String -> Key (Keyed prim) #

Storable (Key ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

sizeOf :: Key ChaCha20 -> Int #

alignment :: Key ChaCha20 -> Int #

peekElemOff :: Ptr (Key ChaCha20) -> Int -> IO (Key ChaCha20) #

pokeElemOff :: Ptr (Key ChaCha20) -> Int -> Key ChaCha20 -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Key ChaCha20) #

pokeByteOff :: Ptr b -> Int -> Key ChaCha20 -> IO () #

peek :: Ptr (Key ChaCha20) -> IO (Key ChaCha20) #

poke :: Ptr (Key ChaCha20) -> Key ChaCha20 -> IO () #

Storable (Key XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

sizeOf :: Key XChaCha20 -> Int #

alignment :: Key XChaCha20 -> Int #

peekElemOff :: Ptr (Key XChaCha20) -> Int -> IO (Key XChaCha20) #

pokeElemOff :: Ptr (Key XChaCha20) -> Int -> Key XChaCha20 -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Key XChaCha20) #

pokeByteOff :: Ptr b -> Int -> Key XChaCha20 -> IO () #

peek :: Ptr (Key XChaCha20) -> IO (Key XChaCha20) #

poke :: Ptr (Key XChaCha20) -> Key XChaCha20 -> IO () #

Encodable (Key ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

toByteString :: Key ChaCha20 -> ByteString

fromByteString :: ByteString -> Maybe (Key ChaCha20)

unsafeFromByteString :: ByteString -> Key ChaCha20

Encodable (Key XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

toByteString :: Key XChaCha20 -> ByteString

fromByteString :: ByteString -> Maybe (Key XChaCha20)

unsafeFromByteString :: ByteString -> Key XChaCha20

Encodable (Key (Keyed prim)) 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

Methods

toByteString :: Key (Keyed prim) -> ByteString

fromByteString :: ByteString -> Maybe (Key (Keyed prim))

unsafeFromByteString :: ByteString -> Key (Keyed prim)

EndianStore (Key ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

store :: Ptr (Key ChaCha20) -> Key ChaCha20 -> IO ()

load :: Ptr (Key ChaCha20) -> IO (Key ChaCha20)

adjustEndian :: Ptr (Key ChaCha20) -> Int -> IO ()

EndianStore (Key XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

store :: Ptr (Key XChaCha20) -> Key XChaCha20 -> IO ()

load :: Ptr (Key XChaCha20) -> IO (Key XChaCha20)

adjustEndian :: Ptr (Key XChaCha20) -> Int -> IO ()

Equality (Key ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

eq :: Key ChaCha20 -> Key ChaCha20 -> Result

Random (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Random

Methods

random :: RandomState -> IO (Key ChaCha20) Source #

Random (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Random

Methods

random :: RandomState -> IO (Key XChaCha20) Source #

Storable prim => Random (Key (Keyed prim)) Source # 
Instance details

Defined in Raaz.Random

Methods

random :: RandomState -> IO (Key (Keyed prim)) Source #

RandomStorable (Key ChaCha20) Source # 
Instance details

Defined in Raaz.Random

Methods

fillRandomElements :: Int -> Ptr (Key ChaCha20) -> RandomState -> IO () Source #

RandomStorable (Key XChaCha20) Source # 
Instance details

Defined in Raaz.Random

Methods

fillRandomElements :: Int -> Ptr (Key XChaCha20) -> RandomState -> IO () Source #

Initialisable (MemoryCell (Key ChaCha20)) (Key XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

initialise :: Key XChaCha20 -> MemoryCell (Key ChaCha20) -> IO ()

newtype Key ChaCha20 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Key ChaCha20 = Key KEY
newtype Key XChaCha20 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Key XChaCha20 = XKey KEY
data Key Poly1305 
Instance details

Defined in Raaz.Primitive.Poly1305.Internal

data Key Poly1305 = Key R S
newtype Key (Keyed prim) 
Instance details

Defined in Raaz.Primitive.Keyed.Internal

newtype Key (Keyed prim) = Key ByteString

data family Nounce p #

Instances

Instances details
Initialisable ChaCha20Mem (Nounce ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

initialise :: Nounce ChaCha20 -> ChaCha20Mem -> IO ()

Initialisable AEADMem (Nounce Cipher) 
Instance details

Defined in Interface

Methods

initialise :: Nounce Cipher -> AEADMem -> IO ()

Initialisable Internals (Nounce XChaCha20) 
Instance details

Defined in XChaCha20.Implementation

Methods

initialise :: Nounce XChaCha20 -> Internals -> IO ()

Eq (Nounce ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

(==) :: Nounce ChaCha20 -> Nounce ChaCha20 -> Bool #

(/=) :: Nounce ChaCha20 -> Nounce ChaCha20 -> Bool #

Show (Nounce ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

showsPrec :: Int -> Nounce ChaCha20 -> ShowS #

show :: Nounce ChaCha20 -> String #

showList :: [Nounce ChaCha20] -> ShowS #

Show (Nounce XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

showsPrec :: Int -> Nounce XChaCha20 -> ShowS #

show :: Nounce XChaCha20 -> String #

showList :: [Nounce XChaCha20] -> ShowS #

IsString (Nounce ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

fromString :: String -> Nounce ChaCha20 #

IsString (Nounce XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

fromString :: String -> Nounce XChaCha20 #

Storable (Nounce ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

sizeOf :: Nounce ChaCha20 -> Int #

alignment :: Nounce ChaCha20 -> Int #

peekElemOff :: Ptr (Nounce ChaCha20) -> Int -> IO (Nounce ChaCha20) #

pokeElemOff :: Ptr (Nounce ChaCha20) -> Int -> Nounce ChaCha20 -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Nounce ChaCha20) #

pokeByteOff :: Ptr b -> Int -> Nounce ChaCha20 -> IO () #

peek :: Ptr (Nounce ChaCha20) -> IO (Nounce ChaCha20) #

poke :: Ptr (Nounce ChaCha20) -> Nounce ChaCha20 -> IO () #

Storable (Nounce XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

sizeOf :: Nounce XChaCha20 -> Int #

alignment :: Nounce XChaCha20 -> Int #

peekElemOff :: Ptr (Nounce XChaCha20) -> Int -> IO (Nounce XChaCha20) #

pokeElemOff :: Ptr (Nounce XChaCha20) -> Int -> Nounce XChaCha20 -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Nounce XChaCha20) #

pokeByteOff :: Ptr b -> Int -> Nounce XChaCha20 -> IO () #

peek :: Ptr (Nounce XChaCha20) -> IO (Nounce XChaCha20) #

poke :: Ptr (Nounce XChaCha20) -> Nounce XChaCha20 -> IO () #

Encodable (Nounce ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Encodable (Nounce XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

EndianStore (Nounce ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

store :: Ptr (Nounce ChaCha20) -> Nounce ChaCha20 -> IO ()

load :: Ptr (Nounce ChaCha20) -> IO (Nounce ChaCha20)

adjustEndian :: Ptr (Nounce ChaCha20) -> Int -> IO ()

EndianStore (Nounce XChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

store :: Ptr (Nounce XChaCha20) -> Nounce XChaCha20 -> IO ()

load :: Ptr (Nounce XChaCha20) -> IO (Nounce XChaCha20)

adjustEndian :: Ptr (Nounce XChaCha20) -> Int -> IO ()

Equality (Nounce ChaCha20) 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Methods

eq :: Nounce ChaCha20 -> Nounce ChaCha20 -> Result

Random (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Random

Methods

random :: RandomState -> IO (Nounce ChaCha20) Source #

Random (Nounce XChaCha20) Source # 
Instance details

Defined in Raaz.Random

Methods

random :: RandomState -> IO (Nounce XChaCha20) Source #

RandomStorable (Nounce ChaCha20) Source # 
Instance details

Defined in Raaz.Random

Methods

fillRandomElements :: Int -> Ptr (Nounce ChaCha20) -> RandomState -> IO () Source #

RandomStorable (Nounce XChaCha20) Source # 
Instance details

Defined in Raaz.Random

Methods

fillRandomElements :: Int -> Ptr (Nounce XChaCha20) -> RandomState -> IO () Source #

newtype Nounce ChaCha20 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Nounce ChaCha20 = Nounce (Tuple 3 WORD)
newtype Nounce XChaCha20 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

newtype Nounce XChaCha20 = XNounce (Tuple 6 WORD)

withMemory :: Memory mem => (mem -> IO a) -> IO a #

withSecureMemory :: Memory mem => (mem -> IO a) -> IO a #

Library information.

version :: Version Source #

Raaz library version number.