{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Core
( Context(..)
, Dimension(..)
, Entity(..)
, Lang(..)
, Locale
, Node(..)
, Options(..)
, Range(..)
, Region(..)
, Some(..)
, fromName
, makeLocale
, toName
, parse
, supportedDimensions
, allLocales
, currentReftime
, fromZonedTime
, makeReftime
) where
import Data.HashMap.Strict (HashMap)
import Data.Text (Text)
import Data.Time
import Data.Time.LocalTime.TimeZone.Series
import Prelude
import qualified Data.HashMap.Strict as HashMap
import Duckling.Api
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Resolve
import Duckling.Types
makeReftime :: HashMap Text TimeZoneSeries -> Text -> UTCTime -> DucklingTime
makeReftime series tz utcTime = DucklingTime $ ZoneSeriesTime ducklingTime tzs
where
tzs = HashMap.lookupDefault (TimeZoneSeries utc []) tz series
ducklingTime = toUTC $ utcToLocalTime' tzs utcTime
currentReftime :: HashMap Text TimeZoneSeries -> Text -> IO DucklingTime
currentReftime series tz = do
utcNow <- getCurrentTime
return $ makeReftime series tz utcNow
fromZonedTime :: ZonedTime -> DucklingTime
fromZonedTime (ZonedTime localTime timeZone) = DucklingTime $
ZoneSeriesTime (toUTC localTime) (TimeZoneSeries timeZone [])