mirror of
https://github.com/facebook/duckling.git
synced 2025-01-07 06:19:10 +03:00
latent entities
Summary: Adding latent matching rules. Matching Numerical to QuantityData with Unnamed as unit Reviewed By: chinmay87 Differential Revision: D17225711 fbshipit-source-id: 8e423454e5e7b83eb8de4cabfd4f85a2a35b7a6d
This commit is contained in:
parent
721e3f48db
commit
70681e3302
@ -8,17 +8,37 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Duckling.Quantity.EN.Corpus
|
||||
( corpus ) where
|
||||
( corpus
|
||||
, latentCorpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Quantity.Types
|
||||
import Duckling.Resolve (Options(..))
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext, testOptions, allExamples)
|
||||
|
||||
|
||||
latentCorpus :: Corpus
|
||||
latentCorpus = (testContext, testOptions {withLatent = True}, latentExamples)
|
||||
where
|
||||
latentExamples = concat
|
||||
[
|
||||
examples (simple Unnamed 4 Nothing)
|
||||
[ "around 4"
|
||||
, "four"
|
||||
, "~ four"
|
||||
]
|
||||
,
|
||||
examples (simple Unnamed 38.5 Nothing)
|
||||
[ "about 38.5"
|
||||
]
|
||||
]
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (simple Pound 2 (Just "meat"))
|
||||
|
@ -219,6 +219,19 @@ ruleIntervalMin = Rule
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleQuantityLatent :: Rule
|
||||
ruleQuantityLatent = Rule
|
||||
{ name = "<quantity> (latent)"
|
||||
, pattern =
|
||||
[ Predicate isPositive
|
||||
]
|
||||
, prod = \case
|
||||
(Token Numeral NumeralData{TNumeral.value = v}: _) ->
|
||||
Just $ (Token Quantity . mkLatent) $ valueOnly v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleQuantityOfProduct
|
||||
@ -229,6 +242,7 @@ rules =
|
||||
, ruleIntervalNumeralDash
|
||||
, ruleIntervalDash
|
||||
, rulePrecision
|
||||
, ruleQuantityLatent
|
||||
]
|
||||
++ ruleNumeralQuantities
|
||||
++ ruleAQuantity
|
||||
|
@ -12,12 +12,14 @@ module Duckling.Quantity.Helpers
|
||||
, isSimpleQuantity
|
||||
, quantity
|
||||
, unitOnly
|
||||
, valueOnly
|
||||
, withProduct
|
||||
, withUnit
|
||||
, withValue
|
||||
, withInterval
|
||||
, withMin
|
||||
, withMax
|
||||
, mkLatent
|
||||
) where
|
||||
|
||||
import Data.HashMap.Strict (HashMap)
|
||||
@ -51,14 +53,24 @@ quantity u v = QuantityData {TQuantity.unit = Just u
|
||||
, TQuantity.value = Just v
|
||||
, TQuantity.aproduct = Nothing
|
||||
, TQuantity.minValue = Nothing
|
||||
, TQuantity.maxValue = Nothing}
|
||||
, TQuantity.maxValue = Nothing
|
||||
, TQuantity.latent = False}
|
||||
|
||||
unitOnly :: TQuantity.Unit -> QuantityData
|
||||
unitOnly u = QuantityData {TQuantity.unit = Just u
|
||||
, TQuantity.value = Nothing
|
||||
, TQuantity.aproduct = Nothing
|
||||
, TQuantity.minValue = Nothing
|
||||
, TQuantity.maxValue = Nothing}
|
||||
, TQuantity.maxValue = Nothing
|
||||
, TQuantity.latent = False}
|
||||
|
||||
valueOnly :: Double -> QuantityData
|
||||
valueOnly v = QuantityData {TQuantity.unit = Nothing
|
||||
, TQuantity.value = Just v
|
||||
, TQuantity.aproduct = Nothing
|
||||
, TQuantity.minValue = Nothing
|
||||
, TQuantity.maxValue = Nothing
|
||||
, TQuantity.latent = False}
|
||||
|
||||
withProduct :: Text -> QuantityData -> QuantityData
|
||||
withProduct p qd = qd {TQuantity.aproduct = Just p}
|
||||
@ -77,3 +89,6 @@ withMin from qd = qd {minValue = Just from}
|
||||
|
||||
withMax :: Double -> QuantityData -> QuantityData
|
||||
withMax to qd = qd {maxValue = Just to}
|
||||
|
||||
mkLatent :: QuantityData -> QuantityData
|
||||
mkLatent qd = qd {TQuantity.latent = True}
|
||||
|
@ -10,18 +10,20 @@
|
||||
{-# LANGUAGE NoRebindableSyntax #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
|
||||
module Duckling.Quantity.Types where
|
||||
|
||||
import Control.DeepSeq
|
||||
import Data.Aeson
|
||||
import qualified Data.HashMap.Strict as H
|
||||
import Data.Hashable
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as Text
|
||||
import Duckling.Resolve
|
||||
( Resolve(..)
|
||||
, Options(..)
|
||||
)
|
||||
import GHC.Generics
|
||||
import Prelude
|
||||
import Duckling.Resolve (Resolve(..))
|
||||
import qualified Data.HashMap.Strict as H
|
||||
import qualified Data.Text as Text
|
||||
|
||||
data Unit
|
||||
= Bowl
|
||||
@ -48,48 +50,57 @@ data QuantityData = QuantityData
|
||||
, aproduct :: Maybe Text
|
||||
, minValue :: Maybe Double
|
||||
, maxValue :: Maybe Double
|
||||
, latent :: Bool
|
||||
} deriving (Eq, Generic, Hashable, Ord, Show, NFData)
|
||||
|
||||
|
||||
instance Resolve QuantityData where
|
||||
type ResolvedValue QuantityData = QuantityValue
|
||||
resolve _ Options {withLatent = False} QuantityData {latent = True}
|
||||
= Nothing
|
||||
|
||||
resolve _ _ QuantityData {value = Just value
|
||||
, unit = Nothing
|
||||
, aproduct = aproduct
|
||||
, latent = latent}
|
||||
= Just (simple Unnamed value aproduct, latent)
|
||||
|
||||
resolve _ _ QuantityData {value = Just value
|
||||
, unit = Just unit
|
||||
, aproduct = aproduct}
|
||||
= Just (simple unit value aproduct, False)
|
||||
, aproduct = aproduct
|
||||
, latent = latent}
|
||||
= Just (simple unit value aproduct, latent)
|
||||
|
||||
resolve _ _ QuantityData {value = Nothing
|
||||
, unit = Just unit
|
||||
, aproduct = aproduct
|
||||
, minValue = Just from
|
||||
, maxValue = Just to}
|
||||
= Just (between unit (from, to) aproduct, False)
|
||||
, maxValue = Just to
|
||||
, latent = latent}
|
||||
= Just (between unit (from, to) aproduct, latent)
|
||||
|
||||
resolve _ _ QuantityData {value = Nothing
|
||||
, unit = Just unit
|
||||
, aproduct = aproduct
|
||||
, minValue = Just from
|
||||
, maxValue = Nothing}
|
||||
= Just (above unit from aproduct, False)
|
||||
, maxValue = Nothing
|
||||
, latent = latent}
|
||||
= Just (above unit from aproduct, latent)
|
||||
|
||||
resolve _ _ QuantityData {value = Nothing
|
||||
, unit = Just unit
|
||||
, aproduct = aproduct
|
||||
, minValue = Nothing
|
||||
, maxValue = Just to}
|
||||
= Just (under unit to aproduct, False)
|
||||
, maxValue = Just to
|
||||
, latent = latent}
|
||||
= Just (under unit to aproduct, latent)
|
||||
|
||||
resolve _ _ _ = Nothing
|
||||
|
||||
data IntervalDirection = Above | Under
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, NFData)
|
||||
|
||||
data SingleValue = SingleValue
|
||||
{ vUnit :: Unit
|
||||
, vValue :: Double
|
||||
, vProduct :: Maybe Text
|
||||
}
|
||||
data SingleValue =
|
||||
SingleValue { vUnit :: Unit, vValue :: Double, vProduct :: Maybe Text }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, NFData)
|
||||
|
||||
instance ToJSON SingleValue where
|
||||
@ -99,7 +110,6 @@ instance ToJSON SingleValue where
|
||||
]
|
||||
++ [ "product" .= p | Just p <- [aproduct] ]
|
||||
|
||||
|
||||
data QuantityValue
|
||||
= SimpleValue SingleValue
|
||||
| IntervalValue (SingleValue, SingleValue)
|
||||
@ -123,6 +133,7 @@ instance ToJSON QuantityValue where
|
||||
[ "type" .= ("interval" :: Text)
|
||||
, "to" .= toJSON to
|
||||
]
|
||||
|
||||
-- -----------------------------------------------------------------
|
||||
-- Value helpers
|
||||
|
||||
@ -130,7 +141,7 @@ simple :: Unit -> Double -> Maybe Text -> QuantityValue
|
||||
simple u v p = SimpleValue $ single u v p
|
||||
|
||||
between :: Unit -> (Double, Double) -> Maybe Text -> QuantityValue
|
||||
between u (from,to) p = IntervalValue (single u from p, single u to p)
|
||||
between u (from, to) p = IntervalValue (single u from p, single u to p)
|
||||
|
||||
above :: Unit -> Double -> Maybe Text -> QuantityValue
|
||||
above = openInterval Above
|
||||
@ -138,11 +149,8 @@ above = openInterval Above
|
||||
under :: Unit -> Double -> Maybe Text -> QuantityValue
|
||||
under = openInterval Under
|
||||
|
||||
openInterval :: IntervalDirection
|
||||
-> Unit
|
||||
-> Double
|
||||
-> Maybe Text
|
||||
-> QuantityValue
|
||||
openInterval
|
||||
:: IntervalDirection -> Unit -> Double -> Maybe Text -> QuantityValue
|
||||
openInterval direction u v p = OpenIntervalValue (single u v p, direction)
|
||||
|
||||
single :: Unit -> Double -> Maybe Text -> SingleValue
|
||||
|
@ -20,4 +20,5 @@ import Duckling.Testing.Asserts
|
||||
tests :: TestTree
|
||||
tests = testGroup "EN Tests"
|
||||
[ makeCorpusTest [This Quantity] corpus
|
||||
, makeCorpusTest [This Quantity] latentCorpus
|
||||
]
|
||||
|
Loading…
Reference in New Issue
Block a user