module Data.TimeSeries.Series
( DataPoint
, Series
, dpIndex
, dpValue
, emptySeries
, rolling
, resample
, series
, size
, slice
, toList
, tsSeries
, valueAt
, values
) where
import Prelude hiding (max, min)
import Data.Time (UTCTime, NominalDiffTime, diffUTCTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Data.TimeSeries.Time (TimeResolution, nextTime)
data DataPoint a = DP { dpIndex :: !UTCTime
, dpValue :: a }
deriving (Show, Eq)
instance Functor DataPoint where
fmap f (DP x y) = DP x (f y)
instance Foldable DataPoint where
foldMap f (DP _ y) = f y
data Series a = Series [DataPoint a]
deriving (Show, Eq)
instance Functor Series where
fmap f (Series xs) = Series (map (fmap f) xs)
instance Foldable Series where
foldMap f (Series xs) = foldMap (foldMap f) xs
length = size
emptySeries :: Series a
emptySeries = Series []
series :: [(UTCTime, a)] -> Series a
series xs = Series $ map (\(x, y) -> DP x y) xs
tsSeries :: [Integer]
-> [a]
-> Series a
tsSeries ts vs = Series (zipWith DP idx vs)
where idx = map (posixSecondsToUTCTime . fromIntegral) ts
toList :: Series a -> [(UTCTime, a)]
toList (Series xs) = map (\(DP x y) -> (x, y)) xs
values :: Series a -> [a]
values ts = map (\(_, y) -> y) (toList ts)
size :: Series a -> Int
size (Series xs) = length xs
valueAt :: UTCTime
-> Series a
-> Maybe a
valueAt ts (Series xs) = safeHead [y | DP x y <- xs, x == ts]
where safeHead [] = Nothing
safeHead (i:_) = Just i
slice :: UTCTime
-> UTCTime
-> Series a
-> Series a
slice start end (Series xs) = Series [DP x y | DP x y <- xs, x >= start && x <= end]
rolling :: NominalDiffTime
-> ([a] -> b)
-> Series a
-> Series b
rolling dt f (Series xs) = Series $ map (\(i, vs) -> DP i (f vs)) (windows dt xs)
windows :: NominalDiffTime -> [DataPoint a] -> [(UTCTime, [a])]
windows _ [] = []
windows dt xs = g ys : if length xs > length ys then windows dt (tail xs) else []
where
ys = takeWhile (isInTimeRange dt (head xs)) xs
g vs = (dpIndex (last vs), values (Series vs))
isInTimeRange :: NominalDiffTime -> DataPoint a -> DataPoint a -> Bool
isInTimeRange dt (DP i _) (DP j _) = diffUTCTime j i < dt
resample :: UTCTime
-> TimeResolution
-> ([a] -> b)
-> Series a
-> Series b
resample utc res f (Series xs) = Series (map (\(i, vs) -> DP i (f (g vs))) (resample' utc res xs))
where
g :: [DataPoint a] -> [a]
g = map dpValue
resample' :: UTCTime -> TimeResolution -> [DataPoint a] -> [(UTCTime, [DataPoint a])]
resample' _ _ [] = []
resample' utc res xs = (utc, ys) : resample' utc2 res zs
where
utc2 = nextTime res utc
(ys, zs) = break (\(DP x _) -> x >= utc2) xs