epi-sim-0.4.2: 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

type Rep AbsoluteTime Source # 
Instance details

Defined in Epidemic.Types.Time

type Rep AbsoluteTime = D1 ('MetaData "AbsoluteTime" "Epidemic.Types.Time" "epi-sim-0.4.2-4l1mCHWa7vKLa54bgYWgDR" '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.4.2-4l1mCHWa7vKLa54bgYWgDR" 'True) (C1 ('MetaCons "TimeDelta" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

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.4.2-4l1mCHWa7vKLa54bgYWgDR" 'True) (C1 ('MetaCons "Timed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(AbsoluteTime, a)])))

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

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

Evaluate the timed object treating it as a direct delta function

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

The time after a given delay

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

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

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

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

Evaluate the timed object treating it as a cadlag function

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

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

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

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

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]

asTimed Source #

Arguments

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

list of ascending times and values

-> Maybe (Timed a) 

Construct a timed list if possible.