Numeral: refactor 'Text.singleton' usages

Summary:
* refactored `Text.singleton` usages into `Text` literals
* removed redundant `join` imports with `NoRebindableSyntax` language pragma
* ET: merged 2 rules into one

Reviewed By: blandinw

Differential Revision: D6080231

fbshipit-source-id: 47c18df
This commit is contained in:
Julien Odent 2017-10-17 13:12:26 -07:00 committed by Facebook Github Bot
parent b2de97800f
commit ed58115caf
29 changed files with 205 additions and 211 deletions

View File

@ -10,19 +10,20 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.AR.Rules
( rules ) where
( rules
) where
import Data.Maybe
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleInteger5 :: Rule
ruleInteger5 = Rule
@ -127,7 +128,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
@ -336,7 +337,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}

View File

@ -11,7 +11,8 @@
{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Numeral.BG.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import Data.Maybe
@ -217,7 +218,7 @@ ruleCommas = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,7 +10,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.CS.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import Data.Maybe

View File

@ -10,22 +10,23 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.DA.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude
import Data.String
import Data.Text (Text)
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
@ -79,7 +80,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton '.') Text.empty match) >>= double
parseDouble (Text.replace "." Text.empty match) >>= double
_ -> Nothing
}
@ -299,7 +300,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton '.') Text.empty match) >>= double
parseDouble (Text.replace "." Text.empty match) >>= double
_ -> Nothing
}

View File

@ -7,26 +7,27 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.DE.Rules
( rules ) where
( rules
) where
import Control.Monad (join)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude
import Data.String
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
@ -79,10 +80,8 @@ ruleDecimalWithThousandsSeparator = Rule
[ regex "(\\d+(\\.\\d\\d\\d)+\\,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -361,7 +360,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton '.') Text.empty match) >>= double
parseDouble (Text.replace "." Text.empty match) >>= double
_ -> Nothing
}

View File

@ -11,7 +11,8 @@
{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Numeral.EN.Rules
( rules ) where
( rules
) where
import Control.Applicative ((<|>))
import Data.HashMap.Strict (HashMap)
@ -225,7 +226,7 @@ ruleCommas = Rule
, pattern = [regex "(\\d+(,\\d\\d\\d)+(\\.\\d+)?)"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,20 +10,21 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.ES.Rules
( rules ) where
( rules
) where
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
@ -58,10 +59,8 @@ ruleDecimalWithThousandsSeparator = Rule
[ regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -292,7 +291,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton '.') Text.empty match) >>= double
parseDouble (Text.replace "." Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,31 +10,20 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.ET.Rules
( rules ) where
( rules
) where
import Data.Maybe
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.Text as Text
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
ruleIntegerWithThousandsSeparatorSpace :: Rule
ruleIntegerWithThousandsSeparatorSpace = Rule
{ name = "integer with thousands separator space"
, pattern =
[ regex "(\\d{1,3}(\\s\\d\\d\\d){1,5})"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ' ') Text.empty match) >>= double
_ -> Nothing
}
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
@ -275,11 +264,11 @@ 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.singleton ',') Text.empty match) >>= double
(Token RegexMatch (GroupMatch (match:_:sep:_)):_) ->
parseDouble (Text.replace sep Text.empty match) >>= double
_ -> Nothing
}
@ -295,7 +284,6 @@ rules =
, ruleInteger4
, ruleIntegerNumeric
, ruleIntegerWithThousandsSeparator
, ruleIntegerWithThousandsSeparatorSpace
, ruleIntersect
, ruleMultiply
, ruleNumeralDotNumeral

View File

@ -10,18 +10,19 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.GA.Rules
( rules ) where
( rules
) where
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
@ -84,7 +85,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
@ -206,7 +207,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}

View File

@ -9,7 +9,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.HE.Rules
( rules ) where
( rules
) where
import Data.Maybe
import Data.String
@ -352,7 +353,7 @@ ruleCommas = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}

View File

@ -9,7 +9,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.HR.Rules
( rules ) where
( rules
) where
import Data.Maybe
import Data.String
@ -74,10 +75,8 @@ ruleDecimalWithThousandsSeparator = Rule
[ regex "(\\d+(\\.\\d\\d\\d)+\\,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -341,7 +340,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace (Text.singleton '.') Text.empty match
_) -> let fmt = Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}

View File

@ -11,7 +11,8 @@
{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Numeral.HU.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import Data.Maybe

View File

@ -10,22 +10,23 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.ID.Rules
( rules ) where
( rules
) where
import qualified Data.HashMap.Strict as HashMap
import Data.HashMap.Strict (HashMap)
import Data.Maybe
import qualified Data.Text as Text
import Data.Text (Text)
import Prelude
import Data.String
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleIntegerMap :: HashMap Text Integer
ruleIntegerMap = HashMap.fromList
@ -111,9 +112,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -255,7 +254,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton '.') Text.empty match) >>= double
parseDouble (Text.replace "." Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,18 +10,19 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.IT.Rules
( rules ) where
( rules
) where
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
@ -55,10 +56,8 @@ ruleDecimalWithThousandsSeparator = Rule
[ regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -303,7 +302,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton '.') Text.empty match) >>= double
parseDouble (Text.replace "." Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,21 +10,22 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.JA.Rules
( rules ) where
( rules
) where
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
import Data.HashMap.Strict (HashMap)
import Data.String
import Data.Text (Text)
import Prelude
import Data.String
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleInteger5 :: Rule
ruleInteger5 = Rule
@ -81,7 +82,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
@ -323,7 +324,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,7 +10,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.KA.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import Data.Maybe

View File

@ -10,19 +10,20 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.KO.Rules
( rules ) where
( rules
) where
import Data.Maybe
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleIntegerForOrdinals :: Rule
ruleIntegerForOrdinals = Rule
@ -71,7 +72,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
@ -306,7 +307,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,17 +10,18 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.MY.Rules
( rules ) where
( rules
) where
import Prelude
import Data.String
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
import qualified Duckling.Numeral.Types as TNumeral
ruleInteger5 :: Rule
ruleInteger5 = Rule

View File

@ -10,22 +10,23 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.NB.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude
import Data.String
import Data.Text (Text)
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleIntersectWithAnd :: Rule
ruleIntersectWithAnd = Rule
@ -85,9 +86,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -298,7 +297,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton '.') Text.empty match) >>= double
parseDouble (Text.replace "." Text.empty match) >>= double
_ -> Nothing
}

View File

@ -7,26 +7,27 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.NL.Rules
( rules ) where
( rules
) where
import Control.Monad (join)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude
import Data.String
import Data.Text (Text)
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
@ -79,9 +80,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}

View File

@ -10,19 +10,20 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.PL.Rules
( rules ) where
( rules
) where
import Data.Maybe
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleSixteen :: Rule
ruleSixteen = Rule
@ -141,7 +142,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
@ -542,7 +543,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,19 +10,20 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.PT.Rules
( rules ) where
( rules
) where
import Data.Maybe
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
@ -57,9 +58,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -281,7 +280,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace (Text.singleton '.') Text.empty match
_) -> let fmt = Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}

View File

@ -10,22 +10,23 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.RO.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude
import Data.String
import Data.Text (Text)
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleNumeralsPrefixWithOrMinus :: Rule
ruleNumeralsPrefixWithOrMinus = Rule
@ -74,9 +75,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -291,7 +290,7 @@ ruleIntegerCuSeparatorDeMiiDot = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace (Text.singleton '.') Text.empty match
_) -> let fmt = Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}

View File

@ -10,22 +10,23 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.RU.Rules
( rules ) where
( rules
) where
import qualified Data.HashMap.Strict as HashMap
import Data.HashMap.Strict (HashMap)
import Data.Maybe
import qualified Data.Text as Text
import Data.String
import Data.Text (Text)
import Prelude
import Data.String
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
dozensMap :: HashMap Text Integer
dozensMap = HashMap.fromList
@ -72,7 +73,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
@ -255,7 +256,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,22 +10,23 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.SV.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude
import Data.String
import Data.Text (Text)
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleIntersectWithAnd :: Rule
ruleIntersectWithAnd = Rule
@ -87,10 +88,8 @@ ruleDecimalWithThousandsSeparator = Rule
[ regex "(\\d+(\\.\\d\\d\\d)+\\,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -295,7 +294,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace (Text.singleton '.') Text.empty match
_) -> let fmt = Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}

View File

@ -10,22 +10,23 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.TR.Rules
( rules ) where
( rules
) where
import qualified Data.HashMap.Strict as HashMap
import Data.HashMap.Strict (HashMap)
import Data.Maybe
import qualified Data.Text as Text
import Data.String
import Data.Text (Text)
import Prelude
import Data.String
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
hundredsMap :: HashMap Text Integer
hundredsMap = HashMap.fromList
@ -113,10 +114,8 @@ ruleDecimalWithThousandsSeparator = Rule
[ regex "(\\d+(\\.\\d\\d\\d)+,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
let dot = Text.singleton '.'
comma = Text.singleton ','
fmt = Text.replace comma dot $ Text.replace dot Text.empty match
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
@ -698,7 +697,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton '.') Text.empty match) >>= double
parseDouble (Text.replace "." Text.empty match) >>= double
_ -> Nothing
}

View File

@ -10,33 +10,34 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.UK.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude
import Data.String
import Data.Text (Text)
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
twentyNinetyMap :: HashMap Text Integer
twentyNinetyMap = HashMap.fromList
[ ( "двадцять" , 20 )
, ( "тридцять" , 30 )
, ( "сорок" , 40 )
, ( "п‘ятдесят" , 50 )
, ( "шістдесят" , 60 )
, ( "сімдесят" , 70 )
, ( "дев‘яносто" , 90 )
, ( "вісімдесят" , 80 )
[ ( "двадцять" , 20 )
, ( "тридцять" , 30 )
, ( "сорок" , 40 )
, ( "п‘ятдесят" , 50 )
, ( "шістдесят" , 60 )
, ( "сімдесят" , 70 )
, ( "дев‘яносто", 90 )
, ( "вісімдесят", 80 )
]
ruleInteger5 :: Rule
@ -72,7 +73,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
@ -253,7 +254,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace (Text.singleton ',') Text.empty match
_) -> let fmt = Text.replace "," Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}

View File

@ -10,20 +10,21 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.VI.Rules
( rules ) where
( rules
) where
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
powersOfTenMap :: HashMap.HashMap Text.Text (Double, Int)
powersOfTenMap = HashMap.fromList
@ -33,7 +34,7 @@ powersOfTenMap = HashMap.fromList
, ( "nghìn", (1e3, 3) )
, ( "triệ", (1e6, 6) )
, ( "triệu", (1e6, 6) )
, ( "t", (1e9, 9) )
, ( "t", (1e9, 9) )
, ( "tỷ", (1e9, 9) )
]
@ -112,7 +113,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
@ -322,7 +323,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace (Text.singleton ',') Text.empty match
_) -> let fmt = Text.replace "," Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}

View File

@ -10,20 +10,21 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.ZH.Rules
( rules ) where
( rules
) where
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
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
import qualified Duckling.Numeral.Types as TNumeral
ruleInteger5 :: Rule
ruleInteger5 = Rule
@ -89,7 +90,7 @@ ruleDecimalWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace (Text.singleton ',') Text.empty match) >>= double
parseDouble (Text.replace "," Text.empty match) >>= double
_ -> Nothing
}
@ -180,7 +181,7 @@ ruleIntegerWithThousandsSeparator = Rule
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace (Text.singleton ',') Text.empty match
_) -> let fmt = Text.replace "," Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}