elynx-tree-0.5.0.1: Handle phylogenetic trees
Copyright(c) Dominik Schrempf 2020
LicenseGPL-3.0-or-later
Maintainerdominik.schrempf@gmail.com
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

ELynx.Tree.Rooted

Description

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

Rooted Trees differes from a classical rose Tree in that it has 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 value constructor Node and the record function label 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

Data type

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).

Lifted instances are not provided.

Constructors

Node 

Fields

Instances

Instances details
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) #

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 #

(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 #

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 #

Monoid e => MonadFix (Tree e) Source # 
Instance details

Defined in ELynx.Tree.Rooted

Methods

mfix :: (a -> Tree e a) -> 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.

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 #

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) #

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 #

(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 #

(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) #

(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 #

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 #

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

Defined in ELynx.Tree.Rooted

Methods

rnf :: 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 #

(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] #

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.5.0.1-8lHaLcgw2sVHCDcE59DvPG" '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 #

A shorthand.

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 #

Get 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.

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

Change the root branch 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 the label to a given value.

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

Change the root branch of a tree.

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

Return node labels in pre-order.

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.

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

Change the root label of a tree.

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

Label the nodes with unique integers starting at the root with 0.

Structure

degree :: Tree e a -> Int Source #

The degree of the root node.

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

Prune degree two nodes.

The information stored in 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 parent nodes of which all daughter nodes are dropped.

Return Nothing if the root node satisfies the predicate.

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

Drop leaves satisfying predicate.

Degree two nodes may arise.

Also drop parent nodes of which all leaves 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.

Return Nothing if the topologies are different.

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

Zip two trees with the same topology.

Return Nothing if the topologies are different.