elynx-tree-0.7.0.1: Handle phylogenetic trees
Copyright2021 Dominik Schrempf
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 is slow, 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 a 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.

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.

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 #

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 tree is bifurcating.

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

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

Root tree using an outgroup.

If the root note is bifurcating, the root node is moved to the position specified by the outgroup.

If the root node is multifurcating, a new root node is introduced using the Default instance of the node labels. Thereby, the degree of the original root node is reduced by one.

Branches are connected and split according to the provided Semigroup and Splittable instances.

Return Left if

  • the root node is a leaf;
  • the root node has degree two;
  • the tree has duplicate leaves;
  • the provided outgroup is polyphyletic or not found on the tree.

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

Root tree at midpoint.

Branches are connected and split according to the provided Semigroup and Splittable instances.

Return Left if

  • the root node is a leaf;
  • the root node has degree two.

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

Get all rooted trees with bifurcating root nodes.

If the root node of the original tree is bifurcating, the root node (label and branch) is moved, and the original tree is part of the result.

If the root node of the original tree is multifurcating, a new root node is introduced using the Default instance of the node labels. Thereby, the degree of the original root node is reduced by one. The original, multifurcating tree is not part of the result.

Branches are connected and split according to the provided Semigroup and Splittable instances.

For a tree with n nodes we have:

  • n-2 rooted trees if the root node is bifurcating;
  • (n-1) rooted trees if the root node is multifurcating.

Branch labels

data Phylo Source #

Branch label for phylogenetic trees.

Branches may have a length and a support value.

Especially useful to export trees to Newick format; see toNewick.

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 #

ToJSON Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

FromJSON Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

NFData Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

Methods

rnf :: Phylo -> () #

HasMaybeLength Phylo Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

HasMaybeSupport 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.7.0.1-Jt8eoneXz15KtUzqKUMsOx" 'False) (C1 ('MetaCons "Phylo" 'PrefixI 'True) (S1 ('MetaSel ('Just "pBranchLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Length)) :*: S1 ('MetaSel ('Just "pBranchSupport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Support))))

toPhyloLabel :: (HasMaybeLength e, HasMaybeSupport e) => e -> Phylo Source #

Set branch length and support value.

lengthToPhyloLabel :: HasMaybeLength e => e -> Phylo Source #

Set branch length. Do not set support value.

supportToPhyloLabel :: HasMaybeSupport e => e -> Phylo Source #

Set support value. Do not set branch length.

toLengthTree :: HasMaybeLength e => Tree e 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.

toSupportTree :: HasMaybeSupport e => Tree e 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.

Explicit branch labels

data PhyloExplicit Source #

Explicit branch label with branch length and branch support value.

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

HasMaybeLength PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

HasSupport PhyloExplicit Source # 
Instance details

Defined in ELynx.Tree.Phylogeny

HasMaybeSupport 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.7.0.1-Jt8eoneXz15KtUzqKUMsOx" 'False) (C1 ('MetaCons "PhyloExplicit" 'PrefixI 'True) (S1 ('MetaSel ('Just "eBranchLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Length) :*: S1 ('MetaSel ('Just "eBranchSupport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Support)))