mirror of
https://github.com/facebook/duckling.git
synced 2024-11-30 23:33:33 +03:00
Support Dutch Durations
Summary: This change adds support for durations in Dutch/Netherlands (NL) Implemented: TimeGrain/NL, Durations/NL Reviewed By: patapizza Differential Revision: D6049404 fbshipit-source-id: 3621cdb
This commit is contained in:
parent
ab0ad0256e
commit
33a08bb76b
@ -15,6 +15,7 @@ import Duckling.Dimensions.Types
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ This Distance
|
||||
, This Duration
|
||||
, This Numeral
|
||||
, This Ordinal
|
||||
, This Volume
|
||||
|
83
Duckling/Duration/NL/Corpus.hs
Normal file
83
Duckling/Duration/NL/Corpus.hs
Normal file
@ -0,0 +1,83 @@
|
||||
-- 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.NL.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(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {locale = makeLocale NL Nothing}, allExamples)
|
||||
|
||||
negativeCorpus :: NegativeCorpus
|
||||
negativeCorpus = (testContext {locale = makeLocale NL Nothing}, examples)
|
||||
where
|
||||
examples =
|
||||
[ "voor maanden"
|
||||
, "in enkele dagen"
|
||||
, "secretaris"
|
||||
, "last minute"
|
||||
, "12 uurtje"
|
||||
]
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "een seconde"
|
||||
, "één seconde"
|
||||
, "1 secondes"
|
||||
, "1 s"
|
||||
, "1\""
|
||||
]
|
||||
, examples (DurationData 14 Second)
|
||||
[ "veertien seconden"
|
||||
, "14 s"
|
||||
]
|
||||
, examples (DurationData 2 Minute)
|
||||
[ "2 min"
|
||||
, "twee minuten"
|
||||
, "2 m"
|
||||
, "2'"
|
||||
]
|
||||
, examples (DurationData 30 Day)
|
||||
[ "30 dagen"
|
||||
]
|
||||
, examples (DurationData 7 Week)
|
||||
[ "zeven weken"
|
||||
, "7 w"
|
||||
]
|
||||
, examples (DurationData 1 Month)
|
||||
[ "1 mnd"
|
||||
, "een maand"
|
||||
, "één maand"
|
||||
]
|
||||
, examples (DurationData 3 Quarter)
|
||||
[ "drie kwartier"
|
||||
]
|
||||
, examples (DurationData 2 Year)
|
||||
[ "2 jaar"
|
||||
, "2 jaren"
|
||||
, "twee jaren"
|
||||
, "2 j"
|
||||
]
|
||||
, examples (DurationData 150 Minute)
|
||||
[ "twee en een half uur"
|
||||
, "2,5 uur"
|
||||
]
|
||||
]
|
114
Duckling/Duration/NL/Rules.hs
Normal file
114
Duckling/Duration/NL/Rules.hs
Normal file
@ -0,0 +1,114 @@
|
||||
-- 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.NL.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import Prelude
|
||||
import Data.String
|
||||
import qualified Data.Text as Text
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Numeral.Helpers (parseInt, parseInteger)
|
||||
import Duckling.Numeral.Types (NumeralData(..))
|
||||
import Duckling.Regex.Types
|
||||
import Duckling.Types
|
||||
import qualified Duckling.Numeral.Types as TNumeral
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
|
||||
ruleDurationQuarterOfAnHour :: Rule
|
||||
ruleDurationQuarterOfAnHour = Rule
|
||||
{ name = "quarter of an hour"
|
||||
, pattern = [ regex "1/4\\s?uur"]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 15
|
||||
}
|
||||
|
||||
ruleDurationHalfAnHour :: Rule
|
||||
ruleDurationHalfAnHour = Rule
|
||||
{ name = "half an hour"
|
||||
, pattern = [regex "(1/2\\s?uur|half uur)"]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleDurationThreeQuartersOfAnHour :: Rule
|
||||
ruleDurationThreeQuartersOfAnHour = Rule
|
||||
{ name = "three-quarters of an hour"
|
||||
, pattern = [regex "3/4\\s?uur"]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 45
|
||||
}
|
||||
|
||||
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 TG.Minute $ floor v
|
||||
"\"" -> Just . Token Duration . duration TG.Second $ floor v
|
||||
_ -> Nothing
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationDotNumeralHours :: Rule
|
||||
ruleDurationDotNumeralHours = Rule
|
||||
{ name = "number,number uur"
|
||||
, pattern = [regex "(\\d+)\\,(\\d+) *(uur|uren)"]
|
||||
, 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
|
||||
}
|
||||
|
||||
ruleDurationAndHalfHour :: Rule
|
||||
ruleDurationAndHalfHour = Rule
|
||||
{ name = "<integer> and an half hour"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "en een half (uur|uren)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Numeral (NumeralData {TNumeral.value = v}):_) ->
|
||||
Just . Token Duration . duration TG.Minute $ 30 + 60 * floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationPrecision :: Rule
|
||||
ruleDurationPrecision = Rule
|
||||
{ name = "about|exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "(ongeveer|precies|plusminus|exact)"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDurationQuarterOfAnHour
|
||||
, ruleDurationHalfAnHour
|
||||
, ruleDurationThreeQuartersOfAnHour
|
||||
, ruleDurationDotNumeralHours
|
||||
, ruleDurationAndHalfHour
|
||||
, ruleDurationPrecision
|
||||
, ruleNumeralQuotes
|
||||
]
|
@ -47,6 +47,10 @@ allExamples = concat
|
||||
, "drie en dertig"
|
||||
, "0033"
|
||||
]
|
||||
, examples (NumeralValue 12)
|
||||
[ "twaalf"
|
||||
, "dozijn"
|
||||
]
|
||||
, examples (NumeralValue 14)
|
||||
[ "14"
|
||||
, "veertien"
|
||||
@ -80,6 +84,9 @@ allExamples = concat
|
||||
[ "5 duizend"
|
||||
, "vijf duizend"
|
||||
]
|
||||
, examples (NumeralValue 144)
|
||||
[ "gros"
|
||||
]
|
||||
, examples (NumeralValue 122)
|
||||
[ "honderd tweeëntwintig"
|
||||
, "honderd tweeentwintig"
|
||||
|
@ -205,6 +205,15 @@ ruleDozen = Rule
|
||||
, prod = \_ -> integer 12 >>= withGrain 1
|
||||
}
|
||||
|
||||
ruleGross :: Rule
|
||||
ruleGross = Rule
|
||||
{ name = "gros"
|
||||
, pattern =
|
||||
[ regex "gros"
|
||||
]
|
||||
, prod = \_ -> integer 144 >>= withGrain 1
|
||||
}
|
||||
|
||||
zeroNineteenMap :: HashMap Text Integer
|
||||
zeroNineteenMap = HashMap.fromList
|
||||
[ ("niks", 0)
|
||||
@ -274,6 +283,7 @@ rules =
|
||||
, ruleDecimalNumeral
|
||||
, ruleDecimalWithThousandsSeparator
|
||||
, ruleDozen
|
||||
, ruleGross
|
||||
, ruleFew
|
||||
, ruleInteger
|
||||
, ruleInteger2
|
||||
|
@ -19,8 +19,10 @@ import Duckling.Dimensions.Types
|
||||
import Duckling.Locale
|
||||
import Duckling.Types
|
||||
import qualified Duckling.Distance.NL.Rules as Distance
|
||||
import qualified Duckling.Duration.NL.Rules as Duration
|
||||
import qualified Duckling.Numeral.NL.Rules as Numeral
|
||||
import qualified Duckling.Ordinal.NL.Rules as Ordinal
|
||||
import qualified Duckling.TimeGrain.NL.Rules as TimeGrain
|
||||
import qualified Duckling.Volume.NL.Rules as Volume
|
||||
|
||||
defaultRules :: Some Dimension -> [Rule]
|
||||
@ -32,7 +34,7 @@ localeRules _ _ = []
|
||||
langRules :: Some Dimension -> [Rule]
|
||||
langRules (This AmountOfMoney) = []
|
||||
langRules (This Distance) = Distance.rules
|
||||
langRules (This Duration) = []
|
||||
langRules (This Duration) = Duration.rules
|
||||
langRules (This Email) = []
|
||||
langRules (This Numeral) = Numeral.rules
|
||||
langRules (This Ordinal) = Ordinal.rules
|
||||
@ -41,6 +43,6 @@ 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) = Volume.rules
|
||||
|
40
Duckling/TimeGrain/NL/Rules.hs
Normal file
40
Duckling/TimeGrain/NL/Rules.hs
Normal file
@ -0,0 +1,40 @@
|
||||
-- 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.NL.Rules
|
||||
( rules ) where
|
||||
|
||||
import Data.Text (Text)
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
|
||||
grains :: [(Text, String, TG.Grain)]
|
||||
grains = [ ("second (grain) " , "(seconde(n|s)?|sec|s)" , TG.Second)
|
||||
, ("minute (grain)" , "(minuut|minuten|min|m)", TG.Minute)
|
||||
, ("hour (grain)" , "(u|h|uur|uren)", TG.Hour)
|
||||
, ("day (grain)" , "(dagen|dag|d)", TG.Day)
|
||||
, ("week (grain)" , "(weken|week|w)", TG.Week)
|
||||
, ("month (grain)" , "(maanden|maand|mnd)", TG.Month)
|
||||
, ("quarter (grain)" , "kwartier", TG.Quarter)
|
||||
, ("year (grain)" , "(jaren|jaar|j)", TG.Year)
|
||||
]
|
||||
|
||||
rules :: [Rule]
|
||||
rules = map go grains
|
||||
where
|
||||
go (name, regexPattern, grain) = Rule
|
||||
{ name = name
|
||||
, pattern = [regex regexPattern]
|
||||
, prod = \_ -> Just $ Token TimeGrain grain
|
||||
}
|
@ -223,6 +223,8 @@ library
|
||||
, Duckling.Duration.KO.Rules
|
||||
, Duckling.Duration.NB.Corpus
|
||||
, Duckling.Duration.NB.Rules
|
||||
, Duckling.Duration.NL.Corpus
|
||||
, Duckling.Duration.NL.Rules
|
||||
, Duckling.Duration.PL.Corpus
|
||||
, Duckling.Duration.PL.Rules
|
||||
, Duckling.Duration.PT.Corpus
|
||||
@ -289,6 +291,8 @@ library
|
||||
, Duckling.Numeral.MY.Rules
|
||||
, Duckling.Numeral.NB.Corpus
|
||||
, Duckling.Numeral.NB.Rules
|
||||
, Duckling.Numeral.NL.Corpus
|
||||
, Duckling.Numeral.NL.Rules
|
||||
, Duckling.Numeral.PL.Corpus
|
||||
, Duckling.Numeral.PL.Rules
|
||||
, Duckling.Numeral.PT.Corpus
|
||||
@ -305,8 +309,6 @@ library
|
||||
, Duckling.Numeral.VI.Rules
|
||||
, Duckling.Numeral.ZH.Corpus
|
||||
, Duckling.Numeral.ZH.Rules
|
||||
, Duckling.Numeral.NL.Corpus
|
||||
, Duckling.Numeral.NL.Rules
|
||||
, Duckling.Numeral.RO.Corpus
|
||||
, Duckling.Numeral.RO.Rules
|
||||
, Duckling.Numeral.Helpers
|
||||
@ -484,6 +486,7 @@ library
|
||||
, Duckling.TimeGrain.JA.Rules
|
||||
, Duckling.TimeGrain.KO.Rules
|
||||
, Duckling.TimeGrain.NB.Rules
|
||||
, Duckling.TimeGrain.NL.Rules
|
||||
, Duckling.TimeGrain.PL.Rules
|
||||
, Duckling.TimeGrain.PT.Rules
|
||||
, Duckling.TimeGrain.RO.Rules
|
||||
@ -605,6 +608,7 @@ test-suite duckling-test
|
||||
, Duckling.Duration.JA.Tests
|
||||
, Duckling.Duration.KO.Tests
|
||||
, Duckling.Duration.NB.Tests
|
||||
, Duckling.Duration.NL.Tests
|
||||
, Duckling.Duration.PL.Tests
|
||||
, Duckling.Duration.PT.Tests
|
||||
, Duckling.Duration.RO.Tests
|
||||
|
25
tests/Duckling/Duration/NL/Tests.hs
Normal file
25
tests/Duckling/Duration/NL/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.NL.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.NL.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "NL Tests"
|
||||
[ makeCorpusTest [This Duration] corpus
|
||||
, makeNegativeCorpusTest [This Duration] negativeCorpus
|
||||
]
|
@ -21,6 +21,7 @@ import qualified Duckling.Duration.HU.Tests as HU
|
||||
import qualified Duckling.Duration.JA.Tests as JA
|
||||
import qualified Duckling.Duration.KO.Tests as KO
|
||||
import qualified Duckling.Duration.NB.Tests as NB
|
||||
import qualified Duckling.Duration.NL.Tests as NL
|
||||
import qualified Duckling.Duration.PL.Tests as PL
|
||||
import qualified Duckling.Duration.PT.Tests as PT
|
||||
import qualified Duckling.Duration.RO.Tests as RO
|
||||
@ -37,6 +38,7 @@ tests = testGroup "Duration Tests"
|
||||
, JA.tests
|
||||
, KO.tests
|
||||
, NB.tests
|
||||
, NL.tests
|
||||
, PL.tests
|
||||
, PT.tests
|
||||
, RO.tests
|
||||
|
Loading…
Reference in New Issue
Block a user