Skip to content

Commit ba26ca7

Browse files
serefayarfacebook-github-bot
authored andcommitted
Volume for TR
Summary: Closes facebook#34 Reviewed By: niteria Differential Revision: D5168380 Pulled By: patapizza fbshipit-source-id: 31d0a11
1 parent 4a17415 commit ba26ca7

File tree

7 files changed

+127
-1
lines changed

7 files changed

+127
-1
lines changed

Duckling/Dimensions/TR.hs

+1
Original file line numberDiff line numberDiff line change
@@ -19,4 +19,5 @@ allDimensions =
1919
, This Numeral
2020
, This Ordinal
2121
, This Temperature
22+
, This Volume
2223
]

Duckling/Rules/TR.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ import qualified Duckling.Numeral.TR.Rules as Numeral
2121
import qualified Duckling.Ordinal.TR.Rules as Ordinal
2222
import qualified Duckling.Temperature.TR.Rules as Temperature
2323
import qualified Duckling.TimeGrain.TR.Rules as TimeGrain
24+
import qualified Duckling.Volume.TR.Rules as Volume
2425

2526
rules :: Some Dimension -> [Rule]
2627
rules (This Distance) = Distance.rules
@@ -36,4 +37,4 @@ rules (This Temperature) = Temperature.rules
3637
rules (This Time) = []
3738
rules (This TimeGrain) = TimeGrain.rules
3839
rules (This Url) = []
39-
rules (This Volume) = []
40+
rules (This Volume) = Volume.rules

Duckling/Volume/TR/Corpus.hs

+44
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,44 @@
1+
-- Copyright (c) 2016-present, Facebook, Inc.
2+
-- All rights reserved.
3+
--
4+
-- This source code is licensed under the BSD-style license found in the
5+
-- LICENSE file in the root directory of this source tree. An additional grant
6+
-- of patent rights can be found in the PATENTS file in the same directory.
7+
8+
9+
{-# LANGUAGE OverloadedStrings #-}
10+
11+
module Duckling.Volume.TR.Corpus
12+
( corpus ) where
13+
14+
import Data.String
15+
import Prelude
16+
17+
import Duckling.Lang
18+
import Duckling.Resolve
19+
import Duckling.Testing.Types
20+
import Duckling.Volume.Types
21+
22+
corpus :: Corpus
23+
corpus = (testContext {lang = TR}, allExamples)
24+
25+
allExamples :: [Example]
26+
allExamples = concat
27+
[ examples (VolumeValue Millilitre 250)
28+
[ "250 mililitre"
29+
, "250ml"
30+
, "250 ml"
31+
]
32+
, examples (VolumeValue Litre 2)
33+
[ "2 litre" ]
34+
, examples (VolumeValue Gallon 3)
35+
[ "3 galon"
36+
, "3 gal"
37+
]
38+
, examples (VolumeValue Hectolitre 3)
39+
[ "3 hektolitre"
40+
]
41+
, examples (VolumeValue Litre 0.5)
42+
[ "yarım litre"
43+
]
44+
]

Duckling/Volume/TR/Rules.hs

+51
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,51 @@
1+
-- Copyright (c) 2016-present, Facebook, Inc.
2+
-- All rights reserved.
3+
--
4+
-- This source code is licensed under the BSD-style license found in the
5+
-- LICENSE file in the root directory of this source tree. An additional grant
6+
-- of patent rights can be found in the PATENTS file in the same directory.
7+
8+
9+
{-# LANGUAGE GADTs #-}
10+
{-# LANGUAGE OverloadedStrings #-}
11+
12+
module Duckling.Volume.TR.Rules
13+
( rules ) where
14+
15+
import Data.String
16+
import Data.Text (Text)
17+
import Prelude
18+
19+
import Duckling.Dimensions.Types
20+
import Duckling.Types
21+
import Duckling.Volume.Helpers
22+
import qualified Duckling.Volume.Types as TVolume
23+
24+
ruleHalfLiter :: Rule
25+
ruleHalfLiter = Rule
26+
{ name = "half liter"
27+
, pattern = [ regex "yar\305m l(t|itre)" ]
28+
, prod = \_ -> Just . Token Volume . withUnit TVolume.Litre $ volume 0.5
29+
}
30+
31+
volumes :: [(Text, String, TVolume.Unit)]
32+
volumes = [ ("<latent vol> ml" , "m(l|ililitre)" , TVolume.Millilitre)
33+
, ("<vol> hectoliters" , "hektolitre" , TVolume.Hectolitre)
34+
, ("<vol> liters" , "l(t|itre)" , TVolume.Litre)
35+
, ("<latent vol> gallon", "gal(l?on?)?" , TVolume.Gallon)
36+
]
37+
38+
ruleVolumes :: [Rule]
39+
ruleVolumes = map go volumes
40+
where
41+
go :: (Text, String, TVolume.Unit) -> Rule
42+
go (name, regexPattern, u) = Rule
43+
{ name = name
44+
, pattern = [ dimension Volume, regex regexPattern ]
45+
, prod = \tokens -> case tokens of
46+
(Token Volume vd:_) -> Just . Token Volume $ withUnit u vd
47+
_ -> Nothing
48+
}
49+
50+
rules :: [Rule]
51+
rules = ruleHalfLiter:ruleVolumes

duckling.cabal

+3
Original file line numberDiff line numberDiff line change
@@ -488,6 +488,8 @@ library
488488
, Duckling.Volume.NL.Rules
489489
, Duckling.Volume.RO.Corpus
490490
, Duckling.Volume.RO.Rules
491+
, Duckling.Volume.TR.Corpus
492+
, Duckling.Volume.TR.Rules
491493
, Duckling.Volume.Helpers
492494
, Duckling.Volume.Rules
493495
, Duckling.Volume.Types
@@ -702,6 +704,7 @@ test-suite duckling-test
702704
, Duckling.Volume.PT.Tests
703705
, Duckling.Volume.NL.Tests
704706
, Duckling.Volume.RO.Tests
707+
, Duckling.Volume.TR.Tests
705708
, Duckling.Volume.Tests
706709

707710
ghc-options: -threaded -rtsopts -with-rtsopts=-N

tests/Duckling/Volume/TR/Tests.hs

+24
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,24 @@
1+
-- Copyright (c) 2016-present, Facebook, Inc.
2+
-- All rights reserved.
3+
--
4+
-- This source code is licensed under the BSD-style license found in the
5+
-- LICENSE file in the root directory of this source tree. An additional grant
6+
-- of patent rights can be found in the PATENTS file in the same directory.
7+
8+
9+
module Duckling.Volume.TR.Tests
10+
( tests
11+
) where
12+
13+
import Prelude
14+
import Data.String
15+
import Test.Tasty
16+
17+
import Duckling.Dimensions.Types
18+
import Duckling.Testing.Asserts
19+
import Duckling.Volume.TR.Corpus
20+
21+
tests :: TestTree
22+
tests = testGroup "TR Tests"
23+
[ makeCorpusTest [This Volume] corpus
24+
]

tests/Duckling/Volume/Tests.hs

+2
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ import qualified Duckling.Volume.KO.Tests as KO
2222
import qualified Duckling.Volume.NL.Tests as NL
2323
import qualified Duckling.Volume.PT.Tests as PT
2424
import qualified Duckling.Volume.RO.Tests as RO
25+
import qualified Duckling.Volume.TR.Tests as TR
2526

2627
tests :: TestTree
2728
tests = testGroup "Volume Tests"
@@ -35,4 +36,5 @@ tests = testGroup "Volume Tests"
3536
, NL.tests
3637
, PT.tests
3738
, RO.tests
39+
, TR.tests
3840
]

0 commit comments

Comments
 (0)