Copyright | (c) 2013-2018 Brendan Hay |
---|---|
License | Mozilla Public License, v. 2.0. |
Maintainer | Brendan Hay <brendan.g.hay+amazonka@gmail.com> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Network.AWS.Data.Crypto
Description
Synopsis
- digestToBS :: ByteArrayAccess a => a -> ByteString
- digestToBase :: ByteArrayAccess a => Base -> a -> ByteString
- hmacSHA1 :: (ByteArrayAccess a, ByteArray b) => a -> b -> HMAC SHA1
- hmacSHA256 :: (ByteArrayAccess a, ByteArray b) => a -> b -> HMAC SHA256
- hashSHA256 :: ByteArrayAccess a => a -> Digest SHA256
- hashMD5 :: ByteArrayAccess a => a -> Digest MD5
- hash :: (ByteArrayAccess ba, HashAlgorithm a) => ba -> Digest a
- hashlazy :: HashAlgorithm a => ByteString -> Digest a
- hashInit :: HashAlgorithm a => Context a
- hashUpdate :: (ByteArrayAccess ba, HashAlgorithm a) => Context a -> ba -> Context a
- hashFinalize :: HashAlgorithm a => Context a -> Digest a
- data HMAC a
- data Digest a
- class HashAlgorithm a
- data SHA256 = SHA256
- data MD5 = MD5
- data Base
Conversion
digestToBS :: ByteArrayAccess a => a -> ByteString Source #
digestToBase :: ByteArrayAccess a => Base -> a -> ByteString Source #
Algorithms
hmacSHA1 :: (ByteArrayAccess a, ByteArray b) => a -> b -> HMAC SHA1 Source #
Apply an HMAC sha1 with the given secret to the given value.
hmacSHA256 :: (ByteArrayAccess a, ByteArray b) => a -> b -> HMAC SHA256 Source #
hashSHA256 :: ByteArrayAccess a => a -> Digest SHA256 Source #
Contexts
hash :: (ByteArrayAccess ba, HashAlgorithm a) => ba -> Digest a #
Hash a strict bytestring into a digest.
hashlazy :: HashAlgorithm a => ByteString -> Digest a #
Hash a lazy bytestring into a digest.
hashInit :: HashAlgorithm a => Context a #
Initialize a new context for this hash algorithm
hashUpdate :: (ByteArrayAccess ba, HashAlgorithm a) => Context a -> ba -> Context a #
run hashUpdates on one single bytestring and return the updated context.
hashFinalize :: HashAlgorithm a => Context a -> Digest a #
Finalize a context and return a digest.
Re-exported
Represent an HMAC that is a phantom type with the hash used to produce the mac.
The Eq instance is constant time.
Instances
Eq (HMAC a) | |
ByteArrayAccess (HMAC a) | |
Represent a digest for a given hash algorithm.
This type is an instance of ByteArrayAccess
from package
memory.
Module Data.ByteArray provides many primitives to work with those values
including conversion to other types.
Creating a digest from a bytearray is also possible with function
digestFromByteString
.
class HashAlgorithm a #
Class representing hashing algorithms.
The interface presented here is update in place and lowlevel. the Hash module takes care of hidding the mutable interface properly.
Minimal complete definition
hashBlockSize, hashDigestSize, hashInternalContextSize, hashInternalInit, hashInternalUpdate, hashInternalFinalize
Instances
SHA256 cryptographic hash algorithm
Constructors
SHA256 |
Instances
Data SHA256 | |
Defined in Crypto.Hash.SHA256 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA256 -> c SHA256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA256 # toConstr :: SHA256 -> Constr # dataTypeOf :: SHA256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA256) # gmapT :: (forall b. Data b => b -> b) -> SHA256 -> SHA256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # | |
Show SHA256 | |
HashAlgorithm SHA256 | |
Defined in Crypto.Hash.SHA256 Associated Types type HashBlockSize SHA256 :: Nat # type HashDigestSize SHA256 :: Nat # type HashInternalContextSize SHA256 :: Nat # Methods hashBlockSize :: SHA256 -> Int # hashDigestSize :: SHA256 -> Int # hashInternalContextSize :: SHA256 -> Int # hashInternalInit :: Ptr (Context SHA256) -> IO () # hashInternalUpdate :: Ptr (Context SHA256) -> Ptr Word8 -> Word32 -> IO () # hashInternalFinalize :: Ptr (Context SHA256) -> Ptr (Digest SHA256) -> IO () # | |
type HashInternalContextSize SHA256 | |
Defined in Crypto.Hash.SHA256 | |
type HashDigestSize SHA256 | |
Defined in Crypto.Hash.SHA256 | |
type HashBlockSize SHA256 | |
Defined in Crypto.Hash.SHA256 |
MD5 cryptographic hash algorithm
Constructors
MD5 |
Instances
Data MD5 | |
Defined in Crypto.Hash.MD5 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MD5 -> c MD5 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MD5 # dataTypeOf :: MD5 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MD5) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MD5) # gmapT :: (forall b. Data b => b -> b) -> MD5 -> MD5 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MD5 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MD5 -> r # gmapQ :: (forall d. Data d => d -> u) -> MD5 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MD5 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MD5 -> m MD5 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MD5 -> m MD5 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MD5 -> m MD5 # | |
Show MD5 | |
HashAlgorithm MD5 | |
Defined in Crypto.Hash.MD5 Associated Types type HashBlockSize MD5 :: Nat # type HashDigestSize MD5 :: Nat # type HashInternalContextSize MD5 :: Nat # | |
type HashInternalContextSize MD5 | |
Defined in Crypto.Hash.MD5 | |
type HashDigestSize MD5 | |
Defined in Crypto.Hash.MD5 | |
type HashBlockSize MD5 | |
Defined in Crypto.Hash.MD5 |
The different bases that can be used.
See RFC4648 for details. In particular, Base64 can be standard or URL-safe. URL-safe encoding is often used in other specifications without padding characters.
Examples
A quick example to show the differences:
>>>
let input = "Is 3 > 2?" :: ByteString
>>>
let convertedTo base = convertToBase base input :: ByteString
>>>
convertedTo Base16
"49732033203e20323f">>>
convertedTo Base32
"JFZSAMZAHYQDEPY=">>>
convertedTo Base64
"SXMgMyA+IDI/">>>
convertedTo Base64URLUnpadded
"SXMgMyA-IDI_">>>
convertedTo Base64OpenBSD
"QVKeKw.8GBG9"
Constructors
Base16 | similar to hexadecimal |
Base32 | |
Base64 | standard Base64 |
Base64URLUnpadded | unpadded URL-safe Base64 |
Base64OpenBSD | Base64 as used in OpenBSD password encoding (such as bcrypt) |