hnix-store-core-0.4.2.0: Core effects for interacting with the Nix store.
Safe HaskellNone
LanguageHaskell2010

System.Nix.Hash

Description

 
Synopsis

Documentation

data Digest (a :: HashAlgorithm) Source #

The result of running a HashAlgorithm.

Instances

Instances details
Eq (Digest a) Source # 
Instance details

Defined in System.Nix.Internal.Hash

Methods

(==) :: Digest a -> Digest a -> Bool #

(/=) :: Digest a -> Digest a -> Bool #

Ord (Digest a) Source # 
Instance details

Defined in System.Nix.Internal.Hash

Methods

compare :: Digest a -> Digest a -> Ordering #

(<) :: Digest a -> Digest a -> Bool #

(<=) :: Digest a -> Digest a -> Bool #

(>) :: Digest a -> Digest a -> Bool #

(>=) :: Digest a -> Digest a -> Bool #

max :: Digest a -> Digest a -> Digest a #

min :: Digest a -> Digest a -> Digest a #

Show (Digest a) Source # 
Instance details

Defined in System.Nix.Internal.Hash

Methods

showsPrec :: Int -> Digest a -> ShowS #

show :: Digest a -> String #

showList :: [Digest a] -> ShowS #

Hashable (Digest a) Source # 
Instance details

Defined in System.Nix.Internal.Hash

Methods

hashWithSalt :: Int -> Digest a -> Int #

hash :: Digest a -> Int #

data HashAlgorithm Source #

The universe of supported hash algorithms.

Currently only intended for use at the type level.

Constructors

MD5 
SHA1 
SHA256 
SHA512 
Truncated Nat HashAlgorithm

The hash algorithm obtained by truncating the result of the input HashAlgorithm to the given number of bytes. See truncateDigest for a description of the truncation algorithm.

class ValidAlgo (a :: HashAlgorithm) where Source #

The primitive interface for incremental hashing for a given HashAlgorithm. Every HashAlgorithm should have an instance.

Associated Types

type AlgoCtx a Source #

The incremental state for constructing a hash.

Methods

initialize :: AlgoCtx a Source #

Start building a new hash.

update :: AlgoCtx a -> ByteString -> AlgoCtx a Source #

Append a ByteString to the overall contents to be hashed.

finalize :: AlgoCtx a -> Digest a Source #

Finish hashing and generate the output.

Instances

Instances details
ValidAlgo 'MD5 Source #

Uses Crypto.Hash.MD5 from cryptohash-md5.

Instance details

Defined in System.Nix.Internal.Hash

Associated Types

type AlgoCtx 'MD5 Source #

ValidAlgo 'SHA1 Source #

Uses Crypto.Hash.SHA1 from cryptohash-sha1.

Instance details

Defined in System.Nix.Internal.Hash

Associated Types

type AlgoCtx 'SHA1 Source #

ValidAlgo 'SHA256 Source #

Uses Crypto.Hash.SHA256 from cryptohash-sha256.

Instance details

Defined in System.Nix.Internal.Hash

Associated Types

type AlgoCtx 'SHA256 Source #

ValidAlgo 'SHA512 Source #

Uses Crypto.Hash.SHA512 from cryptohash-sha512.

Instance details

Defined in System.Nix.Internal.Hash

Associated Types

type AlgoCtx 'SHA512 Source #

(ValidAlgo a, KnownNat n) => ValidAlgo ('Truncated n a) Source #

Reuses the underlying ValidAlgo instance, but does a truncateDigest at the end.

Instance details

Defined in System.Nix.Internal.Hash

Associated Types

type AlgoCtx ('Truncated n a) Source #

class ValidAlgo a => NamedAlgo (a :: HashAlgorithm) where Source #

A HashAlgorithm with a canonical name, for serialization purposes (e.g. SRI hashes)

Instances

Instances details
NamedAlgo 'MD5 Source # 
Instance details

Defined in System.Nix.Internal.Hash

NamedAlgo 'SHA1 Source # 
Instance details

Defined in System.Nix.Internal.Hash

NamedAlgo 'SHA256 Source # 
Instance details

Defined in System.Nix.Internal.Hash

NamedAlgo 'SHA512 Source # 
Instance details

Defined in System.Nix.Internal.Hash

data SomeNamedDigest Source #

A digest whose NamedAlgo is not known at compile time.

Constructors

forall a.NamedAlgo a => SomeDigest (Digest a) 

Instances

Instances details
Show SomeNamedDigest Source # 
Instance details

Defined in System.Nix.Internal.Hash

hash :: forall a. ValidAlgo a => ByteString -> Digest a Source #

Hash an entire (strict) ByteString as a single call.

For example: > let d = hash "Hello, sha-256!" :: Digest SHA256 or > :set -XTypeApplications > let d = hash @SHA256 "Hello, sha-256!"

hashLazy :: forall a. ValidAlgo a => ByteString -> Digest a Source #

Hash an entire (lazy) ByteString as a single call.

Use is the same as for hash. This runs in constant space, but forces the entire bytestring.

data BaseEncoding Source #

Constructors to indicate the base encodings

Constructors

Base16 
Base32 
Base64

^ Nix has a special map of Base32 encoding

encodeInBase :: BaseEncoding -> Digest a -> Text Source #

Take BaseEncoding type of the output -> take the Digeest as input -> encode Digest

decodeBase :: BaseEncoding -> Text -> Either String (Digest a) Source #

Take BaseEncoding type of the input -> take the input itself -> decodeBase into Digest