{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Numeral.KN.Rules
( rules
) where
import Data.HashMap.Strict (HashMap)
import Data.Maybe
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.Regex.Types
import Duckling.Types
ankiMap :: HashMap Char Char
ankiMap :: HashMap Char Char
ankiMap = [(Char, Char)] -> HashMap Char Char
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
[ (Char
'೦', Char
'0')
, (Char
'೧', Char
'1')
, (Char
'೨', Char
'2')
, (Char
'೩', Char
'3')
, (Char
'೪', Char
'4')
, (Char
'೫', Char
'5')
, (Char
'೬', Char
'6')
, (Char
'೭', Char
'7')
, (Char
'೮', Char
'8')
, (Char
'೯', Char
'9')
]
ankiToArab :: Char -> Char
ankiToArab :: Char -> Char
ankiToArab Char
c = Char -> Char -> HashMap Char Char -> Char
forall k v. (Eq k, Hashable k) => v -> k -> HashMap k v -> v
HashMap.lookupDefault Char
c Char
c HashMap Char Char
ankiMap
ruleAnki :: Rule
ruleAnki :: Rule
ruleAnki = Rule :: Text -> Pattern -> Production -> Rule
Rule
{ name :: Text
name = Text
"anki forms"
, pattern :: Pattern
pattern =
[ String -> PatternItem
regex String
"([೦೧೨೩೪೫೬೭೮೯]{1,10})"
]
, prod :: Production
prod = \case
(Token Dimension a
RegexMatch (GroupMatch (match:_)):[Token]
_) ->
Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> Maybe Int -> Maybe Integer
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Int
parseInt ((Char -> Char) -> Text -> Text
Text.map Char -> Char
ankiToArab Text
match) Maybe Integer -> (Integer -> Maybe Token) -> Maybe Token
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Integer -> Maybe Token
integer
[Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
}
ruleNumeralMap :: [(Text, Integer)]
ruleNumeralMap :: [(Text, Integer)]
ruleNumeralMap =
[ (Text
"ಸೊನ್ನೆ", Integer
0)
, (Text
"ಒಂದು", Integer
1)
, (Text
"ಎರಡು", Integer
2)
, (Text
"ಮೂರು", Integer
3)
, (Text
"ನಾಲ್ಕು", Integer
4)
, (Text
"ಐದು", Integer
5)
, (Text
"ಆರು", Integer
6)
, (Text
"ಏಳು", Integer
7)
, (Text
"ಎಂಟು", Integer
8)
, (Text
"ಒಂಬತ್ತು", Integer
9)
]
ruleNumerals :: [Rule]
ruleNumerals :: [Rule]
ruleNumerals =
((Text, Integer) -> Rule) -> [(Text, Integer)] -> [Rule]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Integer) -> Rule
constructRule [(Text, Integer)]
ruleNumeralMap
where
constructRule :: (Text, Integer) -> Rule
constructRule :: (Text, Integer) -> Rule
constructRule (Text
s, Integer
i) = Rule :: Text -> Pattern -> Production -> Rule
Rule
{ name :: Text
name = Text
"number: " Text -> Text -> Text
forall a. Monoid a => a -> a -> a
`mappend` Text
s
, pattern :: Pattern
pattern =
[ String -> PatternItem
regex (String -> PatternItem) -> String -> PatternItem
forall a b. (a -> b) -> a -> b
$ Text -> String
Text.unpack Text
s
]
, prod :: Production
prod = Maybe Token -> Production
forall a b. a -> b -> a
const (Maybe Token -> Production) -> Maybe Token -> Production
forall a b. (a -> b) -> a -> b
$ Integer -> Maybe Token
integer Integer
i
}
rules :: [Rule]
rules :: [Rule]
rules =
[ Rule
ruleAnki
]
[Rule] -> [Rule] -> [Rule]
forall a. [a] -> [a] -> [a]
++ [Rule]
ruleNumerals