Added Quantity for NL, small fix for Volume NL (#302)

Summary:
* Added Quantity for NL (kg, mg, g, cup)
* Small fix for Volume (removed Gallon, fixed 'milliliter' typo)
Pull Request resolved: https://github.com/facebook/duckling/pull/302

Reviewed By: chinmay87

Differential Revision: D13554637

Pulled By: patapizza

fbshipit-source-id: 445fcb062c8cc2643b8e7810722759c168b5242f
This commit is contained in:
Eelco den Heijer 2019-01-02 13:50:25 -08:00 committed by Facebook Github Bot
parent e662269626
commit f3088ae252
14 changed files with 383 additions and 31 deletions

View File

@ -18,6 +18,7 @@ allDimensions =
, This Duration
, This Numeral
, This Ordinal
, This Quantity
, This Time
, This Volume
]

View File

@ -98,9 +98,6 @@ opsMap = HashMap.fromList
, ( "كيلو جرامين", (* 2000))
]
getValue :: Text -> Double -> Double
getValue match = HashMap.lookupDefault id (Text.toLower match) opsMap
ruleNumeralQuantities :: [Rule]
ruleNumeralQuantities = map go quantities
where
@ -112,7 +109,7 @@ ruleNumeralQuantities = map go quantities
(Token Numeral nd:
Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u value
where value = getValue match $ TNumeral.value nd
where value = getValue opsMap match $ TNumeral.value nd
_ -> Nothing
}
@ -125,7 +122,7 @@ ruleAQuantity = map go quantities
, pattern = [ regex regexPattern ]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u $ getValue match 1
_) -> Just . Token Quantity $ quantity u $ getValue opsMap match 1
_ -> Nothing
}

View File

@ -46,6 +46,7 @@ allExamples = concat
]
, examples (simple Cup 3 (Just "sugar"))
[ "3 Cups of sugar"
, "3 Cups of SugAr"
]
, examples (simple Cup 0.75 Nothing)
[ "3/4 cup"

View File

@ -24,9 +24,9 @@ import qualified Data.Text as Text
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Quantity.Helpers
import Duckling.Regex.Types
import Duckling.Regex.Types (GroupMatch(..))
import Duckling.Types
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Numeral.Types (NumeralData(..))
import Duckling.Quantity.Types (QuantityData(..))
import qualified Duckling.Numeral.Types as TNumeral
import qualified Duckling.Quantity.Types as TQuantity
@ -51,9 +51,6 @@ opsMap = HashMap.fromList
, ( "kgs" , (* 1000))
]
getValue :: Text -> Double -> Double
getValue match = HashMap.lookupDefault id (Text.toLower match) opsMap
ruleNumeralQuantities :: [Rule]
ruleNumeralQuantities = map go quantities
where
@ -65,7 +62,7 @@ ruleNumeralQuantities = map go quantities
(Token Numeral nd:
Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u value
where value = getValue match $ TNumeral.value nd
where value = getValue opsMap match $ TNumeral.value nd
_ -> Nothing
}
@ -78,7 +75,7 @@ ruleAQuantity = map go quantities
, pattern = [ regex ("an? " ++ regexPattern) ]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u $ getValue match 1
_) -> Just . Token Quantity $ quantity u $ getValue opsMap match 1
_ -> Nothing
}
@ -91,7 +88,7 @@ ruleQuantityOfProduct = Rule
]
, prod = \case
(Token Quantity qd:Token RegexMatch (GroupMatch (product:_)):_) ->
Just . Token Quantity $ withProduct product qd
Just . Token Quantity $ withProduct (Text.toLower product) qd
_ -> Nothing
}
@ -191,8 +188,6 @@ ruleIntervalDash = Rule
_ -> Nothing
}
ruleIntervalMax :: Rule
ruleIntervalMax = Rule
{ name = "under/below/less/lower/at most/no more than <dist>"
@ -224,6 +219,7 @@ ruleIntervalMin = Rule
_) -> Just . Token Quantity . withMin from $ unitOnly u
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleQuantityOfProduct

View File

@ -9,7 +9,8 @@
module Duckling.Quantity.Helpers
( isSimpleQuantity
( getValue
, isSimpleQuantity
, quantity
, unitOnly
, withProduct
@ -20,22 +21,29 @@ module Duckling.Quantity.Helpers
, withMax
) where
import Data.HashMap.Strict (HashMap)
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.Quantity.Types (QuantityData(..))
import Duckling.Types
import qualified Duckling.Quantity.Types as TQuantity
getValue :: HashMap Text (Double -> Double) -> Text -> Double -> Double
getValue opsMap match = HashMap.lookupDefault id (Text.toLower match) opsMap
-- -----------------------------------------------------------------
-- Patterns
isSimpleQuantity :: Predicate
isSimpleQuantity (Token Quantity QuantityData {TQuantity.unit = Just _
, TQuantity.value = Just _})
= True
isSimpleQuantity _ = False
-- -----------------------------------------------------------------
-- Production

View File

@ -91,9 +91,6 @@ opsMap = HashMap.fromList
, ( "គីឡូក្រាម" , (* 1000))
]
getValue :: Text -> Double -> Double
getValue match = HashMap.lookupDefault id match opsMap
ruleNumeralUnits2 :: [Rule]
ruleNumeralUnits2 = map go quantities
where
@ -105,7 +102,7 @@ ruleNumeralUnits2 = map go quantities
(Token Numeral nd:
Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u value
where value = getValue match $ TNumeral.value nd
where value = getValue opsMap match $ TNumeral.value nd
_ -> Nothing
}

View File

@ -0,0 +1,87 @@
-- 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 OverloadedStrings #-}
module Duckling.Quantity.NL.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Quantity.Types
import Duckling.Resolve
import Duckling.Testing.Types
context :: Context
context = testContext {locale = makeLocale NL Nothing}
corpus :: Corpus
corpus = (context, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Gram 2 Nothing)
[ "2 gram"
, "0,002 kg"
, "0,002 kilo"
, "2/1000 kilogram"
, "2000 milligram"
]
, examples (simple Gram 1000 Nothing)
[ "1 kg"
, "1,0 kg"
, "1 kilogram"
, "1 kilo"
, "1000 gram"
, "1000 g"
, "1000 gr"
, "duizend gram"
, "duizend gr"
, "2,0 pond"
, "10 ons"
, "1000000 mg"
, "1000000 milligram"
]
, examples (simple Cup 1 (Just "suiker"))
[ "1 kopje suiker"
]
, examples (simple Cup 3 (Just "suiker"))
[ "3 kopjes suiker"
]
, examples (simple Cup 0.75 Nothing)
[ "3/4 kopje"
, "0,75 kopje"
, ",75 kopje"
]
, examples (simple Gram 500 (Just "aardbeien"))
[ "500 gram aardbeien"
, "500g aardbeien"
, "0,5 kilogram aardbeien"
, "0,5 kg aardbeien"
, "5 ons aardbeien"
, "1 pond aardbeien"
, "500000mg aardbeien"
]
, examples (between Gram (100,1000) (Just "aardbeien"))
[ "100-1000 gram aardbeien"
, "tussen 100 en 1000 gram aardbeien"
, "van 100 tot 1000 g aardbeien"
, "tussen 1 ons en 10 ons aardbeien"
, "100 - 1000 g aardbeien"
]
, examples (between Gram (2,7) Nothing)
[ "~2-7 gram"
, "van 2 tot 7 g"
, "tussen 2,0 g en ongeveer 7,0 g"
, "tussen 0,002 kg en ongeveer 0,007 kg"
, "2 - ~7 gram"
]
]

View File

@ -0,0 +1,236 @@
-- 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 GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
module Duckling.Quantity.NL.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
quantities :: [(Text, String, TQuantity.Unit)]
quantities =
[ ("<quantity> kopje", "(kopjes?)", TQuantity.Cup)
, ("<quantity> grams", "(g((r)?(am)?)?)", TQuantity.Gram)
, ("<quantity> milligrams", "((m(illi)?)(g(ram)?))", TQuantity.Gram)
, ("<quantity> kilograms", "((k(ilo)?)(g(ram)?)?)", TQuantity.Gram)
, ("<quantity> pond", "(pond(je(s)?)?)", TQuantity.Gram)
, ("<quantity> ons", "(ons(je(s)?)?)", TQuantity.Gram)
]
opsMap :: HashMap Text (Double -> Double)
opsMap = HashMap.fromList
[ ( "milligram" , (/ 1000))
, ( "mg" , (/ 1000))
, ( "kilo" , (* 1000))
, ( "kilogram" , (* 1000))
, ( "kg" , (* 1000))
, ( "pond" , (* 500))
, ( "ons" , (* 100))
]
ruleNumeralQuantities :: [Rule]
ruleNumeralQuantities = map go quantities
where
go :: (Text, String, TQuantity.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern = [Predicate isPositive, regex regexPattern]
, prod = \case
(Token Numeral nd:
Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u value
where value = getValue opsMap match $ TNumeral.value nd
_ -> Nothing
}
ruleAQuantity :: [Rule]
ruleAQuantity = map go quantities
where
go :: (Text, String, TQuantity.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern = [ regex ("een? " ++ regexPattern) ]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u $ getValue opsMap match 1
_ -> Nothing
}
ruleQuantityOfProduct :: Rule
ruleQuantityOfProduct = Rule
{ name = "<quantity> product"
, pattern =
[ dimension Quantity
, regex "(\\w+)"
]
, prod = \case
(Token Quantity qd:Token RegexMatch (GroupMatch (product:_)):_) ->
Just . Token Quantity $ withProduct (Text.toLower product) qd
_ -> Nothing
}
rulePrecision :: Rule
rulePrecision = Rule
{ name = "ongeveer|plm|plusminus <quantity>"
, pattern =
[ regex "\\~|precies|exact|ongeveer|bijna|ongeveer"
, dimension Quantity
]
, prod = \case
(_:token:_) -> Just token
_ -> Nothing
}
ruleIntervalBetweenNumeral :: Rule
ruleIntervalBetweenNumeral = Rule
{ name = "tussen|van <numeral> en|tot <quantity>"
, pattern =
[ regex "tussen|van"
, Predicate isPositive
, regex "tot|en"
, 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 = "rond|tussen|van <quantity> tot|en <quantity>"
, pattern =
[ regex "tussen|van"
, Predicate isSimpleQuantity
, regex "en|tot"
, 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 = "minder dan/hoogstens/op zijn hoogst/maximaal/hooguit <quantity>"
, pattern =
[ regex "minder dan|hoogstens|hooguit|maximaal|op zijn hoogst"
, 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 = "meer dan/minstens/op zijn minst <quantity>"
, pattern =
[ regex "meer dan|minstens|minimaal|op zijn minst|minder dan"
, 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
}
rules :: [Rule]
rules =
[ ruleQuantityOfProduct
, ruleIntervalMin
, ruleIntervalMax
, ruleIntervalBetweenNumeral
, ruleIntervalBetween
, ruleIntervalNumeralDash
, ruleIntervalDash
, rulePrecision
]
++ ruleNumeralQuantities
++ ruleAQuantity

View File

@ -24,6 +24,7 @@ import qualified Duckling.Distance.NL.Rules as Distance
import qualified Duckling.Duration.NL.Rules as Duration
import qualified Duckling.Numeral.NL.Rules as Numeral
import qualified Duckling.Ordinal.NL.Rules as Ordinal
import qualified Duckling.Quantity.NL.Rules as Quantity
import qualified Duckling.Time.NL.Rules as Time
import qualified Duckling.Time.NL.BE.Rules as TimeBE
import qualified Duckling.Time.NL.NL.Rules as TimeNL
@ -48,7 +49,7 @@ langRules (This Email) = []
langRules (This Numeral) = Numeral.rules
langRules (This Ordinal) = Ordinal.rules
langRules (This PhoneNumber) = []
langRules (This Quantity) = []
langRules (This Quantity) = Quantity.rules
langRules (This RegexMatch) = []
langRules (This Temperature) = []
langRules (This Time) = Time.rules

View File

@ -25,20 +25,19 @@ corpus = (testContext {locale = makeLocale NL Nothing}, testOptions, allExamples
allExamples :: [Example]
allExamples = concat
[ examples (simple Millilitre 250)
[ "250 mililiter"
[ "250 milliliter"
, "250ml"
, "250 ml"
]
, examples (simple Litre 2)
[ "2 liter"
, "2 liters"
, "2l"
, "2 l"
]
, examples (simple Gallon 3)
[ "3 gallon"
]
, examples (simple Hectolitre 3)
[ "3 hectoliter"
, "3 hl"
]
, examples (simple Litre 0.5)
[ "halve liter"

View File

@ -11,7 +11,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Volume.NL.Rules
( rules ) where
( rules
) where
import Data.String
import Data.Text (Text)
@ -19,17 +20,16 @@ import Prelude
import Duckling.Dimensions.Types
import Duckling.Types
import Duckling.Regex.Types
import Duckling.Regex.Types (GroupMatch(..))
import Duckling.Volume.Helpers
import Duckling.Numeral.Helpers (isPositive)
import qualified Duckling.Volume.Types as TVolume
import qualified Duckling.Numeral.Types as TNumeral
volumes :: [(Text, String, TVolume.Unit)]
volumes = [ ("<latent vol> ml" , "m(ili)?l(iter)?" , TVolume.Millilitre)
, ("<vol> hectoliters" , "(hectoliter?)" , TVolume.Hectolitre)
, ("<vol> liters" , "l(iter)?" , TVolume.Litre)
, ("<latent vol> gallon", "(gallon?)" , TVolume.Gallon)
volumes = [ ("<latent vol> ml" , "m(illi)?l(iter)?" , TVolume.Millilitre)
, ("<vol> hl" , "h(ecto)?l(iter)?" , TVolume.Hectolitre)
, ("<vol> liters" , "l(iters?)?" , TVolume.Litre)
]
rulesVolumes :: [Rule]

View File

@ -550,6 +550,8 @@ library
, Duckling.Quantity.KO.Rules
, Duckling.Quantity.MN.Corpus
, Duckling.Quantity.MN.Rules
, Duckling.Quantity.NL.Corpus
, Duckling.Quantity.NL.Rules
, Duckling.Quantity.PT.Corpus
, Duckling.Quantity.PT.Rules
, Duckling.Quantity.RO.Corpus
@ -978,6 +980,7 @@ test-suite duckling-test
, Duckling.Quantity.KM.Tests
, Duckling.Quantity.KO.Tests
, Duckling.Quantity.MN.Tests
, Duckling.Quantity.NL.Tests
, Duckling.Quantity.PT.Tests
, Duckling.Quantity.RO.Tests
, Duckling.Quantity.RU.Tests

View File

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

View File

@ -21,6 +21,7 @@ import qualified Duckling.Quantity.HR.Tests as HR
import qualified Duckling.Quantity.KM.Tests as KM
import qualified Duckling.Quantity.KO.Tests as KO
import qualified Duckling.Quantity.MN.Tests as MN
import qualified Duckling.Quantity.NL.Tests as NL
import qualified Duckling.Quantity.PT.Tests as PT
import qualified Duckling.Quantity.RO.Tests as RO
import qualified Duckling.Quantity.RU.Tests as RU
@ -35,6 +36,7 @@ tests = testGroup "Quantity Tests"
, KM.tests
, KO.tests
, MN.tests
, NL.tests
, PT.tests
, RO.tests
, RU.tests