Move onto dependent-sum instead of custom local data Some

Summary:
No need to reinvent the wheel when `dependent-sum` has what we need. I re-export `Some(..)` from `Duckling.Dimensions.Types` to cut down on import bloat.
Instead of a `Read` instance I created a `fromName` function.

Reviewed By: zilberstein

Differential Revision: D4710014

fbshipit-source-id: 1d4e86d
This commit is contained in:
Jonathan Coens 2017-03-15 10:15:42 -07:00 committed by Facebook Github Bot
parent d23ae54ab9
commit 41800a3171
180 changed files with 707 additions and 704 deletions

View File

@ -49,7 +49,7 @@ analyze :: Text -> Context -> HashSet (Some Dimension) -> [ResolvedToken]
analyze input context@Context{..} targets =
rank (classifiers lang) targets
. filter (\(Resolved{node = Node{token = (Token d _)}}) ->
HashSet.null targets || HashSet.member (Some d) targets
HashSet.null targets || HashSet.member (This d) targets
)
$ parseAndResolve (rulesFor lang targets) input context

View File

@ -38,7 +38,7 @@ tests = testGroup "API Tests"
parseTest :: TestTree
parseTest = testCase "Parse Test" $
case parse sentence testContext [Some Numeral] of
case parse sentence testContext [This Numeral] of
[] -> assertFailure "empty result"
(Entity dim body value start end:_) -> do
assertEqual "dim" "number" dim
@ -60,39 +60,39 @@ rankFilterTest :: TestTree
rankFilterTest = testCase "Rank Filter Tests" $ do
mapM_ check
[ ( "in 2 minutes"
, [Some Numeral, Some Duration, Some Time]
, [Some Time]
, [This Numeral, This Duration, This Time]
, [This Time]
)
, ( "in 2 minutes, about 42 degrees"
, [Some Numeral, Some Temperature, Some Time]
, [Some Time, Some Temperature]
, [This Numeral, This Temperature, This Time]
, [This Time, This Temperature]
)
, ( "today works... and tomorrow at 9pm too"
, [Some Numeral, Some Time]
, [Some Time, Some Time]
, [This Numeral, This Time]
, [This Time, This Time]
)
, ( "between 9:30 and 11:00 on thursday or Saturday and Thanksgiving Day"
, [Some Numeral, Some Time]
, [Some Time, Some Time, Some Time]
, [This Numeral, This Time]
, [This Time, This Time, This Time]
)
, ("the day after tomorrow 5pm", [Some Time], [Some Time])
, ("the day after tomorrow 5pm", [Some Time, Some Numeral], [Some Time])
, ("the day after tomorrow 5pm", [], [Some Time])
, ("the day after tomorrow 5pm", [This Time], [This Time])
, ("the day after tomorrow 5pm", [This Time, This Numeral], [This Time])
, ("the day after tomorrow 5pm", [], [This Time])
]
where
check :: (Text, [Some Dimension], [Some Dimension]) -> IO ()
check (sentence, targets, expected) =
let go = analyze sentence testContext $ HashSet.fromList targets
actual = flip map go $
\(Resolved{node=Node{token=Token d _}}) -> Some d
\(Resolved{node=Node{token=Token d _}}) -> This d
in assertEqual ("wrong winners for " ++ show sentence) expected actual
rankOrderTest :: TestTree
rankOrderTest = testCase "Rank Order Tests" $ do
mapM_ check
[ ("tomorrow at 5PM or 8PM", [Some Time])
, ("321 12 3456 ... 7", [Some Numeral])
, ("42 today 23 tomorrow", [Some Numeral, Some Time])
[ ("tomorrow at 5PM or 8PM", [This Time])
, ("321 12 3456 ... 7", [This Numeral])
, ("42 today 23 tomorrow", [This Numeral, This Time])
]
where
check (s, targets) =
@ -104,13 +104,13 @@ rangeTest = testCase "Range Tests" $ do
mapM_ (analyzedFirstTest testContext) xs
where
xs = map (\(input, targets, range) -> (input, targets, f range))
[ ( "order status 3233763377", [Some PhoneNumber], Range 13 23 )
, ( " 3233763377 " , [Some PhoneNumber], Range 2 12 )
, ( " -3233763377" , [Some PhoneNumber], Range 2 12 )
, ( " now" , [Some Time] , Range 2 5 )
, ( " Monday " , [Some Time] , Range 3 9 )
, ( " next week " , [Some Time] , Range 2 13 )
, ( " 42\n\n" , [Some Numeral] , Range 3 5 )
[ ( "order status 3233763377", [This PhoneNumber], Range 13 23 )
, ( " 3233763377 " , [This PhoneNumber], Range 2 12 )
, ( " -3233763377" , [This PhoneNumber], Range 2 12 )
, ( " now" , [This Time] , Range 2 5 )
, ( " Monday " , [This Time] , Range 3 9 )
, ( " next week " , [This Time] , Range 2 13 )
, ( " 42\n\n" , [This Numeral] , Range 3 5 )
]
f :: Range -> TestPredicate
f expected _ (Resolved {range = actual}) = expected == actual
@ -119,13 +119,13 @@ supportedDimensionsTest :: TestTree
supportedDimensionsTest = testCase "Supported Dimensions Test" $ do
mapM_ check
[ ( AR
, [ Some Email, Some Finance, Some PhoneNumber, Some Url, Some Numeral
, Some Ordinal
, [ This Email, This Finance, This PhoneNumber, This Url, This Numeral
, This Ordinal
]
)
, ( PL
, [ Some Email, Some Finance, Some PhoneNumber, Some Url, Some Duration
, Some Numeral, Some Ordinal, Some Time
, [ This Email, This Finance, This PhoneNumber, This Url, This Duration
, This Numeral, This Ordinal, This Time
]
)
]

View File

@ -13,6 +13,7 @@
module Duckling.Core
( Context(..)
, Dimension(..)
, fromName
, Entity(..)
, Lang(..)
, Some(..)

View File

@ -60,7 +60,7 @@ parses l sentence targets = flip filter tokens $
\(Resolved {node = Node{token = (Token d _)}}) ->
case targets of
[] -> True
_ -> elem (Some d) targets
_ -> elem (This d) targets
where
tokens = parseAndResolve rules sentence testContext {lang = l}
rules = rulesFor l $ HashSet.fromList targets

View File

@ -56,21 +56,21 @@ explicitDimensions targets = HashSet.union targets deps
-- | Ordinal depends on Numeral for JA, KO, and ZH.
dependents :: Some Dimension -> HashSet (Some Dimension)
dependents (Some Distance) = HashSet.singleton (Some Numeral)
dependents (Some Duration) = HashSet.fromList [Some Numeral, Some TimeGrain]
dependents (Some Numeral) = HashSet.empty
dependents (Some Email) = HashSet.empty
dependents (Some Finance) = HashSet.singleton (Some Numeral)
dependents (Some Ordinal) = HashSet.singleton (Some Numeral)
dependents (Some PhoneNumber) = HashSet.empty
dependents (Some Quantity) = HashSet.singleton (Some Numeral)
dependents (Some RegexMatch) = HashSet.empty
dependents (Some Temperature) = HashSet.singleton (Some Numeral)
dependents (Some Time) =
HashSet.fromList [Some Numeral, Some Duration, Some Ordinal, Some TimeGrain]
dependents (Some TimeGrain) = HashSet.empty
dependents (Some Url) = HashSet.empty
dependents (Some Volume) = HashSet.singleton (Some Numeral)
dependents (This Distance) = HashSet.singleton (This Numeral)
dependents (This Duration) = HashSet.fromList [This Numeral, This TimeGrain]
dependents (This Numeral) = HashSet.empty
dependents (This Email) = HashSet.empty
dependents (This Finance) = HashSet.singleton (This Numeral)
dependents (This Ordinal) = HashSet.singleton (This Numeral)
dependents (This PhoneNumber) = HashSet.empty
dependents (This Quantity) = HashSet.singleton (This Numeral)
dependents (This RegexMatch) = HashSet.empty
dependents (This Temperature) = HashSet.singleton (This Numeral)
dependents (This Time) =
HashSet.fromList [This Numeral, This Duration, This Ordinal, This TimeGrain]
dependents (This TimeGrain) = HashSet.empty
dependents (This Url) = HashSet.empty
dependents (This Volume) = HashSet.singleton (This Numeral)
langDimensions :: Lang -> [Some Dimension]
langDimensions AR = ARDimensions.allDimensions

View File

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

View File

@ -14,8 +14,8 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Email
, Some Finance
, Some PhoneNumber
, Some Url
[ This Email
, This Finance
, This PhoneNumber
, This Url
]

View File

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

View File

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

View File

@ -14,12 +14,12 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Distance
, Some Duration
, Some Numeral
, Some Ordinal
, Some Quantity
, Some Temperature
, Some Time
, Some Volume
[ This Distance
, This Duration
, This Numeral
, This Ordinal
, This Quantity
, This Temperature
, This Time
, This Volume
]

View File

@ -14,11 +14,11 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Distance
, Some Duration
, Some Numeral
, Some Ordinal
, Some Temperature
, Some Time
, Some Volume
[ This Distance
, This Duration
, This Numeral
, This Ordinal
, This Temperature
, This Time
, This Volume
]

View File

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

View File

@ -14,12 +14,12 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Distance
, Some Duration
, Some Numeral
, Some Ordinal
, Some Quantity
, Some Temperature
, Some Time
, Some Volume
[ This Distance
, This Duration
, This Numeral
, This Ordinal
, This Quantity
, This Temperature
, This Time
, This Volume
]

View File

@ -14,11 +14,11 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Distance
, Some Duration
, Some Numeral
, Some Ordinal
, Some Temperature
, Some Time
, Some Volume
[ This Distance
, This Duration
, This Numeral
, This Ordinal
, This Temperature
, This Time
, This Volume
]

View File

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

View File

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

View File

@ -14,9 +14,9 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Duration
, Some Numeral
, Some Ordinal
, Some Temperature
, Some Time
[ This Duration
, This Numeral
, This Ordinal
, This Temperature
, This Time
]

View File

@ -14,12 +14,12 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Distance
, Some Duration
, Some Numeral
, Some Ordinal
, Some Quantity
, Some Temperature
, Some Time
, Some Volume
[ This Distance
, This Duration
, This Numeral
, This Ordinal
, This Quantity
, This Temperature
, This Time
, This Volume
]

View File

@ -14,5 +14,5 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Numeral
[ This Numeral
]

View File

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

View File

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

View File

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

View File

@ -14,12 +14,12 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Distance
, Some Duration
, Some Numeral
, Some Ordinal
, Some Quantity
, Some Temperature
, Some Time
, Some Volume
[ This Distance
, This Duration
, This Numeral
, This Ordinal
, This Quantity
, This Temperature
, This Time
, This Volume
]

View File

@ -14,12 +14,12 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Distance
, Some Duration
, Some Numeral
, Some Ordinal
, Some Quantity
, Some Temperature
, Some Time
, Some Volume
[ This Distance
, This Duration
, This Numeral
, This Ordinal
, This Quantity
, This Temperature
, This Time
, This Volume
]

View File

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

View File

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

View File

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

View File

@ -12,16 +12,22 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE StandaloneDeriving #-}
module Duckling.Dimensions.Types
( Some(..)
, Dimension(..)
, dimEq
, fromName
) where
import Data.GADT.Compare
import Data.GADT.Show
import Data.Hashable
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe
import Data.Some
import Data.Text (Text)
-- Intentionally limit use of Typeable to avoid casting or typeOf usage
import Data.Typeable ((:~:)(..))
import TextShow (TextShow(..))
@ -43,11 +49,6 @@ import Duckling.TimeGrain.Types (Grain)
import Duckling.Url.Types (UrlData)
import Duckling.Volume.Types (VolumeData)
-- -----------------------------------------------------------------
-- Wrapper to house the existential
data Some t = forall a . Some (t a)
-- -----------------------------------------------------------------
-- Dimension
@ -71,7 +72,6 @@ data Dimension a where
Volume :: Dimension VolumeData
-- Show
deriving instance Show (Some Dimension)
instance Show (Dimension a) where
show RegexMatch = "regex"
show Distance = "distance"
@ -87,21 +87,17 @@ instance Show (Dimension a) where
show TimeGrain = "time-grain"
show Url = "url"
show Volume = "volume"
instance GShow Dimension where gshowsPrec = showsPrec
-- TextShow
instance TextShow (Dimension a) where
showb d = TS.fromString $ show d
instance TextShow (Some Dimension) where
showb (Some d) = showb d
-- Eq
deriving instance Eq (Dimension a)
instance Eq (Some Dimension) where
(==) (Some a) (Some b) = isJust $ dimEq a b
showb (This d) = showb d
-- Hashable
instance Hashable (Some Dimension) where
hashWithSalt s (Some a) = hashWithSalt s a
hashWithSalt s (This a) = hashWithSalt s a
instance Hashable (Dimension a) where
hashWithSalt s RegexMatch = hashWithSalt s (0::Int)
hashWithSalt s Distance = hashWithSalt s (1::Int)
@ -118,50 +114,51 @@ instance Hashable (Dimension a) where
hashWithSalt s Url = hashWithSalt s (12::Int)
hashWithSalt s Volume = hashWithSalt s (13::Int)
instance Read (Some Dimension) where
-- Regex is intentionally ignored
readsPrec _ "amount-of-money" = [(Some Finance, "")]
readsPrec _ "distance" = [(Some Distance, "")]
readsPrec _ "duration" = [(Some Duration, "")]
readsPrec _ "email" = [(Some Email, "")]
readsPrec _ "number" = [(Some Numeral, "")]
readsPrec _ "ordinal" = [(Some Ordinal, "")]
readsPrec _ "phone-number" = [(Some PhoneNumber, "")]
readsPrec _ "quantity" = [(Some Quantity, "")]
readsPrec _ "temperature" = [(Some Temperature, "")]
readsPrec _ "time" = [(Some Time, "")]
readsPrec _ "url" = [(Some Url, "")]
readsPrec _ "volume" = [(Some Volume, "")]
readsPrec _ _ = []
-- | Proof that 2 dimensions are the same Type
-- 2 matches per dimension for pattern exhaustiveness sake
dimEq :: Dimension a -> Dimension b -> Maybe (a :~: b)
dimEq RegexMatch RegexMatch = Just Refl
dimEq RegexMatch _ = Nothing
dimEq Distance Distance = Just Refl
dimEq Distance _ = Nothing
dimEq Duration Duration = Just Refl
dimEq Duration _ = Nothing
dimEq Email Email = Just Refl
dimEq Email _ = Nothing
dimEq Finance Finance = Just Refl
dimEq Finance _ = Nothing
dimEq Numeral Numeral = Just Refl
dimEq Numeral _ = Nothing
dimEq Ordinal Ordinal = Just Refl
dimEq Ordinal _ = Nothing
dimEq PhoneNumber PhoneNumber = Just Refl
dimEq PhoneNumber _ = Nothing
dimEq Quantity Quantity = Just Refl
dimEq Quantity _ = Nothing
dimEq Temperature Temperature = Just Refl
dimEq Temperature _ = Nothing
dimEq Time Time = Just Refl
dimEq Time _ = Nothing
dimEq TimeGrain TimeGrain = Just Refl
dimEq TimeGrain _ = Nothing
dimEq Url Url = Just Refl
dimEq Url _ = Nothing
dimEq Volume Volume = Just Refl
dimEq Volume _ = Nothing
fromName :: Text -> Maybe (Some Dimension)
fromName name = HashMap.lookup name m
where
m = HashMap.fromList
[ ("amount-of-money", This Finance)
, ("distance", This Distance)
, ("duration", This Duration)
, ("email", This Email)
, ("number", This Numeral)
, ("ordinal", This Ordinal)
, ("phone-number", This PhoneNumber)
, ("quantity", This Quantity)
, ("temperature", This Temperature)
, ("time", This Time)
, ("url", This Url)
, ("volume", This Volume)
]
instance GEq Dimension where
geq RegexMatch RegexMatch = Just Refl
geq RegexMatch _ = Nothing
geq Distance Distance = Just Refl
geq Distance _ = Nothing
geq Duration Duration = Just Refl
geq Duration _ = Nothing
geq Email Email = Just Refl
geq Email _ = Nothing
geq Finance Finance = Just Refl
geq Finance _ = Nothing
geq Numeral Numeral = Just Refl
geq Numeral _ = Nothing
geq Ordinal Ordinal = Just Refl
geq Ordinal _ = Nothing
geq PhoneNumber PhoneNumber = Just Refl
geq PhoneNumber _ = Nothing
geq Quantity Quantity = Just Refl
geq Quantity _ = Nothing
geq Temperature Temperature = Just Refl
geq Temperature _ = Nothing
geq Time Time = Just Refl
geq Time _ = Nothing
geq TimeGrain TimeGrain = Just Refl
geq TimeGrain _ = Nothing
geq Url Url = Just Refl
geq Url _ = Nothing
geq Volume Volume = Just Refl
geq Volume _ = Nothing

View File

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

View File

@ -14,5 +14,5 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Numeral
[ This Numeral
]

View File

@ -14,9 +14,9 @@ import Duckling.Dimensions.Types
allDimensions :: [Some Dimension]
allDimensions =
[ Some Duration
, Some Numeral
, Some Ordinal
, Some Temperature
, Some Time
[ This Duration
, This Numeral
, This Ordinal
, This Temperature
, This Time
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "EN Tests"
[ makeCorpusTest [Some Distance] corpus
[ makeCorpusTest [This Distance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Distance.ES.Corpus
tests :: TestTree
tests = testGroup "ES Tests"
[ makeCorpusTest [Some Distance] corpus
[ makeCorpusTest [This Distance] corpus
]

View File

@ -17,5 +17,5 @@ import Duckling.Distance.FR.Corpus
tests :: TestTree
tests = testGroup "FR Tests"
[ makeCorpusTest [Some Distance] corpus
[ makeCorpusTest [This Distance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "GA Tests"
[ makeCorpusTest [Some Distance] corpus
[ makeCorpusTest [This Distance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Distance.KO.Corpus
tests :: TestTree
tests = testGroup "KO Tests"
[ makeCorpusTest [Some Distance] corpus
[ makeCorpusTest [This Distance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Distance.NL.Corpus
tests :: TestTree
tests = testGroup "NL Tests"
[ makeCorpusTest [Some Distance] corpus
[ makeCorpusTest [This Distance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Distance.PT.Corpus
tests :: TestTree
tests = testGroup "PT Tests"
[ makeCorpusTest [Some Distance] corpus
[ makeCorpusTest [This Distance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Distance.RO.Corpus
tests :: TestTree
tests = testGroup "RO Tests"
[ makeCorpusTest [Some Distance] corpus
[ makeCorpusTest [This Distance] corpus
]

View File

@ -20,6 +20,6 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "EN Tests"
[ makeCorpusTest [Some Duration] corpus
, makeNegativeCorpusTest [Some Duration] negativeCorpus
[ makeCorpusTest [This Duration] corpus
, makeNegativeCorpusTest [This Duration] negativeCorpus
]

View File

@ -20,6 +20,6 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "FR Tests"
[ makeCorpusTest [Some Duration] corpus
, makeNegativeCorpusTest [Some Duration] negativeCorpus
[ makeCorpusTest [This Duration] corpus
, makeNegativeCorpusTest [This Duration] negativeCorpus
]

View File

@ -20,5 +20,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "GA Tests"
[ makeCorpusTest [Some Duration] corpus
[ makeCorpusTest [This Duration] corpus
]

View File

@ -20,5 +20,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "JA Tests"
[ makeCorpusTest [Some Duration] corpus
[ makeCorpusTest [This Duration] corpus
]

View File

@ -20,5 +20,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "KO Tests"
[ makeCorpusTest [Some Duration] corpus
[ makeCorpusTest [This Duration] corpus
]

View File

@ -20,5 +20,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "NB Tests"
[ makeCorpusTest [Some Duration] corpus
[ makeCorpusTest [This Duration] corpus
]

View File

@ -20,5 +20,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "PL Tests"
[ makeCorpusTest [Some Duration] corpus
[ makeCorpusTest [This Duration] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "PT Tests"
[ makeCorpusTest [Some Duration] corpus
[ makeCorpusTest [This Duration] corpus
]

View File

@ -20,5 +20,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "RO Tests"
[ makeCorpusTest [Some Duration] corpus
[ makeCorpusTest [This Duration] corpus
]

View File

@ -20,5 +20,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "SV Tests"
[ makeCorpusTest [Some Duration] corpus
[ makeCorpusTest [This Duration] corpus
]

View File

@ -24,7 +24,7 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ZH Tests"
[ testCase "Corpus Tests" $
mapM_ (analyzedFirstTest context {lang = ZH} . withTargets [Some Duration])
mapM_ (analyzedFirstTest context {lang = ZH} . withTargets [This Duration])
xs
]
where

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "Email Tests"
[ makeCorpusTest [Some Email] corpus
[ makeCorpusTest [This Email] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "Email Tests"
[ makeCorpusTest [Some Email] corpus
[ makeCorpusTest [This Email] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "Email Tests"
[ makeCorpusTest [Some Email] corpus
[ makeCorpusTest [This Email] corpus
]

View File

@ -21,8 +21,8 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "Email Tests"
[ makeCorpusTest [Some Email] corpus
, makeNegativeCorpusTest [Some Email] negativeCorpus
[ makeCorpusTest [This Email] corpus
, makeNegativeCorpusTest [This Email] negativeCorpus
, EN.tests
, FR.tests
, IT.tests

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "EN Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Finance.ES.Corpus
tests :: TestTree
tests = testGroup "ES Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Finance.FR.Corpus
tests :: TestTree
tests = testGroup "FR Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Finance.GA.Corpus
tests :: TestTree
tests = testGroup "GA Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Finance.ID.Corpus
tests :: TestTree
tests = testGroup "ID Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Finance.KO.Corpus
tests :: TestTree
tests = testGroup "KO Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "NB Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "PT Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Finance.RO.Corpus
tests :: TestTree
tests = testGroup "RO Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "SV Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "VI Tests"
[ makeCorpusTest [Some Finance] corpus
[ makeCorpusTest [This Finance] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "AR Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "DA Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "DE Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -25,13 +25,13 @@ import Duckling.Testing.Types
tests :: TestTree
tests = testGroup "EN Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
, surroundTests
]
surroundTests :: TestTree
surroundTests = testCase "Surround Tests" $
mapM_ (analyzedFirstTest testContext . withTargets [Some Numeral]) xs
mapM_ (analyzedFirstTest testContext . withTargets [This Numeral]) xs
where
xs = concat
[ examples (NumberValue 3)

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ES Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ET Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "FR Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "GA Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ID Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "IT Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "JA Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "KO Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "MY Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "NB Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "NL Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "PL Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "PT Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "RO Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "RU Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "SV Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "TR Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "UK Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "VI Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ZH Tests"
[ makeCorpusTest [Some Numeral] corpus
[ makeCorpusTest [This Numeral] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "AR Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "DA Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "DE Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -20,5 +20,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "EN Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ET Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "FR Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -20,5 +20,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "GA Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "ID Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "IT Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "JA Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

View File

@ -19,5 +19,5 @@ import Duckling.Testing.Asserts
tests :: TestTree
tests = testGroup "KO Tests"
[ makeCorpusTest [Some Ordinal] corpus
[ makeCorpusTest [This Ordinal] corpus
]

Some files were not shown because too many files have changed in this diff Show More