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

module Duckling.Numeral.IS.Rules
  ( rules
  ) where

import Data.HashMap.Strict (HashMap)
import Data.Maybe
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
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral

zeroToTwentyMap:: HashMap Text Integer
zeroToTwentyMap :: HashMap Text Integer
zeroToTwentyMap = [(Text, Integer)] -> HashMap Text Integer
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
  [ ( Text
"núll", Integer
0 )
  , ( Text
"null", Integer
0 )
  , ( Text
"einn", Integer
1 )
  , ( Text
"tveir", Integer
2 )
  , ( Text
"þrír", Integer
3 )
  , ( Text
"fjórir", Integer
4 )
  , ( Text
"fimm", Integer
5 )
  , ( Text
"sex", Integer
6 )
  , ( Text
"sjö", Integer
7 )
  , ( Text
"átta", Integer
8 )
  , ( Text
"níu", Integer
9 )
  , ( Text
"tíu", Integer
10 )
  , ( Text
"ellefu", Integer
11 )
  , ( Text
"tólf", Integer
12 )
  , ( Text
"þrettán", Integer
13 )
  , ( Text
"fjórtán", Integer
14 )
  , ( Text
"fimmtán", Integer
15 )
  , ( Text
"sextán", Integer
16 )
  , ( Text
"sautján", Integer
17 )
  , ( Text
"átján", Integer
18 )
  , ( Text
"nítján", Integer
19 )
  , ( Text
"tuttugu", Integer
20 )
  ]

ruleZeroToTwenty :: Rule
ruleZeroToTwenty :: Rule
ruleZeroToTwenty = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"number (0..20)"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex String
"(n[úu]ll|einn|tveir|þrír|fjórir|fimm(tán)?|sex(tán)?|sjö|átta|níu|tíu|ellefu|tólf|þrettán|fjórtán|sautján|átján|nítján|tuttugu)"
    ]
  , prod :: Production
prod = \case
      (Token Dimension a
RegexMatch (GroupMatch (match:_)):[Token]
_) ->
        Text -> HashMap Text Integer -> Maybe Integer
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HashMap.lookup (Text -> Text
Text.toLower Text
match) HashMap Text Integer
zeroToTwentyMap Maybe Integer -> (Integer -> Maybe Token) -> Maybe Token
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Integer -> Maybe Token
integer
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }

rules :: [Rule]
rules :: [Rule]
rules =
  [ Rule
ruleZeroToTwenty
  ]