mirror of
https://github.com/facebook/duckling.git
synced 2024-11-28 08:34:46 +03:00
Added TimeGrain, Duration, and Ordinal
Summary: Closes https://github.com/facebook/duckling/pull/164 Reviewed By: chinmay87 Differential Revision: D7280110 Pulled By: patapizza fbshipit-source-id: d98ddd900fe83f06b28afd39ea3311f42716288c
This commit is contained in:
parent
519c9519a3
commit
21c3b32e4d
@ -15,5 +15,7 @@ import Duckling.Dimensions.Types
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ This Distance
|
||||
, This Duration
|
||||
, This Numeral
|
||||
, This Ordinal
|
||||
]
|
||||
|
95
Duckling/Duration/BG/Corpus.hs
Normal file
95
Duckling/Duration/BG/Corpus.hs
Normal file
@ -0,0 +1,95 @@
|
||||
-- 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.BG.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Locale
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {locale = makeLocale BG Nothing}, testOptions, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "1 сек"
|
||||
, "1 секунда"
|
||||
, "секунда"
|
||||
, "1\""
|
||||
]
|
||||
, examples (DurationData 15 Minute)
|
||||
[ "15 мин"
|
||||
, "петнадесет минути"
|
||||
, "15'"
|
||||
]
|
||||
, examples (DurationData 30 Minute)
|
||||
[ "30 минути"
|
||||
, "половин час"
|
||||
, "тридесет минути"
|
||||
]
|
||||
, examples (DurationData 90 Minute)
|
||||
[ "час и половина"
|
||||
, "90 мин"
|
||||
]
|
||||
, examples (DurationData 5400 Second)
|
||||
[ "1.5 часа"
|
||||
, "5400 секунди"
|
||||
]
|
||||
, examples (DurationData 8 Hour)
|
||||
[ "8 часа"
|
||||
, "8 ч"
|
||||
, "осем часа"
|
||||
]
|
||||
, examples (DurationData 15 Day)
|
||||
[ "15 дни"
|
||||
, "петнадесет дни"
|
||||
, "половин месец"
|
||||
]
|
||||
, examples (DurationData 7 Week)
|
||||
[ "7 седмици"
|
||||
, "седем седмици"
|
||||
]
|
||||
, examples (DurationData 1 Month)
|
||||
[ "1 месец"
|
||||
, "месец"
|
||||
]
|
||||
, examples (DurationData 6 Month)
|
||||
[ "6 месеца"
|
||||
, "шест месеца"
|
||||
, "половин година"
|
||||
]
|
||||
, examples (DurationData 9072000 Second)
|
||||
[ "3.5 месеца"
|
||||
, "приблизително 3.5 месеца"
|
||||
]
|
||||
, examples (DurationData 30 Month)
|
||||
[ "две години и половина"
|
||||
, "2 години и половина"
|
||||
]
|
||||
, examples (DurationData 3 Quarter)
|
||||
[ "3 тримесечия"
|
||||
]
|
||||
, examples (DurationData 2 Year)
|
||||
[ "2 години"
|
||||
, "две години"
|
||||
]
|
||||
, examples (DurationData 12 Hour)
|
||||
[ "12 часа"
|
||||
, "дванадесет часа"
|
||||
]
|
||||
]
|
134
Duckling/Duration/BG/Rules.hs
Normal file
134
Duckling/Duration/BG/Rules.hs
Normal file
@ -0,0 +1,134 @@
|
||||
-- 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.Duration.BG.Rules
|
||||
( rules
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Data.Text (Text)
|
||||
import Prelude
|
||||
import qualified Data.Text as Text
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Numeral.Helpers (numberWith)
|
||||
import Duckling.Numeral.Types (NumeralData(..), isInteger)
|
||||
import Duckling.Duration.Types (DurationData (DurationData))
|
||||
import Duckling.Regex.Types
|
||||
import Duckling.Types
|
||||
import Duckling.TimeGrain.Types
|
||||
import qualified Duckling.Numeral.Types as TNumeral
|
||||
|
||||
ruleHalves :: Rule
|
||||
ruleHalves = Rule
|
||||
{ name = "half of a <time-grain>"
|
||||
, pattern =
|
||||
[ regex "половин"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Token Duration <$> timesOneAndAHalf grain 0
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleGrainAndAHalf :: Rule
|
||||
ruleGrainAndAHalf = Rule
|
||||
{ name = "<time-grain> and a half"
|
||||
, pattern =
|
||||
[ dimension TimeGrain
|
||||
, regex "и половина"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token TimeGrain grain:_) -> Token Duration <$> timesOneAndAHalf grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationAndAHalf :: Rule
|
||||
ruleDurationAndAHalf = Rule
|
||||
{ name = "<positive-numeral> <time-grain> and a half"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, dimension TimeGrain
|
||||
, regex "и половина"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Numeral NumeralData{TNumeral.value = v}:
|
||||
Token TimeGrain grain:
|
||||
_) -> timesOneAndAHalf grain (floor $ v) >>= Just . Token Duration
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleNumeralQuotes :: Rule
|
||||
ruleNumeralQuotes = Rule
|
||||
{ name = "<integer> + '\""
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "(['\"])"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Numeral NumeralData{TNumeral.value = v}:
|
||||
Token RegexMatch (GroupMatch (x:_)):
|
||||
_) -> case x of
|
||||
"'" -> Just . Token Duration . duration Minute $ floor v
|
||||
"\"" -> Just . Token Duration . duration Second $ floor v
|
||||
_ -> Nothing
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationPrecision :: Rule
|
||||
ruleDurationPrecision = Rule
|
||||
{ name = "about|exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "(към|приблизително|примерно|някъде)"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleGrainAsDuration :: Rule
|
||||
ruleGrainAsDuration = Rule
|
||||
{ name = "a <unit-of-duration>"
|
||||
, pattern =
|
||||
[ dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token TimeGrain grain:_) -> Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rulePositiveDuration :: Rule
|
||||
rulePositiveDuration = Rule
|
||||
{ name = "<positive-numeral> <time-grain>"
|
||||
, pattern =
|
||||
[ numberWith TNumeral.value $ and . sequence [not . isInteger, (>0)]
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Numeral NumeralData{TNumeral.value = v}:
|
||||
Token TimeGrain grain:
|
||||
_) -> Just . Token Duration . duration Second . floor $ inSeconds grain v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDurationAndAHalf
|
||||
, ruleGrainAndAHalf
|
||||
, rulePositiveDuration
|
||||
, ruleDurationPrecision
|
||||
, ruleNumeralQuotes
|
||||
, ruleGrainAsDuration
|
||||
, ruleHalves
|
||||
]
|
262
Duckling/Ordinal/BG/Corpus.hs
Normal file
262
Duckling/Ordinal/BG/Corpus.hs
Normal file
@ -0,0 +1,262 @@
|
||||
-- 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.BG.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 BG Nothing}, testOptions, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (OrdinalData 1)
|
||||
[ "първи"
|
||||
, "първите"
|
||||
, "първия"
|
||||
, "първият"
|
||||
, "първо"
|
||||
, "първото"
|
||||
, "първа"
|
||||
, "първата"
|
||||
, "1ви"
|
||||
, "1-ви"
|
||||
, "1вите"
|
||||
, "1-вите"
|
||||
, "1вия"
|
||||
, "1-вия"
|
||||
, "1вият"
|
||||
, "1-вият"
|
||||
, "1во"
|
||||
, "1-во"
|
||||
, "1вото"
|
||||
, "1-вото"
|
||||
, "1ва"
|
||||
, "1-ва"
|
||||
, "1вата"
|
||||
, "1-вата"
|
||||
]
|
||||
, examples (OrdinalData 3)
|
||||
[ "трети"
|
||||
, "третите"
|
||||
, "третия"
|
||||
, "третият"
|
||||
, "трето"
|
||||
, "третото"
|
||||
, "трета"
|
||||
, "третата"
|
||||
, "3ти"
|
||||
, "3-ти"
|
||||
, "3тите"
|
||||
, "3-тите"
|
||||
, "3тия"
|
||||
, "3-тия"
|
||||
, "3тият"
|
||||
, "3-тият"
|
||||
, "3то"
|
||||
, "3-то"
|
||||
, "3тото"
|
||||
, "3-тото"
|
||||
, "3та"
|
||||
, "3-та"
|
||||
, "3тата"
|
||||
, "3-тата"
|
||||
]
|
||||
, examples (OrdinalData 8)
|
||||
[ "осми"
|
||||
, "осмите"
|
||||
, "осмия"
|
||||
, "осмият"
|
||||
, "осмо"
|
||||
, "осмото"
|
||||
, "осма"
|
||||
, "осмата"
|
||||
, "8ми"
|
||||
, "8-ми"
|
||||
, "8мите"
|
||||
, "8-мите"
|
||||
, "8мия"
|
||||
, "8-мия"
|
||||
, "8мият"
|
||||
, "8-мият"
|
||||
, "8мо"
|
||||
, "8-мо"
|
||||
, "8мото"
|
||||
, "8-мото"
|
||||
, "8ма"
|
||||
, "8-ма"
|
||||
, "8мата"
|
||||
, "8-мата"
|
||||
]
|
||||
, examples (OrdinalData 15)
|
||||
[ "петнадесети"
|
||||
, "петнадесетите"
|
||||
, "петнадесетия"
|
||||
, "петнадесетият"
|
||||
, "петнадесето"
|
||||
, "петнадесетото"
|
||||
, "петнадесета"
|
||||
, "петнадесетата"
|
||||
, "15ти"
|
||||
, "15-ти"
|
||||
, "15тите"
|
||||
, "15-тите"
|
||||
, "15тия"
|
||||
, "15-тия"
|
||||
, "15тият"
|
||||
, "15-тият"
|
||||
, "15то"
|
||||
, "15-то"
|
||||
, "15тото"
|
||||
, "15-тото"
|
||||
, "15та"
|
||||
, "15-та"
|
||||
, "15тата"
|
||||
, "15-тата"
|
||||
]
|
||||
, examples (OrdinalData 21)
|
||||
[ "двадесет и първи"
|
||||
, "двадесет и първите"
|
||||
, "двадесет и първия"
|
||||
, "двадесет и първият"
|
||||
, "двадесет и първо"
|
||||
, "двадесет и първото"
|
||||
, "двадесет и първа"
|
||||
, "двадесет и първата"
|
||||
, "21ви"
|
||||
, "21-ви"
|
||||
, "21вите"
|
||||
, "21-вите"
|
||||
, "21вия"
|
||||
, "21-вия"
|
||||
, "21вият"
|
||||
, "21-вият"
|
||||
, "21во"
|
||||
, "21-во"
|
||||
, "21вото"
|
||||
, "21-вото"
|
||||
, "21ва"
|
||||
, "21-ва"
|
||||
, "21вата"
|
||||
, "21-вата"
|
||||
]
|
||||
, examples (OrdinalData 23)
|
||||
[ "двадесет и трети"
|
||||
, "двадесет и третите"
|
||||
, "двадесет и третия"
|
||||
, "двадесет и третият"
|
||||
, "двадесет и трето"
|
||||
, "двадесет и третото"
|
||||
, "двадесет и трета"
|
||||
, "двадесет и третата"
|
||||
, "23ти"
|
||||
, "23-ти"
|
||||
, "23тите"
|
||||
, "23-тите"
|
||||
, "23тия"
|
||||
, "23-тия"
|
||||
, "23тият"
|
||||
, "23-тият"
|
||||
, "23то"
|
||||
, "23-то"
|
||||
, "23тото"
|
||||
, "23-тото"
|
||||
, "23та"
|
||||
, "23-та"
|
||||
, "23тата"
|
||||
, "23-тата"
|
||||
]
|
||||
, examples (OrdinalData 31)
|
||||
[ "тридесет и първи"
|
||||
, "тридесет и първите"
|
||||
, "тридесет и първия"
|
||||
, "тридесет и първият"
|
||||
, "тридесет и първо"
|
||||
, "тридесет и първото"
|
||||
, "тридесет и първа"
|
||||
, "тридесет и първата"
|
||||
, "31ви"
|
||||
, "31-ви"
|
||||
, "31вите"
|
||||
, "31-вите"
|
||||
, "31вия"
|
||||
, "31-вия"
|
||||
, "31вият"
|
||||
, "31-вият"
|
||||
, "31во"
|
||||
, "31-во"
|
||||
, "31вото"
|
||||
, "31-вото"
|
||||
, "31ва"
|
||||
, "31-ва"
|
||||
, "31вата"
|
||||
, "31-вата"
|
||||
]
|
||||
, examples (OrdinalData 48)
|
||||
[ "четирдесет и осми"
|
||||
, "четирдесет и осмите"
|
||||
, "четирдесет и осмия"
|
||||
, "четирдесет и осмият"
|
||||
, "четирдесет и осмо"
|
||||
, "четирдесет и осмото"
|
||||
, "четирдесет и осма"
|
||||
, "четирдесет и осмата"
|
||||
, "48ми"
|
||||
, "48-ми"
|
||||
, "48мите"
|
||||
, "48-мите"
|
||||
, "48мия"
|
||||
, "48-мия"
|
||||
, "48мият"
|
||||
, "48-мият"
|
||||
, "48мо"
|
||||
, "48-мо"
|
||||
, "48мото"
|
||||
, "48-мото"
|
||||
, "48ма"
|
||||
, "48-ма"
|
||||
, "48мата"
|
||||
, "48-мата"
|
||||
]
|
||||
, examples (OrdinalData 99)
|
||||
[ "деветдесет и девети"
|
||||
, "деветдесет и деветите"
|
||||
, "деветдесет и деветия"
|
||||
, "деветдесет и деветият"
|
||||
, "деветдесет и девето"
|
||||
, "деветдесет и деветото"
|
||||
, "деветдесет и девета"
|
||||
, "деветдесет и деветата"
|
||||
, "99ти"
|
||||
, "99-ти"
|
||||
, "99тите"
|
||||
, "99-тите"
|
||||
, "99тия"
|
||||
, "99-тия"
|
||||
, "99тият"
|
||||
, "99-тият"
|
||||
, "99то"
|
||||
, "99-то"
|
||||
, "99тото"
|
||||
, "99-тото"
|
||||
, "99та"
|
||||
, "99-та"
|
||||
, "99тата"
|
||||
, "99-тата"
|
||||
]
|
||||
]
|
111
Duckling/Ordinal/BG/Rules.hs
Normal file
111
Duckling/Ordinal/BG/Rules.hs
Normal file
@ -0,0 +1,111 @@
|
||||
-- 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 NoRebindableSyntax #-}
|
||||
|
||||
module Duckling.Ordinal.BG.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 )
|
||||
, ( "втор" , 2 )
|
||||
, ( "трет" , 3 )
|
||||
, ( "четвърт" , 4 )
|
||||
, ( "пет" , 5 )
|
||||
, ( "шест" , 6 )
|
||||
, ( "седм" , 7 )
|
||||
, ( "осм" , 8 )
|
||||
, ( "девет" , 9 )
|
||||
, ( "десет" , 10 )
|
||||
, ( "единадесет" , 11 )
|
||||
, ( "дванадесет" , 12 )
|
||||
, ( "тринадесет" , 13 )
|
||||
, ( "четиринадесет", 14 )
|
||||
, ( "петнадесет" , 15 )
|
||||
, ( "шестнадесет" , 16 )
|
||||
, ( "седемнадесет" , 17 )
|
||||
, ( "осемнадесет" , 18 )
|
||||
, ( "деветнадесет" , 19 )
|
||||
, ( "двадесет" , 20 )
|
||||
]
|
||||
|
||||
ruleOrdinalsFirstth :: Rule
|
||||
ruleOrdinalsFirstth = Rule
|
||||
{ name = "ordinals (first..19th)"
|
||||
, pattern =
|
||||
[ regex "(първ|втор|трет|четвърт|пет|шест|седм|осм|девет|десет|единадесет|дванадесет|тринадесет|четиринадесет|петнадесет|шестнадесет|седемнадесет|осемнадесет|деветнадесет|двадесет)(и(я(т)?|те)?|а(та)?|о(то)?)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (match:_)):_) ->
|
||||
ordinal <$> HashMap.lookup (Text.toLower match) ordinalsMap
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
dozensMap :: HashMap Text Int
|
||||
dozensMap = HashMap.fromList
|
||||
[ ( "двадесет" , 20 )
|
||||
, ( "тридесет" , 30 )
|
||||
, ( "четирдесет", 40 )
|
||||
, ( "петдесет" , 50 )
|
||||
, ( "шестдесет" , 60 )
|
||||
, ( "седемдесет", 70 )
|
||||
, ( "осемдесет" , 80 )
|
||||
, ( "деветдесет", 90 )
|
||||
]
|
||||
|
||||
ruleOrdinal :: Rule
|
||||
ruleOrdinal = Rule
|
||||
{ name = "ordinal 21..99"
|
||||
, pattern =
|
||||
[ regex "(двадесет|тридесет|четирдесет|петдесет|шестдесет|седемдесет|осемдесет|деветдесет)"
|
||||
, regex "и (първ|втор|трет|четвърт|пет|шест|седм|осм|девет)(и(ят?|те)?|а(та)?|о(то)?)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (m1:_)):
|
||||
Token RegexMatch (GroupMatch (m2:_)):
|
||||
_) -> do
|
||||
dozen <- HashMap.lookup (Text.toLower m1) dozensMap
|
||||
unit <- HashMap.lookup (Text.toLower m2) ordinalsMap
|
||||
Just . ordinal $ dozen + unit
|
||||
_ -> 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 =
|
||||
[ ruleOrdinal
|
||||
, ruleOrdinalDigits
|
||||
, ruleOrdinalsFirstth
|
||||
]
|
@ -9,10 +9,11 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Duckling.Ordinal.EN.Corpus
|
||||
( corpus ) where
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Ordinal.Types
|
||||
import Duckling.Testing.Types
|
||||
|
@ -70,7 +70,6 @@ cardinalsMap = HashMap.fromList
|
||||
, ( "ninety", 90 )
|
||||
]
|
||||
|
||||
|
||||
ruleOrdinals :: Rule
|
||||
ruleOrdinals = Rule
|
||||
{ name = "ordinals (first..twentieth,thirtieth,...)"
|
||||
|
@ -8,14 +8,15 @@
|
||||
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE NoRebindableSyntax #-}
|
||||
|
||||
module Duckling.Ordinal.RU.Rules
|
||||
( rules ) where
|
||||
( rules
|
||||
) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import qualified Data.Text as Text
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Prelude
|
||||
import qualified Data.Text as Text
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Numeral.Helpers (parseInt)
|
||||
|
@ -320,10 +320,10 @@ classifiers
|
||||
unseen = -4.31748811353631,
|
||||
likelihoods =
|
||||
HashMap.fromList
|
||||
[("<integer> (latent time-of-day)", -0.9718605830289658),
|
||||
[("<integer> (latent time-of-day)", -0.9718605830289657),
|
||||
("intersect by \"di\", \"della\", \"del\"", -3.20545280453606),
|
||||
("day", -2.3581549441488563), ("Lunedi", -3.6109179126442243),
|
||||
("hour", -0.9718605830289658),
|
||||
("hour", -0.9718605830289657),
|
||||
("two time tokens separated by `di`", -3.20545280453606),
|
||||
("Domenica", -3.6109179126442243)],
|
||||
n = 33}}),
|
||||
|
@ -18,7 +18,7 @@ module Duckling.Resolve
|
||||
, toUTC
|
||||
) where
|
||||
|
||||
import Data.Aeson
|
||||
import Data.Aeson (ToJSON)
|
||||
import Prelude
|
||||
import qualified Data.Time as Time
|
||||
import qualified Data.Time.LocalTime.TimeZone.Series as Series
|
||||
|
@ -21,6 +21,9 @@ import Duckling.Types
|
||||
import qualified Duckling.Numeral.BG.Rules as Numeral
|
||||
import qualified Duckling.AmountOfMoney.BG.Rules as AmountOfMoney
|
||||
import qualified Duckling.Distance.BG.Rules as Distance
|
||||
import qualified Duckling.Duration.BG.Rules as Duration
|
||||
import qualified Duckling.TimeGrain.BG.Rules as TimeGrain
|
||||
import qualified Duckling.Ordinal.BG.Rules as Ordinal
|
||||
|
||||
defaultRules :: Some Dimension -> [Rule]
|
||||
defaultRules = langRules
|
||||
@ -31,15 +34,15 @@ localeRules _ _ = []
|
||||
langRules :: Some Dimension -> [Rule]
|
||||
langRules (This AmountOfMoney) = AmountOfMoney.rules
|
||||
langRules (This Distance) = Distance.rules
|
||||
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 TimeGrain) = TimeGrain.rules
|
||||
langRules (This Url) = []
|
||||
langRules (This Volume) = []
|
||||
|
41
Duckling/TimeGrain/BG/Rules.hs
Normal file
41
Duckling/TimeGrain/BG/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 OverloadedStrings #-}
|
||||
|
||||
module Duckling.TimeGrain.BG.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 = \_ -> Just $ Token TimeGrain grain
|
||||
}
|
@ -9,15 +9,16 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Duckling.TimeGrain.EN.Rules
|
||||
( rules ) where
|
||||
( rules
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Data.Text (Text)
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
|
||||
grains :: [(Text, String, TG.Grain)]
|
||||
grains = [ ("second (grain) ", "sec(ond)?s?", TG.Second)
|
||||
@ -26,8 +27,8 @@ grains = [ ("second (grain) ", "sec(ond)?s?", TG.Second)
|
||||
, ("day (grain)" , "days?", TG.Day)
|
||||
, ("week (grain)" , "weeks?", TG.Week)
|
||||
, ("month (grain)" , "months?", TG.Month)
|
||||
, ("quarter (grain)", "(quarter|qtr)s?", TG.Quarter)
|
||||
, ("year (grain)" , "y(ea)?rs?", TG.Year)
|
||||
, ("quarter (grain)", "(quarter|qtr)s?", TG.Quarter)
|
||||
, ("year (grain)" , "y(ea)?rs?", TG.Year)
|
||||
]
|
||||
|
||||
rules :: [Rule]
|
||||
|
@ -232,6 +232,8 @@ library
|
||||
-- Duration
|
||||
, Duckling.Duration.AR.Corpus
|
||||
, Duckling.Duration.AR.Rules
|
||||
, Duckling.Duration.BG.Corpus
|
||||
, Duckling.Duration.BG.Rules
|
||||
, Duckling.Duration.DA.Rules
|
||||
, Duckling.Duration.DE.Rules
|
||||
, Duckling.Duration.EL.Corpus
|
||||
@ -357,6 +359,8 @@ library
|
||||
-- Ordinal
|
||||
, Duckling.Ordinal.AR.Corpus
|
||||
, Duckling.Ordinal.AR.Rules
|
||||
, Duckling.Ordinal.BG.Corpus
|
||||
, Duckling.Ordinal.BG.Rules
|
||||
, Duckling.Ordinal.DA.Corpus
|
||||
, Duckling.Ordinal.DA.Rules
|
||||
, Duckling.Ordinal.DE.Corpus
|
||||
@ -559,6 +563,7 @@ library
|
||||
|
||||
-- TimeGrain
|
||||
, Duckling.TimeGrain.AR.Rules
|
||||
, Duckling.TimeGrain.BG.Rules
|
||||
, Duckling.TimeGrain.DA.Rules
|
||||
, Duckling.TimeGrain.DE.Rules
|
||||
, Duckling.TimeGrain.EN.Rules
|
||||
@ -698,6 +703,7 @@ test-suite duckling-test
|
||||
|
||||
-- Duration
|
||||
, Duckling.Duration.AR.Tests
|
||||
, Duckling.Duration.BG.Tests
|
||||
, Duckling.Duration.EL.Tests
|
||||
, Duckling.Duration.EN.Tests
|
||||
, Duckling.Duration.FR.Tests
|
||||
@ -761,6 +767,7 @@ test-suite duckling-test
|
||||
|
||||
-- Ordinal
|
||||
, Duckling.Ordinal.AR.Tests
|
||||
, Duckling.Ordinal.BG.Tests
|
||||
, Duckling.Ordinal.DA.Tests
|
||||
, Duckling.Ordinal.DE.Tests
|
||||
, Duckling.Ordinal.EL.Tests
|
||||
|
@ -17,6 +17,7 @@ import Test.Tasty
|
||||
import qualified Duckling.Distance.BG.Tests as BG
|
||||
import qualified Duckling.Distance.CS.Tests as CS
|
||||
import qualified Duckling.Distance.EN.Tests as EN
|
||||
import qualified Duckling.Distance.BG.Tests as BG
|
||||
import qualified Duckling.Distance.ES.Tests as ES
|
||||
import qualified Duckling.Distance.FR.Tests as FR
|
||||
import qualified Duckling.Distance.GA.Tests as GA
|
||||
|
24
tests/Duckling/Duration/BG/Tests.hs
Normal file
24
tests/Duckling/Duration/BG/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.Duration.BG.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.BG.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "BG Tests"
|
||||
[ makeCorpusTest [This Duration] corpus
|
||||
]
|
@ -15,6 +15,7 @@ import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import qualified Duckling.Duration.AR.Tests as AR
|
||||
import qualified Duckling.Duration.BG.Tests as BG
|
||||
import qualified Duckling.Duration.EL.Tests as EL
|
||||
import qualified Duckling.Duration.EN.Tests as EN
|
||||
import qualified Duckling.Duration.FR.Tests as FR
|
||||
@ -35,6 +36,7 @@ import qualified Duckling.Duration.ZH.Tests as ZH
|
||||
tests :: TestTree
|
||||
tests = testGroup "Duration Tests"
|
||||
[ AR.tests
|
||||
, BG.tests
|
||||
, EL.tests
|
||||
, EN.tests
|
||||
, FR.tests
|
||||
|
23
tests/Duckling/Ordinal/BG/Tests.hs
Normal file
23
tests/Duckling/Ordinal/BG/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.BG.Tests
|
||||
( tests ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Ordinal.BG.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "BG Tests"
|
||||
[ makeCorpusTest [This Ordinal] corpus
|
||||
]
|
@ -13,6 +13,7 @@ import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import qualified Duckling.Ordinal.AR.Tests as AR
|
||||
import qualified Duckling.Ordinal.BG.Tests as BG
|
||||
import qualified Duckling.Ordinal.DA.Tests as DA
|
||||
import qualified Duckling.Ordinal.DE.Tests as DE
|
||||
import qualified Duckling.Ordinal.EL.Tests as EL
|
||||
@ -44,6 +45,7 @@ import qualified Duckling.Ordinal.ZH.Tests as ZH
|
||||
tests :: TestTree
|
||||
tests = testGroup "Ordinal Tests"
|
||||
[ AR.tests
|
||||
, BG.tests
|
||||
, DA.tests
|
||||
, DE.tests
|
||||
, EL.tests
|
||||
|
Loading…
Reference in New Issue
Block a user