lazy-hash-0.1.0.0: Identifiers for not-yet-computed values

Copyright(c) Justus Sagemüller 2017
LicenseGPL v3
Maintainer(@) jsagemue $ uni-koeln.de
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.LazyHash.Class

Description

 

Synopsis

Documentation

class Hash' h where Source #

Minimal complete definition

zeroHash, distinguisher, defaultSalt, combine

Methods

zeroHash :: h Source #

distinguisher :: h Source #

defaultSalt :: h Source #

combine :: h -> h -> h Source #

Instances

Hash' Int Source # 

Methods

zeroHash :: Int Source #

distinguisher :: Int Source #

defaultSalt :: Int Source #

combine :: Int -> Int -> Int Source #

class Hash' h => Hashable h a where Source #

Minimal complete definition

(#)

Methods

(#) :: h -> a -> h infixl 6 Source #

Aka hashWithSalt.

hash :: a -> h Source #

Instances

Hashable Int Bool Source # 

Methods

(#) :: Int -> Bool -> Int Source #

hash :: Bool -> Int Source #

Hashable Int Char Source # 

Methods

(#) :: Int -> Char -> Int Source #

hash :: Char -> Int Source #

Hashable Int Double Source # 

Methods

(#) :: Int -> Double -> Int Source #

hash :: Double -> Int Source #

Hashable Int Float Source # 

Methods

(#) :: Int -> Float -> Int Source #

hash :: Float -> Int Source #

Hashable Int Int Source # 

Methods

(#) :: Int -> Int -> Int Source #

hash :: Int -> Int Source #

Hashable Int Integer Source # 

Methods

(#) :: Int -> Integer -> Int Source #

hash :: Integer -> Int Source #

Hashable Int () Source # 

Methods

(#) :: Int -> () -> Int Source #

hash :: () -> Int Source #

Hashable Int Void Source # 

Methods

(#) :: Int -> Void -> Int Source #

hash :: Void -> Int Source #

Hashable Int TypeRep Source # 

Methods

(#) :: Int -> TypeRep -> Int Source #

hash :: TypeRep -> Int Source #

Hashable h a => Hashable h (Maybe a) Source # 

Methods

(#) :: h -> Maybe a -> h Source #

hash :: Maybe a -> h Source #

Hashable h a => Hashable h [a] Source # 

Methods

(#) :: h -> [a] -> h Source #

hash :: [a] -> h Source #

Hash h => Hashable h (Prehashed h a) Source # 

Methods

(#) :: h -> Prehashed h a -> h Source #

hash :: Prehashed h a -> h Source #

(Hashable h a, Hashable h b) => Hashable h (Either a b) Source # 

Methods

(#) :: h -> Either a b -> h Source #

hash :: Either a b -> h Source #

(Hashable h a, Hashable h b) => Hashable h (a, b) Source # 

Methods

(#) :: h -> (a, b) -> h Source #

hash :: (a, b) -> h Source #

Hash h => Hashable h (LazilyHashableFunction h a b) Source # 

Methods

(#) :: h -> LazilyHashableFunction h a b -> h Source #

hash :: LazilyHashableFunction h a b -> h Source #

data Prehashed h a Source #

Constructors

Prehashed 

Fields

Instances

Hash h => Hashable h (Prehashed h a) Source # 

Methods

(#) :: h -> Prehashed h a -> h Source #

hash :: Prehashed h a -> h Source #

(Read a, Hashable h a) => Read (Prehashed h a) Source # 

Methods

readsPrec :: Int -> ReadS (Prehashed h a)

readList :: ReadS [Prehashed h a]

readPrec :: ReadPrec (Prehashed h a)

readListPrec :: ReadPrec [Prehashed h a]

type Diff (Prehashed h x) # 
type Diff (Prehashed h x) = Prehashed h (Diff x)
type Scalar (Prehashed h v) # 
type Scalar (Prehashed h v) = Prehashed h (Scalar v)

type Hash h = (Hashable h h, Hashable h Char, Hashable h (), Hashable h Void, Hashable h TypeRep, Num h) Source #

shash :: QuasiQuoter Source #

Compute the hash of a string at compile-time.

fundamental :: QuasiQuoter Source #

Transform an ordinary value into a pre-hashed one. This hashes the source code contained in the quasi quote, making the assumption that the behaviour of anything invoked therein will never change.

Applying this to anything but named, fixed-predefined values (standard library functions etc.) is probably a bad idea.

fundamental' :: QuasiQuoter Source #

fundamental for single-argument functions (yields a LazilyHashableFunction instead of a Prehashed).

(<#>) :: Hash h => Prehashed h (a -> b) -> Prehashed h a -> Prehashed h b infixl 4 Source #

Analogous to <$>: apply a hash-supported function to a hash-supported value.

liftPH2 :: Hash h => Prehashed h (a -> b -> c) -> Prehashed h a -> Prehashed h b -> Prehashed h c Source #