-- 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.NL.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

zeroNineteenMap :: HashMap Text Int
zeroNineteenMap :: HashMap Text Int
zeroNineteenMap = [(Text, Int)] -> HashMap Text Int
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
  [ (Text
"eerste", Int
1)
  , (Text
"tweede", Int
2)
  , (Text
"derde", Int
3)
  , (Text
"vierde", Int
4)
  , (Text
"vijfde", Int
5)
  , (Text
"zesde", Int
6)
  , (Text
"zevende", Int
7)
  , (Text
"achste", Int
8)
  , (Text
"negende", Int
9)
  , (Text
"tiende", Int
10)
  , (Text
"elfde", Int
11)
  , (Text
"twaalfde", Int
12)
  , (Text
"dertiende", Int
13)
  , (Text
"veertiende", Int
14)
  , (Text
"vijftiende", Int
15)
  , (Text
"zestiende", Int
16)
  , (Text
"zeventiende", Int
17)
  , (Text
"achtiende", Int
18)
  , (Text
"negentiende", Int
19)
  ]

ruleOrdinalsFirstth :: Rule
ruleOrdinalsFirstth :: Rule
ruleOrdinalsFirstth = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"ordinals (first..19th)"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex String
"(eerste|tweede|derde|vierde|vijfde|zeste|zevende|achtste|negende|tiende|elfde|twaalfde|veertiende|vijftiende|zestiende|zeventiende|achtiende|negentiende)"
    ]
  , 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
zeroNineteenMap
      [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+)(\\.| ?(ste|de))"
    ]
  , 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
ruleOrdinalsFirstth
  ]