Implement AmountOfMoney

Summary: implement AmountOfMoney rules and corpus for ZH

Reviewed By: patapizza

Differential Revision: D7508507

fbshipit-source-id: 3591b399a9880c5278587979c6576720343cc123
This commit is contained in:
Aaron Yue 2018-04-17 16:44:32 -07:00 committed by Facebook Github Bot
parent babe317723
commit 4df76289bc
9 changed files with 399 additions and 3 deletions

View File

@ -12,8 +12,11 @@
module Duckling.AmountOfMoney.Helpers
( currencyOnly
, financeWith
, isSimpleAmountOfMoney
, isCent
, isCents
, isCurrencyOnly
, isDime
, isMoneyWithValue
, isWithoutCents
, withCents
@ -28,7 +31,7 @@ import Data.Maybe (isJust)
import Prelude
import Duckling.AmountOfMoney.Types (Currency (..), AmountOfMoneyData (..))
import Duckling.Numeral.Types (isInteger)
import Duckling.Numeral.Types (getIntValue, isInteger)
import Duckling.Dimensions.Types
import Duckling.Types hiding (Entity(..))
@ -60,6 +63,23 @@ isCurrencyOnly (Token AmountOfMoney AmountOfMoneyData
{value = Nothing, minValue = Nothing, maxValue = Nothing}) = True
isCurrencyOnly _ = False
isSimpleAmountOfMoney :: Predicate
isSimpleAmountOfMoney (Token AmountOfMoney AmountOfMoneyData
{minValue = Nothing, maxValue = Nothing}) = True
isSimpleAmountOfMoney _ = False
isDime :: Predicate
isDime (Token AmountOfMoney AmountOfMoneyData
{value = Just d, currency = Cent}) =
maybe False (\i -> (i `mod` 10) == 0) $ getIntValue d
isDime _ = False
isCent :: Predicate
isCent (Token AmountOfMoney AmountOfMoneyData
{value = Just c, currency = Cent}) =
maybe False (\i -> i >= 0 && i <= 9) $ getIntValue c
isCent _ = False
-- -----------------------------------------------------------------
-- Production

View File

@ -40,6 +40,9 @@ currencies = HashMap.fromList
, ("byn", BYN)
, ("¢", Cent)
, ("c", Cent)
, ("cny", CNY)
, ("rmb", CNY)
, ("yuan", CNY)
, ("$", Dollar)
, ("dinar", Dinar)
, ("dinars", Dinar)
@ -103,7 +106,7 @@ ruleCurrencies :: Rule
ruleCurrencies = Rule
{ name = "currencies"
, pattern =
[ regex "(aed|aud|bgn|brl|byn|¢|c|\\$|dinars?|dollars?|egp|(e|€)uro?s?|€|gbp|hrk|idr|ils|inr|iqd|jod|¥|jpy|krw|kwd|lbp|mad|myr|rm|nok|£|pta?s?|qar|₽|rs\\.?|riy?als?|ron|rub|rupees?|sar|sek|sgb|shekels?|us(d|\\$)|vnd|yen)"
[ regex "(aed|aud|bgn|brl|byn|¢|c|cny|\\$|dinars?|dollars?|egp|(e|€)uro?s?|€|gbp|hrk|idr|ils|inr|iqd|jod|¥|jpy|krw|kwd|lbp|mad|myr|rm|nok|£|pta?s?|qar|₽|rs\\.?|riy?als?|ron|rub|rupees?|sar|sek|sgb|shekels?|us(d|\\$)|vnd|yen|yuan)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> do

View File

@ -41,6 +41,7 @@ data Currency
| BGN
| BRL
| BYN
| CNY
| EGP
| EUR
| GBP
@ -82,6 +83,7 @@ instance ToJSON Currency where
toJSON BGN = "BGN"
toJSON BRL = "BRL"
toJSON BYN = "BYN"
toJSON CNY = "CNY"
toJSON EGP = "EGP"
toJSON EUR = "EUR"
toJSON GBP = "GBP"

View File

@ -0,0 +1,68 @@
-- 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.ZH.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 ZH Nothing},
testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Cent 5)
[ "五分"
, "5分"
]
, examples (simple Cent 20)
[ "20分"
, "二十分"
, "2角"
, "两毛"
]
, examples (simple Cent 25)
[ "25分"
, "二十五分"
, "两角五分"
, "两毛五"
]
, examples (simple Dollar 7)
[ "7块"
, "七元"
]
, examples (simple CNY 3.14)
[ "3.14人民币"
, "人民幣3.14"
]
, examples (under Dollar 1.2)
[ "1.2元以下"
, "最多一块二角"
, "最多一块二"
]
, examples (above Dollar 3.04)
[ "3.04块以上"
, "至少三块四分"
, "至少三块零四"
]
, examples (between Dollar (5.6, 5.78))
[ "5.6到5.78元"
, "五元六角-五元七毛八分"
, "五块六到五块七毛八"
]
]

View File

@ -0,0 +1,274 @@
-- 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.ZH.Rules
( rules
) where
import Data.Maybe
import Data.String
import Prelude
import qualified Data.Text as Text
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency (..), AmountOfMoneyData (..))
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers (isNatural, isPositive, oneOf)
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.AmountOfMoney.Types as TAmountOfMoney
import qualified Duckling.Numeral.Types as TNumeral
ruleCNY :: Rule
ruleCNY = Rule
{ name = "cny"
, pattern =
[ regex "人民币|人民幣"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly CNY
}
ruleCNYPrefix :: Rule
ruleCNYPrefix = Rule
{ name = "cny prefix"
, pattern =
[ regex "人民币|人民幣"
, Predicate isPositive
]
, prod = \case
(_:Token Numeral NumeralData{TNumeral.value = v}:_) ->
Just . Token AmountOfMoney . withValue v $ currencyOnly CNY
_ -> Nothing
}
ruleCent :: Rule
ruleCent = Rule
{ name = "cent"
, pattern =
[ regex ""
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Cent
}
ruleDime :: Rule
ruleDime = Rule
{ name = "dime"
, pattern =
[ Predicate isPositive
, regex "角|毛"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:_) ->
Just . Token AmountOfMoney $
withCents (v * 10) $ currencyOnly Cent
_ -> Nothing
}
ruleDollar :: Rule
ruleDollar = Rule
{ name = "dollar"
, pattern =
[ regex "元|圆|块"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Dollar
}
rulePrecision :: Rule
rulePrecision = Rule
{ name = "exactly/about <amount-of-money>"
, pattern =
[ regex "刚好|恰好|大概"
, Predicate isMoneyWithValue
]
, prod = \case
(_:token:_) -> Just token
_ -> Nothing
}
rulePrecision2 :: Rule
rulePrecision2 = Rule
{ name = "about <amount-of-money>"
, pattern =
[ Predicate isMoneyWithValue
, regex "左右"
]
, prod = \case
(token:_) -> Just token
_ -> Nothing
}
ruleIntersectDimesAndCents :: Rule
ruleIntersectDimesAndCents = Rule
{ name = "intersect (X dimes and X cents)"
, pattern =
[ Predicate $ and . sequence [isSimpleAmountOfMoney, isDime]
, Predicate $ and . sequence [isSimpleAmountOfMoney, isCent]
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just d}:
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just c}:
_) ->
Just . Token AmountOfMoney $ withCents (c + d) $ currencyOnly Cent
_ -> Nothing
}
ruleIntersectDollarsAndDimesCents :: Rule
ruleIntersectDollarsAndDimesCents = Rule
{ name = "intersect (X dollars and X dimes/cents)"
, pattern =
[ Predicate $ and . sequence [isSimpleAmountOfMoney, isWithoutCents]
, Predicate $ and . sequence [isSimpleAmountOfMoney, isCents]
]
, prod = \case
(Token AmountOfMoney fd:
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just c}:
_) -> Just . Token AmountOfMoney $ withCents c fd
_ -> Nothing
}
ruleIntersect :: Rule
ruleIntersect = Rule
{ name = "intersect (implicit 0 delimited cents)"
, pattern =
[ Predicate $ and . sequence [isSimpleAmountOfMoney, isWithoutCents]
, regex "0|零|"
, oneOf [1..9]
]
, prod = \case
(Token AmountOfMoney fd:_:
Token Numeral NumeralData{TNumeral.value = c}:
_) -> Just . Token AmountOfMoney $ withCents c fd
_ -> Nothing
}
ruleIntersect2 :: Rule
ruleIntersect2 = Rule
{ name = "intersect (implicit unitless cents)"
, pattern =
[ Predicate $ and . sequence [isSimpleAmountOfMoney, isDime]
, Predicate isNatural
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just v}:
Token Numeral NumeralData{TNumeral.value = c}:
_) -> Just . Token AmountOfMoney $ withCents (v + c) $ currencyOnly Cent
_ -> Nothing
}
ruleIntersect3 :: Rule
ruleIntersect3 = Rule
{ name = "intersect (implicit unitless dimes)"
, pattern =
[ Predicate $ and . sequence [isSimpleAmountOfMoney, isWithoutCents]
, Predicate isNatural
]
, prod = \case
(Token AmountOfMoney fd:
Token Numeral NumeralData{TNumeral.value = d}:
_) -> Just . Token AmountOfMoney $ withCents (d * 10) fd
_ -> Nothing
}
ruleIntervalNumeralDash :: Rule
ruleIntervalNumeralDash = Rule
{ name = "<numeral> - <amount-of-money>"
, pattern =
[ Predicate isPositive
, regex "-|~|到"
, financeWith TAmountOfMoney.value isJust
]
, 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 =
[ financeWith TAmountOfMoney.value isJust
, regex "-|~|到"
, financeWith TAmountOfMoney.value isJust
]
, 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
}
ruleIntervalBound :: Rule
ruleIntervalBound = Rule
{ name = "under/less/lower/no more than <amount-of-money> (最多|至少|最少)"
, pattern =
[ regex "(最多|至少|最少)"
, financeWith TAmountOfMoney.value isJust
]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c}:
_) -> case match of
"最多" -> Just . Token AmountOfMoney . withMax to $ currencyOnly c
"最少" -> Just . Token AmountOfMoney . withMin to $ currencyOnly c
"至少" -> Just . Token AmountOfMoney . withMin to $ currencyOnly c
_ -> Nothing
_ -> Nothing
}
ruleIntervalBound2 :: Rule
ruleIntervalBound2 = Rule
{ name = "under/less/lower/no more than <amount-of-money> (以下|以上)"
, pattern =
[ financeWith TAmountOfMoney.value isJust
, regex "(以下|以上)"
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c}:
Token RegexMatch (GroupMatch (match:_)):
_) -> case match of
"以下" -> Just . Token AmountOfMoney . withMax to $ currencyOnly c
"以上" -> Just . Token AmountOfMoney . withMin to $ currencyOnly c
_ -> Nothing
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleCent
, ruleCNY
, ruleCNYPrefix
, ruleDime
, ruleDollar
, ruleIntersect
, ruleIntersect2
, ruleIntersect3
, ruleIntersectDimesAndCents
, ruleIntersectDollarsAndDimesCents
, ruleIntervalDash
, ruleIntervalNumeralDash
, ruleIntervalBound
, ruleIntervalBound2
, rulePrecision
, rulePrecision2
]

View File

@ -18,6 +18,7 @@ module Duckling.Rules.ZH
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.AmountOfMoney.ZH.Rules as AmountOfMoney
import qualified Duckling.Distance.ZH.Rules as Distance
import qualified Duckling.Numeral.ZH.Rules as Numeral
import qualified Duckling.Ordinal.ZH.Rules as Ordinal
@ -40,7 +41,7 @@ localeRules TW (This Time) = TimeTW.rules
localeRules _ _ = []
langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = []
langRules (This AmountOfMoney) = AmountOfMoney.rules
langRules (This Distance) = Distance.rules
langRules (This Duration) = []
langRules (This Email) = []

View File

@ -196,6 +196,8 @@ library
, Duckling.AmountOfMoney.VI.Rules
, Duckling.AmountOfMoney.NL.Corpus
, Duckling.AmountOfMoney.NL.Rules
, Duckling.AmountOfMoney.ZH.Corpus
, Duckling.AmountOfMoney.ZH.Rules
, Duckling.AmountOfMoney.Helpers
, Duckling.AmountOfMoney.Rules
, Duckling.AmountOfMoney.Types
@ -690,6 +692,7 @@ test-suite duckling-test
, Duckling.AmountOfMoney.SV.Tests
, Duckling.AmountOfMoney.VI.Tests
, Duckling.AmountOfMoney.NL.Tests
, Duckling.AmountOfMoney.ZH.Tests
, Duckling.AmountOfMoney.Tests
-- Distance

View File

@ -30,6 +30,7 @@ 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.VI.Tests as VI
import qualified Duckling.AmountOfMoney.ZH.Tests as ZH
tests :: TestTree
tests = testGroup "AmountOfMoney Tests"
@ -49,4 +50,5 @@ tests = testGroup "AmountOfMoney Tests"
, RU.tests
, SV.tests
, VI.tests
, ZH.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.ZH.Tests
( tests ) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.AmountOfMoney.ZH.Corpus
import Duckling.Dimensions.Types
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ZH Tests"
[ makeCorpusTest [This AmountOfMoney] corpus
]