mirror of
https://github.com/facebook/duckling.git
synced 2024-11-30 23:33:33 +03:00
Added HU Ordinals
Summary: Closes https://github.com/facebookincubator/duckling/pull/82 Reviewed By: JonCoens Differential Revision: D5631927 Pulled By: patapizza fbshipit-source-id: d68b238
This commit is contained in:
parent
98b58647b1
commit
5cad4359e2
@ -15,4 +15,5 @@ import Duckling.Dimensions.Types
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ This Numeral
|
||||
, This Ordinal
|
||||
]
|
||||
|
67
Duckling/Ordinal/HU/Corpus.hs
Normal file
67
Duckling/Ordinal/HU/Corpus.hs
Normal file
@ -0,0 +1,67 @@
|
||||
-- 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.HU.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Lang
|
||||
import Duckling.Ordinal.Types
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = HU}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (OrdinalData 1)
|
||||
[ "első"
|
||||
, "1."
|
||||
]
|
||||
, examples (OrdinalData 2)
|
||||
[ "második"
|
||||
, "2."
|
||||
]
|
||||
, examples (OrdinalData 3)
|
||||
[ "harmadik"
|
||||
, "3."
|
||||
]
|
||||
, examples (OrdinalData 4)
|
||||
[ "negyedik"
|
||||
, "4."
|
||||
]
|
||||
, examples (OrdinalData 8)
|
||||
[ "nyolcadik"
|
||||
, "8."
|
||||
]
|
||||
, examples (OrdinalData 25)
|
||||
[ "huszonötödik"
|
||||
, "25."
|
||||
]
|
||||
, examples (OrdinalData 31)
|
||||
[ "harmincegyedik"
|
||||
, "31."
|
||||
]
|
||||
, examples (OrdinalData 42)
|
||||
[ "negyvenkettedik"
|
||||
, "42."
|
||||
]
|
||||
, examples (OrdinalData 77)
|
||||
[ "hetvenhetedik"
|
||||
, "77."
|
||||
]
|
||||
, examples (OrdinalData 90)
|
||||
[ "kilencvenedik"
|
||||
, "90."
|
||||
]
|
||||
]
|
119
Duckling/Ordinal/HU/Rules.hs
Normal file
119
Duckling/Ordinal/HU/Rules.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 GADTs #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Duckling.Ordinal.HU.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
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
|
||||
|
||||
ordinalsMap :: HashMap Text Int
|
||||
ordinalsMap = HashMap.fromList
|
||||
[ ( "első", 1 )
|
||||
, ( "második", 2 )
|
||||
, ( "harmadik", 3 )
|
||||
, ( "negyedik", 4 )
|
||||
, ( "ötödik", 5 )
|
||||
, ( "hatodik", 6 )
|
||||
, ( "hetedik", 7 )
|
||||
, ( "nyolcadik", 8 )
|
||||
, ( "kilencedik", 9 )
|
||||
, ( "tizedik", 10 )
|
||||
, ( "huszadik", 20 )
|
||||
, ( "harmincadik", 30 )
|
||||
, ( "negyvenedik", 40 )
|
||||
, ( "ötvenedik", 50 )
|
||||
, ( "hatvanadik", 60 )
|
||||
, ( "hetvenedik", 70 )
|
||||
, ( "nyolcvanadik", 80 )
|
||||
, ( "kilencvenedik", 90 )
|
||||
]
|
||||
|
||||
ordinalsMap2 :: HashMap Text Int
|
||||
ordinalsMap2 = HashMap.fromList
|
||||
[ ( "egyedik", 1 )
|
||||
, ( "kettedik", 2 )
|
||||
, ( "harmadik", 3 )
|
||||
, ( "negyedik", 4 )
|
||||
, ( "ötödik", 5 )
|
||||
, ( "hatodik", 6 )
|
||||
, ( "hetedik", 7 )
|
||||
, ( "nyolcadik", 8 )
|
||||
, ( "kilencedik", 9 )
|
||||
]
|
||||
|
||||
cardinalsMap :: HashMap Text Int
|
||||
cardinalsMap = HashMap.fromList
|
||||
[ ( "tizen", 10 )
|
||||
, ( "huszon", 20 )
|
||||
, ( "harminc", 30 )
|
||||
, ( "negyven", 40 )
|
||||
, ( "ötven", 50 )
|
||||
, ( "hatvan", 60 )
|
||||
, ( "hetven", 70 )
|
||||
, ( "nyolcvan", 80 )
|
||||
, ( "kilencven", 90 )
|
||||
]
|
||||
|
||||
ruleOrdinals :: Rule
|
||||
ruleOrdinals = Rule
|
||||
{ name = "ordinals (first..twentieth,thirtieth,...)"
|
||||
, pattern =
|
||||
[ regex "(első|második|harmadik|negyedik|ötödik|hatodik|hetedik|nyolcadik|kilencedik|tizedik|huszadik|harmincadik|negyvenedik|ötvenedik|hatvanadik|hetvenedik|nyolcvanadik|kilencvenedik)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (match:_)):_) ->
|
||||
ordinal <$> HashMap.lookup (Text.toLower match) ordinalsMap
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleCompositeOrdinals :: Rule
|
||||
ruleCompositeOrdinals = Rule
|
||||
{ name = "ordinals (composite, e.g., eighty-seven)"
|
||||
, pattern =
|
||||
[ regex "(tizen|huszon|harminc|negyven|ötven|hatvan|hetven|nyolcvan|kilencven)\\-?(egyedik|kettedik|harmadik|negyedik|ötödik|hatodik|hetedik|nyolcadik|kilencedik)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (tens:units:_)):_) -> do
|
||||
tt <- HashMap.lookup (Text.toLower tens) cardinalsMap
|
||||
uu <- HashMap.lookup (Text.toLower units) ordinalsMap2
|
||||
Just . ordinal $ tt + uu
|
||||
_ -> 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
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleOrdinals
|
||||
, ruleCompositeOrdinals
|
||||
, ruleOrdinalDigits
|
||||
]
|
@ -16,6 +16,7 @@ module Duckling.Rules.HU
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Types
|
||||
import qualified Duckling.Numeral.HU.Rules as Numeral
|
||||
import qualified Duckling.Ordinal.HU.Rules as Ordinal
|
||||
|
||||
rules :: Some Dimension -> [Rule]
|
||||
rules (This Distance) = []
|
||||
@ -23,7 +24,7 @@ rules (This Duration) = []
|
||||
rules (This Numeral) = Numeral.rules
|
||||
rules (This Email) = []
|
||||
rules (This AmountOfMoney) = []
|
||||
rules (This Ordinal) = []
|
||||
rules (This Ordinal) = Ordinal.rules
|
||||
rules (This PhoneNumber) = []
|
||||
rules (This Quantity) = []
|
||||
rules (This RegexMatch) = []
|
||||
|
@ -323,6 +323,8 @@ library
|
||||
, Duckling.Ordinal.HE.Rules
|
||||
, Duckling.Ordinal.HR.Corpus
|
||||
, Duckling.Ordinal.HR.Rules
|
||||
, Duckling.Ordinal.HU.Corpus
|
||||
, Duckling.Ordinal.HU.Rules
|
||||
, Duckling.Ordinal.ID.Corpus
|
||||
, Duckling.Ordinal.ID.Rules
|
||||
, Duckling.Ordinal.IT.Corpus
|
||||
@ -641,6 +643,7 @@ test-suite duckling-test
|
||||
, Duckling.Ordinal.GA.Tests
|
||||
, Duckling.Ordinal.HE.Tests
|
||||
, Duckling.Ordinal.HR.Tests
|
||||
, Duckling.Ordinal.HU.Tests
|
||||
, Duckling.Ordinal.ID.Tests
|
||||
, Duckling.Ordinal.IT.Tests
|
||||
, Duckling.Ordinal.JA.Tests
|
||||
|
24
tests/Duckling/Ordinal/HU/Tests.hs
Normal file
24
tests/Duckling/Ordinal/HU/Tests.hs
Normal 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.Ordinal.HU.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Ordinal.HU.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "HU Tests"
|
||||
[ makeCorpusTest [This Ordinal] corpus
|
||||
]
|
@ -21,6 +21,7 @@ import qualified Duckling.Ordinal.FR.Tests as FR
|
||||
import qualified Duckling.Ordinal.GA.Tests as GA
|
||||
import qualified Duckling.Ordinal.HE.Tests as HE
|
||||
import qualified Duckling.Ordinal.HR.Tests as HR
|
||||
import qualified Duckling.Ordinal.HU.Tests as HU
|
||||
import qualified Duckling.Ordinal.ID.Tests as ID
|
||||
import qualified Duckling.Ordinal.IT.Tests as IT
|
||||
import qualified Duckling.Ordinal.JA.Tests as JA
|
||||
@ -48,6 +49,7 @@ tests = testGroup "Ordinal Tests"
|
||||
, GA.tests
|
||||
, HE.tests
|
||||
, HR.tests
|
||||
, HU.tests
|
||||
, ID.tests
|
||||
, IT.tests
|
||||
, JA.tests
|
||||
|
Loading…
Reference in New Issue
Block a user