{-# LANGUAGE DeriveGeneric #-}
module Epidemic.Types.Parameter where
import qualified Data.Aeson as Json
import qualified Data.List as List
import qualified Data.Maybe as Maybe
import GHC.Generics
type Time = Double
newtype Timed a =
Timed [(Time, a)]
deriving (Generic, Eq, Show)
instance Json.FromJSON a => Json.FromJSON (Timed a)
instance Json.ToJSON a => Json.ToJSON (Timed a)
instance Semigroup (Timed a) where
(Timed x) <> (Timed y) = Timed $ List.sortOn fst (x ++ y)
type Rate = Double
type Probability = Double
asTimed :: Num a
=> [(Time,a)]
-> Maybe (Timed a)
asTimed tas = if isAscending $ map fst tas then Just (Timed $ tas ++ [(1e100,-1)]) else Nothing
isAscending :: Ord a => [a] -> Bool
isAscending xs = case xs of
[] -> True
[_] -> True
(x:y:xs') -> x <= y && isAscending (y:xs')
cadlagValue :: Timed a -> Time -> Maybe a
cadlagValue (Timed txs) = cadlagValue' txs
cadlagValue' :: [(Time,a)] -> Time -> Maybe a
cadlagValue' [] _ = Nothing
cadlagValue' ((t, x):txs) q =
if q < t
then Nothing
else let nextCLV = cadlagValue' txs q
in if Maybe.isNothing nextCLV
then Just x
else nextCLV
diracDeltaValue :: Timed a -> Time -> Maybe a
diracDeltaValue (Timed txs) = diracDeltaValue' txs
diracDeltaValue' :: [(Time,a)] -> Time -> Maybe a
diracDeltaValue' txs q = case txs of
((t,x):txs') -> if t == q then Just x else diracDeltaValue' txs' q
[] -> Nothing
hasTime :: Timed a -> Time -> Bool
hasTime (Timed txs) = hasTime' txs
hasTime' :: [(Time,a)] -> Time -> Bool
hasTime' txs q = case txs of
((t,_):txs') -> t == q || hasTime' txs' q
[] -> False
nextTime :: Timed a -> Time -> Maybe Time
nextTime (Timed txs) = nextTime' txs
nextTime' :: [(Time,a)] -> Time -> Maybe Time
nextTime' txs q = case txs of
((t,_):txs') -> if q < t then Just t else nextTime' txs' q
[] -> Nothing