Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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
- data HashAnn hash f a = HashAnn hash (f a)
- getHash :: HashAnn hash f a -> hash
- unHashAnn :: HashAnn hash f a -> f a
- type HashMu hash f = Mu (HashAnn hash f)
- topHash :: HashMu hash f -> hash
- forgetHash :: Functor f => HashMu hash f -> Mu f
- data HashValue hash = HashValue {
- _emptyHash :: hash
- _hashChar :: Char -> hash -> hash
- _hashHash :: hash -> hash -> hash
- hashTree :: (Foldable f, Functor f, ShowF f) => HashValue hash -> Mu f -> HashMu hash f
- hashTreeWith :: (Foldable f, Functor f) => HashValue hash -> (f Hole -> hash -> hash) -> Mu f -> HashMu hash f
- hashNode :: (Foldable f, Functor f, ShowF f) => HashValue hash -> f (HashMu hash f) -> HashMu hash f
- hashNodeWith :: (Foldable f, Functor f) => HashValue hash -> (f Hole -> hash -> hash) -> f (HashMu hash f) -> HashMu hash f
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.
HashAnn hash (f a) |
Instances
Functor f => Functor (HashAnn hash f) Source # | |
Foldable f => Foldable (HashAnn hash f) Source # | |
Defined in Data.Generics.Fixplate.Hash 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 # | |
Traversable f => Traversable (HashAnn hash f) Source # | |
Defined in Data.Generics.Fixplate.Hash 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 # | |
Defined in Data.Generics.Fixplate.Hash | |
(Ord hash, OrdF f) => OrdF (HashAnn hash f) Source # | |
(Eq hash, EqF f) => EqF (HashAnn hash f) Source # | |
(Show hash, Show (f a)) => Show (HashAnn hash 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.
Interface to the user's hash functions
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.
HashValue | |
|
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 #