pantry-0.1.1.1: Content addressable Haskell package management

Safe HaskellNone
LanguageHaskell2010

Pantry.SHA256

Contents

Description

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 representats 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

Types

data SHA256 Source #

A SHA256 hash, stored in a static size for more efficient memory representation.

Since: 0.1.0.0

Instances
Eq SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

(==) :: SHA256 -> SHA256 -> Bool #

(/=) :: SHA256 -> SHA256 -> Bool #

Data SHA256 Source # 
Instance details

Defined in Pantry.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 #

Ord SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Show SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Generic SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Associated Types

type Rep SHA256 :: Type -> Type #

Methods

from :: SHA256 -> Rep SHA256 x #

to :: Rep SHA256 x -> SHA256 #

NFData SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

rnf :: SHA256 -> () #

Hashable SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Methods

hashWithSalt :: Int -> SHA256 -> Int #

hash :: SHA256 -> Int #

ToJSON SHA256 Source # 
Instance details

Defined in Pantry.SHA256

FromJSON SHA256 Source # 
Instance details

Defined in Pantry.SHA256

PersistFieldSql SHA256 Source # 
Instance details

Defined in Pantry.SHA256

PersistField SHA256 Source # 
Instance details

Defined in Pantry.SHA256

Display SHA256 Source # 
Instance details

Defined in Pantry.SHA256

type Rep SHA256 Source # 
Instance details

Defined in Pantry.SHA256

type Rep SHA256 = D1 (MetaData "SHA256" "Pantry.SHA256" "pantry-0.1.1.1-5a9ZoDfWeOpAuTQX9rwyGx" True) (C1 (MetaCons "SHA256" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bytes32)))

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

fromHexText :: Text -> Either SHA256Exception SHA256 Source #

Convert a base16-encoded Text value containing a hash into a SHA256.

Since: 0.1.0.0

fromHexBytes :: ByteString -> Either SHA256Exception SHA256 Source #

Convert a base16-encoded ByteString value containing a hash into a SHA256.

Since: 0.1.0.0

fromDigest :: Digest SHA256 -> SHA256 Source #

Convert a Digest 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

toRaw :: SHA256 -> ByteString Source #

Convert a SHA256 into a raw binary representation.

Since: 0.1.0.0