Add support for Ordinal, Quantity, & Temperature dimension for KM. (#251)

Summary:
Hello.
I added 3 new dimensions: Ordinal, Quantity, & Temperature. And I also added more data to Numeral dimension.
Thank you!
Pull Request resolved: https://github.com/facebook/duckling/pull/251

Reviewed By: beauby

Differential Revision: D9656646

Pulled By: patapizza

fbshipit-source-id: f17797be811d58b0b5bcd02b83c0a699650c9f6e
This commit is contained in:
pheaktra21 2018-09-06 06:50:07 -07:00 committed by Facebook Github Bot
parent 4a77765134
commit cd33b26acf
18 changed files with 538 additions and 15 deletions

View File

@ -14,4 +14,8 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ This Numeral ]
[ This Numeral
, This Ordinal
, This Quantity
, This Temperature
]

View File

@ -9,7 +9,8 @@
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.KM.Corpus
( corpus ) where
( corpus
) where
import Data.String
import Prelude
@ -30,41 +31,78 @@ allExamples = concat
[ examples (NumeralValue 0)
[ "0"
, ""
, "សូន្យ"
]
, examples (NumeralValue 1)
[ "1"
, ""
, "មួយ"
]
, examples (NumeralValue 2)
[ "2"
, ""
, "ពីរ"
]
, examples (NumeralValue 3)
[ "3"
, ""
, "បី"
]
, examples (NumeralValue 4)
[ "4"
, ""
, "បួន"
]
, examples (NumeralValue 5)
[ "5"
, ""
, "ប្រាំ"
]
, examples (NumeralValue 6)
[ "6"
, ""
, "ប្រាំមួយ"
]
, examples (NumeralValue 7)
[ "7"
, ""
, "ប្រាំពីរ"
]
, examples (NumeralValue 8)
[ "8"
, ""
, "ប្រាំបី"
]
, examples (NumeralValue 9)
[ "9"
, ""
, "ប្រាំបួន"
]
, examples (NumeralValue 10)
[ "ដប់"
]
, examples (NumeralValue 11)
[ "ដប់មួយ"
]
, examples (NumeralValue 22)
[ "ម្ភៃពីរ"
]
, examples (NumeralValue 33)
[ "សាមបី"
]
, examples (NumeralValue 99)
[ "កៅប្រាំបួន"
]
, examples (NumeralValue 320)
[ "បីរយម្ភៃ"
]
, examples (NumeralValue 6078)
[ "ប្រាំមួយពាន់ចិតប្រាំបី"
]
, examples (NumeralValue 5689443)
[ "ប្រាំលានប្រាំមួយសែនប្រាំបីម៉ឺនប្រាំបួនពាន់បួនរយសែបី"
]
, examples (NumeralValue 800000000)
[ "ប្រាំបីរយលាន"
]
]

View File

@ -11,7 +11,8 @@
{-# LANGUAGE NoRebindableSyntax #-}
module Duckling.Numeral.KM.Rules
( rules ) where
( rules
) where
import Data.HashMap.Strict (HashMap)
import Data.Maybe
@ -40,13 +41,24 @@ ruleNumeralMap = HashMap.fromList
, ( "", 7 )
, ( "", 8 )
, ( "", 9 )
, ( "សូន្យ", 0 )
, ( "មួយ", 1 )
, ( "ពីរ", 2 )
, ( "បី", 3 )
, ( "បួន", 4 )
, ( "ប្រាំ", 5 )
, ( "ប្រាំមួយ", 6 )
, ( "ប្រាំពីរ", 7 )
, ( "ប្រាំបី", 8 )
, ( "ប្រាំបួន", 9 )
]
ruleNumeral :: Rule
ruleNumeral = Rule
{ name = "number (0..9)"
{ name = "integer (0..9)"
-- ត្រូវដាក់ពាក្យ ប្រាំមួយ ប្រាំពីរ ប្រាំបី និងប្រាំបួន នៅខាងមុខលេខប្រាំ។ បើមិនដូច្នោះទេ វាមិនអាចផ្គូរផ្គងត្រូវទេ។
, pattern =
[ regex "(០|១|២|៣|៤|៥|៦|៧|៨|៩)"
[ regex "(០|១|២|៣|៤|៥|៦|៧|៨|៩|ប្រាំបួន|ប្រាំបី|ប្រាំពីរ|ប្រាំមួយ|ប្រាំ|បួន|បី|ពីរ|មួយ|សូន្យ)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
@ -54,7 +66,99 @@ ruleNumeral = Rule
_ -> Nothing
}
ruleTensMap :: HashMap Text Integer
ruleTensMap = HashMap.fromList
-- លេខ ១០ ២០ ៣០ ៤០ ៥០ ៦០ ៧០ ៨០ ៩០ អត់ត្រូវបានបញ្ចូលទេ ព្រោះមិនទាន់អាចរក
-- វិធីដកលេខ ០ ចេញ នៅពេលផ្គំុជាមួយលេខដទៃ។
-- ពពួក "សិប" ក៏មិនត្រូវបានបញ្ចូលដែរ ព្រោះមិនទាន់រកឃើញវិធីផ្គូរផ្គងត្រូវ។
[ ( "ដប់", 10 )
, ( "ម្ភៃ", 20 )
, ( "សាម", 30 )
, ( "សែ", 40 )
, ( "ហា", 50 )
, ( "ហុក", 60 )
, ( "ចិត", 70 )
, ( "ប៉ែត", 80 )
, ( "កៅ", 90 )
]
ruleTens :: Rule
ruleTens = Rule
{ name = "integer (10..90)"
, pattern =
[ regex "(កៅ|ប៉ែត|ចិត|ហុក|ហា|សែ|សាម|ម្ភៃ|ដប់)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) ->
HashMap.lookup match ruleTensMap >>= integer
_ -> Nothing
}
ruleCompositeTens :: Rule
ruleCompositeTens = Rule
{ name = "integer (11..99)"
, pattern =
[ oneOf [10, 20 .. 90]
, oneOf [1 .. 9]
]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = v1}:
Token Numeral NumeralData{TNumeral.value = v2}:
_) -> double $ v1 + v2
_ -> Nothing
}
rulePowersOfTen :: Rule
rulePowersOfTen = Rule
{ name = "powers of tens"
, pattern =
[ regex "(រយ|ពាន់|ម៉ឺន|សែន|លាន)"
]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> case match of
"រយ" -> double 1e2 >>= withGrain 2 >>= withMultipliable
"ពាន់" -> double 1e3 >>= withGrain 3 >>= withMultipliable
"ម៉ឺន" -> double 1e4 >>= withGrain 4 >>= withMultipliable
"សែន" -> double 1e5 >>= withGrain 5 >>= withMultipliable
"លាន" -> double 1e6 >>= withGrain 6 >>= withMultipliable
_ -> Nothing
_ -> Nothing
}
-- សម្រាប់ផ្គុំពីរលេខ ដែលចាប់ពីខ្ទង់រយទៅ និងខ្ទង់រាយ
ruleSum :: Rule
ruleSum = Rule
{ name = "intersect 2 numbers"
, pattern =
[ Predicate $ and . sequence [hasGrain, isPositive]
, Predicate $ and . sequence [not . isMultipliable, isPositive]
]
, prod = \tokens -> case tokens of
(Token Numeral NumeralData{TNumeral.value = val1, TNumeral.grain = Just g}:
Token Numeral NumeralData{TNumeral.value = val2}:
_) | (10 ** fromIntegral g) > val2 -> double $ val1 + val2
_ -> Nothing
}
-- សម្រាប់លេខចាប់ពីខ្ទង់រយទៅ
ruleMultiply :: Rule
ruleMultiply = Rule
{ name = "compose by multiplication"
, pattern =
[ dimension Numeral
, Predicate isMultipliable
]
, prod = \tokens -> case tokens of
(token1:token2:_) -> multiply token1 token2
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleNumeral
, ruleTens
, ruleCompositeTens
, rulePowersOfTen
, ruleSum
, ruleMultiply
]

View File

@ -0,0 +1,38 @@
-- 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.Ordinal.KM.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Ordinal.Types
import Duckling.Resolve
import Duckling.Testing.Types
context :: Context
context = testContext{locale = makeLocale KM Nothing}
corpus :: Corpus
corpus = (context, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (OrdinalData 1)
[ "ទីមួយ"
, "ទី១"
]
, examples (OrdinalData 400)
[ "ទីបួនរយ"
]
]

View File

@ -0,0 +1,42 @@
-- 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 LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Ordinal.KM.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.Dimensions.Types
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Ordinal.Helpers
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
ruleOrdinalDigits :: Rule
ruleOrdinalDigits = Rule
{ name = "ordinal (digits)"
, pattern =
[ regex "ទី"
, dimension Numeral
]
, prod = \case
(_:Token Numeral NumeralData{TNumeral.value = x}:_) ->
Just . ordinal $ floor x
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleOrdinalDigits
]

View File

@ -7,22 +7,24 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Quantity.FR.Rules
( rules ) where
( rules
) where
import qualified Data.Text as Text
import Prelude
import Data.String
import Prelude
import qualified Data.Text as Text
import Duckling.Dimensions.Types
import Duckling.Quantity.Helpers
import qualified Duckling.Quantity.Types as TQuantity
import Duckling.Numeral.Types (NumeralData (..))
import qualified Duckling.Numeral.Types as TNumeral
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
import qualified Duckling.Quantity.Types as TQuantity
ruleNumeralUnits :: Rule
ruleNumeralUnits = Rule
@ -31,7 +33,7 @@ ruleNumeralUnits = Rule
[ dimension Numeral
, regex "(tasses?|cuill?(e|è)res? (a|à) soupe?)"
]
, prod = \tokens -> case tokens of
, prod = \case
(Token Numeral NumeralData {TNumeral.value = v}:
Token RegexMatch (GroupMatch (match:_)):
_) -> case Text.toLower match of
@ -48,7 +50,7 @@ ruleQuantityOfProduct = Rule
[ dimension Quantity
, regex "de (caf(e|é)|sucre)"
]
, prod = \tokens -> case tokens of
, prod = \case
(Token Quantity qd:
Token RegexMatch (GroupMatch (match:_)):
_) -> Just . Token Quantity $ withProduct match qd

View File

@ -0,0 +1,40 @@
-- 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.Quantity.KM.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Quantity.Types
import Duckling.Resolve
import Duckling.Testing.Types
context :: Context
context = testContext{locale = makeLocale KM Nothing}
corpus :: Corpus
corpus = (context, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Cup 3 Nothing)
[ "បីកែវ"
]
, examples (simple Bowl 1 Nothing)
[ "១ចាន"
]
, examples (simple Pint 15 Nothing)
[ "ដប់៥ថូ"
]
]

View File

@ -0,0 +1,74 @@
-- 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 LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Quantity.KM.Rules
( rules
) where
import Data.HashMap.Strict (HashMap)
import Data.Text (Text)
import Data.String
import Prelude
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
import Duckling.Dimensions.Types
import Duckling.Numeral.Types (NumeralData (..))
import Duckling.Quantity.Helpers
import Duckling.Regex.Types
import Duckling.Types
import qualified Duckling.Numeral.Types as TNumeral
import qualified Duckling.Quantity.Types as TQuantity
ruleQuantityOfProduct :: Rule
ruleQuantityOfProduct = Rule
{ name = "<quantity> of product"
, pattern =
[ regex "(មនុស្ស|បងប្អូន|សត្វ|ឆ្កែ|ឆ្មា|ដើមឈើ|ផ្កា|កុលាប|ផ្ទះ)"
, dimension Quantity
]
, prod = \case
(Token RegexMatch (GroupMatch (match:_)):
Token Quantity qd:
_) -> Just . Token Quantity $ withProduct (Text.toLower match) qd
_ -> Nothing
}
unitsMap :: HashMap Text TQuantity.Unit
unitsMap = HashMap.fromList
[ ("ចាន", TQuantity.Bowl)
, ("ពែង", TQuantity.Cup)
, ("កែវ", TQuantity.Cup)
, ("ថូ", TQuantity.Pint)
]
ruleNumeralUnits :: Rule
ruleNumeralUnits = Rule
{ name = "<number><units>"
, pattern =
[ dimension Numeral
, regex "(ចាន|ពែង|កែវ|ថូ)"
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = v}:
Token RegexMatch (GroupMatch (match:_)):
_) -> do
unit <- HashMap.lookup (Text.toLower match) unitsMap
Just . Token Quantity $ quantity unit v
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleNumeralUnits
, ruleQuantityOfProduct
]

View File

@ -19,6 +19,9 @@ import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.Numeral.KM.Rules as Numeral
import qualified Duckling.Ordinal.KM.Rules as Ordinal
import qualified Duckling.Quantity.KM.Rules as Quantity
import qualified Duckling.Temperature.KM.Rules as Temperature
defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules
@ -33,11 +36,11 @@ langRules (This Distance) = []
langRules (This Duration) = []
langRules (This Email) = []
langRules (This Numeral) = Numeral.rules
langRules (This Ordinal) = []
langRules (This Ordinal) = Ordinal.rules
langRules (This PhoneNumber) = []
langRules (This Quantity) = []
langRules (This Quantity) = Quantity.rules
langRules (This RegexMatch) = []
langRules (This Temperature) = []
langRules (This Temperature) = Temperature.rules
langRules (This Time) = []
langRules (This TimeGrain) = []
langRules (This Url) = []

View File

@ -0,0 +1,39 @@
-- 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.Temperature.KM.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Temperature.Types
import Duckling.Testing.Types
context :: Context
context = testContext{locale = makeLocale KM Nothing}
corpus :: Corpus
corpus = (context, testOptions, allExamples)
allExamples :: [Example]
allExamples = concat
[ examples (simple Celsius 30)
[ "30អង្សា"
, "30អង្សាសេ"
]
, examples (simple Degree 21)
[ "21ដឺក្រេ"
, "21°"
]
]

View File

@ -0,0 +1,55 @@
-- 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 LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Temperature.KM.Rules
( rules
) where
import Data.String
import Prelude
import Duckling.Dimensions.Types
import Duckling.Temperature.Helpers
import Duckling.Types
import qualified Duckling.Temperature.Types as TTemperature
ruleLatentTempDegrees :: Rule
ruleLatentTempDegrees = Rule
{ name = "<latent temp> degrees"
, pattern =
[ Predicate $ isValueOnly False
, regex "ដឺក្រេ|°"
]
, prod = \case
(Token Temperature td:_) -> Just . Token Temperature $
withUnit TTemperature.Degree td
_ -> Nothing
}
ruleTempCelcius :: Rule
ruleTempCelcius = Rule
{ name = "<temp> Celcius"
, pattern =
[ Predicate $ isValueOnly True
, regex "អង្សា(សេ)?"
]
, prod = \case
(Token Temperature td:_) -> Just . Token Temperature $
withUnit TTemperature.Celsius td
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleTempCelcius
, ruleLatentTempDegrees
]

View File

@ -459,6 +459,8 @@ library
, Duckling.Ordinal.JA.Rules
, Duckling.Ordinal.KA.Corpus
, Duckling.Ordinal.KA.Rules
, Duckling.Ordinal.KM.Corpus
, Duckling.Ordinal.KM.Rules
, Duckling.Ordinal.KO.Corpus
, Duckling.Ordinal.KO.Rules
, Duckling.Ordinal.NB.Corpus
@ -504,6 +506,8 @@ library
, Duckling.Quantity.FR.Rules
, Duckling.Quantity.HR.Corpus
, Duckling.Quantity.HR.Rules
, Duckling.Quantity.KM.Corpus
, Duckling.Quantity.KM.Rules
, Duckling.Quantity.KO.Corpus
, Duckling.Quantity.KO.Rules
, Duckling.Quantity.PT.Corpus
@ -539,6 +543,8 @@ library
, Duckling.Temperature.IT.Rules
, Duckling.Temperature.JA.Corpus
, Duckling.Temperature.JA.Rules
, Duckling.Temperature.KM.Corpus
, Duckling.Temperature.KM.Rules
, Duckling.Temperature.KO.Corpus
, Duckling.Temperature.KO.Rules
, Duckling.Temperature.PT.Corpus
@ -878,6 +884,7 @@ test-suite duckling-test
, Duckling.Ordinal.IT.Tests
, Duckling.Ordinal.JA.Tests
, Duckling.Ordinal.KA.Tests
, Duckling.Ordinal.KM.Tests
, Duckling.Ordinal.KO.Tests
, Duckling.Ordinal.NB.Tests
, Duckling.Ordinal.NL.Tests
@ -902,6 +909,7 @@ test-suite duckling-test
, Duckling.Quantity.EN.Tests
, Duckling.Quantity.FR.Tests
, Duckling.Quantity.HR.Tests
, Duckling.Quantity.KM.Tests
, Duckling.Quantity.KO.Tests
, Duckling.Quantity.PT.Tests
, Duckling.Quantity.RO.Tests
@ -919,6 +927,7 @@ test-suite duckling-test
, Duckling.Temperature.HR.Tests
, Duckling.Temperature.IT.Tests
, Duckling.Temperature.JA.Tests
, Duckling.Temperature.KM.Tests
, Duckling.Temperature.KO.Tests
, Duckling.Temperature.PT.Tests
, Duckling.Temperature.RO.Tests

View File

@ -0,0 +1,23 @@
-- 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.Ordinal.KM.Tests
( tests ) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Ordinal.KM.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "KM Tests"
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -30,6 +30,7 @@ import qualified Duckling.Ordinal.ID.Tests as ID
import qualified Duckling.Ordinal.IT.Tests as IT
import qualified Duckling.Ordinal.JA.Tests as JA
import qualified Duckling.Ordinal.KA.Tests as KA
import qualified Duckling.Ordinal.KM.Tests as KM
import qualified Duckling.Ordinal.KO.Tests as KO
import qualified Duckling.Ordinal.NB.Tests as NB
import qualified Duckling.Ordinal.NL.Tests as NL
@ -64,6 +65,7 @@ tests = testGroup "Ordinal Tests"
, IT.tests
, JA.tests
, KA.tests
, KM.tests
, KO.tests
, NB.tests
, NL.tests

View File

@ -0,0 +1,23 @@
-- 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.Quantity.KM.Tests
( tests ) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Quantity.KM.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "KM Tests"
[ makeCorpusTest [This Quantity] corpus
]

View File

@ -18,6 +18,7 @@ import qualified Duckling.Quantity.AR.Tests as AR
import qualified Duckling.Quantity.EN.Tests as EN
import qualified Duckling.Quantity.FR.Tests as FR
import qualified Duckling.Quantity.HR.Tests as HR
import qualified Duckling.Quantity.KM.Tests as KM
import qualified Duckling.Quantity.KO.Tests as KO
import qualified Duckling.Quantity.PT.Tests as PT
import qualified Duckling.Quantity.RO.Tests as RO
@ -30,6 +31,7 @@ tests = testGroup "Quantity Tests"
, EN.tests
, FR.tests
, HR.tests
, KM.tests
, KO.tests
, PT.tests
, RO.tests

View File

@ -0,0 +1,23 @@
-- 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.Temperature.KM.Tests
( tests ) where
import Prelude
import Data.String
import Test.Tasty
import Duckling.Dimensions.Types
import Duckling.Temperature.KM.Corpus
import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "KM Tests"
[ makeCorpusTest [This Temperature] corpus
]

View File

@ -21,6 +21,7 @@ import qualified Duckling.Temperature.HI.Tests as HI
import qualified Duckling.Temperature.HR.Tests as HR
import qualified Duckling.Temperature.IT.Tests as IT
import qualified Duckling.Temperature.JA.Tests as JA
import qualified Duckling.Temperature.KM.Tests as KM
import qualified Duckling.Temperature.KO.Tests as KO
import qualified Duckling.Temperature.PT.Tests as PT
import qualified Duckling.Temperature.RO.Tests as RO
@ -38,6 +39,7 @@ tests = testGroup "Temperature Tests"
, HR.tests
, IT.tests
, JA.tests
, KM.tests
, KO.tests
, PT.tests
, RO.tests