duckling/Duckling/Core.hs
Ezgi Çiçek 2254034e62 Add Node to Entity to pass along the parse tree information
Summary:
- add `Node` field to `Entity`
- ignore `Node` field of `Entity` for toJSON for now (will be fixed later)
- change `Debug.hs` so that we print the respective Entity's Node
- add wildcard for the new Node field in `parseTest` of Api/Tests.hs`

Reviewed By: patapizza

Differential Revision: D7174696

fbshipit-source-id: 240e4c53b72323b500ac58a74f873ce247bb3387
2018-03-07 10:45:28 -08:00

71 lines
1.9 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE NoRebindableSyntax #-}
-- | Everything needed to run Duckling.
module Duckling.Core
( Context(..)
, Region(..)
, Dimension(..)
, Entity(..)
, Node(..)
, Range(..)
, Lang(..)
, Locale
, Some(..)
, fromName
, makeLocale
, toName
-- Duckling API
, parse
, supportedDimensions
, allLocales
-- Reference time builders
, currentReftime
, fromZonedTime
, makeReftime
) where
import Data.HashMap.Strict (HashMap)
import Data.Maybe
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 = do
utcNow <- getCurrentTime
return $ makeReftime series tz utcNow
-- | Builds a `DucklingTime` from a `ZonedTime`.
fromZonedTime :: ZonedTime -> DucklingTime
fromZonedTime (ZonedTime localTime timeZone) = DucklingTime $
ZoneSeriesTime (toUTC localTime) (TimeZoneSeries timeZone [])