module ELynx.Data.MarkovProcess.CXXModels
( cxx,
)
where
import qualified Data.Vector as V
import ELynx.Data.MarkovProcess.AminoAcid
import ELynx.Data.MarkovProcess.CXXModelsData
import qualified ELynx.Data.MarkovProcess.MixtureModel as M
import ELynx.Data.MarkovProcess.RateMatrix
import qualified ELynx.Data.MarkovProcess.SubstitutionModel as S
cxx :: Int -> Maybe [M.Weight] -> M.MixtureModel
cxx :: Int -> Maybe [Weight] -> MixtureModel
cxx Int
10 (Just [Weight]
ws) = [Weight] -> MixtureModel
c10CustomWeights [Weight]
ws
cxx Int
20 (Just [Weight]
ws) = [Weight] -> MixtureModel
c20CustomWeights [Weight]
ws
cxx Int
30 (Just [Weight]
ws) = [Weight] -> MixtureModel
c30CustomWeights [Weight]
ws
cxx Int
40 (Just [Weight]
ws) = [Weight] -> MixtureModel
c40CustomWeights [Weight]
ws
cxx Int
50 (Just [Weight]
ws) = [Weight] -> MixtureModel
c50CustomWeights [Weight]
ws
cxx Int
60 (Just [Weight]
ws) = [Weight] -> MixtureModel
c60CustomWeights [Weight]
ws
cxx Int
10 Maybe [Weight]
Nothing = MixtureModel
c10
cxx Int
20 Maybe [Weight]
Nothing = MixtureModel
c20
cxx Int
30 Maybe [Weight]
Nothing = MixtureModel
c30
cxx Int
40 Maybe [Weight]
Nothing = MixtureModel
c40
cxx Int
50 Maybe [Weight]
Nothing = MixtureModel
c50
cxx Int
60 Maybe [Weight]
Nothing = MixtureModel
c60
cxx Int
n Maybe [Weight]
_ =
[Char] -> MixtureModel
forall a. HasCallStack => [Char] -> a
error ([Char] -> MixtureModel) -> [Char] -> MixtureModel
forall a b. (a -> b) -> a -> b
$ [Char]
"cxx: cannot create CXX model with " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
n [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" components."
c10 :: M.MixtureModel
c10 :: MixtureModel
c10 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
c10Weights [StationaryDistribution]
c10StatDists
c20 :: M.MixtureModel
c20 :: MixtureModel
c20 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
c20Weights [StationaryDistribution]
c20StatDists
c30 :: M.MixtureModel
c30 :: MixtureModel
c30 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
c30Weights [StationaryDistribution]
c30StatDists
c40 :: M.MixtureModel
c40 :: MixtureModel
c40 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
c40Weights [StationaryDistribution]
c40StatDists
c50 :: M.MixtureModel
c50 :: MixtureModel
c50 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
c50Weights [StationaryDistribution]
c50StatDists
c60 :: M.MixtureModel
c60 :: MixtureModel
c60 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
c60Weights [StationaryDistribution]
c60StatDists
c10CustomWeights :: [M.Weight] -> M.MixtureModel
c10CustomWeights :: [Weight] -> MixtureModel
c10CustomWeights [Weight]
ws
| [Weight] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Weight]
ws Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
10 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
ws [StationaryDistribution]
c10StatDists
| Bool
otherwise = [Char] -> MixtureModel
forall a. HasCallStack => [Char] -> a
error [Char]
"Number of weights does not match C10 model."
c20CustomWeights :: [M.Weight] -> M.MixtureModel
c20CustomWeights :: [Weight] -> MixtureModel
c20CustomWeights [Weight]
ws
| [Weight] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Weight]
ws Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
20 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
ws [StationaryDistribution]
c20StatDists
| Bool
otherwise = [Char] -> MixtureModel
forall a. HasCallStack => [Char] -> a
error [Char]
"Number of weights does not match C20 model."
c30CustomWeights :: [M.Weight] -> M.MixtureModel
c30CustomWeights :: [Weight] -> MixtureModel
c30CustomWeights [Weight]
ws
| [Weight] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Weight]
ws Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
30 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
ws [StationaryDistribution]
c30StatDists
| Bool
otherwise = [Char] -> MixtureModel
forall a. HasCallStack => [Char] -> a
error [Char]
"Number of weights does not match C30 model."
c40CustomWeights :: [M.Weight] -> M.MixtureModel
c40CustomWeights :: [Weight] -> MixtureModel
c40CustomWeights [Weight]
ws
| [Weight] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Weight]
ws Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
40 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
ws [StationaryDistribution]
c40StatDists
| Bool
otherwise = [Char] -> MixtureModel
forall a. HasCallStack => [Char] -> a
error [Char]
"Number of weights does not match C40 model."
c50CustomWeights :: [M.Weight] -> M.MixtureModel
c50CustomWeights :: [Weight] -> MixtureModel
c50CustomWeights [Weight]
ws
| [Weight] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Weight]
ws Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
50 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
ws [StationaryDistribution]
c50StatDists
| Bool
otherwise = [Char] -> MixtureModel
forall a. HasCallStack => [Char] -> a
error [Char]
"Number of weights does not match C50 model."
c60CustomWeights :: [M.Weight] -> M.MixtureModel
c60CustomWeights :: [Weight] -> MixtureModel
c60CustomWeights [Weight]
ws
| [Weight] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Weight]
ws Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
60 = [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
ws [StationaryDistribution]
c60StatDists
| Bool
otherwise = [Char] -> MixtureModel
forall a. HasCallStack => [Char] -> a
error [Char]
"Number of weights does not match C60 model."
cxxName :: Int -> String
cxxName :: Int -> [Char]
cxxName Int
nComps = Char
'C' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Int -> [Char]
forall a. Show a => a -> [Char]
show Int
nComps
componentName :: Int -> Int -> String
componentName :: Int -> Int -> [Char]
componentName Int
nComps Int
comp = Int -> [Char]
cxxName Int
nComps [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"; component " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Int -> [Char]
forall a. Show a => a -> [Char]
show Int
comp
cxxSubstitutionModelFromStatDist ::
Int -> Int -> StationaryDistribution -> S.SubstitutionModel
cxxSubstitutionModelFromStatDist :: Int -> Int -> StationaryDistribution -> SubstitutionModel
cxxSubstitutionModelFromStatDist Int
nComps Int
comp StationaryDistribution
d =
Maybe [Char] -> StationaryDistribution -> SubstitutionModel
poissonCustom
([Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
name)
(StationaryDistribution -> StationaryDistribution
normalizeSD StationaryDistribution
d)
where
name :: [Char]
name = Int -> Int -> [Char]
componentName Int
nComps Int
comp
cxxSubstitutionModelsFromStatDists ::
[StationaryDistribution] -> [S.SubstitutionModel]
cxxSubstitutionModelsFromStatDists :: [StationaryDistribution] -> [SubstitutionModel]
cxxSubstitutionModelsFromStatDists [StationaryDistribution]
ds =
(Int -> StationaryDistribution -> SubstitutionModel)
-> [Int] -> [StationaryDistribution] -> [SubstitutionModel]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
(Int -> Int -> StationaryDistribution -> SubstitutionModel
cxxSubstitutionModelFromStatDist Int
nComp)
[Int
1 ..]
[StationaryDistribution]
ds
where
nComp :: Int
nComp = [StationaryDistribution] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [StationaryDistribution]
ds
cxxFromStatDistsAndWeights ::
[M.Weight] -> [StationaryDistribution] -> M.MixtureModel
cxxFromStatDistsAndWeights :: [Weight] -> [StationaryDistribution] -> MixtureModel
cxxFromStatDistsAndWeights [Weight]
ws [StationaryDistribution]
ds =
[Char] -> Vector Weight -> Vector SubstitutionModel -> MixtureModel
M.fromSubstitutionModels
(Int -> [Char]
cxxName Int
n)
([Weight] -> Vector Weight
forall a. [a] -> Vector a
V.fromList [Weight]
ws)
Vector SubstitutionModel
sms
where
n :: Int
n = [StationaryDistribution] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [StationaryDistribution]
ds
sms :: Vector SubstitutionModel
sms = [SubstitutionModel] -> Vector SubstitutionModel
forall a. [a] -> Vector a
V.fromList ([SubstitutionModel] -> Vector SubstitutionModel)
-> [SubstitutionModel] -> Vector SubstitutionModel
forall a b. (a -> b) -> a -> b
$ [StationaryDistribution] -> [SubstitutionModel]
cxxSubstitutionModelsFromStatDists [StationaryDistribution]
ds