Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Provides a data type (SHA256
) for efficient memory representation of a
sha-256 hash value, together with helper functions for converting to and from
that value. This module is intended to be imported qualified as SHA256
.
Some nomenclature:
- Hashing calculates a new hash value from some input.
from
takes a value that represents an existing hash. - Raw means a raw binary representation of the hash value, without any hex encoding.
- Text always uses lower case hex encoding
Since: 0.1.0.0
Synopsis
- data SHA256
- data SHA256Exception
- hashFile :: MonadIO m => FilePath -> m SHA256
- hashBytes :: ByteString -> SHA256
- hashLazyBytes :: LByteString -> SHA256
- sinkHash :: Monad m => ConduitT ByteString o m SHA256
- fromHexText :: Text -> Either SHA256Exception SHA256
- fromHexBytes :: ByteString -> Either SHA256Exception SHA256
- fromDigest :: Digest SHA256 -> SHA256
- fromRaw :: ByteString -> Either SHA256Exception SHA256
- toHexText :: SHA256 -> Text
- toHexBytes :: SHA256 -> ByteString
- toRaw :: SHA256 -> ByteString
Types
A SHA256 hash, stored in a static size for more efficient memory representation.
Since: 0.1.0.0
Instances
FromJSON SHA256 Source # | |
ToJSON SHA256 Source # | |
Defined in Pantry.SHA256 | |
Data SHA256 Source # | |
Defined in Pantry.SHA256 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 :: forall r r'. (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 # | |
Generic SHA256 Source # | |
Show SHA256 Source # | |
NFData SHA256 Source # | |
Defined in Pantry.SHA256 | |
Eq SHA256 Source # | |
Ord SHA256 Source # | |
Hashable SHA256 Source # | |
Defined in Pantry.SHA256 | |
PersistField SHA256 Source # | |
Defined in Pantry.SHA256 toPersistValue :: SHA256 -> PersistValue # | |
PersistFieldSql SHA256 Source # | |
Display SHA256 Source # | |
Defined in Pantry.SHA256 display :: SHA256 -> Utf8Builder # textDisplay :: SHA256 -> Text # | |
type Rep SHA256 Source # | |
Defined in Pantry.SHA256 |
data SHA256Exception Source #
Exceptions which can occur in this module
Since: 0.1.0.0
Instances
Exception SHA256Exception Source # | |
Defined in Pantry.SHA256 | |
Show SHA256Exception Source # | |
Defined in Pantry.SHA256 showsPrec :: Int -> SHA256Exception -> ShowS # show :: SHA256Exception -> String # showList :: [SHA256Exception] -> ShowS # | |
Display SHA256Exception Source # | |
Defined in Pantry.SHA256 display :: SHA256Exception -> Utf8Builder # textDisplay :: SHA256Exception -> Text # |
Hashing
hashFile :: MonadIO m => FilePath -> m SHA256 Source #
Generate a SHA256
value by hashing the contents of a file.
Since: 0.1.0.0
hashBytes :: ByteString -> SHA256 Source #
Generate a SHA256
value by hashing a ByteString
.
Since: 0.1.0.0
hashLazyBytes :: LByteString -> SHA256 Source #
Generate a SHA256
value by hashing a lazy ByteString
.
Since: 0.1.0.0
sinkHash :: Monad m => ConduitT ByteString o m SHA256 Source #
Generate a SHA256
value by hashing the contents of a stream.
Since: 0.1.0.0
Convert from a hash representation
fromHexBytes :: ByteString -> Either SHA256Exception SHA256 Source #
Convert a base16-encoded ByteString
value containing a hash into a
SHA256
.
Since: 0.1.0.0
fromRaw :: ByteString -> Either SHA256Exception SHA256 Source #
Convert a raw representation of a hash into a SHA256
.
Since: 0.1.0.0
Convert to a hash representation
toHexText :: SHA256 -> Text Source #
Convert a SHA256
into a base16-encoded SHA256 hash.
Since: 0.1.0.0
toHexBytes :: SHA256 -> ByteString Source #
Convert a SHA256
into a base16-encoded SHA256 hash.
Since: 0.1.0.0