duckling/Duckling/Rules/AR.hs
Amr Keleg 703ff13210 Add a new Arabic locale (EG) (#554)
Summary:
Egyptian Arabic is a dialect of Arabic that is mostly a spoken language that is used in everyday communications.
This PR adds new locale to Arabic to support the differences between Modern Standard Arabic (MSA) and Egyptian Arabic (EG).
I have mainly depended on the different locales of Spanish that are supported by Duckling to create the new Egyptian Arabic locale.
New modifications are added to the `Numeral` dimension since I didn't spot differences in other dimensions.

Pull Request resolved: https://github.com/facebook/duckling/pull/554

Reviewed By: patapizza

Differential Revision: D25543502

Pulled By: chessai

fbshipit-source-id: 4cbb7be78a52071c8681380077f0b4dc033a60de
2020-12-15 11:33:40 -08:00

57 lines
1.9 KiB
Haskell

-- 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 #-}
module Duckling.Rules.AR
( defaultRules
, langRules
, localeRules
) where
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.AmountOfMoney.AR.Rules as AmountOfMoney
import qualified Duckling.Duration.AR.Rules as Duration
import qualified Duckling.Numeral.AR.Rules as Numeral
import qualified Duckling.Numeral.AR.EG.Rules as NumeralEG
import qualified Duckling.Ordinal.AR.Rules as Ordinal
import qualified Duckling.PhoneNumber.AR.Rules as PhoneNumber
import qualified Duckling.Quantity.AR.Rules as Quantity
import qualified Duckling.Temperature.AR.Rules as Temperature
import qualified Duckling.Time.AR.Rules as Time
import qualified Duckling.TimeGrain.AR.Rules as TimeGrain
import qualified Duckling.Volume.AR.Rules as Volume
defaultRules :: Seal Dimension -> [Rule]
defaultRules = langRules
localeRules :: Region -> Seal Dimension -> [Rule]
localeRules EG (Seal Numeral) = NumeralEG.rules
localeRules region (Seal (CustomDimension dim)) = dimLocaleRules region dim
localeRules _ _ = []
langRules :: Seal Dimension -> [Rule]
langRules (Seal AmountOfMoney) = AmountOfMoney.rules
langRules (Seal CreditCardNumber) = []
langRules (Seal Distance) = []
langRules (Seal Duration) = Duration.rules
langRules (Seal Email) = []
langRules (Seal Numeral) = Numeral.rules
langRules (Seal Ordinal) = Ordinal.rules
langRules (Seal PhoneNumber) = PhoneNumber.rules
langRules (Seal Quantity) = Quantity.rules
langRules (Seal RegexMatch) = []
langRules (Seal Temperature) = Temperature.rules
langRules (Seal Time) = Time.rules
langRules (Seal TimeGrain) = TimeGrain.rules
langRules (Seal Url) = []
langRules (Seal Volume) = Volume.rules
langRules (Seal (CustomDimension dim)) = dimLangRules AR dim