elynx-tree-0.3.2: Handle phylogenetic trees

Copyright(c) Dominik Schrempf 2020
LicenseGPL-3.0-or-later
Maintainerdominik.schrempf@gmail.com
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

ELynx.Data.Tree.Phylogeny

Contents

Description

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

A phylogeny is a Tree with unique leaf labels, and the order of the trees in the sub-forest is considered to be meaningless.

Internally, however, the underlying Tree data structure stores the sub-forest as a list, which has a specific order. Hence, we have to do some tricks when comparing trees, and tree comparison is slow.

Also, the 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 children. This convention is not enforced here. Newick trees are just parsed as they are, and a rooted tree is returned.

The bifurcating root of a tree can be changed with roots, or rootAt.

Trees with multifurcating root nodes can be properly rooted using outgroup.

Synopsis

Functions

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

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

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, Ord a) => Set a -> a -> Tree e a -> Either String (Tree e a) Source #

Resolve a multifurcation at the root using an outgroup.

A bifurcating root node with the provided label is introduced. The affected branch is split.

Note, the degree of the former root node is decreased by one.

If the root node is bifurcating, use rootAt.

Return Left if - the tree has duplicate leaves; - the root node is not multifurcating; - the provided outgroup is not found on the tree or is polyphyletic.

midpoint :: (Semigroup e, Splittable e, Measurable 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 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.

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

Connect branches according to the provided Semigroup instance.

Upon insertion of the root, split the affected branch into one out of two equal entities according to a given function.

Return Left if the root node is not bifurcating.

rootAt :: (Semigroup e, Splittable e, Eq a, Ord a) => Bipartition a -> Tree e a -> Either String (Tree e a) Source #

Root a tree at a specific position.

Root the tree at the branch defined by the given bipartition. The original root node is moved to the new position.

The root node must be bifurcating (see roots and outgroup).

Connect branches according to the provided Semigroup instance.

Upon insertion of the root, split the affected branch according to the provided Splittable instance.

Return Left, if: - the root node is not bifurcating; - the tree has duplicate leaves; - the bipartition does not match the leaves of the tree.

Branch labels

data Phylo Source #

Branch label for phylogenetic trees.

Branches may have a length and a support value.

Constructors

Phylo 
Instances
Eq Phylo Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Methods

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

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

Ord Phylo Source # 
Instance details

Defined in ELynx.Data.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.Data.Tree.Phylogeny

Show Phylo Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Methods

showsPrec :: Int -> Phylo -> ShowS #

show :: Phylo -> String #

showList :: [Phylo] -> ShowS #

Generic Phylo Source # 
Instance details

Defined in ELynx.Data.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.Data.Tree.Phylogeny

Methods

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

sconcat :: NonEmpty Phylo -> Phylo #

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

NFData Phylo Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Methods

rnf :: Phylo -> () #

ToJSON Phylo Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

FromJSON Phylo Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

type Rep Phylo Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

type Rep Phylo = D1 (MetaData "Phylo" "ELynx.Data.Tree.Phylogeny" "elynx-tree-0.3.2-D4z8hEm7d0IGPFAaza2gb3" False) (C1 (MetaCons "Phylo" PrefixI True) (S1 (MetaSel (Just "brLen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BranchLength)) :*: S1 (MetaSel (Just "brSup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BranchSupport))))

newtype Length Source #

Branch length label.

For conversion, see phyloToLengthTree and lengthToPhyloTree.

Constructors

Length 
Instances
Eq Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Methods

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

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

Floating Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Fractional Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Num Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Ord Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Read Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Show Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Generic Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Associated Types

type Rep Length :: Type -> Type #

Methods

from :: Length -> Rep Length x #

to :: Rep Length x -> Length #

Semigroup Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Monoid Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

NFData Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Methods

rnf :: Length -> () #

ToJSON Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

FromJSON Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Measurable Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Splittable Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Methods

split :: Length -> Length Source #

type Rep Length Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

type Rep Length = D1 (MetaData "Length" "ELynx.Data.Tree.Phylogeny" "elynx-tree-0.3.2-D4z8hEm7d0IGPFAaza2gb3" True) (C1 (MetaCons "Length" PrefixI True) (S1 (MetaSel (Just "fromLength") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BranchLength)))

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.

lengthToPhyloTree :: Tree Length a -> Tree Phylo a Source #

Set all branch support values to Nothing.

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

newtype Support Source #

Branch support label.

For conversion, see phyloToSupportTree.

Constructors

Support 
Instances
Eq Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Methods

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

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

Floating Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Fractional Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Num Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Ord Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Read Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Show Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Generic Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Associated Types

type Rep Support :: Type -> Type #

Methods

from :: Support -> Rep Support x #

to :: Rep Support x -> Support #

Semigroup Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

NFData Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Methods

rnf :: Support -> () #

ToJSON Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

FromJSON Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Splittable Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Supported Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

type Rep Support Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

type Rep Support = D1 (MetaData "Support" "ELynx.Data.Tree.Phylogeny" "elynx-tree-0.3.2-D4z8hEm7d0IGPFAaza2gb3" True) (C1 (MetaCons "Support" PrefixI True) (S1 (MetaSel (Just "fromSupport") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BranchSupport)))

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 PhyloStrict Source #

Strict branch label for phylogenetic trees.

Constructors

PhyloStrict 
Instances
Eq PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Ord PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Read PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Show PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Generic PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Associated Types

type Rep PhyloStrict :: Type -> Type #

Semigroup PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

ToJSON PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

FromJSON PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Measurable PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Splittable PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

Supported PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

type Rep PhyloStrict Source # 
Instance details

Defined in ELynx.Data.Tree.Phylogeny

type Rep PhyloStrict = D1 (MetaData "PhyloStrict" "ELynx.Data.Tree.Phylogeny" "elynx-tree-0.3.2-D4z8hEm7d0IGPFAaza2gb3" False) (C1 (MetaCons "PhyloStrict" PrefixI True) (S1 (MetaSel (Just "sBrLen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BranchLength) :*: S1 (MetaSel (Just "sBrSup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BranchSupport)))

fromStrictTree :: Tree PhyloStrict a -> Tree Phylo a Source #

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

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