Add initial support for volumes in Chinese

Reviewed By: girifb

Differential Revision: D26183123

Pulled By: chessai

fbshipit-source-id: 1acd27d5172cfb5bccbeb1576700e2c60a8e3907
This commit is contained in:
kcnhk1@gmail.com 2021-02-01 15:59:07 -08:00 committed by Facebook GitHub Bot
parent 9993911e3b
commit 61e06c3aa6
6 changed files with 316 additions and 1 deletions

View File

@ -30,6 +30,7 @@ import qualified Duckling.Time.ZH.HK.Rules as TimeHK
import qualified Duckling.Time.ZH.MO.Rules as TimeMO
import qualified Duckling.Time.ZH.TW.Rules as TimeTW
import qualified Duckling.TimeGrain.ZH.Rules as TimeGrain
import qualified Duckling.Volume.ZH.Rules as Volume
defaultRules :: Seal Dimension -> [Rule]
defaultRules = langRules
@ -57,5 +58,5 @@ langRules (Seal Temperature) = Temperature.rules
langRules (Seal Time) = Time.rules
langRules (Seal TimeGrain) = TimeGrain.rules
langRules (Seal Url) = []
langRules (Seal Volume) = []
langRules (Seal Volume) = Volume.rules
langRules (Seal (CustomDimension dim)) = dimLangRules ZH dim

View File

@ -0,0 +1,94 @@
-- 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.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Volume.ZH.Corpus
( corpus ) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.Volume.Types
corpus :: Corpus
corpus = (testContext {locale = makeLocale ZH Nothing}, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Litre 1)
[ "1升"
, "一升"
, "一公升"
, "1L"
]
, examples (simple Litre 2)
[ "2升"
, "兩升"
, "兩公升"
, "2L"
]
, examples (simple Litre 1000)
[ "1000公升"
, "一千公升"
]
, examples (simple Litre 0.5)
[ "半公升"
, "0.5L"
]
, examples (simple Litre 0.25)
[ "四分一升"
, "四分之一公升"
]
, examples (simple Millilitre 1)
[ "1毫升"
, "1ml"
, "一毫升"
, "1cc"
]
, examples (simple Millilitre 250)
[ "250毫升"
, "二百五十毫升"
, "250ml"
, "250cc"
]
, examples (simple Gallon 3)
[ "3加侖"
, "三加侖"
]
, examples (simple Gallon 0.5)
[ "0.5加侖"
, "半加侖"
, "二分一加侖"
]
, examples (simple Gallon 0.1)
[ "0.1加侖"
, "零點一加侖"
]
, examples (between Litre (2,3))
[ "二至三公升"
, "2-3L"
, "兩到三升"
, "兩升到三升"
]
, examples (under Gallon 6)
[ "最多六個加侖"
, "六加侖以下"
]
, examples (above Millilitre 4)
[ "至少四ml"
, "最少四毫升"
, "四毫升或以上"
]
, examples (simple Millilitre 5)
[ "一茶匙"
, "三分一湯匙"
]
]

193
Duckling/Volume/ZH/Rules.hs Normal file
View File

@ -0,0 +1,193 @@
-- 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.
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Volume.ZH.Rules
( rules ) where
import Data.Text (Text)
import Prelude
import Data.String
import Duckling.Dimensions.Types
import Duckling.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", "cc|ml|毫升", TVolume.Millilitre)
, ("<vol> liters", "l|L|公升|升", TVolume.Litre)
, ("<latent vol> gallon", "加侖", TVolume.Gallon)
]
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
}
ruleUnitTeaspoon :: Rule
ruleUnitTeaspoon = Rule
{ name = "<numeral> teaspoon"
, pattern =
[ Predicate isPositive
, regex "茶匙"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_) ->
Just . Token Volume $ volume TVolume.Millilitre (5*v)
_ -> Nothing
}
ruleUnitSoupspoon :: Rule
ruleUnitSoupspoon = Rule
{ name = "<numeral> soupspoon"
, pattern =
[ Predicate isPositive
, regex "湯匙"
]
, prod = \case
(Token Numeral TNumeral.NumeralData{TNumeral.value = v}:_) ->
Just . Token Volume $ volume TVolume.Millilitre (15*v)
_ -> 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 =
[ 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 =
[ 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
}
ruleIntervalMax2 :: Rule
ruleIntervalMax2 = Rule
{ name = "<volume> or below"
, pattern =
[ Predicate isSimpleVolume
, regex "(或)?以下"
]
, 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
}
ruleIntervalMin2 :: Rule
ruleIntervalMin2 = Rule
{ name = "<volume> or above"
, pattern =
[ Predicate isSimpleVolume
, regex "(或)?以上"
]
, 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 = [ ruleUnitTeaspoon
, ruleUnitSoupspoon
, rulePrecision
, ruleIntervalBetweenNumeral
, ruleIntervalBetween
, ruleIntervalMax
, ruleIntervalMax2
, ruleIntervalMin
, ruleIntervalMin2
]
++ rulesVolumes

View File

@ -833,6 +833,8 @@ library
, Duckling.Volume.RU.Rules
, Duckling.Volume.TR.Corpus
, Duckling.Volume.TR.Rules
, Duckling.Volume.ZH.Corpus
, Duckling.Volume.ZH.Rules
, Duckling.Volume.Helpers
, Duckling.Volume.Rules
, Duckling.Volume.Types
@ -1143,6 +1145,7 @@ test-suite duckling-test
, Duckling.Volume.RO.Tests
, Duckling.Volume.RU.Tests
, Duckling.Volume.TR.Tests
, Duckling.Volume.ZH.Tests
, Duckling.Volume.Tests
-- CreditCardNumber

View File

@ -29,6 +29,7 @@ import qualified Duckling.Volume.PT.Tests as PT
import qualified Duckling.Volume.RO.Tests as RO
import qualified Duckling.Volume.RU.Tests as RU
import qualified Duckling.Volume.TR.Tests as TR
import qualified Duckling.Volume.ZH.Tests as ZH
tests :: TestTree
tests = testGroup "Volume Tests"
@ -48,4 +49,5 @@ tests = testGroup "Volume Tests"
, RO.tests
, RU.tests
, TR.tests
, ZH.tests
]

View File

@ -0,0 +1,22 @@
-- 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.ZH.Tests
( tests ) where
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Volume.ZH.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ZH Tests"
[ makeCorpusTest [Seal Volume] corpus
]