{-# options_ghc -fno-warn-orphans #-}
{-# options_haddock prune, hide #-}
module Polysemy.Chronos.Orphans where
import qualified Chronos as Chronos
import Chronos (
Date (Date),
Datetime (Datetime),
DayOfMonth (DayOfMonth),
Month (Month),
Time,
TimeOfDay (TimeOfDay),
Timespan (Timespan),
Year (Year),
datetimeToTime,
timeToDatetime,
)
import Polysemy.Time.Calendar (
Calendar (..),
HasDate (..),
HasDay (..),
HasHour (..),
HasMinute (..),
HasMonth (..),
HasNanoSecond (..),
HasSecond (..),
HasYear (..),
)
import Polysemy.Time.Class.Instant (Instant (dateTime))
import Polysemy.Time.Data.TimeUnit (
Days (Days),
Hours (Hours),
Minutes (Minutes),
Months (Months),
NanoSeconds (NanoSeconds),
TimeUnit (..),
Years (Years),
convert,
)
import Prelude hiding (second)
instance HasDate Time Date where
date :: Time -> Date
date =
Datetime -> Date
Chronos.datetimeDate (Datetime -> Date) -> (Time -> Datetime) -> Time -> Date
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Time -> Datetime
Chronos.timeToDatetime
dateToTime :: Date -> Time
dateToTime Date
d =
Datetime -> Time
Chronos.datetimeToTime (Date -> TimeOfDay -> Datetime
Datetime Date
d (Int -> Int -> Int64 -> TimeOfDay
TimeOfDay Int
0 Int
0 Int64
0))
instance HasYear Date where
year :: Date -> Years
year (Date (Chronos.Year Int
y) Month
_ DayOfMonth
_) =
Int64 -> Years
Years (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
y)
instance HasYear Datetime where
year :: Datetime -> Years
year (Datetime Date
d TimeOfDay
_) =
Date -> Years
forall t. HasYear t => t -> Years
year Date
d
instance HasYear Time where
year :: Time -> Years
year =
Datetime -> Years
forall t. HasYear t => t -> Years
year (Datetime -> Years) -> (Time -> Datetime) -> Time -> Years
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Time -> Datetime
Chronos.timeToDatetime
instance HasMonth Date where
month :: Date -> Months
month (Date Year
_ (Chronos.Month Int
m) DayOfMonth
_) =
Int64 -> Months
Months (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m)
instance HasMonth Datetime where
month :: Datetime -> Months
month (Datetime Date
d TimeOfDay
_) =
Date -> Months
forall t. HasMonth t => t -> Months
month Date
d
instance HasMonth Time where
month :: Time -> Months
month =
Datetime -> Months
forall t. HasMonth t => t -> Months
month (Datetime -> Months) -> (Time -> Datetime) -> Time -> Months
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Time -> Datetime
Chronos.timeToDatetime
instance HasDay Date where
day :: Date -> Days
day (Date Year
_ Month
_ (Chronos.DayOfMonth Int
d)) =
Int64 -> Days
Days (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
d)
instance HasDay Datetime where
day :: Datetime -> Days
day (Datetime Date
d TimeOfDay
_) =
Date -> Days
forall t. HasDay t => t -> Days
day Date
d
instance HasDay Time where
day :: Time -> Days
day =
Datetime -> Days
forall t. HasDay t => t -> Days
day (Datetime -> Days) -> (Time -> Datetime) -> Time -> Days
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Time -> Datetime
Chronos.timeToDatetime
instance HasHour TimeOfDay where
hour :: TimeOfDay -> Hours
hour (TimeOfDay Int
h Int
_ Int64
_) =
Int64 -> Hours
Hours (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
h)
instance HasHour Datetime where
hour :: Datetime -> Hours
hour (Datetime Date
_ TimeOfDay
t) =
TimeOfDay -> Hours
forall t. HasHour t => t -> Hours
hour TimeOfDay
t
instance HasHour Time where
hour :: Time -> Hours
hour =
Datetime -> Hours
forall t. HasHour t => t -> Hours
hour (Datetime -> Hours) -> (Time -> Datetime) -> Time -> Hours
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Time -> Datetime
Chronos.timeToDatetime
instance HasMinute TimeOfDay where
minute :: TimeOfDay -> Minutes
minute (TimeOfDay Int
_ Int
m Int64
_) =
Int64 -> Minutes
Minutes (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m)
instance HasMinute Datetime where
minute :: Datetime -> Minutes
minute (Datetime Date
_ TimeOfDay
t) =
TimeOfDay -> Minutes
forall t. HasMinute t => t -> Minutes
minute TimeOfDay
t
instance HasMinute Time where
minute :: Time -> Minutes
minute =
Datetime -> Minutes
forall t. HasMinute t => t -> Minutes
minute (Datetime -> Minutes) -> (Time -> Datetime) -> Time -> Minutes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Time -> Datetime
Chronos.timeToDatetime
instance HasNanoSecond TimeOfDay where
nanoSecond :: TimeOfDay -> NanoSeconds
nanoSecond (TimeOfDay Int
_ Int
_ Int64
s) =
Int64 -> NanoSeconds
NanoSeconds Int64
s
instance HasNanoSecond Datetime where
nanoSecond :: Datetime -> NanoSeconds
nanoSecond (Datetime Date
_ TimeOfDay
t) =
TimeOfDay -> NanoSeconds
forall t. HasNanoSecond t => t -> NanoSeconds
nanoSecond TimeOfDay
t
instance HasNanoSecond Time where
nanoSecond :: Time -> NanoSeconds
nanoSecond =
Datetime -> NanoSeconds
forall t. HasNanoSecond t => t -> NanoSeconds
nanoSecond (Datetime -> NanoSeconds)
-> (Time -> Datetime) -> Time -> NanoSeconds
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Time -> Datetime
Chronos.timeToDatetime
instance HasSecond TimeOfDay where
second :: TimeOfDay -> Seconds
second TimeOfDay
t =
NanoSeconds -> Seconds
forall a b. (TimeUnit a, TimeUnit b) => a -> b
convert (TimeOfDay -> NanoSeconds
forall t. HasNanoSecond t => t -> NanoSeconds
nanoSecond TimeOfDay
t)
instance HasSecond Datetime where
second :: Datetime -> Seconds
second (Datetime Date
_ TimeOfDay
t) =
TimeOfDay -> Seconds
forall t. HasSecond t => t -> Seconds
second TimeOfDay
t
instance HasSecond Time where
second :: Time -> Seconds
second =
Datetime -> Seconds
forall t. HasSecond t => t -> Seconds
second (Datetime -> Seconds) -> (Time -> Datetime) -> Time -> Seconds
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Time -> Datetime
Chronos.timeToDatetime
instance Calendar Datetime where
type CalendarDate Datetime = Date
type CalendarTime Datetime = TimeOfDay
mkDate :: Int64 -> Int64 -> Int64 -> CalendarDate Datetime
mkDate Int64
y Int64
m Int64
d =
Year -> Month -> DayOfMonth -> Date
Date (Int -> Year
Year (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
y)) (Int -> Month
Month (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
m Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)) (Int -> DayOfMonth
DayOfMonth (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
d))
mkTime :: Int64 -> Int64 -> Int64 -> CalendarTime Datetime
mkTime Int64
h Int64
m Int64
s =
Int -> Int -> Int64 -> TimeOfDay
TimeOfDay (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
h) (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
m) (Int64
s Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
* Int64
1000000000)
mkDatetime :: Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> Int64 -> Datetime
mkDatetime Int64
y Int64
mo Int64
d Int64
h Int64
mi Int64
s =
Date -> TimeOfDay -> Datetime
Datetime (forall dt.
Calendar dt =>
Int64 -> Int64 -> Int64 -> CalendarDate dt
mkDate @Datetime Int64
y Int64
mo Int64
d) (forall dt.
Calendar dt =>
Int64 -> Int64 -> Int64 -> CalendarTime dt
mkTime @Datetime Int64
h Int64
mi Int64
s)
instance TimeUnit Timespan where
nanos :: NanoSeconds
nanos =
NanoSeconds
1
toNanos :: Timespan -> NanoSeconds
toNanos (Timespan Int64
ns) =
Int64 -> NanoSeconds
NanoSeconds Int64
ns
fromNanos :: NanoSeconds -> Timespan
fromNanos (NanoSeconds Int64
ns) =
Int64 -> Timespan
Timespan Int64
ns
instance Instant Chronos.Time Chronos.Time where
dateTime :: Time -> Time
dateTime =
Time -> Time
forall a. a -> a
id
instance Instant Chronos.Datetime Chronos.Time where
dateTime :: Datetime -> Time
dateTime =
Datetime -> Time
datetimeToTime