module Data.TimeSeries.Series
( DataPoint
, Series
, Value
, emptySeries
, max
, min
, series
, size
, slice
, tsSeries
, valueAt
) where
import Prelude hiding (max, min)
import Data.Time (UTCTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
type Value = Double
data DataPoint = DP !UTCTime !Value
deriving (Show, Eq)
data Series = Series [DataPoint]
deriving (Show, Eq)
emptySeries :: Series
emptySeries = Series []
series :: [(UTCTime, Double)] -> Series
series xs = Series $ map (\(x, y) -> DP x y) xs
tsSeries :: [Integer] -> [Value] -> Series
tsSeries ts vs = Series (zipWith DP idx vs)
where idx = map (posixSecondsToUTCTime . fromIntegral) ts
size :: Series -> Int
size (Series xs) = length xs
valueAt :: Series -> UTCTime -> Maybe Value
valueAt (Series xs) ts = safeHead [y | DP x y <- xs, x == ts]
where safeHead [] = Nothing
safeHead (a:_) = Just a
slice :: Series -> UTCTime -> UTCTime -> Series
slice (Series xs) start end = Series [DP x y | DP x y <- xs, x >= start && x <= end]
max :: Series -> Value
max (Series xs) = foldl (\d (DP _ y) -> max' d y) 0.0 xs
where max' a b = if a > b then a else b
min :: Series -> Value
min (Series xs) = foldl (\d (DP _ y) -> min' d y) maxValue xs
where min' a b = if a < b then a else b
maxValue = fromIntegral (maxBound :: Int)