-- 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.Numeral.AR.EG.Helpers
  ( digitsMap
  , numeralToStringMap
  , parseArabicDoubleAsText
  , parseArabicDoubleFromText
  , parseArabicIntAsText
  , parseArabicIntegerFromText
  ) where

import Control.Monad (join)
import Data.HashMap.Strict (HashMap)
import Data.Maybe (mapMaybe)
import Data.String
import Data.Text (Text)
import Duckling.Numeral.Helpers
  ( parseDouble
  , parseInteger
  )
import Prelude

import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text

numeralToStringMap :: HashMap Char String
numeralToStringMap :: HashMap Char String
numeralToStringMap =
  [(Char, String)] -> HashMap Char String
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
    [ (Char
'٠', String
"0")
    , (Char
'١', String
"1")
    , (Char
'٢', String
"2")
    , (Char
'٣', String
"3")
    , (Char
'٤', String
"4")
    , (Char
'٥', String
"5")
    , (Char
'٦', String
"6")
    , (Char
'٧', String
"7")
    , (Char
'٨', String
"8")
    , (Char
'٩', String
"9")
    ]

digitsMap :: HashMap Text Integer
digitsMap :: HashMap Text Integer
digitsMap =
  [(Text, Integer)] -> HashMap Text Integer
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList
    [ (Text
"اتنين", Integer
2)
    , (Text
"تلات", Integer
3)
    , (Text
"اربع", Integer
4)
    , (Text
"أربع", Integer
4)
    , (Text
"خمس", Integer
5)
    , (Text
"ست", Integer
6)
    , (Text
"سبع", Integer
7)
    , (Text
"تمان", Integer
8)
    , (Text
"تسع", Integer
9)
    ]

parseArabicIntAsText :: Text -> Text
parseArabicIntAsText :: Text -> Text
parseArabicIntAsText =
  String -> Text
Text.pack
    (String -> Text) -> (Text -> String) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
    ([String] -> String) -> (Text -> [String]) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Maybe String) -> String -> [String]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Char -> HashMap Char String -> Maybe String
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
`HashMap.lookup` HashMap Char String
numeralToStringMap)
    (String -> [String]) -> (Text -> String) -> Text -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack

parseArabicIntegerFromText :: Text -> Maybe Integer
parseArabicIntegerFromText :: Text -> Maybe Integer
parseArabicIntegerFromText = Text -> Maybe Integer
parseInteger (Text -> Maybe Integer) -> (Text -> Text) -> Text -> Maybe Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
parseArabicIntAsText

parseArabicDoubleAsText :: Text -> Text
parseArabicDoubleAsText :: Text -> Text
parseArabicDoubleAsText =
  String -> Text
Text.pack
    (String -> Text) -> (Text -> String) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join
    ([String] -> String) -> (Text -> [String]) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Maybe String) -> String -> [String]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Char -> HashMap Char String -> Maybe String
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
`HashMap.lookup` Char -> String -> HashMap Char String -> HashMap Char String
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HashMap.insert Char
'٫' String
"." HashMap Char String
numeralToStringMap)
    (String -> [String]) -> (Text -> String) -> Text -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack

parseArabicDoubleFromText :: Text -> Maybe Double
parseArabicDoubleFromText :: Text -> Maybe Double
parseArabicDoubleFromText = Text -> Maybe Double
parseDouble (Text -> Maybe Double) -> (Text -> Text) -> Text -> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
parseArabicDoubleAsText