tslib-0.1.4: Time series library

Safe HaskellNone
LanguageHaskell2010

Data.TimeSeries.UTime

Contents

Synopsis

Simple accessors

tsLength :: TSeries ts a => ts a -> Int Source

tsRange :: TSeries ts a => ts a -> Maybe (UTime, UTime) Source

Returns the first and last time stamp of a time series.

tsTraversed :: (TSeries ts a, TSeries ts b) => IndexedTraversal UTime (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) (UTime, a) (UTime, b) Source

Traversal of (UTime, 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 -> [(UTime, a)] Source

Returns a list of (time stamp, value) pairs of a time series sorted by time stamps.

Lookup at time

tsSearch Source

Arguments

:: TSeries ts a 
=> ts a 
-> UTime

the reference time stamp t

-> Int

the returned index i

Returns the lowest index i such that all events after i have time stamp at least t.

firstAfter Source

Arguments

:: TSeries ts a 
=> ts a 
-> UTime

the refenrece time stmap t

-> Maybe (UTime, a) 

Returns the first event that has time stamp not earlier than t or Nothing if there's no such event in the series.

lastBefore Source

Arguments

:: TSeries ts a 
=> ts a 
-> UTime

the reference time stamp t

-> Maybe (UTime, a) 

Returns the last event that has time stamp not later than t or Nothing if there's no such event in the series.

Construction

fromSortedPairList :: TSeries ts a => [(UTime, 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 => [(UTime, 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.

Constructors

TSInterpolate 

Fields

tsiBefore :: UTime -> (UTime, a) -> Maybe (UTime, a)

Function to interpolate for time stamps that are before the first item in the time series.

tsiAfter :: UTime -> (UTime, a) -> Maybe (UTime, a)

Function to interpolate for time stamps that are after the last item in the time series.

tsiBetween :: UTime -> (UTime, a) -> (UTime, a) -> Maybe (UTime, a)

Function to interpolate for time stamps in the middle of the time series.

interpolateAt Source

Arguments

:: TSeries ts a 
=> TSInterpolate a

Parameters to use during the interpolation.

-> ts a

Input time series to interpolate from.

-> UTime

Time stamp to interpolate at.

-> Maybe (UTime, a)

The result of interpolation.

linearBetween :: Fractional a => UTime -> (UTime, a) -> (UTime, a) -> Maybe (UTime, a) Source

Helper function to linearly interpolate a numeric value between two events.

Assumes that the two events are in order and the interpolating time is strictly between the two time stamps.

Useful as the tsiBetween field of a TSInterpolate.

tsiExtend :: UTime -> (UTime, a) -> Maybe (UTime, 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 :: UTime -> (UTime, a) -> Maybe (UTime, 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 -> UTime -> a Source

Access any time stamp in the given time series, with linear interpolation and trivial extension at the ends if needed.

Slicing

tsSlice Source

Arguments

:: TSeries ts a 
=> ts a 
-> UTime

start time (inclusive)

-> UTime

end time (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 start time is inclusive, but the end time is not. If you need different behavior use the provided convenience function: justAfter (for start time, to make it exclusive; for end time, to make it inclusive).

justAfter :: UTime -> UTime Source

Returns the next representable time value.

tsSliceByCount Source

Arguments

:: TSeries ts a 
=> ts a 
-> Int

start index (inclusive)

-> Int

end index (exclusive)

-> ts a 

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.

tsSplitAt :: TSeries ts a => UTime -> ts a -> (ts a, ts a) Source

Split the time series into two parts: everything strictly before the given time stamp, and everything after the given time stamp (including it).

Merging time series

data TSMerge a b c Source

Structure describing a recipe for a generic merge.

Constructors

TSMerge 

Fields

tsmLeft :: UTime -> a -> Maybe c
 
tsmRight :: UTime -> b -> Maybe c
 
tsmBoth :: UTime -> a -> b -> Maybe c
 

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) => (UTime -> 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) -> (UTime -> 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

tsResampleLocal Source

Arguments

:: TSeries ts a 
=> Bool

extend?

-> TSInterpolate a

interpolator

-> [UTime]

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 -> [UTime] -> ts a -> ts a Source

Extend/resample a time series by copying values forward.

extendBackward :: TSeries ts a => Bool -> [UTime] -> ts a -> ts a Source

Extend/resample a time series by copying values backward.

tsResampleGlobal :: TSeries ts a => (UTime -> ts a -> ts a -> Maybe (UTime, a)) -> [UTime] -> 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.

tsResampleMoving Source

Arguments

:: TSeries ts a 
=> (UTime -> ts a -> Maybe a) 
-> Period

window duration

-> [UTime]

times: time stamps for the window ends

-> 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 psOver (tsRange series) as the times argument.

Shifting time series in time

tsOffsetGeneral :: TSeries ts a => (UTime -> UTime) -> 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