{-| Module : Data.Interval.Time Description : Closed intervals on the UTC time axis Copyright : (c) Lackmann Phymetric License : GPL-3 Maintainer : olaf.klinke@phymetric.de Stability : experimental This module defines datatypes for closed intervals with end points on the 'UTCTime' axis. -} {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, KindSignatures, GADTs, DataKinds #-} module Data.Interval.Time ( -- * Time intervals of statically known length MinuteInterval, fromEndTime, ubZoned, -- ** Time intervals of length 10 minutes Min10, until10, -- ** Time intervals of length 15 minutes Min15, until15 ) where import Data.Interval (Interval(..),addTime) import Data.Function (on) import Data.Time (ZonedTime,zonedTimeToUTC,UTCTime,NominalDiffTime) import GHC.TypeLits (Nat,KnownNat,natVal) import Data.Proxy (Proxy(..)) -- * Time intervals of statically known length. -- | Closed time intervals of statically known length in minutes. -- Although such intervals are completely determined by the end time of type 'ZonedTime' -- that was used for construction, -- we cache 'lb' and 'ub' als lazy fields of type 'UTCTime' to speed up 'Interval' queries. -- -- @since 0.2.1 data MinuteInterval (n :: Nat) where Until :: KnownNat n => ZonedTime -> UTCTime -> UTCTime -> MinuteInterval n -- | Retrieve the upper bound that was used in construction, see 'fromEndTime'. ubZoned :: MinuteInterval n -> ZonedTime ubZoned (Until z _ _) = z -- | Time intervals of equal length are considered equal -- if they describe the same interval on the 'UTCTime' axis, -- regardless of time zone. instance Eq (MinuteInterval n) where (==) = (==) `on` ub -- | Intervals of fixed length are ordered by their end time. -- Hence you can put them into a @Set@ or use as keys in a @Map@. instance Ord (MinuteInterval n) where compare = compare `on` ub instance Interval UTCTime (MinuteInterval n) where ub (Until _ _ u) = u lb (Until _ l _) = l beginMinutes :: KnownNat n => Proxy n -> NominalDiffTime beginMinutes = fromInteger . negate . (60*) . natVal -- | Smart constructor. -- -- @ -- 'ub' ('fromEndTime' p z) == 'zonedTimeToUTC' z -- 'ubZoned' ('fromEndTime' p z) == z -- @ fromEndTime :: KnownNat n => Proxy n -> ZonedTime -> MinuteInterval n fromEndTime p z = let u = zonedTimeToUTC z in Until z (addTime (beginMinutes p) u) u -- * Intervals of length 10 Minutes -- | Time intervals of length 10 minutes. -- In logging applications, aggregate values (e.g. averages, sums, ...) -- are often taken over a period of 10 minutes -- and associated with the time -- when the aggregation was computed. -- -- To create your custom aggregate data type, pair this time interval -- with the aggregate value, like follows. -- -- @ -- data SumOver10Minutes s = Aggregate { -- aggregateValue :: s, -- aggregatedOver :: Min10 -- } -- -- instance Interval UTCTime (SumOver10Minutes s) where -- lb = lb.aggregatedOver -- ub = ub.aggregatedOver -- -- compositeAggregate :: (Interval UTCTime i, Monoid s, Foldable f, IntersectionQuery f UTCTime t) => -- i -> t (SumOver10Minutes s) -> s -- compositeAggregate i = foldMap aggregateValue . getProperIntersects i -- @ -- -- @since 0.2.1 type Min10 = MinuteInterval 10 instance Show (MinuteInterval 10) where show i = "until10 " ++ show (ubZoned i) -- | smart constructor until10 :: ZonedTime -> Min10 until10 = fromEndTime (Proxy :: Proxy 10) -- * Intervals of length 15 minutes -- | Time intervals comprising quarter of an hour. -- -- @since 0.2.1 type Min15 = MinuteInterval 15 instance Show (MinuteInterval 15) where show i = "until15 " ++ show (ubZoned i) -- | smart constructor until15 :: ZonedTime -> Min15 until15 = fromEndTime (Proxy :: Proxy 15)