{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module TLynx.Simulate.Options
( Process (..),
SimulateArguments (..),
simulateArguments,
reportSimulateArguments,
)
where
import Data.Aeson
import Data.List
import Data.Maybe
import ELynx.Tools.Options
import ELynx.Tools.Reproduction
import ELynx.Tree.Simulate.PointProcess (TimeSpec (..))
import GHC.Generics
import Options.Applicative
deriving instance Eq TimeSpec
deriving instance Generic TimeSpec
instance Show TimeSpec where
show :: TimeSpec -> [Char]
show TimeSpec
Random = [Char]
"Random"
show (Origin Double
o) = [Char]
"Condition on height of origin: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> [Char]
forall a. Show a => a -> [Char]
show Double
o
show (Mrca Double
m) = [Char]
"Condition on height of MRCA: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> [Char]
forall a. Show a => a -> [Char]
show Double
m
instance FromJSON TimeSpec
instance ToJSON TimeSpec
data Process
= BirthDeath
{
Process -> Double
bdLambda :: Double,
Process -> Double
bdMu :: Double,
Process -> Maybe Double
bdRho :: Maybe Double,
Process -> TimeSpec
bdHeight :: TimeSpec
}
| Coalescent
deriving (Process -> Process -> Bool
(Process -> Process -> Bool)
-> (Process -> Process -> Bool) -> Eq Process
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Process -> Process -> Bool
== :: Process -> Process -> Bool
$c/= :: Process -> Process -> Bool
/= :: Process -> Process -> Bool
Eq, Int -> Process -> ShowS
[Process] -> ShowS
Process -> [Char]
(Int -> Process -> ShowS)
-> (Process -> [Char]) -> ([Process] -> ShowS) -> Show Process
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Process -> ShowS
showsPrec :: Int -> Process -> ShowS
$cshow :: Process -> [Char]
show :: Process -> [Char]
$cshowList :: [Process] -> ShowS
showList :: [Process] -> ShowS
Show, (forall x. Process -> Rep Process x)
-> (forall x. Rep Process x -> Process) -> Generic Process
forall x. Rep Process x -> Process
forall x. Process -> Rep Process x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Process -> Rep Process x
from :: forall x. Process -> Rep Process x
$cto :: forall x. Rep Process x -> Process
to :: forall x. Rep Process x -> Process
Generic)
instance FromJSON Process
instance ToJSON Process
reportProcess :: Process -> String
reportProcess :: Process -> [Char]
reportProcess (BirthDeath Double
l Double
m Maybe Double
mr TimeSpec
ts) =
[Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate
[Char]
"\n"
[ [Char]
"Model: Birth and death process",
[Char]
" Birth rate: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> [Char]
forall a. Show a => a -> [Char]
show Double
l,
[Char]
" Death rate: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> [Char]
forall a. Show a => a -> [Char]
show Double
m,
[Char]
" Sampling probability: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char] -> (Double -> [Char]) -> Maybe Double -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"1.0" Double -> [Char]
forall a. Show a => a -> [Char]
show Maybe Double
mr,
[Char]
" Height specification: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ TimeSpec -> [Char]
forall a. Show a => a -> [Char]
show TimeSpec
ts
]
reportProcess Process
Coalescent = [Char]
"Model: Coalescent process"
data SimulateArguments = SimulateArguments
{
SimulateArguments -> Int
argsNTrees :: Int,
SimulateArguments -> Int
argsNLeaves :: Int,
SimulateArguments -> Process
argsProcess :: Process,
SimulateArguments -> Maybe Double
argsSubSample :: Maybe Double,
SimulateArguments -> Bool
argsSumStat :: Bool,
SimulateArguments -> SeedOpt
argsSeed :: SeedOpt
}
deriving (SimulateArguments -> SimulateArguments -> Bool
(SimulateArguments -> SimulateArguments -> Bool)
-> (SimulateArguments -> SimulateArguments -> Bool)
-> Eq SimulateArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SimulateArguments -> SimulateArguments -> Bool
== :: SimulateArguments -> SimulateArguments -> Bool
$c/= :: SimulateArguments -> SimulateArguments -> Bool
/= :: SimulateArguments -> SimulateArguments -> Bool
Eq, Int -> SimulateArguments -> ShowS
[SimulateArguments] -> ShowS
SimulateArguments -> [Char]
(Int -> SimulateArguments -> ShowS)
-> (SimulateArguments -> [Char])
-> ([SimulateArguments] -> ShowS)
-> Show SimulateArguments
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SimulateArguments -> ShowS
showsPrec :: Int -> SimulateArguments -> ShowS
$cshow :: SimulateArguments -> [Char]
show :: SimulateArguments -> [Char]
$cshowList :: [SimulateArguments] -> ShowS
showList :: [SimulateArguments] -> ShowS
Show, (forall x. SimulateArguments -> Rep SimulateArguments x)
-> (forall x. Rep SimulateArguments x -> SimulateArguments)
-> Generic SimulateArguments
forall x. Rep SimulateArguments x -> SimulateArguments
forall x. SimulateArguments -> Rep SimulateArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SimulateArguments -> Rep SimulateArguments x
from :: forall x. SimulateArguments -> Rep SimulateArguments x
$cto :: forall x. Rep SimulateArguments x -> SimulateArguments
to :: forall x. Rep SimulateArguments x -> SimulateArguments
Generic)
instance Reproducible SimulateArguments where
inFiles :: SimulateArguments -> [[Char]]
inFiles SimulateArguments
_ = []
outSuffixes :: SimulateArguments -> [[Char]]
outSuffixes SimulateArguments
_ = [[Char]
".tree"]
getSeed :: SimulateArguments -> Maybe SeedOpt
getSeed = SeedOpt -> Maybe SeedOpt
forall a. a -> Maybe a
Just (SeedOpt -> Maybe SeedOpt)
-> (SimulateArguments -> SeedOpt)
-> SimulateArguments
-> Maybe SeedOpt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SimulateArguments -> SeedOpt
argsSeed
setSeed :: SimulateArguments -> SeedOpt -> SimulateArguments
setSeed SimulateArguments
a SeedOpt
s = SimulateArguments
a {argsSeed = s}
parser :: Parser SimulateArguments
parser = Parser SimulateArguments
simulateArguments
cmdName :: [Char]
cmdName = [Char]
"simulate"
cmdDsc :: [[Char]]
cmdDsc = [[Char]
"Simulate phylogenetic trees using a birth and death or coalescent process."]
cmdFtr :: [[Char]]
cmdFtr = [[Char]]
simulateFooter
instance FromJSON SimulateArguments
instance ToJSON SimulateArguments
reportSimulateArguments :: SimulateArguments -> String
reportSimulateArguments :: SimulateArguments -> [Char]
reportSimulateArguments SimulateArguments
a =
[Char] -> [[Char]] -> [Char]
forall a. [a] -> [[a]] -> [a]
intercalate
[Char]
"\n"
[ [Char]
"Number of simulated trees: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show (SimulateArguments -> Int
argsNTrees SimulateArguments
a),
[Char]
"Number of leaves per tree: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show (SimulateArguments -> Int
argsNLeaves SimulateArguments
a),
Process -> [Char]
reportProcess (SimulateArguments -> Process
argsProcess SimulateArguments
a),
[Char]
"Perform sub-sampling: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
ssStr,
[Char]
"Summary statistics only: " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Bool -> [Char]
forall a. Show a => a -> [Char]
show (SimulateArguments -> Bool
argsSumStat SimulateArguments
a)
]
where
ssStr :: [Char]
ssStr = case SimulateArguments -> Maybe Double
argsSubSample SimulateArguments
a of
Maybe Double
Nothing -> [Char]
"No"
Just Double
p -> [Char]
"Yes, with probability " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> [Char]
forall a. Show a => a -> [Char]
show Double
p
simulateArguments :: Parser SimulateArguments
simulateArguments :: Parser SimulateArguments
simulateArguments =
Int
-> Int
-> Process
-> Maybe Double
-> Bool
-> SeedOpt
-> SimulateArguments
SimulateArguments
(Int
-> Int
-> Process
-> Maybe Double
-> Bool
-> SeedOpt
-> SimulateArguments)
-> Parser Int
-> Parser
(Int
-> Process -> Maybe Double -> Bool -> SeedOpt -> SimulateArguments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Int
nTreeOpt
Parser
(Int
-> Process -> Maybe Double -> Bool -> SeedOpt -> SimulateArguments)
-> Parser Int
-> Parser
(Process -> Maybe Double -> Bool -> SeedOpt -> SimulateArguments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int
nLeavesOpt
Parser
(Process -> Maybe Double -> Bool -> SeedOpt -> SimulateArguments)
-> Parser Process
-> Parser (Maybe Double -> Bool -> SeedOpt -> SimulateArguments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Process
process
Parser (Maybe Double -> Bool -> SeedOpt -> SimulateArguments)
-> Parser (Maybe Double)
-> Parser (Bool -> SeedOpt -> SimulateArguments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Double)
subSampleOpt
Parser (Bool -> SeedOpt -> SimulateArguments)
-> Parser Bool -> Parser (SeedOpt -> SimulateArguments)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
sumStatOpt
Parser (SeedOpt -> SimulateArguments)
-> Parser SeedOpt -> Parser SimulateArguments
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser SeedOpt
seedOpt
nTreeOpt :: Parser Int
nTreeOpt :: Parser Int
nTreeOpt =
ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (Mod OptionFields Int -> Parser Int)
-> Mod OptionFields Int -> Parser Int
forall a b. (a -> b) -> a -> b
$
[Char] -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
long [Char]
"nTrees"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
't'
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
metavar [Char]
"INT"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Int
forall (f :: * -> *) a. [Char] -> Mod f a
help [Char]
"Number of trees"
nLeavesOpt :: Parser Int
nLeavesOpt :: Parser Int
nLeavesOpt =
ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (Mod OptionFields Int -> Parser Int)
-> Mod OptionFields Int -> Parser Int
forall a b. (a -> b) -> a -> b
$
[Char] -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
long [Char]
"nLeaves"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'n'
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
metavar [Char]
"INT"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Int
forall (f :: * -> *) a. [Char] -> Mod f a
help [Char]
"Number of leaves per tree"
lambdaOpt :: Parser Double
lambdaOpt :: Parser Double
lambdaOpt =
ReadM Double -> Mod OptionFields Double -> Parser Double
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Double
forall a. Read a => ReadM a
auto (Mod OptionFields Double -> Parser Double)
-> Mod OptionFields Double -> Parser Double
forall a b. (a -> b) -> a -> b
$
[Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
long [Char]
"lambda"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'l'
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
metavar [Char]
"DOUBLE"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. [Char] -> Mod f a
help [Char]
"Birth rate lambda"
muOpt :: Parser Double
muOpt :: Parser Double
muOpt =
ReadM Double -> Mod OptionFields Double -> Parser Double
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Double
forall a. Read a => ReadM a
auto (Mod OptionFields Double -> Parser Double)
-> Mod OptionFields Double -> Parser Double
forall a b. (a -> b) -> a -> b
$
[Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
long [Char]
"mu"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'm'
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
metavar [Char]
"DOUBLE"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. [Char] -> Mod f a
help [Char]
"Death rate mu"
rhoOpt :: Parser Double
rhoOpt :: Parser Double
rhoOpt =
ReadM Double -> Mod OptionFields Double -> Parser Double
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Double
forall a. Read a => ReadM a
auto (Mod OptionFields Double -> Parser Double)
-> Mod OptionFields Double -> Parser Double
forall a b. (a -> b) -> a -> b
$
[Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
long [Char]
"rho"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'r'
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
metavar [Char]
"DOUBLE"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. [Char] -> Mod f a
help [Char]
"Sampling probability rho"
mrca :: Parser TimeSpec
mrca :: Parser TimeSpec
mrca =
Double -> TimeSpec
Mrca
(Double -> TimeSpec) -> Parser Double -> Parser TimeSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM Double -> Mod OptionFields Double -> Parser Double
forall a. ReadM a -> Mod OptionFields a -> Parser a
option
ReadM Double
forall a. Read a => ReadM a
auto
( [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
long [Char]
"mrca"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
metavar [Char]
"DOUBLE"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. [Char] -> Mod f a
help [Char]
"Condition on height of most recent common ancestor"
)
origin :: Parser TimeSpec
origin :: Parser TimeSpec
origin =
Double -> TimeSpec
Origin
(Double -> TimeSpec) -> Parser Double -> Parser TimeSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM Double -> Mod OptionFields Double -> Parser Double
forall a. ReadM a -> Mod OptionFields a -> Parser a
option
ReadM Double
forall a. Read a => ReadM a
auto
( [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
long [Char]
"origin"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
metavar [Char]
"DOUBLE"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. [Char] -> Mod f a
help [Char]
"Condition on height of origin"
)
timeSpec :: Parser TimeSpec
timeSpec :: Parser TimeSpec
timeSpec = TimeSpec -> Maybe TimeSpec -> TimeSpec
forall a. a -> Maybe a -> a
fromMaybe TimeSpec
Random (Maybe TimeSpec -> TimeSpec)
-> Parser (Maybe TimeSpec) -> Parser TimeSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser TimeSpec -> Parser (Maybe TimeSpec)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser TimeSpec
mrca Parser TimeSpec -> Parser TimeSpec -> Parser TimeSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser TimeSpec
origin)
birthDeath :: Parser Process
birthDeath :: Parser Process
birthDeath = Double -> Double -> Maybe Double -> TimeSpec -> Process
BirthDeath (Double -> Double -> Maybe Double -> TimeSpec -> Process)
-> Parser Double
-> Parser (Double -> Maybe Double -> TimeSpec -> Process)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Double
lambdaOpt Parser (Double -> Maybe Double -> TimeSpec -> Process)
-> Parser Double -> Parser (Maybe Double -> TimeSpec -> Process)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Double
muOpt Parser (Maybe Double -> TimeSpec -> Process)
-> Parser (Maybe Double) -> Parser (TimeSpec -> Process)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Double -> Parser (Maybe Double)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser Double
rhoOpt Parser (TimeSpec -> Process) -> Parser TimeSpec -> Parser Process
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser TimeSpec
timeSpec
coalescent :: Parser Process
coalescent :: Parser Process
coalescent = Process -> Parser Process
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Process
Coalescent
process :: Parser Process
process :: Parser Process
process =
Mod CommandFields Process -> Parser Process
forall a. Mod CommandFields a -> Parser a
hsubparser (Mod CommandFields Process -> Parser Process)
-> Mod CommandFields Process -> Parser Process
forall a b. (a -> b) -> a -> b
$
( [Char] -> ParserInfo Process -> Mod CommandFields Process
forall a. [Char] -> ParserInfo a -> Mod CommandFields a
command
[Char]
"birthdeath"
( Parser Process -> InfoMod Process -> ParserInfo Process
forall a. Parser a -> InfoMod a -> ParserInfo a
info
Parser Process
birthDeath
( [Char] -> InfoMod Process
forall a. [Char] -> InfoMod a
progDesc [Char]
"Birth and death process"
InfoMod Process -> InfoMod Process -> InfoMod Process
forall a. Semigroup a => a -> a -> a
<> [Char] -> InfoMod Process
forall a. [Char] -> InfoMod a
footer [Char]
"Height: If no tree height is given, the heights will be randomly drawn from the expected distribution given the number of leaves, the birth and the death rate assuming a uniform prior."
)
)
Mod CommandFields Process
-> Mod CommandFields Process -> Mod CommandFields Process
forall a. Semigroup a => a -> a -> a
<> [Char] -> ParserInfo Process -> Mod CommandFields Process
forall a. [Char] -> ParserInfo a -> Mod CommandFields a
command
[Char]
"coalescent"
(Parser Process -> InfoMod Process -> ParserInfo Process
forall a. Parser a -> InfoMod a -> ParserInfo a
info Parser Process
coalescent ([Char] -> InfoMod Process
forall a. [Char] -> InfoMod a
progDesc [Char]
"Coalescent process"))
)
Mod CommandFields Process
-> Mod CommandFields Process -> Mod CommandFields Process
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod CommandFields Process
forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
metavar [Char]
"PROCESS"
Mod CommandFields Process
-> Mod CommandFields Process -> Mod CommandFields Process
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod CommandFields Process
forall a. [Char] -> Mod CommandFields a
commandGroup [Char]
"Available processes:"
subSampleOpt :: Parser (Maybe Double)
subSampleOpt :: Parser (Maybe Double)
subSampleOpt =
Parser Double -> Parser (Maybe Double)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser Double -> Parser (Maybe Double))
-> Parser Double -> Parser (Maybe Double)
forall a b. (a -> b) -> a -> b
$
ReadM Double -> Mod OptionFields Double -> Parser Double
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Double
forall a. Read a => ReadM a
auto (Mod OptionFields Double -> Parser Double)
-> Mod OptionFields Double -> Parser Double
forall a b. (a -> b) -> a -> b
$
[Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
long
[Char]
"sub-sample"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'u'
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. HasMetavar f => [Char] -> Mod f a
metavar [Char]
"DOUBLE"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Double
forall a (f :: * -> *). Show a => Mod f a
showDefault
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod OptionFields Double
forall (f :: * -> *) a. [Char] -> Mod f a
help [Char]
"Perform sub-sampling; see below."
sumStatOpt :: Parser Bool
sumStatOpt :: Parser Bool
sumStatOpt =
Mod FlagFields Bool -> Parser Bool
switch (Mod FlagFields Bool -> Parser Bool)
-> Mod FlagFields Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$
[Char] -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => [Char] -> Mod f a
long [Char]
"summary-statistics"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
's'
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall a (f :: * -> *). Show a => Mod f a
showDefault
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> [Char] -> Mod FlagFields Bool
forall (f :: * -> *) a. [Char] -> Mod f a
help
[Char]
"For each branch, print length and number of children"
simulateFooter :: [String]
=
[ [Char]
"See, for example, 'tlynx simulate birthdeath --help'.",
[Char]
"Sub-sample with probability p:\n 1. Simulate one big tree with n'=round(n/p), n'>=n, leaves;\n 2. Randomly sample sub trees with n leaves.\n (With p=1.0, the same tree is reported over and over again.)"
]