epi-sim-0.7.0: A library for simulating epidemics as birth-death processes.
Safe HaskellNone
LanguageHaskell2010

Epidemic.Types.Time

Synopsis

Documentation

newtype AbsoluteTime Source #

Absolute time.

Constructors

AbsoluteTime Double 

Instances

Instances details
Eq AbsoluteTime Source # 
Instance details

Defined in Epidemic.Types.Time

Ord AbsoluteTime Source # 
Instance details

Defined in Epidemic.Types.Time

Show AbsoluteTime Source # 
Instance details

Defined in Epidemic.Types.Time

Generic AbsoluteTime Source # 
Instance details

Defined in Epidemic.Types.Time

Associated Types

type Rep AbsoluteTime :: Type -> Type #

ToJSON AbsoluteTime Source # 
Instance details

Defined in Epidemic.Types.Time

FromJSON AbsoluteTime Source # 
Instance details

Defined in Epidemic.Types.Time

TimeStamp AbsoluteTime Source # 
Instance details

Defined in Epidemic.Types.Time

type Rep AbsoluteTime Source # 
Instance details

Defined in Epidemic.Types.Time

type Rep AbsoluteTime = D1 ('MetaData "AbsoluteTime" "Epidemic.Types.Time" "epi-sim-0.7.0-DViI2uXntfg6JZVuToo6fh" 'True) (C1 ('MetaCons "AbsoluteTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

newtype TimeDelta Source #

Duration of time between two absolute times.

Constructors

TimeDelta Double 

Instances

Instances details
Eq TimeDelta Source # 
Instance details

Defined in Epidemic.Types.Time

Ord TimeDelta Source # 
Instance details

Defined in Epidemic.Types.Time

Show TimeDelta Source # 
Instance details

Defined in Epidemic.Types.Time

Generic TimeDelta Source # 
Instance details

Defined in Epidemic.Types.Time

Associated Types

type Rep TimeDelta :: Type -> Type #

ToJSON TimeDelta Source # 
Instance details

Defined in Epidemic.Types.Time

FromJSON TimeDelta Source # 
Instance details

Defined in Epidemic.Types.Time

type Rep TimeDelta Source # 
Instance details

Defined in Epidemic.Types.Time

type Rep TimeDelta = D1 ('MetaData "TimeDelta" "Epidemic.Types.Time" "epi-sim-0.7.0-DViI2uXntfg6JZVuToo6fh" 'True) (C1 ('MetaCons "TimeDelta" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

data TimeInterval Source #

An interval of time

Instances

Instances details
Eq TimeInterval Source # 
Instance details

Defined in Epidemic.Types.Time

Show TimeInterval Source # 
Instance details

Defined in Epidemic.Types.Time

Generic TimeInterval Source # 
Instance details

Defined in Epidemic.Types.Time

Associated Types

type Rep TimeInterval :: Type -> Type #

ToJSON TimeInterval Source # 
Instance details

Defined in Epidemic.Types.Time

FromJSON TimeInterval Source # 
Instance details

Defined in Epidemic.Types.Time

type Rep TimeInterval Source # 
Instance details

Defined in Epidemic.Types.Time

type Rep TimeInterval = D1 ('MetaData "TimeInterval" "Epidemic.Types.Time" "epi-sim-0.7.0-DViI2uXntfg6JZVuToo6fh" 'False) (C1 ('MetaCons "TimeInterval" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeIntEndPoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AbsoluteTime, AbsoluteTime)) :*: S1 ('MetaSel ('Just "timeIntDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeDelta)))

newtype Timed a Source #

Type containing values at times. The times are increasing as required by asTimed.

Constructors

Timed [(AbsoluteTime, a)] 

Instances

Instances details
Eq a => Eq (Timed a) Source # 
Instance details

Defined in Epidemic.Types.Time

Methods

(==) :: Timed a -> Timed a -> Bool #

(/=) :: Timed a -> Timed a -> Bool #

Show a => Show (Timed a) Source # 
Instance details

Defined in Epidemic.Types.Time

Methods

showsPrec :: Int -> Timed a -> ShowS #

show :: Timed a -> String #

showList :: [Timed a] -> ShowS #

Generic (Timed a) Source # 
Instance details

Defined in Epidemic.Types.Time

Associated Types

type Rep (Timed a) :: Type -> Type #

Methods

from :: Timed a -> Rep (Timed a) x #

to :: Rep (Timed a) x -> Timed a #

Semigroup (Timed a) Source # 
Instance details

Defined in Epidemic.Types.Time

Methods

(<>) :: Timed a -> Timed a -> Timed a #

sconcat :: NonEmpty (Timed a) -> Timed a #

stimes :: Integral b => b -> Timed a -> Timed a #

ToJSON a => ToJSON (Timed a) Source # 
Instance details

Defined in Epidemic.Types.Time

FromJSON a => FromJSON (Timed a) Source # 
Instance details

Defined in Epidemic.Types.Time

type Rep (Timed a) Source # 
Instance details

Defined in Epidemic.Types.Time

type Rep (Timed a) = D1 ('MetaData "Timed" "Epidemic.Types.Time" "epi-sim-0.7.0-DViI2uXntfg6JZVuToo6fh" 'True) (C1 ('MetaCons "Timed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(AbsoluteTime, a)])))

class TimeStamp a where Source #

A type that has an absolute time associated with it and can be treated as having a temporal ordering.

a = AbsoluteTime 1
b = AbsoluteTime 2
a `isBefore` b

Minimal complete definition

absTime

Methods

absTime :: a -> AbsoluteTime Source #

isAfter :: a -> a -> Bool Source #

isBefore :: a -> a -> Bool Source #

allTimes :: Timed a -> [AbsoluteTime] Source #

Return a list of the (finite) absolute times that the step function changes value.

>>> let demoMaybeTimed = asTimed [(AbsoluteTime 1,2),(AbsoluteTime 1.5,1)]
>>> liftM allTimes demoMaybeTimed
Just [AbsoluteTime 1.0,AbsoluteTime 1.5]

allValues :: Timed a -> [a] Source #

The values that the timed variable takes. NOTE that it is safe to use fromJust here because allTimes only returns times for which there is a cadlag value anyway.

>>> (Just tx) = asTimed [(AbsoluteTime 1,2),(AbsoluteTime 1.5,1)]
>>> allValues tx
[2,1]

asConsecutiveIntervals1 :: [AbsoluteTime] -> [TimeInterval] Source #

Construct a list of consecutive intervals divided by the given absolute times.

asTimed Source #

Arguments

:: Num a 
=> [(AbsoluteTime, a)]

list of ascending times and values

-> Maybe (Timed a) 

Construct a timed list if possible.

cadlagValue :: Timed a -> AbsoluteTime -> Maybe a Source #

Evaluate the timed object treating it as a cadlag function

diracDeltaValue :: Timed a -> AbsoluteTime -> Maybe a Source #

Evaluate the timed object treating it as a direct delta function

hasTime :: Timed a -> AbsoluteTime -> Bool Source #

Check if there exists a pair with a particular time index.

inInterval :: TimeStamp a => TimeInterval -> a -> Bool Source #

Check if an AbsoluteTime sits within a TimeInterval.

isAscending :: Ord a => [a] -> Bool Source #

Predicate to check if a list of orderable objects is in ascending order.

maybeNextTimed :: Timed a -> Timed b -> AbsoluteTime -> Maybe (AbsoluteTime, Either a b) Source #

Look at both of the timed objects and, if possible, return the time that the first one changes along with the value it changes to.

>>> (Just tA) = asTimed [(AbsoluteTime 1, (1.1 :: Double)), (AbsoluteTime 3, 2.3)]
>>> (Just tB) = asTimed [(AbsoluteTime 2, (1 :: Int))]
>>> maybeNextTimed tA tB (AbsoluteTime 0.5)
Just (AbsoluteTime 1.0,Left 1.1)
>>> maybeNextTimed tA tB (AbsoluteTime 1.5)
Just (AbsoluteTime 2.0,Right 1)
>>> maybeNextTimed tA tB (AbsoluteTime 3.5)
Nothing

nextTime :: Timed a -> AbsoluteTime -> Maybe AbsoluteTime Source #

Return the value of the next time if possible or an exact match if it exists.

timeAfterDelta :: AbsoluteTime -> TimeDelta -> AbsoluteTime Source #

The time after a given delay

>>> timeAfterDelta (AbsoluteTime 1) (TimeDelta 2.5)
AbsoluteTime 3.5

timeDelta Source #

Arguments

:: AbsoluteTime

start

-> AbsoluteTime

finish

-> TimeDelta 

The duration of time between two absolute times

>>> timeDelta (AbsoluteTime 1) (AbsoluteTime 2.5)
TimeDelta 1.5

timeInterval1 :: AbsoluteTime -> AbsoluteTime -> TimeInterval Source #

Construct a TimeInterval from the end points.

timeInterval2 :: AbsoluteTime -> TimeDelta -> TimeInterval Source #

Construct a TimeInterval from the start time and the duration.