Added IT Rules and Corpus for AmountOfMoney (#284)

Summary:
Hi,
I've added Rules and Corpus for Italian language on "AmountOfMoney".
Running `stack test`, I always get `empty result on "10 000 dollari"`.
I've checked my code more than once but I can't figure out what is not working. I made a PR in order to make it easier for you to understand what's going wrong :)

I really hope that my contribution can help.
Regards!
Pull Request resolved: https://github.com/facebook/duckling/pull/284

Reviewed By: chinmay87

Differential Revision: D13551890

Pulled By: patapizza

fbshipit-source-id: c1b448e44c2c6720ad93f61c6396f4d75231131e
This commit is contained in:
Michele Riva 2019-01-02 13:49:21 -08:00 committed by Facebook Github Bot
parent c0e4c8c926
commit 9a45a0cf7b
10 changed files with 403 additions and 8 deletions

View File

@ -206,7 +206,6 @@ ruleIntervalMin = Rule
_ -> Nothing
}
rulePounds :: Rule
rulePounds = Rule
{ name = "£"

View File

@ -0,0 +1,78 @@
-- 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.IT.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 IT Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Dollar 10)
[ "$10"
, "10$"
, "dieci dollari"
]
, examples (simple Dollar 10000)
[ "$10.000"
, "10K$"
, "$10k"
, "10 000 dollari"
, "10 000,00 $"
]
, examples (simple USD 1.23)
[ "USD1,23"
, "1 USD e 23 centesimi"
, "1 USD 23 centesimi"
]
, examples (simple EUR 20)
[ "20€"
, "20 euro"
, "20 Euro"
, "20 Euro"
, "EUR 20"
]
, examples (simple EUR 29.99)
[ "EUR29,99"
]
, examples (simple Pound 9)
[ "nove sterline"
, "quasi nove sterline"
]
, examples (simple GBP 3.01)
[ "GBP3,01"
, "GBP 3,01"
]
, examples (between EUR (10, 20))
[ "tra 10 e 20 euro"
, "tra 10 euro e 20 euro"
, "10 - 20 euro"
, "10 euro - 20 euro"
]
, examples (above EUR 10)
[ "almeno 10 euro"
, "più di 10 euro"
, "più di 10 euro"
]
, examples (under Dollar 10)
[ "meno di 10 dollari"
, "non più di 10 dollari"
]
]

View File

@ -0,0 +1,271 @@
-- 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.IT.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)
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Regex.Types (GroupMatch (..))
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
}
ruleIntersectAndNumeral :: Rule
ruleIntersectAndNumeral = Rule
{ name = "intersect (and number)"
, pattern =
[ Predicate isWithoutCents
, regex "e"
, Predicate isNatural
]
, prod = \tokens -> case tokens of
(Token AmountOfMoney fd:
_:
Token Numeral NumeralData{TNumeral.value = c}:
_) -> Just . Token AmountOfMoney $ withCents c fd
_ -> Nothing
}
rulePrecision :: Rule
rulePrecision = Rule
{ name = "precision"
, pattern =
[ regex "esattamente|quasi|più o meno|circa"
, Predicate isMoneyWithValue
]
, prod = \tokens -> case tokens of
(_:token:_) -> Just token
_ -> Nothing
}
ruleCent :: Rule
ruleCent = Rule
{ name = "cent"
, pattern =
[ regex "cent(esim)i?o?"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Cent
}
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
}
ruleIntervalBetweenNumeral :: Rule
ruleIntervalBetweenNumeral = Rule
{ name = "between|from <numeral> to|and <amount-of-money>"
, pattern =
[ regex "tra"
, Predicate isPositive
, regex "e"
, Predicate isSimpleAmountOfMoney
]
, prod = \tokens -> case tokens of
(_:
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 "tra"
, Predicate isSimpleAmountOfMoney
, regex "e"
, Predicate isSimpleAmountOfMoney
]
, prod = \tokens -> case tokens of
(_:
Token AmountOfMoney AmountOfMoneyData {
TAmountOfMoney.value = Just from,
TAmountOfMoney.currency = c1
}:
_:
Token AmountOfMoney AmountOfMoneyData {
TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c2
}:
_) | c1 == c2, from < to ->
Just . Token AmountOfMoney . withInterval (from, to) $ currencyOnly c1
_ -> Nothing
}
ruleIntervalNumeralDash :: Rule
ruleIntervalNumeralDash = Rule
{ name = "<numeral> - <amount-of-money>"
, pattern =
[ Predicate isNatural
, regex "-"
, Predicate isSimpleAmountOfMoney
]
, prod = \tokens -> case tokens of
(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 = \tokens -> case tokens of
(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 "(meno|non più) di"
, Predicate isSimpleAmountOfMoney
]
, prod = \tokens -> case tokens of
(_:
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 "più di|almeno"
, Predicate isSimpleAmountOfMoney
]
, prod = \tokens -> case tokens of
(_:
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c}:
_) -> Just . Token AmountOfMoney . withMin to $ currencyOnly c
_ -> Nothing
}
ruleCurrencies :: Rule
ruleCurrencies = Rule
{ name = "£, $"
, pattern =
[ regex "(dollari|sterline)"
]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):_) -> case Text.toLower match of
"dollari" -> Just . Token AmountOfMoney $ currencyOnly Dollar
"sterline" -> Just . Token AmountOfMoney $ currencyOnly Pound
_ -> Nothing
_ -> Nothing
}
ruleIntersectAndXCents :: Rule
ruleIntersectAndXCents = Rule
{ name = "intersect (and X cents)"
, pattern =
[ Predicate isWithoutCents
, regex "e"
, 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
}
rules :: [Rule]
rules =
[ ruleUnitAmount
, ruleCent
, ruleIntersect
, ruleIntersectAndNumeral
, ruleIntersectAndXCents
, ruleIntersectXCents
, ruleIntervalBetween
, ruleIntervalBetweenNumeral
, ruleIntervalDash
, ruleIntervalMax
, ruleIntervalMin
, ruleIntervalNumeralDash
, ruleCurrencies
, rulePrecision
]

View File

@ -126,4 +126,11 @@ allExamples = concat
, "-1200K"
, "-,0012G"
]
, examples (NumeralValue 6.7)
[ "6,7"
]
, examples (NumeralValue 6700.54)
[ "6.700,54"
, "6 700,54"
]
]

View File

@ -129,12 +129,14 @@ allExamples = concat
, "100000"
, "100K"
, "100k"
, "100 000"
]
, examples (NumeralValue 3000000)
[ "3M"
, "3000K"
, "3000000"
, "3.000.000"
, "3 000 000"
]
, examples (NumeralValue 1200000)
[ "1.200.000"
@ -152,4 +154,11 @@ allExamples = concat
, "-1200K"
, "-,0012G"
]
, examples (NumeralValue 6.7)
[ "6,7"
]
, examples (NumeralValue 6700.54)
[ "6.700,54"
, "6 700,54"
]
]

View File

@ -43,11 +43,11 @@ ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator"
, pattern =
[ regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"
[ regex "(\\d+(([\\. ])\\d\\d\\d)+,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
(Token RegexMatch (GroupMatch (match:_:sep:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace sep Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -304,11 +304,12 @@ ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ."
, pattern =
[ regex "(\\d{1,3}(\\.\\d\\d\\d){1,5})"
[ regex "(\\d{1,3}(([\\. ])\\d\\d\\d){1,5})"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace "." Text.empty match) >>= double
(Token RegexMatch (GroupMatch (match:_:sep:_)):
_) -> let fmt = Text.replace sep Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}

View File

@ -18,6 +18,7 @@ module Duckling.Rules.IT
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.AmountOfMoney.IT.Rules as AmountOfMoney
import qualified Duckling.Duration.IT.Rules as Duration
import qualified Duckling.Email.IT.Rules as Email
import qualified Duckling.Numeral.IT.Rules as Numeral
@ -35,7 +36,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

@ -236,6 +236,8 @@ library
, Duckling.AmountOfMoney.HR.Rules
, Duckling.AmountOfMoney.ID.Corpus
, Duckling.AmountOfMoney.ID.Rules
, Duckling.AmountOfMoney.IT.Rules
, Duckling.AmountOfMoney.IT.Corpus
, Duckling.AmountOfMoney.KA.Corpus
, Duckling.AmountOfMoney.KA.Rules
, Duckling.AmountOfMoney.KO.Corpus
@ -818,6 +820,7 @@ test-suite duckling-test
, Duckling.AmountOfMoney.GA.Tests
, Duckling.AmountOfMoney.HR.Tests
, Duckling.AmountOfMoney.ID.Tests
, Duckling.AmountOfMoney.IT.Tests
, Duckling.AmountOfMoney.KA.Tests
, Duckling.AmountOfMoney.KO.Tests
, Duckling.AmountOfMoney.MN.Tests

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.AmountOfMoney.IT.Tests
( tests
) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.AmountOfMoney.IT.Corpus
import Duckling.Dimensions.Types
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "IT Tests"
[ makeCorpusTest [This AmountOfMoney] corpus
]

View File

@ -22,6 +22,7 @@ import qualified Duckling.AmountOfMoney.FR.Tests as FR
import qualified Duckling.AmountOfMoney.GA.Tests as GA
import qualified Duckling.AmountOfMoney.HR.Tests as HR
import qualified Duckling.AmountOfMoney.ID.Tests as ID
import qualified Duckling.AmountOfMoney.IT.Tests as IT
import qualified Duckling.AmountOfMoney.KA.Tests as KA
import qualified Duckling.AmountOfMoney.KO.Tests as KO
import qualified Duckling.AmountOfMoney.MN.Tests as MN
@ -44,6 +45,7 @@ tests = testGroup "AmountOfMoney Tests"
, GA.tests
, HR.tests
, ID.tests
, IT.tests
, KA.tests
, KO.tests
, MN.tests