Support Greek ordinals

Summary: Adding support for Greek ordinals

Reviewed By: patapizza

Differential Revision: D6263781

fbshipit-source-id: ff339ee51e4e8ad6b0c8f3fa75f5652391dbe48e
This commit is contained in:
Panagiotis Vekris 2017-11-08 10:57:57 -08:00 committed by Facebook Github Bot
parent 5d2c5c78ba
commit 536f2844e3
9 changed files with 226 additions and 3 deletions

View File

@ -16,4 +16,5 @@ allDimensions :: [Some Dimension]
allDimensions =
[ This Duration
, This Numeral
, This Ordinal
]

View File

@ -22,11 +22,14 @@ import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.TimeGrain.Types (Grain(..))
context :: Context
context = testContext {locale = makeLocale EL Nothing}
corpus :: Corpus
corpus = (testContext {locale = makeLocale EL Nothing}, allExamples)
corpus = (context, allExamples)
negativeCorpus :: NegativeCorpus
negativeCorpus = (testContext, examples)
negativeCorpus = (context, examples)
where
examples =
[ "για μήνες"

View File

@ -0,0 +1,72 @@
-- 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.EL.Corpus
( corpus ) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Ordinal.Types
import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale EL Nothing}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (OrdinalData 1)
[ "πρώτος"
, "1ος"
, "1ου"
, "πρώτων"
]
, examples (OrdinalData 2)
[ "δεύτερος"
, "2ου"
, "δευτέρου"
]
, examples (OrdinalData 3)
[ "τρίτος"
, "3ης"
]
, examples (OrdinalData 4)
[ "τέταρτος"
, "4ος"
]
, examples (OrdinalData 8)
[ "όγδοος"
, "ογδόου"
, "8ος"
]
, examples (OrdinalData 25)
[ "εικοστός πέμπτος"
, "25ος"
, "εικοστού πέμπτου"
]
, examples (OrdinalData 31)
[ "τριακοστός πρώτος"
, "31ος"
]
, examples (OrdinalData 42)
[ "τεσσαρακοστός δεύτερος"
, "42 ος"
]
, examples (OrdinalData 77)
[ "εβδομηκοστού εβδόμου"
, "77ου"
]
, examples (OrdinalData 90)
[ "ενενηκοστός"
, "90ος"
]
]

View File

@ -0,0 +1,108 @@
-- 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.Ordinal.EL.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.Ordinal.Types (OrdinalData (..), isBetween)
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.Ordinal.Types as TOrdinal
ordinalsMap :: HashMap Text Int
ordinalsMap = HashMap.fromList
[ ( "πρώτ" , 1 )
, ( "δεύτερ" , 2 )
, ( "δευτέρ" , 2 )
, ( "τρίτ" , 3 )
, ( "τέταρτ" , 4 )
, ( "τετάρτ" , 4 )
, ( "πέμπτ" , 5 )
, ( "έκτ" , 6 )
, ( "έβδομ" , 7 )
, ( "εβδόμ" , 7 )
, ( "όγδο" , 8 )
, ( "ογδό" , 8 )
, ( "ένατ" , 9 )
, ( "ενάτ" , 9 )
, ( "δέκατ" , 10 )
, ( "δεκάτ" , 10 )
, ( "ενδέκατ" , 11 )
, ( "ενδεκάτ" , 11 )
, ( "δωδέκατ" , 12 )
, ( "δωδεκάτ" , 12 )
, ( "εικοστ" , 20 )
, ( "τριακοστ" , 30 )
, ( "τεσσαρακοστ" , 40 )
, ( "πεντηκοστ" , 50 )
, ( "εξηκοστ" , 60 )
, ( "εβδομηκοστ" , 70 )
, ( "ογδοηκοστ" , 80 )
, ( "ενενηκοστ" , 90 )
]
ruleOrdinals :: Rule
ruleOrdinals = Rule
{ name = "ordinals (1st..12th, 20th, 30th..90th)"
, pattern =
[ regex $ "(πρώτ|δε[υύ]τ[εέ]ρ|τρίτ|τ[εέ]τ[αά]ρτ|πέμπτ|"
++ "έκτ|[εέ]βδ[οό]μ(ηκοστ)?|[οό]γδ[οό](ηκοστ)?|[εέ]ν[αά]τ|δ[εέ]κ[αά]τ|"
++ "εν[δτ][εέ]κ[αά]τ|δωδ[εέ]κ[αά]τ|"
++ "εικοστ|τριακοστ|τεσσαρακοστ|πεντηκοστ|"
++ "εξηκοστ|ενενηκοστ)"
++ "([οό][υύιί]?ς?|[ηή]ς?|[εέ]ς|ων)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
ordinal <$> HashMap.lookup (Text.toLower match) ordinalsMap
_ -> Nothing
}
ruleCompositeOrdinals :: Rule
ruleCompositeOrdinals = Rule
{ name = "ordinals (composite: 11th..19th, 21st..29th, ..., 91st..99th)"
, pattern =
[ oneOf [10..90]
, oneOf [1..9]
]
, prod = \tokens -> case tokens of
( Token Ordinal (OrdinalData {TOrdinal.value = t}) :
Token Ordinal (OrdinalData {TOrdinal.value = u}) : _ )
-> Just $ ordinal $ t + u
_ -> 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
]

View File

@ -6,8 +6,11 @@
-- of patent rights can be found in the PATENTS file in the same directory.
{-# LANGUAGE GADTs #-}
module Duckling.Ordinal.Helpers
( ordinal
, oneOf
) where
import Prelude
@ -25,3 +28,9 @@ import Duckling.Types
ordinal :: Int -> Token
ordinal x = Token Ordinal OrdinalData {TOrdinal.value = x}
oneOf :: [Int] -> PatternItem
oneOf vs = Predicate $ \x ->
case x of
(Token Ordinal OrdinalData {TOrdinal.value = v}) -> elem v vs
_ -> False

View File

@ -20,6 +20,7 @@ import Duckling.Locale
import Duckling.Types
import qualified Duckling.Duration.EL.Rules as Duration
import qualified Duckling.Numeral.EL.Rules as Numeral
import qualified Duckling.Ordinal.EL.Rules as Ordinal
import qualified Duckling.TimeGrain.EL.Rules as TimeGrain
defaultRules :: Some Dimension -> [Rule]
@ -34,7 +35,7 @@ langRules (This Distance) = []
langRules (This Duration) = Duration.rules
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) = []

View File

@ -337,6 +337,8 @@ library
, Duckling.Ordinal.DA.Rules
, Duckling.Ordinal.DE.Corpus
, Duckling.Ordinal.DE.Rules
, Duckling.Ordinal.EL.Corpus
, Duckling.Ordinal.EL.Rules
, Duckling.Ordinal.EN.Corpus
, Duckling.Ordinal.EN.Rules
, Duckling.Ordinal.ES.Corpus
@ -714,6 +716,7 @@ test-suite duckling-test
, Duckling.Ordinal.AR.Tests
, Duckling.Ordinal.DA.Tests
, Duckling.Ordinal.DE.Tests
, Duckling.Ordinal.EL.Tests
, Duckling.Ordinal.EN.Tests
, Duckling.Ordinal.ES.Tests
, Duckling.Ordinal.ET.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.Ordinal.EL.Tests
( tests
) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Ordinal.EL.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "EL Tests"
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -15,6 +15,7 @@ import Test.Tasty
import qualified Duckling.Ordinal.AR.Tests as AR
import qualified Duckling.Ordinal.DA.Tests as DA
import qualified Duckling.Ordinal.DE.Tests as DE
import qualified Duckling.Ordinal.EL.Tests as EL
import qualified Duckling.Ordinal.EN.Tests as EN
import qualified Duckling.Ordinal.ES.Tests as ES
import qualified Duckling.Ordinal.ET.Tests as ET
@ -44,6 +45,7 @@ tests = testGroup "Ordinal Tests"
[ AR.tests
, DA.tests
, DE.tests
, EL.tests
, EN.tests
, ES.tests
, ET.tests