| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Tree.RoseTrie
Description
A "trie" based on Map where you can store objects o to an arbitrary path
constructed of paths-segments p. The idea of the RoseTrie data structure is that it behaves
exctly like a Map except each individual branch node is labeled with a path segmet,
and can be accessed and altered arbitrarily.
Because of the way similar paths [p] are merged, when you perform a foldr,
mergeWithKey, or traverse operation, you have a choice of how to order the
objects o, with DepthFirst or BreadthFirst. Functions like elems and assocs require an
additional RunRoseTrie parameter to decide the ordering of the objects o.
Therefore, this data type instantiates Foldable only when
it is paired with a RunRoseTrie to determine if the foldr will occur in
DepthFirst or BreadthFirst order.
- newtype RoseTrie p o = RoseTrie (Maybe o, Map p (RoseTrie p o))
- class DataFromRoseTrie d p o where
- fromRoseTrie :: RoseTrie p o -> d
- class DataToRoseTrie d p o where
- toRoseTrie :: d -> RoseTrie p o
- data RunRoseTrie
- data ReduceRoseTrie p o = ReduceRoseTrie {
- reduceRoseTrieBy :: RunRoseTrie
- getReduced :: RoseTrie p o
- roseTrie :: Monad m => Iso m (RoseTrie p o) (Maybe o, Map p (RoseTrie p o))
- empty :: RoseTrie p o
- newRoseTrie :: [RoseTrie p o -> Identity (RoseTrie p o)] -> RoseTrie p o
- leaf :: Monad m => Lens m (RoseTrie p o) (Maybe o)
- branches :: Monad m => Lens m (RoseTrie p o) (Map p (RoseTrie p o))
- node :: (Monad m, Ord p) => [p] -> Lens m (RoseTrie p o) (RoseTrie p o)
- path :: (Monad m, Ord p) => [p] -> Lens m (RoseTrie p o) (Maybe o)
- mergeWithKeyM :: forall m p a b c. (Monad m, Ord p) => RunRoseTrie -> ([p] -> Maybe a -> Maybe b -> m (Maybe c)) -> (RoseTrie p a -> m (RoseTrie p c)) -> (RoseTrie p b -> m (RoseTrie p c)) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p c)
- alter :: Ord p => (Maybe o -> Maybe o) -> [p] -> RoseTrie p o -> RoseTrie p o
- alterM :: (Monad m, Ord p) => (Maybe o -> m (Maybe o)) -> [p] -> RoseTrie p o -> m (RoseTrie p o)
- insertWith :: Ord p => (o -> o -> o) -> [p] -> o -> RoseTrie p o -> RoseTrie p o
- insert :: Ord p => [p] -> o -> RoseTrie p o -> RoseTrie p o
- update :: Ord p => (o -> Maybe o) -> [p] -> RoseTrie p o -> RoseTrie p o
- delete :: Ord p => [p] -> RoseTrie p o -> RoseTrie p o
- fromListWith :: Ord p => (o -> o -> o) -> [([p], o)] -> RoseTrie p o
- fromList :: Ord p => [([p], o)] -> RoseTrie p o
- blankRoseTrie :: Ord p => [[p]] -> RoseTrie p ()
- singleton :: Ord p => [p] -> a -> RoseTrie p a
- lookup :: Ord p => [p] -> RoseTrie p a -> Maybe a
- slowLookup :: Ord b => (p -> b -> Bool) -> [p] -> RoseTrie b a -> [([b], a)]
- slowLookup1 :: Ord b => (p -> b -> Bool) -> [p] -> RoseTrie b a -> Maybe ([b], a)
- assocs :: RunRoseTrie -> RoseTrie p a -> [([p], a)]
- partitions :: (Eq p, Ord p) => RunRoseTrie -> [p] -> RoseTrie p a -> [(([p], [p]), a)]
- partitionsWith :: (Eq p, Ord p) => RunRoseTrie -> (p -> q -> Maybe r) -> [q] -> RoseTrie p a -> [(([r], [q]), a)]
- partitionWithM :: (Eq p, Ord p, Monad m) => RunRoseTrie -> (p -> q -> m (Maybe r)) -> [q] -> RoseTrie p a -> m [(([r], [q]), a)]
- elems :: RunRoseTrie -> RoseTrie p a -> [a]
- size :: RoseTrie p a -> Word64
- leafCount :: RoseTrie p a -> Word64
- branchCount :: RoseTrie p a -> Word64
- null :: RoseTrie p a -> Bool
- mergeWithKey :: Ord p => ([p] -> Maybe a -> Maybe b -> Maybe c) -> (RoseTrie p a -> RoseTrie p c) -> (RoseTrie p b -> RoseTrie p c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
- mergeWithM :: (Monad m, Ord p) => RunRoseTrie -> (Maybe a -> Maybe b -> m (Maybe c)) -> (RoseTrie p a -> m (RoseTrie p c)) -> (RoseTrie p b -> m (RoseTrie p c)) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p c)
- mergeWith :: Ord p => (Maybe a -> Maybe b -> Maybe c) -> (RoseTrie p a -> RoseTrie p c) -> (RoseTrie p b -> RoseTrie p c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
- unionWithKeyM :: (Monad m, Ord p) => RunRoseTrie -> ([p] -> a -> a -> m a) -> RoseTrie p a -> RoseTrie p a -> m (RoseTrie p a)
- unionWithKey :: Ord p => ([p] -> a -> a -> a) -> RoseTrie p a -> RoseTrie p a -> RoseTrie p a
- unionWithM :: (Monad m, Ord p) => RunRoseTrie -> (a -> a -> m a) -> RoseTrie p a -> RoseTrie p a -> m (RoseTrie p a)
- unionWith :: Ord p => (a -> a -> a) -> RoseTrie p a -> RoseTrie p a -> RoseTrie p a
- union :: Ord p => RoseTrie p a -> RoseTrie p a -> RoseTrie p a
- unionsWith :: Ord p => (a -> a -> a) -> [RoseTrie p a] -> RoseTrie p a
- unions :: Ord p => [RoseTrie p a] -> RoseTrie p a
- intersectionWithKeyM :: (Monad m, Ord p) => RunRoseTrie -> ([p] -> a -> b -> m c) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p c)
- intersectionWithKey :: Ord p => ([p] -> a -> b -> c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
- intersectionWithM :: (Monad m, Ord p) => RunRoseTrie -> (a -> b -> m c) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p c)
- intersectionWith :: Ord p => (a -> b -> c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
- intersection :: Ord p => RoseTrie p a -> RoseTrie p b -> RoseTrie p a
- intersectionsWith :: Ord p => (a -> a -> a) -> [RoseTrie p a] -> RoseTrie p a
- intersections :: Ord p => [RoseTrie p a] -> RoseTrie p a
- differenceWithKeyM :: (Monad m, Ord p) => RunRoseTrie -> ([p] -> a -> b -> m (Maybe a)) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p a)
- differenceWithKey :: Ord p => ([p] -> a -> b -> Maybe a) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p a
- differenceWithM :: (Monad m, Ord p) => RunRoseTrie -> (a -> b -> m (Maybe a)) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p a)
- differenceWith :: Ord p => (a -> b -> Maybe a) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p a
- difference :: Ord p => RoseTrie p a -> RoseTrie p b -> RoseTrie p a
- differencesWith :: Ord p => (a -> a -> Maybe a) -> [RoseTrie p a] -> RoseTrie p a
- differences :: Ord p => [RoseTrie p a] -> RoseTrie p a
- productWith :: Ord p => (a -> b -> c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
- product :: (Ord p, Monoid a) => RoseTrie p a -> RoseTrie p a -> RoseTrie p a
- newtype ZipRoseTrie p o = ZipRoseTrie (RoseTrie p o, [(p, RoseTrie p o)])
- zipRoseTrie :: Monad m => Iso m (ZipRoseTrie p o) (RoseTrie p o, [(p, RoseTrie p o)])
- zipperSubRoseTrie :: Monad m => Lens m (ZipRoseTrie p o) (RoseTrie p o)
- zipperHistory :: Monad m => Lens m (ZipRoseTrie p o) [(p, RoseTrie p o)]
- newtype UpdateRoseTrieT p o m a = UpdateRoseTrieT (StateT (ZipRoseTrie p o) m a)
- type UpdateRoseTrie p o a = UpdateRoseTrieT p o Identity a
- runUpdateRoseTrieT :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m a -> RoseTrie p o -> m (a, RoseTrie p o)
- execUpdateRoseTrieT :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m a -> RoseTrie p o -> m (RoseTrie p o)
- evalUpdateRoseTrieT :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m a -> RoseTrie p o -> m a
- goto :: (Functor m, Applicative m, Monad m, Ord p) => [p] -> UpdateRoseTrieT p o m ()
- back :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m Bool
- atTop :: (Functor m, Applicative m, Monad m) => UpdateRoseTrieT p o m Bool
- home :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m ()
- getPath :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m [p]
- data RoseTrieDiff a b
- = LeftOnly a
- | RightOnly b
- | RoseTrieDiff a b
- treeDiffWithM :: forall m p a b. (Monad m, Ord p) => RunRoseTrie -> ([p] -> a -> b -> m Bool) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p (RoseTrieDiff a b))
- treeDiffWith :: Ord p => ([p] -> a -> b -> Bool) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p (RoseTrieDiff a b)
- treeDiffM :: (Monad m, Eq a, Ord p) => RunRoseTrie -> RoseTrie p a -> RoseTrie p a -> m (RoseTrie p (RoseTrieDiff a a))
- treeDiff :: (Eq a, Ord p) => RoseTrie p a -> RoseTrie p a -> RoseTrie p (RoseTrieDiff a a)
Documentation
newtype RoseTrie p o
A RoseTrie is just a newtype around a pair of two elements forming a node, the first being the
leaf of the node, and the second being the branches of the node. The leaf may or may not exist,
so it is wrapped in a Maybe data structure.
When you associate an object o at a path [p], a walk is performed, with each segment of the
path [p] selecting a branch that contains another sub-node. When the path [p] is empty, the
walk stops and the object o is placed into the current sub-node.
Instances
| Functor (RoseTrie p) | |
| (Ord p, Monoid o) => Monoid (Sum (RoseTrie p o)) | |
| (Ord p, Monoid o) => Monoid (Product (RoseTrie p o)) | |
| (Eq p, Eq o) => Eq (RoseTrie p o) | |
| (Ord p, Ord o) => Ord (RoseTrie p o) | |
| (Show p, Show o) => Show (RoseTrie p o) | |
| (NFData a, NFData b) => NFData (RoseTrie a b) | |
| Typeable (* -> * -> *) RoseTrie |
class DataFromRoseTrie d p o where
This class provides fromRoseTrie, which generates a data structure of type d from a
RoseTrie of type RoseTrie p o, similar to how the Read class can generate a data
structure from a String.
Methods
fromRoseTrie :: RoseTrie p o -> d
class DataToRoseTrie d p o where
This class provides fromRoseTrie, which generates a RoseTrie of type RoseTrie p o from a
data type of type d, similar to how the Show class can generate a String
from a data structure.
Methods
toRoseTrie :: d -> RoseTrie p o
data RunRoseTrie
This data type controls algorithms like mergeWithKeyM where monadic evaluation needs to occur
in a certain order. This simple operation code decides whether evaluation of leaves happens
before evaluation of sub-RoseTries (BreadthFirst) or whether evaluation of leaves happens after
evaluation of sub-RoseTries (DepthFirst).
Constructors
| DepthFirst | will have the |
| BreadthFirst | will have the |
data ReduceRoseTrie p o
Like RunRoseTrie, but pairs the RunRoseTrie value with the RoseTrie data type itself. This is used to
instantiate Foldable and Traversable, which means in order to
use foldr or traverse, it is first necessary to store the tree
in this data type along with the RunRoseTrie operator indicating the order in which the leaf
objects o will be retrieved.
Constructors
| ReduceRoseTrie | |
Fields
| |
Instances
| Functor (ReduceRoseTrie p) | |
| Foldable (ReduceRoseTrie p) | |
| Ord p => Traversable (ReduceRoseTrie p) | |
| (Eq p, Eq o) => Eq (ReduceRoseTrie p o) | |
| (Ord p, Ord o) => Ord (ReduceRoseTrie p o) | |
| (Show p, Show o) => Show (ReduceRoseTrie p o) | |
| Typeable (* -> * -> *) ReduceRoseTrie |
newRoseTrie :: [RoseTrie p o -> Identity (RoseTrie p o)] -> RoseTrie p o
Since RoseTrie does not directly instantiate Monoid, it cannot be used with the
new function. So the newTrie function is provided which behaves similarly.
In other words, this function takes a list of transfomration functions that modify a RoseTrie,
and starting with an empty RoiseTrie, applies each transformation in order to build the
RoseTrie.
node :: (Monad m, Ord p) => [p] -> Lens m (RoseTrie p o) (RoseTrie p o)
This is a focusing lens that focuses on a RoseTrie node at a given path [p], rather than an
element at the given path.
path :: (Monad m, Ord p) => [p] -> Lens m (RoseTrie p o) (Maybe o)
Focuses on an individual leaf at the given path.
mergeWithKeyM :: forall m p a b c. (Monad m, Ord p) => RunRoseTrie -> ([p] -> Maybe a -> Maybe b -> m (Maybe c)) -> (RoseTrie p a -> m (RoseTrie p c)) -> (RoseTrie p b -> m (RoseTrie p c)) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p c)
This function merges two trees together, given a leaf-merging function that can optionally
create or remove leaves based on whether or not leaves exist on the left and right at any given
point in the path [p].
Also required are two RoseTrie functions: a function that can convert the first (left)
RoseTrie parameter to a RoseTrie of the resultant type, and a function that can convert the
second (right) RoseTrie parameter to a RoseTrie of the resultant type. These functions are
used for when leaves exist only on the left RoseTrie, or for when leaves only exist on the
right RoseTrie.
The given leaf-merging function is called for every single sub-RoseTrie node where the path
[p] exists in both the overlay and target RoseTries. Each sub-RoseTrie node may or may not
have a Leaf.
- If the
RoseTrienode for the overlayRoseTrieand the targetRoseTrieare both without leaves, the merging function is passedNothingas both arguments to the updating function. - If only the target
RoseTriehas aLeaf, the overlayLeafas passed withJustas the first (left) argument to the updating function, andNothingis passed as the second (right) argument. - If only the overlay
RoseTriehas a leaf,Nothingis passed as the first (left) argument to the merging function, and the overlayLeafis passed withJustas the second (right) argument. - If both the target and the overlay
RoseTries haveLeafs, bothLeafs are passed withJustto the merging function.
Also, it is necessary to specify (as the first parameter to this function) the RunRoseTrie
type, which indicates DepthFirst or BreadthFirst evaluation.
In this section I have made my best effor to create API functions as similar as possible to that of the Data.Map module.
insertWith :: Ord p => (o -> o -> o) -> [p] -> o -> RoseTrie p o -> RoseTrie p o
Insert a leaf at a given address, updating it with the combining function if it already exist.
update :: Ord p => (o -> Maybe o) -> [p] -> RoseTrie p o -> RoseTrie p o
Update a leaf at a given address.
fromListWith :: Ord p => (o -> o -> o) -> [([p], o)] -> RoseTrie p o
blankRoseTrie :: Ord p => [[p]] -> RoseTrie p ()
Create a RoseTrie with () nodes. This is useful for times when the structure of the tree is
all you need.
lookup :: Ord p => [p] -> RoseTrie p a -> Maybe a
This function analogous to the lookup function, which returns a value stored in a
leaf, or nothing if there is no leaf at the given path.
slowLookup :: Ord b => (p -> b -> Bool) -> [p] -> RoseTrie b a -> [([b], a)]
This function works like lookup, but takes a key predicate to match keys of the tree, rather
than using (. This means the efficient O(log n) ==)Map lookup
function in the Data.Map module cannot be used, each key must be inspected one-by-one making
this algorithm O(n^2). This also means multiple values may match the given key predicate. Lookups
are always performed in DepthFirst order, this helps improve efficiency a little bit, as the
matches nearest the beggining of each list of assocs are chosen first, and lazily
taking only the first few matches will save us from searching the entire tree.
Take note of the different types p and b. This means the path p you use to search the
RoseTrie need not be the same type as the branches b of the RoseTrie, and what is returned
are the actual branches b that matched the path p, not the path p itself.
slowLookup1 :: Ord b => (p -> b -> Bool) -> [p] -> RoseTrie b a -> Maybe ([b], a)
This function calls slowLookup and returns only the first result. This can be used to take
advantage of Haskell's laziness and save time by halting the search for matching paths as soon as
the first match is found.
assocs :: RunRoseTrie -> RoseTrie p a -> [([p], a)]
Get all items and their associated path.
partitions :: (Eq p, Ord p) => RunRoseTrie -> [p] -> RoseTrie p a -> [(([p], [p]), a)]
Like assocs but restricts the resulting list of associations to only include elements that
lie along a given path. This function walks through the tree with the given path, and collects
every leaf along the way. Where there is a leaf, the path is partitioned into the path up to
the leaf and the path after the leaf. The list of returned values are these partitioned paths
paired with their associated leaves.
partitionsWith :: (Eq p, Ord p) => RunRoseTrie -> (p -> q -> Maybe r) -> [q] -> RoseTrie p a -> [(([r], [q]), a)]
Like partitions, but allows you to use a matching function that other than (==).
The matching function should return Nothing for non-matching path elements, and a
Just containing a path element that may have been transformed by the matching function.
partitionWithM :: (Eq p, Ord p, Monad m) => RunRoseTrie -> (p -> q -> m (Maybe r)) -> [q] -> RoseTrie p a -> m [(([r], [q]), a)]
Like partitionsWith but uses a monadic matching function.
elems :: RunRoseTrie -> RoseTrie p a -> [a]
branchCount :: RoseTrie p a -> Word64
Counts the number of branches only, not leaves.
mergeWithKey :: Ord p => ([p] -> Maybe a -> Maybe b -> Maybe c) -> (RoseTrie p a -> RoseTrie p c) -> (RoseTrie p b -> RoseTrie p c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
Since this function does not merge trees monadically, it is not important whether merging
happens in DepthFirst or BreadthFirst order.
mergeWithM :: (Monad m, Ord p) => RunRoseTrie -> (Maybe a -> Maybe b -> m (Maybe c)) -> (RoseTrie p a -> m (RoseTrie p c)) -> (RoseTrie p b -> m (RoseTrie p c)) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p c)
mergeWith :: Ord p => (Maybe a -> Maybe b -> Maybe c) -> (RoseTrie p a -> RoseTrie p c) -> (RoseTrie p b -> RoseTrie p c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
unionWithKeyM :: (Monad m, Ord p) => RunRoseTrie -> ([p] -> a -> a -> m a) -> RoseTrie p a -> RoseTrie p a -> m (RoseTrie p a)
unionWithKey :: Ord p => ([p] -> a -> a -> a) -> RoseTrie p a -> RoseTrie p a -> RoseTrie p a
unionWithM :: (Monad m, Ord p) => RunRoseTrie -> (a -> a -> m a) -> RoseTrie p a -> RoseTrie p a -> m (RoseTrie p a)
unionsWith :: Ord p => (a -> a -> a) -> [RoseTrie p a] -> RoseTrie p a
intersectionWithKeyM :: (Monad m, Ord p) => RunRoseTrie -> ([p] -> a -> b -> m c) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p c)
intersectionWithKey :: Ord p => ([p] -> a -> b -> c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
intersectionWithM :: (Monad m, Ord p) => RunRoseTrie -> (a -> b -> m c) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p c)
intersectionWith :: Ord p => (a -> b -> c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
intersection :: Ord p => RoseTrie p a -> RoseTrie p b -> RoseTrie p a
intersectionsWith :: Ord p => (a -> a -> a) -> [RoseTrie p a] -> RoseTrie p a
intersections :: Ord p => [RoseTrie p a] -> RoseTrie p a
differenceWithKeyM :: (Monad m, Ord p) => RunRoseTrie -> ([p] -> a -> b -> m (Maybe a)) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p a)
differenceWithKey :: Ord p => ([p] -> a -> b -> Maybe a) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p a
differenceWithM :: (Monad m, Ord p) => RunRoseTrie -> (a -> b -> m (Maybe a)) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p a)
difference :: Ord p => RoseTrie p a -> RoseTrie p b -> RoseTrie p a
differencesWith :: Ord p => (a -> a -> Maybe a) -> [RoseTrie p a] -> RoseTrie p a
differences :: Ord p => [RoseTrie p a] -> RoseTrie p a
productWith :: Ord p => (a -> b -> c) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p c
This function computes the cartesian of two trees. For example, if the assocs of two trees
are:
-- tree X tree Y [( [a, b, c], t ), [( [b, c], w ), ( [a, b ], u ), ( [a ], x )] ( [b ], v )]
Then the product of these two trees X and Y is the evaluation of fromList on:
[( [a, b, c] ++ [b, c], t<>w ), ( [a, b, c] ++ [a ], t<>x ), ( [a, b, ] ++ [b, c], u<>w ), ( [a, b, ] ++ [a, ], u<>x ), ( [b, ] ++ [b, c], v<>w ), ( [b, ] ++ [a ], v<>x )]
product :: (Ord p, Monoid a) => RoseTrie p a -> RoseTrie p a -> RoseTrie p a
Like productWith but uses mappend as the function that computes the product of
each element.
newtype ZipRoseTrie p o
If you have read the chapter about zippers in the book "Learn You a Haskell for Great Good",
you might appreciate that a zipper is provided for RoseTrie in this module, and a number of
useful Control.Monad.Stateful APIs are also provided, namely goto and back.
Although it should be noted usually, Lenses, folds,
traversals, and mergeWithKeyM are all you will need.
Constructors
| ZipRoseTrie (RoseTrie p o, [(p, RoseTrie p o)]) |
Instances
| (Eq p, Eq o) => Eq (ZipRoseTrie p o) | |
| (Ord p, Ord o) => Ord (ZipRoseTrie p o) | |
| Typeable (* -> * -> *) ZipRoseTrie |
zipRoseTrie :: Monad m => Iso m (ZipRoseTrie p o) (RoseTrie p o, [(p, RoseTrie p o)])
zipperSubRoseTrie :: Monad m => Lens m (ZipRoseTrie p o) (RoseTrie p o)
zipperHistory :: Monad m => Lens m (ZipRoseTrie p o) [(p, RoseTrie p o)]
newtype UpdateRoseTrieT p o m a
A monadic function type that keeps the ZipRoseTrie in a StateT for you, and
instantiates MonadState such that get and
put operate on leaves of the RoseTrie. Use goto, back, and home to
navigate the RoseTrie.
Constructors
| UpdateRoseTrieT (StateT (ZipRoseTrie p o) m a) |
Instances
| (Ord p, Functor m, Applicative m, Monad m) => MonadState (Maybe o) (UpdateRoseTrieT p o m) | |
| MonadTrans (UpdateRoseTrieT p o) | |
| (Functor m, Applicative m, Monad m) => Monad (UpdateRoseTrieT p o m) | |
| Functor m => Functor (UpdateRoseTrieT p o m) | |
| (Functor m, Applicative m, Monad m) => Applicative (UpdateRoseTrieT p o m) |
type UpdateRoseTrie p o a = UpdateRoseTrieT p o Identity a
runUpdateRoseTrieT :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m a -> RoseTrie p o -> m (a, RoseTrie p o)
Run the UpdateRoseTrieT function, returning the modified RoseTrie and the last result returned by
the UpdateRoseTrieT function.
execUpdateRoseTrieT :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m a -> RoseTrie p o -> m (RoseTrie p o)
Analogous to execStateT, does the same thing as runUpdateRoseTrieT but
disgards the final return value of the UpdateRoseTrieT function.
evalUpdateRoseTrieT :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m a -> RoseTrie p o -> m a
Analogous to execStateT, does the same thing as runUpdateRoseTrieT but
disgards the updated RoseTrie and only keeps the last return value of the UpdateRoseTrieT function.
goto :: (Functor m, Applicative m, Monad m, Ord p) => [p] -> UpdateRoseTrieT p o m ()
Go to the node with the given path. If the path does not exist, it is created.
back :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m Bool
atTop :: (Functor m, Applicative m, Monad m) => UpdateRoseTrieT p o m Bool
Returns True if we are at the top level of the tree.
home :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m ()
Go back to the top level of the tree.
getPath :: (Functor m, Applicative m, Monad m, Ord p) => UpdateRoseTrieT p o m [p]
Return the current path.
data RoseTrieDiff a b
This data type lets you store a "diff", that is a structure tracking the differences, between
two RoseTries. This is essentially the result of a mergeWithKeyM operation tracking all of the
changes that would happen in a data structure without actually applying the changes. Traversing
over the RoseTrie of RoseTrieDiffs with traverse to actually convert the
RoseTrieDiffs would then apply the changes.
Constructors
| LeftOnly a | |
| RightOnly b | |
| RoseTrieDiff a b |
Instances
| (Eq a, Eq b) => Eq (RoseTrieDiff a b) | |
| Typeable (* -> * -> *) RoseTrieDiff |
treeDiffWithM :: forall m p a b. (Monad m, Ord p) => RunRoseTrie -> ([p] -> a -> b -> m Bool) -> RoseTrie p a -> RoseTrie p b -> m (RoseTrie p (RoseTrieDiff a b))
treeDiffWith :: Ord p => ([p] -> a -> b -> Bool) -> RoseTrie p a -> RoseTrie p b -> RoseTrie p (RoseTrieDiff a b)
treeDiffM :: (Monad m, Eq a, Ord p) => RunRoseTrie -> RoseTrie p a -> RoseTrie p a -> m (RoseTrie p (RoseTrieDiff a a))
Call treeDiffWith using 'Prelude.(==)' as the comparison predicate.
treeDiff :: (Eq a, Ord p) => RoseTrie p a -> RoseTrie p a -> RoseTrie p (RoseTrieDiff a a)
Call treeDiffWith using 'Prelude.(==)' as the comparison predicate.