elynx-tree-0.7.1.0: Handle phylogenetic trees
Copyright2021 Dominik Schrempf
LicenseGPL-3.0-or-later
Maintainerdominik.schrempf@gmail.com
Stabilityunstable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

ELynx.Tree.Rooted

Description

Creation date: Thu Jan 17 09:57:29 2019.

Rooted Trees differs from a classical rose Trees in that they have labeled branches.

For rooted topologies, please see Rooted.

A Tree is defined as:

data Tree e a = Node
  { branch :: e,
    label :: a,
    forest :: Forest e a
  }

where

type Forest e a = [Tree e a]

This means, that the word Node is reserved for the constructor of a tree, and that a Node has an attached branch, a label, and a sub-forest. The terms Node and label referring to the value constructor Node and the record function label, respectively, are not to be confused. The elements of the sub-forest are often called children.

In mathematical terms: A Tree is a directed acyclic graph without loops, with vertex labels, and with edge labels.

A short recap of recursive tree traversals:

  • Pre-order: Root first, then sub trees from left to right. Also called depth first.
  • In-order: Only valid for bifurcating trees. Left sub tree first, then root, then right sub tree.
  • Post-order: Sub trees from left to right, then the root. Also called breadth first.

Here, pre-order traversals are used exclusively, for example, by accessor functions such as branches, or labels which is the same as toList. Please let me know, if post-order algorithms are required.

Synopsis

Tree with branch labels

data Tree e a Source #

Rooted rose trees with branch labels.

Unary instances such as Functor act on node labels, and not on branch labels. Binary instances such as Bifunctor act on both labels (first acts on branches, second on node labels).

Constructors

Node 

Fields

Instances

Instances details
Bifoldable Tree Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

bifold :: Monoid m => Tree m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Tree a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Tree a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Tree a b -> c #

Bifunctor Tree Source #

The function first acts on branch labels, second on node labels.

Instance details

Defined in ELynx.Tree.Rooted

Methods

bimap :: (a -> b) -> (c -> d) -> Tree a c -> Tree b d #

first :: (a -> b) -> Tree a c -> Tree b c #

second :: (b -> c) -> Tree a b -> Tree a c #

Bitraversable Tree Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Tree a b -> f (Tree c d) #

Foldable (Tree e) Source #

Combine node labels in pre-order.

Instance details

Defined in ELynx.Tree.Rooted

Methods

fold :: Monoid m => Tree e m -> m #

foldMap :: Monoid m => (a -> m) -> Tree e a -> m #

foldMap' :: Monoid m => (a -> m) -> Tree e a -> m #

foldr :: (a -> b -> b) -> b -> Tree e a -> b #

foldr' :: (a -> b -> b) -> b -> Tree e a -> b #

foldl :: (b -> a -> b) -> b -> Tree e a -> b #

foldl' :: (b -> a -> b) -> b -> Tree e a -> b #

foldr1 :: (a -> a -> a) -> Tree e a -> a #

foldl1 :: (a -> a -> a) -> Tree e a -> a #

toList :: Tree e a -> [a] #

null :: Tree e a -> Bool #

length :: Tree e a -> Int #

elem :: Eq a => a -> Tree e a -> Bool #

maximum :: Ord a => Tree e a -> a #

minimum :: Ord a => Tree e a -> a #

sum :: Num a => Tree e a -> a #

product :: Num a => Tree e a -> a #

Traversable (Tree e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

traverse :: Applicative f => (a -> f b) -> Tree e a -> f (Tree e b) #

sequenceA :: Applicative f => Tree e (f a) -> f (Tree e a) #

mapM :: Monad m => (a -> m b) -> Tree e a -> m (Tree e b) #

sequence :: Monad m => Tree e (m a) -> m (Tree e a) #

(Semigroup e, Monoid e) => Applicative (Tree e) Source #

The Semigroup instance of the branch labels determines how the branches are combined. For example, distances can be summed using Sum.

The Monoid instance of the branch labels determines the default branch label when using pure.

This instance is similar to the one provided by Tree. For an alternative, see ZipTree.

Instance details

Defined in ELynx.Tree.Rooted

Methods

pure :: a -> Tree e a #

(<*>) :: Tree e (a -> b) -> Tree e a -> Tree e b #

liftA2 :: (a -> b -> c) -> Tree e a -> Tree e b -> Tree e c #

(*>) :: Tree e a -> Tree e b -> Tree e b #

(<*) :: Tree e a -> Tree e b -> Tree e a #

Functor (Tree e) Source #

Map over node labels.

Instance details

Defined in ELynx.Tree.Rooted

Methods

fmap :: (a -> b) -> Tree e a -> Tree e b #

(<$) :: a -> Tree e b -> Tree e a #

(Semigroup e, Monoid e) => Monad (Tree e) Source #

The Semigroup instance of the branch labels determines how the branches are combined. For example, distances can be summed using Sum.

The Monoid instance of the branch labels determines the default branch label when using return.

Instance details

Defined in ELynx.Tree.Rooted

Methods

(>>=) :: Tree e a -> (a -> Tree e b) -> Tree e b #

(>>) :: Tree e a -> Tree e b -> Tree e b #

return :: a -> Tree e a #

Comonad (Tree e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

extract :: Tree e a -> a #

duplicate :: Tree e a -> Tree e (Tree e a) #

extend :: (Tree e a -> b) -> Tree e a -> Tree e b #

(FromJSON e, FromJSON a) => FromJSON (Tree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

parseJSON :: Value -> Parser (Tree e a) #

parseJSONList :: Value -> Parser [Tree e a] #

(ToJSON e, ToJSON a) => ToJSON (Tree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

toJSON :: Tree e a -> Value #

toEncoding :: Tree e a -> Encoding #

toJSONList :: [Tree e a] -> Value #

toEncodingList :: [Tree e a] -> Encoding #

(Data e, Data a) => Data (Tree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tree e a -> c (Tree e a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree e a) #

toConstr :: Tree e a -> Constr #

dataTypeOf :: Tree e a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tree e a)) #

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (Tree e a)) #

gmapT :: (forall b. Data b => b -> b) -> Tree e a -> Tree e a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tree e a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tree e a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tree e a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tree e a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tree e a -> m (Tree e a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree e a -> m (Tree e a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree e a -> m (Tree e a) #

Generic (Tree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Associated Types

type Rep (Tree e a) :: Type -> Type #

Methods

from :: Tree e a -> Rep (Tree e a) x #

to :: Rep (Tree e a) x -> Tree e a #

(Read e, Read a) => Read (Tree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

readsPrec :: Int -> ReadS (Tree e a) #

readList :: ReadS [Tree e a] #

readPrec :: ReadPrec (Tree e a) #

readListPrec :: ReadPrec [Tree e a] #

(Show e, Show a) => Show (Tree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

showsPrec :: Int -> Tree e a -> ShowS #

show :: Tree e a -> String #

showList :: [Tree e a] -> ShowS #

(NFData e, NFData a) => NFData (Tree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

rnf :: Tree e a -> () #

(Eq e, Eq a) => Eq (Tree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

(==) :: Tree e a -> Tree e a -> Bool #

(/=) :: Tree e a -> Tree e a -> Bool #

type Rep (Tree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

type Rep (Tree e a) = D1 ('MetaData "Tree" "ELynx.Tree.Rooted" "elynx-tree-0.7.1.0-7Gi9UsmIXjOISPjpUoE244" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "branch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: (S1 ('MetaSel ('Just "label") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "forest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Forest e a)))))

type Forest e a = [Tree e a] Source #

Shorthand.

fromRoseTree :: Tree a -> Tree () a Source #

Conversion from Tree.

toTreeBranchLabels :: Tree e a -> Tree e Source #

Conversion to Tree using branch labels.

toTreeNodeLabels :: Tree e a -> Tree a Source #

Conversion to Tree using node labels.

Access leaves, branches and labels

leaves :: Tree e a -> [a] Source #

List of leaves.

duplicateLeaves :: Ord a => Tree e a -> Bool Source #

Check if a tree has duplicate leaves.

setStem :: e -> Tree e a -> Tree e a Source #

Set the stem to a given value.

modifyStem :: (e -> e) -> Tree e a -> Tree e a Source #

Modify the stem of a tree.

branches :: Tree e a -> [e] Source #

Get branch labels in pre-order.

setBranches :: Bitraversable t => [f] -> t e a -> Maybe (t f a) Source #

Set branch labels in pre-order.

Return Nothing if the provided list of branch labels is too short.

setLabel :: a -> Tree e a -> Tree e a Source #

Set label.

modifyLabel :: (a -> a) -> Tree e a -> Tree e a Source #

Modify the root label of a tree.

labels :: Tree e a -> [a] Source #

Return node labels in pre-order.

duplicateLabels :: Ord a => Tree e a -> Bool Source #

Check if a tree has duplicate labels.

setLabels :: Traversable t => [b] -> t a -> Maybe (t b) Source #

Set node labels in pre-order.

Return Nothing if the provided list of node labels is too short.

identify :: Traversable t => t a -> t Int Source #

Label the nodes in pre-order with unique indices starting at 0.

Structure

degree :: Tree e a -> Int Source #

Degree of the root node.

The degree of a node is the number of branches attached to the node.

depth :: Tree e a -> Int Source #

Depth of a tree.

The depth of a tree is the largest number of nodes traversed on a path from the root to a leaf.

By convention, the depth is larger equal 1. That is, the depth of a leaf tree is 1.

prune :: Semigroup e => Tree e a -> Tree e a Source #

Prune degree two nodes.

The label of a pruned node is lost. The branches are combined according to their Semigroup instance of the form

daughterBranch parentBranch -> combinedBranch.

dropNodesWith :: (a -> Bool) -> Tree e a -> Maybe (Tree e a) Source #

Drop nodes satisfying predicate.

Degree two nodes may arise.

Also drop nodes of which all daughter nodes are dropped.

Return Nothing if

  • The root node satisfies the predicate.
  • All daughter nodes of the root are dropped.

dropLeavesWith :: (a -> Bool) -> Tree e a -> Maybe (Tree e a) Source #

Drop leaves satisfying predicate.

Degree two nodes may arise.

Also drop nodes of which all daughter nodes are dropped.

Return Nothing if all leaves satisfy the predicate.

zipTreesWith :: (e1 -> e2 -> e) -> (a1 -> a2 -> a) -> Tree e1 a1 -> Tree e2 a2 -> Maybe (Tree e a) Source #

Zip two trees with the same topology.

This function differs from the Applicative instance of ZipTree in that it fails when the topologies don't match. Further, it allows specification of a zipping function for the branches.

Return Nothing if the topologies are different.

zipTrees :: Tree e1 a1 -> Tree e2 a2 -> Maybe (Tree (e1, e2) (a1, a2)) Source #

flipLabels :: Tree e a -> Tree a e Source #

Flip the branch and node lables.

Newtypes with specific instances

newtype ZipTree e a Source #

This newtype provides a zip-like applicative instance, similar to ZipList.

The default applicative instance of Tree is not zip-like, because the zip-like instance makes the Monad instance meaningless (similar to the behavior observed with lists).

Constructors

ZipTree 

Fields

Instances

Instances details
Foldable (ZipTree e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

fold :: Monoid m => ZipTree e m -> m #

foldMap :: Monoid m => (a -> m) -> ZipTree e a -> m #

foldMap' :: Monoid m => (a -> m) -> ZipTree e a -> m #

foldr :: (a -> b -> b) -> b -> ZipTree e a -> b #

foldr' :: (a -> b -> b) -> b -> ZipTree e a -> b #

foldl :: (b -> a -> b) -> b -> ZipTree e a -> b #

foldl' :: (b -> a -> b) -> b -> ZipTree e a -> b #

foldr1 :: (a -> a -> a) -> ZipTree e a -> a #

foldl1 :: (a -> a -> a) -> ZipTree e a -> a #

toList :: ZipTree e a -> [a] #

null :: ZipTree e a -> Bool #

length :: ZipTree e a -> Int #

elem :: Eq a => a -> ZipTree e a -> Bool #

maximum :: Ord a => ZipTree e a -> a #

minimum :: Ord a => ZipTree e a -> a #

sum :: Num a => ZipTree e a -> a #

product :: Num a => ZipTree e a -> a #

Traversable (ZipTree e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

traverse :: Applicative f => (a -> f b) -> ZipTree e a -> f (ZipTree e b) #

sequenceA :: Applicative f => ZipTree e (f a) -> f (ZipTree e a) #

mapM :: Monad m => (a -> m b) -> ZipTree e a -> m (ZipTree e b) #

sequence :: Monad m => ZipTree e (m a) -> m (ZipTree e a) #

Monoid e => Applicative (ZipTree e) Source #

The Monoid instance of the branch labels determines the default branch label, and how the branches are combined. For example, distances can be summed using the Sum monoid.

>>> let t = ZipTree $ Node "" 0 [Node "" 1 [], Node "" 2 []] :: ZipTree String Int
>>> let f = ZipTree $ Node "+3" (+3) [Node "*5" (*5) [], Node "+10" (+10) []] :: ZipTree String (Int -> Int)
>>> f <*> t

ZipTree {getZipTree = Node {branch = "+3", label = 3, forest = [Node {branch = "*5", label = 5, forest = []},Node {branch = "+10", label = 12, forest = []}]}}

Instance details

Defined in ELynx.Tree.Rooted

Methods

pure :: a -> ZipTree e a #

(<*>) :: ZipTree e (a -> b) -> ZipTree e a -> ZipTree e b #

liftA2 :: (a -> b -> c) -> ZipTree e a -> ZipTree e b -> ZipTree e c #

(*>) :: ZipTree e a -> ZipTree e b -> ZipTree e b #

(<*) :: ZipTree e a -> ZipTree e b -> ZipTree e a #

Functor (ZipTree e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

fmap :: (a -> b) -> ZipTree e a -> ZipTree e b #

(<$) :: a -> ZipTree e b -> ZipTree e a #

Comonad (ZipTree e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

extract :: ZipTree e a -> a #

duplicate :: ZipTree e a -> ZipTree e (ZipTree e a) #

extend :: (ZipTree e a -> b) -> ZipTree e a -> ZipTree e b #

(Data e, Data a) => Data (ZipTree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZipTree e a -> c (ZipTree e a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ZipTree e a) #

toConstr :: ZipTree e a -> Constr #

dataTypeOf :: ZipTree e a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ZipTree e a)) #

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (ZipTree e a)) #

gmapT :: (forall b. Data b => b -> b) -> ZipTree e a -> ZipTree e a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZipTree e a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZipTree e a -> r #

gmapQ :: (forall d. Data d => d -> u) -> ZipTree e a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ZipTree e a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZipTree e a -> m (ZipTree e a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipTree e a -> m (ZipTree e a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipTree e a -> m (ZipTree e a) #

Generic (ZipTree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Associated Types

type Rep (ZipTree e a) :: Type -> Type #

Methods

from :: ZipTree e a -> Rep (ZipTree e a) x #

to :: Rep (ZipTree e a) x -> ZipTree e a #

(Read e, Read a) => Read (ZipTree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

(Show e, Show a) => Show (ZipTree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

showsPrec :: Int -> ZipTree e a -> ShowS #

show :: ZipTree e a -> String #

showList :: [ZipTree e a] -> ShowS #

(Eq e, Eq a) => Eq (ZipTree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

(==) :: ZipTree e a -> ZipTree e a -> Bool #

(/=) :: ZipTree e a -> ZipTree e a -> Bool #

type Rep (ZipTree e a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

type Rep (ZipTree e a) = D1 ('MetaData "ZipTree" "ELynx.Tree.Rooted" "elynx-tree-0.7.1.0-7Gi9UsmIXjOISPjpUoE244" 'True) (C1 ('MetaCons "ZipTree" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipTree") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Tree e a))))

newtype BranchTree a e Source #

This newtype provides instances acting on the branch labels, and not on the node labels as it is the case in Tree.

Constructors

BranchTree 

Fields

Instances

Instances details
Foldable (BranchTree a) Source #

Combine branch labels in pre-order.

Instance details

Defined in ELynx.Tree.Rooted

Methods

fold :: Monoid m => BranchTree a m -> m #

foldMap :: Monoid m => (a0 -> m) -> BranchTree a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> BranchTree a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> BranchTree a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> BranchTree a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> BranchTree a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> BranchTree a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> BranchTree a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> BranchTree a a0 -> a0 #

toList :: BranchTree a a0 -> [a0] #

null :: BranchTree a a0 -> Bool #

length :: BranchTree a a0 -> Int #

elem :: Eq a0 => a0 -> BranchTree a a0 -> Bool #

maximum :: Ord a0 => BranchTree a a0 -> a0 #

minimum :: Ord a0 => BranchTree a a0 -> a0 #

sum :: Num a0 => BranchTree a a0 -> a0 #

product :: Num a0 => BranchTree a a0 -> a0 #

Traversable (BranchTree a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

traverse :: Applicative f => (a0 -> f b) -> BranchTree a a0 -> f (BranchTree a b) #

sequenceA :: Applicative f => BranchTree a (f a0) -> f (BranchTree a a0) #

mapM :: Monad m => (a0 -> m b) -> BranchTree a a0 -> m (BranchTree a b) #

sequence :: Monad m => BranchTree a (m a0) -> m (BranchTree a a0) #

Monoid a => Applicative (BranchTree a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

pure :: a0 -> BranchTree a a0 #

(<*>) :: BranchTree a (a0 -> b) -> BranchTree a a0 -> BranchTree a b #

liftA2 :: (a0 -> b -> c) -> BranchTree a a0 -> BranchTree a b -> BranchTree a c #

(*>) :: BranchTree a a0 -> BranchTree a b -> BranchTree a b #

(<*) :: BranchTree a a0 -> BranchTree a b -> BranchTree a a0 #

Functor (BranchTree a) Source #

Map over branch labels.

Instance details

Defined in ELynx.Tree.Rooted

Methods

fmap :: (a0 -> b) -> BranchTree a a0 -> BranchTree a b #

(<$) :: a0 -> BranchTree a b -> BranchTree a a0 #

Comonad (BranchTree a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

extract :: BranchTree a a0 -> a0 #

duplicate :: BranchTree a a0 -> BranchTree a (BranchTree a a0) #

extend :: (BranchTree a a0 -> b) -> BranchTree a a0 -> BranchTree a b #

(Data a, Data e) => Data (BranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BranchTree a e -> c (BranchTree a e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BranchTree a e) #

toConstr :: BranchTree a e -> Constr #

dataTypeOf :: BranchTree a e -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (BranchTree a e)) #

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (BranchTree a e)) #

gmapT :: (forall b. Data b => b -> b) -> BranchTree a e -> BranchTree a e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BranchTree a e -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BranchTree a e -> r #

gmapQ :: (forall d. Data d => d -> u) -> BranchTree a e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BranchTree a e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BranchTree a e -> m (BranchTree a e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BranchTree a e -> m (BranchTree a e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BranchTree a e -> m (BranchTree a e) #

Generic (BranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Associated Types

type Rep (BranchTree a e) :: Type -> Type #

Methods

from :: BranchTree a e -> Rep (BranchTree a e) x #

to :: Rep (BranchTree a e) x -> BranchTree a e #

(Read e, Read a) => Read (BranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

(Show e, Show a) => Show (BranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

showsPrec :: Int -> BranchTree a e -> ShowS #

show :: BranchTree a e -> String #

showList :: [BranchTree a e] -> ShowS #

(Eq e, Eq a) => Eq (BranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

(==) :: BranchTree a e -> BranchTree a e -> Bool #

(/=) :: BranchTree a e -> BranchTree a e -> Bool #

type Rep (BranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

type Rep (BranchTree a e) = D1 ('MetaData "BranchTree" "ELynx.Tree.Rooted" "elynx-tree-0.7.1.0-7Gi9UsmIXjOISPjpUoE244" 'True) (C1 ('MetaCons "BranchTree" 'PrefixI 'True) (S1 ('MetaSel ('Just "getBranchTree") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Tree e a))))

newtype ZipBranchTree a e Source #

Like ZipTree but act on branch labels; see BranchTree.

Constructors

ZipBranchTree 

Fields

Instances

Instances details
Foldable (ZipBranchTree a) Source #

Combine branch labels in pre-order.

Instance details

Defined in ELynx.Tree.Rooted

Methods

fold :: Monoid m => ZipBranchTree a m -> m #

foldMap :: Monoid m => (a0 -> m) -> ZipBranchTree a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> ZipBranchTree a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> ZipBranchTree a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> ZipBranchTree a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> ZipBranchTree a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> ZipBranchTree a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> ZipBranchTree a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> ZipBranchTree a a0 -> a0 #

toList :: ZipBranchTree a a0 -> [a0] #

null :: ZipBranchTree a a0 -> Bool #

length :: ZipBranchTree a a0 -> Int #

elem :: Eq a0 => a0 -> ZipBranchTree a a0 -> Bool #

maximum :: Ord a0 => ZipBranchTree a a0 -> a0 #

minimum :: Ord a0 => ZipBranchTree a a0 -> a0 #

sum :: Num a0 => ZipBranchTree a a0 -> a0 #

product :: Num a0 => ZipBranchTree a a0 -> a0 #

Traversable (ZipBranchTree a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

traverse :: Applicative f => (a0 -> f b) -> ZipBranchTree a a0 -> f (ZipBranchTree a b) #

sequenceA :: Applicative f => ZipBranchTree a (f a0) -> f (ZipBranchTree a a0) #

mapM :: Monad m => (a0 -> m b) -> ZipBranchTree a a0 -> m (ZipBranchTree a b) #

sequence :: Monad m => ZipBranchTree a (m a0) -> m (ZipBranchTree a a0) #

Monoid a => Applicative (ZipBranchTree a) Source #

See the Applicative instance of ZipTree.

Instance details

Defined in ELynx.Tree.Rooted

Methods

pure :: a0 -> ZipBranchTree a a0 #

(<*>) :: ZipBranchTree a (a0 -> b) -> ZipBranchTree a a0 -> ZipBranchTree a b #

liftA2 :: (a0 -> b -> c) -> ZipBranchTree a a0 -> ZipBranchTree a b -> ZipBranchTree a c #

(*>) :: ZipBranchTree a a0 -> ZipBranchTree a b -> ZipBranchTree a b #

(<*) :: ZipBranchTree a a0 -> ZipBranchTree a b -> ZipBranchTree a a0 #

Functor (ZipBranchTree a) Source #

Map over branch labels.

Instance details

Defined in ELynx.Tree.Rooted

Methods

fmap :: (a0 -> b) -> ZipBranchTree a a0 -> ZipBranchTree a b #

(<$) :: a0 -> ZipBranchTree a b -> ZipBranchTree a a0 #

Comonad (ZipBranchTree a) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

extract :: ZipBranchTree a a0 -> a0 #

duplicate :: ZipBranchTree a a0 -> ZipBranchTree a (ZipBranchTree a a0) #

extend :: (ZipBranchTree a a0 -> b) -> ZipBranchTree a a0 -> ZipBranchTree a b #

(Data a, Data e) => Data (ZipBranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZipBranchTree a e -> c (ZipBranchTree a e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ZipBranchTree a e) #

toConstr :: ZipBranchTree a e -> Constr #

dataTypeOf :: ZipBranchTree a e -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ZipBranchTree a e)) #

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (ZipBranchTree a e)) #

gmapT :: (forall b. Data b => b -> b) -> ZipBranchTree a e -> ZipBranchTree a e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZipBranchTree a e -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZipBranchTree a e -> r #

gmapQ :: (forall d. Data d => d -> u) -> ZipBranchTree a e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ZipBranchTree a e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZipBranchTree a e -> m (ZipBranchTree a e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipBranchTree a e -> m (ZipBranchTree a e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipBranchTree a e -> m (ZipBranchTree a e) #

Generic (ZipBranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Associated Types

type Rep (ZipBranchTree a e) :: Type -> Type #

Methods

from :: ZipBranchTree a e -> Rep (ZipBranchTree a e) x #

to :: Rep (ZipBranchTree a e) x -> ZipBranchTree a e #

(Read e, Read a) => Read (ZipBranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

(Show e, Show a) => Show (ZipBranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

(Eq e, Eq a) => Eq (ZipBranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

(==) :: ZipBranchTree a e -> ZipBranchTree a e -> Bool #

(/=) :: ZipBranchTree a e -> ZipBranchTree a e -> Bool #

type Rep (ZipBranchTree a e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

type Rep (ZipBranchTree a e) = D1 ('MetaData "ZipBranchTree" "ELynx.Tree.Rooted" "elynx-tree-0.7.1.0-7Gi9UsmIXjOISPjpUoE244" 'True) (C1 ('MetaCons "ZipBranchTree" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipBranchTree") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Tree e a))))