fixplate-0.1.8: Uniplate-style generic traversals for optionally annotated fixed-point types.

Safe HaskellSafe
LanguageHaskell2010

Data.Generics.Fixplate.Hash

Contents

Description

Generic hashing on trees. We recursively compute hashes of all subtrees, giving fast inequality testing, and a fast, but meaningless (more-or-less random) ordering on the set of trees (so that we can put them into Map-s).

The way it works is that when we compute the hash of a node, we use the hashes of the children directly; this way, you can also incrementally build up a hashed tree.

Synopsis

Hashed tree type

data HashAnn hash f a Source #

Hash annotation (question: should the Hash field be strict? everything else in the library is lazy...)

This is custom datatype instead of reusing Ann because of the different Eq/Ord instances we need.

Constructors

HashAnn hash (f a) 
Instances
Functor f => Functor (HashAnn hash f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Hash

Methods

fmap :: (a -> b) -> HashAnn hash f a -> HashAnn hash f b #

(<$) :: a -> HashAnn hash f b -> HashAnn hash f a #

Foldable f => Foldable (HashAnn hash f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Hash

Methods

fold :: Monoid m => HashAnn hash f m -> m #

foldMap :: Monoid m => (a -> m) -> HashAnn hash f a -> m #

foldr :: (a -> b -> b) -> b -> HashAnn hash f a -> b #

foldr' :: (a -> b -> b) -> b -> HashAnn hash f a -> b #

foldl :: (b -> a -> b) -> b -> HashAnn hash f a -> b #

foldl' :: (b -> a -> b) -> b -> HashAnn hash f a -> b #

foldr1 :: (a -> a -> a) -> HashAnn hash f a -> a #

foldl1 :: (a -> a -> a) -> HashAnn hash f a -> a #

toList :: HashAnn hash f a -> [a] #

null :: HashAnn hash f a -> Bool #

length :: HashAnn hash f a -> Int #

elem :: Eq a => a -> HashAnn hash f a -> Bool #

maximum :: Ord a => HashAnn hash f a -> a #

minimum :: Ord a => HashAnn hash f a -> a #

sum :: Num a => HashAnn hash f a -> a #

product :: Num a => HashAnn hash f a -> a #

Traversable f => Traversable (HashAnn hash f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Hash

Methods

traverse :: Applicative f0 => (a -> f0 b) -> HashAnn hash f a -> f0 (HashAnn hash f b) #

sequenceA :: Applicative f0 => HashAnn hash f (f0 a) -> f0 (HashAnn hash f a) #

mapM :: Monad m => (a -> m b) -> HashAnn hash f a -> m (HashAnn hash f b) #

sequence :: Monad m => HashAnn hash f (m a) -> m (HashAnn hash f a) #

(ShowF f, Show hash) => ShowF (HashAnn hash f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Hash

Methods

showsPrecF :: Show a => Int -> HashAnn hash f a -> ShowS Source #

(Ord hash, OrdF f) => OrdF (HashAnn hash f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Hash

Methods

compareF :: Ord a => HashAnn hash f a -> HashAnn hash f a -> Ordering Source #

(Eq hash, EqF f) => EqF (HashAnn hash f) Source # 
Instance details

Defined in Data.Generics.Fixplate.Hash

Methods

equalF :: Eq a => HashAnn hash f a -> HashAnn hash f a -> Bool Source #

(Show hash, Show (f a)) => Show (HashAnn hash f a) Source # 
Instance details

Defined in Data.Generics.Fixplate.Hash

Methods

showsPrec :: Int -> HashAnn hash f a -> ShowS #

show :: HashAnn hash f a -> String #

showList :: [HashAnn hash f a] -> ShowS #

getHash :: HashAnn hash f a -> hash Source #

unHashAnn :: HashAnn hash f a -> f a Source #

type HashMu hash f = Mu (HashAnn hash f) Source #

A tree annotated with hashes of all subtrees. This gives us fast inequality testing, and fast (but meaningless!) ordering for Map-s.

topHash :: HashMu hash f -> hash Source #

The hash of the complete tree.

forgetHash :: Functor f => HashMu hash f -> Mu f Source #

Interface to the user's hash functions

data HashValue hash Source #

A concrete hash implementation. We don't use type classes since

  • a hash type class does not belong to this library;
  • we don't want to restrict the user's design space

Thus we simulate type classes with record types.

Constructors

HashValue 

Fields

  • _emptyHash :: hash

    the hash of an empty byte sequence

  • _hashChar :: Char -> hash -> hash

    digest a (unicode) character

  • _hashHash :: hash -> hash -> hash

    digest a hash value

Hashing tres

hashTree :: (Foldable f, Functor f, ShowF f) => HashValue hash -> Mu f -> HashMu hash f Source #

This function uses the ShowF instance to compute the hash of a node; this way you always have a working version without writing any additional code.

However, you can also supply your own hash implementation (which can be more efficient, for example), if you use hashTreeWith instead.

hashTreeWith :: (Foldable f, Functor f) => HashValue hash -> (f Hole -> hash -> hash) -> Mu f -> HashMu hash f Source #

hashNode :: (Foldable f, Functor f, ShowF f) => HashValue hash -> f (HashMu hash f) -> HashMu hash f Source #

Build a hashed node from the children.

hashNodeWith :: (Foldable f, Functor f) => HashValue hash -> (f Hole -> hash -> hash) -> f (HashMu hash f) -> HashMu hash f Source #