| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Epidemic.Types.Time
Synopsis
- newtype AbsoluteTime = AbsoluteTime Double
- newtype TimeDelta = TimeDelta Double
- data TimeInterval = TimeInterval {}
- newtype Timed a = Timed [(AbsoluteTime, a)]
- class TimeStamp a where
- allTimes :: Timed a -> [AbsoluteTime]
- allValues :: Timed a -> [a]
- asConsecutiveIntervals1 :: [AbsoluteTime] -> [TimeInterval]
- asTimed :: Num a => [(AbsoluteTime, a)] -> Maybe (Timed a)
- cadlagValue :: Timed a -> AbsoluteTime -> Maybe a
- diracDeltaValue :: Timed a -> AbsoluteTime -> Maybe a
- hasTime :: Timed a -> AbsoluteTime -> Bool
- inInterval :: TimeStamp a => TimeInterval -> a -> Bool
- isAscending :: Ord a => [a] -> Bool
- maybeNextTimed :: Timed a -> Timed b -> AbsoluteTime -> Maybe (AbsoluteTime, Either a b)
- nextTime :: Timed a -> AbsoluteTime -> Maybe AbsoluteTime
- timeAfterDelta :: AbsoluteTime -> TimeDelta -> AbsoluteTime
- timeDelta :: AbsoluteTime -> AbsoluteTime -> TimeDelta
- timeInterval1 :: AbsoluteTime -> AbsoluteTime -> TimeInterval
- timeInterval2 :: AbsoluteTime -> TimeDelta -> TimeInterval
Documentation
newtype AbsoluteTime Source #
Absolute time.
Constructors
| AbsoluteTime Double |
Instances
Duration of time between two absolute times.
Instances
| Eq TimeDelta Source # | |
| Ord TimeDelta Source # | |
| Show TimeDelta Source # | |
| Generic TimeDelta Source # | |
| ToJSON TimeDelta Source # | |
Defined in Epidemic.Types.Time | |
| FromJSON TimeDelta Source # | |
| type Rep TimeDelta Source # | |
Defined in Epidemic.Types.Time | |
data TimeInterval Source #
An interval of time
Constructors
| TimeInterval | |
Fields | |
Instances
Type containing values at times. The times are increasing as required by
asTimed.
Constructors
| Timed [(AbsoluteTime, a)] |
Instances
| Eq a => Eq (Timed a) Source # | |
| Show a => Show (Timed a) Source # | |
| Generic (Timed a) Source # | |
| Semigroup (Timed a) Source # | |
| ToJSON a => ToJSON (Timed a) Source # | |
Defined in Epidemic.Types.Time | |
| FromJSON a => FromJSON (Timed a) Source # | |
| type Rep (Timed a) Source # | |
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
Instances
| TimeStamp AbsoluteTime Source # | |
Defined in Epidemic.Types.Time Methods absTime :: AbsoluteTime -> AbsoluteTime Source # isAfter :: AbsoluteTime -> AbsoluteTime -> Bool Source # isBefore :: AbsoluteTime -> AbsoluteTime -> Bool Source # | |
| TimeStamp EpidemicEvent Source # | |
Defined in Epidemic.Types.Events Methods absTime :: EpidemicEvent -> AbsoluteTime Source # isAfter :: EpidemicEvent -> EpidemicEvent -> Bool Source # isBefore :: EpidemicEvent -> EpidemicEvent -> Bool Source # | |
| TimeStamp Observation Source # | |
Defined in Epidemic.Types.Observations Methods absTime :: Observation -> AbsoluteTime Source # isAfter :: Observation -> Observation -> Bool Source # isBefore :: Observation -> Observation -> 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 demoMaybeTimedJust [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.
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
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.