Added Quantity Dimension to Arabic language

Summary: Closes https://github.com/facebook/duckling/pull/127

Reviewed By: panagosg7

Differential Revision: D6616298

Pulled By: patapizza

fbshipit-source-id: dc774ff1e870bbd083a9cca8ee6f75db852afce9
This commit is contained in:
Abdallatif Sulaiman 2017-12-20 17:51:20 -08:00 committed by Facebook Github Bot
parent c056a0b46a
commit 2d726d3837
10 changed files with 274 additions and 17 deletions

View File

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

View File

@ -0,0 +1,68 @@
-- 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.AR.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Quantity.Types
import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale AR Nothing}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (QuantityData Ounce 3 (Just "الذهب"))
[ "ثلاثة اونصات من الذهب"
]
, examples (QuantityData Gram 2 Nothing)
[ "2 غرام"
, "2 جرام"
, "0.002 كيلوغرام"
, "0.002 كيلوجرام"
, "2/1000 كغ"
, "2000 ملغ"
, "2000 ملج"
]
, examples (QuantityData Gram 1000 Nothing)
[ "كغ"
, "كيلوغرام"
, "كيلوجرام"
]
, examples (QuantityData Ounce 2 Nothing)
[ "2 اونصة"
, "أونصتان"
, "اونصتين"
]
, examples (QuantityData Cup 3 (Just "السكر"))
[ "3 اكواب من السكر"
]
, examples (QuantityData Cup 0.75 Nothing)
[ "3/4 كوب"
, "0.75 كوب"
, ".75 كوب"
]
, examples (QuantityData Gram 500 (Just "الفراولة"))
[ "500 غرام من الفراولة"
, "500 غم من الفراولة"
, "500 جرام من الفراولة"
, "500 جم من الفراولة"
, "0.5 كيلوجرام من الفراولة"
, "0.5 كيلوغرام من الفراولة"
, "0.5 كغ من الفراولة"
, "500000 ملغ من الفراولة"
]
]

View File

@ -0,0 +1,150 @@
-- 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 #-}
module Duckling.Quantity.AR.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
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
import qualified Duckling.Quantity.Types as TQuantity
quantities :: [(Text, String, TQuantity.Unit)]
quantities =
[ ("<quantity> cups", "(كوب(ان|ين)?|[أا]كواب)", TQuantity.Cup)
, ("<quantity> grams", "(((كيلو|مي?لي?) ?)?((غ|ج)رام(ات|ين|ان)?)|ك(غ|ج)م?|مل(غ|ج)|(غ|ج)م)", TQuantity.Gram)
, ("<quantity> lb", "(باوند(ان|ين)?)", TQuantity.Pound)
, ("<quantity> oz", "([أا]ونص([ةه]|تان|تين|ات))", TQuantity.Ounce)
]
opsMap :: HashMap Text (Double -> Double)
opsMap = HashMap.fromList
[ ( "غرامان", (* 2))
, ( "غرامين", (* 2))
, ( "كوبان", (* 2))
, ( "كوبين", (* 2))
, ( "باوندان", (* 2))
, ( "باوندين", (* 2))
, ( "اونصتان", (* 2))
, ( "اونصتين", (* 2))
, ( "أونصتان", (* 2))
, ( "أونصتين", (* 2))
, ( "جرامان", (* 2))
, ( "جرامين", (* 2))
, ( "ميلي غرامان", (/ 500))
, ( "ميليغرامان", (/ 500))
, ( "ميلغرامان", (/ 500))
, ( "ميلي غرامين", (/ 500))
, ( "ميليغرامين", (/ 500))
, ( "ميلغرامين", (/ 500))
, ( "ميلي جرامان", (/ 500))
, ( "ميليجرامان", (/ 500))
, ( "ميلجرامان", (/ 500))
, ( "ميلي جرامين", (/ 500))
, ( "ميليجرامين", (/ 500))
, ( "ميلجرامين", (/ 500))
, ( "ميلي غرام", (/ 1000))
, ( "ميليغرام", (/ 1000))
, ( "ميلغرام", (/ 1000))
, ( "كيلوغرام", (* 1000))
, ( "كيلو غرام", (* 1000))
, ( "ميلي غرامات", (/ 1000))
, ( "ميليغرامات", (/ 1000))
, ( "ميلغرامات", (/ 1000))
, ( "ملغ", (/ 1000))
, ( "كغ", (* 1000))
, ( "كغم", (* 1000))
, ( "ميلي جرام", (/ 1000))
, ( "ميليجرام", (/ 1000))
, ( "ميلجرام", (/ 1000))
, ( "ميلي جرامات", (/ 1000))
, ( "ميليجرامات", (/ 1000))
, ( "ميلجرامات", (/ 1000))
, ( "كيلوغرامات", (* 1000))
, ( "كيلو غرامات", (* 1000))
, ( "ملج", (/ 1000))
, ( "كيلوجرام", (* 1000))
, ( "كيلو جرام", (* 1000))
, ( "كيلوجرامات", (* 1000))
, ( "كيلو جرامات", (* 1000))
, ( "كج", (* 1000))
, ( "كجم", (* 1000))
, ( "كيلوغرامان", (* 2000))
, ( "كيلوغرامين", (* 2000))
, ( "كيلو غرامان", (* 2000))
, ( "كيلو غرامين", (* 2000))
, ( "كيلوجرامان", (* 2000))
, ( "كيلوجرامين", (* 2000))
, ( "كيلو جرامان", (* 2000))
, ( "كيلو جرامين", (* 2000))
]
getValue :: Text -> Double -> Double
getValue match = HashMap.lookupDefault id (Text.toLower match) opsMap
ruleNumeralQuantities :: [Rule]
ruleNumeralQuantities = map go quantities
where
go :: (Text, String, TQuantity.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern = [ numberWith TNumeral.value (> 0), regex regexPattern ]
, prod = \tokens -> case tokens of
(Token Numeral nd:
Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u value
where value = getValue 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 regexPattern ]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u $ getValue match 1
_ -> Nothing
}
ruleQuantityOfProduct :: Rule
ruleQuantityOfProduct = Rule
{ name = "<quantity> of product"
, pattern =
[ dimension Quantity
, regex "من ([ء-ي]+)"
]
, prod = \tokens -> case tokens of
(Token Quantity qd:Token RegexMatch (GroupMatch (product:_)):_) ->
Just . Token Quantity $ withProduct product qd
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleQuantityOfProduct
]
++ ruleNumeralQuantities
++ ruleAQuantity

View File

@ -10,11 +10,14 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Quantity.EN.Rules
( rules ) where
( 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
@ -33,17 +36,20 @@ quantities =
, ("<quantity> oz", "((ounces?)|oz)", TQuantity.Ounce)
]
opsMap :: HashMap Text (Double -> Double)
opsMap = HashMap.fromList
[ ( "milligram" , (/ 1000))
, ( "milligrams", (/ 1000))
, ( "mg" , (/ 1000))
, ( "mgs" , (/ 1000))
, ( "kilogram" , (* 1000))
, ( "kilograms" , (* 1000))
, ( "kg" , (* 1000))
, ( "kgs" , (* 1000))
]
getValue :: Text -> Double -> Double
getValue match value = case Text.toLower match of
"milligram" -> value / 1000
"milligrams" -> value / 1000
"mg" -> value / 1000
"mgs" -> value / 1000
"kilogram" -> value * 1000
"kilograms" -> value * 1000
"kg" -> value * 1000
"kgs" -> value * 1000
_ -> value
getValue match = HashMap.lookupDefault id (Text.toLower match) opsMap
ruleNumeralQuantities :: [Rule]
ruleNumeralQuantities = map go quantities

View File

@ -21,6 +21,7 @@ import Duckling.Types
import qualified Duckling.Duration.AR.Rules as Duration
import qualified Duckling.Numeral.AR.Rules as Numeral
import qualified Duckling.Ordinal.AR.Rules as Ordinal
import qualified Duckling.Quantity.AR.Rules as Quantity
import qualified Duckling.Temperature.AR.Rules as Temperature
import qualified Duckling.Time.AR.Rules as Time
import qualified Duckling.TimeGrain.AR.Rules as TimeGrain
@ -40,7 +41,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) = Temperature.rules
langRules (This Time) = Time.rules

View File

@ -406,6 +406,8 @@ library
, Duckling.PhoneNumber.Types
-- Quantity
, Duckling.Quantity.AR.Corpus
, Duckling.Quantity.AR.Rules
, Duckling.Quantity.EN.Corpus
, Duckling.Quantity.EN.Rules
, Duckling.Quantity.FR.Corpus
@ -771,6 +773,7 @@ test-suite duckling-test
, Duckling.PhoneNumber.Tests
-- Quantity
, Duckling.Quantity.AR.Tests
, Duckling.Quantity.EN.Tests
, Duckling.Quantity.FR.Tests
, Duckling.Quantity.HR.Tests

View File

@ -123,7 +123,7 @@ supportedDimensionsTest = testCase "Supported Dimensions Test" $ do
[ ( AR
, [ This Email, This AmountOfMoney, This PhoneNumber, This Url
, This Duration, This Numeral, This Ordinal, This Time, This Volume
, This Temperature
, This Temperature, This Quantity
]
)
, ( PL

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

View File

@ -10,8 +10,8 @@ module Duckling.Quantity.EN.Tests
( tests
) where
import Prelude
import Data.String
import Prelude
import Test.Tasty
import Duckling.Dimensions.Types

View File

@ -6,12 +6,15 @@
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Quantity.Tests (tests) where
module Duckling.Quantity.Tests
( tests
) where
import Prelude
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.FR.Tests as FR
import qualified Duckling.Quantity.HR.Tests as HR
@ -22,7 +25,8 @@ import qualified Duckling.Quantity.RU.Tests as RU
tests :: TestTree
tests = testGroup "Quantity Tests"
[ EN.tests
[ AR.tests
, EN.tests
, FR.tests
, HR.tests
, KO.tests