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

Description

Creation date: Thu Jan 17 16:08:54 2019.

The purpose of this module is to facilitate usage of Trees in phylogenetic analyses. A phylogeny is a Tree with unique leaf labels, and unordered sub-forest.

Using the Tree data type has some disadvantages.

  1. All trees are rooted. Unrooted trees can be treated with a rooted data structure, as it is used here. However, some functions may be meaningless.
  2. Changing branch labels, node labels, or the topology of the tree are slow operations, especially, when the changes are close to the leaves of the tree.
  3. Internally, the underlying Tree data structure stores the sub-forest as an ordered list. Hence, we have to do some tricks when comparing phylogenies (see equal), and comparison is slow.
  4. Uniqueness of the leaves is not ensured by the data type, but has to be checked at runtime. Functions relying on the tree to have unique leaves do perform this check, and return Left with an error message, if the tree has duplicate leaves.

Note: Trees are rooted.

Note: Trees encoded in Newick format correspond to rooted trees. By convention only, a tree parsed from Newick format is usually thought to be unrooted, when the root node is multifurcating and has three or more children. This convention is not used here. Newick trees are just parsed as they are, and a rooted tree is returned.

A multifurcating root node can be resolved to a bifurcating root node with outgroup.

The bifurcating root node can be changed with outgroup or midpoint.

For a given tree with bifurcating root node, a list of all rooted trees is returned by roots.

Synopsis

Functions

equal :: (Eq e, Eq a, Ord a) => Tree e a -> Tree e a -> Either String Bool Source #

The equality check is slow because the order of children is considered to be arbitrary.

NOTE: The equality check is only meaningful if the trees have unique leaves.

Return Left if a tree does not have unique leaves.

equal' :: (Eq e, Eq a) => Tree e a -> Tree e a -> Bool Source #

Same as equal, but assume that leaves are unique.

intersect :: (Semigroup e, Eq e, Ord a) => Forest e a -> Either String (Forest e a) Source #

Compute the intersection of trees.

The intersections are the largest subtrees sharing the same leaf set.

Degree two nodes are pruned with prune.

Return Left if:

  • the intersection of leaves is empty.

bifurcating :: Tree e a -> Bool Source #

Check if a tree is bifurcating.

A Bifurcating tree only contains degree one (leaves) and degree three nodes (internal bifurcating nodes).

outgroup :: (Semigroup e, Splittable e, Monoid a, Ord a) => Set a -> Tree e a -> Either String (Tree e a) Source #

Root the tree using an outgroup.

If the current root node is multifurcating, a bifurcating root node with the empty label is introduced by splitting the leftmost branch. The Monoid instance of the node label and the Splittable instance of the branch length are used. Note that in this case, the degree of the former root node is decreased by one!

Given that the root note is bifurcating, the root node is moved to the required position specified by the outgroup.

Branches are connected according to the provided Semigroup instance.

Upon insertion of the root node at the required position, the affected branch is split according to the provided Splittable instance.

Return Left if

  • the root node is not multifurcating;
  • the tree has duplicate leaves;
  • the provided outgroup is not found on the tree or is polyphyletic.

midpoint :: (Semigroup e, Splittable e, HasLength e) => Tree e a -> Either String (Tree e a) Source #

Root tree at the midpoint.

Return Left if

  • the root node is not bifurcating.

roots :: (Semigroup e, Splittable e) => Tree e a -> Either String (Forest e a) Source #

For a rooted tree with a bifurcating root node, get all possible rooted trees.

The root node (label and branch) is moved.

For a tree with l=2 leaves, there is one rooted tree. For a bifurcating tree with l>2 leaves, there are (2l-3) rooted trees. For a general tree with a bifurcating root node, and a total number of n>2 nodes, there are (n-2) rooted trees.

A bifurcating root is required because moving a multifurcating root node to another branch would change the degree of the root node. To resolve a multifurcating root, please use outgroup.

Connect branches according to the provided Semigroup instance.

Split the affected branch into one out of two equal entities according the provided Splittable instance.

Return Left if the root node is not bifurcating.

Branch labels

data Phylo Source #

Branch label for phylogenetic trees.

Branches may have a length and a support value.

Constructors

Phylo 

Instances

Instances details
Eq Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Methods

(==) :: Phylo -> Phylo -> Bool #

(/=) :: Phylo -> Phylo -> Bool #

Ord Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Methods

compare :: Phylo -> Phylo -> Ordering #

(<) :: Phylo -> Phylo -> Bool #

(<=) :: Phylo -> Phylo -> Bool #

(>) :: Phylo -> Phylo -> Bool #

(>=) :: Phylo -> Phylo -> Bool #

max :: Phylo -> Phylo -> Phylo #

min :: Phylo -> Phylo -> Phylo #

Read Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Show Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Methods

showsPrec :: Int -> Phylo -> ShowS #

show :: Phylo -> String #

showList :: [Phylo] -> ShowS #

Generic Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Associated Types

type Rep Phylo :: Type -> Type #

Methods

from :: Phylo -> Rep Phylo x #

to :: Rep Phylo x -> Phylo #

Semigroup Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Methods

(<>) :: Phylo -> Phylo -> Phylo #

sconcat :: NonEmpty Phylo -> Phylo #

stimes :: Integral b => b -> Phylo -> Phylo #

NFData Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Methods

rnf :: Phylo -> () #

ToJSON Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

FromJSON Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

type Rep Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

type Rep Phylo = D1 ('MetaData "Phylo" "ELynx.Tree.Phylogeny" "elynx-tree-0.5.0.1-8lHaLcgw2sVHCDcE59DvPG" 'False) (C1 ('MetaCons "Phylo" 'PrefixI 'True) (S1 ('MetaSel ('Just "brLen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Length)) :*: S1 ('MetaSel ('Just "brSup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Support))))

toPhyloTree :: (HasLength e, HasSupport e) => Tree e a -> Tree Phylo a Source #

Set all branch lengths and support values to Just the value.

Useful to export a tree with branch lengths in Newick format.

measurableToPhyloTree :: HasLength e => Tree e a -> Tree Phylo a Source #

Set all branch lengths to Just the values, and all support values to Nothing.

Useful to export a tree with branch lengths but without branch support values to Newick format.

supportedToPhyloTree :: HasSupport e => Tree e a -> Tree Phylo a Source #

Set all branch lengths to Nothing, and all support values to Just the values.

Useful to export a tree with branch support values but without branch lengths to Newick format.

phyloToLengthTree :: Tree Phylo a -> Either String (Tree Length a) Source #

If root branch length is not available, set it to 0.

Return Left if any other branch length is unavailable.

phyloToSupportTree :: Tree Phylo a -> Either String (Tree Support a) Source #

Set branch support values of branches leading to the leaves and of the root branch to maximum support.

Return Left if any other branch has no available support value.

phyloToSupportTreeUnsafe :: Tree Phylo a -> Tree Support a Source #

Set all unavailable branch support values to maximum support.

data PhyloExplicit Source #

Explicit branch label with branch length and branch support value.

Constructors

PhyloExplicit 

Fields

Instances

Instances details
Eq PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Ord PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Read PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Show PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Generic PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Associated Types

type Rep PhyloExplicit :: Type -> Type #

Semigroup PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

ToJSON PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

FromJSON PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Splittable PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

HasLength PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

HasSupport PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

type Rep PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

type Rep PhyloExplicit = D1 ('MetaData "PhyloExplicit" "ELynx.Tree.Phylogeny" "elynx-tree-0.5.0.1-8lHaLcgw2sVHCDcE59DvPG" 'False) (C1 ('MetaCons "PhyloExplicit" 'PrefixI 'True) (S1 ('MetaSel ('Just "sBrLen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Length) :*: S1 ('MetaSel ('Just "sBrSup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Support)))