mirror of
https://github.com/facebook/duckling.git
synced 2024-11-28 08:34:46 +03:00
Volume for TR
Summary: Closes https://github.com/facebookincubator/duckling/pull/34 Reviewed By: niteria Differential Revision: D5168380 Pulled By: patapizza fbshipit-source-id: 31d0a11
This commit is contained in:
parent
4a1741528c
commit
ba26ca7e91
@ -19,4 +19,5 @@ allDimensions =
|
||||
, This Numeral
|
||||
, This Ordinal
|
||||
, This Temperature
|
||||
, This Volume
|
||||
]
|
||||
|
@ -21,6 +21,7 @@ import qualified Duckling.Numeral.TR.Rules as Numeral
|
||||
import qualified Duckling.Ordinal.TR.Rules as Ordinal
|
||||
import qualified Duckling.Temperature.TR.Rules as Temperature
|
||||
import qualified Duckling.TimeGrain.TR.Rules as TimeGrain
|
||||
import qualified Duckling.Volume.TR.Rules as Volume
|
||||
|
||||
rules :: Some Dimension -> [Rule]
|
||||
rules (This Distance) = Distance.rules
|
||||
@ -36,4 +37,4 @@ rules (This Temperature) = Temperature.rules
|
||||
rules (This Time) = []
|
||||
rules (This TimeGrain) = TimeGrain.rules
|
||||
rules (This Url) = []
|
||||
rules (This Volume) = []
|
||||
rules (This Volume) = Volume.rules
|
||||
|
44
Duckling/Volume/TR/Corpus.hs
Normal file
44
Duckling/Volume/TR/Corpus.hs
Normal 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.TR.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.Volume.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = TR}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (VolumeValue Millilitre 250)
|
||||
[ "250 mililitre"
|
||||
, "250ml"
|
||||
, "250 ml"
|
||||
]
|
||||
, examples (VolumeValue Litre 2)
|
||||
[ "2 litre" ]
|
||||
, examples (VolumeValue Gallon 3)
|
||||
[ "3 galon"
|
||||
, "3 gal"
|
||||
]
|
||||
, examples (VolumeValue Hectolitre 3)
|
||||
[ "3 hektolitre"
|
||||
]
|
||||
, examples (VolumeValue Litre 0.5)
|
||||
[ "yarım litre"
|
||||
]
|
||||
]
|
51
Duckling/Volume/TR/Rules.hs
Normal file
51
Duckling/Volume/TR/Rules.hs
Normal file
@ -0,0 +1,51 @@
|
||||
-- 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.TR.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
|
||||
|
||||
ruleHalfLiter :: Rule
|
||||
ruleHalfLiter = Rule
|
||||
{ name = "half liter"
|
||||
, pattern = [ regex "yar\305m l(t|itre)" ]
|
||||
, prod = \_ -> Just . Token Volume . withUnit TVolume.Litre $ volume 0.5
|
||||
}
|
||||
|
||||
volumes :: [(Text, String, TVolume.Unit)]
|
||||
volumes = [ ("<latent vol> ml" , "m(l|ililitre)" , TVolume.Millilitre)
|
||||
, ("<vol> hectoliters" , "hektolitre" , TVolume.Hectolitre)
|
||||
, ("<vol> liters" , "l(t|itre)" , TVolume.Litre)
|
||||
, ("<latent vol> gallon", "gal(l?on?)?" , TVolume.Gallon)
|
||||
]
|
||||
|
||||
ruleVolumes :: [Rule]
|
||||
ruleVolumes = map go volumes
|
||||
where
|
||||
go :: (Text, String, TVolume.Unit) -> Rule
|
||||
go (name, regexPattern, u) = Rule
|
||||
{ name = name
|
||||
, pattern = [ dimension Volume, regex regexPattern ]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Volume vd:_) -> Just . Token Volume $ withUnit u vd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules = ruleHalfLiter:ruleVolumes
|
@ -488,6 +488,8 @@ library
|
||||
, Duckling.Volume.NL.Rules
|
||||
, Duckling.Volume.RO.Corpus
|
||||
, Duckling.Volume.RO.Rules
|
||||
, Duckling.Volume.TR.Corpus
|
||||
, Duckling.Volume.TR.Rules
|
||||
, Duckling.Volume.Helpers
|
||||
, Duckling.Volume.Rules
|
||||
, Duckling.Volume.Types
|
||||
@ -702,6 +704,7 @@ test-suite duckling-test
|
||||
, Duckling.Volume.PT.Tests
|
||||
, Duckling.Volume.NL.Tests
|
||||
, Duckling.Volume.RO.Tests
|
||||
, Duckling.Volume.TR.Tests
|
||||
, Duckling.Volume.Tests
|
||||
|
||||
ghc-options: -threaded -rtsopts -with-rtsopts=-N
|
||||
|
24
tests/Duckling/Volume/TR/Tests.hs
Normal file
24
tests/Duckling/Volume/TR/Tests.hs
Normal 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.TR.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Testing.Asserts
|
||||
import Duckling.Volume.TR.Corpus
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "TR Tests"
|
||||
[ makeCorpusTest [This Volume] corpus
|
||||
]
|
@ -22,6 +22,7 @@ import qualified Duckling.Volume.KO.Tests as KO
|
||||
import qualified Duckling.Volume.NL.Tests as NL
|
||||
import qualified Duckling.Volume.PT.Tests as PT
|
||||
import qualified Duckling.Volume.RO.Tests as RO
|
||||
import qualified Duckling.Volume.TR.Tests as TR
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "Volume Tests"
|
||||
@ -35,4 +36,5 @@ tests = testGroup "Volume Tests"
|
||||
, NL.tests
|
||||
, PT.tests
|
||||
, RO.tests
|
||||
, TR.tests
|
||||
]
|
||||
|
Loading…
Reference in New Issue
Block a user