Add Volume/KM and Distance/KM (#256)

Summary:
Hello.
I have updated Quantity/KM and added 3 more dimensions (Volume/KM, Time/KM, and Distance/KM) for KM.
Please take a look at it.
Pull Request resolved: https://github.com/facebook/duckling/pull/256

Reviewed By: patapizza

Differential Revision: D9758093

Pulled By: xhavokx

fbshipit-source-id: 5a800fd443789795b8e63c88dade3785cfca706c
This commit is contained in:
PhalPheaktra Chhaya 2018-10-31 16:32:10 -07:00 committed by Facebook Github Bot
parent d0425f15d0
commit 3374f4ea50
13 changed files with 749 additions and 9 deletions

View File

@ -14,8 +14,10 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ This Numeral
[ This Distance
, This Numeral
, This Ordinal
, This Quantity
, This Temperature
, This Volume
]

View File

@ -0,0 +1,60 @@
-- 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.Distance.KM.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Distance.Types
import Duckling.Resolve
import Duckling.Testing.Types
context :: Context
context = testContext{locale = makeLocale KM Nothing}
corpus :: Corpus
corpus = (context, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Kilometre 3)
[ "3 km"
, "៣គីឡូ"
, "បីគីឡូម៉ែត្រ"
]
, examples (simple Centimetre 2)
[ "2cm"
, "២សង់ទីម៉ែត្រ"
, "ពីរសង់ទីម៉ែត្រ"
]
, examples (between Metre (3, 5))
[ "ចាប់ពី 3 ដល់ 5 m"
, "ចន្លោះពី ៣ ដល់ ៥ម៉ែត្រ"
, "ចន្លោះ ៣ម៉ែត្រ និង ៥ម៉ែត្រ"
, "ប្រហែល ៣-៥ ម៉ែត្រ"
, "~3-5ម៉ែត្រ"
]
, examples (under Centimetre 4)
[ "តិចជាងបួនសង់ទីម៉ែត្រ"
, "មិនលើស៤សង់ទីម៉ែត្រ"
, "ក្រោម៤សង់ទីម៉ែត្រ"
, "យ៉ាងច្រើន៤សង់ទីម៉ែត្រ"
]
, examples (above Millimetre 10)
[ "ច្រើនជាងដប់មីលីម៉ែត្រ"
, "មិនតិចជាងដប់មីលីម៉ែត្រ"
, "លើសពីដប់មីលីម៉ែត្រ"
, "យ៉ាងតិចដប់មីលីម៉ែត្រ"
]
]

View File

@ -0,0 +1,179 @@
-- 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 #-}
module Duckling.Distance.KM.Rules
( rules
) where
import Data.String
import Data.Text (Text)
import Prelude
import Duckling.Dimensions.Types
import Duckling.Distance.Helpers
import Duckling.Distance.Types (DistanceData(..))
import Duckling.Numeral.Helpers
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Types
import qualified Duckling.Distance.Types as TDistance
import qualified Duckling.Numeral.Types as TNumeral
distances :: [(Text, String, TDistance.Unit)]
distances = [ ("km", "km|គីឡូ(ម៉ែត្រ)?", TDistance.Kilometre)
, ("meters", "m|ម៉ែត្រ", TDistance.Metre)
, ("centimeters", "cm|សង់ទីម៉ែត្រ", TDistance.Centimetre)
, ("millimeters", "mm|មីលីម៉ែត្រ", TDistance.Millimetre)
]
rulePrecision :: Rule
rulePrecision = Rule
{ name = "about|exactly <dist>"
, pattern =
[ regex "\\~|ប្រហែល"
, dimension Distance
]
, prod = \case
(_:token:_) -> Just token
_ -> Nothing
}
ruleDistances :: [Rule]
ruleDistances = map go distances
where
go :: (Text, String, TDistance.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern = [ dimension Distance, regex regexPattern ]
, prod = \case
(Token Distance dd:_) -> Just . Token Distance $ withUnit u dd
_ -> Nothing
}
ruleIntervalBetweenNumeral :: Rule
ruleIntervalBetweenNumeral = Rule
{ name = "between|from <numeral> to|and <dist>"
, pattern =
[ regex "ចន្លោះ(ពី)?|ចាប់ពី"
, Predicate isPositive
, regex "និង|ដល់"
, Predicate isSimpleDistance
]
, prod = \case
(_:
Token Numeral NumeralData{TNumeral.value = from}:
_:
Token Distance DistanceData{TDistance.value = Just to,
TDistance.unit = Just u}:
_) | from < to ->
Just . Token Distance . withInterval (from, to) $ unitOnly u
_ -> Nothing
}
ruleIntervalBetween :: Rule
ruleIntervalBetween = Rule
{ name = "between|from <dist> to|and <dist>"
, pattern =
[ regex "ចន្លោះ(ពី)?|ចាប់ពី"
, Predicate isSimpleDistance
, regex "និង|ដល់"
, Predicate isSimpleDistance
]
, prod = \case
(_:
Token Distance DistanceData{TDistance.value = Just from,
TDistance.unit = Just u1}:
_:
Token Distance DistanceData{TDistance.value = Just to,
TDistance.unit = Just u2}:
_) | from < to && u1 == u2 ->
Just . Token Distance . withInterval (from, to) $ unitOnly u1
_ -> Nothing
}
ruleIntervalNumeralDash :: Rule
ruleIntervalNumeralDash = Rule
{ name = "<numeral> - <dist>"
, pattern =
[ Predicate isPositive
, regex "-"
, Predicate isSimpleDistance
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = from}:
_:
Token Distance DistanceData{TDistance.value = Just to,
TDistance.unit = Just u}:
_) | from < to ->
Just . Token Distance . withInterval (from, to) $ unitOnly u
_ -> Nothing
}
ruleIntervalDash :: Rule
ruleIntervalDash = Rule
{ name = "<dist> - <dist>"
, pattern =
[ Predicate isSimpleDistance
, regex "-"
, Predicate isSimpleDistance
]
, prod = \case
(Token Distance DistanceData{TDistance.value = Just from,
TDistance.unit = Just u1}:
_:
Token Distance DistanceData{TDistance.value = Just to,
TDistance.unit = Just u2}:
_) | from < to && u1 == u2 ->
Just . Token Distance . withInterval (from, to) $ unitOnly u1
_ -> Nothing
}
ruleIntervalMax :: Rule
ruleIntervalMax = Rule
{ name = "Max Rule"
, pattern =
[ regex "ក្រោម|តិចជាង|មិនដល់|យ៉ាងច្រើន|មិនលើស"
, Predicate isSimpleDistance
]
, prod = \case
(_:
Token Distance DistanceData{TDistance.value = Just to,
TDistance.unit = Just u}:
_) -> Just . Token Distance . withMax to $ unitOnly u
_ -> Nothing
}
ruleIntervalMin :: Rule
ruleIntervalMin = Rule
{ name = "Min Rule"
, pattern =
[ regex "លើស(ពី)?|មិនតិចជាង|លើ|ច្រើនជាង|យ៉ាងតិច|យ៉ាងហោច"
, Predicate isSimpleDistance
]
, prod = \case
(_:
Token Distance DistanceData{TDistance.value = Just to,
TDistance.unit = Just u}:
_) -> Just . Token Distance . withMin to $ unitOnly u
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleIntervalBetweenNumeral
, ruleIntervalBetween
, ruleIntervalMax
, ruleIntervalMin
, ruleIntervalNumeralDash
, ruleIntervalDash
, rulePrecision
]
++ ruleDistances

View File

@ -35,6 +35,38 @@ allExamples = concat
[ "១ចាន"
]
, examples (simple Pint 15 Nothing)
[ "ដប់៥ថូ"
[ "ដប់ប្រាំថូ"
]
, examples (simple (Custom "For Persons") 2 (Just "មនុស្ស"))
[ "មនុស្ស២នាក់"
, "មនុស្សពីរនាក់"
]
, examples (simple (Custom "For Buildings") 8 (Just "ផ្ទះ"))
[ "ផ្ទះ៨ខ្នង"
, "ផ្ទះប្រាំបីខ្នង"
]
, examples (simple Gram 1000 Nothing)
[ "មួយពាន់ក្រាម"
, "មួយគីឡូក្រាម"
, "មួយលានមីលីក្រាម"
]
, examples (between Gram (2,7) Nothing)
[ "ចាប់ពី 2 ដល់ 7 ក្រាម"
, "ចន្លោះពី ២ ដល់ ៧ក្រាម"
, "ចន្លោះ ២ក្រាម និង ៧ក្រាម"
, "ប្រហែល ២-៧ ក្រាម"
, "~2-7ក្រាម"
]
, examples (under Tablespoon 4 Nothing)
[ "តិចជាងបួនស្លាបព្រា"
, "មិនលើស៤ស្លាបព្រា"
, "ក្រោម៤ស្លាបព្រា"
, "យ៉ាងច្រើន៤ស្លាបព្រា"
]
, examples (above Bowl 10 Nothing)
[ "ច្រើនជាងដប់ចាន"
, "មិនតិចជាងដប់ចាន"
, "លើសពីដប់ចាន"
, "យ៉ាងតិចដប់ចាន"
]
]

View File

@ -15,17 +15,19 @@ module Duckling.Quantity.KM.Rules
) where
import Data.HashMap.Strict (HashMap)
import Data.Text (Text)
import Data.Text (Text, toLower)
import Data.String
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
import Duckling.Dimensions.Types
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Numeral.Helpers
import Duckling.Quantity.Helpers
import Duckling.Regex.Types
import Duckling.Types
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Quantity.Types (QuantityData(..))
import qualified Duckling.Numeral.Types as TNumeral
import qualified Duckling.Quantity.Types as TQuantity
@ -39,7 +41,7 @@ ruleQuantityOfProduct = Rule
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):
Token Quantity qd:
_) -> Just . Token Quantity $ withProduct (Text.toLower match) qd
_) -> Just . Token Quantity $ withProduct match qd
_ -> Nothing
}
@ -49,6 +51,17 @@ unitsMap = HashMap.fromList
, ("ពែង", TQuantity.Cup)
, ("កែវ", TQuantity.Cup)
, ("ថូ", TQuantity.Pint)
, ("ស្លាបព្រា", TQuantity.Tablespoon)
, ("ស្លាបព្រាបាយ", TQuantity.Tablespoon)
, ("ស្លាបព្រាកាហ្វេ", TQuantity.Teaspoon)
, ("នាក់", TQuantity.Custom "For Persons")
, ("ក្បាល", TQuantity.Custom "For Animals")
, ("ដើម", TQuantity.Custom "For Trees")
, ("ទង", TQuantity.Custom "For Flowers")
, ("ខ្នង", TQuantity.Custom "For Buildings")
, ("គ្រឿង", TQuantity.Custom "For Vehicles/Devices")
, ("កញ្ចប់", TQuantity.Custom "For Packages")
, ("ឈុត", TQuantity.Custom "Sets")
]
ruleNumeralUnits :: Rule
@ -56,19 +69,184 @@ ruleNumeralUnits = Rule
{ name = "<number><units>"
, pattern =
[ dimension Numeral
, regex "(ចាន|ពែង|កែវ|ថូ)"
, regex "(ចាន|ពែង|កែវ|ថូ|ស្លាបព្រា|ស្លាបព្រាបាយ|ស្លាបព្រាកាហ្វេ|នាក់|ក្បាល|ដើម|ទង|ខ្នង|គ្រឿង|កញ្ចប់|ឈុត)"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:
Token RegexMatch (GroupMatch (match:_)):
_) -> do
unit <- HashMap.lookup (Text.toLower match) unitsMap
unit <- HashMap.lookup match unitsMap
Just . Token Quantity $ quantity unit v
_ -> Nothing
}
quantities :: [(Text, String, TQuantity.Unit)]
quantities =
[ ("<quantity> grams", "((មីលី|គីឡូ)?ក្រាម)", TQuantity.Gram)
]
opsMap :: HashMap Text (Double -> Double)
opsMap = HashMap.fromList
[ ( "មីលីក្រាម" , (/ 1000))
, ( "គីឡូក្រាម" , (* 1000))
]
getValue :: Text -> Double -> Double
getValue match = HashMap.lookupDefault id match opsMap
ruleNumeralUnits2 :: [Rule]
ruleNumeralUnits2 = map go quantities
where
go :: (Text, String, TQuantity.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern = [dimension Numeral, regex regexPattern]
, prod = \case
(Token Numeral nd:
Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ quantity u value
where value = getValue match $ TNumeral.value nd
_ -> Nothing
}
rulePrecision :: Rule
rulePrecision = Rule
{ name = "about|exactly <quantity>"
, pattern =
[ regex "\\~|ប្រហែល"
, dimension Quantity
]
, prod = \case
(_:token:_) -> Just token
_ -> Nothing
}
ruleIntervalBetweenNumeral :: Rule
ruleIntervalBetweenNumeral = Rule
{ name = "between|from <numeral> and|to <quantity>"
, pattern =
[ regex "ចន្លោះ(ពី)?|ចាប់ពី"
, Predicate isPositive
, regex "និង|ដល់"
, Predicate isSimpleQuantity
]
, prod = \case
(_:
Token Numeral NumeralData{TNumeral.value = from}:
_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u
, TQuantity.aproduct = Nothing}:
_) | from < to ->
Just . Token Quantity . withInterval (from, to) $ unitOnly u
_ -> Nothing
}
ruleIntervalBetween :: Rule
ruleIntervalBetween = Rule
{ name = "between|from <quantity> to|and <quantity>"
, pattern =
[ regex "ចន្លោះ(ពី)?|ចាប់ពី"
, Predicate isSimpleQuantity
, regex "និង|ដល់"
, Predicate isSimpleQuantity
]
, prod = \case
(_:
Token Quantity QuantityData{TQuantity.value = Just from
, TQuantity.unit = Just u1
, TQuantity.aproduct = Nothing}:
_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u2
, TQuantity.aproduct = Nothing}:
_) | from < to && u1 == u2 ->
Just . Token Quantity . withInterval (from, to) $ unitOnly u1
_ -> Nothing
}
ruleIntervalNumeralDash :: Rule
ruleIntervalNumeralDash = Rule
{ name = "<numeral> - <quantity>"
, pattern =
[ Predicate isPositive
, regex "\\-"
, Predicate isSimpleQuantity
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = from}:
_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u
, TQuantity.aproduct = Nothing}:
_) | from < to ->
Just . Token Quantity . withInterval (from, to) $ unitOnly u
_ -> Nothing
}
ruleIntervalDash :: Rule
ruleIntervalDash = Rule
{ name = "<quantity> - <quantity>"
, pattern =
[ Predicate isSimpleQuantity
, regex "\\-"
, Predicate isSimpleQuantity
]
, prod = \case
(Token Quantity QuantityData{TQuantity.value = Just from
, TQuantity.unit = Just u1
, TQuantity.aproduct = Nothing}:
_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u2
, TQuantity.aproduct = Nothing}:
_) | from < to && u1 == u2 ->
Just . Token Quantity . withInterval (from, to) $ unitOnly u1
_ -> Nothing
}
ruleIntervalMax :: Rule
ruleIntervalMax = Rule
{ name = "Max Rule"
, pattern =
[ regex "ក្រោម|តិចជាង|មិនដល់|យ៉ាងច្រើន|មិនលើស"
, Predicate isSimpleQuantity
]
, prod = \case
(_:
Token Quantity QuantityData{TQuantity.value = Just to
, TQuantity.unit = Just u
, TQuantity.aproduct = Nothing}:
_) -> Just . Token Quantity . withMax to $ unitOnly u
_ -> Nothing
}
ruleIntervalMin :: Rule
ruleIntervalMin = Rule
{ name = "Min Rule"
, pattern =
[ regex "លើស(ពី)?|មិនតិចជាង|លើ|ច្រើនជាង|យ៉ាងតិច|យ៉ាងហោច"
, Predicate isSimpleQuantity
]
, prod = \case
(_:
Token Quantity QuantityData{TQuantity.value = Just from
, TQuantity.unit = Just u
, TQuantity.aproduct = Nothing}:
_) -> Just . Token Quantity . withMin from $ unitOnly u
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleNumeralUnits
, ruleQuantityOfProduct
, rulePrecision
, ruleIntervalBetweenNumeral
, ruleIntervalBetween
, ruleIntervalNumeralDash
, ruleIntervalDash
, ruleIntervalMax
, ruleIntervalMin
]
++ruleNumeralUnits2

View File

@ -18,10 +18,12 @@ module Duckling.Rules.KM
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.Distance.KM.Rules as Distance
import qualified Duckling.Numeral.KM.Rules as Numeral
import qualified Duckling.Ordinal.KM.Rules as Ordinal
import qualified Duckling.Quantity.KM.Rules as Quantity
import qualified Duckling.Temperature.KM.Rules as Temperature
import qualified Duckling.Volume.KM.Rules as Volume
defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules
@ -32,7 +34,7 @@ localeRules _ _ = []
langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = []
langRules (This Distance) = []
langRules (This Distance) = Distance.rules
langRules (This Duration) = []
langRules (This Email) = []
langRules (This Numeral) = Numeral.rules
@ -44,5 +46,5 @@ langRules (This Temperature) = Temperature.rules
langRules (This Time) = []
langRules (This TimeGrain) = []
langRules (This Url) = []
langRules (This Volume) = []
langRules (This Volume) = Volume.rules
langRules (This (CustomDimension dim)) = dimLangRules KM dim

View File

@ -0,0 +1,67 @@
-- 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.Volume.KM.Corpus
( corpus ) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Volume.Types
import Duckling.Testing.Types
context :: Context
context = testContext{locale = makeLocale KM Nothing}
corpus :: Corpus
corpus = (context, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Litre 1)
[ "1 លីត្រ"
, "1l"
, "១លីត្រ"
]
, examples (simple Litre 0.5)
[ "កន្លះលីត្រ"
, "១/២លីត្រ"
]
, examples (simple Litre 0.25)
[ "មួយភាគបួនលីត្រ"
, "១/៤លីត្រ"
]
, examples (simple Millilitre 1)
[ "1 មីលីលីត្រ"
, "1ml"
, "១មីលីលីត្រ"
]
, examples (between Litre (2,7))
[ "ចាប់ពី 2 ដល់ 7 l"
, "ចន្លោះពី ២ ដល់ ៧លីត្រ"
, "ចន្លោះ ២លីត្រ និង ៧លីត្រ"
, "ប្រហែល ២-៧ លីត្រ"
, "~2-7លីត្រ"
]
, examples (under Millilitre 500)
[ "តិចជាងប្រាំរយមីលីលីត្រ"
, "មិនលើសប្រាំរយមីលីលីត្រ"
, "ក្រោមប្រាំរយមីលីលីត្រ"
, "យ៉ាងច្រើនប្រាំរយមីលីលីត្រ"
]
, examples (above Millilitre 500)
[ "ច្រើនជាងប្រាំរយមីលីលីត្រ"
, "មិនតិចជាងប្រាំរយមីលីលីត្រ"
, "លើសពីប្រាំរយមីលីលីត្រ"
, "យ៉ាងតិចប្រាំរយមីលីលីត្រ"
]
]

163
Duckling/Volume/KM/Rules.hs Normal file
View File

@ -0,0 +1,163 @@
-- 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 #-}
module Duckling.Volume.KM.Rules
( rules ) where
import Data.Text (Text)
import Prelude
import Data.String
import Duckling.Dimensions.Types
import Duckling.Types
import Duckling.Regex.Types
import Duckling.Volume.Helpers
import Duckling.Numeral.Helpers (isPositive)
import qualified Duckling.Volume.Types as TVolume
import qualified Duckling.Numeral.Types as TNumeral
volumes :: [(Text, String, TVolume.Unit)]
volumes = [ ("<latent vol> ml", "ml|មីលីលីត្រ", TVolume.Millilitre)
, ("<vol> liters", "l|លីត្រ", TVolume.Litre)
]
rulesVolumes :: [Rule]
rulesVolumes = map go volumes
where
go :: (Text, String, TVolume.Unit) -> Rule
go (name, regexPattern, u) = Rule
{ name = name
, pattern =
[ regex regexPattern
]
, prod = \_ -> Just . Token Volume $ unitOnly u
}
fractions :: [(Text, String, Double)]
fractions = [ ("half", "កន្លះ|១\\/២", 1/2)
, ("third", "មួយភាគបី|១\\/៣", 1/3)
, ("fourth", "មួយភាគបួន|១\\/៤", 1/4)
, ("fifth", "មួយភាគប្រាំ|១\\/៥", 1/5)
]
rulesFractionalVolume :: [Rule]
rulesFractionalVolume = map go fractions
where
go :: (Text, String, Double) -> Rule
go (name, regexPattern, f) = Rule
{ name = name
, pattern =
[ regex regexPattern
, Predicate isUnitOnly
]
, prod = \case
(_:
Token Volume TVolume.VolumeData{TVolume.unit = Just u}:
_) ->
Just . Token Volume $ volume u f
_ -> Nothing
}
rulePrecision :: Rule
rulePrecision = Rule
{ name = "about <volume>"
, pattern =
[ regex "\\~|ប្រហែល"
, dimension Volume
]
, prod = \case
(_:token:_) -> Just token
_ -> Nothing
}
ruleIntervalBetweenNumeral :: Rule
ruleIntervalBetweenNumeral = Rule
{ name = "between|from <numeral> and|to <volume>"
, pattern =
[ regex "ចន្លោះ(ពី)?|ចាប់ពី"
, Predicate isPositive
, regex "និង|ដល់"
, Predicate isSimpleVolume
]
, prod = \case
(_:
Token Numeral TNumeral.NumeralData{TNumeral.value = from}:
_:
Token Volume TVolume.VolumeData{TVolume.value = Just to
, TVolume.unit = Just u}:
_) | from < to ->
Just . Token Volume . withInterval (from, to) $ unitOnly u
_ -> Nothing
}
ruleIntervalBetween :: Rule
ruleIntervalBetween = Rule
{ name = "between|from <volume> to|and <volume>"
, pattern =
[ regex "ចន្លោះ(ពី)?|ចាប់ពី"
, Predicate isSimpleVolume
, regex "និង|ដល់"
, Predicate isSimpleVolume
]
, prod = \case
(_:
Token Volume TVolume.VolumeData{TVolume.value = Just from
, TVolume.unit = Just u1}:
_:
Token Volume TVolume.VolumeData{TVolume.value = Just to
, TVolume.unit = Just u2}:
_) | from < to && u1 == u2 ->
Just . Token Volume . withInterval (from, to) $ unitOnly u1
_ -> Nothing
}
ruleIntervalMax :: Rule
ruleIntervalMax = Rule
{ name = "at most <volume>"
, pattern =
[ regex "ក្រោម|តិចជាង|មិនដល់|យ៉ាងច្រើន|មិនលើស"
, Predicate isSimpleVolume
]
, prod = \case
(_:
Token Volume TVolume.VolumeData{TVolume.value = Just to
, TVolume.unit = Just u}:
_) ->
Just . Token Volume . withMax to $ unitOnly u
_ -> Nothing
}
ruleIntervalMin :: Rule
ruleIntervalMin = Rule
{ name = "more than <volume>"
, pattern =
[ regex "លើស(ពី)?|មិនតិចជាង|លើ|ច្រើនជាង|យ៉ាងតិច|យ៉ាងហោច"
, Predicate isSimpleVolume
]
, prod = \case
(_:
Token Volume TVolume.VolumeData{TVolume.value = Just from
, TVolume.unit = Just u}:
_) ->
Just . Token Volume . withMin from $ unitOnly u
_ -> Nothing
}
rules :: [Rule]
rules = [ rulePrecision
, ruleIntervalBetweenNumeral
, ruleIntervalBetween
, ruleIntervalMax
, ruleIntervalMin
]
++ rulesVolumes
++ rulesFractionalVolume

View File

@ -272,6 +272,8 @@ library
, Duckling.Distance.GA.Rules
, Duckling.Distance.HR.Corpus
, Duckling.Distance.HR.Rules
, Duckling.Distance.KM.Corpus
, Duckling.Distance.KM.Rules
, Duckling.Distance.KO.Corpus
, Duckling.Distance.KO.Rules
, Duckling.Distance.PT.Corpus
@ -713,6 +715,8 @@ library
, Duckling.Volume.HR.Rules
, Duckling.Volume.IT.Corpus
, Duckling.Volume.IT.Rules
, Duckling.Volume.KM.Corpus
, Duckling.Volume.KM.Rules
, Duckling.Volume.KO.Corpus
, Duckling.Volume.KO.Rules
, Duckling.Volume.PT.Corpus
@ -799,6 +803,7 @@ test-suite duckling-test
, Duckling.Distance.FR.Tests
, Duckling.Distance.GA.Tests
, Duckling.Distance.HR.Tests
, Duckling.Distance.KM.Tests
, Duckling.Distance.KO.Tests
, Duckling.Distance.NL.Tests
, Duckling.Distance.PT.Tests
@ -988,6 +993,7 @@ test-suite duckling-test
, Duckling.Volume.GA.Tests
, Duckling.Volume.HR.Tests
, Duckling.Volume.IT.Tests
, Duckling.Volume.KM.Tests
, Duckling.Volume.KO.Tests
, Duckling.Volume.PT.Tests
, Duckling.Volume.NL.Tests

View 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.Distance.KM.Tests
( tests ) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Testing.Asserts
import Duckling.Distance.KM.Corpus
tests :: TestTree
tests = testGroup "KM Tests"
[ makeCorpusTest [This Distance] corpus
]

View File

@ -21,6 +21,7 @@ import qualified Duckling.Distance.ES.Tests as ES
import qualified Duckling.Distance.FR.Tests as FR
import qualified Duckling.Distance.GA.Tests as GA
import qualified Duckling.Distance.HR.Tests as HR
import qualified Duckling.Distance.KM.Tests as KM
import qualified Duckling.Distance.KO.Tests as KO
import qualified Duckling.Distance.NL.Tests as NL
import qualified Duckling.Distance.PT.Tests as PT
@ -39,6 +40,7 @@ tests = testGroup "Distance Tests"
, FR.tests
, GA.tests
, HR.tests
, KM.tests
, KO.tests
, NL.tests
, PT.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.Volume.KM.Tests
( tests
) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Testing.Asserts
import Duckling.Volume.KM.Corpus
tests :: TestTree
tests = testGroup "KM Tests"
[ makeCorpusTest [This Volume] corpus
]

View File

@ -21,6 +21,7 @@ import qualified Duckling.Volume.FR.Tests as FR
import qualified Duckling.Volume.GA.Tests as GA
import qualified Duckling.Volume.HR.Tests as HR
import qualified Duckling.Volume.IT.Tests as IT
import qualified Duckling.Volume.KM.Tests as KM
import qualified Duckling.Volume.KO.Tests as KO
import qualified Duckling.Volume.NL.Tests as NL
import qualified Duckling.Volume.PT.Tests as PT
@ -37,6 +38,7 @@ tests = testGroup "Volume Tests"
, GA.tests
, HR.tests
, IT.tests
, KM.tests
, KO.tests
, NL.tests
, PT.tests