tie-knot-0.2: "Ties the knot" on a given set of structures that reference each other by keys.

Safe HaskellNone

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 recursion-schemes 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 the embedding function.
 data Loves t = Loves { _name :: String, _loves :: [t] }
 type instance Base Person = Loves
 instance Unfoldable Person where
   embed ~(Loves n ps)    = Person n ps

 -- The easisest way to get 'Foldable' + 'Functor' is to implement
 -- 'Traversable' and then just use the default implementations.
 instance T.Traversable Loves where
     traverse f (Loves n ns) = Loves n <$> T.traverse f ns

 instance Functor Loves where
     fmap = T.fmapDefault
 instance F.Foldable Loves 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"]
           ]

Synopsis

Documentation

tie :: (Ord k, Foldable (Base v), Unfoldable v) => RefMap k (Base v) -> Either (TieError k) (Map k v)Source

Checks consistency by calling isConsistent and then and ties the knot using tie'.

tie' :: (Ord k, Unfoldable v) => RefMap k (Base v) -> Map k vSource

Ties the knot without checking consistency. If the references are inconsistent, an exception is raised.

isConsistentSource

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.

data TieError k Source

Possible errors when tying the knot.

Constructors

MissingKey k k

A value with key k1 referenced non-existent key k2.

Instances

Eq k => Eq (TieError k) 
(Eq (TieError k), Ord k) => Ord (TieError k) 
Show k => Show (TieError k) 

type family Base t :: * -> *

class Functor (Base t) => Unfoldable t where

Methods

embed :: Base t t -> t

Instances

Functor (Base [a]) => Unfoldable [a] 
Functor (Base (Maybe a)) => Unfoldable (Maybe a) 
(Functor (Base (Fix f)), Functor f) => Unfoldable (Fix f) 
(Functor (Base (Mu f)), Functor f) => Unfoldable (Mu f) 
(Functor (Base (Nu f)), Functor f) => Unfoldable (Nu f) 
Functor (Base (Either a b)) => Unfoldable (Either a b) 

embed :: Unfoldable t => Base t t -> t