mirror of
https://github.com/facebook/duckling.git
synced 2024-11-28 08:34:46 +03:00
a3b35880e5
Summary: Modified `Entity` to use the new `ResolvedVal` data type. Other changes follow naturally. Related issues: https://github.com/facebook/duckling/issues/121 and https://github.com/facebook/duckling/issues/172 Now one can pattern match on the output value, for instance: ``` {-# LANGUAGE GADTs #-} import Data.Text import Duckling.Core import Duckling.Testing.Types import qualified Duckling.PhoneNumber.Types as PN parsePhoneNumber :: Text -> Text parsePhoneNumber input = case value entity of (RVal PhoneNumber (PN.PhoneNumberValue v)) -> v where (entity:_) = parse input testContext testOptions [This PhoneNumber] ``` Reviewed By: patapizza Differential Revision: D7502020 fbshipit-source-id: 76ba7b315cfd0d2c61ff95c855b7c95efc0a401c
64 lines
1.9 KiB
Haskell
64 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 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
|
|
|
|
-- | Internal time reference.
|
|
-- We work as if we were in UTC time and use `ZoneSeriesTime` to house the info.
|
|
-- We convert to local time at resolution, using `fromUTC`.
|
|
newtype DucklingTime = DucklingTime Series.ZoneSeriesTime
|
|
deriving (Eq, Show)
|
|
|
|
data Context = Context
|
|
{ referenceTime :: DucklingTime
|
|
, locale :: Locale
|
|
}
|
|
deriving (Eq, Show)
|
|
|
|
newtype Options = Options
|
|
{ withLatent :: Bool -- When set, includes less certain parses, e.g. "7" as an hour of the day
|
|
}
|
|
deriving (Eq, 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)
|
|
|
|
-- | Given a UTCTime and an TimeZone, build a ZonedTime (no conversion)
|
|
fromUTC :: Time.UTCTime -> Time.TimeZone -> Time.ZonedTime
|
|
fromUTC (Time.UTCTime day diffTime) timeZone = Time.ZonedTime localTime timeZone
|
|
where
|
|
localTime = Time.LocalTime day timeOfDay
|
|
timeOfDay = Time.timeToTimeOfDay diffTime
|
|
|
|
-- | Given a LocalTime, build a UTCTime (no conversion)
|
|
toUTC :: Time.LocalTime -> Time.UTCTime
|
|
toUTC (Time.LocalTime day timeOfDay) = Time.UTCTime day diffTime
|
|
where
|
|
diffTime = Time.timeOfDayToTime timeOfDay
|