-- 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.PT.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.Ordinal.Helpers
import Duckling.Ordinal.Types (OrdinalData (..))
import Duckling.Regex.Types (GroupMatch (..))
import Duckling.Types
import qualified Duckling.Ordinal.Types as TOrdinal

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
"primeir", Int
1 )
  , ( Text
"segund", Int
2 )
  , ( Text
"terceir", Int
3 )
  , ( Text
"quart", Int
4 )
  , ( Text
"quint", Int
5 )
  , ( Text
"sext", Int
6 )
  , ( Text
"setim", Int
7 )
  , ( Text
"sétim", Int
7 )
  , ( Text
"oitav", Int
8 )
  , ( Text
"non", Int
9 )
  , ( Text
"decim", Int
10 )
  , ( Text
"décim", Int
10 )
  ]

ruleOrdinals :: Rule
ruleOrdinals :: Rule
ruleOrdinals = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"ordinals (1..10)"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex String
"(primeir|segund|terceir|quart|quint|sext|s[ée]tim|oitav|non|d[ée]cim)[ao]s?"
    ]
  , 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
ordinalsMap
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }

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
"vi", Int
20 )
  , ( Text
"tri", Int
30 )
  , ( Text
"quadra", Int
40 )
  , ( Text
"qüinqua", Int
50 )
  , ( Text
"quinqua", Int
50 )
  , ( Text
"sexa", Int
60 )
  , ( Text
"septua", Int
70 )
  , ( Text
"octo", Int
80 )
  , ( Text
"nona", Int
90 )
  ]

ruleCardinals :: Rule
ruleCardinals :: Rule
ruleCardinals = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"cardinals (20 .. 90)"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex String
"(vi|tri|quadra|q[üu]inqua|sexa|septua|octo|nona)g[ée]sim[ao]s?"
    ]
  , 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
cardinalsMap
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }

ruleCompositeOrdinals :: Rule
ruleCompositeOrdinals :: Rule
ruleCompositeOrdinals = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"ordinals (11..19)"
  , pattern :: Pattern
pattern =
    [ [Int] -> PatternItem
oneOf [Int
10, Int
20 .. Int
90]
    , [Int] -> PatternItem
oneOf [Int
1..Int
9]
    ]
  , prod :: Production
prod = \case
      (Token Dimension a
Ordinal OrdinalData{TOrdinal.value = t}:
       Token Dimension a
Ordinal OrdinalData{TOrdinal.value = u}:
       [Token]
_) -> 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 -> Token) -> Int -> Token
forall a b. (a -> b) -> a -> b
$ Int
t Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
u
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }

rules :: [Rule]
rules :: [Rule]
rules =
  [ Rule
ruleOrdinals
  , Rule
ruleCardinals
  , Rule
ruleCompositeOrdinals
  ]