mirror of
https://github.com/facebook/duckling.git
synced 2024-11-24 15:43:20 +03:00
Support malayalam ordinals
Summary: Add support for malayalam ordinals. Reviewed By: patapizza Differential Revision: D10097075 fbshipit-source-id: 90be5f05d1f9cf4cc6558a4583c8c72518fe0ab0
This commit is contained in:
parent
c46dbb0d92
commit
e349942541
@ -14,5 +14,6 @@ import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ This Numeral
|
||||
[ This Numeral,
|
||||
This Ordinal
|
||||
]
|
||||
|
119
Duckling/Ordinal/ML/Corpus.hs
Normal file
119
Duckling/Ordinal/ML/Corpus.hs
Normal file
@ -0,0 +1,119 @@
|
||||
-- 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.ML.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Locale
|
||||
import Duckling.Ordinal.Types
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
|
||||
context :: Context
|
||||
context = testContext {locale = makeLocale ML Nothing}
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (context, testOptions, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (OrdinalData 1)
|
||||
[ "ഒന്നാം"
|
||||
, "1."
|
||||
]
|
||||
, examples (OrdinalData 2)
|
||||
[ "രണ്ടാം"
|
||||
, "2."
|
||||
]
|
||||
, examples (OrdinalData 3)
|
||||
[ "മൂന്നാം"
|
||||
, "3."
|
||||
]
|
||||
, examples (OrdinalData 4)
|
||||
[ "നാലാം"
|
||||
, "4."
|
||||
]
|
||||
, examples (OrdinalData 5)
|
||||
[ "അഞ്ചാം"
|
||||
, "5."
|
||||
]
|
||||
, examples (OrdinalData 6)
|
||||
[ "ആറാം"
|
||||
, "6."
|
||||
]
|
||||
, examples (OrdinalData 7)
|
||||
[ "ഏഴാം"
|
||||
, "7."
|
||||
]
|
||||
, examples (OrdinalData 8)
|
||||
[ "എട്ടാം"
|
||||
, "8."
|
||||
]
|
||||
, examples (OrdinalData 9)
|
||||
[ "ഒമ്പതാം"
|
||||
, "9."
|
||||
]
|
||||
, examples (OrdinalData 10)
|
||||
[ "പത്താം"
|
||||
, "10."
|
||||
]
|
||||
, examples (OrdinalData 11)
|
||||
[ "പതിനൊന്നാം"
|
||||
, "11."
|
||||
]
|
||||
, examples (OrdinalData 12)
|
||||
[ "പന്ത്രണ്ടാം"
|
||||
, "12."
|
||||
]
|
||||
, examples (OrdinalData 20)
|
||||
[ "ഇരുപതാം"
|
||||
, "20."
|
||||
]
|
||||
, examples (OrdinalData 22)
|
||||
[ "ഇരുപത്തിരണ്ടാം"
|
||||
, "22."
|
||||
]
|
||||
, examples (OrdinalData 26)
|
||||
[ "ഇരുപത്തിആറാം"
|
||||
, "26."
|
||||
]
|
||||
, examples (OrdinalData 30)
|
||||
[ "മുപ്പത്തഞ്ചാം"
|
||||
, "30."
|
||||
]
|
||||
, examples (OrdinalData 33)
|
||||
[ "മുപ്പത്തിമൂന്നാം"
|
||||
, "33."
|
||||
]
|
||||
, examples (OrdinalData 50)
|
||||
[ "അമ്പതാം"
|
||||
, "50."
|
||||
]
|
||||
, examples (OrdinalData 54)
|
||||
[ "അമ്പത്തിനാലാം"
|
||||
, "54."
|
||||
]
|
||||
, examples (OrdinalData 65)
|
||||
[ "അറുപത്തിഅഞ്ചാം"
|
||||
, "65."
|
||||
]
|
||||
, examples (OrdinalData 76)
|
||||
[ "എഴുപത്തിആറാം"
|
||||
, "76."
|
||||
]
|
||||
, examples (OrdinalData 87)
|
||||
[ "എൺപത്തിഏഴാം"
|
||||
, "87."
|
||||
]
|
||||
]
|
137
Duckling/Ordinal/ML/Rules.hs
Normal file
137
Duckling/Ordinal/ML/Rules.hs
Normal file
@ -0,0 +1,137 @@
|
||||
-- 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 #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE NoRebindableSyntax #-}
|
||||
|
||||
module Duckling.Ordinal.ML.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
|
||||
|
||||
oneToNineteenMap :: HashMap Text Int
|
||||
oneToNineteenMap = HashMap.fromList
|
||||
[ ( "ഒന്നാം", 1 )
|
||||
, ( "രണ്ടാം", 2 )
|
||||
, ( "മൂന്നാം", 3 )
|
||||
, ( "നാലാം", 4 )
|
||||
, ( "അഞ്ചാം", 5 )
|
||||
, ( "ആറാം", 6 )
|
||||
, ( "ഏഴാം", 7 )
|
||||
, ( "എട്ടാം", 8 )
|
||||
, ( "ഒമ്പതാം", 9 )
|
||||
, ( "പത്താം", 10 )
|
||||
, ( "പതിനൊന്നാം", 11 )
|
||||
, ( "പന്ത്രണ്ടാം", 12 )
|
||||
, ( "പതിമൂന്നാം", 13 )
|
||||
, ( "പതിനാലാം", 14 )
|
||||
, ( "പതിനഞ്ചാം", 15 )
|
||||
, ( "പതിനാറാം", 16 )
|
||||
, ( "പതിനേഴാം", 17 )
|
||||
, ( "പതിനെട്ടാം", 18 )
|
||||
, ( "പത്തൊൻപതാം", 19 )
|
||||
]
|
||||
|
||||
ruleOneToNineteen :: Rule
|
||||
ruleOneToNineteen = Rule
|
||||
{ name = "integer (1..19)"
|
||||
, pattern =
|
||||
[ regex "(ഒന്നാം|രണ്ടാം|മൂന്നാം|നാലാം|അഞ്ചാം|ആറാം|ഏഴാം|എട്ടാം|ഒമ്പതാം|പത്താം|പതിനൊന്നാം|പന്ത്രണ്ടാം|പതിമൂന്നാം|പതിനാലാം|പതിനഞ്ചാം|പതിനാറാം|പതിനേഴാം|പതിനെട്ടാം|പത്തൊൻപതാം)"
|
||||
]
|
||||
, prod = \case
|
||||
(Token RegexMatch (GroupMatch (match:_)):_) ->
|
||||
ordinal <$> HashMap.lookup (Text.toLower match) oneToNineteenMap
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
tensMap :: HashMap Text Int
|
||||
tensMap = HashMap.fromList
|
||||
[ ( "ഇരുപതാം", 20 )
|
||||
, ( "മുപ്പത്തഞ്ചാം", 30 )
|
||||
, ( "നാല്പതാം", 40 )
|
||||
, ( "അമ്പതാം", 50 )
|
||||
, ( "അറുപതാം", 60 )
|
||||
, ( "എഴുപത്താം", 70 )
|
||||
, ( "എൺപത്താം", 80 )
|
||||
, ( "തൊണ്ണൂറാം", 90 )
|
||||
]
|
||||
|
||||
ruleTens :: Rule
|
||||
ruleTens = Rule
|
||||
{ name = "integer (20..90)"
|
||||
, pattern =
|
||||
[ regex "(ഇരുപതാം|മുപ്പത്തഞ്ചാം|നാല്പതാം|അമ്പതാം|അറുപതാം|എഴുപത്താം|എൺപത്താം|തൊണ്ണൂറാം)"
|
||||
]
|
||||
, prod = \case
|
||||
(Token RegexMatch (GroupMatch (match:_)):_) ->
|
||||
ordinal <$> HashMap.lookup (Text.toLower match) tensMap
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
tensOrdinalMap :: HashMap Text Int
|
||||
tensOrdinalMap = HashMap.fromList
|
||||
[ ( "ഇരുപത്തി", 20 )
|
||||
, ( "മുപ്പത്തി", 30 )
|
||||
, ( "നാല്പത്തി", 40 )
|
||||
, ( "അമ്പത്തി", 50 )
|
||||
, ( "അറുപത്തി", 60 )
|
||||
, ( "എഴുപത്തി", 70 )
|
||||
, ( "എൺപത്തി", 80 )
|
||||
, ( "തൊണ്ണൂറ്റി", 90 )
|
||||
]
|
||||
|
||||
oneToNineMap :: HashMap Text Int
|
||||
oneToNineMap = HashMap.filterWithKey (\_ v -> v <= 9) oneToNineteenMap
|
||||
|
||||
|
||||
ruleCompositeTens :: Rule
|
||||
ruleCompositeTens = Rule
|
||||
{ name = "integer ([2-9][1-9])"
|
||||
, pattern =
|
||||
[ regex "(ഇരുപത്തി|മുപ്പത്തി|നാല്പത്തി|അമ്പത്തി|അറുപത്തി|എഴുപത്തി|എൺപത്തി|തൊണ്ണൂറ്റി)(ആദ്യം|രണ്ടാം|മൂന്നാം|നാലാം|അഞ്ചാം|ആറാം|ഏഴാം|എട്ടാം|ഒമ്പത)"
|
||||
]
|
||||
, prod = \case
|
||||
(Token RegexMatch (GroupMatch (m1:m2:_)):_) -> do
|
||||
v1 <- HashMap.lookup (Text.toLower m1) tensOrdinalMap
|
||||
v2 <- HashMap.lookup (Text.toLower m2) oneToNineMap
|
||||
Just $ ordinal (v1 + v2)
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleOrdinalDigits :: Rule
|
||||
ruleOrdinalDigits = Rule
|
||||
{ name = "ordinal (digits)"
|
||||
, pattern =
|
||||
[ regex "0*(\\d+)\\."
|
||||
]
|
||||
, prod = \case
|
||||
( Token RegexMatch (GroupMatch (match :_)) : _)
|
||||
-> ordinal <$> parseInt match
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleOrdinalDigits
|
||||
, ruleOneToNineteen
|
||||
, ruleTens
|
||||
, ruleCompositeTens
|
||||
]
|
@ -19,6 +19,7 @@ import Duckling.Dimensions.Types
|
||||
import Duckling.Locale
|
||||
import Duckling.Types
|
||||
import qualified Duckling.Numeral.ML.Rules as Numeral
|
||||
import qualified Duckling.Ordinal.ML.Rules as Ordinal
|
||||
|
||||
defaultRules :: Some Dimension -> [Rule]
|
||||
defaultRules = langRules
|
||||
@ -33,7 +34,7 @@ langRules (This Distance) = []
|
||||
langRules (This Duration) = []
|
||||
langRules (This Email) = []
|
||||
langRules (This Numeral) = Numeral.rules
|
||||
langRules (This Ordinal) = []
|
||||
langRules (This Ordinal) = Ordinal.rules
|
||||
langRules (This PhoneNumber) = []
|
||||
langRules (This Quantity) = []
|
||||
langRules (This RegexMatch) = []
|
||||
|
@ -468,6 +468,8 @@ library
|
||||
, Duckling.Ordinal.KM.Rules
|
||||
, Duckling.Ordinal.KO.Corpus
|
||||
, Duckling.Ordinal.KO.Rules
|
||||
, Duckling.Ordinal.ML.Corpus
|
||||
, Duckling.Ordinal.ML.Rules
|
||||
, Duckling.Ordinal.NB.Corpus
|
||||
, Duckling.Ordinal.NB.Rules
|
||||
, Duckling.Ordinal.NL.Corpus
|
||||
@ -892,6 +894,7 @@ test-suite duckling-test
|
||||
, Duckling.Ordinal.KA.Tests
|
||||
, Duckling.Ordinal.KM.Tests
|
||||
, Duckling.Ordinal.KO.Tests
|
||||
, Duckling.Ordinal.ML.Tests
|
||||
, Duckling.Ordinal.NB.Tests
|
||||
, Duckling.Ordinal.NL.Tests
|
||||
, Duckling.Ordinal.PL.Tests
|
||||
|
23
tests/Duckling/Ordinal/ML/Tests.hs
Normal file
23
tests/Duckling/Ordinal/ML/Tests.hs
Normal 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.ML.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Ordinal.ML.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "ML Tests"
|
||||
[ makeCorpusTest [This Ordinal] corpus
|
||||
]
|
@ -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.ML.Tests as ML
|
||||
import qualified Duckling.Ordinal.NB.Tests as NB
|
||||
import qualified Duckling.Ordinal.NL.Tests as NL
|
||||
import qualified Duckling.Ordinal.PL.Tests as PL
|
||||
@ -67,6 +68,7 @@ tests = testGroup "Ordinal Tests"
|
||||
, KA.tests
|
||||
, KM.tests
|
||||
, KO.tests
|
||||
, ML.tests
|
||||
, NB.tests
|
||||
, NL.tests
|
||||
, PL.tests
|
||||
|
Loading…
Reference in New Issue
Block a user