hnix-store-core-0.8.0.0: Core types used for interacting with the Nix store.
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.Nix.Hash

Description

 
Synopsis

Documentation

data HashAlgo :: Type -> Type where Source #

Instances

Instances details
GCompare HashAlgo Source # 
Instance details

Defined in System.Nix.Hash

Methods

gcompare :: forall (a :: k) (b :: k). HashAlgo a -> HashAlgo b -> GOrdering a b #

GEq HashAlgo Source # 
Instance details

Defined in System.Nix.Hash

Methods

geq :: forall (a :: k) (b :: k). HashAlgo a -> HashAlgo b -> Maybe (a :~: b) #

GShow HashAlgo Source # 
Instance details

Defined in System.Nix.Hash

Methods

gshowsPrec :: forall (a :: k). Int -> HashAlgo a -> ShowS #

(c MD5, c SHA1, c SHA256, c SHA512) => Has (c :: Type -> Constraint) HashAlgo Source # 
Instance details

Defined in System.Nix.Hash

Methods

has :: forall (a :: k) r. HashAlgo a -> (c a => r) -> r #

argDict :: forall (a :: k). HashAlgo a -> Dict (c a) #

class HashAlgorithm a => NamedAlgo a where Source #

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

Methods

algoName :: Text Source #

Instances

Instances details
NamedAlgo MD5 Source # 
Instance details

Defined in System.Nix.Hash

Methods

algoName :: Text Source #

NamedAlgo SHA1 Source # 
Instance details

Defined in System.Nix.Hash

Methods

algoName :: Text Source #

NamedAlgo SHA256 Source # 
Instance details

Defined in System.Nix.Hash

Methods

algoName :: Text Source #

NamedAlgo SHA512 Source # 
Instance details

Defined in System.Nix.Hash

Methods

algoName :: Text Source #

algoToText :: forall t. HashAlgo t -> Text Source #

mkNamedDigest Source #

Arguments

:: Text

SRI name

-> Text

base encoded hash

-> Either String (DSum HashAlgo Digest) 

Make DSum HashAlgo Digest based on provided SRI hash name and its encoded form

data BaseEncoding Source #

Constructors to indicate the base encodings

Constructors

NixBase32 
Base16

^ Nix has a special map of Base32 encoding Placed first, since it determines Haskell optimizations of pattern matches, & NixBase seems be the most widely used in Nix.

Base64 

Instances

Instances details
Bounded BaseEncoding Source # 
Instance details

Defined in System.Nix.Base

Enum BaseEncoding Source # 
Instance details

Defined in System.Nix.Base

Generic BaseEncoding Source # 
Instance details

Defined in System.Nix.Base

Associated Types

type Rep BaseEncoding :: Type -> Type #

Show BaseEncoding Source # 
Instance details

Defined in System.Nix.Base

Eq BaseEncoding Source # 
Instance details

Defined in System.Nix.Base

Ord BaseEncoding Source # 
Instance details

Defined in System.Nix.Base

type Rep BaseEncoding Source # 
Instance details

Defined in System.Nix.Base

type Rep BaseEncoding = D1 ('MetaData "BaseEncoding" "System.Nix.Base" "hnix-store-core-0.8.0.0-2YQUX8JlMxk93e1fw1Y66G" 'False) (C1 ('MetaCons "NixBase32" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Base16" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Base64" 'PrefixI 'False) (U1 :: Type -> Type)))

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

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

decodeDigestWith :: HashAlgorithm a => BaseEncoding -> Text -> Either String (Digest a) Source #

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

algoDigestBuilder :: DSum HashAlgo Digest -> Builder Source #

Builder for DSum HashAlgo Digests

digestBuilder :: forall hashAlgo. NamedAlgo hashAlgo => Digest hashAlgo -> Builder Source #

Builder for Digests