Mongolian (#277)

Summary:
MN Setup+Numeral
Pull Request resolved: https://github.com/facebook/duckling/pull/277

Reviewed By: chinmay87

Differential Revision: D13028169

Pulled By: patapizza

fbshipit-source-id: 7d587300918b3ed6211b6ce4147350147b4dc89e
This commit is contained in:
uugan 2018-11-26 15:16:43 -08:00 committed by Facebook Github Bot
parent 97cbde5454
commit 69ffb0f39d
46 changed files with 2085 additions and 14 deletions

View File

@ -221,4 +221,9 @@ allExamples = concat
[ "four crore rupees"
, "4 crores rupees"
]
, examples (simple MNT 10)
[ "ten tugriks"
, "10 Tugrik"
, "10MNT"
]
]

View File

@ -0,0 +1,96 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.AmountOfMoney.MN.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale MN Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple MNT 1)
[ "1 төг"
, "нэг төгрөг"
, "1 ₮"
, "1 төгрөг"
]
, examples (simple MNT 10)
[ "10 төгрөг"
, "₮ 10"
, "10₮"
, "10MNT"
, "10төг"
, "10 төгрөг"
, "төгрөг 10"
, "10 төгрөгийн"
]
, examples (simple Dollar 1)
[ "$1"
, "нэг доллар"
]
, examples (simple Dollar 10)
[ "$10"
, "$ 10"
, "10$"
, "10 доллар"
, "арван доллар"
]
, examples (simple Cent 10)
[ "10 цент"
, "арван пени"
, "арван цент"
, "10 c"
, "10¢"
]
, examples (simple EUR 20)
[ "20€"
, "20 €ur"
, "20 евро"
, "Евро 20"
]
, examples (simple Pound 10)
[ "\x00a3\&10"
, "арван фунт"
]
, examples (simple INR 20)
[ "20Rs"
, "Rs20"
]
, examples (simple GBP 3.01)
[ "GBP3.01"
, "GBP 3.01"
, "3.01 Английн фунт"
]
, examples (under MNT 10)
[ "10₮-c бага"
]
, examples (above MNT 20)
[ "20MNT-c их"
]
, examples (between MNT (5, 10))
[ "5-c MNT10 хүртэл"
, "5-c ₮10 хүртэл"
, "5-c 10 MNT хүртэл"
, "MNT5-c 10 хүртэл"
, "MNT5-c 10₮ хооронд"
, "5-c ₮10-н хооронд"
, "MNT5-c 10₮-н хүртэл"
]
]

View File

@ -0,0 +1,261 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.AmountOfMoney.MN.Rules
( rules
) where
import Data.Maybe
import Data.String
import Prelude
import Duckling.AmountOfMoney.Helpers
import Duckling.AmountOfMoney.Types (Currency(..), AmountOfMoneyData(..))
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers (isNatural, isPositive)
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.AmountOfMoney.Types as TAmountOfMoney
import qualified Duckling.Numeral.Types as TNumeral
ruleUnitAmount :: Rule
ruleUnitAmount = Rule
{ name = "<unit> <amount>"
, pattern =
[ Predicate isCurrencyOnly
, Predicate isPositive
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.currency = c}:
Token Numeral NumeralData{TNumeral.value = v}:
_) -> Just . Token AmountOfMoney . withValue v $ currencyOnly c
_ -> Nothing
}
ruleTugriks :: Rule
ruleTugriks = Rule
{ name = "төг"
, pattern =
[ regex "төг(рөг(ийн)?)?"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly MNT
}
rulePounds :: Rule
rulePounds = Rule
{ name = "£"
, pattern =
[ regex "фунт(аар|тай|аас)?"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Pound
}
ruleGBP :: Rule
ruleGBP = Rule
{ name = "Mongolian GBP"
, pattern =
[ regex "Английн\\s+фунт"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly GBP
}
ruleDollar :: Rule
ruleDollar = Rule
{ name = "$"
, pattern =
[ regex "доллар(ын|оор|оос|той)?"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Dollar
}
ruleCent :: Rule
ruleCent = Rule
{ name = "cent"
, pattern =
[ regex "цент(ийн|ээс|ээр|тэй)?|пени|пенс(ээр|гээр|тэй|ээс|гээс)?|ц"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Cent
}
ruleEUR :: Rule
ruleEUR = Rule
{ name = ""
, pattern =
[ regex "евро"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly EUR
}
ruleBucks :: Rule
ruleBucks = Rule
{ name = "bucks"
, pattern =
[ regex "бакс(аар|тай|аас)?"
]
, prod = \_ -> Just . Token AmountOfMoney $ currencyOnly Unnamed
}
rulePrecision :: Rule
rulePrecision = Rule
{ name = "about|exactly <amount-of-money>"
, pattern =
[ regex "яг|ойролцоогоор|бараг"
, Predicate isMoneyWithValue
]
, prod = \case
(_:token:_) -> Just token
_ -> Nothing
}
ruleIntervalBetweenNumeral :: Rule
ruleIntervalBetweenNumeral = Rule
{ name = "between|from <numeral> to|and <amount-of-money>"
, pattern =
[ Predicate isPositive
, regex "-c"
, Predicate isSimpleAmountOfMoney
, regex "(-н\\s+)?(хооронд|хүртэл)"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = from}:
_:
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c}:
_) | from < to ->
Just . Token AmountOfMoney . withInterval (from, to) $ currencyOnly c
_ -> Nothing
}
ruleIntervalBetweenNumeral2 :: Rule
ruleIntervalBetweenNumeral2 = Rule
{ name = "between|from <amount-of-money> to|and <numeral>"
, pattern =
[ Predicate isSimpleAmountOfMoney
, regex "-c"
, Predicate isNatural
, regex "(-н\\s+)?(хооронд|хүртэл)"
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just from,
TAmountOfMoney.currency = c}:
_:
Token Numeral NumeralData{TNumeral.value = to}:
_) | from < to ->
Just . Token AmountOfMoney . withInterval (from, to) $ currencyOnly c
_ -> Nothing
}
ruleIntervalBetween :: Rule
ruleIntervalBetween = Rule
{ name = "between|from <amount-of-money> to|and <amount-of-money>"
, pattern =
[ Predicate isSimpleAmountOfMoney
, regex "-c"
, Predicate isSimpleAmountOfMoney
, regex "(-н\\s+)?(хооронд|хүртэл)"
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just from,
TAmountOfMoney.currency = c1}:
_:
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c2}:
_) | from < to && c1 == c2 ->
Just . Token AmountOfMoney . withInterval (from, to) $ currencyOnly c1
_ -> Nothing
}
ruleIntervalNumeralDash :: Rule
ruleIntervalNumeralDash = Rule
{ name = "<numeral> - <amount-of-money>"
, pattern =
[ Predicate isPositive
, regex "-"
, Predicate isSimpleAmountOfMoney
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = from}:
_:
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c}:
_) | from < to ->
Just . Token AmountOfMoney . withInterval (from, to) $ currencyOnly c
_ -> Nothing
}
ruleIntervalDash :: Rule
ruleIntervalDash = Rule
{ name = "<amount-of-money> - <amount-of-money>"
, pattern =
[ Predicate isSimpleAmountOfMoney
, regex "-"
, Predicate isSimpleAmountOfMoney
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just from,
TAmountOfMoney.currency = c1}:
_:
Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c2}:
_) | from < to && c1 == c2 ->
Just . Token AmountOfMoney . withInterval (from, to) $ currencyOnly c1
_ -> Nothing
}
ruleIntervalMax :: Rule
ruleIntervalMax = Rule
{ name = "under/less/lower/no more than <amount-of-money>"
, pattern =
[ Predicate isSimpleAmountOfMoney
, regex "-c\\s+(бага|доогуур|ихгүй)"
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c}:
_) -> Just . Token AmountOfMoney . withMax to $ currencyOnly c
_ -> Nothing
}
ruleIntervalMin :: Rule
ruleIntervalMin = Rule
{ name = "over/above/at least/more than <amount-of-money>"
, pattern =
[ Predicate isSimpleAmountOfMoney
, regex "-c\\s+(их|дээгүүр|илүү)"
]
, prod = \case
(Token AmountOfMoney AmountOfMoneyData{TAmountOfMoney.value = Just to,
TAmountOfMoney.currency = c}:
_) -> Just . Token AmountOfMoney . withMin to $ currencyOnly c
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleUnitAmount
, ruleBucks
, ruleCent
, ruleDollar
, ruleEUR
, ruleGBP
, ruleIntervalBetweenNumeral
, ruleIntervalBetweenNumeral2
, ruleIntervalBetween
, ruleIntervalMax
, ruleIntervalMin
, ruleIntervalNumeralDash
, ruleIntervalDash
, rulePounds
, rulePrecision
, ruleTugriks
]

View File

@ -85,8 +85,12 @@ currencies = HashMap.fromList
, ("kwd", KWD)
, ("lbp", LBP)
, ("mad", MAD)
, ("mnt", MNT)
, ("myr", MYR)
, ("rm", MYR)
, ("", MNT)
, ("tugrik", MNT)
, ("tugriks", MNT)
, ("nok", NOK)
, ("nzd", NZD)
, ("pkr", PKR)
@ -121,7 +125,7 @@ ruleCurrencies :: Rule
ruleCurrencies = Rule
{ name = "currencies"
, pattern =
[ regex "(aed|aud|bgn|brl|byn|¢|c|cad|chf|cny|\\$|dinars?|dkk|dollars?|egp|(e|€)uro?s?|€|gbp|gel|\x20BE|hrk|idr|ils|inr|iqd|jmd|jod|¥|jpy|lari|krw|kwd|lbp|mad|myr|rm|nok|nzd|£|pkr|pln|pta?s?|qar|₽|rs\\.?|riy?als?|ron|rub|rupees?|sar|sek|sgb|shekels?|thb|ttd|us(d|\\$)|vnd|yen|yuan|zar)"
[ regex "(aed|aud|bgn|brl|byn|¢|c|cad|chf|cny|\\$|dinars?|dkk|dollars?|egp|(e|€)uro?s?|€|gbp|gel|\x20BE|hrk|idr|ils|inr|iqd|jmd|jod|¥|jpy|lari|krw|kwd|lbp|mad|₮|mnt|tugriks?|myr|rm|nok|nzd|£|pkr|pln|pta?s?|qar|₽|rs\\.?|riy?als?|ron|rub|rupees?|sar|sek|sgb|shekels?|thb|ttd|us(d|\\$)|vnd|yen|yuan|zar)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> do

View File

@ -63,6 +63,7 @@ data Currency
| KWD
| LBP
| MAD
| MNT
| MYR
| NOK
| NZD
@ -118,6 +119,7 @@ instance ToJSON Currency where
toJSON KWD = "KWD"
toJSON LBP = "LBP"
toJSON MAD = "MAD"
toJSON MNT = "MNT"
toJSON MYR = "MYR"
toJSON NOK = "NOK"
toJSON NZD = "NZD"

View File

@ -48,6 +48,7 @@ import qualified Duckling.Dimensions.KM as KMDimensions
import qualified Duckling.Dimensions.KO as KODimensions
import qualified Duckling.Dimensions.LO as LODimensions
import qualified Duckling.Dimensions.ML as MLDimensions
import qualified Duckling.Dimensions.MN as MNDimensions
import qualified Duckling.Dimensions.MY as MYDimensions
import qualified Duckling.Dimensions.NB as NBDimensions
import qualified Duckling.Dimensions.NE as NEDimensions
@ -63,6 +64,7 @@ import qualified Duckling.Dimensions.UK as UKDimensions
import qualified Duckling.Dimensions.VI as VIDimensions
import qualified Duckling.Dimensions.ZH as ZHDimensions
allDimensions :: Lang -> [Some Dimension]
allDimensions lang = CommonDimensions.allDimensions ++ langDimensions lang
@ -119,6 +121,7 @@ langDimensions KM = KMDimensions.allDimensions
langDimensions KO = KODimensions.allDimensions
langDimensions LO = LODimensions.allDimensions
langDimensions ML = MLDimensions.allDimensions
langDimensions MN = MNDimensions.allDimensions
langDimensions MY = MYDimensions.allDimensions
langDimensions NB = NBDimensions.allDimensions
langDimensions NE = NEDimensions.allDimensions

24
Duckling/Dimensions/MN.hs Normal file
View File

@ -0,0 +1,24 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Dimensions.MN
( allDimensions
) where
import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ This Distance
, This Duration
, This Numeral
, This Ordinal
, This Quantity
, This Temperature
, This Volume
]

View File

@ -0,0 +1,58 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Distance.MN.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Distance.Types
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale MN Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Kilometre 3)
[ "3 километр"
, "3 км"
, "3км"
]
, examples (simple Mile 8)
[ "8 миль"
]
, examples (simple Metre 1)
[ "1 м"
, "1 метр"
]
, examples (simple Centimetre 2)
[ "2см"
]
, examples (simple Millimetre 4)
[ "4мм"
, "4 миллиметр"
]
, examples (simple Inch 5)
[ "5 инч"
, "5\""
]
, examples (simple Foot 35)
[ "35 фут"
, "35'"
]
, examples (simple Yard 47)
[ "47 яард"
]
]

View File

@ -0,0 +1,50 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Distance.MN.Rules
( rules
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.Dimensions.Types
import Duckling.Distance.Helpers
import Duckling.Distance.Types (DistanceData(..))
import Duckling.Types
import qualified Duckling.Distance.Types as TDistance
distances :: [(Text, String, TDistance.Unit)]
distances = [ ("<latent dist> km", "км|километр", TDistance.Kilometre)
, ("<latent dist> feet", "('|фут)", TDistance.Foot)
, ("<latent dist> inch", "(\"|''|дюйм|инч)", TDistance.Inch)
, ("<latent dist> yard", "яард", TDistance.Yard)
, ("<dist> meters", "м(етр(ийн|ээр)?)?", TDistance.Metre)
, ("<dist> centimeters", "см|сантиметр", TDistance.Centimetre)
, ("<dist> millimeters", "мм|миллиметр", TDistance.Millimetre)
, ("<dist> miles", "мил(и|ь)", TDistance.Mile)
]
ruleDistances :: [Rule]
ruleDistances = map go distances
where
go :: (Text, String, TDistance.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern = [ dimension Distance, regex regexPattern ]
, prod = \tokens -> case tokens of
(Token Distance dd:_) -> Just . Token Distance $ withUnit u dd
_ -> Nothing
}
rules :: [Rule]
rules = ruleDistances

View File

@ -0,0 +1,68 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Duration.MN.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Duration.Types
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.TimeGrain.Types (Grain(..))
corpus :: Corpus
corpus = (testContext {locale = makeLocale MN Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (DurationData 1 Second)
[ "1 сек"
, "1 секунд"
, "секунд"
, "1\""
]
, examples (DurationData 15 Minute)
[ "15 мин"
, "15'"
]
, examples (DurationData 30 Minute)
[ "30 минут"
]
, examples (DurationData 5400 Second)
[ "5400 секунд"
]
, examples (DurationData 8 Hour)
[ "8 цаг"
, "8 ц"
]
, examples (DurationData 15 Day)
[ "15 өдөр"
]
, examples (DurationData 7 Week)
[ "7 долоо хоног"
]
, examples (DurationData 1 Month)
[ "1 сар"
, "сар"
]
, examples (DurationData 6 Month)
[ "6 сар"
]
, examples (DurationData 2 Year)
[ "2 жил"
]
, examples (DurationData 12 Hour)
[ "12 цаг"
]
]

View File

@ -0,0 +1,118 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Duration.MN.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.Duration.Helpers
import Duckling.Numeral.Helpers (numberWith)
import Duckling.Numeral.Types (NumeralData(..), isInteger)
import Duckling.Duration.Types (DurationData (DurationData))
import Duckling.Regex.Types
import Duckling.Types
import Duckling.TimeGrain.Types
import qualified Duckling.Numeral.Types as TNumeral
grainsMap :: HashMap Text Grain
grainsMap = HashMap.fromList
[ ("жил" , Year)
, ("сар", Month)
, ("өдөр" , Day)
, ("цаг" , Hour)
, ("минут", Minute)
]
-- TODO: Single-word composition (#110)
ruleHalves :: Rule
ruleHalves = Rule
{ name = "half of a grain"
, pattern =
[ regex "хагас\\s?(жил|сар|өдөр|цаг|минут)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (x:_)):_) -> do
grain <- HashMap.lookup (Text.toLower x) grainsMap
Token Duration <$> timesOneAndAHalf grain 0
_ -> Nothing
}
ruleNumeralQuotes :: Rule
ruleNumeralQuotes = Rule
{ name = "<integer> + '\""
, pattern =
[ Predicate isNatural
, regex "(['\"])"
]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v}:
Token RegexMatch (GroupMatch (x:_)):
_) -> case x of
"'" -> Just . Token Duration . duration Minute $ floor v
"\"" -> Just . Token Duration . duration Second $ floor v
_ -> Nothing
_ -> Nothing
}
ruleDurationPrecision :: Rule
ruleDurationPrecision = Rule
{ name = "about|exactly <duration>"
, pattern =
[ regex "(ойролцоогоор|яг)"
, dimension Duration
]
, prod = \tokens -> case tokens of
(_:token:_) -> Just token
_ -> Nothing
}
ruleGrainAsDuration :: Rule
ruleGrainAsDuration = Rule
{ name = "a <unit-of-duration>"
, pattern =
[ dimension TimeGrain
]
, prod = \tokens -> case tokens of
(Token TimeGrain grain:_) -> Just . Token Duration $ duration grain 1
_ -> Nothing
}
rulePositiveDuration :: Rule
rulePositiveDuration = Rule
{ name = "<positive-numeral> <time-grain>"
, pattern =
[ numberWith TNumeral.value $ and . sequence [not . isInteger, (>0)]
, dimension TimeGrain
]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v}:
Token TimeGrain grain:
_) -> Just . Token Duration . duration Second . floor $ inSeconds grain v
_ -> Nothing
}
rules :: [Rule]
rules =
[ rulePositiveDuration
, ruleDurationPrecision
, ruleNumeralQuotes
, ruleGrainAsDuration
, ruleHalves
]

View File

@ -60,6 +60,7 @@ data Lang
| KO
| LO
| ML
| MN
| MY
| NB
| NE

View File

@ -0,0 +1,105 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.MN.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Numeral.Types
import Duckling.Resolve
import Duckling.Testing.Types
context :: Context
context = testContext {locale = makeLocale MN Nothing}
corpus :: Corpus
corpus = (context, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (NumeralValue 0)
[ "0"
, "нойл"
, "тэг"
]
, examples (NumeralValue 1)
[ "1"
, "нэг"
]
, examples (NumeralValue 2)
[ "хоёр"
]
, examples (NumeralValue 3)
[ "гурав"
]
, examples (NumeralValue 4)
[ "дөрөв"
]
, examples (NumeralValue 5)
[ "тав"
]
, examples (NumeralValue 6)
[ "зургаа"
]
, examples (NumeralValue 7)
[ "долоо"
]
, examples (NumeralValue 8)
[ "найм"
]
, examples (NumeralValue 9)
[ "ес"
]
, examples (NumeralValue 11)
[ "арван нэг"
]
, examples (NumeralValue 15)
[ "арван тав"
]
, examples (NumeralValue 17)
[ "арван долоо"
]
, examples (NumeralValue 20)
[ "20"
, "хорь"
]
, examples (NumeralValue 22)
[ "хорин хоёр"
]
, examples (NumeralValue 24)
[ "24"
, "хорин дөрөв"
]
, examples (NumeralValue 26)
[ "хорин зургаа"
]
, examples (NumeralValue 28)
[ "хорин найм"
]
, examples (NumeralValue 10)
[ "арав"
]
, examples (NumeralValue 20)
[ "хорь"
]
, examples (NumeralValue 50)
[ "тавь"
]
, examples (NumeralValue 34)
[ "гучин дөрөв"
]
, examples (NumeralValue 99)
[ "ерэн ес"
]
]

View File

@ -0,0 +1,320 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.MN.Rules
( rules
) where
import Data.HashMap.Strict (HashMap)
import Data.Maybe
import Data.Text (Text)
import Prelude
import Data.String
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
ruleNumeralsPrefixWithNegativeOrMinus :: Rule
ruleNumeralsPrefixWithNegativeOrMinus = Rule
{ name = "numbers prefix with -, negative or minus"
, pattern =
[ regex "-|хасах|сөрөг"
, Predicate isPositive
]
, prod = \tokens -> case tokens of
(_:Token Numeral NumeralData{TNumeral.value = v}:_) ->
double $ v * (- 1)
_ -> Nothing
}
ruleFew :: Rule
ruleFew = Rule
{ name = "few"
, pattern =
[ regex "хэдхэн"
]
, prod = \_ -> integer 3
}
ruleTen :: Rule
ruleTen = Rule
{ name = "ten"
, pattern =
[ regex "арав"
]
, prod = \_ -> integer 10 >>= withGrain 1
}
ruleDecimalWithThousandsSeparator :: Rule
ruleDecimalWithThousandsSeparator = Rule
{ name = "decimal with thousands separator"
, pattern =
[ regex "(\\d+(\\.\\d\\d\\d)+\\,\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):
_) -> let fmt = Text.replace "," "." $ Text.replace "." Text.empty match
in parseDouble fmt >>= double
_ -> Nothing
}
-- TODO: Single-word composition (#110)
ruleInteger3 :: Rule
ruleInteger3 = Rule
{ name = "integer ([2-9][1-9])"
, pattern =
[ regex "(хорин|гучин|дөчин|тавин|жаран|далан|наян|ерэн) ?(нэг|хоёр|гурав|дөрөв|тав|зургаа|долоо|найм|ес)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (m1:m2:_)):_) -> do
v1 <- case Text.toLower m1 of
"хорин" -> Just 20
"гучин" -> Just 30
"дөчин" -> Just 40
"тавин" -> Just 50
"жаран" -> Just 60
"далан" -> Just 70
"наян" -> Just 80
"ерэн" -> Just 90
_ -> Nothing
v2 <- case Text.toLower m2 of
"нэг" -> Just 1
"хоёр" -> Just 2
"гурав" -> Just 3
"дөрөв" -> Just 4
"тав" -> Just 5
"зургаа" -> Just 6
"долоо" -> Just 7
"найм" -> Just 8
"ес" -> Just 9
_ -> Nothing
integer $ v1 + v2
_ -> Nothing
}
ruleNumeralsUnd :: Rule
ruleNumeralsUnd = Rule
{ name = "numbers und"
, pattern =
[ oneOf [20, 30 .. 90]
, numberBetween 1 10
]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v1}:
Token Numeral NumeralData{TNumeral.value = v2}:
_) -> double $ v1 + v2
_ -> Nothing
}
ruleMultiply :: Rule
ruleMultiply = Rule
{ name = "compose by multiplication"
, pattern =
[ dimension Numeral
, Predicate isMultipliable
]
, prod = \tokens -> case tokens of
(token1:token2:_) -> multiply token1 token2
_ -> Nothing
}
ruleIntersect :: Rule
ruleIntersect = Rule
{ name = "intersect"
, pattern =
[ Predicate hasGrain
, Predicate $ and . sequence [not . isMultipliable, isPositive]
]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = val1, TNumeral.grain = Just g}:
Token Numeral NumeralData{TNumeral.value = val2}:
_) | (10 ** fromIntegral g) > val2 -> double $ val1 + val2
_ -> Nothing
}
ruleNumeralsSuffixesKMG :: Rule
ruleNumeralsSuffixesKMG = Rule
{ name = "numbers suffixes (K, M, G)"
, pattern =
[ dimension Numeral
, regex "([kmg])(?=[\\W\\$€]|$)"
]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v}:
Token RegexMatch (GroupMatch (match:_)):
_) -> case Text.toLower match of
"k" -> double $ v * 1e3
"m" -> double $ v * 1e6
"g" -> double $ v * 1e9
_ -> Nothing
_ -> Nothing
}
ruleCouple :: Rule
ruleCouple = Rule
{ name = "couple"
, pattern =
[ regex "хос"
]
, prod = \_ -> integer 2
}
rulePowersOfTen :: Rule
rulePowersOfTen = Rule
{ name = "powers of tens"
, pattern =
[ regex "(зуу?|мянга?|сая?)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> case Text.toLower match of
"зуу" -> double 1e2 >>= withGrain 2 >>= withMultipliable
"зуун" -> double 1e2 >>= withGrain 2 >>= withMultipliable
"мянга" -> double 1e3 >>= withGrain 3 >>= withMultipliable
"мянган" -> double 1e3 >>= withGrain 3 >>= withMultipliable
"сая" -> double 1e6 >>= withGrain 6 >>= withMultipliable
"саяын" -> double 1e6 >>= withGrain 6 >>= withMultipliable
_ -> Nothing
_ -> Nothing
}
zeroNineteenMap :: HashMap Text Integer
zeroNineteenMap = HashMap.fromList
[ ("нуль", 0)
, ("тэг", 0)
, ("нойл", 0)
, ("нэг", 1)
, ("ганц", 1)
, ("хоёр", 2)
, ("гурав", 3)
, ("дөрөв", 4)
, ("тав", 5)
, ("зургаа", 6)
, ("долоо", 7)
, ("найм", 8)
, ("ес", 9)
, ("арван", 10)
, ("арав", 10)
, ("арван нэг", 11)
, ("арван хоёр", 12)
, ("арван гурав", 13)
, ("арван дөрөв", 14)
, ("арван тав", 15)
, ("арван зургаа", 16)
, ("арван долоо", 17)
, ("арван найм", 18)
, ("арван ес", 19)
]
-- TODO: Single-word composition (#110)
ruleZeroToNineteen :: Rule
ruleZeroToNineteen = Rule
{ name = "integer (0..19)"
, pattern =
[ regex "(нуль|тэг|нойл|нэг|ганц|хоёр|гурав|дөрөв|тав|зургаа|долоо|найм|ес|арван нэг|арван хоёр|арван гурав|арван дөрөв|арван тав|арван зургаа|арван долоо|арван найм|арван ес|арав|арван)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
HashMap.lookup (Text.toLower match) zeroNineteenMap >>= integer
_ -> Nothing
}
tensMap :: HashMap Text Integer
tensMap = HashMap.fromList
[ ( "хорь" , 20 )
, ( "гуч", 30 )
, ( "дөч" , 40 )
, ( "тавь" , 50 )
, ( "жар" , 60 )
, ( "дал" , 70 )
, ( "ная" , 80 )
, ( "ер" , 90 )
]
-- TODO: Single-word composition (#110)
ruleInteger2 :: Rule
ruleInteger2 = Rule
{ name = "integer (20..90)"
, pattern =
[ regex "(хорь|гуч|дөч|тавь|жар|дал|ная|ер)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
HashMap.lookup (Text.toLower match) tensMap >>= integer
_ -> Nothing
}
ruleNumeralDotNumeral :: Rule
ruleNumeralDotNumeral = Rule
{ name = "number dot number"
, pattern =
[ dimension Numeral
, regex "цэг"
, Predicate $ not . hasGrain
]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v1}:
_:
Token Numeral NumeralData{TNumeral.value = v2}:
_) -> double $ v1 + decimalsToDouble v2
_ -> Nothing
}
ruleDecimalNumeral :: Rule
ruleDecimalNumeral = Rule
{ name = "decimal number"
, pattern =
[ regex "(\\d*\\.\\d+)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> parseDecimal True match
_ -> Nothing
}
ruleIntegerWithThousandsSeparator :: Rule
ruleIntegerWithThousandsSeparator = Rule
{ name = "integer with thousands separator ."
, pattern =
[ regex "(\\d{1,3}(\\.\\d\\d\\d){1,5})"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
parseDouble (Text.replace "." Text.empty match) >>= double
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleCouple
, ruleDecimalNumeral
, ruleDecimalWithThousandsSeparator
, ruleFew
, ruleInteger2
, ruleInteger3
, ruleIntegerWithThousandsSeparator
, ruleIntersect
, ruleMultiply
, ruleNumeralDotNumeral
, ruleNumeralsPrefixWithNegativeOrMinus
, ruleNumeralsSuffixesKMG
, ruleNumeralsUnd
, rulePowersOfTen
, ruleTen
, ruleZeroToNineteen
]

View File

@ -0,0 +1,60 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Ordinal.MN.Corpus
( corpus ) where
import Prelude
import Data.String
import Duckling.Locale
import Duckling.Ordinal.Types
import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale MN Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (OrdinalData 1)
[ "нэг дүгээр"
, "нэг дэх"
, "1-р"
]
, examples (OrdinalData 3)
[ "гурав дахь"
, "гурав дугаар"
, "3-р"
]
, examples (OrdinalData 4)
[ "дөрөв дэх"
, "4-р"
]
, examples (OrdinalData 15)
[ "15-р"
]
, examples (OrdinalData 21)
[ "21-р"
]
, examples (OrdinalData 23)
[ "23-р"
]
, examples (OrdinalData 31)
[ "31-р"
]
, examples (OrdinalData 48)
[
"48-р"
]
, examples (OrdinalData 99)
[ "99-р"
]
]

View File

@ -0,0 +1,140 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Ordinal.MN.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.Numeral.Helpers (parseInt)
import Duckling.Ordinal.Helpers
import Duckling.Regex.Types
import Duckling.Types
ordinalsFirstthMap :: HashMap Text.Text Int
ordinalsFirstthMap = HashMap.fromList
[ ( "нэг", 1 )
, ( "хоёр", 2 )
, ( "гурав", 3 )
, ( "дөрөв", 4 )
, ( "тав", 5 )
, ( "зургаа", 6 )
, ( "долоо", 7 )
, ( "найм", 8 )
, ( "ес", 9 )
, ( "арав", 10 )
]
cardinalsMap :: HashMap Text.Text Int
cardinalsMap = HashMap.fromList
[ ( "арван", 10 )
, ( "хорин", 20 )
, ( "хорь", 20 )
, ( "гучин", 30 )
, ( "гуч", 30 )
, ( "дөчин", 40 )
, ( "дөч", 40 )
, ( "тавин", 50 )
, ( "тавь", 50 )
, ( "жаран", 60 )
, ( "жар", 60 )
, ( "далан", 70 )
, ( "дал", 70 )
, ( "наян", 80 )
, ( "ная", 80 )
, ( "ерэн", 90 )
, ( "ер", 90 )
]
ruleOrdinalsFirstth :: Rule
ruleOrdinalsFirstth = Rule
{ name = "ordinals (first..19th)"
, pattern =
[ regex "(нэг|хоёр|гурав|дөрөв|тав|зургаа|долоо|найм|ес|арав) ?(дугаар|дүгээр|дахь|дэх)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
ordinal <$> HashMap.lookup (Text.toLower match) ordinalsFirstthMap
_ -> Nothing
}
ruleOrdinal :: Rule
ruleOrdinal = Rule
{ name = "ordinal 10..99"
, pattern =
[ regex "(арван|хорин|гучин|дөчин|тавин|жаран|далан|наян|ерэн) ?(нэг|хоёр|гурав|дөрөв|тав|зургаа|долоо|найм|ес) ?(дугаар|дүгээр|дахь|дэх)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (m1:_)):
Token RegexMatch (GroupMatch (m2:_)):
_) -> do
dozen <- HashMap.lookup (Text.toLower m1) cardinalsMap
unit <- HashMap.lookup (Text.toLower m2) ordinalsFirstthMap
Just . ordinal $ dozen + unit
_ -> Nothing
}
-- TODO: Single-word composition (#110)
ruleInteger2 :: Rule
ruleInteger2 = Rule
{ name = "integer (20..90)"
, pattern =
[ regex "(хорь|гуч|дөч|тавь|жар|дал|ная|ер) ?(дугаар|дүгээр|дахь|дэх)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
ordinal <$> HashMap.lookup (Text.toLower match) cardinalsMap
_ -> Nothing
}
ruleOrdinalDigits :: Rule
ruleOrdinalDigits = Rule
{ name = "ordinal (digits)"
, pattern =
[ regex "0*(\\d+)-?(ын|ийн|р|с|)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> ordinal <$> parseInt match
_ -> Nothing
}
ruleOrdinalDigits2 :: Rule
ruleOrdinalDigits2 = Rule
{ name = "ordinal (digits)"
, pattern =
[ regex "(?<!\\d|\\.)0*(\\d+)(\\.(?!\\d)| ?(дугаар|дүгээр|дахь|дэх))"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> do
v <- parseInt match
Just $ ordinal v
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleOrdinalDigits
, ruleOrdinalDigits2
, ruleOrdinal
, ruleInteger2
, ruleOrdinalsFirstth
]

View File

@ -0,0 +1,59 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Quantity.MN.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Quantity.Types
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale MN Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Pound 2 Nothing)
[ "2 фунт"
]
, examples (simple Gram 2 Nothing)
[ "2 грамм"
, "хоёр грамм"
, "2000 миллиграмм"
, "2000 мг"
]
, examples (simple Gram 1000 Nothing)
[ "килограмм"
, "кг"
]
, examples (simple Gram 2000 Nothing)
[ "2 килограмм"
, "2 кг"
, "2000 грамм"
]
, examples (simple Pound 1 Nothing)
[ "фунт"
, "1 фунт"
]
, examples (simple Ounce 2 Nothing)
[ "2 унц"
]
, examples (simple Gram 500 Nothing)
[ "500 грамм"
, "500г"
, "500 г"
, "0.5 кг"
]
]

View File

@ -0,0 +1,63 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Quantity.MN.Rules
( rules
) where
import Data.String
import Data.Text (Text)
import Prelude
import qualified Data.Text as Text
import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers
import Duckling.Quantity.Helpers
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
import qualified Duckling.Quantity.Types as TQuantity
quantities :: [(Text, String, TQuantity.Unit, Double -> Double)]
quantities =
[ ("<quantity> milligrams", "(мг|миллиграмм)", TQuantity.Gram, (/ 1000))
, ("<quantity> grams", "г(рамм?)?", TQuantity.Gram, id)
, ("<quantity> kilograms", "(кг|килограмм?)", TQuantity.Gram, (* 1000))
, ("<quantity> lb", "фунт", TQuantity.Pound, id)
, ("<quantity> oz", "унц", TQuantity.Ounce, id)
]
ruleNumeralQuantities :: [Rule]
ruleNumeralQuantities = map go quantities
where
go :: (Text, String, TQuantity.Unit, Double -> Double) -> Rule
go (name, regexPattern, u, convert) = Rule
{ name = name
, pattern =
[ numberWith TNumeral.value (> 0), regex regexPattern ]
, prod = \tokens -> case tokens of
(Token Numeral nd:_) ->
Just . Token Quantity . quantity u . convert $ TNumeral.value nd
_ -> Nothing
}
ruleAQuantity :: [Rule]
ruleAQuantity = map go quantities
where
go :: (Text, String, TQuantity.Unit, Double -> Double) -> Rule
go (name, regexPattern, u, convert) = Rule
{ name = name
, pattern = [ regex regexPattern ]
, prod = \_ -> Just . Token Quantity . quantity u $ convert 1
}
rules :: [Rule]
rules = ruleNumeralQuantities ++ ruleAQuantity

View File

@ -42,6 +42,7 @@ import qualified Duckling.Ranking.Classifiers.KM_XX as KM_XXClassifiers
import qualified Duckling.Ranking.Classifiers.KO_XX as KO_XXClassifiers
import qualified Duckling.Ranking.Classifiers.LO_XX as LO_XXClassifiers
import qualified Duckling.Ranking.Classifiers.ML_XX as ML_XXClassifiers
import qualified Duckling.Ranking.Classifiers.MN_XX as MN_XXClassifiers
import qualified Duckling.Ranking.Classifiers.MY_XX as MY_XXClassifiers
import qualified Duckling.Ranking.Classifiers.NB_XX as NB_XXClassifiers
import qualified Duckling.Ranking.Classifiers.NE_XX as NE_XXClassifiers
@ -86,6 +87,7 @@ classifiers (Locale KM _) = KM_XXClassifiers.classifiers
classifiers (Locale KO _) = KO_XXClassifiers.classifiers
classifiers (Locale LO _) = LO_XXClassifiers.classifiers
classifiers (Locale ML _) = ML_XXClassifiers.classifiers
classifiers (Locale MN _) = MN_XXClassifiers.classifiers
classifiers (Locale MY _) = MY_XXClassifiers.classifiers
classifiers (Locale NB _) = NB_XXClassifiers.classifiers
classifiers (Locale NE _) = NE_XXClassifiers.classifiers

View File

@ -0,0 +1,22 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
-----------------------------------------------------------------
-- Auto-generated by regenClassifiers
--
-- DO NOT EDIT UNLESS YOU ARE SURE THAT YOU KNOW WHAT YOU ARE DOING
-- @generated
-----------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Ranking.Classifiers.MN_XX (classifiers) where
import Data.String
import Prelude
import qualified Data.HashMap.Strict as HashMap
import Duckling.Ranking.Types
classifiers :: Classifiers
classifiers = HashMap.fromList []

View File

@ -33,6 +33,7 @@ data Region
| IE
| IN
| JM
| MN
| MO
| NL
| NZ

View File

@ -49,6 +49,7 @@ import qualified Duckling.Rules.KM as KMRules
import qualified Duckling.Rules.KO as KORules
import qualified Duckling.Rules.LO as LORules
import qualified Duckling.Rules.ML as MLRules
import qualified Duckling.Rules.MN as MNRules
import qualified Duckling.Rules.MY as MYRules
import qualified Duckling.Rules.NB as NBRules
import qualified Duckling.Rules.NE as NERules
@ -111,6 +112,7 @@ defaultRules KM = KMRules.defaultRules
defaultRules KO = KORules.defaultRules
defaultRules LO = LORules.defaultRules
defaultRules ML = MLRules.defaultRules
defaultRules MN = MNRules.defaultRules
defaultRules MY = MYRules.defaultRules
defaultRules NB = NBRules.defaultRules
defaultRules NE = NERules.defaultRules
@ -153,6 +155,7 @@ localeRules KM = KMRules.localeRules
localeRules KO = KORules.localeRules
localeRules LO = LORules.localeRules
localeRules ML = MLRules.localeRules
localeRules MN = MNRules.localeRules
localeRules MY = MYRules.localeRules
localeRules NB = NBRules.localeRules
localeRules NE = NERules.localeRules
@ -195,6 +198,7 @@ langRules KM = KMRules.langRules
langRules KO = KORules.langRules
langRules LO = LORules.langRules
langRules ML = MLRules.langRules
langRules MN = MNRules.langRules
langRules MY = MYRules.langRules
langRules NB = NBRules.langRules
langRules NE = NERules.langRules

54
Duckling/Rules/MN.hs Normal file
View File

@ -0,0 +1,54 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
module Duckling.Rules.MN
( defaultRules
, langRules
, localeRules
) where
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.AmountOfMoney.MN.Rules as AmountOfMoney
import qualified Duckling.Distance.MN.Rules as Distance
import qualified Duckling.Duration.MN.Rules as Duration
import qualified Duckling.Numeral.MN.Rules as Numeral
import qualified Duckling.Ordinal.MN.Rules as Ordinal
import qualified Duckling.Quantity.MN.Rules as Quantity
import qualified Duckling.TimeGrain.MN.Rules as TimeGrain
import qualified Duckling.Volume.MN.Rules as Volume
import qualified Duckling.Temperature.MN.Rules as Temperature
defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules
localeRules :: Region -> Some Dimension -> [Rule]
localeRules region (This (CustomDimension dim)) = dimLocaleRules region dim
localeRules _ _ = []
langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = AmountOfMoney.rules
langRules (This CreditCardNumber) = []
langRules (This Distance) = Distance.rules
langRules (This Duration) = Duration.rules
langRules (This Email) = []
langRules (This Numeral) = Numeral.rules
langRules (This Ordinal) = Ordinal.rules
langRules (This PhoneNumber) = []
langRules (This Quantity) = Quantity.rules
langRules (This RegexMatch) = []
langRules (This Temperature) = Temperature.rules
langRules (This Time) = []
langRules (This TimeGrain) = TimeGrain.rules
langRules (This Url) = []
langRules (This Volume) = Volume.rules
langRules (This (CustomDimension dim)) = dimLangRules MN dim

View File

@ -0,0 +1,43 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Temperature.MN.Corpus
( corpus
) where
import Prelude
import Data.String
import Duckling.Locale
import Duckling.Resolve
import Duckling.Temperature.Types
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale MN Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Celsius 37)
[ "37°C"
]
, examples (simple Fahrenheit 70)
[ "70°F"
]
, examples (simple Degree 45)
[ "45°"
, "45 хэм"
]
, examples (simple Degree (-2))
[ "-2°"
, "- 2 хэм"
]
]

View File

@ -0,0 +1,134 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Temperature.MN.Rules
( rules ) where
import Prelude
import Data.String
import Duckling.Dimensions.Types
import Duckling.Temperature.Helpers
import Duckling.Temperature.Types (TemperatureData(..))
import qualified Duckling.Temperature.Types as TTemperature
import Duckling.Types
ruleTemperatureDegrees :: Rule
ruleTemperatureDegrees = Rule
{ name = "<latent temp> градус"
, pattern =
[ Predicate $ isValueOnly False
, regex "градус|°|хэм"
]
, prod = \case
(Token Temperature td:_) -> Just . Token Temperature $
withUnit TTemperature.Degree td
_ -> Nothing
}
ruleTemperatureCelsius :: Rule
ruleTemperatureCelsius = Rule
{ name = "<temp> Celsius"
, pattern =
[ Predicate $ isValueOnly True
, regex "c(el[cs]?(ius)?)?\\.?"
]
, prod = \case
(Token Temperature td:_) -> Just . Token Temperature $
withUnit TTemperature.Celsius td
_ -> Nothing
}
ruleTempC :: Rule
ruleTempC = Rule
{ name = "<temp> °C"
, pattern =
[ Predicate $ isValueOnly True
, regex "c"
]
, prod = \tokens -> case tokens of
(Token Temperature td:_) -> Just . Token Temperature $
withUnit TTemperature.Celsius td
_ -> Nothing
}
ruleTemperatureFahrenheit :: Rule
ruleTemperatureFahrenheit = Rule
{ name = "<temp> Fahrenheit"
, pattern =
[ Predicate $ isValueOnly True
, regex "((f(ah?rh?eh?n(h?eit)?)?\\.?)|фарангейт)"
]
, prod = \case
(Token Temperature td:_) -> Just . Token Temperature $
withUnit TTemperature.Fahrenheit td
_ -> Nothing
}
ruleTemperatureBelowZero :: Rule
ruleTemperatureBelowZero = Rule
{ name = "<temp> below zero"
, pattern =
[ Predicate $ isValueOnly True
, regex "тэгээс доош"
]
, prod = \case
(Token Temperature td@TemperatureData {TTemperature.value = Just v}:
_) -> case TTemperature.unit td of
Nothing -> Just . Token Temperature . withUnit TTemperature.Degree $
td {TTemperature.value = Just (- v)}
_ -> Just . Token Temperature $ td {TTemperature.value = Just (- v)}
_ -> Nothing
}
ruleIntervalMax :: Rule
ruleIntervalMax = Rule
{ name = "under/less/lower/no more than <temp>"
, pattern =
[ regex "доогуур|(бага|ихгүй|их биш)"
, Predicate isSimpleTemperature
]
, prod = \case
(_:
Token Temperature TemperatureData{TTemperature.value = Just to,
TTemperature.unit = Just u}:
_) -> Just . Token Temperature . withMax to $ unitOnly u
_ -> Nothing
}
ruleIntervalMin :: Rule
ruleIntervalMin = Rule
{ name = "over/above/at least/more than <temp>"
, pattern =
[ regex "дээгүүр|их|багадаа"
, Predicate isSimpleTemperature
]
, prod = \case
(_:
Token Temperature TemperatureData{TTemperature.value = Just from,
TTemperature.unit = Just u}:
_) -> Just . Token Temperature . withMin from $ unitOnly u
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleTemperatureDegrees
, ruleTemperatureCelsius
, ruleTemperatureFahrenheit
, ruleTemperatureBelowZero
, ruleTempC
, ruleIntervalMin
, ruleIntervalMax
]

View File

@ -0,0 +1,41 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.TimeGrain.MN.Rules
( rules
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.Dimensions.Types
import Duckling.TimeGrain.Types
import Duckling.Types
grains :: [(Text, String, Grain)]
grains = [ ("second (grain) ", "сек(унд)?", Second)
, ("minute (grain)" , "мин(ут)?", Minute)
, ("hour (grain)" , "ц(аг)?", Hour)
, ("day (grain)" , "өдөр?", Day)
, ("week (grain)" , "долоо хоног?", Week)
, ("month (grain)" , "сар?", Month)
, ("quarter (grain)", "улирал?", Quarter)
, ("year (grain)" , "жил?|жил", Year)
]
rules :: [Rule]
rules = map go grains
where
go (name, regexPattern, grain) = Rule
{ name = name
, pattern = [regex regexPattern]
, prod = \_ -> Just $ Token TimeGrain grain
}

View File

@ -0,0 +1,51 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Volume.MN.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.Volume.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale MN Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Millilitre 250)
[ "250 миллилитр"
, "250мл"
, "250 мл"
]
, examples (simple Litre 2)
[ "2 литр"
, "2 л"
, "хоёр литр"
]
, examples (simple Litre 1)
[ "1 литр"
, "нэг литр"
, ""
]
, examples (simple Gallon 3)
[ "3 галлон"
]
, examples (simple Hectolitre 3)
[ "3 гектолитр"
, "3 гл"
, "3гл"
]
]

View File

@ -0,0 +1,52 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Volume.MN.Rules
( rules
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.Dimensions.Types
import Duckling.Types
import Duckling.Regex.Types
import Duckling.Volume.Helpers
import Duckling.Numeral.Helpers (isPositive)
import qualified Duckling.Volume.Types as TVolume
import qualified Duckling.Numeral.Types as TNumeral
volumes :: [(Text, String, TVolume.Unit)]
volumes = [ ("<latent vol> ml" , "мл|миллилитр" , TVolume.Millilitre)
, ("<vol> hectoliters" , "гл|гектолитр" , TVolume.Hectolitre)
, ("<vol> liters" , "л(итр(ийн|ээр)?)?" , TVolume.Litre)
, ("<latent vol> gallon", "галлон" , TVolume.Gallon)
]
rulesVolumes :: [Rule]
rulesVolumes = map go volumes
where
go :: (Text, String, TVolume.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern =
[ regex regexPattern
]
, prod = \_ -> Just . Token Volume $ unitOnly u
}
rules :: [Rule]
rules = [
]
++ rulesVolumes

View File

@ -75,6 +75,7 @@ library
, Duckling.Rules.KO
, Duckling.Rules.LO
, Duckling.Rules.ML
, Duckling.Rules.MN
, Duckling.Rules.MY
, Duckling.Rules.NB
, Duckling.Rules.NE
@ -125,6 +126,7 @@ library
, Duckling.Ranking.Classifiers.KO_XX
, Duckling.Ranking.Classifiers.LO_XX
, Duckling.Ranking.Classifiers.ML_XX
, Duckling.Ranking.Classifiers.MN_XX
, Duckling.Ranking.Classifiers.MY_XX
, Duckling.Ranking.Classifiers.NB_XX
, Duckling.Ranking.Classifiers.NE_XX
@ -177,6 +179,7 @@ library
, Duckling.Dimensions.KO
, Duckling.Dimensions.LO
, Duckling.Dimensions.ML
, Duckling.Dimensions.MN
, Duckling.Dimensions.MY
, Duckling.Dimensions.NB
, Duckling.Dimensions.NE
@ -195,6 +198,8 @@ library
-- AmountOfMoney
, Duckling.AmountOfMoney.AR.Corpus
, Duckling.AmountOfMoney.AR.Rules
, Duckling.AmountOfMoney.BG.Corpus
, Duckling.AmountOfMoney.BG.Rules
, Duckling.AmountOfMoney.EN.AU.Corpus
, Duckling.AmountOfMoney.EN.AU.Rules
, Duckling.AmountOfMoney.EN.BZ.Corpus
@ -221,8 +226,6 @@ library
, Duckling.AmountOfMoney.EN.US.Rules
, Duckling.AmountOfMoney.EN.ZA.Corpus
, Duckling.AmountOfMoney.EN.ZA.Rules
, Duckling.AmountOfMoney.BG.Corpus
, Duckling.AmountOfMoney.BG.Rules
, Duckling.AmountOfMoney.ES.Corpus
, Duckling.AmountOfMoney.ES.Rules
, Duckling.AmountOfMoney.FR.Corpus
@ -237,8 +240,12 @@ library
, Duckling.AmountOfMoney.KA.Rules
, Duckling.AmountOfMoney.KO.Corpus
, Duckling.AmountOfMoney.KO.Rules
, Duckling.AmountOfMoney.MN.Corpus
, Duckling.AmountOfMoney.MN.Rules
, Duckling.AmountOfMoney.NB.Corpus
, Duckling.AmountOfMoney.NB.Rules
, Duckling.AmountOfMoney.NL.Corpus
, Duckling.AmountOfMoney.NL.Rules
, Duckling.AmountOfMoney.PT.Corpus
, Duckling.AmountOfMoney.PT.Rules
, Duckling.AmountOfMoney.RO.Corpus
@ -249,8 +256,6 @@ library
, Duckling.AmountOfMoney.SV.Rules
, Duckling.AmountOfMoney.VI.Corpus
, Duckling.AmountOfMoney.VI.Rules
, Duckling.AmountOfMoney.NL.Corpus
, Duckling.AmountOfMoney.NL.Rules
, Duckling.AmountOfMoney.ZH.Corpus
, Duckling.AmountOfMoney.ZH.Rules
, Duckling.AmountOfMoney.Helpers
@ -276,18 +281,20 @@ library
, Duckling.Distance.KM.Rules
, Duckling.Distance.KO.Corpus
, Duckling.Distance.KO.Rules
, Duckling.Distance.PT.Corpus
, Duckling.Distance.PT.Rules
, Duckling.Distance.MN.Corpus
, Duckling.Distance.MN.Rules
, Duckling.Distance.NL.Corpus
, Duckling.Distance.NL.Rules
, Duckling.Distance.PT.Corpus
, Duckling.Distance.PT.Rules
, Duckling.Distance.RO.Corpus
, Duckling.Distance.RO.Rules
, Duckling.Distance.RU.Corpus
, Duckling.Distance.RU.Rules
, Duckling.Distance.TR.Corpus
, Duckling.Distance.TR.Rules
, Duckling.Distance.SV.Corpus
, Duckling.Distance.SV.Rules
, Duckling.Distance.TR.Corpus
, Duckling.Distance.TR.Rules
, Duckling.Distance.ZH.Corpus
, Duckling.Distance.ZH.Rules
, Duckling.Distance.Helpers
@ -321,6 +328,8 @@ library
, Duckling.Duration.KA.Rules
, Duckling.Duration.KO.Corpus
, Duckling.Duration.KO.Rules
, Duckling.Duration.MN.Corpus
, Duckling.Duration.MN.Rules
, Duckling.Duration.NB.Corpus
, Duckling.Duration.NB.Rules
, Duckling.Duration.NL.Corpus
@ -328,17 +337,17 @@ library
, Duckling.Duration.PL.Corpus
, Duckling.Duration.PL.Rules
, Duckling.Duration.PT.Corpus
, Duckling.Duration.SV.Corpus
, Duckling.Duration.SV.Rules
, Duckling.Duration.ZH.Corpus
, Duckling.Duration.RO.Corpus
, Duckling.Duration.RO.Rules
, Duckling.Duration.RU.Corpus
, Duckling.Duration.RU.Rules
, Duckling.Duration.SV.Corpus
, Duckling.Duration.SV.Rules
, Duckling.Duration.TR.Corpus
, Duckling.Duration.TR.Rules
, Duckling.Duration.UK.Corpus
, Duckling.Duration.UK.Rules
, Duckling.Duration.ZH.Corpus
, Duckling.Duration.Helpers
, Duckling.Duration.Rules
, Duckling.Duration.Types
@ -411,6 +420,8 @@ library
, Duckling.Numeral.LO.Rules
, Duckling.Numeral.ML.Corpus
, Duckling.Numeral.ML.Rules
, Duckling.Numeral.MN.Corpus
, Duckling.Numeral.MN.Rules
, Duckling.Numeral.MY.Corpus
, Duckling.Numeral.MY.Rules
, Duckling.Numeral.NB.Corpus
@ -423,6 +434,8 @@ library
, Duckling.Numeral.PL.Rules
, Duckling.Numeral.PT.Corpus
, Duckling.Numeral.PT.Rules
, Duckling.Numeral.RO.Corpus
, Duckling.Numeral.RO.Rules
, Duckling.Numeral.RU.Corpus
, Duckling.Numeral.RU.Rules
, Duckling.Numeral.SV.Corpus
@ -437,8 +450,6 @@ library
, Duckling.Numeral.VI.Rules
, Duckling.Numeral.ZH.Corpus
, Duckling.Numeral.ZH.Rules
, Duckling.Numeral.RO.Corpus
, Duckling.Numeral.RO.Rules
, Duckling.Numeral.Helpers
, Duckling.Numeral.Rules
, Duckling.Numeral.Types
@ -486,6 +497,8 @@ library
, Duckling.Ordinal.KO.Rules
, Duckling.Ordinal.ML.Corpus
, Duckling.Ordinal.ML.Rules
, Duckling.Ordinal.MN.Corpus
, Duckling.Ordinal.MN.Rules
, Duckling.Ordinal.NB.Corpus
, Duckling.Ordinal.NB.Rules
, Duckling.Ordinal.NL.Corpus
@ -533,6 +546,8 @@ library
, Duckling.Quantity.KM.Rules
, Duckling.Quantity.KO.Corpus
, Duckling.Quantity.KO.Rules
, Duckling.Quantity.MN.Corpus
, Duckling.Quantity.MN.Rules
, Duckling.Quantity.PT.Corpus
, Duckling.Quantity.PT.Rules
, Duckling.Quantity.RO.Corpus
@ -570,6 +585,8 @@ library
, Duckling.Temperature.KM.Rules
, Duckling.Temperature.KO.Corpus
, Duckling.Temperature.KO.Rules
, Duckling.Temperature.MN.Rules
, Duckling.Temperature.MN.Corpus
, Duckling.Temperature.PT.Corpus
, Duckling.Temperature.PT.Rules
, Duckling.Temperature.RO.Corpus
@ -690,6 +707,7 @@ library
, Duckling.TimeGrain.JA.Rules
, Duckling.TimeGrain.KA.Rules
, Duckling.TimeGrain.KO.Rules
, Duckling.TimeGrain.MN.Rules
, Duckling.TimeGrain.NB.Rules
, Duckling.TimeGrain.NL.Rules
, Duckling.TimeGrain.PL.Rules
@ -730,6 +748,8 @@ library
, Duckling.Volume.KO.Rules
, Duckling.Volume.PT.Corpus
, Duckling.Volume.PT.Rules
, Duckling.Volume.MN.Corpus
, Duckling.Volume.MN.Rules
, Duckling.Volume.NL.Corpus
, Duckling.Volume.NL.Rules
, Duckling.Volume.RO.Corpus
@ -800,6 +820,7 @@ test-suite duckling-test
, Duckling.AmountOfMoney.ID.Tests
, Duckling.AmountOfMoney.KA.Tests
, Duckling.AmountOfMoney.KO.Tests
, Duckling.AmountOfMoney.MN.Tests
, Duckling.AmountOfMoney.NB.Tests
, Duckling.AmountOfMoney.PT.Tests
, Duckling.AmountOfMoney.RO.Tests
@ -820,6 +841,7 @@ test-suite duckling-test
, Duckling.Distance.HR.Tests
, Duckling.Distance.KM.Tests
, Duckling.Distance.KO.Tests
, Duckling.Distance.MN.Tests
, Duckling.Distance.NL.Tests
, Duckling.Distance.PT.Tests
, Duckling.Distance.RO.Tests
@ -841,6 +863,7 @@ test-suite duckling-test
, Duckling.Duration.JA.Tests
, Duckling.Duration.KA.Tests
, Duckling.Duration.KO.Tests
, Duckling.Duration.MN.Tests
, Duckling.Duration.NB.Tests
, Duckling.Duration.NL.Tests
, Duckling.Duration.PL.Tests
@ -886,6 +909,7 @@ test-suite duckling-test
, Duckling.Numeral.KO.Tests
, Duckling.Numeral.LO.Tests
, Duckling.Numeral.ML.Tests
, Duckling.Numeral.MN.Tests
, Duckling.Numeral.MY.Tests
, Duckling.Numeral.NB.Tests
, Duckling.Numeral.NE.Tests
@ -923,6 +947,7 @@ test-suite duckling-test
, Duckling.Ordinal.KA.Tests
, Duckling.Ordinal.KM.Tests
, Duckling.Ordinal.KO.Tests
, Duckling.Ordinal.MN.Tests
, Duckling.Ordinal.ML.Tests
, Duckling.Ordinal.NB.Tests
, Duckling.Ordinal.NL.Tests
@ -949,6 +974,7 @@ test-suite duckling-test
, Duckling.Quantity.HR.Tests
, Duckling.Quantity.KM.Tests
, Duckling.Quantity.KO.Tests
, Duckling.Quantity.MN.Tests
, Duckling.Quantity.PT.Tests
, Duckling.Quantity.RO.Tests
, Duckling.Quantity.RU.Tests
@ -965,6 +991,7 @@ test-suite duckling-test
, Duckling.Temperature.HR.Tests
, Duckling.Temperature.IT.Tests
, Duckling.Temperature.JA.Tests
, Duckling.Temperature.MN.Tests
, Duckling.Temperature.KM.Tests
, Duckling.Temperature.KO.Tests
, Duckling.Temperature.PT.Tests
@ -1013,6 +1040,7 @@ test-suite duckling-test
, Duckling.Volume.KM.Tests
, Duckling.Volume.KO.Tests
, Duckling.Volume.PT.Tests
, Duckling.Volume.MN.Tests
, Duckling.Volume.NL.Tests
, Duckling.Volume.RO.Tests
, Duckling.Volume.RU.Tests

View File

@ -196,6 +196,7 @@ getCorpusForLang KM = (testContext, testOptions, [])
getCorpusForLang KO = KOTime.corpus
getCorpusForLang LO = (testContext, testOptions, [])
getCorpusForLang ML = (testContext, testOptions, [])
getCorpusForLang MN = (testContext, testOptions, [])
getCorpusForLang MY = (testContext, testOptions, [])
getCorpusForLang NB = NBTime.corpus
getCorpusForLang NE = (testContext, testOptions, [])

View File

@ -0,0 +1,23 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.AmountOfMoney.MN.Tests
( tests ) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.AmountOfMoney.MN.Corpus
import Duckling.Dimensions.Types
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "MN Tests"
[ makeCorpusTest [This AmountOfMoney] corpus
]

View File

@ -24,6 +24,7 @@ import qualified Duckling.AmountOfMoney.HR.Tests as HR
import qualified Duckling.AmountOfMoney.ID.Tests as ID
import qualified Duckling.AmountOfMoney.KA.Tests as KA
import qualified Duckling.AmountOfMoney.KO.Tests as KO
import qualified Duckling.AmountOfMoney.MN.Tests as MN
import qualified Duckling.AmountOfMoney.NB.Tests as NB
import qualified Duckling.AmountOfMoney.NL.Tests as NL
import qualified Duckling.AmountOfMoney.PT.Tests as PT
@ -45,6 +46,7 @@ tests = testGroup "AmountOfMoney Tests"
, ID.tests
, KA.tests
, KO.tests
, MN.tests
, NB.tests
, NL.tests
, PT.tests

View File

@ -0,0 +1,23 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Distance.MN.Tests
( tests ) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Distance.MN.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "MN Tests"
[ makeCorpusTest [This Distance] corpus
]

View File

@ -23,6 +23,7 @@ import qualified Duckling.Distance.GA.Tests as GA
import qualified Duckling.Distance.HR.Tests as HR
import qualified Duckling.Distance.KM.Tests as KM
import qualified Duckling.Distance.KO.Tests as KO
import qualified Duckling.Distance.MN.Tests as MN
import qualified Duckling.Distance.NL.Tests as NL
import qualified Duckling.Distance.PT.Tests as PT
import qualified Duckling.Distance.RO.Tests as RO
@ -42,6 +43,7 @@ tests = testGroup "Distance Tests"
, HR.tests
, KM.tests
, KO.tests
, MN.tests
, NL.tests
, PT.tests
, RO.tests

View File

@ -0,0 +1,24 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Duration.MN.Tests
( tests
) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Duration.MN.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "MN Tests"
[ makeCorpusTest [This Duration] corpus
]

View File

@ -25,6 +25,7 @@ import qualified Duckling.Duration.HU.Tests as HU
import qualified Duckling.Duration.JA.Tests as JA
import qualified Duckling.Duration.KA.Tests as KA
import qualified Duckling.Duration.KO.Tests as KO
import qualified Duckling.Duration.MN.Tests as MN
import qualified Duckling.Duration.NB.Tests as NB
import qualified Duckling.Duration.NL.Tests as NL
import qualified Duckling.Duration.PL.Tests as PL
@ -49,6 +50,7 @@ tests = testGroup "Duration Tests"
, JA.tests
, KA.tests
, KO.tests
, MN.tests
, NB.tests
, NL.tests
, PL.tests

View File

@ -0,0 +1,22 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Numeral.MN.Tests
( tests ) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Numeral.MN.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "MN Tests"
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -38,6 +38,7 @@ import qualified Duckling.Numeral.KM.Tests as KM
import qualified Duckling.Numeral.KO.Tests as KO
import qualified Duckling.Numeral.LO.Tests as LO
import qualified Duckling.Numeral.ML.Tests as ML
import qualified Duckling.Numeral.MN.Tests as MN
import qualified Duckling.Numeral.MY.Tests as MY
import qualified Duckling.Numeral.NB.Tests as NB
import qualified Duckling.Numeral.NE.Tests as NE
@ -81,6 +82,7 @@ tests = testGroup "Numeral Tests"
, KO.tests
, LO.tests
, ML.tests
, MN.tests
, MY.tests
, NB.tests
, NE.tests

View File

@ -0,0 +1,23 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Ordinal.MN.Tests
( tests ) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Ordinal.MN.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "MN Tests"
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -32,6 +32,7 @@ import qualified Duckling.Ordinal.JA.Tests as JA
import qualified Duckling.Ordinal.KA.Tests as KA
import qualified Duckling.Ordinal.KM.Tests as KM
import qualified Duckling.Ordinal.KO.Tests as KO
import qualified Duckling.Ordinal.MN.Tests as MN
import qualified Duckling.Ordinal.ML.Tests as ML
import qualified Duckling.Ordinal.NB.Tests as NB
import qualified Duckling.Ordinal.NL.Tests as NL
@ -68,6 +69,7 @@ tests = testGroup "Ordinal Tests"
, KA.tests
, KM.tests
, KO.tests
, MN.tests
, ML.tests
, NB.tests
, NL.tests

View File

@ -0,0 +1,24 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Quantity.MN.Tests
( tests
) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Quantity.MN.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "MN Tests"
[ makeCorpusTest [This Quantity] corpus
]

View File

@ -20,6 +20,7 @@ import qualified Duckling.Quantity.FR.Tests as FR
import qualified Duckling.Quantity.HR.Tests as HR
import qualified Duckling.Quantity.KM.Tests as KM
import qualified Duckling.Quantity.KO.Tests as KO
import qualified Duckling.Quantity.MN.Tests as MN
import qualified Duckling.Quantity.PT.Tests as PT
import qualified Duckling.Quantity.RO.Tests as RO
import qualified Duckling.Quantity.RU.Tests as RU
@ -33,6 +34,7 @@ tests = testGroup "Quantity Tests"
, HR.tests
, KM.tests
, KO.tests
, MN.tests
, PT.tests
, RO.tests
, RU.tests

View File

@ -0,0 +1,23 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Temperature.MN.Tests
( tests ) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Temperature.MN.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "MN Tests"
[ makeCorpusTest [This Temperature] corpus
]

View File

@ -23,6 +23,7 @@ import qualified Duckling.Temperature.IT.Tests as IT
import qualified Duckling.Temperature.JA.Tests as JA
import qualified Duckling.Temperature.KM.Tests as KM
import qualified Duckling.Temperature.KO.Tests as KO
import qualified Duckling.Temperature.MN.Tests as MN
import qualified Duckling.Temperature.PT.Tests as PT
import qualified Duckling.Temperature.RO.Tests as RO
import qualified Duckling.Temperature.TR.Tests as TR
@ -41,6 +42,7 @@ tests = testGroup "Temperature Tests"
, JA.tests
, KM.tests
, KO.tests
, MN.tests
, PT.tests
, RO.tests
, TR.tests

View File

@ -0,0 +1,23 @@
-- 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. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.
module Duckling.Volume.MN.Tests
( tests ) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Testing.Asserts
import Duckling.Volume.MN.Corpus
tests :: TestTree
tests = testGroup "MN Tests"
[ makeCorpusTest [This Volume] corpus
]

View File

@ -23,6 +23,7 @@ import qualified Duckling.Volume.HR.Tests as HR
import qualified Duckling.Volume.IT.Tests as IT
import qualified Duckling.Volume.KM.Tests as KM
import qualified Duckling.Volume.KO.Tests as KO
import qualified Duckling.Volume.MN.Tests as MN
import qualified Duckling.Volume.NL.Tests as NL
import qualified Duckling.Volume.PT.Tests as PT
import qualified Duckling.Volume.RO.Tests as RO
@ -40,6 +41,7 @@ tests = testGroup "Volume Tests"
, IT.tests
, KM.tests
, KO.tests
, MN.tests
, NL.tests
, PT.tests
, RO.tests