module ELynx.Data.MarkovProcess.SubstitutionModel
(
Name,
Params,
SubstitutionModel,
alphabet,
name,
params,
stationaryDistribution,
exchangeabilityMatrix,
rateMatrix,
totalRate,
substitutionModel,
scale,
normalize,
appendName,
)
where
import qualified Data.Vector.Storable as V
import ELynx.Data.Alphabet.Alphabet
import qualified ELynx.Data.MarkovProcess.RateMatrix as R
import qualified Numeric.LinearAlgebra as LinAlg
type Name = String
type Params = [Double]
data SubstitutionModel = SubstitutionModel
{
SubstitutionModel -> Alphabet
alphabet :: Alphabet,
SubstitutionModel -> Name
name :: Name,
SubstitutionModel -> Params
params :: Params,
SubstitutionModel -> StationaryDistribution
stationaryDistribution :: R.StationaryDistribution,
SubstitutionModel -> ExchangeabilityMatrix
exchangeabilityMatrix :: R.ExchangeabilityMatrix
}
deriving (Int -> SubstitutionModel -> ShowS
[SubstitutionModel] -> ShowS
SubstitutionModel -> Name
(Int -> SubstitutionModel -> ShowS)
-> (SubstitutionModel -> Name)
-> ([SubstitutionModel] -> ShowS)
-> Show SubstitutionModel
forall a.
(Int -> a -> ShowS) -> (a -> Name) -> ([a] -> ShowS) -> Show a
showList :: [SubstitutionModel] -> ShowS
$cshowList :: [SubstitutionModel] -> ShowS
show :: SubstitutionModel -> Name
$cshow :: SubstitutionModel -> Name
showsPrec :: Int -> SubstitutionModel -> ShowS
$cshowsPrec :: Int -> SubstitutionModel -> ShowS
Show, ReadPrec [SubstitutionModel]
ReadPrec SubstitutionModel
Int -> ReadS SubstitutionModel
ReadS [SubstitutionModel]
(Int -> ReadS SubstitutionModel)
-> ReadS [SubstitutionModel]
-> ReadPrec SubstitutionModel
-> ReadPrec [SubstitutionModel]
-> Read SubstitutionModel
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SubstitutionModel]
$creadListPrec :: ReadPrec [SubstitutionModel]
readPrec :: ReadPrec SubstitutionModel
$creadPrec :: ReadPrec SubstitutionModel
readList :: ReadS [SubstitutionModel]
$creadList :: ReadS [SubstitutionModel]
readsPrec :: Int -> ReadS SubstitutionModel
$creadsPrec :: Int -> ReadS SubstitutionModel
Read)
rateMatrix :: SubstitutionModel -> R.RateMatrix
rateMatrix :: SubstitutionModel -> ExchangeabilityMatrix
rateMatrix SubstitutionModel
sm =
ExchangeabilityMatrix
-> StationaryDistribution -> ExchangeabilityMatrix
R.fromExchangeabilityMatrix
(SubstitutionModel -> ExchangeabilityMatrix
exchangeabilityMatrix SubstitutionModel
sm)
(SubstitutionModel -> StationaryDistribution
stationaryDistribution SubstitutionModel
sm)
totalRate :: SubstitutionModel -> Double
totalRate :: SubstitutionModel -> Double
totalRate SubstitutionModel
sm = ExchangeabilityMatrix -> Double
R.totalRate (SubstitutionModel -> ExchangeabilityMatrix
rateMatrix SubstitutionModel
sm)
normalizeSumVec :: V.Vector Double -> V.Vector Double
normalizeSumVec :: StationaryDistribution -> StationaryDistribution
normalizeSumVec StationaryDistribution
v = (Double -> Double)
-> StationaryDistribution -> StationaryDistribution
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
V.map (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
s) StationaryDistribution
v
where
s :: Double
s = StationaryDistribution -> Double
forall a. (Storable a, Num a) => Vector a -> a
V.sum StationaryDistribution
v
{-# INLINE normalizeSumVec #-}
substitutionModel ::
Alphabet ->
Name ->
Params ->
R.StationaryDistribution ->
R.ExchangeabilityMatrix ->
SubstitutionModel
substitutionModel :: Alphabet
-> Name
-> Params
-> StationaryDistribution
-> ExchangeabilityMatrix
-> SubstitutionModel
substitutionModel Alphabet
c Name
n Params
ps StationaryDistribution
d ExchangeabilityMatrix
e =
if StationaryDistribution -> Bool
R.isValid StationaryDistribution
d
then SubstitutionModel -> SubstitutionModel
normalize (SubstitutionModel -> SubstitutionModel)
-> SubstitutionModel -> SubstitutionModel
forall a b. (a -> b) -> a -> b
$ Alphabet
-> Name
-> Params
-> StationaryDistribution
-> ExchangeabilityMatrix
-> SubstitutionModel
SubstitutionModel Alphabet
c Name
n Params
ps (StationaryDistribution -> StationaryDistribution
normalizeSumVec StationaryDistribution
d) ExchangeabilityMatrix
e
else
Name -> SubstitutionModel
forall a. HasCallStack => Name -> a
error (Name -> SubstitutionModel) -> Name -> SubstitutionModel
forall a b. (a -> b) -> a -> b
$
Name
"substitionModel: Stationary distribution does not sum to 1.0: "
Name -> ShowS
forall a. [a] -> [a] -> [a]
++ StationaryDistribution -> Name
forall a. Show a => a -> Name
show StationaryDistribution
d
scale :: Double -> SubstitutionModel -> SubstitutionModel
scale :: Double -> SubstitutionModel -> SubstitutionModel
scale Double
r SubstitutionModel
sm = SubstitutionModel
sm {exchangeabilityMatrix :: ExchangeabilityMatrix
exchangeabilityMatrix = ExchangeabilityMatrix
em'}
where
em' :: ExchangeabilityMatrix
em' = Double -> ExchangeabilityMatrix -> ExchangeabilityMatrix
forall t (c :: * -> *). Linear t c => t -> c t -> c t
LinAlg.scale Double
r (ExchangeabilityMatrix -> ExchangeabilityMatrix)
-> ExchangeabilityMatrix -> ExchangeabilityMatrix
forall a b. (a -> b) -> a -> b
$ SubstitutionModel -> ExchangeabilityMatrix
exchangeabilityMatrix SubstitutionModel
sm
normalize :: SubstitutionModel -> SubstitutionModel
normalize :: SubstitutionModel -> SubstitutionModel
normalize SubstitutionModel
sm = Double -> SubstitutionModel -> SubstitutionModel
scale (Double
1.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
r) SubstitutionModel
sm where r :: Double
r = SubstitutionModel -> Double
totalRate SubstitutionModel
sm
appendName :: Name -> SubstitutionModel -> SubstitutionModel
appendName :: Name -> SubstitutionModel -> SubstitutionModel
appendName Name
n SubstitutionModel
sm = SubstitutionModel
sm {name :: Name
name = Name
n'} where n' :: Name
n' = SubstitutionModel -> Name
name SubstitutionModel
sm Name -> ShowS
forall a. Semigroup a => a -> a -> a
<> Name
n