mirror of
https://github.com/facebook/duckling.git
synced 2025-01-07 14:29:37 +03:00
TimeGrain,Duration/UK: added dimensions
Summary: - added TimeGrain dimension for UK language - added Duration dimension for UK language Reviewed By: patapizza Differential Revision: D12871569 fbshipit-source-id: 356c2031aa9582620be11ea634c854c0d96ebbeb
This commit is contained in:
parent
4bee26851e
commit
3c5790f605
@ -14,6 +14,7 @@ import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ This Numeral
|
||||
[ This Duration
|
||||
, This Numeral
|
||||
, This Ordinal
|
||||
]
|
||||
|
79
Duckling/Duration/UK/Corpus.hs
Normal file
79
Duckling/Duration/UK/Corpus.hs
Normal file
@ -0,0 +1,79 @@
|
||||
-- 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.UK.Corpus
|
||||
( corpus
|
||||
, negativeCorpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Locale
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
context :: Context
|
||||
context = testContext {locale = makeLocale UK Nothing}
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (context, testOptions, allExamples)
|
||||
|
||||
negativeCorpus :: NegativeCorpus
|
||||
negativeCorpus = (context, testOptions, examples)
|
||||
where
|
||||
examples =
|
||||
[ "в дні"
|
||||
, "секретар"
|
||||
, "хвилини"
|
||||
]
|
||||
|
||||
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 2 Year)
|
||||
[ "2 роки"
|
||||
]
|
||||
, examples (DurationData 30 Minute)
|
||||
[ "півгодини"
|
||||
, "1/2 години"
|
||||
]
|
||||
, examples (DurationData 12 Hour)
|
||||
[ "пів дня"
|
||||
]
|
||||
, examples (DurationData 90 Minute)
|
||||
[ "півтори години"
|
||||
]
|
||||
, examples (DurationData 27 Month)
|
||||
[ "2 роки і 3 місяці"
|
||||
, "2 роки, 3 місяці"
|
||||
]
|
||||
, examples (DurationData 31719604 Second)
|
||||
[ "1 рік, 2 дня, 3 години і 4 секунди"
|
||||
]
|
||||
]
|
145
Duckling/Duration/UK/Rules.hs
Normal file
145
Duckling/Duration/UK/Rules.hs
Normal file
@ -0,0 +1,145 @@
|
||||
-- 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.Duration.UK.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
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
|
||||
|
||||
ruleHalfAnHour :: Rule
|
||||
ruleHalfAnHour = Rule
|
||||
{ name = "half an hour"
|
||||
, pattern =
|
||||
[ regex "(1/2\\s?|пів\\s?)години?"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleNumeralnumberHours :: Rule
|
||||
ruleNumeralnumberHours = Rule
|
||||
{ name = "number.number hours"
|
||||
, pattern =
|
||||
[ regex "(\\d+)\\.(\\d+) години?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (h:m:_)):_) -> do
|
||||
hh <- parseInteger h
|
||||
mnum <- parseInteger m
|
||||
let mden = 10 ^ Text.length m
|
||||
Just . Token Duration $ minutesFromHourMixedFraction hh mnum mden
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntegerAndAnHalfHours :: Rule
|
||||
ruleIntegerAndAnHalfHours = Rule
|
||||
{ name = "<integer> and an half hours"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "з половиною години"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Numeral NumeralData{TNumeral.value = v}:_) ->
|
||||
Just . Token Duration . duration TG.Minute $ 30 + 60 * floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAboutDuration :: Rule
|
||||
ruleAboutDuration = Rule
|
||||
{ name = "about <duration>"
|
||||
, pattern =
|
||||
[ regex "близько"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleExactlyDuration :: Rule
|
||||
ruleExactlyDuration = Rule
|
||||
{ name = "exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "рівно"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationHalfATimeGrain :: Rule
|
||||
ruleDurationHalfATimeGrain = Rule
|
||||
{ name = "half a <time-grain>"
|
||||
, pattern =
|
||||
[ regex "(1/2|пів)"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Token Duration <$> timesOneAndAHalf grain 0
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationOneGrainAndHalf :: Rule
|
||||
ruleDurationOneGrainAndHalf = Rule
|
||||
{ name = "one and a hald <unit-of-duration>"
|
||||
, pattern =
|
||||
[ regex "півтори"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Token Duration <$> timesOneAndAHalf grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleCompositeDurationCommasAnd :: Rule
|
||||
ruleCompositeDurationCommasAnd = Rule
|
||||
{ name = "composite <duration> (with ,/and)"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, dimension TimeGrain
|
||||
, regex ",|і"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(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
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleAboutDuration
|
||||
, ruleExactlyDuration
|
||||
, ruleHalfAnHour
|
||||
, ruleIntegerAndAnHalfHours
|
||||
, ruleNumeralnumberHours
|
||||
, ruleDurationHalfATimeGrain
|
||||
, ruleDurationOneGrainAndHalf
|
||||
, ruleCompositeDurationCommasAnd
|
||||
]
|
@ -18,8 +18,10 @@ module Duckling.Rules.UK
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Locale
|
||||
import Duckling.Types
|
||||
import qualified Duckling.Duration.UK.Rules as Duration
|
||||
import qualified Duckling.Numeral.UK.Rules as Numeral
|
||||
import qualified Duckling.Ordinal.UK.Rules as Ordinal
|
||||
import qualified Duckling.TimeGrain.UK.Rules as TimeGrain
|
||||
|
||||
defaultRules :: Some Dimension -> [Rule]
|
||||
defaultRules = langRules
|
||||
@ -32,7 +34,7 @@ langRules :: Some Dimension -> [Rule]
|
||||
langRules (This AmountOfMoney) = []
|
||||
langRules (This CreditCardNumber) = []
|
||||
langRules (This Distance) = []
|
||||
langRules (This Duration) = []
|
||||
langRules (This Duration) = Duration.rules
|
||||
langRules (This Email) = []
|
||||
langRules (This Numeral) = Numeral.rules
|
||||
langRules (This Ordinal) = Ordinal.rules
|
||||
@ -41,7 +43,7 @@ langRules (This Quantity) = []
|
||||
langRules (This RegexMatch) = []
|
||||
langRules (This Temperature) = []
|
||||
langRules (This Time) = []
|
||||
langRules (This TimeGrain) = []
|
||||
langRules (This TimeGrain) = TimeGrain.rules
|
||||
langRules (This Url) = []
|
||||
langRules (This Volume) = []
|
||||
langRules (This (CustomDimension dim)) = dimLangRules UK dim
|
||||
|
41
Duckling/TimeGrain/UK/Rules.hs
Normal file
41
Duckling/TimeGrain/UK/Rules.hs
Normal 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 GADTs #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Duckling.TimeGrain.UK.Rules
|
||||
( rules ) where
|
||||
|
||||
import Data.String
|
||||
import Data.Text (Text)
|
||||
import Prelude
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
|
||||
grains :: [(Text, String, TG.Grain)]
|
||||
grains = [ ("second (grain)", "секунд(а|и|і|у)?|сек", TG.Second)
|
||||
, ("minute (grain)", "хвилин(а|и|і|у)?|хв", TG.Minute)
|
||||
, ("hour (grain)", "годин(а|и|і|у)?", TG.Hour)
|
||||
, ("day (grain)", "день|дн(і|я)в?", TG.Day)
|
||||
, ("week (grain)", "тиждень|тижн(я|і)в?", TG.Week)
|
||||
, ("month (grain)", "місяц(ь|я|і)в?", TG.Month)
|
||||
, ("quarter (grain)", "квартал(и|і)?в?", TG.Quarter)
|
||||
, ("year (grain)", "рік|ро(к|ц)(и|і|у)?в?", TG.Year)
|
||||
]
|
||||
|
||||
rules :: [Rule]
|
||||
rules = map go grains
|
||||
where
|
||||
go (name, regexPattern, grain) = Rule
|
||||
{ name = name
|
||||
, pattern = [regex regexPattern]
|
||||
, prod = \_ -> Just $ Token TimeGrain grain
|
||||
}
|
@ -337,6 +337,8 @@ library
|
||||
, Duckling.Duration.RU.Rules
|
||||
, Duckling.Duration.TR.Corpus
|
||||
, Duckling.Duration.TR.Rules
|
||||
, Duckling.Duration.UK.Corpus
|
||||
, Duckling.Duration.UK.Rules
|
||||
, Duckling.Duration.Helpers
|
||||
, Duckling.Duration.Rules
|
||||
, Duckling.Duration.Types
|
||||
@ -694,6 +696,7 @@ library
|
||||
, Duckling.TimeGrain.RU.Rules
|
||||
, Duckling.TimeGrain.SV.Rules
|
||||
, Duckling.TimeGrain.TR.Rules
|
||||
, Duckling.TimeGrain.UK.Rules
|
||||
, Duckling.TimeGrain.VI.Rules
|
||||
, Duckling.TimeGrain.ZH.Rules
|
||||
, Duckling.TimeGrain.Types
|
||||
@ -844,6 +847,7 @@ test-suite duckling-test
|
||||
, Duckling.Duration.RU.Tests
|
||||
, Duckling.Duration.SV.Tests
|
||||
, Duckling.Duration.TR.Tests
|
||||
, Duckling.Duration.UK.Tests
|
||||
, Duckling.Duration.ZH.Tests
|
||||
, Duckling.Duration.Tests
|
||||
|
||||
|
@ -33,6 +33,7 @@ import qualified Duckling.Duration.RO.Tests as RO
|
||||
import qualified Duckling.Duration.RU.Tests as RU
|
||||
import qualified Duckling.Duration.SV.Tests as SV
|
||||
import qualified Duckling.Duration.TR.Tests as TR
|
||||
import qualified Duckling.Duration.UK.Tests as UK
|
||||
import qualified Duckling.Duration.ZH.Tests as ZH
|
||||
|
||||
tests :: TestTree
|
||||
@ -56,5 +57,6 @@ tests = testGroup "Duration Tests"
|
||||
, RU.tests
|
||||
, SV.tests
|
||||
, TR.tests
|
||||
, UK.tests
|
||||
, ZH.tests
|
||||
]
|
||||
|
25
tests/Duckling/Duration/UK/Tests.hs
Normal file
25
tests/Duckling/Duration/UK/Tests.hs
Normal 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.Duration.UK.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.UK.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "UK Tests"
|
||||
[ makeCorpusTest [This Duration] corpus
|
||||
, makeNegativeCorpusTest [This Duration] negativeCorpus
|
||||
]
|
Loading…
Reference in New Issue
Block a user