module Data.TimeSeries.UTime (
tsLength,
tsRange,
tsTraversed,
tsTraversedWithIndex,
toPairList,
tsSearch,
firstAfter,
lastBefore,
fromSortedPairList,
fromUnsortedPairList,
fromPeriodicData,
TSInterpolate(..),
interpolateAt,
linearBetween,
tsiExtend,
tsiNoExtend,
interpolateLinear,
extendInterpolateLinear,
tsGet,
tsSlice,
justAfter,
tsSliceByCount,
tsSplitAt,
TSMerge(..),
tsMerge,
tsMergeWith,
tsMergeEnhance,
tsResampleLocal,
extendForward,
extendBackward,
tsResampleGlobal,
tsResampleMoving,
tsOffsetGeneral,
tsOffsetByPeriod,
) where
import Control.Lens
import Data.Bits (shiftR)
import Data.Ord (comparing)
import Data.Maybe (catMaybes, fromJust)
import Data.TimeSeries.Class
import Data.TimeSeries.Periodic
import Data.UTime (UTime(..))
import qualified Data.Vector.Generic as G
import Statistics.Function (sortBy)
tsLength :: TSeries ts a => ts a -> Int
tsLength = G.length . toVector
tsRange :: TSeries ts a => ts a -> Maybe (UTime, UTime)
tsRange ts = case tsLength ts of
0 -> Nothing
_ -> Just (G.head v, G.last v)
where
v = tsTimes ts
tsTraversed :: (TSeries ts a, TSeries ts b) => IndexedTraversal UTime (ts a) (ts b) a b
tsTraversed f ts
= fromVector . G.fromListN (G.length v) <$> traverse (itraversed f) (G.toList v)
where
v = toVector ts
tsTraversedWithIndex :: (TSeries ts a, TSeries ts b)
=> IndexedTraversal Int (ts a) (ts b) (UTime, a) (UTime, b)
tsTraversedWithIndex f ts
= fromVector . G.fromListN (G.length v) <$> itraversed f (G.toList v)
where
v = toVector ts
fromSortedPairList :: TSeries ts a => [(UTime, a)] -> ts a
fromSortedPairList = fromVector . G.fromList
fromUnsortedPairList :: TSeries ts a => [(UTime, a)] -> ts a
fromUnsortedPairList = fromVector . sortBy (comparing fst) . G.fromList
toPairList :: TSeries ts a => ts a -> [(UTime, a)]
toPairList = G.toList . toVector
fromPeriodicData :: TSeries ts a => PeriodicSequence -> [a] -> ts a
fromPeriodicData ps as = fromSortedPairList $ zip (psToUTimeList ps) as
tsSearch :: TSeries ts a => ts a
-> UTime
-> Int
tsSearch ts t | n == 0 = 0
| otherwise = t `seq` go 0 n
where
v = tsTimes ts
n = G.length v
go !l !u | l >= u = l
| G.unsafeIndex v k < t = go (k+1) u
| otherwise = go l k
where
k = (l + u) `shiftR` 1
firstAfter :: TSeries ts a => ts a
-> UTime
-> Maybe (UTime, a)
firstAfter ts t | k < tsLength ts = Just (toVector ts G.! k)
| otherwise = Nothing
where
k = tsSearch ts t
lastBefore :: TSeries ts a => ts a
-> UTime
-> Maybe (UTime, a)
lastBefore ts t | k < n, t == t2 = Just e2
| k > 0 = Just e1
| otherwise = Nothing
where
k = tsSearch ts t
v = toVector ts
n = tsLength ts
e2@(t2, _) = v G.! k
e1 = v G.! (k1)
tsSlice :: TSeries ts a => ts a
-> UTime
-> UTime
-> ts a
tsSlice ts tStart tEnd
| tStart > tEnd = error "tsSlice: start time later than end time"
| otherwise = fromVector $ G.slice start (end start) $ toVector ts
where
start = tsSearch ts tStart
end = tsSearch ts tEnd
justAfter :: UTime -> UTime
justAfter = succ
tsSliceByCount :: TSeries ts a => ts a
-> Int
-> Int
-> ts a
tsSliceByCount ts start end = fromVector $ G.slice start (end start) $ toVector ts
tsSplitAt :: TSeries ts a => UTime -> ts a -> (ts a, ts a)
tsSplitAt t ts = (before, after)
where
i = tsSearch ts t
v = toVector ts
(before, after) = G.splitAt i v & both %~ fromVector
data TSInterpolate a =
TSInterpolate
{ tsiBefore :: UTime -> (UTime, a) -> Maybe (UTime, a)
, tsiAfter :: UTime -> (UTime, a) -> Maybe (UTime, a)
, tsiBetween :: UTime -> (UTime, a) -> (UTime, a) -> Maybe (UTime, a)
}
interpolateAt :: TSeries ts a => TSInterpolate a
-> ts a
-> UTime
-> Maybe (UTime, a)
interpolateAt inter ts t | k < n, t == t2 = Just e2
| k < n, k > 0 = tsiBetween inter t e1 e2
| n > 0, k == 0 = tsiBefore inter t e2
| n > 0, k == n = tsiAfter inter t e1
| otherwise = Nothing
where
k = tsSearch ts t
v = toVector ts
n = tsLength ts
e2@(t2, _) = v G.! k
e1 = v G.! (k1)
linearBetween :: Fractional a => UTime -> (UTime, a) -> (UTime, a)
-> Maybe (UTime, a)
linearBetween ut (ut0, x0) (ut1, x1) = Just (ut, wx / (t1 t0))
where
f (UTime us) = fromIntegral us
t = f ut
t0 = f ut0
t1 = f ut1
wx = x0 * (t1 t) + x1 * (t t0)
tsiExtend :: UTime -> (UTime, a) -> Maybe (UTime, a)
tsiExtend t (_, x) = Just (t, x)
tsiNoExtend :: UTime -> (UTime, a) -> Maybe (UTime, a)
tsiNoExtend = const $ const Nothing
interpolateLinear :: Fractional a => TSInterpolate a
interpolateLinear = TSInterpolate tsiNoExtend tsiNoExtend linearBetween
extendInterpolateLinear :: Fractional a => TSInterpolate a
extendInterpolateLinear = TSInterpolate tsiExtend tsiExtend linearBetween
tsGet :: (Fractional a, TSeries ts a) => ts a -> UTime -> a
tsGet ts = snd . fromJust . interpolateAt extendInterpolateLinear ts
data TSMerge a b c =
TSMerge
{ 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
tsMerge (TSMerge mleft mright mboth) tsa tsb = fromSortedPairList . catMaybes $ go as0 bs0
where
as0 = toPairList tsa
bs0 = toPairList tsb
fleft (t,a) = (t,) <$> mleft t a
fright (t,b) = (t,) <$> mright t b
go as [] = map fleft as
go [] bs = map fright bs
go as@((ta, a) : as') bs@((tb, b) : bs')
| ta < tb = fleft (ta, a) : go as' bs
| ta > tb = fright (tb, b) : go as bs'
| otherwise = ((ta,) <$> mboth ta a b) : go as' bs'
tsMergeWith :: (TSeries ts a, TSeries ts b, TSeries ts c)
=> (UTime -> a -> b -> c) -> ts a -> ts b -> ts c
tsMergeWith fboth tsa tsb = tsMerge merger tsa tsb
where
merger = TSMerge (const $ const Nothing) (const $ const Nothing) mboth
mboth t a b = Just $ fboth t a b
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
tsMergeEnhance aInterp bInterp fboth tsa tsb = tsMergeWith fboth tsaEnhanced tsbEnhanced
where
tsaEnhanced = tsResampleLocal (fst aInterp) (snd aInterp) (G.toList $ tsTimes tsb) tsa
tsbEnhanced = tsResampleLocal (fst bInterp) (snd bInterp) (G.toList $ tsTimes tsa) tsb
tsResampleLocal :: TSeries ts a
=> Bool
-> TSInterpolate a
-> [UTime]
-> ts a -> ts a
tsResampleLocal keepOriginal interp times series
= fromSortedPairList $ catMaybes $ go False (toPairList series) times
where
go _ [] _ = []
go eLast (p : ps) []
| not keepOriginal = []
| otherwise = map Just $ if eLast then ps else p : ps
go eLast ps@(p1@(t1, _) : ps') ts@(t : ts')
| t1 < t, keepOriginal, not eLast = Just p1 : go True ps ts
| t < t1 = tsiBefore interp t p1 : go eLast ps ts'
| t == t1 = Just p1 : go False ps' ts'
| otherwise = case ps' of
[] -> map (flip (tsiAfter interp) p1) ts
(p2@(t2, _) : _)
| t < t2 -> tsiBetween interp t p1 p2 : go eLast ps ts'
| otherwise -> go False ps' ts
extendForward :: TSeries ts a => Bool -> [UTime] -> ts a -> ts a
extendForward keepOriginal = tsResampleLocal keepOriginal interpForward
where
interpForward = TSInterpolate tsiNoExtend tsiExtend keepLeft
keepLeft t (_,x) _ = Just (t, x)
extendBackward :: TSeries ts a => Bool -> [UTime] -> ts a -> ts a
extendBackward keepOriginal = tsResampleLocal keepOriginal interpBackward
where
interpBackward = TSInterpolate tsiExtend tsiNoExtend keepRight
keepRight t _ (_,x) = Just (t, x)
tsResampleGlobal :: TSeries ts a
=> (UTime -> ts a -> ts a -> Maybe (UTime, a))
-> [UTime]
-> ts a -> ts a
tsResampleGlobal sample times series = fromSortedPairList $ catMaybes $ map sliceOn times
where
sliceOn t = sample t before after
where
(before, after) = tsSplitAt t series
tsResampleMoving :: TSeries ts a
=> (UTime -> ts a -> Maybe a)
-> Period
-> [UTime]
-> ts a -> ts a
tsResampleMoving sample p = tsResampleGlobal gSample
where
gSample t before _ = (t,) <$> sample t window
where
(_, window) = tsSplitAt (periodStepBackUTime p t) before
tsOffsetGeneral :: TSeries ts a
=> (UTime -> UTime)
-> ts a -> ts a
tsOffsetGeneral f = tsTraversedWithIndex . _1 %~ f
tsOffsetByPeriod :: TSeries ts a
=> Period
-> ts a -> ts a
tsOffsetByPeriod p = tsOffsetGeneral $ periodStepUTime p