Safe Haskell | None |
---|---|
Language | Haskell2010 |
- tsLength :: TSeries ts a => ts a -> Int
- (!) :: TSeries ts a => ts a -> Int -> (UTCTime, a)
- tsRange :: TSeries ts a => ts a -> Maybe (UTCTime, UTCTime)
- tsTraversed :: (TSeries ts a, TSeries ts b) => IndexedTraversal UTCTime (ts a) (ts b) a b
- tsTraversedWithIndex :: (TSeries ts a, TSeries ts b) => IndexedTraversal Int (ts a) (ts b) (UTCTime, a) (UTCTime, b)
- toPairList :: TSeries ts a => ts a -> [(UTCTime, a)]
- data TSLook
- tsSearch :: TSeries ts a => ts a -> TSLook -> Int
- tsLookup :: TSeries ts a => ts a -> TSLook -> Maybe (UTCTime, a)
- fromSortedPairList :: TSeries ts a => [(UTCTime, a)] -> ts a
- fromUnsortedPairList :: TSeries ts a => [(UTCTime, a)] -> ts a
- fromPeriodicData :: TSeries ts a => PeriodicSequence -> [a] -> ts a
- data TSInterpolate a
- = TSInterpolate { }
- | TSInterpolateUT (TSInterpolate a)
- interpolateAt :: TSeries ts a => TSInterpolate a -> ts a -> UTCTime -> Maybe (UTCTime, a)
- tsiExtend :: UTCTime -> (UTCTime, a) -> Maybe (UTCTime, a)
- tsiNoExtend :: UTCTime -> (UTCTime, a) -> Maybe (UTCTime, a)
- interpolateLinear :: Fractional a => TSInterpolate a
- extendInterpolateLinear :: Fractional a => TSInterpolate a
- tsGet :: (Fractional a, TSeries ts a) => ts a -> UTCTime -> a
- tsSlice :: TSeries ts a => ts a -> TSLook -> TSLook -> ts a
- tsSliceByCount :: TSeries ts a => ts a -> Int -> Int -> ts a
- tsSplitAt :: TSeries ts a => TSLook -> ts a -> (ts a, ts a)
- data TSMerge a b c = TSMerge {}
- tsMerge :: (TSeries ts a, TSeries ts b, TSeries ts c) => TSMerge a b c -> ts a -> ts b -> ts c
- tsMergeWith :: (TSeries ts a, TSeries ts b, TSeries ts c) => (UTCTime -> a -> b -> c) -> ts a -> ts b -> ts c
- tsMergeEnhance :: (TSeries ts a, TSeries ts b, TSeries ts c) => (Bool, TSInterpolate a) -> (Bool, TSInterpolate b) -> (UTCTime -> a -> b -> c) -> ts a -> ts b -> ts c
- tsResampleLocal :: TSeries ts a => Bool -> TSInterpolate a -> [UTCTime] -> ts a -> ts a
- extendForward :: TSeries ts a => Bool -> [UTCTime] -> ts a -> ts a
- extendBackward :: TSeries ts a => Bool -> [UTCTime] -> ts a -> ts a
- tsResampleGlobal :: TSeries ts a => (UTCTime -> ts a -> ts a -> Maybe (UTCTime, a)) -> [UTCTime] -> ts a -> ts a
- tsResampleMoving :: TSeries ts a => (UTCTime -> ts a -> Maybe a) -> Period -> [UTCTime] -> ts a -> ts a
- tsOffsetGeneral :: TSeries ts a => (UTCTime -> UTCTime) -> ts a -> ts a
- tsOffsetByPeriod :: TSeries ts a => Period -> ts a -> ts a
- tsMapMaybe :: (TSeries ts a, TSeries ts b) => (a -> Maybe b) -> ts a -> ts b
Simple accessors
tsRange :: TSeries ts a => ts a -> Maybe (UTCTime, UTCTime) Source
Returns the first and last time stamp of a time series.
tsTraversed :: (TSeries ts a, TSeries ts b) => IndexedTraversal UTCTime (ts a) (ts b) a b Source
Traversal of the values of a time series with access to the time stamp as index.
tsTraversedWithIndex :: (TSeries ts a, TSeries ts b) => IndexedTraversal Int (ts a) (ts b) (UTCTime, a) (UTCTime, b) Source
Traversal of (UTCTime
, value
) pairs of a time series with
access to a positional index.
The user of this traversal should guarantee to not reorder the events (ie. that the time stamps are modified in a monotonic way).
toPairList :: TSeries ts a => ts a -> [(UTCTime, a)] Source
Returns a list of (time stamp, value) pairs of a time series sorted by time stamps.
Lookup at time
tsSearch :: TSeries ts a => ts a -> TSLook -> Int Source
Returns the position in the time series corresponding to the
TSLook
parameter.
tsLookup :: TSeries ts a => ts a -> TSLook -> Maybe (UTCTime, a) Source
Returns the element of the time series corresponding to the
TSLook
parameter, or Nothing
if there is no suitable element.
Examples:
tsLookup ts (
returns the first element with the time
stamp not earlier than AtOrAfter
t)t
.
tsLookup ts (
returns the last element with
the time stamp strictly before StrictBefore
t)t
.
Construction
fromSortedPairList :: TSeries ts a => [(UTCTime, a)] -> ts a Source
Construct a time series from a list of (time stamp, value) pairs
Precondition: the list have to be sorted by time stamps.
fromUnsortedPairList :: TSeries ts a => [(UTCTime, a)] -> ts a Source
Construct a time series from a list of (time stamp, value) pairs
The list is sorted by time stamps on construction.
fromPeriodicData :: TSeries ts a => PeriodicSequence -> [a] -> ts a Source
Zip a PeriodicSequence
with a list of values.
Lookup with interpolation
data TSInterpolate a Source
Data type used to set up interpolation functions like
interpolateAt
, tsMergeEnhance
and tsResampleLocal
.
TSInterpolate | |
| |
TSInterpolateUT (TSInterpolate a) |
:: TSeries ts a | |
=> TSInterpolate a | Parameters to use during the interpolation. |
-> ts a | Input time series to interpolate from. |
-> UTCTime | Time stamp to interpolate at. |
-> Maybe (UTCTime, a) | The result of interpolation. |
tsiExtend :: UTCTime -> (UTCTime, a) -> Maybe (UTCTime, a) Source
Defines trivial extending of a time series: uses the the same value as the first/last item.
To be used as tsiBefore
or tsiAfter
field of a TSInterpolate
.
tsiNoExtend :: UTCTime -> (UTCTime, a) -> Maybe (UTCTime, a) Source
Defines non-extending time series.
To be used as tsiBefore
or tsiAfter
field of a TSInterpolate
.
interpolateLinear :: Fractional a => TSInterpolate a Source
Linearly interpolates within time series; does not extend.
extendInterpolateLinear :: Fractional a => TSInterpolate a Source
Linearly interpolates within time series; extends at the ends.
tsGet :: (Fractional a, TSeries ts a) => ts a -> UTCTime -> a Source
Access any time stamp in the given time series, with linear interpolation and trivial extension at the ends if needed.
Slicing
:: TSeries ts a | |
=> ts a | |
-> TSLook | start descriptor (inclusive) |
-> TSLook | end descriptor (exclusive) |
-> ts a |
Returns the slice of the time series within the provided time interval.
The time interval is interpreted as half-open, ie. the element
corresponding to the start paramenter is included, but the one
corresponding to the end parameter is not. With this, using
AtOrAfter
and After
it is possible to synthesize both inclusive
and exclusive behavior at either end. Eg.:
tsSlice ts (AtOrAfter t0) (After t1)
returns series of all
elements with time stamp at least t0
and at most t1
, both ends
included.
tsSlice ts (After t0) (AtOrAfter t1)
-- like before, but now both
t0
and t1
are excluded.
Returns the slice of the time series within the provided index interval.
The index interval is half-open: start index is inclusive, end index is exclusive.
Merging time series
Structure describing a recipe for a generic merge.
tsMerge :: (TSeries ts a, TSeries ts b, TSeries ts c) => TSMerge a b c -> ts a -> ts b -> ts c Source
Generic (non-interpolating) merge.
Every time stamp considered independently from all the other. Conversion or combination of values is made according to the provided recipe, based on whether the value is present in one or both time series.
tsMergeWith :: (TSeries ts a, TSeries ts b, TSeries ts c) => (UTCTime -> a -> b -> c) -> ts a -> ts b -> ts c Source
Simple (non-interpolating) merge, similar to zipWith.
Only the time stamps for which value is present in both series are considered. Values are combined by the user-supplied function.
tsMergeEnhance :: (TSeries ts a, TSeries ts b, TSeries ts c) => (Bool, TSInterpolate a) -> (Bool, TSInterpolate b) -> (UTCTime -> a -> b -> c) -> ts a -> ts b -> ts c Source
Merges two time series by extending/resampling them to match each other.
The two time series are extended/resampled with tsResampleLocal
using the provided interpolators; and then merged with
tsMergeWith
.
Resampling time series
:: TSeries ts a | |
=> Bool | extend? |
-> TSInterpolate a | interpolator |
-> [UTCTime] | time stamp sequence |
-> ts a | |
-> ts a |
Resample or extend a time series to have values at the provided time stamps.
Resampling is done by locally interpolating between the two
neighboring events (using the provided interpolator
).
If the extend?
argument is True
, the original time series is
extended; otherwise the result will have values only at the new
time stamps (and the elements of the original time series are
discarded if they don't appear in the provided time stamp
sequence).
extendForward :: TSeries ts a => Bool -> [UTCTime] -> ts a -> ts a Source
Extend/resample a time series by copying values forward.
extendBackward :: TSeries ts a => Bool -> [UTCTime] -> ts a -> ts a Source
Extend/resample a time series by copying values backward.
tsResampleGlobal :: TSeries ts a => (UTCTime -> ts a -> ts a -> Maybe (UTCTime, a)) -> [UTCTime] -> ts a -> ts a Source
Resample a time series to have values at provided time stamps.
For every new time stamp a user supplied function is evaluated with that time stamp and two sub-series: one containing every event strictly before the time stamp, and one containing events at or after the time stamp. The results are collected to create the resulting time series.
:: TSeries ts a | |
=> (UTCTime -> ts a -> Maybe a) | |
-> Period | window duration |
-> [UTCTime] |
|
-> ts a | |
-> ts a |
Resamples a time series by calculating aggregates over a moving window of a given duration at the given time stamps.
If the time stamps for the window positions should be periodic too, you can use
as the psOver
(tsRange
series)times
argument.
Note that each timestamp defines the end of a window, and the timestamp is included in the window.
Shifting time series in time
tsOffsetGeneral :: TSeries ts a => (UTCTime -> UTCTime) -> ts a -> ts a Source
Shift time series in time by applying the user provided function to all the time stamps.
Prerequisite: the provided time-modifying function has to be monotone.
tsOffsetByPeriod :: TSeries ts a => Period -> ts a -> ts a Source
Utilities
tsMapMaybe :: (TSeries ts a, TSeries ts b) => (a -> Maybe b) -> ts a -> ts b Source