Added Volume Dimension to Arabic language

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

Reviewed By: panagosg7

Differential Revision: D6614574

Pulled By: patapizza

fbshipit-source-id: 054ed04e0cc1cf79be31340ebb8b7fea3bc67f57
This commit is contained in:
Abdallatif Sulaiman 2017-12-20 17:51:20 -08:00 committed by Facebook Github Bot
parent 1393098bcc
commit 380457db8f
9 changed files with 202 additions and 6 deletions

View File

@ -18,4 +18,5 @@ allDimensions =
, This Numeral
, This Ordinal
, This Time
, This Volume
]

View File

@ -23,6 +23,7 @@ import qualified Duckling.Numeral.AR.Rules as Numeral
import qualified Duckling.Ordinal.AR.Rules as Ordinal
import qualified Duckling.Time.AR.Rules as Time
import qualified Duckling.TimeGrain.AR.Rules as TimeGrain
import qualified Duckling.Volume.AR.Rules as Volume
defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules
@ -44,4 +45,4 @@ langRules (This Temperature) = []
langRules (This Time) = Time.rules
langRules (This TimeGrain) = TimeGrain.rules
langRules (This Url) = []
langRules (This Volume) = []
langRules (This Volume) = Volume.rules

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 OverloadedStrings #-}
module Duckling.Volume.AR.Corpus
( corpus ) where
import Data.String
import Prelude
import Duckling.Testing.Types
import Duckling.Locale
import Duckling.Resolve
import Duckling.Volume.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale AR Nothing}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (VolumeValue Millilitre 250)
[ "250 مل"
, "250مل"
, "250 ميليلتر"
, "250 ملي لتر"
]
, examples (VolumeValue Litre 2)
[ "2 لتر"
, "لتران"
, "لترين"
]
, examples (VolumeValue Gallon 3)
[ "3 غالون"
, "3 جالون"
, "3 غالونات"
, "3 جالونات"
]
, examples (VolumeValue Hectolitre 3)
[ "3 هكتوليتر"
, "3 هكتو ليتر"
]
, examples (VolumeValue Litre 0.5)
[ "نصف لتر"
, "نص لتر"
]
, examples (VolumeValue Litre 0.25)
[ "ربع لتر"
]
, examples (VolumeValue Litre 1.5)
[ "لتر ونصف"
, "لتر و نص"
, "لتر و نصف"
, "لتر ونص"
]
, examples (VolumeValue Litre 1.25)
[ "لتر وربع"
, "لتر و ربع"
]
]

View File

@ -0,0 +1,98 @@
-- 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.AR.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 "نصف? لي?تي?ر"
]
, prod = \_ -> Just . Token Volume . withUnit TVolume.Litre $ volume 0.5
}
ruleQuartorOfLiter :: Rule
ruleQuartorOfLiter = Rule
{ name = "quartor of liter"
, pattern =
[ regex "ربع لي?تي?ر"
]
, prod = \_ -> Just . Token Volume . withUnit TVolume.Litre $ volume 0.25
}
ruleLiterAndHalf :: Rule
ruleLiterAndHalf = Rule
{ name = "liter and half"
, pattern =
[ regex "لي?تي?ر و ?نصف?"
]
, prod = \_ -> Just . Token Volume . withUnit TVolume.Litre $ volume 1.5
}
ruleTwoLiters :: Rule
ruleTwoLiters = Rule
{ name = "two liters"
, pattern =
[ regex "لي?تي?ر(ان|ين)"
]
, prod = \_ -> Just . Token Volume . withUnit TVolume.Litre $ volume 2
}
ruleLiterAndQuartor :: Rule
ruleLiterAndQuartor = Rule
{ name = "liter and quartor"
, pattern =
[ regex "لي?تي?ر و ?ربع"
]
, prod = \_ -> Just . Token Volume . withUnit TVolume.Litre $ volume 1.25
}
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
, ruleTwoLiters
, ruleQuartorOfLiter
, ruleLiterAndHalf
, ruleLiterAndQuartor
]
++ ruleVolumes

View File

@ -18,9 +18,9 @@ import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Types (NumeralData(..))
import qualified Duckling.Numeral.Types as TNumeral
import Duckling.Types
import Duckling.Volume.Helpers
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralAsVolume :: Rule
ruleNumeralAsVolume = Rule

View File

@ -570,6 +570,8 @@ library
, Duckling.Url.Types
-- Volume
, Duckling.Volume.AR.Corpus
, Duckling.Volume.AR.Rules
, Duckling.Volume.EN.Corpus
, Duckling.Volume.EN.Rules
, Duckling.Volume.ES.Corpus
@ -819,6 +821,7 @@ test-suite duckling-test
, Duckling.Url.Tests
-- Volume
, Duckling.Volume.AR.Tests
, Duckling.Volume.EN.Tests
, Duckling.Volume.ES.Tests
, Duckling.Volume.FR.Tests

View File

@ -122,7 +122,7 @@ supportedDimensionsTest = testCase "Supported Dimensions Test" $ do
mapM_ check
[ ( AR
, [ This Email, This AmountOfMoney, This PhoneNumber, This Url
, This Duration, This Numeral, This Ordinal, This Time
, This Duration, This Numeral, This Ordinal, This Time, This Volume
]
)
, ( 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.Volume.AR.Tests
( tests
) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Testing.Asserts
import Duckling.Volume.AR.Corpus
tests :: TestTree
tests = testGroup "AR Tests"
[ makeCorpusTest [This Volume] corpus
]

View File

@ -6,12 +6,15 @@
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Volume.Tests (tests) where
module Duckling.Volume.Tests
( tests
) where
import Prelude
import Data.String
import Prelude
import Test.Tasty
import qualified Duckling.Volume.AR.Tests as AR
import qualified Duckling.Volume.EN.Tests as EN
import qualified Duckling.Volume.ES.Tests as ES
import qualified Duckling.Volume.FR.Tests as FR
@ -27,7 +30,8 @@ import qualified Duckling.Volume.TR.Tests as TR
tests :: TestTree
tests = testGroup "Volume Tests"
[ EN.tests
[ AR.tests
, EN.tests
, ES.tests
, FR.tests
, GA.tests