module Data.TimeSeries (
tsLength,
(!),
tsRange,
tsTraversed,
tsTraversedWithIndex,
toPairList,
TSLook(..),
tsSearch,
tsLookup,
fromSortedPairList,
fromUnsortedPairList,
TSU.fromPeriodicData,
TSInterpolate(..),
interpolateAt,
tsiExtend,
tsiNoExtend,
interpolateLinear,
extendInterpolateLinear,
tsGet,
tsSlice,
TSU.tsSliceByCount,
tsSplitAt,
TSMerge(..),
tsMerge,
tsMergeWith,
tsMergeEnhance,
tsResampleLocal,
extendForward,
extendBackward,
tsResampleGlobal,
tsResampleMoving,
tsOffsetGeneral,
tsOffsetByPeriod,
tsMapMaybe
) where
import Control.Lens
import Data.Time (UTCTime)
import Data.TimeSeries.Class
import Data.TimeSeries.Periodic
import qualified Data.TimeSeries.UTime as TSU
import Data.UTime
import qualified Data.Vector.Generic as G
ut2utc :: Setting (->) s t UTime UTCTime -> s -> t
ut2utc s = over s fromUTime
ut2utcL :: [(UTime, a)] -> [(UTCTime, a)]
ut2utcL = ut2utc (mapped._1)
utc2ut :: Setting (->) s t UTCTime UTime -> s -> t
utc2ut s = over s toUTime
utc2utL :: [(UTCTime, a)] -> [(UTime, a)]
utc2utL = utc2ut (mapped._1)
tsLength :: TSeries ts a => ts a -> Int
tsLength = TSU.tsLength
(!) :: TSeries ts a => ts a -> Int -> (UTCTime, a)
(!) ts i = ut2utc _1 $ toVector ts G.! i
tsRange :: TSeries ts a => ts a -> Maybe (UTCTime, UTCTime)
tsRange = ut2utc (mapped.both) . TSU.tsRange
tsTraversed :: (TSeries ts a, TSeries ts b) => IndexedTraversal UTCTime (ts a) (ts b) a b
tsTraversed f ts = fromVector . G.fromListN (G.length v) <$> traverse g (G.toList v)
where
v = toVector ts
g (t, x) = (t,) <$> indexed f (fromUTime t) x
tsTraversedWithIndex :: (TSeries ts a, TSeries ts b)
=> IndexedTraversal Int (ts a) (ts b) (UTCTime, a) (UTCTime, b)
tsTraversedWithIndex f ts
= fromVector . G.fromListN (G.length v) . utc2utL <$> itraversed f (ut2utcL $ G.toList v)
where
v = toVector ts
fromSortedPairList :: TSeries ts a => [(UTCTime, a)] -> ts a
fromSortedPairList = TSU.fromSortedPairList . utc2utL
fromUnsortedPairList :: TSeries ts a => [(UTCTime, a)] -> ts a
fromUnsortedPairList = TSU.fromUnsortedPairList . utc2utL
toPairList :: TSeries ts a => ts a -> [(UTCTime, a)]
toPairList = ut2utcL . TSU.toPairList
data TSLook
= AtOrAfter UTCTime
| After UTCTime
| AtOrBefore UTCTime
| Before UTCTime
deriving (Eq, Show)
tsSearch :: TSeries ts a => ts a -> TSLook -> Int
tsSearch ts l = if before then i 1 else i
where
(before, ut) = case l of
AtOrAfter t -> (False, toUTimeUp t)
After t -> (False, toUTimeUp' t)
AtOrBefore t -> (True, toUTimeUp' t)
Before t -> (True, toUTimeUp t)
i = TSU.tsSearch ts ut
tsLookup :: TSeries ts a => ts a -> TSLook -> Maybe (UTCTime, a)
tsLookup ts l | i >= 0, i < tsLength ts = Just (ts ! i)
| otherwise = Nothing
where
i = tsSearch ts l
tsSlice :: TSeries ts a => ts a
-> TSLook
-> TSLook
-> ts a
tsSlice ts lStart lEnd
| start > end = error "tsSlice: start position later than the end position"
| otherwise = fromVector $ G.slice start (end start) $ toVector ts
where
start = max 0 $ tsSearch ts lStart
end = max 0 $ tsSearch ts lEnd
tsSplitAt :: TSeries ts a => TSLook -> ts a -> (ts a, ts a)
tsSplitAt l ts = (before, after)
where
i = tsSearch ts l
v = toVector ts
(before, after) = G.splitAt i v & both %~ fromVector
data TSInterpolate a =
TSInterpolate
{ tsiBefore :: UTCTime -> (UTCTime, a) -> Maybe (UTCTime, a)
, tsiAfter :: UTCTime -> (UTCTime, a) -> Maybe (UTCTime, a)
, tsiBetween :: UTCTime -> (UTCTime, a) -> (UTCTime, a) -> Maybe (UTCTime, a)
}
| TSInterpolateUT (TSU.TSInterpolate a)
tsi2ut :: TSInterpolate a -> TSU.TSInterpolate a
tsi2ut (TSInterpolateUT interp) = interp
tsi2ut (TSInterpolate before after between) = TSU.TSInterpolate before' after' between'
where
before' t = utc2ut (mapped._1) . before (fromUTime t) . ut2utc _1
after' t = utc2ut (mapped._1) . after (fromUTime t) . ut2utc _1
between' t (t0, a) = utc2ut (mapped._1) . between (fromUTime t) (fromUTime t0, a) . ut2utc _1
interpolateAt :: TSeries ts a => TSInterpolate a
-> ts a
-> UTCTime
-> Maybe (UTCTime, a)
interpolateAt inter ts = ut2utc (mapped._1) . TSU.interpolateAt (tsi2ut inter) ts . toUTime
tsiExtend :: UTCTime -> (UTCTime, a) -> Maybe (UTCTime, a)
tsiExtend t (_, x) = Just (t, x)
tsiNoExtend :: UTCTime -> (UTCTime, a) -> Maybe (UTCTime, a)
tsiNoExtend = const $ const Nothing
interpolateLinear :: Fractional a => TSInterpolate a
interpolateLinear = TSInterpolateUT TSU.interpolateLinear
extendInterpolateLinear :: Fractional a => TSInterpolate a
extendInterpolateLinear = TSInterpolateUT TSU.extendInterpolateLinear
tsGet :: (Fractional a, TSeries ts a) => ts a -> UTCTime -> a
tsGet ts = TSU.tsGet ts . toUTime
data TSMerge a b c =
TSMerge
{ tsmLeft :: UTCTime -> a -> Maybe c
, tsmRight :: UTCTime -> b -> Maybe c
, tsmBoth :: UTCTime -> a -> b -> Maybe c
}
tsm2ut :: TSMerge a b c -> TSU.TSMerge a b c
tsm2ut (TSMerge mleft mright mboth) = TSU.TSMerge mleft' mright' mboth'
where
mleft' = mleft . fromUTime
mright' = mright . fromUTime
mboth' = mboth . fromUTime
tsMerge :: (TSeries ts a, TSeries ts b, TSeries ts c)
=> TSMerge a b c -> ts a -> ts b -> ts c
tsMerge = TSU.tsMerge . tsm2ut
tsMergeWith :: (TSeries ts a, TSeries ts b, TSeries ts c)
=> (UTCTime -> a -> b -> c) -> ts a -> ts b -> ts c
tsMergeWith fboth = TSU.tsMergeWith (fboth . fromUTime)
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
tsMergeEnhance aInterp bInterp fboth
= TSU.tsMergeEnhance (over _2 tsi2ut aInterp) (over _2 tsi2ut bInterp) (fboth . fromUTime)
tsResampleLocal :: TSeries ts a
=> Bool
-> TSInterpolate a
-> [UTCTime]
-> ts a -> ts a
tsResampleLocal keepOriginal interp
= TSU.tsResampleLocal keepOriginal (tsi2ut interp) . map toUTime
extendForward :: TSeries ts a => Bool -> [UTCTime] -> ts a -> ts a
extendForward keepOriginal = TSU.extendForward keepOriginal . map toUTime
extendBackward :: TSeries ts a => Bool -> [UTCTime] -> ts a -> ts a
extendBackward keepOriginal = TSU.extendBackward keepOriginal . map toUTime
tsResampleGlobal :: TSeries ts a
=> (UTCTime -> ts a -> ts a -> Maybe (UTCTime, a))
-> [UTCTime]
-> ts a -> ts a
tsResampleGlobal sample = TSU.tsResampleGlobal sample' . map toUTime
where
sample' t tsl tsr = utc2ut (mapped._1) $ sample (fromUTime t) tsl tsr
tsResampleMoving :: TSeries ts a
=> (UTCTime -> ts a -> Maybe a)
-> Period
-> [UTCTime]
-> ts a -> ts a
tsResampleMoving sample p = TSU.tsResampleMoving (sample . fromUTime) p . map (TSU.justAfter . toUTime)
tsOffsetGeneral :: TSeries ts a
=> (UTCTime -> UTCTime)
-> ts a -> ts a
tsOffsetGeneral f = tsTraversedWithIndex . _1 %~ f
tsOffsetByPeriod :: TSeries ts a
=> Period
-> ts a -> ts a
tsOffsetByPeriod p = tsOffsetGeneral $ periodStep p
tsMapMaybe
:: (TSeries ts a, TSeries ts b)
=> (a -> Maybe b)
-> ts a
-> ts b
tsMapMaybe f
= fromSortedPairList . toListOf (folded . aside _Just) . map (_2 %~ f) . toPairList