| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Data.Digest.Pure.SHA
Contents
Description
Pure implementations of the SHA suite of hash functions. The implementation is basically an unoptimized translation of FIPS 180-2 into Haskell. If you're looking for performance, you probably won't find it here.
Synopsis
- data Digest t
- data SHA1State
- data SHA256State
- data SHA512State
- showDigest :: Digest t -> String
- integerDigest :: Digest t -> Integer
- bytestringDigest :: Digest t -> ByteString
- sha1 :: ByteString -> Digest SHA1State
- sha224 :: ByteString -> Digest SHA256State
- sha256 :: ByteString -> Digest SHA256State
- sha384 :: ByteString -> Digest SHA512State
- sha512 :: ByteString -> Digest SHA512State
- sha1Incremental :: Decoder SHA1State
- completeSha1Incremental :: Decoder SHA1State -> Int -> Digest SHA1State
- sha224Incremental :: Decoder SHA256State
- completeSha224Incremental :: Decoder SHA256State -> Int -> Digest SHA256State
- sha256Incremental :: Decoder SHA256State
- completeSha256Incremental :: Decoder SHA256State -> Int -> Digest SHA256State
- sha384Incremental :: Decoder SHA512State
- completeSha384Incremental :: Decoder SHA512State -> Int -> Digest SHA512State
- sha512Incremental :: Decoder SHA512State
- completeSha512Incremental :: Decoder SHA512State -> Int -> Digest SHA512State
- hmacSha1 :: ByteString -> ByteString -> Digest SHA1State
- hmacSha224 :: ByteString -> ByteString -> Digest SHA256State
- hmacSha256 :: ByteString -> ByteString -> Digest SHA256State
- hmacSha384 :: ByteString -> ByteString -> Digest SHA512State
- hmacSha512 :: ByteString -> ByteString -> Digest SHA512State
- toBigEndianSBS :: (Integral a, Bits a) => Int -> a -> ByteString
- fromBigEndianSBS :: (Integral a, Bits a) => ByteString -> a
- calc_k :: Word64 -> Word64 -> Word64 -> Word64
- padSHA1 :: ByteString -> ByteString
- padSHA512 :: ByteString -> ByteString
- padSHA1Chunks :: Int -> [ByteString]
- padSHA512Chunks :: Int -> [ByteString]
Digest and related functions
An abstract datatype for digests.
Instances
| Eq (Digest t) Source # | |
| Ord (Digest t) Source # | |
| Defined in Data.Digest.Pure.SHA | |
| Show (Digest t) Source # | |
| Binary (Digest SHA512State) Source # | |
| Defined in Data.Digest.Pure.SHA Methods put :: Digest SHA512State -> Put # get :: Get (Digest SHA512State) # putList :: [Digest SHA512State] -> Put # | |
| Binary (Digest SHA256State) Source # | |
| Defined in Data.Digest.Pure.SHA Methods put :: Digest SHA256State -> Put # get :: Get (Digest SHA256State) # putList :: [Digest SHA256State] -> Put # | |
| Binary (Digest SHA1State) Source # | |
data SHA256State Source #
Instances
| Binary SHA256State Source # | |
| Defined in Data.Digest.Pure.SHA | |
| Binary (Digest SHA256State) Source # | |
| Defined in Data.Digest.Pure.SHA Methods put :: Digest SHA256State -> Put # get :: Get (Digest SHA256State) # putList :: [Digest SHA256State] -> Put # | |
data SHA512State Source #
Instances
| Binary SHA512State Source # | |
| Defined in Data.Digest.Pure.SHA | |
| Binary (Digest SHA512State) Source # | |
| Defined in Data.Digest.Pure.SHA Methods put :: Digest SHA512State -> Put # get :: Get (Digest SHA512State) # putList :: [Digest SHA512State] -> Put # | |
showDigest :: Digest t -> String Source #
Convert a digest to a string. The digest is rendered as fixed with hexadecimal number.
integerDigest :: Digest t -> Integer Source #
Convert a digest to an Integer.
bytestringDigest :: Digest t -> ByteString Source #
Convert a digest to a ByteString.
Calculating hashes
sha1 :: ByteString -> Digest SHA1State Source #
Compute the SHA-1 hash of the given ByteString. The output is guaranteed to be exactly 160 bits, or 20 bytes, long. This is a good default for programs that need a good, but not necessarily hyper-secure, hash function.
sha224 :: ByteString -> Digest SHA256State Source #
Compute the SHA-224 hash of the given ByteString. Note that SHA-224 and SHA-384 differ only slightly from SHA-256 and SHA-512, and use truncated versions of the resulting hashes. So using 224/384 may not, in fact, save you very much ...
sha256 :: ByteString -> Digest SHA256State Source #
Compute the SHA-256 hash of the given ByteString. The output is guaranteed to be exactly 256 bits, or 32 bytes, long. If your security requirements are pretty serious, this is a good choice. For truly significant security concerns, however, you might try one of the bigger options.
sha384 :: ByteString -> Digest SHA512State Source #
Compute the SHA-384 hash of the given ByteString. Yup, you guessed it, the output will be exactly 384 bits, or 48 bytes, long.
sha512 :: ByteString -> Digest SHA512State Source #
For those for whom only the biggest hashes will do, this computes the SHA-512 hash of the given ByteString. The output will be 64 bytes, or 512 bits, long.
sha1Incremental :: Decoder SHA1State Source #
Similar to sha1 but use an incremental interface. When the decoder has
 been completely fed, completeSha1Incremental must be used so it can
 finish successfully.
sha224Incremental :: Decoder SHA256State Source #
Similar to sha224 but use an incremental interface. When the decoder has
 been completely fed, completeSha224Incremental must be used so it can
 finish successfully.
sha256Incremental :: Decoder SHA256State Source #
Similar to sha256 but use an incremental interface. When the decoder has
 been completely fed, completeSha256Incremental must be used so it can
 finish successfully.
sha384Incremental :: Decoder SHA512State Source #
Similar to sha384 but use an incremental interface. When the decoder has
 been completely fed, completeSha384Incremental must be used so it can
 finish successfully.
sha512Incremental :: Decoder SHA512State Source #
Similar to sha512 but use an incremental interface. When the decoder has
 been completely fed, completeSha512Incremental must be used so it can
 finish successfully.
Calculating message authentication codes (MACs)
Arguments
| :: ByteString | secret key | 
| -> ByteString | message | 
| -> Digest SHA1State | SHA-1 MAC | 
Compute an HMAC using SHA-1.
Arguments
| :: ByteString | secret key | 
| -> ByteString | message | 
| -> Digest SHA256State | SHA-224 MAC | 
Compute an HMAC using SHA-224.
Arguments
| :: ByteString | secret key | 
| -> ByteString | message | 
| -> Digest SHA256State | SHA-256 MAC | 
Compute an HMAC using SHA-256.
Arguments
| :: ByteString | secret key | 
| -> ByteString | message | 
| -> Digest SHA512State | SHA-384 MAC | 
Compute an HMAC using SHA-384.
Arguments
| :: ByteString | secret key | 
| -> ByteString | message | 
| -> Digest SHA512State | SHA-512 MAC | 
Compute an HMAC using SHA-512.
Internal routines included for testing
toBigEndianSBS :: (Integral a, Bits a) => Int -> a -> ByteString Source #
fromBigEndianSBS :: (Integral a, Bits a) => ByteString -> a Source #
padSHA1 :: ByteString -> ByteString Source #
padSHA512 :: ByteString -> ByteString Source #
padSHA1Chunks :: Int -> [ByteString] Source #
padSHA512Chunks :: Int -> [ByteString] Source #