{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Ordinal.HI.Rules
  ( rules
  ) where
import Data.HashMap.Strict (HashMap)
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 (parseInt)
import Duckling.Ordinal.Helpers
import Duckling.Regex.Types
import Duckling.Types
ordinalsMap :: HashMap Text Int
ordinalsMap :: HashMap Text Int
ordinalsMap = [(Text, Int)] -> HashMap Text Int
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
  [ ( Text
"शून्य" , Int
0 )
  , ( Text
"प्रथम" , Int
1 )
  , ( Text
"पहला" , Int
1 )
  , ( Text
"पहली" , Int
1 )
  , ( Text
"पहले" , Int
1 )
  , ( Text
"द्वितीय" , Int
2 )
  , ( Text
"दूसरा" , Int
2 )
  , ( Text
"दूसरी" , Int
2 )
  , ( Text
"दूसरे" , Int
2 )
  , ( Text
"तृतीय" , Int
3 )
  , ( Text
"तीसरा" , Int
3 )
  , ( Text
"तीसरी" , Int
3 )
  , ( Text
"तीसरे" , Int
3 )
  , ( Text
"चौथा" , Int
4 )
  , ( Text
"चौथी" , Int
4 )
  , ( Text
"चौथे" , Int
4 )
  , ( Text
"छठा" , Int
6 )
  , ( Text
"छठी" , Int
6 )
  , ( Text
"छठे" , Int
6 )
  ]
cardinalsMap :: HashMap Text Int
cardinalsMap :: HashMap Text Int
cardinalsMap = [(Text, Int)] -> HashMap Text Int
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
  [ ( Text
"पाँच", Int
5 )
  , ( Text
"सात", Int
7 )
  , ( Text
"आठ", Int
8 )
  , ( Text
"नौ" , Int
9 )
  , ( Text
"दस", Int
10 )
  , ( Text
"ग्यारह", Int
11 )
  , ( Text
"बारह", Int
12 )
  , ( Text
"तेरह", Int
13 )
  , ( Text
"चौदह", Int
14 )
  , ( Text
"पन्द्रह", Int
15 )
  , ( Text
"सोलह", Int
16 )
  , ( Text
"सत्रह", Int
17 )
  , ( Text
"अठारह", Int
18 )
  , ( Text
"उन्नीस", Int
19 )
  , ( Text
"बीस", Int
20 )
  , ( Text
"इक्कीस", Int
21 )
  , ( Text
"बाईस", Int
22 )
  , ( Text
"तेईस", Int
23 )
  , ( Text
"चौबीस", Int
24 )
  , ( Text
"पच्चीस", Int
25 )
  , ( Text
"छब्बीस", Int
26 )
  , ( Text
"सत्ताईस", Int
27 )
  , ( Text
"अट्ठाईस", Int
28 )
  , ( Text
"उनतीस", Int
29 )
  , ( Text
"तीस", Int
30 )
  , ( Text
"चालीस", Int
40 )
  , ( Text
"पचास", Int
50 )
  , ( Text
"साठ", Int
60 )
  , ( Text
"सत्तर", Int
70 )
  , ( Text
"अस्सी", Int
80 )
  , ( Text
"नब्बे", Int
90 )
  ]
ruleOrdinals :: Rule
ruleOrdinals :: Rule
ruleOrdinals = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"ordinals (first..fourth, sixth)"
  , pattern :: Pattern
pattern = [String -> PatternItem
regex String
"(शून्य|प्रथम|पहला|पहली|पहले|द्वितीय|दूसरा|दूसरी|दूसरे|तृतीय|तीसरा|तीसरी|तीसरे|चौथा|चौथी|चौथे|छठा|छठी|छठे)"]
  , prod :: Production
prod = \[Token]
tokens -> case [Token]
tokens of
      (Token Dimension a
RegexMatch (GroupMatch (match:_)):[Token]
_) ->
        Int -> Token
ordinal (Int -> Token) -> Maybe Int -> Maybe Token
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> HashMap Text Int -> Maybe Int
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (Text -> Text
Text.toLower Text
match) HashMap Text Int
ordinalsMap
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
    }
ruleOtherOrdinals :: Rule
ruleOtherOrdinals :: Rule
ruleOtherOrdinals = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"ordinals (fifth, seventh ...)"
  , pattern :: Pattern
pattern = [String -> PatternItem
regex String
"(पाँच|सात|आठ|नौ|दस|ग्यारह|बारह|तेरह|चौदह|पन्द्रह|सोलह|सत्रह|अठारह|उन्नीस|बीस|इक्कीस|बाईस|तेईस|चौबीस|पच्चीस|छब्बीस|सत्ताईस|अट्ठाईस|उनतीस|तीस|चालीस|पचास|साठ|सत्तर|अस्सी|नब्बे)(वा|वी|वे)"]
  , prod :: Production
prod = \[Token]
tokens -> case [Token]
tokens of
      (Token Dimension a
RegexMatch (GroupMatch (match:_)):[Token]
_) ->
        Int -> Token
ordinal (Int -> Token) -> Maybe Int -> Maybe Token
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> HashMap Text Int -> Maybe Int
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (Text -> Text
Text.toLower Text
match) HashMap Text Int
cardinalsMap
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }
ruleOrdinalDigits :: Rule
ruleOrdinalDigits :: Rule
ruleOrdinalDigits = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"ordinal (digits)"
  , pattern :: Pattern
pattern = [String -> PatternItem
regex String
"0*(\\d+) ?(वा|वी|वे)"]
  , prod :: Production
prod = \[Token]
tokens -> case [Token]
tokens of
      (Token Dimension a
RegexMatch (GroupMatch (match:_)):[Token]
_) -> Int -> Token
ordinal (Int -> Token) -> Maybe Int -> Maybe Token
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Int
parseInt Text
match
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }
rules :: [Rule]
rules :: [Rule]
rules =
  [ Rule
ruleOrdinals
  , Rule
ruleOtherOrdinals
  , Rule
ruleOrdinalDigits
  ]