{-# LANGUAGE RecordWildCards #-}
module Epidemic.InhomogeneousBDS
( configuration
, allEvents
, observedEvents
, inhomBDSRates
) where
import Epidemic.Types.Population
import Epidemic.Types.Events
import Epidemic.Types.Parameter
import Control.Monad (liftM)
import Data.Maybe (fromJust)
import qualified Data.Vector as V
import System.Random.MWC
import System.Random.MWC.Distributions (categorical, exponential)
import Epidemic
import Epidemic.Utility
data InhomBDSRates =
InhomBDSRates (Timed Rate) Rate Rate
instance ModelParameters InhomBDSRates where
rNaught (InhomBDSRates timedBirthRate deathRate sampleRate) time =
let birthRate = cadlagValue timedBirthRate time
in liftM (/ (deathRate + sampleRate)) birthRate
eventRate (InhomBDSRates timedBirthRate deathRate sampleRate) time =
let birthRate = cadlagValue timedBirthRate time
in liftM (+ (deathRate + sampleRate)) birthRate
birthProb (InhomBDSRates timedBirthRate deathRate sampleRate) time =
liftM (\br -> br / (br + deathRate + sampleRate)) $ cadlagValue timedBirthRate time
newtype InhomBDSPop =
InhomBDSPop People
deriving (Show)
instance Population InhomBDSPop where
susceptiblePeople _ = Nothing
infectiousPeople (InhomBDSPop people) = Just people
removedPeople _ = Nothing
isInfected (InhomBDSPop people) = not $ nullPeople people
inhomBDSRates :: [(Time, Rate)]
-> Rate
-> Rate
-> Maybe InhomBDSRates
inhomBDSRates tBrPairs deathRate sampleRate
| all (\x -> 0 < snd x) tBrPairs && deathRate >= 0 && sampleRate >= 0 =
(\tbr -> InhomBDSRates tbr deathRate sampleRate) <$> asTimed tBrPairs
| otherwise = Nothing
configuration :: Time
-> ([(Time,Rate)], Rate, Rate)
-> Maybe (SimulationConfiguration InhomBDSRates InhomBDSPop)
configuration maxTime (tBrPairs, deathRate, sampleRate) =
let (seedPerson, newId) = newPerson initialIdentifier
bdsPop = InhomBDSPop (People $ V.singleton seedPerson)
in do maybeIBDSRates <- inhomBDSRates tBrPairs deathRate sampleRate
if maxTime > 0
then Just
(SimulationConfiguration maybeIBDSRates bdsPop newId maxTime)
else Nothing
randomEvent ::
InhomBDSRates
-> Time
-> InhomBDSPop
-> Integer
-> GenIO
-> IO (Time, EpidemicEvent, InhomBDSPop, Integer)
randomEvent inhomRates@(InhomBDSRates brts@(Timed brts') dr sr) currTime (InhomBDSPop (people@(People peopleVec))) currId gen =
let popSize = fromIntegral $ numPeople people :: Double
stepTimes = map fst brts'
stepFunction = fromJust $ asTimed [(t-currTime,popSize * fromJust (eventRate inhomRates t)) | t <- stepTimes]
eventWeights t = V.fromList [fromJust (cadlagValue brts t), dr, sr]
in do delay <- inhomExponential stepFunction gen
eventIx <- categorical (eventWeights (currTime + delay)) gen
(selectedPerson, unselectedPeople) <- randomPerson peopleVec gen
return $ case eventIx of
0 -> let newTime = currTime + delay
(birthedPerson, newId) = newPerson currId
event = Infection newTime selectedPerson birthedPerson
in ( newTime
, event
, InhomBDSPop (addPerson birthedPerson people)
, newId)
1 -> let newTime = currTime + delay
event = Removal newTime selectedPerson
in (newTime, event, InhomBDSPop (People unselectedPeople), currId)
2 -> let newTime = currTime + delay
event = Sampling newTime selectedPerson
in (newTime, event, InhomBDSPop (People unselectedPeople), currId)
_ -> error "no birth-death-sampling event selected."
allEvents ::
InhomBDSRates
-> Time
-> (Time, [EpidemicEvent], InhomBDSPop, Integer)
-> GenIO
-> IO (Time, [EpidemicEvent], InhomBDSPop, Integer)
allEvents rates maxTime currState@(currTime, currEvents, currPop, currId) gen =
if isInfected currPop
then do
(newTime, event, newPop, newId) <-
randomEvent rates currTime currPop currId gen
if newTime < maxTime
then allEvents
rates
maxTime
(newTime, event : currEvents, newPop, newId)
gen
else return currState
else return currState
observedEvents :: [EpidemicEvent]
-> [EpidemicEvent]
observedEvents [] = []
observedEvents events = sort $ sampleTreeEvents''
where
sampleTreeEvents'' =
sampleTreeEvents . sampleTree $ transmissionTree events (Person 1)