-- 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 LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}

module Duckling.Ordinal.DE.Rules
  ( rules
  ) where

import Data.Semigroup ((<>))
import Prelude
import Data.String
import Data.Text (Text)
import qualified Data.HashMap.Strict as HashMap
import qualified Data.List as List
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

ordinalList :: [(Text, Int)]
ordinalList :: [(Text, Int)]
ordinalList =
  [ (Text
"erste", Int
1)
  , (Text
"zweite", Int
2)
  , (Text
"dritte", Int
3)
  , (Text
"vierte", Int
4)
  , (Text
"fünfte", Int
5)
  , (Text
"sechste", Int
6)
  , (Text
"siebte", Int
7)
  , (Text
"achte", Int
8)
  , (Text
"neunte", Int
9)
  , (Text
"zehnte", Int
10)
  , (Text
"elfte", Int
11)
  , (Text
"zwölfte", Int
12)
  , (Text
"dreizente", Int
13)
  , (Text
"vierzehnte", Int
14)
  , (Text
"fünfzehnte", Int
15)
  , (Text
"sechzente", Int
16)
  , (Text
"siebzehnte", Int
17)
  , (Text
"achtzehnte", Int
18)
  , (Text
"neunzehnte", Int
19)
  , (Text
"zwanzigste", Int
20)
  , (Text
"einundzwanzigste", Int
21)
  , (Text
"zweiundzwanzigste", Int
22)
  , (Text
"dreiundzwanzigste", Int
23)
  , (Text
"vierundzwanzigste", Int
24)
  , (Text
"fünfundzwanzigste", Int
25)
  , (Text
"sechsundzwanzigste", Int
26)
  , (Text
"siebenundzwanzigste", Int
27)
  , (Text
"achtundzwanzigste", Int
28)
  , (Text
"neunundzwanzigste", Int
29)
  , (Text
"dreissigste", Int
30)
  , (Text
"dreißigste", Int
30)
  , (Text
"einunddreissigste", Int
31)
  , (Text
"einunddreißigste", Int
31)
  ]

ruleOrdinalsFirstth :: Rule
ruleOrdinalsFirstth :: Rule
ruleOrdinalsFirstth = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"ordinal (1..31)"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex (String -> PatternItem) -> String -> PatternItem
forall a b. (a -> b) -> a -> b
$ Text -> String
Text.unpack Text
construction
    ]
  , prod :: Production
prod = \case
      (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
ordinalMap
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }
  where
    ordinalMap :: HashMap.HashMap Text Int
    ordinalMap :: HashMap Text Int
ordinalMap = [(Text, Int)] -> HashMap Text Int
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList [(Text, Int)]
ordinalList

    construction :: Text
    construction :: Text
construction =
      Text
"("
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat (Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
List.intersperse Text
"|" ((Text, Int) -> Text
forall a b. (a, b) -> a
fst ((Text, Int) -> Text) -> [(Text, Int)] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Int)]
ordinalList))
      Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")[rsn]?"

ruleOrdinalDigits :: Rule
ruleOrdinalDigits :: Rule
ruleOrdinalDigits = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"ordinal (digits)"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex String
"(?<!\\d|\\.)0*(\\d+)(\\.(?!\\d)| ?(te(n|r|s)?)|(ste(n|r|s)?))"
    ]
  , prod :: Production
prod = \case
      (Token Dimension a
RegexMatch (GroupMatch (match:_)):[Token]
_) -> do
        Int
v <- Text -> Maybe Int
parseInt Text
match
        Token -> Maybe Token
forall a. a -> Maybe a
Just (Token -> Maybe Token) -> Token -> Maybe Token
forall a b. (a -> b) -> a -> b
$ Int -> Token
ordinal Int
v
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }

rules :: [Rule]
rules :: [Rule]
rules =
  [ Rule
ruleOrdinalsFirstth
  , Rule
ruleOrdinalDigits
  ]