mirror of
https://github.com/facebook/duckling.git
synced 2024-11-24 07:23:03 +03:00
Init
Summary: Initialise Volume for CA (Catalan) language Reviewed By: stroxler Differential Revision: D28298901 Pulled By: chessai fbshipit-source-id: 72fd95062393b8b780e521b56b097b66e2263aef
This commit is contained in:
parent
219e5600d6
commit
0e3d0604a2
@ -9,6 +9,7 @@
|
||||
* AmountOfMoney: **new!**
|
||||
* Distance: **new!**
|
||||
* Temperature: **new!**
|
||||
* Volume: **new!**
|
||||
|
||||
* EN (English)
|
||||
* Time: Allow latent match for \<part-of-day\> \<latent-time-of-day\>
|
||||
|
@ -18,4 +18,5 @@ allDimensions =
|
||||
, Seal Numeral
|
||||
, Seal Ordinal
|
||||
, Seal Temperature
|
||||
, Seal Volume
|
||||
]
|
||||
|
@ -22,6 +22,7 @@ import qualified Duckling.Distance.CA.Rules as Distance
|
||||
import qualified Duckling.Numeral.CA.Rules as Numeral
|
||||
import qualified Duckling.Ordinal.CA.Rules as Ordinal
|
||||
import qualified Duckling.Temperature.CA.Rules as Temperature
|
||||
import qualified Duckling.Volume.CA.Rules as Volume
|
||||
import Duckling.Types
|
||||
|
||||
defaultRules :: Seal Dimension -> [Rule]
|
||||
@ -46,5 +47,5 @@ langRules (Seal Temperature) = Temperature.rules
|
||||
langRules (Seal Time) = []
|
||||
langRules (Seal TimeGrain) = []
|
||||
langRules (Seal Url) = []
|
||||
langRules (Seal Volume) = []
|
||||
langRules (Seal Volume) = Volume.rules
|
||||
langRules (Seal (CustomDimension _)) = []
|
||||
|
43
Duckling/Volume/CA/Corpus.hs
Normal file
43
Duckling/Volume/CA/Corpus.hs
Normal file
@ -0,0 +1,43 @@
|
||||
-- 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.CA.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Locale
|
||||
import Duckling.Resolve
|
||||
import Duckling.Volume.Types
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {locale = makeLocale CA Nothing}, testOptions, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (simple Millilitre 250)
|
||||
[ "250 mililitres"
|
||||
, "250ml"
|
||||
, "250 ml"
|
||||
]
|
||||
, examples (simple Litre 2)
|
||||
[ "2 litres"
|
||||
]
|
||||
, examples (simple Gallon 3)
|
||||
[ "3 galó"
|
||||
]
|
||||
, examples (simple Hectolitre 3)
|
||||
[ "3 hectolitres"
|
||||
]
|
||||
, examples (simple Litre 0.5)
|
||||
[ "mig litre"
|
||||
]
|
||||
]
|
67
Duckling/Volume/CA/Rules.hs
Normal file
67
Duckling/Volume/CA/Rules.hs
Normal 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.
|
||||
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Duckling.Volume.CA.Rules
|
||||
( rules ) where
|
||||
|
||||
import Data.String
|
||||
import Data.Text (Text)
|
||||
import Prelude
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Types
|
||||
import Duckling.Volume.Helpers
|
||||
import qualified Duckling.Volume.Types as TVolume
|
||||
|
||||
volumes :: [(Text, String, TVolume.Unit)]
|
||||
volumes = [ ("<latent vol> ml" , "m(l|ililitres?)", TVolume.Millilitre)
|
||||
, ("<vol> hectoliters" , "(hectolitres?)" , TVolume.Hectolitre)
|
||||
, ("<vol> liters" , "l(itres?)?" , TVolume.Litre)
|
||||
, ("<latent vol> gallon", "gal(ons|ó)" , 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
|
||||
}
|
||||
|
||||
fractions :: [(Text, String, Double)]
|
||||
fractions = [ ("half", "mig", 1/2)
|
||||
]
|
||||
|
||||
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
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
rulesVolumes
|
||||
++ rulesFractionalVolume
|
@ -824,6 +824,8 @@ library
|
||||
-- Volume
|
||||
, Duckling.Volume.AR.Corpus
|
||||
, Duckling.Volume.AR.Rules
|
||||
, Duckling.Volume.CA.Corpus
|
||||
, Duckling.Volume.CA.Rules
|
||||
, Duckling.Volume.DE.Corpus
|
||||
, Duckling.Volume.DE.Rules
|
||||
, Duckling.Volume.EN.Corpus
|
||||
@ -1158,6 +1160,7 @@ test-suite duckling-test
|
||||
|
||||
-- Volume
|
||||
, Duckling.Volume.AR.Tests
|
||||
, Duckling.Volume.CA.Tests
|
||||
, Duckling.Volume.DE.Tests
|
||||
, Duckling.Volume.EN.Tests
|
||||
, Duckling.Volume.ES.Tests
|
||||
|
22
tests/Duckling/Volume/CA/Tests.hs
Normal file
22
tests/Duckling/Volume/CA/Tests.hs
Normal 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.
|
||||
|
||||
|
||||
module Duckling.Volume.CA.Tests
|
||||
( tests ) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Volume.CA.Corpus
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "CA Tests"
|
||||
[ makeCorpusTest [Seal Volume] corpus
|
||||
]
|
Loading…
Reference in New Issue
Block a user