mirror of
https://github.com/facebook/duckling.git
synced 2025-01-07 06:19:10 +03:00
Feature/Turkish money (#579)
Summary: Added amount of money dimension for Turkish language Pull Request resolved: https://github.com/facebook/duckling/pull/579 Test Plan: :test Endpoint.Duckling.Test Reviewed By: haoxuany, bugra Differential Revision: D27017300 Pulled By: chessai fbshipit-source-id: e8cb257a2953675f54269ed358948e8cbe38af7b
This commit is contained in:
parent
8de488475a
commit
56fd7b0aaf
@ -122,13 +122,16 @@ currencies = HashMap.fromList
|
||||
, ("us$", USD)
|
||||
, ("vnd", VND)
|
||||
, ("zar", ZAR)
|
||||
, ("tl", TRY)
|
||||
, ("lira", TRY)
|
||||
, ("₺", TRY)
|
||||
]
|
||||
|
||||
ruleCurrencies :: Rule
|
||||
ruleCurrencies = Rule
|
||||
{ name = "currencies"
|
||||
, pattern =
|
||||
[ regex "(aed|aud|bgn|brl|byn|¢|cad|chf|cny|c|\\$|dinars?|dkk|dollars?|egp|(e|€)uro?s?|€|gbp|gel|\x20BE|hkd|hrk|idr|ils|₪|inr|iqd|jmd|jod|¥|jpy|lari|krw|kwd|lbp|mad|₮|mnt|tugriks?|myr|rm|nis|nok|nzd|£|pkr|pln|pta?s?|qar|₽|rs\\.?|riy?als?|ron|rub|rupees?|sar|sek|sgb|shekels?|thb|ttd|₴|uah|us(d|\\$)|vnd|yen|yuan|zar)"
|
||||
[ regex "(aed|aud|bgn|brl|byn|¢|cad|chf|cny|c|\\$|dinars?|dkk|dollars?|egp|(e|€)uro?s?|€|gbp|gel|\x20BE|hkd|hrk|idr|ils|₪|inr|iqd|jmd|jod|¥|jpy|lari|krw|kwd|lbp|mad|₮|mnt|tugriks?|myr|rm|nis|nok|nzd|£|pkr|pln|pta?s?|qar|₽|rs\\.?|riy?als?|ron|rub|rupees?|sar|sek|sgb|shekels?|thb|ttd|₴|uah|us(d|\\$)|vnd|yen|yuan|zar|tl|lira|₺)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (match:_)):_) -> do
|
||||
|
55
Duckling/AmountOfMoney/TR/Corpus.hs
Normal file
55
Duckling/AmountOfMoney/TR/Corpus.hs
Normal file
@ -0,0 +1,55 @@
|
||||
-- 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.
|
||||
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Duckling.AmountOfMoney.TR.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Data.String (fromString)
|
||||
import Prelude
|
||||
|
||||
import Duckling.AmountOfMoney.Types
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.Locale
|
||||
import Duckling.Resolve
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {locale = makeLocale TR Nothing}, testOptions, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (simple TRY 10000)
|
||||
[ "10 bin lira"
|
||||
, "on bin lira"
|
||||
, "10000 lira"
|
||||
]
|
||||
, examples (simple TRY 1)
|
||||
[ "bir lira"
|
||||
, "1 lira"
|
||||
]
|
||||
, examples (simple Cent 10)
|
||||
[ "on kuruş"
|
||||
, "10 kuruş"
|
||||
]
|
||||
, examples (simple Cent 25)
|
||||
[ "25 kuruş"
|
||||
, "yirmi beş kuruş"
|
||||
]
|
||||
, examples (simple Cent 5)
|
||||
[ "beş kuruş"
|
||||
, "5 kuruş"
|
||||
]
|
||||
, examples (simple Cent 66)
|
||||
[ "altmış altı kuruş"
|
||||
, "66 kuruş"
|
||||
]
|
||||
, examples (simple TRY 100.75)
|
||||
[ "yüz lira yetmiş beş kuruş"
|
||||
, "100 lira 75 kuruş"
|
||||
]
|
||||
]
|
160
Duckling/AmountOfMoney/TR/Rules.hs
Normal file
160
Duckling/AmountOfMoney/TR/Rules.hs
Normal file
@ -0,0 +1,160 @@
|
||||
-- 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.
|
||||
|
||||
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Duckling.AmountOfMoney.TR.Rules
|
||||
( rules
|
||||
) where
|
||||
|
||||
import Data.String (fromString)
|
||||
import Prelude
|
||||
|
||||
import Duckling.AmountOfMoney.Helpers
|
||||
import Duckling.AmountOfMoney.Types (Currency(..), AmountOfMoneyData (..))
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Numeral.Helpers (isNatural, isPositive)
|
||||
import Duckling.Numeral.Types (NumeralData (..))
|
||||
import Duckling.Types
|
||||
import qualified Duckling.AmountOfMoney.Types as TAmountOfMoney
|
||||
import qualified Duckling.Numeral.Types as TNumeral
|
||||
|
||||
ruleUnitAmount :: Rule
|
||||
ruleUnitAmount = Rule
|
||||
{ name = "<unit> <amount>"
|
||||
, pattern =
|
||||
[ Predicate isCurrencyOnly
|
||||
, Predicate isPositive
|
||||
]
|
||||
, prod = \case
|
||||
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.currency = c}:
|
||||
Token Numeral NumeralData{TNumeral.value = v}:
|
||||
_) -> Just $ Token AmountOfMoney $ withValue v $ currencyOnly c
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rulePounds :: Rule
|
||||
rulePounds = Rule
|
||||
{ name = "₺"
|
||||
, pattern =
|
||||
[ regex "₺"
|
||||
]
|
||||
, prod = \_ -> Just $ Token AmountOfMoney $ currencyOnly TRY
|
||||
}
|
||||
|
||||
ruleCent :: Rule
|
||||
ruleCent = Rule
|
||||
{ name = "cent"
|
||||
, pattern =
|
||||
[ regex "kuruş?"
|
||||
]
|
||||
, prod = \_ -> Just $ Token AmountOfMoney $ currencyOnly Cent
|
||||
}
|
||||
|
||||
ruleADollarCoin :: Rule
|
||||
ruleADollarCoin = Rule
|
||||
{ name = "a <dollar coin>"
|
||||
, pattern =
|
||||
[ regex "kuruş"
|
||||
, Predicate isDollarCoin
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:
|
||||
Token AmountOfMoney fd:
|
||||
_) -> Just $ Token AmountOfMoney fd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleNumDollarCoins :: Rule
|
||||
ruleNumDollarCoins = Rule
|
||||
{ name = "X <dollar coins>"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, Predicate isDollarCoin
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Numeral NumeralData{TNumeral.value = c}:
|
||||
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just d,
|
||||
TAmountOfMoney.currency = cur}:
|
||||
_) -> Just $ Token AmountOfMoney $ withValue (c * d) $ currencyOnly cur
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntersectAndXCents :: Rule
|
||||
ruleIntersectAndXCents = Rule
|
||||
{ name = "intersect (and X cents)"
|
||||
, pattern =
|
||||
[ Predicate isWithoutCents
|
||||
, regex "(lira|tl)"
|
||||
, Predicate isCents
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token AmountOfMoney fd:
|
||||
_:
|
||||
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just c}:
|
||||
_) -> Just $ Token AmountOfMoney $ withCents c fd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntersect :: Rule
|
||||
ruleIntersect = Rule
|
||||
{ name = "intersect"
|
||||
, pattern =
|
||||
[ Predicate isWithoutCents
|
||||
, Predicate isNatural
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token AmountOfMoney fd:
|
||||
Token Numeral NumeralData{TNumeral.value = c}:
|
||||
_) -> Just $ Token AmountOfMoney $ withCents c fd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntersectAndNumeral :: Rule
|
||||
ruleIntersectAndNumeral = Rule
|
||||
{ name = "intersect (and number)"
|
||||
, pattern =
|
||||
[ Predicate isWithoutCents
|
||||
, regex "(lira|tl)"
|
||||
, Predicate isNatural
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token AmountOfMoney fd:
|
||||
_:
|
||||
Token Numeral NumeralData{TNumeral.value = c}:
|
||||
_) -> Just $ Token AmountOfMoney $ withCents c fd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntersectXCents :: Rule
|
||||
ruleIntersectXCents = Rule
|
||||
{ name = "intersect (X cents)"
|
||||
, pattern =
|
||||
[ Predicate isWithoutCents
|
||||
, Predicate isCents
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token AmountOfMoney fd:
|
||||
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just c}:
|
||||
_) -> Just $ Token AmountOfMoney $ withCents c fd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleUnitAmount
|
||||
, ruleCent
|
||||
, ruleADollarCoin
|
||||
, ruleNumDollarCoins
|
||||
, ruleIntersect
|
||||
, ruleIntersectAndNumeral
|
||||
, ruleIntersectAndXCents
|
||||
, ruleIntersectXCents
|
||||
, rulePounds
|
||||
]
|
@ -81,6 +81,7 @@ data Currency
|
||||
| VND
|
||||
| ZAR
|
||||
| UAH
|
||||
| TRY
|
||||
deriving (Eq, Generic, Hashable, Show, Ord, NFData)
|
||||
|
||||
instance ToJSON Currency where
|
||||
@ -138,6 +139,7 @@ instance ToJSON Currency where
|
||||
toJSON VND = "VND"
|
||||
toJSON ZAR = "ZAR"
|
||||
toJSON UAH = "UAH"
|
||||
toJSON TRY = "TRY"
|
||||
|
||||
data AmountOfMoneyData = AmountOfMoneyData
|
||||
{ value :: Maybe Double
|
||||
|
@ -24,6 +24,7 @@ import qualified Duckling.Ordinal.TR.Rules as Ordinal
|
||||
import qualified Duckling.Temperature.TR.Rules as Temperature
|
||||
import qualified Duckling.TimeGrain.TR.Rules as TimeGrain
|
||||
import qualified Duckling.Volume.TR.Rules as Volume
|
||||
import qualified Duckling.AmountOfMoney.TR.Rules as AmountOfMoney
|
||||
|
||||
defaultRules :: Seal Dimension -> [Rule]
|
||||
defaultRules = langRules
|
||||
@ -33,7 +34,7 @@ localeRules region (Seal (CustomDimension dim)) = dimLocaleRules region dim
|
||||
localeRules _ _ = []
|
||||
|
||||
langRules :: Seal Dimension -> [Rule]
|
||||
langRules (Seal AmountOfMoney) = []
|
||||
langRules (Seal AmountOfMoney) = AmountOfMoney.rules
|
||||
langRules (Seal CreditCardNumber) = []
|
||||
langRules (Seal Distance) = Distance.rules
|
||||
langRules (Seal Duration) = Duration.rules
|
||||
|
@ -278,6 +278,8 @@ library
|
||||
, Duckling.AmountOfMoney.RU.Rules
|
||||
, Duckling.AmountOfMoney.SV.Corpus
|
||||
, Duckling.AmountOfMoney.SV.Rules
|
||||
, Duckling.AmountOfMoney.TR.Corpus
|
||||
, Duckling.AmountOfMoney.TR.Rules
|
||||
, Duckling.AmountOfMoney.VI.Corpus
|
||||
, Duckling.AmountOfMoney.VI.Rules
|
||||
, Duckling.AmountOfMoney.ZH.Corpus
|
||||
@ -911,6 +913,7 @@ test-suite duckling-test
|
||||
, Duckling.AmountOfMoney.RO.Tests
|
||||
, Duckling.AmountOfMoney.RU.Tests
|
||||
, Duckling.AmountOfMoney.SV.Tests
|
||||
, Duckling.AmountOfMoney.TR.Tests
|
||||
, Duckling.AmountOfMoney.VI.Tests
|
||||
, Duckling.AmountOfMoney.NL.Tests
|
||||
, Duckling.AmountOfMoney.ZH.Tests
|
||||
|
22
tests/Duckling/AmountOfMoney/TR/Tests.hs
Normal file
22
tests/Duckling/AmountOfMoney/TR/Tests.hs
Normal file
@ -0,0 +1,22 @@
|
||||
-- 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.
|
||||
|
||||
|
||||
module Duckling.AmountOfMoney.TR.Tests
|
||||
( tests ) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.AmountOfMoney.TR.Corpus
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "TR Tests"
|
||||
[ makeCorpusTest [Seal AmountOfMoney] corpus
|
||||
]
|
@ -32,6 +32,7 @@ import qualified Duckling.AmountOfMoney.PT.Tests as PT
|
||||
import qualified Duckling.AmountOfMoney.RO.Tests as RO
|
||||
import qualified Duckling.AmountOfMoney.RU.Tests as RU
|
||||
import qualified Duckling.AmountOfMoney.SV.Tests as SV
|
||||
import qualified Duckling.AmountOfMoney.TR.Tests as TR
|
||||
import qualified Duckling.AmountOfMoney.VI.Tests as VI
|
||||
import qualified Duckling.AmountOfMoney.ZH.Tests as ZH
|
||||
|
||||
@ -56,6 +57,7 @@ tests = testGroup "AmountOfMoney Tests"
|
||||
, RO.tests
|
||||
, RU.tests
|
||||
, SV.tests
|
||||
, TR.tests
|
||||
, VI.tests
|
||||
, ZH.tests
|
||||
]
|
||||
|
Loading…
Reference in New Issue
Block a user