Added Quantity dimension to Russian language

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

Reviewed By: blandinw

Differential Revision: D6312605

Pulled By: patapizza

fbshipit-source-id: 69ec673f95ec8a2d86ec207a6d75cd8ebfcdb4f6
This commit is contained in:
Igor Drozdov 2017-11-14 20:46:48 -08:00 committed by Facebook Github Bot
parent fb10a6e6ba
commit f6492b5da0
7 changed files with 157 additions and 1 deletions

View File

@ -17,5 +17,6 @@ allDimensions =
[ This Distance
, This Numeral
, This Ordinal
, This Quantity
, This Volume
]

View File

@ -0,0 +1,60 @@
-- 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.RU.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Quantity.Types
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale RU Nothing}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (QuantityData Pound 2 Nothing)
[ "2 фунта"
]
, examples (QuantityData Gram 2 Nothing)
[ "2 грамма"
, "два грамма"
, "0.002 кг"
, "2000 миллиграмм"
, "2000 мг"
]
, examples (QuantityData Gram 1000 Nothing)
[ "килограмм"
, "кг"
]
, examples (QuantityData Gram 2000 Nothing)
[ "2 килограмма"
, "2 кг"
]
, examples (QuantityData Pound 1 Nothing)
[ "фунт"
, "1 фунт"
]
, examples (QuantityData Ounce 2 Nothing)
[ "2 унции"
]
, examples (QuantityData Gram 500 Nothing)
[ "500 грамм"
, "500г"
, "500 г"
, "0.5 кг"
, "пятьсот грамм"
]
]

View File

@ -0,0 +1,65 @@
-- 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.RU.Rules
( rules
) where
import Data.String
import Data.Text (Text)
import Prelude
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, Double -> Double)]
quantities =
[ ("<quantity> milligrams", "(мг|миллиграмма?)", TQuantity.Gram, (/ 1000))
, ("<quantity> grams", "г(рамма?)?", TQuantity.Gram, id)
, ("<quantity> kilograms", "(кг|килограмма?)", TQuantity.Gram, (* 1000))
, ("<quantity> lb", "фунт(а|ов)?", TQuantity.Pound, id)
, ("<quantity> oz", "унц(ия|ии|ий)", TQuantity.Ounce, id)
]
ruleNumeralQuantities :: [Rule]
ruleNumeralQuantities = map go quantities
where
go :: (Text, String, TQuantity.Unit, Double -> Double) -> Rule
go (name, regexPattern, u, convert) = Rule
{ name = name
, pattern =
[ numberWith TNumeral.value (> 0)
, regex regexPattern
]
, prod = \tokens -> case tokens of
(Token Numeral nd:_) ->
Just . Token Quantity . quantity u . convert $ TNumeral.value nd
_ -> Nothing
}
ruleAQuantity :: [Rule]
ruleAQuantity = map go quantities
where
go :: (Text, String, TQuantity.Unit, Double -> Double) -> Rule
go (name, regexPattern, u, convert) = Rule
{ name = name
, pattern = [ regex regexPattern ]
, prod = \_ -> Just . Token Quantity . quantity u $ convert 1
}
rules :: [Rule]
rules = ruleNumeralQuantities ++ ruleAQuantity

View File

@ -21,6 +21,7 @@ import Duckling.Types
import qualified Duckling.Distance.RU.Rules as Distance
import qualified Duckling.Numeral.RU.Rules as Numeral
import qualified Duckling.Ordinal.RU.Rules as Ordinal
import qualified Duckling.Quantity.RU.Rules as Quantity
import qualified Duckling.Volume.RU.Rules as Volume
defaultRules :: Some Dimension -> [Rule]
@ -37,7 +38,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) = []

View File

@ -408,6 +408,8 @@ library
, Duckling.Quantity.PT.Rules
, Duckling.Quantity.RO.Corpus
, Duckling.Quantity.RO.Rules
, Duckling.Quantity.RU.Corpus
, Duckling.Quantity.RU.Rules
, Duckling.Quantity.Helpers
, Duckling.Quantity.Types
@ -753,6 +755,7 @@ test-suite duckling-test
, Duckling.Quantity.KO.Tests
, Duckling.Quantity.PT.Tests
, Duckling.Quantity.RO.Tests
, Duckling.Quantity.RU.Tests
, Duckling.Quantity.Tests
-- Temperature

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

View File

@ -18,6 +18,7 @@ import qualified Duckling.Quantity.HR.Tests as HR
import qualified Duckling.Quantity.KO.Tests as KO
import qualified Duckling.Quantity.PT.Tests as PT
import qualified Duckling.Quantity.RO.Tests as RO
import qualified Duckling.Quantity.RU.Tests as RU
tests :: TestTree
tests = testGroup "Quantity Tests"
@ -27,4 +28,5 @@ tests = testGroup "Quantity Tests"
, KO.tests
, PT.tests
, RO.tests
, RU.tests
]