duckling/Duckling/Core.hs
Steven Troxler eba5d0a825 Simple style fixes for outer layers around Engine.hs
Summary:
Easy style fixes for ExampleMain.hs, Debug.hs, Api.hs, Core.hs

Most of these are just lint fixes, but I also made a few not-just-lint changes
to conform to some elements of our style guide that I agree with:
- if the type signature doesn't fit on one line, then put one type per line
  with nothing on the first line, so that all types are vertically aligned - makes
  for a quick skim
- try to avoid mixing same-line function args with hanging function args: hang
  all arguments or none at all to get a more outline-like feel, again better for
  skimming

I was actually able to eliminate all errors for most of these modules - the name
collisions I usually give up on were manageable by hiding + easy variable renames

Reviewed By: chessai

Differential Revision: D28213246

fbshipit-source-id: 1f77d56f2ff8dccfd5f3b534f087c07047b92885
2021-05-06 08:54:56 -07:00

71 lines
1.8 KiB
Haskell

-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree.
{-# LANGUAGE NoRebindableSyntax #-}
-- | Everything needed to run Duckling.
module Duckling.Core
( Context(..)
, Dimension(..)
, Entity(..)
, Lang(..)
, Locale
, Node(..)
, Options(..)
, Range(..)
, Region(..)
, ResolvedVal(..)
, Seal(..)
, withSeal
, fromName
, makeLocale
, toJText
, toName
-- Duckling API
, parse
, supportedDimensions
, allLocales
-- Reference time builders
, 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
-- | Builds a `DucklingTime` for timezone `tz` at `utcTime`.
-- If no `series` found for `tz`, uses UTC.
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
-- | Builds a `DucklingTime` for timezone `tz` at current time.
-- If no `series` found for `tz`, uses UTC.
currentReftime :: HashMap Text TimeZoneSeries -> Text -> IO DucklingTime
currentReftime series tz = makeReftime series tz <$> getCurrentTime
-- | Builds a `DucklingTime` from a `ZonedTime`.
fromZonedTime :: ZonedTime -> DucklingTime
fromZonedTime (ZonedTime localTime timeZone) = DucklingTime $
ZoneSeriesTime (toUTC localTime) (TimeZoneSeries timeZone [])