-- 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.Ordinal.TR.Rules
  ( rules ) where

import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Text (Text)
import qualified Data.Text as Text
import Prelude
import Data.String

import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers (parseInt)
import Duckling.Ordinal.Helpers
import Duckling.Regex.Types
import Duckling.Types

ordinals :: [Text]
ordinals :: [Text]
ordinals =
  [ Text
"birinci"
  , Text
"ikinci"
  , Text
"üçüncü"
  , Text
"dördüncü"
  , Text
"beşinci"
  , Text
"altıncı"
  , Text
"yedinci"
  , Text
"sekizinci"
  , Text
"dokuzuncu"
  , Text
"onuncu"
  , Text
"on birinci"
  , Text
"on ikinci"
  , Text
"on üçüncü"
  , Text
"on dördüncü"
  , Text
"on beşinci"
  , Text
"on altıncı"
  , Text
"on yedinci"
  , Text
"on sekizinci"
  , Text
"on dokuzuncu"
  , Text
"yirminci"
  , Text
"yirmi birinci"
  , Text
"yirmi ikinci"
  , Text
"yirmi üçüncü"
  , Text
"yirmi dördüncü"
  , Text
"yirmi beşinci"
  , Text
"yirmi altıncı"
  , Text
"yirmi yedinci"
  , Text
"yirmi sekizinci"
  , Text
"yirmi dokuzuncu"
  , Text
"otuzuncu"
  , Text
"otuz birinci"
  ]

ordinalsHashMap :: HashMap Text Int
ordinalsHashMap :: HashMap Text Int
ordinalsHashMap = [(Text, Int)] -> HashMap Text Int
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList ([(Text, Int)] -> HashMap Text Int)
-> [(Text, Int)] -> HashMap Text Int
forall a b. (a -> b) -> a -> b
$ [Text] -> [Int] -> [(Text, Int)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Text]
ordinals [Int
1..]

ruleOrdinalsFirstst :: Rule
ruleOrdinalsFirstst :: Rule
ruleOrdinalsFirstst = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"ordinals (first..31st)"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex (String -> PatternItem) -> (Text -> String) -> Text -> PatternItem
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack (Text -> PatternItem) -> Text -> PatternItem
forall a b. (a -> b) -> a -> b
$
        [Text] -> Text
Text.concat [ Text
"(", Text -> [Text] -> Text
Text.intercalate Text
"|" [Text]
ordinals, Text
")" ]
    ]
  , 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
ordinalsHashMap
      [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+) ?('?)(inci|nci|ıncı|ncı|uncu|ncu|üncü|ncü|.)"
    ]
  , 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
ruleOrdinalDigits
  , Rule
ruleOrdinalsFirstst
  ]