| Safe Haskell | Safe-Inferred |
|---|
Data.Knot
Description
Module for tying the knot on data structures that reference each other by
some kind of keys. The tie function replaces all such references with the actual
value, creating possibly recursive or cyclic data structures.
The module re-exports a part of the fixpoint package.
An example how to construct a structure with circular dependencies:
data Person = Person { name :: String, loves :: [Person] }
-- Define a variant of Person where the recursive type
-- is given as a parameter, and injection/projection functions.
instance Fixpoint Person where
data Pre Person t = Loves { _name :: String, _loves :: [t] }
inject ~(Loves n ps) = Person n ps
project ~(Person n ps) = Loves n ps
-- The easisest way to get 'Foldable' + 'Functor' is to implement
-- 'Traversable' and then just use the default implementations.
instance T.Traversable (Pre Person) where
traverse f (Loves n ns) = Loves n <$> T.traverse f ns
instance Functor (Pre Person) where
fmap = T.fmapDefault
instance F.Foldable (Pre Person) where
foldMap = T.foldMapDefault
-- Let's create a person with cicrular dependencies:
alice :: Person
alice = fromJust . Map.lookup "Alice" .
tie' . Map.fromList . map (\l -> (_name l, l)) $ lst
where
lst = [ Loves "Alice" ["Bob", "cat"]
, Loves "Bob" ["Alice"]
-- you may disagree, but the cat thinks of itself as Person
, Loves "cat" ["cat"]
]
- tie :: (Ord k, Foldable (Pre v), Fixpoint v) => RefMap k (Pre v) -> Either (TieError k) (Map k v)
- tie' :: (Ord k, Fixpoint v) => RefMap k (Pre v) -> Map k v
- isConsistent :: (Ord k, Foldable v, Functor v) => RefMap k v -> Either (TieError k) (RefMap k v)
- type RefMap k v = Map k (v k)
- data TieError k = MissingKey k k
- class Functor (Pre t) => Fixpoint t where
- data family Pre t1 ($a)
- inject :: Fixpoint t => Pre t t -> t
- project :: Fixpoint t => t -> Pre t t
Documentation
tie :: (Ord k, Foldable (Pre v), Fixpoint v) => RefMap k (Pre v) -> Either (TieError k) (Map k v)Source
Checks consistency by calling isConsistent and then and ties the knot using tie'.
tie' :: (Ord k, Fixpoint v) => RefMap k (Pre v) -> Map k vSource
Ties the knot without checking consistency. If the references are inconsistent, an exception is raised.
Arguments
| :: (Ord k, Foldable v, Functor v) | |
| => RefMap k v | The loader to check. |
| -> Either (TieError k) (RefMap k v) | The loader argument or an error. |
Check the loader for consistency, i.e. if all referenced keys
have a corresponding value. Values need to implement Foldable
that traverses over all referenced keys.
type RefMap k v = Map k (v k)Source
Represents a set of data v that reference each other
using keys of type k.
Possible errors when tying the knot.
Constructors
| MissingKey k k | A value with key k1 referenced non-existent key k2. |
class Functor (Pre t) => Fixpoint t where
The class of data types representable by fixpoints.
Associated Types
data Pre t1 ($a)
Methods
Projection from the data type to its underlying functor.
Injection from the underlying functor into the data type.
data family Pre t1 ($a)