Copyright | (c) Piyush P Kurur 2016 |
---|---|
License | Apache-2.0 OR BSD-3-Clause |
Maintainer | Piyush P Kurur <ppk@iitpkd.ac.in> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- module Raaz.Digest
- module Raaz.Auth
- module Raaz.AuthEncrypt
- module Raaz.Random
- data family Key p
- data family Nounce p
- withMemory :: Memory mem => (mem -> IO a) -> IO a
- withSecureMemory :: Memory mem => (mem -> IO a) -> IO a
- version :: Version
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 aBlake2b
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
andwithSecureMemory
. These combinators take any IO action that expects a memory element (captured by the classMemory
) 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.Digest
module Raaz.Auth
module Raaz.AuthEncrypt
module Raaz.Random
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
- 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. - Timing safe comparison will get compromised if one compares the encodings (bytestring) instead of the types themselves
Core types and operations of raaz
Instances
Initialisable AEADMem (Key Cipher) | |
Defined in Interface initialise :: Key Cipher -> AEADMem -> IO () | |
Initialisable ChaCha20Mem (Key ChaCha20) | |
Defined in Raaz.Primitive.ChaCha20.Internal initialise :: Key ChaCha20 -> ChaCha20Mem -> IO () | |
Initialisable Internals (Key (Keyed Prim)) | |
Defined in Mac.Implementation initialise :: Key (Keyed Prim) -> Internals -> IO () | |
Initialisable Internals (Key XChaCha20) | |
Defined in XChaCha20.Implementation initialise :: Key XChaCha20 -> Internals -> IO () | |
IsString (Key ChaCha20) | |
Defined in Raaz.Primitive.ChaCha20.Internal fromString :: String -> Key ChaCha20 # | |
IsString (Key XChaCha20) | |
Defined in Raaz.Primitive.ChaCha20.Internal fromString :: String -> Key XChaCha20 # | |
IsString (Key (Keyed prim)) | |
Defined in Raaz.Primitive.Keyed.Internal fromString :: String -> Key (Keyed prim) # | |
Storable (Key ChaCha20) | |
Defined in Raaz.Primitive.ChaCha20.Internal 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 () # | |
Storable (Key XChaCha20) | |
Defined in Raaz.Primitive.ChaCha20.Internal 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 () # | |
Show (Key ChaCha20) | |
Show (Key XChaCha20) | |
Show (Key (Keyed prim)) | |
Show (Key Poly1305) | |
Eq (Key ChaCha20) | |
Random (Key ChaCha20) Source # | |
Defined in Raaz.Random | |
Random (Key XChaCha20) Source # | |
Defined in Raaz.Random | |
Storable prim => Random (Key (Keyed prim)) Source # | |
Defined in Raaz.Random | |
RandomStorable (Key ChaCha20) Source # | |
Defined in Raaz.Random fillRandomElements :: Int -> Ptr (Key ChaCha20) -> RandomState -> IO () Source # | |
RandomStorable (Key XChaCha20) Source # | |
Defined in Raaz.Random fillRandomElements :: Int -> Ptr (Key XChaCha20) -> RandomState -> IO () Source # | |
Encodable (Key ChaCha20) | |
Defined in Raaz.Primitive.ChaCha20.Internal toByteString :: Key ChaCha20 -> ByteString fromByteString :: ByteString -> Maybe (Key ChaCha20) unsafeFromByteString :: ByteString -> Key ChaCha20 | |
Encodable (Key XChaCha20) | |
Defined in Raaz.Primitive.ChaCha20.Internal toByteString :: Key XChaCha20 -> ByteString fromByteString :: ByteString -> Maybe (Key XChaCha20) unsafeFromByteString :: ByteString -> Key XChaCha20 | |
Encodable (Key (Keyed prim)) | |
Defined in Raaz.Primitive.Keyed.Internal toByteString :: Key (Keyed prim) -> ByteString fromByteString :: ByteString -> Maybe (Key (Keyed prim)) unsafeFromByteString :: ByteString -> Key (Keyed prim) | |
EndianStore (Key ChaCha20) | |
EndianStore (Key XChaCha20) | |
Equality (Key ChaCha20) | |
Defined in Raaz.Primitive.ChaCha20.Internal | |
Initialisable (MemoryCell (Key ChaCha20)) (Key XChaCha20) | |
Defined in Raaz.Primitive.ChaCha20.Internal initialise :: Key XChaCha20 -> MemoryCell (Key ChaCha20) -> IO () | |
newtype Key ChaCha20 | |
Defined in Raaz.Primitive.ChaCha20.Internal | |
newtype Key XChaCha20 | |
Defined in Raaz.Primitive.ChaCha20.Internal | |
data Key Poly1305 | |
Defined in Raaz.Primitive.Poly1305.Internal | |
newtype Key (Keyed prim) | |
Defined in Raaz.Primitive.Keyed.Internal |
Instances
withMemory :: Memory mem => (mem -> IO a) -> IO a #
withSecureMemory :: Memory mem => (mem -> IO a) -> IO a #