AmountOfMoney/HE Extend support

Summary: Improve support for amount of money in Hebrew

Reviewed By: patapizza

Differential Revision: D13685915

fbshipit-source-id: f9796f52b4d011bdc5e1ef903d5e3dc789bfcd04
This commit is contained in:
Micha Molko 2019-02-06 02:10:53 -08:00 committed by Facebook Github Bot
parent d31bf25bf4
commit 301f74ea2e
9 changed files with 521 additions and 2 deletions

View File

@ -0,0 +1,125 @@
-- 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.AmountOfMoney.HE.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus =
(testContext { locale = makeLocale HE Nothing }, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple ILS 10)
[ "עשר שקל"
, "עשרה שקלים"
, "עשר ש״ח"
, "עשר שח"
, "10₪"
]
, examples (simple ILS 10000)
[ "עשר אלף שקל"
, "10000 שקלים"
, "10 אשח"
, "10 אש״ח"
]
, examples (simple ILS 10000000)
[ "10 מיליון שקלים"
, "10 משח"
, "10 מש״ח"
]
, examples (simple ILS 0.01)
[ "אגורה"
]
, examples (simple ILS 1)
[ "שקל"
, "שקל אחד"
, "שקל בודד"
, "100 אגורות"
]
, examples (simple ILS 0.05)
[ "חמש אגורות"
]
, examples (simple ILS 0)
[ "אפס ש״ח"
]
, examples (simple ILS 1.5)
[ "שקל וחצי"
, "1.5 ש״ח"
]
, examples (simple ILS 2)
[ "שנקל"
, "2 שקל"
]
, examples (simple Dollar 10)
[ "$10"
, "10$"
, "עשר דולר"
, "עשרה דולר"
, "עשרה דולרים"
, "עשר דולרים"
]
, examples (simple Dollar 20)
[ "עשרים דולר"
]
, examples (simple Dollar 2.23)
[ "2 דולר ו23 סנט"
]
, examples (simple EUR 20)
[ "20€"
, "20 יורו"
, "EUR 20"
, "20 אירו"
]
, examples (simple EUR 29.99)
[ "29.99 יורו"
]
, examples (simple Pound 9)
[ "£9"
, "תשע פאונד"
]
, examples (simple GBP 1)
[ "לירה שטרלינג"
]
, examples (simple GBP 10)
[ "10 לירות שטרלינג"
]
, examples (between Dollar (10, 20))
[ "מ10 עד 20 דולר"
, "מעשר עד עשרים דולר"
, "בין 10 ל20 דולר"
, "10$-20$"
, "10-20$"
, "10-20 דולר"
, "בין 10 דולר ל20 דולר"
]
, examples (under EUR 7)
[ "פחות מ7 יורו"
, "עד 7 יורו"
, "לא יותר מ7 יורו"
, "מתחת ל7 יורו"
, "לא מעל 7 יורו"
]
, examples (above Dollar 5)
[ "יותר מ5 דולר"
, "מעל 5 דולר"
, "מ5 דולר"
, "לא פחות מ5 דולר"
, "לא מתחת ל5 דולר"
]
]

View File

@ -0,0 +1,349 @@
-- 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 LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.AmountOfMoney.HE.Rules
( rules
) where
import Data.Maybe
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types
( Currency(..)
, AmountOfMoneyData(..)
)
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
( 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
}
ruleOneShekel :: Rule
ruleOneShekel = Rule
{ name = "שקל"
, pattern = [regex "שקל( אחד| בודד)?"]
, prod = \_ -> Just . Token AmountOfMoney $ withValue 1 $ currencyOnly ILS
}
ruleTwoShekel :: Rule
ruleTwoShekel = Rule
{ name = "שנקל"
, pattern = [regex "שנקל"]
, prod = \_ -> Just . Token AmountOfMoney $ withValue 2 $ currencyOnly ILS
}
ruleOneAgura :: Rule
ruleOneAgura = Rule
{ name = "oneAgura"
, pattern = [regex "אגורה( אחת| בודדת)?"]
, prod = \_ -> Just . Token AmountOfMoney $ withValue 0.01 $
currencyOnly ILS
}
ruleShekel :: Rule
ruleShekel = Rule
{ name = "שקל"
, pattern = [regex "שקל(ים)?|ש״?ח"]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly ILS
}
ruleThousandShekel :: Rule
ruleThousandShekel = Rule
{ name = "אש״ח"
, pattern =
[ Predicate isPositive
, regex "אש״?ח"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:
_) -> Just . Token AmountOfMoney $ withValue (v*1000) $
currencyOnly ILS
_ -> Nothing
}
ruleMillionShekel :: Rule
ruleMillionShekel = Rule
{ name = "מש״ח"
, pattern =
[ Predicate isPositive
, regex "מש״?ח"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:
_) -> Just . Token AmountOfMoney $ withValue (v*1000000) $
currencyOnly ILS
_ -> Nothing
}
ruleAgura :: Rule
ruleAgura = Rule
{ name = "multiple agura"
, pattern =
[ Predicate isPositive
, regex "אגורות"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:
_) -> Just . Token AmountOfMoney $ withValue (v*0.01) $
currencyOnly ILS
_ -> Nothing
}
ruleIntersect :: Rule
ruleIntersect = Rule
{ name = "intersect"
, pattern =
[ Predicate isWithoutCents
, regex "ו"
, Predicate isPositive
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just v,
TAmountOfMoney.currency = c}:
_:
Token Numeral NumeralData { TNumeral.value = p }:
_) -> Just . Token AmountOfMoney $ withValue (v + p) $ currencyOnly c
_ -> Nothing
}
ruleIntersectAndXCents :: Rule
ruleIntersectAndXCents = Rule
{ name = "intersect (and X cents)"
, pattern =
[ Predicate isWithoutCents
, regex "ו"
, Predicate isCents
]
, prod = \case
(Token AmountOfMoney fd :
_ :
Token AmountOfMoney AmountOfMoneyData { TAmountOfMoney.value = Just c }:
_) -> Just . Token AmountOfMoney $ withCents c fd
_ -> Nothing
}
rulePounds :: Rule
rulePounds = Rule
{ name = "£"
, pattern =
[ regex "פאונד(ים)?"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Pound
}
ruleDollar :: Rule
ruleDollar = Rule
{ name = "$"
, pattern =
[ regex "דולר(ים)?"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Dollar
}
ruleCent :: Rule
ruleCent = Rule
{ name = "cent"
, pattern =
[ regex "סנט(ים)?"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Cent
}
ruleEUR :: Rule
ruleEUR = Rule
{ name = ""
, pattern =
[ regex "אירו|יורו"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly EUR
}
ruleOneGBP :: Rule
ruleOneGBP = Rule
{ name = "OneGBP"
, pattern =
[ regex "לירה שטרלינג"
]
, prod = \_ -> Just . Token AmountOfMoney $ withValue 1 $ currencyOnly GBP
}
ruleGBP :: Rule
ruleGBP = Rule
{ name = "OneGBP"
, pattern =
[ regex "לירות שטרלינג"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly GBP
}
rulePrecision :: Rule
rulePrecision = Rule
{ name = "about|exactly <amount-of-money>"
, pattern =
[ regex "בערך|בדיוק|קרוב ל"
, Predicate isMoneyWithValue
]
, prod = \case
(_:
token:
_) -> Just token
_ -> Nothing
}
ruleIntervalBetweenNumeral :: Rule
ruleIntervalBetweenNumeral = Rule
{ name = "between|from <numeral> to|and <amount-of-money>"
, pattern =
[ regex "מ?|בין "
, Predicate isPositive
, regex "עד |ל"
, Predicate isSimpleAmountOfMoney
]
, prod = \case
(_:
Token Numeral NumeralData { TNumeral.value = from }:
_:
Token AmountOfMoney AmountOfMoneyData { TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c }:
_) | from < to ->
Just . Token AmountOfMoney . withInterval (from, to) $ currencyOnly c
_ -> Nothing
}
ruleIntervalBetween :: Rule
ruleIntervalBetween = Rule
{ name = "between|from <amount-of-money> to|and <amount-of-money>"
, pattern =
[ regex "מ?|בין "
, Predicate isSimpleAmountOfMoney
, regex "עד |ל"
, Predicate isSimpleAmountOfMoney
]
, prod = \case
(_:
Token AmountOfMoney AmountOfMoneyData { TAmountOfMoney.value = Just from,
TAmountOfMoney.currency = c1 }:
_:
Token AmountOfMoney AmountOfMoneyData { TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c2 }:
_) | from < to && c1 == c2 ->
Just . Token AmountOfMoney . withInterval (from, to) $
currencyOnly c1
_ -> Nothing
}
ruleIntervalNumeralDash :: Rule
ruleIntervalNumeralDash = Rule
{ name = "<numeral> - <amount-of-money>"
, pattern =
[ Predicate isPositive
, regex "-"
, Predicate isSimpleAmountOfMoney
]
, prod = \case
(Token Numeral NumeralData { TNumeral.value = from }:
_:
Token AmountOfMoney AmountOfMoneyData { TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c }:
_) | from < to -> Just . Token AmountOfMoney . withInterval (from, to) $
currencyOnly c
_ -> Nothing
}
ruleIntervalDash :: Rule
ruleIntervalDash = Rule
{ name = "<amount-of-money> - <amount-of-money>"
, pattern =
[ Predicate isSimpleAmountOfMoney
, regex "-"
, Predicate isSimpleAmountOfMoney
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData { TAmountOfMoney.value = Just from,
TAmountOfMoney.currency = c1 }:
_:
Token AmountOfMoney AmountOfMoneyData { TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c2 }:
_) | from < to && c1 == c2 ->
Just . Token AmountOfMoney . withInterval (from, to) $
currencyOnly c1
_ -> Nothing
}
ruleIntervalMax :: Rule
ruleIntervalMax = Rule
{ name = "under/less/lower/no more than <amount-of-money>"
, pattern =
[ regex "פחות מ|עד|לא יותר מ|מתחת ל?|לא מעל"
, Predicate isSimpleAmountOfMoney
]
, prod = \case
(_:
Token AmountOfMoney AmountOfMoneyData { TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c }:
_) -> Just . Token AmountOfMoney . withMax to $ currencyOnly c
_ -> Nothing
}
ruleIntervalMin :: Rule
ruleIntervalMin = Rule
{ name = "over/above/at least/more than <amount-of-money>"
, pattern =
[ regex "יותר מ|מעל|מ|לא פחות מ|לא מתחת ל"
, Predicate isSimpleAmountOfMoney
]
, prod = \case
(_:
Token AmountOfMoney AmountOfMoneyData { TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c }:
_) -> Just . Token AmountOfMoney . withMin to $ currencyOnly c
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleUnitAmount
, ruleCent
, ruleEUR
, ruleIntersectAndXCents
, ruleIntervalBetweenNumeral
, ruleIntervalBetween
, ruleIntervalMax
, ruleIntervalMin
, ruleIntervalNumeralDash
, ruleIntervalDash
, rulePounds
, ruleOneGBP
, ruleGBP
, rulePrecision
, ruleIntersect
, ruleAgura
, ruleShekel
, ruleOneShekel
, ruleTwoShekel
, ruleOneAgura
, ruleThousandShekel
, ruleMillionShekel
, ruleDollar
]

View File

@ -68,6 +68,8 @@ currencies = HashMap.fromList
, ("hrk", HRK)
, ("idr", IDR)
, ("ils", ILS)
, ("", ILS)
, ("nis", ILS)
, ("inr", INR)
, ("iqd", IQD)
, ("rs", INR)
@ -125,7 +127,7 @@ ruleCurrencies :: Rule
ruleCurrencies = Rule
{ name = "currencies"
, pattern =
[ regex "(aed|aud|bgn|brl|byn|¢|c|cad|chf|cny|\\$|dinars?|dkk|dollars?|egp|(e|€)uro?s?|€|gbp|gel|\x20BE|hrk|idr|ils|inr|iqd|jmd|jod|¥|jpy|lari|krw|kwd|lbp|mad|₮|mnt|tugriks?|myr|rm|nok|nzd|£|pkr|pln|pta?s?|qar|₽|rs\\.?|riy?als?|ron|rub|rupees?|sar|sek|sgb|shekels?|thb|ttd|us(d|\\$)|vnd|yen|yuan|zar)"
[ regex "(aed|aud|bgn|brl|byn|¢|c|cad|chf|cny|\\$|dinars?|dkk|dollars?|egp|(e|€)uro?s?|€|gbp|gel|\x20BE|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|us(d|\\$)|vnd|yen|yuan|zar)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> do

View File

@ -70,6 +70,10 @@ allExamples = concat
, "1.10"
, "01.10"
]
, examples (NumeralValue 0.5)
[ "חצי"
, "0.5"
]
, examples (NumeralValue 0.77)
[ "0.77"
, ".77"

View File

@ -344,6 +344,15 @@ ruleCommas = Rule
_ -> Nothing
}
ruleHalf :: Rule
ruleHalf = Rule
{ name = "half"
, pattern =
[ regex "חצי"
]
, prod = \_ -> double 0.5
}
rules :: [Rule]
rules =
[ ruleCommas
@ -373,4 +382,5 @@ rules =
, ruleNumeralsPrefixWithNegativeOrMinus
, rulePowersOfTen
, ruleSingle
, ruleHalf
]

View File

@ -18,6 +18,7 @@ module Duckling.Rules.HE
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.AmountOfMoney.HE.Rules as AmountOfMoney
import qualified Duckling.Duration.HE.Rules as Duration
import qualified Duckling.Numeral.HE.Rules as Numeral
import qualified Duckling.Ordinal.HE.Rules as Ordinal
@ -32,7 +33,7 @@ localeRules region (This (CustomDimension dim)) = dimLocaleRules region dim
localeRules _ _ = []
langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = []
langRules (This AmountOfMoney) = AmountOfMoney.rules
langRules (This CreditCardNumber) = []
langRules (This Distance) = []
langRules (This Duration) = Duration.rules

View File

@ -235,6 +235,8 @@ library
, Duckling.AmountOfMoney.FR.Rules
, Duckling.AmountOfMoney.GA.Corpus
, Duckling.AmountOfMoney.GA.Rules
, Duckling.AmountOfMoney.HE.Corpus
, Duckling.AmountOfMoney.HE.Rules
, Duckling.AmountOfMoney.HR.Corpus
, Duckling.AmountOfMoney.HR.Rules
, Duckling.AmountOfMoney.ID.Corpus
@ -831,6 +833,7 @@ test-suite duckling-test
, Duckling.AmountOfMoney.ES.Tests
, Duckling.AmountOfMoney.FR.Tests
, Duckling.AmountOfMoney.GA.Tests
, Duckling.AmountOfMoney.HE.Tests
, Duckling.AmountOfMoney.HR.Tests
, Duckling.AmountOfMoney.ID.Tests
, Duckling.AmountOfMoney.IT.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.AmountOfMoney.HE.Tests
( tests ) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.AmountOfMoney.HE.Corpus
import Duckling.Dimensions.Types
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "HE Tests"
[ makeCorpusTest [This AmountOfMoney] corpus
]

View File

@ -20,6 +20,7 @@ import qualified Duckling.AmountOfMoney.BG.Tests as BG
import qualified Duckling.AmountOfMoney.ES.Tests as ES
import qualified Duckling.AmountOfMoney.FR.Tests as FR
import qualified Duckling.AmountOfMoney.GA.Tests as GA
import qualified Duckling.AmountOfMoney.HE.Tests as HE
import qualified Duckling.AmountOfMoney.HR.Tests as HR
import qualified Duckling.AmountOfMoney.ID.Tests as ID
import qualified Duckling.AmountOfMoney.IT.Tests as IT
@ -43,6 +44,7 @@ tests = testGroup "AmountOfMoney Tests"
, ES.tests
, FR.tests
, GA.tests
, HE.tests
, HR.tests
, ID.tests
, IT.tests