{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

-- |
--   Module      :  ELynx.Tree.Distribution.TimeOfOrigin
--   Description :  Distribution of time of origin for birth and death trees
--   Copyright   :  (c) Dominik Schrempf 2021
--   License     :  GPL-3.0-or-later
--
--   Maintainer  :  dominik.schrempf@gmail.com
--   Stability   :  unstable
--   Portability :  portable
--
-- Creation date: Tue Feb 13 13:16:18 2018.
--
-- See Gernhard, T. (2008). The conditioned reconstructed process. Journal of
-- Theoretical Biology, 253(4), 769–778. http://doi.org/10.1016/j.jtbi.2008.04.005.
--
-- Distribution of the time of origin for birth and death trees. See corollary 3.3
-- in the paper cited above.
module ELynx.Tree.Distribution.TimeOfOrigin
  ( TimeOfOriginDistribution (..),
    cumulative,
    density,
    quantile,
  )
where

import Data.Data
  ( Data,
    Typeable,
  )
import ELynx.Tree.Distribution.Types
import GHC.Generics (Generic)
import qualified Statistics.Distribution as D

-- | Distribution of the time of origin for a phylogenetic tree evolving under
-- the birth and death process and conditioned on observing n leaves today.
data TimeOfOriginDistribution = TOD
  { -- | Number of leaves of the tree.
    TimeOfOriginDistribution -> Int
todTN :: Int,
    -- | Birth rate.
    TimeOfOriginDistribution -> Rate
todLa :: Rate,
    -- | Death rate.
    TimeOfOriginDistribution -> Rate
todMu :: Rate
  }
  deriving (TimeOfOriginDistribution -> TimeOfOriginDistribution -> Bool
(TimeOfOriginDistribution -> TimeOfOriginDistribution -> Bool)
-> (TimeOfOriginDistribution -> TimeOfOriginDistribution -> Bool)
-> Eq TimeOfOriginDistribution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeOfOriginDistribution -> TimeOfOriginDistribution -> Bool
$c/= :: TimeOfOriginDistribution -> TimeOfOriginDistribution -> Bool
== :: TimeOfOriginDistribution -> TimeOfOriginDistribution -> Bool
$c== :: TimeOfOriginDistribution -> TimeOfOriginDistribution -> Bool
Eq, Typeable, Typeable TimeOfOriginDistribution
DataType
Constr
Typeable TimeOfOriginDistribution
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> TimeOfOriginDistribution
    -> c TimeOfOriginDistribution)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c TimeOfOriginDistribution)
-> (TimeOfOriginDistribution -> Constr)
-> (TimeOfOriginDistribution -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d))
    -> Maybe (c TimeOfOriginDistribution))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c TimeOfOriginDistribution))
-> ((forall b. Data b => b -> b)
    -> TimeOfOriginDistribution -> TimeOfOriginDistribution)
-> (forall r r'.
    (r -> r' -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> TimeOfOriginDistribution
    -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r
    -> (forall d. Data d => d -> r')
    -> TimeOfOriginDistribution
    -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> TimeOfOriginDistribution -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> TimeOfOriginDistribution -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> TimeOfOriginDistribution -> m TimeOfOriginDistribution)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> TimeOfOriginDistribution -> m TimeOfOriginDistribution)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> TimeOfOriginDistribution -> m TimeOfOriginDistribution)
-> Data TimeOfOriginDistribution
TimeOfOriginDistribution -> DataType
TimeOfOriginDistribution -> Constr
(forall b. Data b => b -> b)
-> TimeOfOriginDistribution -> TimeOfOriginDistribution
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> TimeOfOriginDistribution
-> c TimeOfOriginDistribution
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TimeOfOriginDistribution
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> TimeOfOriginDistribution -> u
forall u.
(forall d. Data d => d -> u) -> TimeOfOriginDistribution -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> TimeOfOriginDistribution
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> TimeOfOriginDistribution
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TimeOfOriginDistribution -> m TimeOfOriginDistribution
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TimeOfOriginDistribution -> m TimeOfOriginDistribution
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TimeOfOriginDistribution
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> TimeOfOriginDistribution
-> c TimeOfOriginDistribution
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TimeOfOriginDistribution)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TimeOfOriginDistribution)
$cTOD :: Constr
$tTimeOfOriginDistribution :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> TimeOfOriginDistribution -> m TimeOfOriginDistribution
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TimeOfOriginDistribution -> m TimeOfOriginDistribution
gmapMp :: (forall d. Data d => d -> m d)
-> TimeOfOriginDistribution -> m TimeOfOriginDistribution
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TimeOfOriginDistribution -> m TimeOfOriginDistribution
gmapM :: (forall d. Data d => d -> m d)
-> TimeOfOriginDistribution -> m TimeOfOriginDistribution
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TimeOfOriginDistribution -> m TimeOfOriginDistribution
gmapQi :: Int
-> (forall d. Data d => d -> u) -> TimeOfOriginDistribution -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> TimeOfOriginDistribution -> u
gmapQ :: (forall d. Data d => d -> u) -> TimeOfOriginDistribution -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> TimeOfOriginDistribution -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> TimeOfOriginDistribution
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> TimeOfOriginDistribution
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> TimeOfOriginDistribution
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> TimeOfOriginDistribution
-> r
gmapT :: (forall b. Data b => b -> b)
-> TimeOfOriginDistribution -> TimeOfOriginDistribution
$cgmapT :: (forall b. Data b => b -> b)
-> TimeOfOriginDistribution -> TimeOfOriginDistribution
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TimeOfOriginDistribution)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c TimeOfOriginDistribution)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TimeOfOriginDistribution)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TimeOfOriginDistribution)
dataTypeOf :: TimeOfOriginDistribution -> DataType
$cdataTypeOf :: TimeOfOriginDistribution -> DataType
toConstr :: TimeOfOriginDistribution -> Constr
$ctoConstr :: TimeOfOriginDistribution -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TimeOfOriginDistribution
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TimeOfOriginDistribution
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> TimeOfOriginDistribution
-> c TimeOfOriginDistribution
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> TimeOfOriginDistribution
-> c TimeOfOriginDistribution
$cp1Data :: Typeable TimeOfOriginDistribution
Data, (forall x.
 TimeOfOriginDistribution -> Rep TimeOfOriginDistribution x)
-> (forall x.
    Rep TimeOfOriginDistribution x -> TimeOfOriginDistribution)
-> Generic TimeOfOriginDistribution
forall x.
Rep TimeOfOriginDistribution x -> TimeOfOriginDistribution
forall x.
TimeOfOriginDistribution -> Rep TimeOfOriginDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep TimeOfOriginDistribution x -> TimeOfOriginDistribution
$cfrom :: forall x.
TimeOfOriginDistribution -> Rep TimeOfOriginDistribution x
Generic)

instance D.Distribution TimeOfOriginDistribution where
  cumulative :: TimeOfOriginDistribution -> Rate -> Rate
cumulative = TimeOfOriginDistribution -> Rate -> Rate
cumulative

-- | Cumulative distribution function Corollary 3.3.
cumulative :: TimeOfOriginDistribution -> Time -> Double
cumulative :: TimeOfOriginDistribution -> Rate -> Rate
cumulative (TOD Int
n Rate
l Rate
m) Rate
x
  | Rate
x Rate -> Rate -> Bool
forall a. Ord a => a -> a -> Bool
<= Rate
0 = Rate
0
  | Bool
otherwise = Rate
te Rate -> Rate -> Rate
forall a. Floating a => a -> a -> a
** Int -> Rate
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n
  where
    d :: Rate
d = Rate
l Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate
m
    te :: Rate
te = Rate
l Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* (Rate
1.0 Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate -> Rate
forall a. Floating a => a -> a
exp (- Rate
d Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
x)) Rate -> Rate -> Rate
forall a. Fractional a => a -> a -> a
/ (Rate
l Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate
m Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate -> Rate
forall a. Floating a => a -> a
exp (- Rate
d Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
x))

instance D.ContDistr TimeOfOriginDistribution where
  density :: TimeOfOriginDistribution -> Rate -> Rate
density = TimeOfOriginDistribution -> Rate -> Rate
density
  quantile :: TimeOfOriginDistribution -> Rate -> Rate
quantile = TimeOfOriginDistribution -> Rate -> Rate
quantile

-- | The density function Eq. (5).
density :: TimeOfOriginDistribution -> Time -> Double
density :: TimeOfOriginDistribution -> Rate -> Rate
density (TOD Int
nn Rate
l Rate
m) Rate
x
  | Rate
x Rate -> Rate -> Bool
forall a. Ord a => a -> a -> Bool
< Rate
0 = Rate
0
  | Bool
otherwise = Rate
n Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
l Rate -> Rate -> Rate
forall a. Floating a => a -> a -> a
** Rate
n Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
d Rate -> Rate -> Rate
forall a. Floating a => a -> a -> a
** Rate
2 Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
t1 Rate -> Rate -> Rate
forall a. Floating a => a -> a -> a
** (Rate
n Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate
1.0) Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
ex Rate -> Rate -> Rate
forall a. Fractional a => a -> a -> a
/ (Rate
t2 Rate -> Rate -> Rate
forall a. Floating a => a -> a -> a
** (Rate
n Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
+ Rate
1.0))
  where
    d :: Rate
d = Rate
l Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate
m
    n :: Rate
n = Int -> Rate
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nn
    ex :: Rate
ex = Rate -> Rate
forall a. Floating a => a -> a
exp (- Rate
d Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
x)
    t1 :: Rate
t1 = Rate
1.0 Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate
ex
    t2 :: Rate
t2 = Rate
l Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate
m Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
ex

-- | The inverted cumulative probability distribution 'cumulative'. See also
-- 'D.ContDistr'.
quantile :: TimeOfOriginDistribution -> Double -> Time
quantile :: TimeOfOriginDistribution -> Rate -> Rate
quantile (TOD Int
n' Rate
l Rate
m) Rate
p
  | Rate
p Rate -> Rate -> Bool
forall a. Ord a => a -> a -> Bool
>= Rate
0 Bool -> Bool -> Bool
&& Rate
p Rate -> Rate -> Bool
forall a. Ord a => a -> a -> Bool
<= Rate
1 =
    -Rate
1.0 Rate -> Rate -> Rate
forall a. Fractional a => a -> a -> a
/ Rate
d Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate -> Rate
forall a. Floating a => a -> a
log (Rate
t1 Rate -> Rate -> Rate
forall a. Fractional a => a -> a -> a
/ Rate
t2)
  | Bool
otherwise =
    [Char] -> Rate
forall a. HasCallStack => [Char] -> a
error ([Char] -> Rate) -> [Char] -> Rate
forall a b. (a -> b) -> a -> b
$
      [Char]
"PointProcess.quantile: p must be in [0,1] range. Got: "
        [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Rate -> [Char]
forall a. Show a => a -> [Char]
show Rate
p
        [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"."
  where
    d :: Rate
d = Rate
l Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate
m
    n :: Rate
n = Int -> Rate
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n'
    t1 :: Rate
t1 = Rate
l Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* (Rate
1.0 Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate
p Rate -> Rate -> Rate
forall a. Floating a => a -> a -> a
** (Rate
1.0 Rate -> Rate -> Rate
forall a. Fractional a => a -> a -> a
/ Rate
n))
    t2 :: Rate
t2 = Rate
l Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
- Rate
p Rate -> Rate -> Rate
forall a. Floating a => a -> a -> a
** (Rate
1.0 Rate -> Rate -> Rate
forall a. Fractional a => a -> a -> a
/ Rate
n) Rate -> Rate -> Rate
forall a. Num a => a -> a -> a
* Rate
m

instance D.ContGen TimeOfOriginDistribution where
  genContVar :: TimeOfOriginDistribution -> Gen (PrimState m) -> m Rate
genContVar = TimeOfOriginDistribution -> Gen (PrimState m) -> m Rate
forall d (m :: * -> *).
(ContDistr d, PrimMonad m) =>
d -> Gen (PrimState m) -> m Rate
D.genContinuous