Added Distance and Volume Dimensions for Russian language

Summary:
- Added Distance Dimension for Russian language (RU)
- Added Volume Dimension for Russian language (RU)
- Extended `Duckling.Distance.Types.Unit` type definition by adding `Millimetre` representation
Closes https://github.com/facebook/duckling/pull/101

Reviewed By: JonCoens

Differential Revision: D6254070

Pulled By: patapizza

fbshipit-source-id: 579f7a259f76ff1c23ccfe2371afea385eb56aa1
This commit is contained in:
Igor Drozdov 2017-11-08 10:50:20 -08:00 committed by Facebook Github Bot
parent 8cbdabef09
commit 5d2c5c78ba
12 changed files with 294 additions and 4 deletions

View File

@ -14,6 +14,8 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ This Numeral
[ This Distance
, This Numeral
, This Ordinal
, This Volume
]

View File

@ -0,0 +1,66 @@
-- 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.Distance.RU.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Distance.Types
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale RU Nothing}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (DistanceValue Kilometre 3)
[ "3 километра"
, "3 км"
, "3км"
, "3.0 км"
]
, examples (DistanceValue Mile 8)
[ "8 миль"
, "восемь миль"
]
, examples (DistanceValue Metre 1)
[ "1 м",
"1 метр",
"один метр"
]
, examples (DistanceValue Centimetre 2)
[ "2см"
, "2 сантиметра"
]
, examples (DistanceValue Millimetre 4)
[ "4мм"
, "4 миллиметра"
]
, examples (DistanceValue Inch 5)
[ "5 дюймов"
, "5''"
, "пять дюймов"
, "5\""
]
, examples (DistanceValue Foot 35)
[ "35 футов"
, "35'"
, "тридцать пять футов"
]
, examples (DistanceValue Yard 47)
[ "47 ярдов"
, "сорок семь ярдов"
]
]

View File

@ -0,0 +1,50 @@
-- 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.Distance.RU.Rules
( rules
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.Dimensions.Types
import Duckling.Distance.Helpers
import Duckling.Distance.Types (DistanceData(..))
import Duckling.Types
import qualified Duckling.Distance.Types as TDistance
distances :: [(Text, String, TDistance.Unit)]
distances = [ ("<latent dist> km", "км|километр(а|ов)?", TDistance.Kilometre)
, ("<latent dist> feet", "('|фут(а|ов)?)", TDistance.Foot)
, ("<latent dist> inch", "(\"|''|дюйм(а|ов)?)", TDistance.Inch)
, ("<latent dist> yard", "ярд(а|ов)?", TDistance.Yard)
, ("<dist> meters", "м(етр(а|ов)?)?", TDistance.Metre)
, ("<dist> centimeters", "см|сантиметр(а|ов)?", TDistance.Centimetre)
, ("<dist> millimeters", "мм|миллиметр(а|ов)?", TDistance.Millimetre)
, ("<dist> miles", "мил(я|и|ь)", TDistance.Mile)
]
ruleDistances :: [Rule]
ruleDistances = map go distances
where
go :: (Text, String, TDistance.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern = [ dimension Distance, regex regexPattern ]
, prod = \tokens -> case tokens of
(Token Distance dd:_) -> Just . Token Distance $ withUnit u dd
_ -> Nothing
}
rules :: [Rule]
rules = ruleDistances

View File

@ -19,9 +19,9 @@ import Control.DeepSeq
import Data.Aeson
import Data.Hashable
import Data.Text (Text)
import qualified Data.Text as Text
import GHC.Generics
import Prelude
import qualified Data.Text as Text
import Duckling.Resolve (Resolve(..))
@ -33,6 +33,7 @@ data Unit
| M -- ambiguous between Mile and Metre
| Metre
| Mile
| Millimetre
| Yard
deriving (Eq, Generic, Hashable, Ord, Show, NFData)

View File

@ -18,8 +18,10 @@ module Duckling.Rules.RU
import Duckling.Dimensions.Types
import Duckling.Locale
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.Volume.RU.Rules as Volume
defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules
@ -29,7 +31,7 @@ localeRules _ _ = []
langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = []
langRules (This Distance) = []
langRules (This Distance) = Distance.rules
langRules (This Duration) = []
langRules (This Email) = []
langRules (This Numeral) = Numeral.rules
@ -41,4 +43,4 @@ langRules (This Temperature) = []
langRules (This Time) = []
langRules (This TimeGrain) = []
langRules (This Url) = []
langRules (This Volume) = []
langRules (This Volume) = Volume.rules

View File

@ -0,0 +1,59 @@
-- 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.Volume.RU.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.Volume.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale RU Nothing}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (VolumeValue Millilitre 250)
[ "250 миллилитров"
, "250мл"
, "250 мл"
]
, examples (VolumeValue Litre 2)
[ "2 литра"
, "2 л"
, "два литра"
]
, examples (VolumeValue Litre 1)
[ "1 литр"
, "один литр"
, ""
]
, examples (VolumeValue Gallon 3)
[ "3 галлона"
]
, examples (VolumeValue Hectolitre 3)
[ "3 гектолитра"
, "3 гл"
, "3гл"
]
, examples (VolumeValue Litre 0.5)
[ "пол-литра"
, "поллитра"
, "пол литра"
]
, examples (VolumeValue Litre 1.5)
[ "полтора литра"
]
]

View File

@ -0,0 +1,54 @@
-- 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.Volume.RU.Rules
( rules
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.Dimensions.Types
import Duckling.Types
import Duckling.Volume.Helpers
import qualified Duckling.Volume.Types as TVolume
ruleHalfLiter :: Rule
ruleHalfLiter = Rule
{ name = "half liter"
, pattern =
[ regex "пол[-\\s]?литра"
]
, prod = \_ -> Just . Token Volume . withUnit TVolume.Litre $ volume 0.5
}
volumes :: [(Text, String, TVolume.Unit)]
volumes = [ ("<latent vol> ml" , "мл|миллилитр(а|ов)?" , TVolume.Millilitre)
, ("<vol> hectoliters" , "гл|гектолитр(а|ов)?" , TVolume.Hectolitre)
, ("<vol> liters" , "л(итр(а|ов)?)?" , TVolume.Litre)
, ("<latent vol> gallon", "галлон(а|ов)?" , TVolume.Gallon)
]
ruleVolumes :: [Rule]
ruleVolumes = map go volumes
where
go :: (Text, String, TVolume.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern = [ dimension Volume, regex regexPattern ]
, prod = \tokens -> case tokens of
(Token Volume vd:_) -> Just . Token Volume $ withUnit u vd
_ -> Nothing
}
rules :: [Rule]
rules = ruleHalfLiter:ruleVolumes

View File

@ -206,6 +206,8 @@ library
, Duckling.Distance.NL.Rules
, Duckling.Distance.RO.Corpus
, Duckling.Distance.RO.Rules
, Duckling.Distance.RU.Corpus
, Duckling.Distance.RU.Rules
, Duckling.Distance.TR.Corpus
, Duckling.Distance.TR.Rules
, Duckling.Distance.Helpers
@ -569,6 +571,8 @@ library
, Duckling.Volume.NL.Rules
, Duckling.Volume.RO.Corpus
, Duckling.Volume.RO.Rules
, Duckling.Volume.RU.Corpus
, Duckling.Volume.RU.Rules
, Duckling.Volume.TR.Corpus
, Duckling.Volume.TR.Rules
, Duckling.Volume.Helpers
@ -643,6 +647,7 @@ test-suite duckling-test
, Duckling.Distance.NL.Tests
, Duckling.Distance.PT.Tests
, Duckling.Distance.RO.Tests
, Duckling.Distance.RU.Tests
, Duckling.Distance.TR.Tests
, Duckling.Distance.Tests
@ -798,6 +803,7 @@ test-suite duckling-test
, Duckling.Volume.PT.Tests
, Duckling.Volume.NL.Tests
, Duckling.Volume.RO.Tests
, Duckling.Volume.RU.Tests
, Duckling.Volume.TR.Tests
, Duckling.Volume.Tests

View File

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

View File

@ -22,6 +22,7 @@ import qualified Duckling.Distance.KO.Tests as KO
import qualified Duckling.Distance.NL.Tests as NL
import qualified Duckling.Distance.PT.Tests as PT
import qualified Duckling.Distance.RO.Tests as RO
import qualified Duckling.Distance.RU.Tests as RU
import qualified Duckling.Distance.TR.Tests as TR
tests :: TestTree
@ -36,5 +37,6 @@ tests = testGroup "Distance Tests"
, NL.tests
, PT.tests
, RO.tests
, RU.tests
, TR.tests
]

View File

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

View File

@ -22,6 +22,7 @@ import qualified Duckling.Volume.KO.Tests as KO
import qualified Duckling.Volume.NL.Tests as NL
import qualified Duckling.Volume.PT.Tests as PT
import qualified Duckling.Volume.RO.Tests as RO
import qualified Duckling.Volume.RU.Tests as RU
import qualified Duckling.Volume.TR.Tests as TR
tests :: TestTree
@ -36,5 +37,6 @@ tests = testGroup "Volume Tests"
, NL.tests
, PT.tests
, RO.tests
, RU.tests
, TR.tests
]