duckling/tests/Duckling/Numeral/EN/Tests.hs
Josef Svenningsson 7889f396f3 Remove dependency on Data.Some (#533)
Summary:
Pull Request resolved: https://github.com/facebook/duckling/pull/533

In recent versions of Data.Some the name of the constructor, `This` has changed name to `Some`. This has become rather problematic for us to migrate so we're just going to remove the dependency. The meat of this diff is adding the type `Seal` to `Duckling.Types`. That type replaces `Some`.

Reviewed By: pepeiborra

Differential Revision: D23929459

fbshipit-source-id: 8ff4146ecba4f1119a17899961b2d877547f6e4f
2020-09-28 01:33:01 -07:00

67 lines
1.7 KiB
Haskell

-- 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.
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Numeral.EN.Tests
( tests
) where
import Data.String
import Prelude
import Test.Tasty
import Test.Tasty.HUnit
import Duckling.Dimensions.Types
import Duckling.Numeral.EN.Corpus
import Duckling.Numeral.Types
import Duckling.Testing.Asserts
import Duckling.Testing.Types
import Duckling.Types (Range(..))
tests :: TestTree
tests = testGroup "EN Tests"
[ makeCorpusTest [Seal Numeral] corpus
, surroundTests
, intersectTests
, rangeTests
]
surroundTests :: TestTree
surroundTests = testCase "Surround Tests" $
mapM_ (analyzedFirstTest testContext testOptions .
withTargets [Seal Numeral]) xs
where
xs = concat
[ examples (NumeralValue 3)
[ "3km"
]
, examples (NumeralValue 100000)
[ "100k€"
, "100k\x20ac"
]
, examples (NumeralValue 10.99)
[ "10.99$"
]
]
intersectTests :: TestTree
intersectTests = testCase "Intersect Test" $
mapM_ (analyzedNTest testContext testOptions . withTargets [Seal Numeral]) xs
where
xs = [ ("10 millions minus 10", 2)
]
rangeTests :: TestTree
rangeTests = testCase "Range Test" $
mapM_ (analyzedRangeTest testContext testOptions . withTargets [Seal Numeral]) xs
where
xs = [ ("negative negative 5", Range 9 19) -- prevent double negatives
, ("negative-5", Range 8 10) -- prevent double negatives
, ("- -5", Range 2 4) -- prevent clash with engine tokenizer
]