{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Time.Series
( AllTimes
#if ( __GLASGOW_HASKELL__ >= 804 )
, type (...)
#endif
, SeriesF (..)
, unitsF
, SeriesP (..)
, unitsP
) where
import Data.Char (isDigit, isLetter)
import Data.Semigroup ((<>))
import Text.Read (readMaybe)
#if ( __GLASGOW_HASKELL__ >= 804 )
import Data.Kind (Constraint)
import Data.Type.Bool (type (&&), If)
import Data.Type.Equality (type (==))
import GHC.TypeLits (TypeError, ErrorMessage (Text))
import Time.Rational (type (>=%), withRuntimeDivRat)
#endif
import Time.Rational (Rat)
import Time.Units (Day, Fortnight, Hour, KnownRatName, Microsecond, Millisecond, Minute, Nanosecond,
Picosecond, Second, Time (..), Week, floorUnit, toUnit)
import Time.Timestamp ((-:-))
type AllTimes =
'[ Fortnight, Week, Day, Hour, Minute, Second
, Millisecond , Microsecond, Nanosecond, Picosecond
]
#if ( __GLASGOW_HASKELL__ >= 804 )
type family (from :: Rat) ... (to :: Rat) :: [Rat] where
from ... to = If (IsDescending '[from, to])
(TakeWhileNot to (DropWhileNot from AllTimes))
(TypeError ('Text "Units should be in descending order"))
type family DropWhileNot (from :: Rat) (units :: [Rat]) :: [Rat] where
DropWhileNot x '[] = '[]
DropWhileNot x (u ': units) = If (u == x) (u ': units) (DropWhileNot x units)
type family TakeWhileNot (to :: Rat) (units :: [Rat]) :: [Rat] where
TakeWhileNot x '[] = '[]
TakeWhileNot x (u ': units) = If (u == x) '[u] (u ': TakeWhileNot x units)
type family IsDescending (units :: [Rat]) :: Bool where
IsDescending ('[]) = 'True
IsDescending ('[unit]) = 'True
IsDescending (unit1 ': unit2 ': units) =
(unit1 >=% unit2) && (IsDescending (unit2 ': units))
type family DescendingConstraint (b :: Bool) :: Constraint where
DescendingConstraint 'True = ()
DescendingConstraint 'False = TypeError ('Text "List of units should be in descending order")
#endif
class SeriesF (units :: [Rat]) where
seriesF :: forall (someUnit :: Rat) . KnownRatName someUnit
=> Time someUnit
-> String
instance SeriesF ('[] :: [Rat]) where
seriesF :: Time someUnit -> String
seriesF _ = ""
instance (KnownRatName unit) => SeriesF ('[unit] :: [Rat]) where
seriesF :: forall (someUnit :: Rat) . KnownRatName someUnit
=> Time someUnit -> String
seriesF t =
#if ( __GLASGOW_HASKELL__ >= 804 )
let newTime = withRuntimeDivRat @someUnit @unit $ toUnit @unit t
#else
let newTime = toUnit @unit t
#endif
in show newTime
instance ( KnownRatName unit
, SeriesF (nextUnit : units)
#if ( __GLASGOW_HASKELL__ >= 804 )
, DescendingConstraint (IsDescending (unit ': nextUnit ': units))
#endif
)
=> SeriesF (unit ': nextUnit ': units :: [Rat]) where
seriesF :: forall (someUnit :: Rat) . KnownRatName someUnit
=> Time someUnit -> String
#if ( __GLASGOW_HASKELL__ >= 804 )
seriesF t = let newUnit = withRuntimeDivRat @someUnit @unit $ toUnit @unit t
#else
seriesF t = let newUnit = toUnit @unit t
#endif
flooredNewUnit = floorUnit newUnit
timeStr = case flooredNewUnit of
Time 0 -> ""
_ -> show flooredNewUnit
#if ( __GLASGOW_HASKELL__ >= 804 )
nextUnit = withRuntimeDivRat @unit @unit $ newUnit -:- flooredNewUnit
#else
nextUnit = newUnit -:- flooredNewUnit
#endif
in if nextUnit == Time 0
then show newUnit
else timeStr ++ seriesF @(nextUnit ': units) @unit nextUnit
unitsF :: forall unit . KnownRatName unit => Time unit -> String
unitsF = seriesF @AllTimes
class SeriesP (units :: [Rat]) where
seriesP :: forall (someUnit :: Rat) . KnownRatName someUnit
=> String -> Maybe (Time someUnit)
instance SeriesP '[] where
seriesP _ = Nothing
instance (KnownRatName unit) => SeriesP '[unit] where
seriesP :: forall (someUnit :: Rat) . KnownRatName someUnit
=> String -> Maybe (Time someUnit)
seriesP "" = Just $ Time 0
seriesP str = readMaybeTime @unit str
instance ( KnownRatName unit
, SeriesP (nextUnit : units)
#if ( __GLASGOW_HASKELL__ >= 804 )
, DescendingConstraint (IsDescending (unit ': nextUnit ': units))
#endif
)
=> SeriesP (unit ': nextUnit ': units :: [Rat]) where
seriesP :: forall (someUnit :: Rat) . KnownRatName someUnit
=> String -> Maybe (Time someUnit)
seriesP "" = Just $ Time 0
seriesP str = let (num, rest) = span isDigit str
(u, nextStr) = span isLetter rest
maybeT = readMaybeTime @unit $ num ++ u
in case maybeT of
Nothing -> seriesP @(nextUnit ': units) str
Just t -> ((t <>)) <$> (seriesP @(nextUnit ': units) nextStr)
unitsP :: forall unit . KnownRatName unit => String -> Maybe (Time unit)
unitsP = seriesP @AllTimes @unit
readMaybeTime :: forall (unit :: Rat) (someUnit :: Rat) . (KnownRatName unit, KnownRatName someUnit)
=> String -> Maybe (Time someUnit)
readMaybeTime str =
#if ( __GLASGOW_HASKELL__ >= 804 )
withRuntimeDivRat @unit @someUnit $
#endif
toUnit @someUnit <$> (readMaybe @(Time unit) str)