{-# 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
ruleDecimalWithThousandsSeparator = Rule :: Text -> Pattern -> Production -> Rule
Rule
{ name :: Text
name = Text
"decimal with thousands separator ."
, pattern :: Pattern
pattern = [String -> PatternItem
regex String
"(\\d+(\\.\\d\\d\\d)+,\\d+)"]
, prod :: Production
prod = \[Token]
tokens -> case [Token]
tokens of
(Token Dimension a
RegexMatch (GroupMatch (match : _)) : [Token]
_) ->
let fmt :: Text
fmt = Text -> Text -> Text -> Text
Text.replace Text
"," Text
"." (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text -> Text
Text.replace Text
"." Text
Text.empty Text
match
in Text -> Maybe Double
parseDouble Text
fmt Maybe Double -> (Double -> Maybe Token) -> Maybe Token
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Double -> Maybe Token
double
[Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule :: Text -> Pattern -> Production -> Rule
Rule
{ name :: Text
name = Text
"decimal number ,"
, pattern :: Pattern
pattern = [String -> PatternItem
regex String
"(\\d*,\\d+)"]
, prod :: Production
prod = \[Token]
tokens -> case [Token]
tokens of
(Token Dimension a
RegexMatch (GroupMatch (match : _)) : [Token]
_) ->
Bool -> Text -> Maybe Token
parseDecimal Bool
False Text
match
[Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule :: Text -> Pattern -> Production -> Rule
Rule
{ name :: Text
name = Text
"integer with thousands separator ."
, pattern :: Pattern
pattern = [String -> PatternItem
regex String
"(\\d{1,3}(\\.\\d\\d\\d){1,5})"]
, prod :: Production
prod = \[Token]
tokens -> case [Token]
tokens of
(Token Dimension a
RegexMatch (GroupMatch (match : _)) : [Token]
_) ->
Text -> Maybe Double
parseDouble (Text -> Text -> Text -> Text
Text.replace Text
"." Text
Text.empty Text
match) Maybe Double -> (Double -> Maybe Token) -> Maybe Token
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Double -> Maybe Token
double
[Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
}
rules :: [Rule]
rules :: [Rule]
rules =
[ Rule
ruleDecimalNumeral
, Rule
ruleDecimalWithThousandsSeparator
, Rule
ruleIntegerWithThousandsSeparator
]