Distance for TR

Summary: Closes https://github.com/facebookincubator/duckling/pull/26

Reviewed By: niteria

Differential Revision: D5112142

Pulled By: patapizza

fbshipit-source-id: d71f654
This commit is contained in:
Şeref R.Ayar 2017-05-23 10:32:00 -07:00 committed by Facebook Github Bot
parent b64f72eb19
commit 6de7c2142b
7 changed files with 165 additions and 3 deletions

View File

@ -14,6 +14,7 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ This Numeral
[ This Distance
, This Numeral
, This Ordinal
]

View File

@ -0,0 +1,52 @@
-- 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.TR.Corpus
( corpus ) where
import Data.String
import Prelude
import Duckling.Distance.Types
import Duckling.Lang
import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus = (testContext {lang = TR}, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (DistanceValue Kilometre 3)
[ "3 Kilometre"
, "3 kilometre"
, "3 km"
, "3km"
]
, examples (DistanceValue Kilometre 3.0)
[ "3.0 km"
]
, examples (DistanceValue Mile 8)
[ "8 Mil"
, "8 mil"
]
, examples (DistanceValue Metre 9)
[ "9 Metre"
, "9 metre"
, "9 m"
, "9m"
]
, examples (DistanceValue Centimetre 2)
[ "2 Santimetre"
, "2 santim"
, "2 cm"
, "2cm"
]
]

View File

@ -0,0 +1,81 @@
-- 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.TR.Rules
( rules ) where
import Data.String
import Prelude
import Duckling.Dimensions.Types
import Duckling.Distance.Helpers
import qualified Duckling.Distance.Types as TDistance
import Duckling.Types
ruleLatentDistKm :: Rule
ruleLatentDistKm = Rule
{ name = "<latent dist> km"
, pattern =
[ dimension Distance
, regex "k(ilo)?m?(etre)?"
]
, prod = \tokens -> case tokens of
(Token Distance dd:_) ->
Just . Token Distance $ withUnit TDistance.Kilometre dd
_ -> Nothing
}
ruleDistMeters :: Rule
ruleDistMeters = Rule
{ name = "<dist> meters"
, pattern =
[ dimension Distance
, regex "m(etre)?"
]
, prod = \tokens -> case tokens of
(Token Distance dd:_) ->
Just . Token Distance $ withUnit TDistance.Metre dd
_ -> Nothing
}
ruleDistCentimeters :: Rule
ruleDistCentimeters = Rule
{ name = "<dist> centimeters"
, pattern =
[ dimension Distance
, regex "cm|santim(etre)?"
]
, prod = \tokens -> case tokens of
(Token Distance dd:_) ->
Just . Token Distance $ withUnit TDistance.Centimetre dd
_ -> Nothing
}
ruleDistMiles :: Rule
ruleDistMiles = Rule
{ name = "<dist> miles"
, pattern =
[ dimension Distance
, regex "mil"
]
, prod = \tokens -> case tokens of
(Token Distance dd:_) ->
Just . Token Distance $ withUnit TDistance.Mile dd
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleDistCentimeters
, ruleDistMeters
, ruleDistMiles
, ruleLatentDistKm
]

View File

@ -14,12 +14,13 @@ module Duckling.Rules.TR
) where
import Duckling.Dimensions.Types
import Duckling.Types
import qualified Duckling.Distance.TR.Rules as Distance
import qualified Duckling.Numeral.TR.Rules as Numeral
import qualified Duckling.Ordinal.TR.Rules as Ordinal
import Duckling.Types
rules :: Some Dimension -> [Rule]
rules (This Distance) = []
rules (This Distance) = Distance.rules
rules (This Duration) = []
rules (This Numeral) = Numeral.rules
rules (This Email) = []

View File

@ -184,6 +184,8 @@ library
, Duckling.Distance.NL.Rules
, Duckling.Distance.RO.Corpus
, Duckling.Distance.RO.Rules
, Duckling.Distance.TR.Corpus
, Duckling.Distance.TR.Rules
, Duckling.Distance.Helpers
, Duckling.Distance.Rules
, Duckling.Distance.Types
@ -552,6 +554,7 @@ test-suite duckling-test
, Duckling.Distance.NL.Tests
, Duckling.Distance.PT.Tests
, Duckling.Distance.RO.Tests
, Duckling.Distance.TR.Tests
, Duckling.Distance.Tests
-- Duration

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.Distance.TR.Tests
( tests ) where
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Distance.TR.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "TR Tests"
[ makeCorpusTest [This Distance] corpus
]

View File

@ -22,6 +22,7 @@ import qualified Duckling.Distance.KO.Tests as KO
import qualified Duckling.Distance.NL.Tests as NL
import qualified Duckling.Distance.PT.Tests as PT
import qualified Duckling.Distance.RO.Tests as RO
import qualified Duckling.Distance.TR.Tests as TR
tests :: TestTree
tests = testGroup "Distance Tests"
@ -35,4 +36,5 @@ tests = testGroup "Distance Tests"
, NL.tests
, PT.tests
, RO.tests
, TR.tests
]