{-# LANGUAGE GADTs #-}
module Epidemic.Types.Simulation
( SimulationConfiguration(..)
, SimulationState(..)
, SimulationRandEvent(..)
) where
import Epidemic.Types.Events
import Epidemic.Types.Parameter
import Epidemic.Types.Population
import Epidemic.Types.Time (AbsoluteTime(..), TimeDelta(..), timeDelta)
import System.Random.MWC
data SimulationConfiguration r p =
SimulationConfiguration
{
SimulationConfiguration r p -> r
scRates :: r
, SimulationConfiguration r p -> p
scPopulation :: p
, SimulationConfiguration r p -> Identifier
scNewIdentifier :: Identifier
, SimulationConfiguration r p -> AbsoluteTime
scStartTime :: AbsoluteTime
, SimulationConfiguration r p -> TimeDelta
scSimDuration :: TimeDelta
, SimulationConfiguration r p -> Maybe (p -> Bool)
scValidPopulation :: Maybe (p -> Bool)
, SimulationConfiguration r p -> Bool
scRequireCherry :: Bool
}
data SimulationState b
= SimulationState (AbsoluteTime, [EpidemicEvent], b, Identifier)
| TerminatedSimulation
deriving (SimulationState b -> SimulationState b -> Bool
(SimulationState b -> SimulationState b -> Bool)
-> (SimulationState b -> SimulationState b -> Bool)
-> Eq (SimulationState b)
forall b. Eq b => SimulationState b -> SimulationState b -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimulationState b -> SimulationState b -> Bool
$c/= :: forall b. Eq b => SimulationState b -> SimulationState b -> Bool
== :: SimulationState b -> SimulationState b -> Bool
$c== :: forall b. Eq b => SimulationState b -> SimulationState b -> Bool
Eq, Int -> SimulationState b -> ShowS
[SimulationState b] -> ShowS
SimulationState b -> String
(Int -> SimulationState b -> ShowS)
-> (SimulationState b -> String)
-> ([SimulationState b] -> ShowS)
-> Show (SimulationState b)
forall b. Show b => Int -> SimulationState b -> ShowS
forall b. Show b => [SimulationState b] -> ShowS
forall b. Show b => SimulationState b -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SimulationState b] -> ShowS
$cshowList :: forall b. Show b => [SimulationState b] -> ShowS
show :: SimulationState b -> String
$cshow :: forall b. Show b => SimulationState b -> String
showsPrec :: Int -> SimulationState b -> ShowS
$cshowsPrec :: forall b. Show b => Int -> SimulationState b -> ShowS
Show)
data SimulationRandEvent a b where
SimulationRandEvent
:: (ModelParameters a b, Population b)
=> (a
-> AbsoluteTime
-> b
-> Identifier
-> GenIO
-> IO (AbsoluteTime, EpidemicEvent, b, Identifier))
-> SimulationRandEvent a b