{- |
This module defines the 'TimeDomain' class.
Its instances model time,
simulated and realtime.
Several instances such as 'UTCTime', 'Double' and 'Integer' are supplied here.
-}

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}

module Data.TimeDomain
  ( module Data.TimeDomain
  , UTCTime
  )
  where

-- time
import Data.Time.Clock (UTCTime, diffUTCTime, addUTCTime)

{- |
A time domain is an affine space representing a notion of time,
such as real time, simulated time, steps, or a completely different notion.

Expected laws:

* @(t1 `diffTime` t3) `difference` (t1 `diffTime` t2) = t2 `diffTime` t3@
* @(t `addTime` dt) `diffTime` t = dt@
* @(t `addTime` dt1) `addTime` dt2 = t `addTime` (dt1 `add` dt2)@
-}
class TimeDifference (Diff time) => TimeDomain time where
  -- | The type of differences or durations between two timestamps
  type Diff time

  {- | Compute the difference between two timestamps.

  Mnemonic: 'diffTime' behaves like the '(-)' operator:

  @'diffTime' earlier later = later `'diffTime'` earlier@ is the duration it takes from @earlier@ to @later@.
  -}
  diffTime :: time -> time -> Diff time

  {- | Add a time difference to a timestamp.
  -}
  addTime :: time -> Diff time -> time

{- | A type of durations, or differences betweens time stamps.

Expected laws:

* `add` is commutative and associative
* @(dt1 `difference` dt2) `add` dt2 = dt1@
-}
class TimeDifference d where
  -- | Calculate the difference between two durations,
  --   compatibly with 'diffTime'.
  difference :: d -> d -> d

  -- | Add two time differences.
  add :: d -> d -> d

-- | Differences between 'UTCTime's are measured in seconds.
instance TimeDomain UTCTime where
  type Diff UTCTime = Double
  diffTime :: UTCTime -> UTCTime -> Diff UTCTime
diffTime UTCTime
t1 UTCTime
t2 = forall a b. (Real a, Fractional b) => a -> b
realToFrac forall a b. (a -> b) -> a -> b
$ UTCTime -> UTCTime -> NominalDiffTime
diffUTCTime UTCTime
t1 UTCTime
t2
  addTime :: UTCTime -> Diff UTCTime -> UTCTime
addTime = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ NominalDiffTime -> UTCTime -> UTCTime
addUTCTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Real a, Fractional b) => a -> b
realToFrac

instance TimeDifference Double where
  difference :: Double -> Double -> Double
difference = (-)
  add :: Double -> Double -> Double
add = forall a. Num a => a -> a -> a
(+)

instance TimeDomain Double where
  type Diff Double = Double
  diffTime :: Double -> Double -> Diff Double
diffTime = (-)
  addTime :: Double -> Diff Double -> Double
addTime = forall a. Num a => a -> a -> a
(+)

instance TimeDifference Float where
  difference :: Float -> Float -> Float
difference = (-)
  add :: Float -> Float -> Float
add = forall a. Num a => a -> a -> a
(+)

instance TimeDomain Float where
  type Diff Float = Float
  diffTime :: Float -> Float -> Diff Float
diffTime = (-)
  addTime :: Float -> Diff Float -> Float
addTime = forall a. Num a => a -> a -> a
(+)

instance TimeDifference Integer where
  difference :: Integer -> Integer -> Integer
difference = (-)
  add :: Integer -> Integer -> Integer
add = forall a. Num a => a -> a -> a
(+)

instance TimeDomain Integer where
  type Diff Integer = Integer
  diffTime :: Integer -> Integer -> Diff Integer
diffTime = (-)
  addTime :: Integer -> Diff Integer -> Integer
addTime = forall a. Num a => a -> a -> a
(+)

instance TimeDifference () where
  difference :: () -> () -> ()
difference ()
_ ()
_ = ()
  add :: () -> () -> ()
add ()
_ ()
_ = ()

instance TimeDomain () where
  type Diff () = ()
  diffTime :: () -> () -> Diff ()
diffTime ()
_ ()
_ = ()
  addTime :: () -> Diff () -> ()
addTime ()
_ Diff ()
_ = ()

-- | Any 'Num' can be wrapped to form a 'TimeDomain'.
newtype NumTimeDomain a = NumTimeDomain { forall a. NumTimeDomain a -> a
fromNumTimeDomain :: a }
  deriving Integer -> NumTimeDomain a
NumTimeDomain a -> NumTimeDomain a
NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
forall a. Num a => Integer -> NumTimeDomain a
forall a. Num a => NumTimeDomain a -> NumTimeDomain a
forall a.
Num a =>
NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> NumTimeDomain a
$cfromInteger :: forall a. Num a => Integer -> NumTimeDomain a
signum :: NumTimeDomain a -> NumTimeDomain a
$csignum :: forall a. Num a => NumTimeDomain a -> NumTimeDomain a
abs :: NumTimeDomain a -> NumTimeDomain a
$cabs :: forall a. Num a => NumTimeDomain a -> NumTimeDomain a
negate :: NumTimeDomain a -> NumTimeDomain a
$cnegate :: forall a. Num a => NumTimeDomain a -> NumTimeDomain a
* :: NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
$c* :: forall a.
Num a =>
NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
- :: NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
$c- :: forall a.
Num a =>
NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
+ :: NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
$c+ :: forall a.
Num a =>
NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
Num

instance Num a => TimeDifference (NumTimeDomain a) where
  difference :: NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
difference = (-)
  add :: NumTimeDomain a -> NumTimeDomain a -> NumTimeDomain a
add = forall a. Num a => a -> a -> a
(+)

instance Num a => TimeDomain (NumTimeDomain a) where
  type Diff (NumTimeDomain a) = NumTimeDomain a
  diffTime :: NumTimeDomain a -> NumTimeDomain a -> Diff (NumTimeDomain a)
diffTime = (-)
  addTime :: NumTimeDomain a -> Diff (NumTimeDomain a) -> NumTimeDomain a
addTime = forall a. Num a => a -> a -> a
(+)