{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
module Duckling.Resolve
( Context(..)
, DucklingTime(..)
, Options(..)
, Resolve(..)
, fromUTC
, toUTC
) where
import Data.Aeson (ToJSON)
import Prelude
import qualified Data.Time as Time
import qualified Data.Time.LocalTime.TimeZone.Series as Series
import Duckling.Locale
newtype DucklingTime = DucklingTime Series.ZoneSeriesTime
deriving (DucklingTime -> DucklingTime -> Bool
(DucklingTime -> DucklingTime -> Bool)
-> (DucklingTime -> DucklingTime -> Bool) -> Eq DucklingTime
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DucklingTime -> DucklingTime -> Bool
$c/= :: DucklingTime -> DucklingTime -> Bool
== :: DucklingTime -> DucklingTime -> Bool
$c== :: DucklingTime -> DucklingTime -> Bool
Eq, Int -> DucklingTime -> ShowS
[DucklingTime] -> ShowS
DucklingTime -> String
(Int -> DucklingTime -> ShowS)
-> (DucklingTime -> String)
-> ([DucklingTime] -> ShowS)
-> Show DucklingTime
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DucklingTime] -> ShowS
$cshowList :: [DucklingTime] -> ShowS
show :: DucklingTime -> String
$cshow :: DucklingTime -> String
showsPrec :: Int -> DucklingTime -> ShowS
$cshowsPrec :: Int -> DucklingTime -> ShowS
Show)
data Context = Context
{ Context -> DucklingTime
referenceTime :: DucklingTime
, Context -> Locale
locale :: Locale
}
deriving (Context -> Context -> Bool
(Context -> Context -> Bool)
-> (Context -> Context -> Bool) -> Eq Context
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Context -> Context -> Bool
$c/= :: Context -> Context -> Bool
== :: Context -> Context -> Bool
$c== :: Context -> Context -> Bool
Eq, Int -> Context -> ShowS
[Context] -> ShowS
Context -> String
(Int -> Context -> ShowS)
-> (Context -> String) -> ([Context] -> ShowS) -> Show Context
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Context] -> ShowS
$cshowList :: [Context] -> ShowS
show :: Context -> String
$cshow :: Context -> String
showsPrec :: Int -> Context -> ShowS
$cshowsPrec :: Int -> Context -> ShowS
Show)
newtype Options = Options
{ Options -> Bool
withLatent :: Bool
}
deriving (Options -> Options -> Bool
(Options -> Options -> Bool)
-> (Options -> Options -> Bool) -> Eq Options
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Options -> Options -> Bool
$c/= :: Options -> Options -> Bool
== :: Options -> Options -> Bool
$c== :: Options -> Options -> Bool
Eq, Int -> Options -> ShowS
[Options] -> ShowS
Options -> String
(Int -> Options -> ShowS)
-> (Options -> String) -> ([Options] -> ShowS) -> Show Options
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Options] -> ShowS
$cshowList :: [Options] -> ShowS
show :: Options -> String
$cshow :: Options -> String
showsPrec :: Int -> Options -> ShowS
$cshowsPrec :: Int -> Options -> ShowS
Show)
class ( Eq (ResolvedValue a)
, Show (ResolvedValue a)
, ToJSON (ResolvedValue a)
) => Resolve a where
type ResolvedValue a
resolve :: Context -> Options -> a -> Maybe (ResolvedValue a, Bool)
fromUTC :: Time.UTCTime -> Time.TimeZone -> Time.ZonedTime
fromUTC :: UTCTime -> TimeZone -> ZonedTime
fromUTC (Time.UTCTime Day
day DiffTime
diffTime) TimeZone
timeZone = LocalTime -> TimeZone -> ZonedTime
Time.ZonedTime LocalTime
localTime TimeZone
timeZone
where
localTime :: LocalTime
localTime = Day -> TimeOfDay -> LocalTime
Time.LocalTime Day
day TimeOfDay
timeOfDay
timeOfDay :: TimeOfDay
timeOfDay = DiffTime -> TimeOfDay
Time.timeToTimeOfDay DiffTime
diffTime
toUTC :: Time.LocalTime -> Time.UTCTime
toUTC :: LocalTime -> UTCTime
toUTC (Time.LocalTime Day
day TimeOfDay
timeOfDay) = Day -> DiffTime -> UTCTime
Time.UTCTime Day
day DiffTime
diffTime
where
diffTime :: DiffTime
diffTime = TimeOfDay -> DiffTime
Time.timeOfDayToTime TimeOfDay
timeOfDay