mirror of
https://github.com/facebook/duckling.git
synced 2024-11-28 08:34:46 +03:00
Added BG distance
Summary: Closes https://github.com/facebook/duckling/pull/162 Reviewed By: chinmay87 Differential Revision: D7239243 Pulled By: patapizza fbshipit-source-id: a5518219a67fa46bb06e97eee3dfd07ab683162f
This commit is contained in:
parent
af0751a748
commit
1493d44465
@ -14,5 +14,6 @@ import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ This Numeral
|
||||
[ This Distance
|
||||
, This Numeral
|
||||
]
|
||||
|
66
Duckling/Distance/BG/Corpus.hs
Normal file
66
Duckling/Distance/BG/Corpus.hs
Normal file
@ -0,0 +1,66 @@
|
||||
-- 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.Distance.BG.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Locale
|
||||
import Duckling.Resolve
|
||||
import Duckling.Distance.Types
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {locale = makeLocale BG Nothing}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (simple Kilometre 3)
|
||||
[ "3 километра"
|
||||
, "3 км"
|
||||
, "3км"
|
||||
, "3.0 км"
|
||||
]
|
||||
, examples (simple Mile 8)
|
||||
[ "8 мили"
|
||||
, "осем мили"
|
||||
]
|
||||
, examples (simple Metre 1)
|
||||
[ "1 м",
|
||||
"1 метър",
|
||||
"един метър"
|
||||
]
|
||||
, examples (simple Centimetre 2)
|
||||
[ "2см"
|
||||
, "2 сантиметра"
|
||||
]
|
||||
, examples (simple Millimetre 4)
|
||||
[ "4мм"
|
||||
, "4 милиметра"
|
||||
]
|
||||
, examples (simple Inch 5)
|
||||
[ "5 инча"
|
||||
, "5''"
|
||||
, "пет инча"
|
||||
, "5\""
|
||||
]
|
||||
, examples (simple Foot 35)
|
||||
[ "35 фута"
|
||||
, "35'"
|
||||
, "тридесет и пет фута"
|
||||
]
|
||||
, examples (simple Yard 47)
|
||||
[ "47 ярда"
|
||||
, "четиридесет и седем ярда"
|
||||
]
|
||||
]
|
50
Duckling/Distance/BG/Rules.hs
Normal file
50
Duckling/Distance/BG/Rules.hs
Normal file
@ -0,0 +1,50 @@
|
||||
-- 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.Distance.BG.Rules
|
||||
( rules
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Data.Text (Text)
|
||||
import Prelude
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Distance.Helpers
|
||||
import Duckling.Distance.Types (DistanceData(..))
|
||||
import Duckling.Types
|
||||
import qualified Duckling.Distance.Types as TDistance
|
||||
|
||||
distances :: [(Text, String, TDistance.Unit)]
|
||||
distances = [ ("<latent dist> km", "км|километ(ра|ри|ър)", TDistance.Kilometre)
|
||||
, ("<latent dist> feet", "('|фут(а|ове)?)", TDistance.Foot)
|
||||
, ("<latent dist> inch", "(\"|''|инч(а|ове)?)", TDistance.Inch)
|
||||
, ("<latent dist> yard", "ярд(а|ове)?", TDistance.Yard)
|
||||
, ("<dist> meters", "м(етър|етр(а|и))?", TDistance.Metre)
|
||||
, ("<dist> centimeters", "см|сантимет(ри|ра|ър)", TDistance.Centimetre)
|
||||
, ("<dist> millimeters", "мм|милимет(ра|ри|ър)", TDistance.Millimetre)
|
||||
, ("<dist> miles", "мил(я|и)", TDistance.Mile)
|
||||
]
|
||||
|
||||
ruleDistances :: [Rule]
|
||||
ruleDistances = map go distances
|
||||
where
|
||||
go :: (Text, String, TDistance.Unit) -> Rule
|
||||
go (name, regexPattern, u) = Rule
|
||||
{ name = name
|
||||
, pattern = [ dimension Distance, regex regexPattern ]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) -> Just . Token Distance $ withUnit u dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules = ruleDistances
|
@ -20,6 +20,7 @@ import Duckling.Locale
|
||||
import Duckling.Types
|
||||
import qualified Duckling.Numeral.BG.Rules as Numeral
|
||||
import qualified Duckling.AmountOfMoney.BG.Rules as AmountOfMoney
|
||||
import qualified Duckling.Distance.BG.Rules as Distance
|
||||
|
||||
defaultRules :: Some Dimension -> [Rule]
|
||||
defaultRules = langRules
|
||||
@ -29,7 +30,7 @@ localeRules _ _ = []
|
||||
|
||||
langRules :: Some Dimension -> [Rule]
|
||||
langRules (This AmountOfMoney) = AmountOfMoney.rules
|
||||
langRules (This Distance) = []
|
||||
langRules (This Distance) = Distance.rules
|
||||
langRules (This Duration) = []
|
||||
langRules (This Email) = []
|
||||
langRules (This Numeral) = Numeral.rules
|
||||
|
@ -196,6 +196,8 @@ library
|
||||
, Duckling.AmountOfMoney.Types
|
||||
|
||||
-- Distance
|
||||
, Duckling.Distance.BG.Corpus
|
||||
, Duckling.Distance.BG.Rules
|
||||
, Duckling.Distance.CS.Corpus
|
||||
, Duckling.Distance.CS.Rules
|
||||
, Duckling.Distance.EN.Corpus
|
||||
@ -674,6 +676,7 @@ test-suite duckling-test
|
||||
, Duckling.AmountOfMoney.Tests
|
||||
|
||||
-- Distance
|
||||
, Duckling.Distance.BG.Tests
|
||||
, Duckling.Distance.CS.Tests
|
||||
, Duckling.Distance.EN.Tests
|
||||
, Duckling.Distance.ES.Tests
|
||||
|
24
tests/Duckling/Distance/BG/Tests.hs
Normal file
24
tests/Duckling/Distance/BG/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.Distance.BG.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Distance.BG.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "BG Tests"
|
||||
[ makeCorpusTest [This Distance] corpus
|
||||
]
|
@ -7,10 +7,11 @@
|
||||
|
||||
|
||||
module Duckling.Distance.EN.Tests
|
||||
( tests ) where
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
@ -6,12 +6,15 @@
|
||||
-- of patent rights can be found in the PATENTS file in the same directory.
|
||||
|
||||
|
||||
module Duckling.Distance.Tests (tests) where
|
||||
module Duckling.Distance.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import qualified Duckling.Distance.BG.Tests as BG
|
||||
import qualified Duckling.Distance.CS.Tests as CS
|
||||
import qualified Duckling.Distance.EN.Tests as EN
|
||||
import qualified Duckling.Distance.ES.Tests as ES
|
||||
@ -27,7 +30,8 @@ import qualified Duckling.Distance.TR.Tests as TR
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "Distance Tests"
|
||||
[ CS.tests
|
||||
[ BG.tests
|
||||
, CS.tests
|
||||
, EN.tests
|
||||
, ES.tests
|
||||
, FR.tests
|
||||
|
Loading…
Reference in New Issue
Block a user