Adding Locales for ES Numeral

Summary:
Adding locale rules for ES Numeral because Spain use "," as decimal but south american country use "." as decimal.

Wiki: https://en.wikipedia.org/wiki/Decimal_separator

Reviewed By: haoxuany

Differential Revision: D20040111

fbshipit-source-id: e2a4bfc2928df19976ef98e90ee82e7d21b52313
This commit is contained in:
Jiaxu Zhu 2020-02-25 15:44:17 -08:00 committed by Facebook Github Bot
parent 4681cf4bba
commit 0527be1ce0
27 changed files with 10047 additions and 288 deletions

View File

@ -8,27 +8,59 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Locale
( Lang(..)
, Locale(..)
, Region(AU,BE,BZ,CA,CN,GB,HK,IE,IN,JM,MO,NZ,PH,TT,TW,US,ZA)
, Region
( AU
, BE
, BZ
, CA
, CL
, CN
, CO
, GB
, HK
, IE
, IN
, JM
, MO
, MX
, NZ
, PE
, PH
, TT
, TW
, US
, VE
, ZA
)
, allLocales
, makeLocale
) where
import Data.Hashable
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import Data.Hashable
import GHC.Generics
import Prelude
import TextShow (TextShow)
import qualified Data.HashMap.Strict as HashMap
import qualified Data.HashSet as HashSet
import qualified TextShow as TS
import Duckling.Region hiding (NL)
import qualified Duckling.Region as R (Region(NL))
import Duckling.Region hiding
( AR
, ES
, NL
)
import qualified Duckling.Region as R
( Region
( AR
, ES
, NL
)
)
-- | ISO 639-1 Language.
-- See https://en.wikipedia.org/wiki/List_of_ISO_639-1_codes
@ -103,8 +135,10 @@ makeLocale lang (Just region)
locales = HashMap.lookupDefault HashSet.empty lang allLocales
allLocales :: HashMap Lang (HashSet Region)
allLocales = HashMap.fromList
[ (EN, HashSet.fromList [AU, BZ, CA, GB, IN, IE, JM, NZ, PH, ZA, TT, US])
, (NL, HashSet.fromList [BE, R.NL])
, (ZH, HashSet.fromList [CN, HK, MO, TW])
]
allLocales =
HashMap.fromList
[ (EN, HashSet.fromList [AU, BZ, CA, GB, IN, IE, JM, NZ, PH, ZA, TT, US])
, (ES, HashSet.fromList [R.AR, CL, CO, R.ES, MX, PE, VE])
, (NL, HashSet.fromList [BE, R.NL])
, (ZH, HashSet.fromList [CN, HK, MO, TW])
]

View File

@ -0,0 +1,32 @@
-- 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.Numeral.ES.AR.Corpus (allExamples) where
import Data.String
import Prelude
import Duckling.Numeral.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples =
concat
[ examples (NumeralValue 1) ["1"]
, examples (NumeralValue 33) ["33"]
, examples (NumeralValue 1.1) ["1,1", "1,10", "01,10"]
, examples (NumeralValue 0.77) ["0,77", ",77"]
, examples (NumeralValue 100000) ["100.000", "100000"]
, examples (NumeralValue 243) ["243"]
, examples (NumeralValue 3000000) ["3000000", "3.000.000"]
, examples (NumeralValue 1200000) ["1.200.000", "1200000"]
, examples
(NumeralValue (-1200000))
["- 1.200.000", "menos 1.200.000", "-1,2M", "-,0012G"]
, examples (NumeralValue 1.5) ["1,5"]
]

View File

@ -0,0 +1,58 @@
-- 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 OverloadedStrings #-}
module Duckling.Numeral.ES.AR.Rules (rules) where
import Data.Maybe
import Data.String
import qualified Data.Text as Text
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Regex.Types
import Duckling.Types
ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator ."
, pattern = [regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule
{ name = "decimal number ,"
, pattern = [regex "(\\d*,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
parseDecimal False match
_ -> Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ."
, pattern = [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
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleDecimalNumeral
, ruleDecimalWithThousandsSeparator
, ruleIntegerWithThousandsSeparator
]

View File

@ -0,0 +1,32 @@
-- 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.Numeral.ES.CL.Corpus (allExamples) where
import Data.String
import Prelude
import Duckling.Numeral.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples =
concat
[ examples (NumeralValue 1) ["1"]
, examples (NumeralValue 33) ["33"]
, examples (NumeralValue 1.1) ["1,1", "1,10", "01,10"]
, examples (NumeralValue 0.77) ["0,77", ",77"]
, examples (NumeralValue 100000) ["100.000", "100000"]
, examples (NumeralValue 243) ["243"]
, examples (NumeralValue 3000000) ["3000000", "3.000.000"]
, examples (NumeralValue 1200000) ["1.200.000", "1200000"]
, examples
(NumeralValue (-1200000))
["- 1.200.000", "menos 1.200.000", "-1,2M", "-,0012G"]
, examples (NumeralValue 1.5) ["1,5"]
]

View File

@ -0,0 +1,58 @@
-- 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 OverloadedStrings #-}
module Duckling.Numeral.ES.CL.Rules (rules) where
import Data.Maybe
import Data.String
import qualified Data.Text as Text
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Regex.Types
import Duckling.Types
ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator ."
, pattern = [regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule
{ name = "decimal number ,"
, pattern = [regex "(\\d*,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
parseDecimal False match
_ -> Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ."
, pattern = [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
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleDecimalNumeral
, ruleDecimalWithThousandsSeparator
, ruleIntegerWithThousandsSeparator
]

View File

@ -0,0 +1,32 @@
-- 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.Numeral.ES.CO.Corpus (allExamples) where
import Data.String
import Prelude
import Duckling.Numeral.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples =
concat
[ examples (NumeralValue 1) ["1"]
, examples (NumeralValue 33) ["33"]
, examples (NumeralValue 1.1) ["1,1", "1,10", "01,10"]
, examples (NumeralValue 0.77) ["0,77", ",77"]
, examples (NumeralValue 100000) ["100.000", "100000"]
, examples (NumeralValue 243) ["243"]
, examples (NumeralValue 3000000) ["3000000", "3.000.000"]
, examples (NumeralValue 1200000) ["1.200.000", "1200000"]
, examples
(NumeralValue (-1200000))
["- 1.200.000", "menos 1.200.000", "-1,2M", "-,0012G"]
, examples (NumeralValue 1.5) ["1,5"]
]

View File

@ -0,0 +1,58 @@
-- 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 OverloadedStrings #-}
module Duckling.Numeral.ES.CO.Rules (rules) where
import Data.Maybe
import Data.String
import qualified Data.Text as Text
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Regex.Types
import Duckling.Types
ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator ."
, pattern = [regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule
{ name = "decimal number ,"
, pattern = [regex "(\\d*,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
parseDecimal False match
_ -> Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ."
, pattern = [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
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleDecimalNumeral
, ruleDecimalWithThousandsSeparator
, ruleIntegerWithThousandsSeparator
]

View File

@ -6,12 +6,10 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.ES.Corpus (corpus) where
module Duckling.Numeral.ES.Corpus
( corpus ) where
import Prelude
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Numeral.Types
@ -19,94 +17,29 @@ import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale ES Nothing}, testOptions, allExamples)
corpus =
(testContext { locale = makeLocale ES Nothing }, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (NumeralValue 1)
[ "1"
, "uno"
, "una"
]
, examples (NumeralValue 11)
[ "once"
]
, examples (NumeralValue 16)
[ "dieciséis"
, "dieciseis"
, "Diesiseis"
, "diez y seis"
]
, examples (NumeralValue 21)
[ "veintiuno"
, "veinte y uno"
]
, examples (NumeralValue 22)
[ "veintidós"
]
, examples (NumeralValue 23)
[ "veintitrés"
, "veinte y tres"
]
, examples (NumeralValue 70)
[ "setenta"
]
, examples (NumeralValue 78)
[ "Setenta y ocho"
]
, examples (NumeralValue 80)
[ "ochenta"
]
, examples (NumeralValue 33)
[ "33"
, "treinta y tres"
, "treinta y 3"
]
, examples (NumeralValue 1.1)
[ "1,1"
, "1,10"
, "01,10"
]
, examples (NumeralValue 0.77)
[ "0,77"
, ",77"
]
, examples (NumeralValue 100000)
[ "100.000"
, "100000"
, "100K"
, "100k"
]
, examples (NumeralValue 300)
[ "trescientos"
]
, examples (NumeralValue 243)
[ "243"
]
, examples (NumeralValue 3000000)
[ "3M"
, "3000K"
, "3000000"
, "3.000.000"
]
, examples (NumeralValue 1200000)
[ "1.200.000"
, "1200000"
, "1,2M"
, "1200K"
, ",0012G"
]
, examples (NumeralValue (-1200000))
[ "- 1.200.000"
, "-1200000"
, "menos 1.200.000"
, "-1,2M"
, "-1200K"
, "-,0012G"
]
, examples (NumeralValue 1.5)
[ "1 punto cinco"
, "una punto cinco"
, "1,5"
]
]
allExamples =
concat
[ examples (NumeralValue 1) ["1", "uno", "una"]
, examples (NumeralValue 11) ["once"]
, examples
(NumeralValue 16)
["dieciséis", "dieciseis", "Diesiseis", "diez y seis"]
, examples (NumeralValue 21) ["veintiuno", "veinte y uno"]
, examples (NumeralValue 22) ["veintidós"]
, examples (NumeralValue 23) ["veintitrés", "veinte y tres"]
, examples (NumeralValue 70) ["setenta"]
, examples (NumeralValue 78) ["Setenta y ocho"]
, examples (NumeralValue 80) ["ochenta"]
, examples (NumeralValue 33) ["33", "treinta y tres", "treinta y 3"]
, examples (NumeralValue 100000) ["100000", "100K", "100k"]
, examples (NumeralValue 300) ["trescientos"]
, examples (NumeralValue 243) ["243"]
, examples (NumeralValue 3000000) ["3M", "3000K", "3000000"]
, examples (NumeralValue 1200000) ["1200000", "1200K"]
, examples (NumeralValue (-1200000)) ["-1200000", "-1200K"]
, examples (NumeralValue 1.5) ["1 punto cinco", "una punto cinco"]
]

View File

@ -0,0 +1,32 @@
-- 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.Numeral.ES.ES.Corpus (allExamples) where
import Data.String
import Prelude
import Duckling.Numeral.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples =
concat
[ examples (NumeralValue 1) ["1"]
, examples (NumeralValue 33) ["33"]
, examples (NumeralValue 1.1) ["1,1", "1,10", "01,10"]
, examples (NumeralValue 0.77) ["0,77", ",77"]
, examples (NumeralValue 100000) ["100.000", "100000"]
, examples (NumeralValue 243) ["243"]
, examples (NumeralValue 3000000) ["3000000", "3.000.000"]
, examples (NumeralValue 1200000) ["1.200.000", "1200000"]
, examples
(NumeralValue (-1200000))
["- 1.200.000", "menos 1.200.000", "-1,2M", "-,0012G"]
, examples (NumeralValue 1.5) ["1,5"]
]

View File

@ -0,0 +1,67 @@
-- 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 OverloadedStrings #-}
module Duckling.Numeral.ES.ES.Rules
( rules
, rulesBackwardCompatible
) where
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.String
import qualified Data.Text as Text
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Numeral.Types (NumeralData(..))
import qualified Duckling.Numeral.Types as TNumeral
import Duckling.Regex.Types
import Duckling.Types
ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator ."
, pattern = [regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule
{ name = "decimal number ,"
, pattern = [regex "(\\d*,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
parseDecimal False match
_ -> Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ."
, pattern = [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
_ -> Nothing
}
rulesBackwardCompatible :: [Rule]
rulesBackwardCompatible =
[ ruleDecimalNumeral
, ruleDecimalWithThousandsSeparator
, ruleIntegerWithThousandsSeparator
]
rules :: [Rule]
rules = rulesBackwardCompatible

View File

@ -0,0 +1,32 @@
-- 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.Numeral.ES.MX.Corpus (allExamples) where
import Data.String
import Prelude
import Duckling.Numeral.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples =
concat
[ examples (NumeralValue 1) ["1"]
, examples (NumeralValue 33) ["33"]
, examples (NumeralValue 1.1) ["1.1", "1.10", "01.10"]
, examples (NumeralValue 0.77) ["0.77", ".77"]
, examples (NumeralValue 100000) ["100,000", "100000"]
, examples (NumeralValue 243) ["243"]
, examples (NumeralValue 3000000) ["3000000", "3,000,000"]
, examples (NumeralValue 1200000) ["1,200,000", "1200000"]
, examples
(NumeralValue (-1200000))
["- 1,200,000", "menos 1,200,000", "-1.2M", "-.0012G"]
, examples (NumeralValue 1.5) ["1.5"]
]

View File

@ -0,0 +1,58 @@
-- 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 OverloadedStrings #-}
module Duckling.Numeral.ES.MX.Rules (rules) where
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.String
import qualified Data.Text as Text
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Regex.Types
import Duckling.Types
ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator"
, pattern = [regex "(\\d+(\\,\\d\\d\\d)+\\.\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule
{ name = "decimal number ."
, pattern = [regex "(\\d*\\.\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
parseDecimal False match
_ -> Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ,"
, pattern = [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
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleDecimalNumeral
, ruleDecimalWithThousandsSeparator
, ruleIntegerWithThousandsSeparator
]

View File

@ -0,0 +1,32 @@
-- 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.Numeral.ES.PE.Corpus (allExamples) where
import Data.String
import Prelude
import Duckling.Numeral.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples =
concat
[ examples (NumeralValue 1) ["1"]
, examples (NumeralValue 33) ["33"]
, examples (NumeralValue 1.1) ["1,1", "1,10", "01,10"]
, examples (NumeralValue 0.77) ["0,77", ",77"]
, examples (NumeralValue 100000) ["100.000", "100000"]
, examples (NumeralValue 243) ["243"]
, examples (NumeralValue 3000000) ["3000000", "3.000.000"]
, examples (NumeralValue 1200000) ["1.200.000", "1200000"]
, examples
(NumeralValue (-1200000))
["- 1.200.000", "menos 1.200.000", "-1,2M", "-,0012G"]
, examples (NumeralValue 1.5) ["1,5"]
]

View File

@ -0,0 +1,58 @@
-- 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 OverloadedStrings #-}
module Duckling.Numeral.ES.PE.Rules (rules) where
import Data.Maybe
import Data.String
import qualified Data.Text as Text
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Regex.Types
import Duckling.Types
ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator ."
, pattern = [regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule
{ name = "decimal number ,"
, pattern = [regex "(\\d*,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
parseDecimal False match
_ -> Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ."
, pattern = [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
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleDecimalNumeral
, ruleDecimalWithThousandsSeparator
, ruleIntegerWithThousandsSeparator
]

View File

@ -7,156 +7,131 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.ES.Rules (rules) where
module Duckling.Numeral.ES.Rules
( rules
) where
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.String
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Numeral.Types (NumeralData(..))
import qualified Duckling.Numeral.Types as TNumeral
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
{ name = "numbers prefix with -, negative or minus"
, pattern =
[ regex "-|menos"
, Predicate isPositive
]
, pattern = [regex "-|menos", Predicate isPositive]
, prod = \tokens -> case tokens of
(_:Token Numeral NumeralData{TNumeral.value = v}:_) ->
double $ v * (- 1)
_ -> Nothing
}
ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator"
, pattern =
[ regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule
{ name = "decimal number"
, pattern =
[ regex "(\\d*,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDecimal False match
(_ : Token Numeral NumeralData { TNumeral.value = v } : _) ->
double $ v * (-1)
_ -> Nothing
}
byTensMap :: HashMap.HashMap Text.Text Integer
byTensMap = HashMap.fromList
[ ( "veinte" , 20 )
, ( "treinta" , 30 )
, ( "cuarenta" , 40 )
, ( "cincuenta" , 50 )
, ( "sesenta" , 60 )
, ( "setenta" , 70 )
, ( "ochenta" , 80 )
, ( "noventa" , 90 )
]
byTensMap =
HashMap.fromList
[ ("veinte", 20)
, ("treinta", 30)
, ("cuarenta", 40)
, ("cincuenta", 50)
, ("sesenta", 60)
, ("setenta", 70)
, ("ochenta", 80)
, ("noventa", 90)
]
ruleNumeral2 :: Rule
ruleNumeral2 = Rule
{ name = "number (20..90)"
, pattern =
[ regex "(veinte|treinta|cuarenta|cincuenta|sesenta|setenta|ochenta|noventa)"
]
[ regex
"(veinte|treinta|cuarenta|cincuenta|sesenta|setenta|ochenta|noventa)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
(Token RegexMatch (GroupMatch (match : _)) : _) ->
HashMap.lookup (Text.toLower match) byTensMap >>= integer
_ -> Nothing
}
zeroToFifteenMap :: HashMap.HashMap Text.Text Integer
zeroToFifteenMap = HashMap.fromList
[ ( "zero" , 0 )
, ( "cero" , 0 )
, ( "un" , 1 )
, ( "una" , 1 )
, ( "uno" , 1 )
, ( "dos" , 2 )
, ( "trés" , 3 )
, ( "tres" , 3 )
, ( "cuatro" , 4 )
, ( "cinco" , 5 )
, ( "seis" , 6 )
, ( "séis" , 6 )
, ( "siete" , 7 )
, ( "ocho" , 8 )
, ( "nueve" , 9 )
, ( "diez" , 10 )
, ( "dies" , 10 )
, ( "once" , 11 )
, ( "doce" , 12 )
, ( "trece" , 13 )
, ( "catorce" , 14 )
, ( "quince" , 15 )
]
zeroToFifteenMap =
HashMap.fromList
[ ("zero", 0)
, ("cero", 0)
, ("un", 1)
, ("una", 1)
, ("uno", 1)
, ("dos", 2)
, ("trés", 3)
, ("tres", 3)
, ("cuatro", 4)
, ("cinco", 5)
, ("seis", 6)
, ("séis", 6)
, ("siete", 7)
, ("ocho", 8)
, ("nueve", 9)
, ("diez", 10)
, ("dies", 10)
, ("once", 11)
, ("doce", 12)
, ("trece", 13)
, ("catorce", 14)
, ("quince", 15)
]
ruleNumeral :: Rule
ruleNumeral = Rule
{ name = "number (0..15)"
, pattern =
[ regex "((c|z)ero|un(o|a)?|dos|tr(é|e)s|cuatro|cinco|s(e|é)is|siete|ocho|nueve|die(z|s)|once|doce|trece|catorce|quince)"
]
[ regex
"((c|z)ero|un(o|a)?|dos|tr(é|e)s|cuatro|cinco|s(e|é)is|siete|ocho|nueve|die(z|s)|once|doce|trece|catorce|quince)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
(Token RegexMatch (GroupMatch (match : _)) : _) ->
HashMap.lookup (Text.toLower match) zeroToFifteenMap >>= integer
_ -> Nothing
}
sixteenToTwentyNineMap :: HashMap.HashMap Text.Text Integer
sixteenToTwentyNineMap = HashMap.fromList
[ ( "dieciseis" , 16 )
, ( "diesiséis" , 16 )
, ( "diesiseis" , 16 )
, ( "dieciséis" , 16 )
, ( "diecisiete" , 17 )
, ( "dieciocho" , 18 )
, ( "diecinueve" , 19 )
, ( "veintiuno" , 21 )
, ( "veintiuna" , 21 )
, ( "veintidos" , 22 )
, ( "veintidós" , 22 )
, ( "veintitrés" , 23 )
, ( "veintitres" , 23 )
, ( "veinticuatro" , 24 )
, ( "veinticinco" , 25 )
, ( "veintiséis" , 26 )
, ( "veintiseis" , 26 )
, ( "veintisiete" , 27 )
, ( "veintiocho" , 28 )
, ( "veintinueve" , 29 )
]
sixteenToTwentyNineMap =
HashMap.fromList
[ ("dieciseis", 16)
, ("diesiséis", 16)
, ("diesiseis", 16)
, ("dieciséis", 16)
, ("diecisiete", 17)
, ("dieciocho", 18)
, ("diecinueve", 19)
, ("veintiuno", 21)
, ("veintiuna", 21)
, ("veintidos", 22)
, ("veintidós", 22)
, ("veintitrés", 23)
, ("veintitres", 23)
, ("veinticuatro", 24)
, ("veinticinco", 25)
, ("veintiséis", 26)
, ("veintiseis", 26)
, ("veintisiete", 27)
, ("veintiocho", 28)
, ("veintinueve", 29)
]
ruleNumeral5 :: Rule
ruleNumeral5 = Rule
{ name = "number (16..19 21..29)"
, pattern =
[ regex "(die(c|s)is(é|e)is|diecisiete|dieciocho|diecinueve|veintiun(o|a)|veintid(o|ó)s|veintitr(é|e)s|veinticuatro|veinticinco|veintis(é|e)is|veintisiete|veintiocho|veintinueve|treinta)"
]
[ regex
"(die(c|s)is(é|e)is|diecisiete|dieciocho|diecinueve|veintiun(o|a)|veintid(o|ó)s|veintitr(é|e)s|veinticuatro|veinticinco|veintis(é|e)is|veintisiete|veintiocho|veintinueve|treinta)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
(Token RegexMatch (GroupMatch (match : _)) : _) ->
HashMap.lookup (Text.toLower match) sixteenToTwentyNineMap >>= integer
_ -> Nothing
}
@ -164,13 +139,9 @@ ruleNumeral5 = Rule
ruleNumeral3 :: Rule
ruleNumeral3 = Rule
{ name = "number (16..19)"
, pattern =
[ numberWith TNumeral.value (== 10)
, regex "y"
, numberBetween 6 10
]
, pattern = [numberWith TNumeral.value (== 10), regex "y", numberBetween 6 10]
, prod = \tokens -> case tokens of
(_:_:Token Numeral NumeralData{TNumeral.value = v}:_) ->
(_ : _ : Token Numeral NumeralData { TNumeral.value = v } : _) ->
double $ 10 + v
_ -> Nothing
}
@ -178,14 +149,10 @@ ruleNumeral3 = Rule
ruleNumeralsSuffixesKMG :: Rule
ruleNumeralsSuffixesKMG = Rule
{ name = "numbers suffixes (K, M, G)"
, pattern =
[ dimension Numeral
, regex "([kmg])(?=[\\W\\$€]|$)"
]
, pattern = [dimension Numeral, regex "([kmg])(?=[\\W\\$€]|$)"]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v}:
Token RegexMatch (GroupMatch (match:_)):
_) -> case Text.toLower match of
(Token Numeral NumeralData { TNumeral.value = v } : Token RegexMatch (GroupMatch (match : _)) : _) ->
case Text.toLower match of
"k" -> double $ v * 1e3
"m" -> double $ v * 1e6
"g" -> double $ v * 1e9
@ -194,30 +161,31 @@ ruleNumeralsSuffixesKMG = Rule
}
oneHundredToThousandMap :: HashMap.HashMap Text.Text Integer
oneHundredToThousandMap = HashMap.fromList
[ ( "cien" , 100 )
, ( "cientos" , 100 )
, ( "ciento" , 100 )
, ( "doscientos" , 200 )
, ( "trescientos" , 300 )
, ( "cuatrocientos" , 400 )
, ( "quinientos" , 500 )
, ( "seiscientos" , 600 )
, ( "setecientos" , 700 )
, ( "ochocientos" , 800 )
, ( "novecientos" , 900 )
, ( "mil" , 1000 )
]
oneHundredToThousandMap =
HashMap.fromList
[ ("cien", 100)
, ("cientos", 100)
, ("ciento", 100)
, ("doscientos", 200)
, ("trescientos", 300)
, ("cuatrocientos", 400)
, ("quinientos", 500)
, ("seiscientos", 600)
, ("setecientos", 700)
, ("ochocientos", 800)
, ("novecientos", 900)
, ("mil", 1000)
]
ruleNumeral6 :: Rule
ruleNumeral6 = Rule
{ name = "number 100..1000 "
, pattern =
[ regex "(cien(to)?s?|doscientos|trescientos|cuatrocientos|quinientos|seiscientos|setecientos|ochocientos|novecientos|mil)"
]
[ regex
"(cien(to)?s?|doscientos|trescientos|cuatrocientos|quinientos|seiscientos|setecientos|ochocientos|novecientos|mil)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
(Token RegexMatch (GroupMatch (match : _)) : _) ->
HashMap.lookup (Text.toLower match) oneHundredToThousandMap >>= integer
_ -> Nothing
}
@ -226,15 +194,10 @@ ruleNumeral4 :: Rule
ruleNumeral4 = Rule
{ name = "number (21..29 31..39 41..49 51..59 61..69 71..79 81..89 91..99)"
, pattern =
[ oneOf [70, 20, 60, 50, 40, 90, 30, 80]
, regex "y"
, numberBetween 1 10
]
[oneOf [70, 20, 60, 50, 40, 90, 30, 80], regex "y", numberBetween 1 10]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v1}:
_:
Token Numeral NumeralData{TNumeral.value = v2}:
_) -> double $ v1 + v2
(Token Numeral NumeralData { TNumeral.value = v1 } : _ : Token Numeral NumeralData { TNumeral.value = v2 } : _) ->
double $ v1 + v2
_ -> Nothing
}
@ -242,52 +205,29 @@ ruleNumerals :: Rule
ruleNumerals = Rule
{ name = "numbers 200..999"
, pattern =
[ numberBetween 2 10
, numberWith TNumeral.value (== 100)
, numberBetween 0 100
]
[ numberBetween 2 10
, numberWith TNumeral.value (== 100)
, numberBetween 0 100
]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v1}:
_:
Token Numeral NumeralData{TNumeral.value = v2}:
_) -> double $ 100 * v1 + v2
(Token Numeral NumeralData { TNumeral.value = v1 } : _ : Token Numeral NumeralData { TNumeral.value = v2 } : _) ->
double $ 100 * v1 + v2
_ -> Nothing
}
ruleNumeralDotNumeral :: Rule
ruleNumeralDotNumeral = Rule
{ name = "number dot number"
, pattern =
[ dimension Numeral
, regex "punto"
, Predicate $ not . hasGrain
]
, pattern = [dimension Numeral, regex "punto", Predicate $ not . hasGrain]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v1}:
_:
Token Numeral NumeralData{TNumeral.value = v2}:
_) -> double $ v1 + decimalsToDouble v2
_ -> Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ."
, pattern =
[ 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 Numeral NumeralData { TNumeral.value = v1 } : _ : Token Numeral NumeralData { TNumeral.value = v2 } : _) ->
double $ v1 + decimalsToDouble v2
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleDecimalNumeral
, ruleDecimalWithThousandsSeparator
, ruleIntegerWithThousandsSeparator
, ruleNumeral
[ ruleNumeral
, ruleNumeral2
, ruleNumeral3
, ruleNumeral4

View File

@ -0,0 +1,32 @@
-- 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.Numeral.ES.VE.Corpus (allExamples) where
import Data.String
import Prelude
import Duckling.Numeral.Types
import Duckling.Testing.Types
allExamples :: [Example]
allExamples =
concat
[ examples (NumeralValue 1) ["1"]
, examples (NumeralValue 33) ["33"]
, examples (NumeralValue 1.1) ["1,1", "1,10", "01,10"]
, examples (NumeralValue 0.77) ["0,77", ",77"]
, examples (NumeralValue 100000) ["100.000", "100000"]
, examples (NumeralValue 243) ["243"]
, examples (NumeralValue 3000000) ["3000000", "3.000.000"]
, examples (NumeralValue 1200000) ["1.200.000", "1200000"]
, examples
(NumeralValue (-1200000))
["- 1.200.000", "menos 1.200.000", "-1,2M", "-,0012G"]
, examples (NumeralValue 1.5) ["1,5"]
]

View File

@ -0,0 +1,58 @@
-- 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 OverloadedStrings #-}
module Duckling.Numeral.ES.VE.Rules (rules) where
import Data.Maybe
import Data.String
import qualified Data.Text as Text
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Regex.Types
import Duckling.Types
ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator ."
, pattern = [regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule
{ name = "decimal number ,"
, pattern = [regex "(\\d*,\\d+)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match : _)) : _) ->
parseDecimal False match
_ -> Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ."
, pattern = [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
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleDecimalNumeral
, ruleDecimalWithThousandsSeparator
, ruleIntegerWithThousandsSeparator
]

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

View File

@ -22,24 +22,31 @@ import qualified TextShow as TS
-- | ISO 3166-1 alpha-2 Country code (includes regions and territories).
-- See https://en.wikipedia.org/wiki/ISO_3166-1_alpha-2
data Region
= AU
= AR
| AU
| BE
| BZ
| CA
| CL
| CN
| CO
| ES
| GB
| HK
| IE
| IN
| JM
| MN
| MX
| MO
| NL
| NZ
| PE
| PH
| TT
| TW
| US
| VE
| ZA
deriving (Bounded, Enum, Eq, Generic, Hashable, Ord, Read, Show)

View File

@ -6,30 +6,52 @@
{-# LANGUAGE GADTs #-}
module Duckling.Rules.ES
( defaultRules
, langRules
, localeRules
) where
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import Prelude
import qualified Duckling.AmountOfMoney.ES.Rules as AmountOfMoney
import Duckling.Dimensions.Types
import qualified Duckling.Distance.ES.Rules as Distance
import Duckling.Locale
import qualified Duckling.Numeral.ES.AR.Rules as NumeralAR
import qualified Duckling.Numeral.ES.CL.Rules as NumeralCL
import qualified Duckling.Numeral.ES.CO.Rules as NumeralCO
import qualified Duckling.Numeral.ES.ES.Rules as NumeralES
import qualified Duckling.Numeral.ES.MX.Rules as NumeralMX
import qualified Duckling.Numeral.ES.PE.Rules as NumeralPE
import qualified Duckling.Numeral.ES.Rules as Numeral
import qualified Duckling.Numeral.ES.VE.Rules as NumeralVE
import qualified Duckling.Ordinal.ES.Rules as Ordinal
import qualified Duckling.Region as R
( Region
( AR
, ES
)
)
import qualified Duckling.Temperature.ES.Rules as Temperature
import qualified Duckling.Time.ES.Rules as Time
import qualified Duckling.TimeGrain.ES.Rules as TimeGrain
import Duckling.Types
import qualified Duckling.Volume.ES.Rules as Volume
defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules
defaultRules dim@(This Numeral) =
NumeralES.rulesBackwardCompatible ++ langRules dim
defaultRules dim = langRules dim
localeRules :: Region -> Some Dimension -> [Rule]
localeRules R.AR (This Numeral) = NumeralAR.rules
localeRules CL (This Numeral) = NumeralCL.rules
localeRules CO (This Numeral) = NumeralCO.rules
localeRules R.ES (This Numeral) = NumeralES.rules
localeRules MX (This Numeral) = NumeralMX.rules
localeRules PE (This Numeral) = NumeralPE.rules
localeRules VE (This Numeral) = NumeralVE.rules
localeRules region (This (CustomDimension dim)) = dimLocaleRules region dim
localeRules _ _ = []

View File

@ -13,10 +13,59 @@ import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Numeral.ES.Corpus
import Duckling.Testing.Asserts
import Duckling.Testing.Types hiding (examples)
import qualified Duckling.Numeral.ES.AR.Corpus as AR
import qualified Duckling.Numeral.ES.CL.Corpus as CL
import qualified Duckling.Numeral.ES.CO.Corpus as CO
import qualified Duckling.Numeral.ES.ES.Corpus as ES
import qualified Duckling.Numeral.ES.MX.Corpus as MX
import qualified Duckling.Numeral.ES.PE.Corpus as PE
import qualified Duckling.Numeral.ES.VE.Corpus as VE
import qualified Duckling.Region as R
( Region
( AR
, ES
)
)
tests :: TestTree
tests = testGroup "ES Tests"
[ makeCorpusTest [This Numeral] corpus
, localeTests
]
localeTests :: TestTree
localeTests = testGroup "Locale Tests"
[ testGroup "ES_AR Tests"
[ makeCorpusTest [This Numeral] $ withLocale corpus localeAR AR.allExamples
]
, testGroup "ES_CL Tests"
[ makeCorpusTest [This Numeral] $ withLocale corpus localeCL CL.allExamples
]
, testGroup "ES_CO Tests"
[ makeCorpusTest [This Numeral] $ withLocale corpus localeCO CO.allExamples
]
, testGroup "ES_ES Tests"
[ makeCorpusTest [This Numeral] $ withLocale corpus localeES ES.allExamples
]
, testGroup "ES_MX Tests"
[ makeCorpusTest [This Numeral] $ withLocale corpus localeMX MX.allExamples
]
, testGroup "ES_PE Tests"
[ makeCorpusTest [This Numeral] $ withLocale corpus localePE PE.allExamples
]
, testGroup "ES_VE Tests"
[ makeCorpusTest [This Numeral] $ withLocale corpus localeVE VE.allExamples
]
]
where
localeAR = makeLocale ES $ Just R.AR
localeCL = makeLocale ES $ Just CL
localeCO = makeLocale ES $ Just CO
localeES = makeLocale ES $ Just R.ES
localeMX = makeLocale ES $ Just MX
localePE = makeLocale ES $ Just PE
localeVE = makeLocale ES $ Just VE