Implement handling of "grand" for EN_?? locales

Summary: Add implementation of "a grand" and "<num> grand" for AU, BZ, CA, GB, IE, IN, JM, NZ, PH, TT, ZA locales. Some resolve to the local currency (AU, IN), others resolve to Dollar (NZ, PH).

Reviewed By: patapizza

Differential Revision: D7943186

fbshipit-source-id: c71ab462fa9df0ee65223ee82dc2c98457a4e13b
This commit is contained in:
RIAN DOUGLAS 2018-05-17 15:37:01 -07:00 committed by Facebook Github Bot
parent 8237ef4503
commit 884904b5ca
23 changed files with 937 additions and 3 deletions

View File

@ -0,0 +1,36 @@
-- 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.EN.AU.Corpus
( allExamples
, negativeExamples
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples = concat
[ examples (simple AUD 1000)
[ "a grand"
, "1 grand"
]
, examples (simple AUD 10000)
[ "10 grand"
]
]
negativeExamples :: [Text]
negativeExamples =
[ "grand"
]

View File

@ -0,0 +1,53 @@
-- 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.EN.AU.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..))
import Duckling.Numeral.Helpers (isPositive)
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleAGrand :: Rule
ruleAGrand = Rule
{ name = "a grand"
, pattern =
[ regex "a grand"
]
, prod = \_ -> Just . Token AmountOfMoney . withValue 1000 $ currencyOnly AUD
}
ruleGrand :: Rule
ruleGrand = Rule
{ name = "<amount> grand"
, pattern =
[ Predicate isPositive
, regex "grand"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_)
-> Just . Token AmountOfMoney . withValue (1000 * v) $ currencyOnly AUD
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleAGrand
, ruleGrand
]

View File

@ -0,0 +1,36 @@
-- 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.EN.BZ.Corpus
( allExamples
, negativeExamples
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples = concat
[ examples (simple Dollar 1000)
[ "a grand"
, "1 grand"
]
, examples (simple Dollar 10000)
[ "10 grand"
]
]
negativeExamples :: [Text]
negativeExamples =
[ "grand"
]

View 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. 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.EN.BZ.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..))
import Duckling.Numeral.Helpers (isPositive)
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleAGrand :: Rule
ruleAGrand = Rule
{ name = "a grand"
, pattern =
[ regex "a grand"
]
, prod = \_ -> Just . Token AmountOfMoney . withValue 1000
$ currencyOnly Dollar
}
ruleGrand :: Rule
ruleGrand = Rule
{ name = "<amount> grand"
, pattern =
[ Predicate isPositive
, regex "grand"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_)
-> Just . Token AmountOfMoney . withValue (1000 * v)
$ currencyOnly Dollar
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleAGrand
, ruleGrand
]

View File

@ -0,0 +1,36 @@
-- 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.EN.IE.Corpus
( allExamples
, negativeExamples
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples = concat
[ examples (simple Dollar 1000)
[ "a grand"
, "1 grand"
]
, examples (simple Dollar 10000)
[ "10 grand"
]
]
negativeExamples :: [Text]
negativeExamples =
[ "grand"
]

View 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. 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.EN.IE.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..))
import Duckling.Numeral.Helpers (isPositive)
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleAGrand :: Rule
ruleAGrand = Rule
{ name = "a grand"
, pattern =
[ regex "a grand"
]
, prod = \_ -> Just . Token AmountOfMoney . withValue 1000
$ currencyOnly Dollar
}
ruleGrand :: Rule
ruleGrand = Rule
{ name = "<amount> grand"
, pattern =
[ Predicate isPositive
, regex "grand"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_)
-> Just . Token AmountOfMoney . withValue (1000 * v)
$ currencyOnly Dollar
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleAGrand
, ruleGrand
]

View File

@ -0,0 +1,36 @@
-- 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.EN.IN.Corpus
( allExamples
, negativeExamples
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples = concat
[ examples (simple Dollar 1000)
[ "a grand"
, "1 grand"
]
, examples (simple Dollar 10000)
[ "10 grand"
]
]
negativeExamples :: [Text]
negativeExamples =
[ "grand"
]

View File

@ -0,0 +1,53 @@
-- 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.EN.IN.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..))
import Duckling.Numeral.Helpers (isPositive)
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleAGrand :: Rule
ruleAGrand = Rule
{ name = "a grand"
, pattern =
[ regex "a grand"
]
, prod = \_ -> Just . Token AmountOfMoney . withValue 1000 $ currencyOnly Dollar
}
ruleGrand :: Rule
ruleGrand = Rule
{ name = "<amount> grand"
, pattern =
[ Predicate isPositive
, regex "grand"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_)
-> Just . Token AmountOfMoney . withValue (1000 * v) $ currencyOnly Dollar
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleAGrand
, ruleGrand
]

View File

@ -0,0 +1,36 @@
-- 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.EN.JM.Corpus
( allExamples
, negativeExamples
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples = concat
[ examples (simple JMD 1000)
[ "a grand"
, "1 grand"
]
, examples (simple JMD 10000)
[ "10 grand"
]
]
negativeExamples :: [Text]
negativeExamples =
[ "grand"
]

View 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. 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.EN.JM.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..))
import Duckling.Numeral.Helpers (isPositive)
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleAGrand :: Rule
ruleAGrand = Rule
{ name = "a grand"
, pattern =
[ regex "a grand"
]
, prod = \_ -> Just . Token AmountOfMoney . withValue 1000
$ currencyOnly JMD
}
ruleGrand :: Rule
ruleGrand = Rule
{ name = "<amount> grand"
, pattern =
[ Predicate isPositive
, regex "grand"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_)
-> Just . Token AmountOfMoney . withValue (1000 * v)
$ currencyOnly JMD
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleAGrand
, ruleGrand
]

View File

@ -0,0 +1,36 @@
-- 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.EN.NZ.Corpus
( allExamples
, negativeExamples
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples = concat
[ examples (simple NZD 1000)
[ "a grand"
, "1 grand"
]
, examples (simple NZD 10000)
[ "10 grand"
]
]
negativeExamples :: [Text]
negativeExamples =
[ "grand"
]

View 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. 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.EN.NZ.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..))
import Duckling.Numeral.Helpers (isPositive)
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleAGrand :: Rule
ruleAGrand = Rule
{ name = "a grand"
, pattern =
[ regex "a grand"
]
, prod = \_ -> Just . Token AmountOfMoney . withValue 1000
$ currencyOnly NZD
}
ruleGrand :: Rule
ruleGrand = Rule
{ name = "<amount> grand"
, pattern =
[ Predicate isPositive
, regex "grand"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_)
-> Just . Token AmountOfMoney . withValue (1000 * v)
$ currencyOnly NZD
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleAGrand
, ruleGrand
]

View File

@ -0,0 +1,36 @@
-- 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.EN.PH.Corpus
( allExamples
, negativeExamples
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples = concat
[ examples (simple Dollar 1000)
[ "a grand"
, "1 grand"
]
, examples (simple Dollar 10000)
[ "10 grand"
]
]
negativeExamples :: [Text]
negativeExamples =
[ "grand"
]

View 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. 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.EN.PH.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..))
import Duckling.Numeral.Helpers (isPositive)
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleAGrand :: Rule
ruleAGrand = Rule
{ name = "a grand"
, pattern =
[ regex "a grand"
]
, prod = \_ -> Just . Token AmountOfMoney . withValue 1000
$ currencyOnly Dollar
}
ruleGrand :: Rule
ruleGrand = Rule
{ name = "<amount> grand"
, pattern =
[ Predicate isPositive
, regex "grand"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_)
-> Just . Token AmountOfMoney . withValue (1000 * v)
$ currencyOnly Dollar
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleAGrand
, ruleGrand
]

View File

@ -0,0 +1,36 @@
-- 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.EN.TT.Corpus
( allExamples
, negativeExamples
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples = concat
[ examples (simple TTD 1000)
[ "a grand"
, "1 grand"
]
, examples (simple TTD 10000)
[ "10 grand"
]
]
negativeExamples :: [Text]
negativeExamples =
[ "grand"
]

View 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. 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.EN.TT.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..))
import Duckling.Numeral.Helpers (isPositive)
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleAGrand :: Rule
ruleAGrand = Rule
{ name = "a grand"
, pattern =
[ regex "a grand"
]
, prod = \_ -> Just . Token AmountOfMoney . withValue 1000
$ currencyOnly TTD
}
ruleGrand :: Rule
ruleGrand = Rule
{ name = "<amount> grand"
, pattern =
[ Predicate isPositive
, regex "grand"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_)
-> Just . Token AmountOfMoney . withValue (1000 * v)
$ currencyOnly TTD
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleAGrand
, ruleGrand
]

View File

@ -0,0 +1,36 @@
-- 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.EN.ZA.Corpus
( allExamples
, negativeExamples
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples = concat
[ examples (simple Dollar 1000)
[ "a grand"
, "1 grand"
]
, examples (simple Dollar 10000)
[ "10 grand"
]
]
negativeExamples :: [Text]
negativeExamples =
[ "grand"
]

View 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. 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.EN.ZA.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..))
import Duckling.Numeral.Helpers (isPositive)
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleAGrand :: Rule
ruleAGrand = Rule
{ name = "a grand"
, pattern =
[ regex "a grand"
]
, prod = \_ -> Just . Token AmountOfMoney . withValue 1000
$ currencyOnly Dollar
}
ruleGrand :: Rule
ruleGrand = Rule
{ name = "<amount> grand"
, pattern =
[ Predicate isPositive
, regex "grand"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_)
-> Just . Token AmountOfMoney . withValue (1000 * v)
$ currencyOnly Dollar
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleAGrand
, ruleGrand
]

View File

@ -69,6 +69,7 @@ currencies = HashMap.fromList
, ("rs.", INR)
, ("rupee", INR)
, ("rupees", INR)
, ("jmd", JMD)
, ("jod", JOD)
, ("¥", JPY)
, ("jpy", JPY)
@ -80,6 +81,7 @@ currencies = HashMap.fromList
, ("myr", MYR)
, ("rm", MYR)
, ("nok", NOK)
, ("nzd", NZD)
, ("£", Pound)
, ("pt", PTS)
, ("pta", PTS)
@ -98,6 +100,7 @@ currencies = HashMap.fromList
, ("sgd", SGD)
, ("shekel", ILS)
, ("shekels", ILS)
, ("ttd", TTD)
, ("usd", USD)
, ("us$", USD)
, ("vnd", VND)
@ -107,7 +110,7 @@ ruleCurrencies :: Rule
ruleCurrencies = Rule
{ name = "currencies"
, pattern =
[ regex "(aed|aud|bgn|brl|byn|¢|c|cad|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)"
[ regex "(aed|aud|bgn|brl|byn|¢|c|cad|cny|\\$|dinars?|dollars?|egp|(e|€)uro?s?|€|gbp|hrk|idr|ils|inr|iqd|jmd|jod|¥|jpy|krw|kwd|lbp|mad|myr|rm|nok|nzd|£|pta?s?|qar|₽|rs\\.?|riy?als?|ron|rub|rupees?|sar|sek|sgb|shekels?|ttd|us(d|\\$)|vnd|yen|yuan)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> do

View File

@ -51,6 +51,7 @@ data Currency
| ILS
| INR
| IQD
| JMD
| JOD
| JPY
| KRW
@ -59,6 +60,7 @@ data Currency
| MAD
| MYR
| NOK
| NZD
| PTS
| QAR
| RON
@ -66,6 +68,7 @@ data Currency
| SAR
| SEK
| SGD
| TTD
| USD
| VND
deriving (Eq, Generic, Hashable, Show, Ord, NFData)
@ -94,6 +97,7 @@ instance ToJSON Currency where
toJSON ILS = "ILS"
toJSON IQD = "IQD"
toJSON INR = "INR"
toJSON JMD = "JMD"
toJSON JOD = "JOD"
toJSON JPY = "JPY"
toJSON KRW = "KRW"
@ -102,6 +106,7 @@ instance ToJSON Currency where
toJSON MAD = "MAD"
toJSON MYR = "MYR"
toJSON NOK = "NOK"
toJSON NZD = "NZD"
toJSON PTS = "PTS"
toJSON QAR = "QAR"
toJSON RON = "RON"
@ -109,6 +114,7 @@ instance ToJSON Currency where
toJSON SAR = "SAR"
toJSON SEK = "SEK"
toJSON SGD = "SGD"
toJSON TTD = "TTD"
toJSON USD = "USD"
toJSON VND = "VND"

View File

@ -21,9 +21,18 @@ import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.AmountOfMoney.EN.Rules as AmountOfMoney
import qualified Duckling.AmountOfMoney.EN.AU.Rules as AmountOfMoneyAU
import qualified Duckling.AmountOfMoney.EN.BZ.Rules as AmountOfMoneyBZ
import qualified Duckling.AmountOfMoney.EN.CA.Rules as AmountOfMoneyCA
import qualified Duckling.AmountOfMoney.EN.GB.Rules as AmountOfMoneyGB
import qualified Duckling.AmountOfMoney.EN.IE.Rules as AmountOfMoneyIE
import qualified Duckling.AmountOfMoney.EN.IN.Rules as AmountOfMoneyIN
import qualified Duckling.AmountOfMoney.EN.JM.Rules as AmountOfMoneyJM
import qualified Duckling.AmountOfMoney.EN.NZ.Rules as AmountOfMoneyNZ
import qualified Duckling.AmountOfMoney.EN.PH.Rules as AmountOfMoneyPH
import qualified Duckling.AmountOfMoney.EN.TT.Rules as AmountOfMoneyTT
import qualified Duckling.AmountOfMoney.EN.US.Rules as AmountOfMoneyUS
import qualified Duckling.AmountOfMoney.EN.ZA.Rules as AmountOfMoneyZA
import qualified Duckling.Distance.EN.Rules as Distance
import qualified Duckling.Duration.EN.Rules as Duration
import qualified Duckling.Email.EN.Rules as Email
@ -52,9 +61,18 @@ defaultRules dim@(This Time) = TimeUS.rulesBackwardCompatible ++ langRules dim
defaultRules dim = langRules dim
localeRules :: Region -> Some Dimension -> [Rule]
localeRules AU (This AmountOfMoney) = AmountOfMoneyAU.rules
localeRules BZ (This AmountOfMoney) = AmountOfMoneyBZ.rules
localeRules CA (This AmountOfMoney) = AmountOfMoneyCA.rules
localeRules GB (This AmountOfMoney) = AmountOfMoneyGB.rules
localeRules IE (This AmountOfMoney) = AmountOfMoneyIE.rules
localeRules IN (This AmountOfMoney) = AmountOfMoneyIN.rules
localeRules JM (This AmountOfMoney) = AmountOfMoneyJM.rules
localeRules NZ (This AmountOfMoney) = AmountOfMoneyNZ.rules
localeRules PH (This AmountOfMoney) = AmountOfMoneyPH.rules
localeRules TT (This AmountOfMoney) = AmountOfMoneyTT.rules
localeRules US (This AmountOfMoney) = AmountOfMoneyUS.rules
localeRules ZA (This AmountOfMoney) = AmountOfMoneyZA.rules
localeRules AU (This Time) = TimeAU.rules
localeRules BZ (This Time) = TimeBZ.rules
localeRules CA (This Time) = TimeCA.rules

View File

@ -166,14 +166,32 @@ library
-- AmountOfMoney
, Duckling.AmountOfMoney.AR.Corpus
, Duckling.AmountOfMoney.AR.Rules
, Duckling.AmountOfMoney.EN.AU.Corpus
, Duckling.AmountOfMoney.EN.AU.Rules
, Duckling.AmountOfMoney.EN.BZ.Corpus
, Duckling.AmountOfMoney.EN.BZ.Rules
, Duckling.AmountOfMoney.EN.CA.Corpus
, Duckling.AmountOfMoney.EN.CA.Rules
, Duckling.AmountOfMoney.EN.Corpus
, Duckling.AmountOfMoney.EN.GB.Corpus
, Duckling.AmountOfMoney.EN.GB.Rules
, Duckling.AmountOfMoney.EN.IE.Corpus
, Duckling.AmountOfMoney.EN.IE.Rules
, Duckling.AmountOfMoney.EN.IN.Corpus
, Duckling.AmountOfMoney.EN.IN.Rules
, Duckling.AmountOfMoney.EN.JM.Corpus
, Duckling.AmountOfMoney.EN.JM.Rules
, Duckling.AmountOfMoney.EN.NZ.Corpus
, Duckling.AmountOfMoney.EN.NZ.Rules
, Duckling.AmountOfMoney.EN.PH.Corpus
, Duckling.AmountOfMoney.EN.PH.Rules
, Duckling.AmountOfMoney.EN.Rules
, Duckling.AmountOfMoney.EN.TT.Corpus
, Duckling.AmountOfMoney.EN.TT.Rules
, Duckling.AmountOfMoney.EN.US.Corpus
, Duckling.AmountOfMoney.EN.US.Rules
, Duckling.AmountOfMoney.EN.ZA.Corpus
, Duckling.AmountOfMoney.EN.ZA.Rules
, Duckling.AmountOfMoney.BG.Corpus
, Duckling.AmountOfMoney.BG.Rules
, Duckling.AmountOfMoney.ES.Corpus

View File

@ -21,9 +21,19 @@ import Duckling.Locale
import Duckling.Testing.Asserts
import Duckling.Testing.Types (testContext, testOptions, withLocale)
import Duckling.Types (Range(..))
import qualified Duckling.AmountOfMoney.EN.AU.Corpus as AU
import qualified Duckling.AmountOfMoney.EN.BZ.Corpus as BZ
import qualified Duckling.AmountOfMoney.EN.CA.Corpus as CA
import qualified Duckling.AmountOfMoney.EN.GB.Corpus as GB
import qualified Duckling.AmountOfMoney.EN.IE.Corpus as GIE
import qualified Duckling.AmountOfMoney.EN.IN.Corpus as IN
import qualified Duckling.AmountOfMoney.EN.IE.Corpus as IE
import qualified Duckling.AmountOfMoney.EN.JM.Corpus as JM
import qualified Duckling.AmountOfMoney.EN.NZ.Corpus as NZ
import qualified Duckling.AmountOfMoney.EN.PH.Corpus as PH
import qualified Duckling.AmountOfMoney.EN.TT.Corpus as TT
import qualified Duckling.AmountOfMoney.EN.US.Corpus as US
import qualified Duckling.AmountOfMoney.EN.ZA.Corpus as ZA
tests :: TestTree
tests = testGroup "EN Tests"
@ -36,7 +46,19 @@ tests = testGroup "EN Tests"
localeTests :: TestTree
localeTests = testGroup "Locale Tests"
[ testGroup "EN_CA Tests"
[ testGroup "EN_AU Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeAU AU.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeAU AU.negativeExamples
]
, testGroup "EN_BZ Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeBZ BZ.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeBZ BZ.negativeExamples
]
, testGroup "EN_CA Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeCA CA.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
@ -48,17 +70,69 @@ localeTests = testGroup "Locale Tests"
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeGB GB.negativeExamples
]
, testGroup "EN_US Tests"
, testGroup "EN_IE Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeIE IE.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeIE IE.negativeExamples
]
, testGroup "EN_IN Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeIN IN.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeIN IN.negativeExamples
]
, testGroup "EN_JM Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeJM JM.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeJM JM.negativeExamples
]
, testGroup "EN_NZ Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeNZ NZ.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeNZ NZ.negativeExamples
]
, testGroup "EN_PH Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localePH PH.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localePH PH.negativeExamples
]
, testGroup "EN_TT Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeTT TT.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeTT TT.negativeExamples
]
, testGroup "EN_US Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeUS US.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeUS US.negativeExamples
]
, testGroup "EN_ZA Tests"
[ makeCorpusTest [This AmountOfMoney]
$ withLocale corpus localeZA ZA.allExamples
, makeNegativeCorpusTest [This AmountOfMoney]
$ withLocale negativeCorpus localeZA ZA.negativeExamples
]
]
where
localeAU = makeLocale EN $ Just AU
localeBZ = makeLocale EN $ Just BZ
localeCA = makeLocale EN $ Just CA
localeGB = makeLocale EN $ Just GB
localeIE = makeLocale EN $ Just IE
localeIN = makeLocale EN $ Just IN
localeJM = makeLocale EN $ Just JM
localeNZ = makeLocale EN $ Just NZ
localePH = makeLocale EN $ Just PH
localeTT = makeLocale EN $ Just TT
localeUS = makeLocale EN $ Just US
localeZA = makeLocale EN $ Just ZA
intersectTests :: TestTree
intersectTests = testCase "Intersect Test" $