Volume for Croatian

Summary: Volume dimension for Croatian

Reviewed By: niteria

Differential Revision: D4957186

fbshipit-source-id: 63012ad
This commit is contained in:
Julien Odent 2017-04-28 07:47:41 -07:00 committed by Facebook Github Bot
parent 0aa4aa56bb
commit 0372f4f3da
7 changed files with 164 additions and 1 deletions

View File

@ -19,4 +19,5 @@ allDimensions =
, This Numeral
, This Ordinal
, This Time
, This Volume
]

View File

@ -22,6 +22,7 @@ import qualified Duckling.Numeral.HR.Rules as Numeral
import qualified Duckling.Ordinal.HR.Rules as Ordinal
import qualified Duckling.Time.HR.Rules as Time
import qualified Duckling.TimeGrain.HR.Rules as TimeGrain
import qualified Duckling.Volume.HR.Rules as Volume
rules :: Some Dimension -> [Rule]
rules (This Distance) = Distance.rules
@ -37,4 +38,4 @@ rules (This Temperature) = []
rules (This Time) = Time.rules
rules (This TimeGrain) = TimeGrain.rules
rules (This Url) = []
rules (This Volume) = []
rules (This Volume) = Volume.rules

View File

@ -0,0 +1,44 @@
-- 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.HR.Corpus
( corpus ) where
import Prelude
import Data.String
import Duckling.Lang
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.Volume.Types
corpus :: Corpus
corpus = (testContext {lang = HR}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (VolumeValue Millilitre 250)
[ "250 mililitara"
, "250ml"
, "250 ml"
]
, examples (VolumeValue Litre 2)
[ "2 litre"
]
, examples (VolumeValue Gallon 3)
[ "3 galona"
, "3 gal"
]
, examples (VolumeValue Hectolitre 3)
[ "3 hektolitra"
]
, examples (VolumeValue Litre 0.5)
[ "pola litre"
]
]

View File

@ -0,0 +1,90 @@
-- 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.Volume.HR.Rules
( rules ) where
import Data.String
import Prelude
import Duckling.Dimensions.Types
import Duckling.Types
import Duckling.Volume.Helpers
import qualified Duckling.Volume.Types as TVolume
ruleLatentVolMl :: Rule
ruleLatentVolMl = Rule
{ name = "<latent vol> ml"
, pattern =
[ dimension Volume
, regex "m(l|ililita?ra?)"
]
, prod = \tokens -> case tokens of
(Token Volume vd:_) ->
Just . Token Volume $ withUnit TVolume.Millilitre vd
_ -> Nothing
}
ruleVolHektolitar :: Rule
ruleVolHektolitar = Rule
{ name = "<vol> hektolitar"
, pattern =
[ dimension Volume
, regex "hektolita?ra?"
]
, prod = \tokens -> case tokens of
(Token Volume vd:_) ->
Just . Token Volume $ withUnit TVolume.Hectolitre vd
_ -> Nothing
}
ruleVolLitra :: Rule
ruleVolLitra = Rule
{ name = "<vol> litra"
, pattern =
[ dimension Volume
, regex "l(it(a)?r(a|e)?)?"
]
, prod = \tokens -> case tokens of
(Token Volume vd:_) ->
Just . Token Volume $ withUnit TVolume.Litre vd
_ -> Nothing
}
rulePolaLitre :: Rule
rulePolaLitre = Rule
{ name = "pola litre"
, pattern =
[ regex "pola litre"
]
, prod = \_ -> Just . Token Volume . withUnit TVolume.Litre $ volume 0.5
}
ruleLatentVolGalon :: Rule
ruleLatentVolGalon = Rule
{ name = "<latent vol> galon"
, pattern =
[ dimension Volume
, regex "gal(ona?)?"
]
, prod = \tokens -> case tokens of
(Token Volume vd:_) ->
Just . Token Volume $ withUnit TVolume.Gallon vd
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleLatentVolGalon
, ruleLatentVolMl
, rulePolaLitre
, ruleVolHektolitar
, ruleVolLitra
]

View File

@ -450,6 +450,8 @@ library
, Duckling.Volume.FR.Rules
, Duckling.Volume.GA.Corpus
, Duckling.Volume.GA.Rules
, Duckling.Volume.HR.Corpus
, Duckling.Volume.HR.Rules
, Duckling.Volume.KO.Corpus
, Duckling.Volume.KO.Rules
, Duckling.Volume.PT.Corpus
@ -669,6 +671,7 @@ test-suite duckling-test
, Duckling.Volume.ES.Tests
, Duckling.Volume.FR.Tests
, Duckling.Volume.GA.Tests
, Duckling.Volume.HR.Tests
, Duckling.Volume.KO.Tests
, Duckling.Volume.PT.Tests
, Duckling.Volume.NL.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.HR.Tests
( tests ) where
import Data.String
import Prelude
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Volume.HR.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "HR Tests"
[ makeCorpusTest [This Volume] corpus
]

View File

@ -16,6 +16,7 @@ import qualified Duckling.Volume.EN.Tests as EN
import qualified Duckling.Volume.ES.Tests as ES
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.KO.Tests as KO
import qualified Duckling.Volume.NL.Tests as NL
import qualified Duckling.Volume.PT.Tests as PT
@ -27,6 +28,7 @@ tests = testGroup "Volume Tests"
, ES.tests
, FR.tests
, GA.tests
, HR.tests
, KO.tests
, NL.tests
, PT.tests