GE + Duration, Ordinal, TimeGrain, Time (#221)

Summary:
Added initial support for ka_GE for

- Duration
- Ordinal
- TimeGrain
- Time
Pull Request resolved: https://github.com/facebook/duckling/pull/221

Differential Revision: D8840919

Pulled By: haoxuany

fbshipit-source-id: 80f94fbaf25786b0f58cd6598c29cd3663858809
This commit is contained in:
David Magaltadze 2018-08-22 18:25:17 -07:00 committed by Facebook Github Bot
parent dd60c1e013
commit 010146d2f4
17 changed files with 2654 additions and 6 deletions

View File

@ -14,4 +14,8 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ This Numeral ]
[ This Numeral
, This Ordinal
, This Duration
, This Time
]

View File

@ -0,0 +1,62 @@
-- 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.KA.Corpus
( corpus
) where
import Prelude
import Data.String
import Duckling.Duration.Types
import Duckling.Testing.Types
import Duckling.TimeGrain.Types (Grain(..))
import Duckling.Locale
import Duckling.Resolve
corpus :: Corpus
corpus = (testContext {locale = makeLocale KA Nothing},
testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (DurationData 1 Second)
[ "ერთი წამი"
, "1 წამი"
]
, examples (DurationData 2 Minute)
[ "2 წუთი"
, "ორი წუთი"
]
, examples (DurationData 30 Day)
[ "30 დღე"
]
, examples (DurationData 7 Week)
[ "შვიდი კვირა"
]
, examples (DurationData 1 Month)
[ "1 თვე"
, "ერთი თვე"
]
, examples (DurationData 3 Quarter)
[ "3 კვარტალი"
]
-- , examples (DurationData 2 Year)
-- [ "2 წელი"
-- ]
, examples (DurationData 27 Month)
[ "2 წელი და 3 თვე"
, "2 წელი, 3 თვე"
]
, examples (DurationData 31719604 Second)
[ "1 წელი, 2 დღე, 3 საათი და 4 წამი"
]
]

View File

@ -0,0 +1,156 @@
-- 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 NoRebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Duration.KA.Rules
( rules
) where
import Data.Semigroup ((<>))
import Data.String
import Prelude
import qualified Data.Text as Text
import Duckling.Dimensions.Types
import Duckling.Duration.Helpers
import Duckling.Duration.Types (DurationData(..))
import Duckling.Numeral.Helpers (parseInt, parseInteger)
import Duckling.Numeral.Types (NumeralData(..))
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.Duration.Types as TDuration
import qualified Duckling.Numeral.Types as TNumeral
import qualified Duckling.TimeGrain.Types as TG
ruleCompositeDuration :: Rule
ruleCompositeDuration = Rule
{ name = "composite <duration>"
, pattern =
[ Predicate isNatural
, dimension TimeGrain
, regex ",|და"
, dimension Duration
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:
Token TimeGrain g:_:
Token Duration dd@DurationData{TDuration.grain = dg}:
_) | g > dg -> Just . Token Duration $ duration g (floor v) <> dd
_ -> Nothing
}
ruleCompositeDuration1 :: Rule
ruleCompositeDuration1 = Rule
{ name = "composite <duration>"
, pattern =
[ dimension TimeGrain
, regex ",|და"
, dimension Duration
]
, prod = \case
(Token TimeGrain g:_:
Token Duration dd@DurationData{TDuration.grain = dg}:
_) | g > dg -> Just . Token Duration $ duration g 1 <> dd
_ -> Nothing
}
ruleDurationYear :: Rule
ruleDurationYear = Rule
{ name = "<integer> year"
, pattern =
[ Predicate isNatural
, regex "წელიწად(ის)?(ი)?(ში)?|წლი(ის)?(ში)?|წელშ?ი"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:_) ->
Just . Token Duration . duration TG.Month $ 12 * floor v
_ -> Nothing
}
ruleDurationAndHalfYear :: Rule
ruleDurationAndHalfYear = Rule
{ name = "<integer> and an half year"
, pattern =
[ Predicate isNatural
, regex "წელიწადნახევა?(რის)?(რი)?(რში)?|წლინახევრ(ის)?(არში)?"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:_) ->
Just . Token Duration . duration TG.Month $ 6 + 12 * floor v
_ -> Nothing
}
ruleDurationAndHalfYear1 :: Rule
ruleDurationAndHalfYear1 = Rule
{ name = "<integer> and an half year"
, pattern =
[ regex "წელიწადნახევა?(რის)?(რი)?(რში)?|წლინახევრ(ის)?(არში)?"
]
, prod = const $ Just . Token Duration . duration TG.Month $ 18
}
ruleDurationAndHalfMonth :: Rule
ruleDurationAndHalfMonth = Rule
{ name = "<integer> and an half month"
, pattern =
[ Predicate isNatural
, regex "თვენახევა?(რის)?(რი)?(რში)?"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:_) ->
Just . Token Duration . duration TG.Day $ 15 + 30 * floor v
_ -> Nothing
}
ruleDurationAndHalfMonth1 :: Rule
ruleDurationAndHalfMonth1 = Rule
{ name = "month and an half month"
, pattern =
[ regex "თვენახევა?(რის)?(რი)?(რში)?"
]
, prod = const $ Just . Token Duration . duration TG.Day $ 45
}
ruleDurationAndHalfWeek :: Rule
ruleDurationAndHalfWeek = Rule
{ name = "<integer> and an half week"
, pattern =
[ Predicate isNatural
, regex "თვენახევა?(რის)?(რი)?(რში)?"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:_) ->
Just . Token Duration . duration TG.Day $ 3 + 7 * floor v
_ -> Nothing
}
ruleDurationAndHalfWeek1 :: Rule
ruleDurationAndHalfWeek1 = Rule
{ name = "week and an half week"
, pattern =
[ regex "კვირანახევა?(რის)?(რი)?(რში)?"
]
, prod = const $ Just . Token Duration . duration TG.Day $ 10
}
rules :: [Rule]
rules =
[ ruleCompositeDuration
, ruleCompositeDuration1
, ruleDurationAndHalfYear
, ruleDurationAndHalfYear1
, ruleDurationAndHalfMonth
, ruleDurationAndHalfMonth1
, ruleDurationAndHalfWeek
, ruleDurationAndHalfWeek1
, ruleDurationYear
]

View File

@ -0,0 +1,70 @@
-- 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.KA.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Ordinal.Types
import Duckling.Testing.Types
import Duckling.Locale
import Duckling.Resolve
corpus :: Corpus
corpus = (testContext {locale = makeLocale KA Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (OrdinalData 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 73)
[ "სამოცდამეცამეტე"
, "73-ე"
]
, examples (OrdinalData 90)
[ "ოთხმოცდამეათე"
, "90-ე"
]
]

View File

@ -0,0 +1,146 @@
-- 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.KA.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
ordinalsMap :: HashMap Text Int
ordinalsMap = HashMap.fromList
[ ("პირველი", 1)
, ("პირველ", 1)
, ("მეერთე", 1)
, ("მეორე", 2)
, ("მესამე", 3)
, ("მეოთხე", 4)
, ("მეხუთე", 5)
, ("მეექვსე", 6)
, ("მეშვიდე", 7)
, ("მერვე", 8)
, ("მეცხრე", 9)
, ("მეათე", 10)
, ("მეთერთმეტე", 11)
, ("მეთორმეტე", 12)
, ("მეცამეტე", 13)
, ("მეთოთხმეტე", 14)
, ("მეთხუთმეტე", 15)
, ("მეთქვსმეტე", 16)
, ("მეჩვიდმეტე", 17)
, ("მეთვრამეტე", 18)
, ("მეცხრამეტე", 19)
, ("მეოცე", 20)
, ("ოცდამეათე", 30)
, ("მეორმოცე", 40)
, ("ორმოცდამეათე", 50)
, ("მესამოცე", 60)
, ("სამოცდამეათე", 70)
, ("მეოთხმოცე", 80)
, ("ოთხმოცდამეათე", 90)
]
cardinalsMap :: HashMap Text Int
cardinalsMap = HashMap.fromList
[ ("ოცი", 20)
, ("ოცდა", 20)
, ("ოცდაათი", 30)
, ("ორმოცი", 40)
, ("ორმოცდა", 40)
, ("ორმოცდაათი", 50)
, ("სამოცი", 60)
, ("სამოცდა", 60)
, ("სამოცდაათი", 70)
, ("ოთხმოცი", 80)
, ("ოთხმოცდა", 80)
, ("ოთხმოცდაათი", 90)
]
ruleOrdinals :: Rule
ruleOrdinals = Rule
{ name = "ordinals (first..twentieth,thirtieth,...)"
, pattern =
[ regex "(პირველი|მეორე|მესამე|მეოთხე|მეხუთე|მეექვსე|მეშვიდე|მერვე|მეცხრე|მეათე|მეთერთმეტე|მეთოთხმეტე|მეცამეტე|მეთოთხმეტე|მეთხუთმეტე|მეთექვსმეტე|მეჩვიდმეტე|მეთვრამეტე|მეცხრამეტე|მეოცე|ოცდამეათე|მეორმოცე|ორმოცდამეათე|მესამოცე|სამოცდამეათე|მეოთხმოცე|ოთხმოცდამეათე)"
]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):_) ->
ordinal <$> HashMap.lookup (Text.toLower match) ordinalsMap
_ -> Nothing
}
ruleCompositeOrdinals :: Rule
ruleCompositeOrdinals = Rule
{ name = "ordinals (composite, e.g. eighty-seven, forty—seventh, twenty ninth, thirtythird)"
, pattern =
[ regex "(ოცდა|ორმოცდა|სამოცდა|ოთხმოცდა)[\\s\\-\\—]?(მეერთე|მეორე|მესამე|მეოთხე|მეხუთე|მეექვსე|მეშვიდე|მერვე|მეცხრე|მეათე|მეთერთმეტე|მეთოთხმეტე|მეცამეტე|მეთოთხმეტე|მეთხუთმეტე|მეთექვსმეტე|მეჩვიდმეტე|მეთვრამეტე|მეცხრამეტე)"
]
, prod = \case
(Token RegexMatch (GroupMatch (tens:units:_)):_) -> do
tt <- HashMap.lookup (Text.toLower tens) cardinalsMap
uu <- HashMap.lookup (Text.toLower units) ordinalsMap
Just (ordinal (tt + uu))
_ -> Nothing
}
ruleOrdinalDigits :: Rule
ruleOrdinalDigits = Rule
{ name = "ordinal (digits)"
, pattern =
[ regex "0*(\\d+) ?(-ლი|-ე)"
]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):_) -> ordinal <$> parseInt match
_ -> Nothing
}
ruleOrdinalDigits1 :: Rule
ruleOrdinalDigits1 = Rule
{ name = "ordinal (digits)"
, pattern =
[ regex "მე-? ?0*(\\d+)"
]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):_) -> ordinal <$> parseInt match
_ -> Nothing
}
ruleOrdinalDigits2 :: Rule
ruleOrdinalDigits2 = Rule
{ name = "ordinal (digits)"
, pattern =
[ regex "მე-? ?0*(\\d+) ?(-ლი|-ე)"
]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):_) -> ordinal <$> parseInt match
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleOrdinals
, ruleCompositeOrdinals
, ruleOrdinalDigits
, ruleOrdinalDigits1
, ruleOrdinalDigits2
]

View File

@ -19,6 +19,10 @@ import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.Numeral.KA.Rules as Numeral
import qualified Duckling.Time.KA.Rules as Time
import qualified Duckling.TimeGrain.KA.Rules as TimeGrain
import qualified Duckling.Ordinal.KA.Rules as Ordinal
import qualified Duckling.Duration.KA.Rules as Duration
defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules
@ -30,16 +34,16 @@ localeRules _ _ = []
langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = []
langRules (This Distance) = []
langRules (This Duration) = []
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) = []
langRules (This Temperature) = []
langRules (This Time) = []
langRules (This TimeGrain) = []
langRules (This Time) = Time.rules
langRules (This TimeGrain) = TimeGrain.rules
langRules (This Url) = []
langRules (This Volume) = []
langRules (This (CustomDimension dim)) = dimLangRules KA dim

View File

@ -23,7 +23,7 @@ module Duckling.Time.Helpers
, inTimezone, longWEBefore, minute, minutesAfter, minutesBefore, mkLatent
, month, monthDay, notLatent, now, nthDOWOfMonth, partOfDay, predLastOf
, predNth, predNthAfter, predNthClosest, season, second, timeOfDayAMPM
, weekday, weekend, withDirection, year, yearMonthDay, tt, durationIntervalAgo
, weekday, weekend, workweek, withDirection, year, yearMonthDay, tt, durationIntervalAgo
, inDurationInterval, intersectWithReplacement, yearADBC, yearMonth
-- Other
, getIntValue, timeComputed
@ -626,6 +626,12 @@ weekend = interval' TTime.Open (fri, mon)
fri = intersect' (dayOfWeek 5, hour False 18)
mon = intersect' (dayOfWeek 1, hour False 0)
workweek :: TimeData
workweek = interval' TTime.Open (mon, fri)
where
mon = intersect' (dayOfWeek 1, hour False 10)
fri = intersect' (dayOfWeek 5, hour False 18)
-- Zero-indexed weeks, Monday is 1
-- Use `predLastOf` for last day of week of month
nthDOWOfMonth :: Int -> Int -> Int -> TimeData

472
Duckling/Time/KA/Corpus.hs Normal file
View File

@ -0,0 +1,472 @@
-- 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.Time.KA.Corpus
( corpus
, defaultCorpus
, latentCorpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types hiding (examples)
import Duckling.Time.Corpus
import Duckling.Time.Types hiding (Month)
import Duckling.TimeGrain.Types
import Duckling.Resolve
corpus :: Corpus
corpus = (testContext {locale = makeLocale KA Nothing},
testOptions, allExamples)
defaultCorpus :: Corpus
defaultCorpus = (testContext {locale = makeLocale KA Nothing},
testOptions, allExamples)
latentCorpus :: Corpus
latentCorpus = (testContext {locale = makeLocale KA Nothing},
testOptions {withLatent = True}, xs)
where
xs = concat
[ examples (datetime (2013, 2, 24, 0, 0, 0) Day)
[ "24 თებერვალს"
]
, examples (datetime (2013, 2, 12, 7, 0, 0) Hour)
[ "7 საათზე"
]
, examples (datetime (1954, 1, 1, 0, 0, 0) Year)
[ "1954 წელი"
]
, examples (datetime (2013, 5, 1, 0, 0, 0) Month)
[ "მაისი"
]
]
allExamples :: [Example]
allExamples = concat
[ examples (datetime (2013, 2, 12, 4, 30, 0) Second)
[ "ახლა"
, "ახლავე"
, "ეხლა"
]
, examples (datetime (2013, 2, 12, 0, 0, 0) Day)
[ "დღეს"
]
, examples (datetime (2013, 2, 1, 0, 0, 0) Day)
[ "2/2013"
]
, examples (datetime (2014, 1, 1, 0, 0, 0) Year)
[ "2014-ში"
]
, examples (datetime (2013, 2, 11, 0, 0, 0) Day)
[ "გუშინ"
]
, examples (datetime (2013, 2, 13, 0, 0, 0) Day)
[ "ხვალ"
, "ხვალე"
]
, examples (datetime (2013, 2, 18, 0, 0, 0) Day)
[ "ორშაბათი"
, "ორშ."
, "ორშ"
, "ამ ორშაბათს"
, "ეს ორშაბათი"
]
, examples (datetime (2013, 2, 19, 0, 0, 0) Day)
[ "სამშაბათი"
]
, examples (datetime (2013, 2, 14, 0, 0, 0) Day)
[ "ხუთშაბათი"
, "ხუთ"
, "ხუთშ"
, "ხუთშ."
]
, examples (datetime (2013, 2, 15, 0, 0, 0) Day)
[ "პარასკევი"
, "პარ"
, "პარ."
]
, examples (datetime (2013, 2, 16, 0, 0, 0) Day)
[ "შაბათი"
, "შაბ"
, "შაბ."
]
, examples (datetime (2013, 2, 17, 0, 0, 0) Day)
[ "კვირა"
, "კვრ"
, "კვ."
]
, examples (datetime (2013, 3, 1, 0, 0, 0) Day)
[ "1-ლი მარტი"
, "პირველი მარტი"
]
, examples (datetime (2013, 3, 3, 0, 0, 0) Day)
[ "3 მარტი"
]
, examples (datetime (2015, 3, 3, 0, 0, 0) Day)
[ "3 მარტი 2015"
, "2015 წლის მე-3 მარტი"
, "2015-3-3"
, "2015-03-03"
]
, examples (datetime (2013, 2, 15, 0, 0, 0) Day)
[ "15 თებერვალი"
, "თებერვლის მეთხუთმეტე დღეს"
, "თხუთმეტი თებერვალი"
]
, examples (datetime (2013, 8, 8, 0, 0, 0) Day)
[ "8 აგვ"
]
, examples (datetime (2014, 10, 1, 0, 0, 0) Month)
[ "2014 წლის ოქტომბერი"
]
, examples (datetime (2015, 4, 14, 0, 0, 0) Day)
[ "14 აპრილი 2015"
, "2015 წლის 14 აპრილი"
, "2015 წლის 14 აპრილს"
]
, examples (datetime (2013, 2, 26, 0, 0, 0) Day)
[ "შემდეგ სამშაბათს"
]
, examples (datetime (2013, 3, 1, 0, 0, 0) Day)
[ "შემდეგის შემდეგი პარასკევი"
]
, examples (datetime (2014, 3, 1, 0, 0, 0) Month)
[ "შემდეგი მარტი"
]
, examples (datetime (2015, 3, 1, 0, 0, 0) Month)
[ "შემდეგის შემდეგი მარტი"
]
, examples (datetimeInterval ((2013, 1, 1, 0, 0, 0), (2013, 2, 1, 0, 0, 0)) Month)
[ "წინა თვე"
]
, examples (datetimeInterval ((2013, 3, 1, 0, 0, 0), (2013, 4, 1, 0, 0, 0)) Month)
[ "შემდეგი თვე"
]
, examples (datetimeInterval ((2013, 4, 1, 0, 0, 0), (2013, 7, 1, 0, 0, 0)) Quarter)
[ "შემდეგ კვარტალში"
]
, examples (datetimeInterval ((2012, 1, 1, 0, 0, 0), (2013, 1, 1, 0, 0, 0)) Year)
[ "შარშან"
, "წინა წელს"
]
, examples (datetimeInterval ((2014, 1, 1, 0, 0, 0), (2015, 1, 1, 0, 0, 0)) Year)
[ "მომავალი წელი"
, "შემდეგ წელს"
]
, examples (datetime (2013, 2, 10, 0, 0, 0) Day)
[ "წინა კვირის კვირას"
]
, examples (datetime (2013, 2, 5, 0, 0, 0) Day)
[ "ბოლო სამშაბათს"
]
, examples (datetime (2013, 2, 26, 0, 0, 0) Day)
[ "შემდეგ სამშაბათს"
]
, examples (datetime (2013, 2, 20, 0, 0, 0) Day)
[ "შემდეგი ოთხშაბათი"
]
, examples (datetime (2013, 2, 20, 0, 0, 0) Day)
[ "შემდეგი კვირის ოთხშაბათი"
]
, examples (datetime (2013, 3, 1, 0, 0, 0) Day)
[ "შემდეგის შემდეგი პარასკევი"
]
, examples (datetime (2013, 2, 10, 0, 0, 0) Day)
[ "გუშინწინ"
]
, examples (datetime (2013, 2, 10, 8, 0, 0) Hour)
[ "გუშინწინ8-ზე"
]
, examples (datetime (2013, 3, 25, 0, 0, 0) Day)
[ "მარტის ბოლო ორშაბათი"
]
, examples (datetime (2013, 10, 3, 0, 0, 0) Day)
[ "ოქტომბრის მესამე დღე"
, "ოქტომბრის მე-3 დღე"
]
, examples (datetime (2013, 10, 1, 0, 0, 0) Day)
[ "ოქტომბრის პირველი სამშაბათი"
, "ოქტომბრის 1-ლი სამშაბათი"
]
, examples (datetime (2013, 9, 17, 0, 0, 0) Day)
[ "სექტემბრის მესამე სამშაბათი"
, "სექტემბრის მე-3 სამშაბათი"
]
, examples (datetime (2013, 10, 2, 0, 0, 0) Day)
[ "ოქტომბრის პირველი ოთხშაბათი"
, "ოქტომბრის 1-ლი ოთხშაბათი"
]
, examples (datetime (2013, 10, 9, 0, 0, 0) Day)
[ "ოქტომბრის მეორე ოთხშაბათი"
, "ოქტომბრის მე-2 ოთხშაბათი"
]
, examples (datetime (2013, 2, 13, 3, 18, 0) Minute)
[ "3:18am"
, "3:18a"
]
, examples (datetime (2013, 2, 12, 15, 0, 0) Hour)
[ "15 საათზე"
, "3PM"
, "3pm"
]
, examples (datetime (2013, 2, 12, 15, 15, 0) Minute)
[ "4-ის 15 წუთზე"
, "3 საათსა და 15 წუთზე"
, "15:15"
, "3:15pm"
, "3:15PM"
, "3:15p"
]
, examples (datetime (2013, 2, 12, 15, 20, 0) Minute)
[ "15 საათსა და 20 წუთზე"
, "4-ის 20 წუთზე"
, "3:20p"
]
, examples (datetime (2013, 2, 12, 15, 30, 0) Minute)
[ "4-ის ნახევარზე"
, "15 საათსა და 30 წუთზე"
, "15:30"
, "3:30pm"
, "3:30PM"
, "330 p.m."
, "3:30 p m"
, "3:30"
]
, examples (datetime (2013, 2, 12, 15, 23, 24) Second)
[ "15:23:24"
]
, examples (datetime (2013, 2, 12, 11, 45, 0) Minute)
[ "11 საათსა და 45 წუთზე"
, "11:45am"
]
, examples (datetime (2013, 2, 12, 20, 0, 0) Hour)
[ "20 საათი"
, "20 საათზე"
]
, examples (datetime (2013, 2, 16, 9, 0, 0) Hour)
[ "შაბათს 9-ზე"
]
, examples (datetime (2013, 2, 16, 9, 0, 0) Hour)
[ "შაბათს 9 საათზე"
]
, examples (datetime (2013, 2, 5, 4, 0, 0) Hour)
[ "7 დღის წინ"
, "შვიდი დღის წინ"
]
, examples (datetime (2013, 1, 29, 4, 0, 0) Hour)
[ "14 დღის წინ"
, "თოთხმეტი დღის წინ"
]
, examples (datetime (2013, 2, 5, 0, 0, 0) Day)
[ "1 კვირის წინ"
, "ერთი კვირის წინ"
]
, examples (datetime (2013, 1, 22, 0, 0, 0) Day)
[ "3 კვირის წინ"
, "სამი კვირის წინ"
]
, examples (datetime (2012, 11, 12, 0, 0, 0) Day)
[ "სამი თვის წინ"
, "3 თვის წინ"
]
, examples (datetime (2011, 2, 1, 0, 0, 0) Month)
[ "ორი წლის წინ"
, "ორი წლის წინ"
]
, examples (datetimeInterval ((2013, 6, 1, 0, 0, 0), (2013, 9, 1, 0, 0, 0)) Day)
[ "ამ ზაფხულს"
, "ამ ზაფხულში"
]
, examples (datetimeInterval ((2012, 12, 1, 0, 0, 0), (2013, 3, 1, 0, 0, 0)) Day)
[ "ამ ზამთარს"
, "ამ ზამთარში"
]
, examples (datetimeInterval ((2012, 9, 23, 0, 0, 0), (2012, 12, 20, 0, 0, 0)) Day)
[ "წინა სეზონზე"
]
, examples (datetimeInterval ((2013, 2, 11, 18, 0, 0), (2013, 2, 12, 0, 0, 0)) Hour)
[ "გუშინ ღამე"
, "გუშინ ღამით"
]
, examples (datetimeInterval ((2013, 2, 11, 21, 0, 0), (2013, 2, 12, 0, 0, 0)) Hour)
[ "გუშინ გვიან ღამე"
, "გუშინ გვიან ღამით"
]
, examples (datetimeInterval ((2013, 2, 12, 18, 0, 0), (2013, 2, 13, 0, 0, 0)) Hour)
[ "დღეს საღამოს"
, "დღეს ღამე"
]
, examples (datetimeInterval ((2013, 2, 8, 18, 0, 0), (2013, 2, 11, 0, 0, 0)) Hour)
[ "გასულ უქმეებზე"
, "გასულ შაბათ-კვირას"
]
, examples (datetimeInterval ((2013, 2, 13, 18, 0, 0), (2013, 2, 14, 0, 0, 0)) Hour)
[ "ხვალ საღამოს"
]
, examples (datetimeInterval ((2013, 2, 11, 18, 0, 0), (2013, 2, 12, 0, 0, 0)) Hour)
[ "გუშინ საღამოს"
]
, examples (datetimeInterval ((2013, 2, 15, 18, 0, 0), (2013, 2, 18, 0, 0, 0)) Hour)
[ "ამ შაბათკვირას"
]
, examples (datetimeInterval ((2013, 2, 18, 4, 0, 0), (2013, 2, 18, 12, 0, 0)) Hour)
[ "ორშაბათს დილას"
, "ორშაბათს დილა"
]
, examples (datetimeInterval ((2013, 2, 15, 4, 0, 0), (2013, 2, 15, 12, 0, 0)) Hour)
[ "15 თებერვალი დილა"
, "15 თებერვალს დილას"
, "15 თებერვლის დილა"
]
, examples (datetimeInterval ((2013, 2, 12, 4, 29, 58), (2013, 2, 12, 4, 30, 1)) Second)
[ "ბოლო 2 წამი"
, "ბოლო 2 წამში"
]
, examples (datetimeInterval ((2013, 7, 13, 0, 0, 0), (2013, 7, 16, 0, 0, 0)) Day)
[ "ივლისი 13-15"
, "13-15 ივლისი"
]
, examples (datetimeInterval ((2013, 8, 8, 0, 0, 0), (2013, 8, 13, 0, 0, 0)) Day)
[ "8-12 აგვ"
]
, examples (datetimeInterval ((2013, 2, 14, 9, 30, 0), (2013, 2, 14, 11, 1, 0)) Minute)
[ "ხუთშაბათი 9:30-დან 11:00-მდე"
, "ხუთშაბათს 10-ის ნახევრიდან 11:00-მდე"
]
, examples (datetimeInterval ((2013, 2, 12, 4, 30, 0), (2013, 2, 26, 0, 0, 0)) Second)
[ "ორი კვირის განმავლობაში"
, "2 კვირის განმავლობაში"
]
, examples (datetimeInterval ((2013, 2, 21, 0, 0, 0), (2013, 3, 1, 0, 0, 0)) Day)
[ "თვის ბოლო"
, "თვის ბოლოსთვის"
, "თვის ბოლოსკენ"
, "ამ თვის ბოლო"
, "ამ თვის ბოლოსთვის"
, "ამ თვის ბოლოსკენ"
]
, examples (datetime (2013, 2, 12, 14, 0, 0) Hour)
[ "დღეს შუადღის 2-ზე"
, "დღეს დღის 2-ზე"
, "დღეს შუადღის ორზე"
]
, examples (datetime (2013, 2, 13, 15, 0, 0) Hour)
[ "ხვალ დღის 3-ზე"
, "ხვალ დღის სამზე"
]
, examples (datetimeInterval ((2013, 2, 12, 18, 0, 0), (2013, 2, 13, 0, 0, 0)) Hour)
[ "საღამოს"
, "დღეს საღამოს"
, "დღეს ღამე"
, "ღამე"
, "ღამით"
]
, examples (datetime (2013, 2, 12, 13, 30, 0) Minute)
[ "1 საათსა და 30 წუთზე"
, "2-ის ნახევარზე"
, "2-ის ნახევარი"
, "1 საათი და 30 წუთი"
]
, examples (datetime (2013, 2, 12, 4, 45, 0) Second)
[ "15 წუთში"
]
, examples (datetimeInterval ((2013, 2, 12, 4, 0, 0), (2013, 2, 12, 12, 0, 0)) Hour)
[ "დღეს დილას"
]
, examples (datetime (2013, 2, 18, 0, 0, 0) Day)
[ "ორშაბათი"
, "ორშაბათს"
]
, examples (datetime (2013, 2, 12, 12, 0, 0) Hour)
[ "12 საათი"
, "12 საათზე"
, "დღის 12 საათზე"
]
, examples (datetime (2013, 3, 1, 0, 0, 0) Month)
[ "მარტი"
]
, examples (datetime (2013, 2, 13, 17, 0, 0) Hour)
[ "ხვალ დღის 5"
, "ხვალ შუადღის 5"
, "ხვალ დღის 5-ზე"
, "ხვალ შუადღის 5-ზე"
, "ხვალ დღის 5 საათი"
, "ხვალ შუადღის 5 საათი"
, "ხვალ დღის 5 საათზე"
, "ხვალ შუადღის 5 საათზე"
]
, examples (datetime (2013, 2, 12, 10, 30, 0) Minute)
[ "დილის 10:30"
, "დილის 10 საათსა და 30 წუთზე"
, "დილის 10 საათი და 30 წუთი"
]
, examples (datetime (2013, 2, 12, 23, 0, 0) Hour)
[ "დღეს ღამის 11"
, "დღეს ღამის 11-ზე"
, "დღეს ღამის 11 საათი"
, "დღეს ღამის 11 საათზე"
]
, examples (datetime (2013, 2, 12, 4, 23, 0) Minute)
[ "4:23-ზე"
]
, examples (datetimeInterval ((2013, 3, 1, 0, 0, 0), (2013, 3, 11, 0, 0, 0)) Day)
[ "მარტის დასაწყისი"
, "მარტის დასაწყისში"
]
, examples (datetimeInterval ((2013, 3, 11, 0, 0, 0), (2013, 3, 21, 0, 0, 0)) Day)
[ "მარტის შუა"
]
, examples (datetimeInterval ((2013, 3, 21, 0, 0, 0), (2013, 4, 1, 0, 0, 0)) Day)
[ "მარტის ბოლო"
]
, examples (datetimeInterval ((2013, 10, 25, 18, 0, 0), (2013, 10, 28, 0, 0, 0)) Hour)
[ "ოქტომბრის ბოლო უქმეები"
, "ოქტომბრის ბოლო შაბათ-კვირა"
]
, examples (datetimeInterval ((2013, 7, 26, 18, 0, 0), (2013, 7, 29, 0, 0, 0)) Hour)
[ "ივლისის ბოლო უქმეები"
, "ივლისის ბოლო შაბათ-კვირა"
, "ივლისის ბოლო შაბათ-კვირა"
]
, examples (datetimeInterval ((2017, 10, 27, 18, 0, 0), (2017, 10, 30, 0, 0, 0)) Hour)
[ "2017 წლის ოქტომბრის ბოლო უქმეები"
, "2017 წლის ოქტომბრის ბოლო შაბათ-კვირა"
]
, examples (datetimeInterval ((2013, 8, 27, 0, 0, 0), (2013, 8, 30, 0, 0, 0)) Day)
[ "27-29 აგვ"
, "27-29 აგვისტო"
]
, examples (datetimeInterval ((2013, 10, 23, 0, 0, 0), (2013, 10, 27, 0, 0, 0)) Day)
[ "23-26 ოქტომბერი"
]
, examples (datetimeInterval ((2013, 9, 1, 0, 0, 0), (2013, 9, 9, 0, 0, 0)) Day)
[ "1-8 სექტემბერი"
]
, examples (datetimeInterval ((2013, 9, 12, 0, 0, 0), (2013, 9, 17, 0, 0, 0)) Day)
[ "12-16 სექტემბერი"
]
, examples (datetimeInterval ((2013, 8, 19, 0, 0, 0), (2013, 8, 22, 0, 0, 0)) Day)
[ "19-21 აგვისტო"
]
, examples (datetimeInterval ((2013, 4, 21, 0, 0, 0), (2013, 5, 1, 0, 0, 0)) Day)
[ "აპრილის ბოლო"
]
, examples (datetimeInterval ((2014, 1, 1, 0, 0, 0), (2014, 1, 11, 0, 0, 0)) Day)
[ "იანვრის დასაწყისი"
]
, examples (datetimeInterval ((2013, 1, 1, 0, 0, 0), (2013, 4, 1, 0, 0, 0)) Month)
[ "წლის დასაწყისი"
, "ამ წლის დასაწყისი"
]
]

1598
Duckling/Time/KA/Rules.hs Normal file

File diff suppressed because it is too large Load Diff

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.KA.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 = const $ Just $ Token TimeGrain grain
}

View File

@ -299,6 +299,8 @@ library
, Duckling.Duration.HU.Rules
, Duckling.Duration.IT.Rules
, Duckling.Duration.JA.Corpus
, Duckling.Duration.KA.Corpus
, Duckling.Duration.KA.Rules
, Duckling.Duration.KO.Corpus
, Duckling.Duration.KO.Rules
, Duckling.Duration.NB.Corpus
@ -448,6 +450,8 @@ library
, Duckling.Ordinal.IT.Rules
, Duckling.Ordinal.JA.Corpus
, Duckling.Ordinal.JA.Rules
, Duckling.Ordinal.KA.Corpus
, Duckling.Ordinal.KA.Rules
, Duckling.Ordinal.KO.Corpus
, Duckling.Ordinal.KO.Rules
, Duckling.Ordinal.NB.Corpus
@ -591,6 +595,8 @@ library
, Duckling.Time.HU.Rules
, Duckling.Time.IT.Corpus
, Duckling.Time.IT.Rules
, Duckling.Time.KA.Corpus
, Duckling.Time.KA.Rules
, Duckling.Time.KO.Corpus
, Duckling.Time.KO.Rules
, Duckling.Time.NB.Corpus
@ -644,6 +650,7 @@ library
, Duckling.TimeGrain.HU.Rules
, Duckling.TimeGrain.IT.Rules
, Duckling.TimeGrain.JA.Rules
, Duckling.TimeGrain.KA.Rules
, Duckling.TimeGrain.KO.Rules
, Duckling.TimeGrain.NB.Rules
, Duckling.TimeGrain.NL.Rules
@ -783,6 +790,7 @@ test-suite duckling-test
, Duckling.Duration.HU.Tests
, Duckling.Duration.HI.Tests
, Duckling.Duration.JA.Tests
, Duckling.Duration.KA.Tests
, Duckling.Duration.KO.Tests
, Duckling.Duration.NB.Tests
, Duckling.Duration.NL.Tests
@ -860,6 +868,7 @@ test-suite duckling-test
, Duckling.Ordinal.ID.Tests
, Duckling.Ordinal.IT.Tests
, Duckling.Ordinal.JA.Tests
, Duckling.Ordinal.KA.Tests
, Duckling.Ordinal.KO.Tests
, Duckling.Ordinal.NB.Tests
, Duckling.Ordinal.NL.Tests
@ -921,6 +930,7 @@ test-suite duckling-test
, Duckling.Time.HE.Tests
, Duckling.Time.HU.Tests
, Duckling.Time.IT.Tests
, Duckling.Time.KA.Tests
, Duckling.Time.KO.Tests
, Duckling.Time.NB.Tests
, Duckling.Time.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.Duration.KA.Tests
( tests
) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Duration.KA.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "KA Tests"
[ makeCorpusTest [This Duration] corpus
]

View File

@ -23,6 +23,7 @@ import qualified Duckling.Duration.GA.Tests as GA
import qualified Duckling.Duration.HI.Tests as HI
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.NB.Tests as NB
import qualified Duckling.Duration.NL.Tests as NL
@ -45,6 +46,7 @@ tests = testGroup "Duration Tests"
, HI.tests
, HU.tests
, JA.tests
, KA.tests
, KO.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.Ordinal.KA.Tests
( tests
) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Ordinal.KA.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "KA Tests"
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -29,6 +29,7 @@ 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
import qualified Duckling.Ordinal.KA.Tests as KA
import qualified Duckling.Ordinal.KO.Tests as KO
import qualified Duckling.Ordinal.NB.Tests as NB
import qualified Duckling.Ordinal.NL.Tests as NL
@ -62,6 +63,7 @@ tests = testGroup "Ordinal Tests"
, ID.tests
, IT.tests
, JA.tests
, KA.tests
, KO.tests
, NB.tests
, NL.tests

View File

@ -0,0 +1,25 @@
-- 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.Time.KA.Tests
( tests
) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Testing.Asserts
import Duckling.Time.KA.Corpus
tests :: TestTree
tests = testGroup "KA Tests"
[ makeCorpusTest [This Time] corpus
, makeCorpusTest [This Time] latentCorpus
]

View File

@ -36,6 +36,7 @@ import qualified Duckling.Time.HR.Tests as HR
import qualified Duckling.Time.HE.Tests as HE
import qualified Duckling.Time.HU.Tests as HU
import qualified Duckling.Time.IT.Tests as IT
import qualified Duckling.Time.KA.Tests as KA
import qualified Duckling.Time.KO.Tests as KO
import qualified Duckling.Time.NB.Tests as NB
import qualified Duckling.Time.NL.Tests as NL
@ -60,6 +61,7 @@ tests = testGroup "Time Tests"
, HE.tests
, HU.tests
, IT.tests
, KA.tests
, KO.tests
, NB.tests
, NL.tests