Quantity rules for Spanish (ES)

Summary:
Spanish (ES) will now have all the same quantity rules as English (EN) (which I think is the most-supported language), plus more.

This includes the following:
* bowls - (bol(es)?|tazón(es)?|cuencos?|platos? (soperos?)|(hondos?)) (EN does not currently have this)
* cups - (tazas?)
* dishes - (platos?|fuentes?) (EN does not currently have this)
* grams - (((m(ili)?)|(k(ilo)?))?g(ramo)?s?)
* ounces - ((onzas?)|oz)
* pints - (pintas?) (EN does not currently have this)
* pounds - ((lb|libra)s?)
* quarts - (cuartos? de galón) (EN does not currently have this)
* tablespoons - (cucharadas? (grande)?) (EN does not currently have this)
* teaspoons - (cucharaditas?) (EN does not currently have this)

Reviewed By: patapizza

Differential Revision: D24628214

fbshipit-source-id: 2e8d500661f30fa0928cb7d3f21470afc01e2285
This commit is contained in:
Daniel Cartwright 2020-11-09 11:09:48 -08:00 committed by Facebook GitHub Bot
parent 888b1cba35
commit eb043d7018
7 changed files with 374 additions and 2 deletions

View File

@ -17,6 +17,7 @@ allDimensions =
, Seal Duration
, Seal Numeral
, Seal Ordinal
, Seal Quantity
, Seal Temperature
, Seal Time
, Seal Volume

View File

@ -0,0 +1,86 @@
-- 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 OverloadedStrings #-}
module Duckling.Quantity.ES.Corpus
( corpus
) where
import Prelude
import Data.String
import Duckling.Locale
import Duckling.Quantity.Types
import Duckling.Resolve
import Duckling.Testing.Types
context :: Context
context = testContext { locale = makeLocale ES Nothing }
corpus :: Corpus
corpus = (context, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Pound 2 (Just "carne"))
[ "dos libras de carne"
]
, examples (simple Gram 2 Nothing)
[ "dos gramos"
, "0,002 kg"
, "2/1000 kilogramos"
, "2000 miligramos"
]
, examples (simple Gram 1000 Nothing)
[ "un kilogramo"
, "un kg"
]
, examples (simple Pound 1 Nothing)
[ "una libra"
, "1 lb"
, "una lb"
]
, examples (simple Ounce 2 Nothing)
[ "2 onzas"
, "2oz"
]
, examples (simple Cup 3 (Just "azucar"))
[ "tres tazas de azucar"
, "3 tazas de AzUcAr"
]
, examples (simple Cup 0.75 Nothing)
[ "3/4 taza"
, "0,75 taza"
, ",75 tazas"
]
, examples (simple Gram 500 (Just "fresas"))
[ "500 gramos de fresas"
, "500g de fresas"
, "0,5 kilogramos de fresas"
, "0,5 kg de fresas"
, "500000mg de fresas"
]
, examples (under Pound 6 (Just "carne"))
[ "menos que seis libras de carne"
, "no más que 6 lbs de carne"
, "por debajo de 6,0 libras de carne"
, "a lo sumo seis libras de carne"
]
, examples (above Cup 2 Nothing)
[ "excesivo 2 tazas"
, "como mínimo dos tazas"
, "mayor de 2 tazas"
, "más de 2 tazas"
]
, examples (above Ounce 4 (Just "chocolate"))
[ "excesivo 4 oz de chocolate"
, "al menos 4,0 oz de chocolate"
, "mayor de cuatro onzas de chocolate"
, "más de cuatro onzas de chocolate"
]
]

View File

@ -0,0 +1,258 @@
-- 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 GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
module Duckling.Quantity.ES.Rules
( rules
) where
import Data.HashMap.Strict (HashMap)
import Data.String
import Data.Text (Text)
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Quantity.Helpers
import Duckling.Regex.Types (GroupMatch(..))
import Duckling.Types
import Duckling.Numeral.Types (NumeralData(..))
import Duckling.Quantity.Types (QuantityData(..))
import qualified Duckling.Numeral.Types as TNumeral
import qualified Duckling.Quantity.Types as TQuantity
-- Our quantities: (name, regex, quantityType). Please make sure to wrap
-- each regex in parentheses, because we extend these regexes later with
-- articles (un/una).
quantities :: [(Text, String, TQuantity.Unit)]
quantities =
[ ("<quantity> bowls", "(bol(es)?|tazón(es)?|cuencos?|platos? (soperos?)|(hondos?))", TQuantity.Bowl)
, ("<quantity> cups", "(tazas?)", TQuantity.Cup)
, ("<quantity> dishes", "(platos?|fuentes?)", TQuantity.Dish)
, ("<quantity> grams", "(((m(ili)?)|(k(ilo)?))?g(ramo)?s?)", TQuantity.Gram)
, ("<quantity> ounces", "((onzas?)|oz)", TQuantity.Ounce)
, ("<quantity> pints", "(pintas?)", TQuantity.Pint)
, ("<quantity> pounds", "((lb|libra)s?)", TQuantity.Pound)
, ("<quantity> quarts", "(cuartos? de galón)", TQuantity.Quart)
, ("<quantity> tablespoons", "(cucharadas? (grande)?)", TQuantity.Tablespoon)
, ("<quantity> teaspoons", "(cucharaditas?)", TQuantity.Teaspoon)
]
opsMap :: HashMap Text (Double -> Double)
opsMap = HashMap.fromList
[ ( "miligram" , (/ 1000))
, ( "miligramos" , (/ 1000))
, ( "mg" , (/ 1000))
, ( "mgs" , (/ 1000))
, ( "kilogramo" , (* 1000))
, ( "kilogramos" , (* 1000))
, ( "kg" , (* 1000))
, ( "kgs" , (* 1000))
]
ruleNumeralQuantities :: [Rule]
ruleNumeralQuantities = map go quantities
where
go :: (Text, String, TQuantity.Unit) -> Rule
go (nm, regexPattern, u) = Rule
{ name = nm
, pattern = [Predicate isPositive, regex regexPattern]
, prod = \case
(Token Numeral nd:
Token RegexMatch (GroupMatch (match:_)):
_) -> Just $ Token Quantity $ quantity u val
where val = getValue opsMap match $ TNumeral.value nd
_ -> Nothing
}
-- Quantities prefixed by "un" or "una"
ruleAQuantity :: [Rule]
ruleAQuantity = map go quantities
where
go :: (Text, String, TQuantity.Unit) -> Rule
go (nm, regexPattern, u) = Rule
{ name = nm
, pattern = [ regex ("una? " ++ regexPattern) ]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):
_) -> Just $ Token Quantity $ quantity u $ getValue opsMap match 1
_ -> Nothing
}
ruleQuantityOfProduct :: Rule
ruleQuantityOfProduct = Rule
{ name = "<quantity> de producto"
, pattern =
[ dimension Quantity
, regex "de (\\w+)"
]
, prod = \case
(Token Quantity qd:Token RegexMatch (GroupMatch (prdct:_)):_) ->
Just $ Token Quantity $ withProduct (Text.toLower prdct) qd
_ -> Nothing
}
rulePrecision :: Rule
rulePrecision = Rule
{ name = "about|exactly <quantity>"
, pattern =
[ regex "exactamente|precisamente|a?cerca( de)?|aproximadamente|casi"
, dimension Quantity
]
, prod = \case
(_:tkn:_) -> Just tkn
_ -> Nothing
}
ruleIntervalBetweenNumeral :: Rule
ruleIntervalBetweenNumeral = Rule
{ name = "between|from <numeral> and|to <quantity>"
, pattern =
[ regex "entre|de"
, Predicate isPositive
, regex "a|y"
, Predicate isSimpleQuantity
]
, prod = \case
(_:
Token Numeral NumeralData{TNumeral.value = from}:
_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u
, TQuantity.aproduct = Nothing}:
_) | from < to ->
Just $ Token Quantity $ withInterval (from, to) $ unitOnly u
_ -> Nothing
}
ruleIntervalBetween :: Rule
ruleIntervalBetween = Rule
{ name = "between|from <quantity> to|and <quantity>"
, pattern =
[ regex "entre/de"
, Predicate isSimpleQuantity
, regex "a/y"
, Predicate isSimpleQuantity
]
, prod = \case
(_:
Token Quantity QuantityData{TQuantity.value = Just from
, TQuantity.unit = Just u1
, TQuantity.aproduct = Nothing}:
_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u2
, TQuantity.aproduct = Nothing}:
_) | from < to && u1 == u2 ->
Just $ Token Quantity $ withInterval (from, to) $ unitOnly u1
_ -> Nothing
}
ruleIntervalNumeralDash :: Rule
ruleIntervalNumeralDash = Rule
{ name = "<numeral> - <quantity>"
, pattern =
[ Predicate isPositive
, regex "\\-"
, Predicate isSimpleQuantity
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = from}:
_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u
, TQuantity.aproduct = Nothing}:
_) | from < to ->
Just $ Token Quantity $ withInterval (from, to) $ unitOnly u
_ -> Nothing
}
ruleIntervalDash :: Rule
ruleIntervalDash = Rule
{ name = "<quantity> - <quantity>"
, pattern =
[ Predicate isSimpleQuantity
, regex "\\-"
, Predicate isSimpleQuantity
]
, prod = \case
(Token Quantity QuantityData{TQuantity.value = Just from
, TQuantity.unit = Just u1
, TQuantity.aproduct = Nothing}:
_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u2
, TQuantity.aproduct = Nothing}:
_) | from < to && u1 == u2 ->
Just $ Token Quantity $ withInterval (from, to) $ unitOnly u1
_ -> Nothing
}
ruleIntervalMax :: Rule
ruleIntervalMax = Rule
{ name = "under/below/less/lower/at most/no more than <dist>"
, pattern =
[ regex "no m(á|a)s que|menos de|por debajo de|como mucho|como m(á|a)xim(o|a)|a lo sumo|menos (que|de)"
, Predicate isSimpleQuantity
]
, prod = \case
(_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u
, TQuantity.aproduct = Nothing}:
_) -> Just $ Token Quantity $ withMax to $ unitOnly u
_ -> Nothing
}
ruleIntervalMin :: Rule
ruleIntervalMin = Rule
{ name = "over/above/exceeding/beyond/at least/more than <quantity>"
, pattern =
[ regex "(?<!no )m(á|a)s( grande| pesado)? (de|que)|mayor de|por encima de|excesivo|fuera de|por lo menos|como m(í|i)nim(o|a)|al menos"
, Predicate isSimpleQuantity
]
, prod = \case
(_:
Token Quantity QuantityData{TQuantity.value = Just from
, TQuantity.unit = Just u
, TQuantity.aproduct = Nothing}:
_) -> Just $ Token Quantity $ withMin from $ unitOnly u
_ -> 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
, ruleIntervalMin
, ruleIntervalMax
, ruleIntervalBetweenNumeral
, ruleIntervalBetween
, ruleIntervalNumeralDash
, ruleIntervalDash
, rulePrecision
, ruleQuantityLatent
]
++ ruleNumeralQuantities
++ ruleAQuantity

View File

@ -39,6 +39,7 @@ import qualified Duckling.TimeGrain.ES.Rules as TimeGrain
import Duckling.Types
import qualified Duckling.Volume.ES.Rules as Volume
import qualified Duckling.Duration.ES.Rules as Duration
import qualified Duckling.Quantity.ES.Rules as Quantity
defaultRules :: Seal Dimension -> [Rule]
defaultRules dim@(Seal Numeral) =
@ -65,7 +66,7 @@ langRules (Seal Email) = []
langRules (Seal Numeral) = Numeral.rules
langRules (Seal Ordinal) = Ordinal.rules
langRules (Seal PhoneNumber) = []
langRules (Seal Quantity) = []
langRules (Seal Quantity) = Quantity.rules
langRules (Seal RegexMatch) = []
langRules (Seal Temperature) = Temperature.rules
langRules (Seal Time) = Time.rules

View File

@ -589,6 +589,8 @@ library
, Duckling.Quantity.AR.Rules
, Duckling.Quantity.EN.Corpus
, Duckling.Quantity.EN.Rules
, Duckling.Quantity.ES.Corpus
, Duckling.Quantity.ES.Rules
, Duckling.Quantity.FR.Corpus
, Duckling.Quantity.FR.Rules
, Duckling.Quantity.HR.Corpus
@ -1041,6 +1043,7 @@ test-suite duckling-test
-- Quantity
, Duckling.Quantity.AR.Tests
, Duckling.Quantity.EN.Tests
, Duckling.Quantity.ES.Tests
, Duckling.Quantity.FR.Tests
, Duckling.Quantity.HR.Tests
, Duckling.Quantity.KM.Tests

View File

@ -0,0 +1,22 @@
-- 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.
module Duckling.Quantity.ES.Tests
( tests
) where
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Quantity.ES.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ES Tests"
[ makeCorpusTest [Seal Quantity] corpus
]

View File

@ -10,11 +10,11 @@ module Duckling.Quantity.Tests
) where
import Data.String
import Prelude
import Test.Tasty
import qualified Duckling.Quantity.AR.Tests as AR
import qualified Duckling.Quantity.EN.Tests as EN
import qualified Duckling.Quantity.ES.Tests as ES
import qualified Duckling.Quantity.FR.Tests as FR
import qualified Duckling.Quantity.HR.Tests as HR
import qualified Duckling.Quantity.KM.Tests as KM
@ -30,6 +30,7 @@ tests :: TestTree
tests = testGroup "Quantity Tests"
[ AR.tests
, EN.tests
, ES.tests
, FR.tests
, HR.tests
, KM.tests