{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module ELynx.Tree.Distribution.BirthDeath
( BirthDeathDistribution (..),
cumulative,
density,
quantile,
)
where
import Data.Data
( Data,
Typeable,
)
import ELynx.Tree.Distribution.Types
import GHC.Generics (Generic)
import qualified Statistics.Distribution as D
data BirthDeathDistribution = BDD
{
BirthDeathDistribution -> Time
bddTOr :: Time,
BirthDeathDistribution -> Time
bddLa :: Rate,
BirthDeathDistribution -> Time
bddMu :: Rate
}
deriving (BirthDeathDistribution -> BirthDeathDistribution -> Bool
(BirthDeathDistribution -> BirthDeathDistribution -> Bool)
-> (BirthDeathDistribution -> BirthDeathDistribution -> Bool)
-> Eq BirthDeathDistribution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BirthDeathDistribution -> BirthDeathDistribution -> Bool
$c/= :: BirthDeathDistribution -> BirthDeathDistribution -> Bool
== :: BirthDeathDistribution -> BirthDeathDistribution -> Bool
$c== :: BirthDeathDistribution -> BirthDeathDistribution -> Bool
Eq, Typeable, Typeable BirthDeathDistribution
DataType
Constr
Typeable BirthDeathDistribution
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> BirthDeathDistribution
-> c BirthDeathDistribution)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BirthDeathDistribution)
-> (BirthDeathDistribution -> Constr)
-> (BirthDeathDistribution -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BirthDeathDistribution))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BirthDeathDistribution))
-> ((forall b. Data b => b -> b)
-> BirthDeathDistribution -> BirthDeathDistribution)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> BirthDeathDistribution
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> BirthDeathDistribution
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> BirthDeathDistribution -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> BirthDeathDistribution -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution)
-> Data BirthDeathDistribution
BirthDeathDistribution -> DataType
BirthDeathDistribution -> Constr
(forall b. Data b => b -> b)
-> BirthDeathDistribution -> BirthDeathDistribution
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> BirthDeathDistribution
-> c BirthDeathDistribution
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BirthDeathDistribution
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) -> BirthDeathDistribution -> u
forall u.
(forall d. Data d => d -> u) -> BirthDeathDistribution -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> BirthDeathDistribution
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> BirthDeathDistribution
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BirthDeathDistribution
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> BirthDeathDistribution
-> c BirthDeathDistribution
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BirthDeathDistribution)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BirthDeathDistribution)
$cBDD :: Constr
$tBirthDeathDistribution :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution
gmapMp :: (forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution
gmapM :: (forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> BirthDeathDistribution -> m BirthDeathDistribution
gmapQi :: Int -> (forall d. Data d => d -> u) -> BirthDeathDistribution -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> BirthDeathDistribution -> u
gmapQ :: (forall d. Data d => d -> u) -> BirthDeathDistribution -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> BirthDeathDistribution -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> BirthDeathDistribution
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> BirthDeathDistribution
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> BirthDeathDistribution
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> BirthDeathDistribution
-> r
gmapT :: (forall b. Data b => b -> b)
-> BirthDeathDistribution -> BirthDeathDistribution
$cgmapT :: (forall b. Data b => b -> b)
-> BirthDeathDistribution -> BirthDeathDistribution
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BirthDeathDistribution)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BirthDeathDistribution)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c BirthDeathDistribution)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BirthDeathDistribution)
dataTypeOf :: BirthDeathDistribution -> DataType
$cdataTypeOf :: BirthDeathDistribution -> DataType
toConstr :: BirthDeathDistribution -> Constr
$ctoConstr :: BirthDeathDistribution -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BirthDeathDistribution
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BirthDeathDistribution
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> BirthDeathDistribution
-> c BirthDeathDistribution
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> BirthDeathDistribution
-> c BirthDeathDistribution
$cp1Data :: Typeable BirthDeathDistribution
Data, (forall x. BirthDeathDistribution -> Rep BirthDeathDistribution x)
-> (forall x.
Rep BirthDeathDistribution x -> BirthDeathDistribution)
-> Generic BirthDeathDistribution
forall x. Rep BirthDeathDistribution x -> BirthDeathDistribution
forall x. BirthDeathDistribution -> Rep BirthDeathDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BirthDeathDistribution x -> BirthDeathDistribution
$cfrom :: forall x. BirthDeathDistribution -> Rep BirthDeathDistribution x
Generic)
instance D.Distribution BirthDeathDistribution where
cumulative :: BirthDeathDistribution -> Time -> Time
cumulative = BirthDeathDistribution -> Time -> Time
cumulative
cumulative :: BirthDeathDistribution -> Time -> Double
cumulative :: BirthDeathDistribution -> Time -> Time
cumulative (BDD Time
t Time
l Time
m) Time
x
| Time
x Time -> Time -> Bool
forall a. Ord a => a -> a -> Bool
<= Time
0 = Time
0
| Time
x Time -> Time -> Bool
forall a. Ord a => a -> a -> Bool
> Time
t = Time
1
| Bool
otherwise = Time
t1 Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
t2
where
d :: Time
d = Time
l Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
m
t1 :: Time
t1 = (Time
1.0 Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
x)) Time -> Time -> Time
forall a. Fractional a => a -> a -> a
/ (Time
l Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
m Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
x))
t2 :: Time
t2 = (Time
l Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
m Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
t)) Time -> Time -> Time
forall a. Fractional a => a -> a -> a
/ (Time
1.0 Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
t))
instance D.ContDistr BirthDeathDistribution where
density :: BirthDeathDistribution -> Time -> Time
density = BirthDeathDistribution -> Time -> Time
density
quantile :: BirthDeathDistribution -> Time -> Time
quantile = BirthDeathDistribution -> Time -> Time
quantile
density :: BirthDeathDistribution -> Time -> Double
density :: BirthDeathDistribution -> Time -> Time
density (BDD Time
t Time
l Time
m) Time
x
| Time
x Time -> Time -> Bool
forall a. Ord a => a -> a -> Bool
< Time
0 = Time
0
| Time
x Time -> Time -> Bool
forall a. Ord a => a -> a -> Bool
> Time
t = Time
0
| Bool
otherwise = Time
d Time -> Time -> Time
forall a. Floating a => a -> a -> a
** Time
2 Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
t1 Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
t2
where
d :: Time
d = Time
l Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
m
t1 :: Time
t1 = Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
x) Time -> Time -> Time
forall a. Fractional a => a -> a -> a
/ ((Time
l Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
m Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
x)) Time -> Time -> Time
forall a. Floating a => a -> a -> a
** Time
2)
t2 :: Time
t2 = (Time
l Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
m Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
t)) Time -> Time -> Time
forall a. Fractional a => a -> a -> a
/ (Time
1.0 Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
t))
quantile :: BirthDeathDistribution -> Double -> Time
quantile :: BirthDeathDistribution -> Time -> Time
quantile (BDD Time
t Time
l Time
m) Time
p
| Time
p Time -> Time -> Bool
forall a. Ord a => a -> a -> Bool
>= Time
0 Bool -> Bool -> Bool
&& Time
p Time -> Time -> Bool
forall a. Ord a => a -> a -> Bool
<= Time
1 =
Time
res
| Bool
otherwise =
[Char] -> Time
forall a. HasCallStack => [Char] -> a
error ([Char] -> Time) -> [Char] -> Time
forall a b. (a -> b) -> a -> b
$
[Char]
"BirthDeath.quantile: p must be in range [0,1] but got "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Time -> [Char]
forall a. Show a => a -> [Char]
show Time
p
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"."
where
d :: Time
d = Time
l Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
m
t2 :: Time
t2 = (Time
l Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
m Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
t)) Time -> Time -> Time
forall a. Fractional a => a -> a -> a
/ (Time
1.0 Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time -> Time
forall a. Floating a => a -> a
exp (- Time
d Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
t))
res :: Time
res = (-Time
1.0 Time -> Time -> Time
forall a. Fractional a => a -> a -> a
/ Time
d) Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time -> Time
forall a. Floating a => a -> a
log ((Time
1.0 Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
p Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
l Time -> Time -> Time
forall a. Fractional a => a -> a -> a
/ Time
t2) Time -> Time -> Time
forall a. Fractional a => a -> a -> a
/ (Time
1.0 Time -> Time -> Time
forall a. Num a => a -> a -> a
- Time
p Time -> Time -> Time
forall a. Num a => a -> a -> a
* Time
m Time -> Time -> Time
forall a. Fractional a => a -> a -> a
/ Time
t2))
instance D.ContGen BirthDeathDistribution where
genContVar :: BirthDeathDistribution -> Gen (PrimState m) -> m Time
genContVar = BirthDeathDistribution -> Gen (PrimState m) -> m Time
forall d (m :: * -> *).
(ContDistr d, PrimMonad m) =>
d -> Gen (PrimState m) -> m Time
D.genContinuous