mirror of
https://github.com/facebook/duckling.git
synced 2024-11-24 07:23:03 +03:00
Initial commit
fbshipit-source-id: 301a10f448e9623aa1c953544f42de562909e192
This commit is contained in:
commit
3f8e52e70a
62
Duckling/Api.hs
Normal file
62
Duckling/Api.hs
Normal file
@ -0,0 +1,62 @@
|
||||
-- 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 RecordWildCards #-}
|
||||
{-# LANGUAGE NoRebindableSyntax #-}
|
||||
|
||||
module Duckling.Api
|
||||
( analyze
|
||||
, formatToken
|
||||
, parse
|
||||
, supportedDimensions
|
||||
) where
|
||||
|
||||
import Data.HashMap.Strict (HashMap)
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Data.HashSet (HashSet)
|
||||
import qualified Data.HashSet as HashSet
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as Text
|
||||
import Prelude
|
||||
import TextShow
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Dimensions
|
||||
import Duckling.Engine
|
||||
import Duckling.Lang
|
||||
import Duckling.Ranking.Classifiers
|
||||
import Duckling.Ranking.Rank
|
||||
import Duckling.Resolve
|
||||
import Duckling.Rules
|
||||
import Duckling.Types
|
||||
|
||||
-- | Parses `input` and returns a curated list of entities found.
|
||||
parse :: Text -> Context -> [Some Dimension] -> [Entity]
|
||||
parse input ctx = map (formatToken input) . analyze input ctx . HashSet.fromList
|
||||
|
||||
supportedDimensions :: HashMap Lang [Some Dimension]
|
||||
supportedDimensions =
|
||||
HashMap.fromList [ (l, allDimensions l) | l <- [minBound..maxBound] ]
|
||||
|
||||
-- | Returns a curated list of resolved tokens found
|
||||
-- When `targets` is non-empty, returns only tokens of such dimensions.
|
||||
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
|
||||
)
|
||||
$ parseAndResolve (rulesFor lang targets) input context
|
||||
|
||||
-- | Converts the resolved token to the API format
|
||||
formatToken :: Text -> ResolvedToken -> Entity
|
||||
formatToken sentence (Resolved (Range start end) (Node{token=Token dimension _}) jsonValue) =
|
||||
Entity (showt dimension) body val start end
|
||||
where
|
||||
body = Text.drop start $ Text.take end sentence
|
||||
val = toJText jsonValue
|
137
Duckling/Api/Tests.hs
Normal file
137
Duckling/Api/Tests.hs
Normal file
@ -0,0 +1,137 @@
|
||||
-- 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 NoRebindableSyntax #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
|
||||
module Duckling.Api.Tests (tests) where
|
||||
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import qualified Data.HashSet as HashSet
|
||||
import Data.List (sortOn)
|
||||
import Data.Text (Text)
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit
|
||||
|
||||
import Duckling.Api
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Lang
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Testing.Asserts
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.Types
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "API Tests"
|
||||
[ parseTest
|
||||
, rankTest
|
||||
, rangeTest
|
||||
, supportedDimensionsTest
|
||||
]
|
||||
|
||||
parseTest :: TestTree
|
||||
parseTest = testCase "Parse Test" $
|
||||
case parse sentence testContext [Some DNumber] of
|
||||
[] -> assertFailure "empty result"
|
||||
(Entity dim body value start end:_) -> do
|
||||
assertEqual "dim" "number" dim
|
||||
assertEqual "body" "42" body
|
||||
assertEqual "value" val value
|
||||
assertEqual "start" 4 start
|
||||
assertEqual "end" 6 end
|
||||
where
|
||||
sentence = "hey 42 there"
|
||||
val = toJText TNumber.NumberValue {TNumber.vValue = 42.0}
|
||||
|
||||
rankTest :: TestTree
|
||||
rankTest = testGroup "Rank Tests"
|
||||
[ rankFilterTest
|
||||
, rankOrderTest
|
||||
]
|
||||
|
||||
rankFilterTest :: TestTree
|
||||
rankFilterTest = testCase "Rank Filter Tests" $ do
|
||||
mapM_ check
|
||||
[ ( "in 2 minutes"
|
||||
, [Some DNumber, Some Duration, Some Time]
|
||||
, [Some Time]
|
||||
)
|
||||
, ( "in 2 minutes, about 42 degrees"
|
||||
, [Some DNumber, Some Temperature, Some Time]
|
||||
, [Some Time, Some Temperature]
|
||||
)
|
||||
, ( "today works... and tomorrow at 9pm too"
|
||||
, [Some DNumber, Some Time]
|
||||
, [Some Time, Some Time]
|
||||
)
|
||||
, ( "between 9:30 and 11:00 on thursday or Saturday and Thanksgiving Day"
|
||||
, [Some DNumber, Some Time]
|
||||
, [Some Time, Some Time, Some Time]
|
||||
)
|
||||
, ("the day after tomorrow 5pm", [Some Time], [Some Time])
|
||||
, ("the day after tomorrow 5pm", [Some Time, Some DNumber], [Some Time])
|
||||
, ("the day after tomorrow 5pm", [], [Some 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
|
||||
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 DNumber])
|
||||
, ("42 today 23 tomorrow", [Some DNumber, Some Time])
|
||||
]
|
||||
where
|
||||
check (s, targets) =
|
||||
let tokens = analyze s testContext $ HashSet.fromList targets
|
||||
in assertEqual "wrong ordering" (sortOn range tokens) tokens
|
||||
|
||||
rangeTest :: TestTree
|
||||
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 DNumber] , Range 3 5 )
|
||||
]
|
||||
f :: Range -> TestPredicate
|
||||
f expected _ (Resolved {range = actual}) = expected == actual
|
||||
|
||||
supportedDimensionsTest :: TestTree
|
||||
supportedDimensionsTest = testCase "Supported Dimensions Test" $ do
|
||||
mapM_ check
|
||||
[ ( AR
|
||||
, [ Some Email, Some Finance, Some PhoneNumber, Some Url, Some DNumber
|
||||
, Some Ordinal
|
||||
]
|
||||
)
|
||||
, ( PL
|
||||
, [ Some Email, Some Finance, Some PhoneNumber, Some Url, Some Duration
|
||||
, Some DNumber, Some Ordinal, Some Time
|
||||
]
|
||||
)
|
||||
]
|
||||
where
|
||||
check :: (Lang, [Some Dimension]) -> IO ()
|
||||
check (l, expected) = case HashMap.lookup l supportedDimensions of
|
||||
Nothing -> assertFailure $ "no dimensions for " ++ show l
|
||||
Just actual ->
|
||||
assertEqual ("wrong dimensions for " ++ show l) expected actual
|
56
Duckling/Core.hs
Normal file
56
Duckling/Core.hs
Normal file
@ -0,0 +1,56 @@
|
||||
-- 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 NoRebindableSyntax #-}
|
||||
|
||||
-- | Everything needed to run Duckling.
|
||||
|
||||
module Duckling.Core
|
||||
( Context(..)
|
||||
, Dimension(..)
|
||||
, Entity(..)
|
||||
, Lang(..)
|
||||
, Some(..)
|
||||
|
||||
-- Duckling API
|
||||
, parse
|
||||
, supportedDimensions
|
||||
|
||||
-- Reference time builders
|
||||
, currentReftime
|
||||
, makeReftime
|
||||
) where
|
||||
|
||||
import Data.HashMap.Strict (HashMap)
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Data.Maybe
|
||||
import Data.Text (Text)
|
||||
import Data.Time
|
||||
import Data.Time.LocalTime.TimeZone.Series
|
||||
import Prelude
|
||||
|
||||
import Duckling.Api
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Types
|
||||
|
||||
-- | Builds a `DucklingTime` for timezone `tz` at `utcTime`.
|
||||
-- If no `series` found for `tz`, uses UTC.
|
||||
makeReftime :: HashMap Text TimeZoneSeries -> Text -> UTCTime -> DucklingTime
|
||||
makeReftime series tz utcTime = DucklingTime $ ZoneSeriesTime ducklingTime tzs
|
||||
where
|
||||
tzs = fromMaybe (TimeZoneSeries utc []) $ HashMap.lookup tz series
|
||||
ducklingTime = toUTC $ utcToLocalTime' tzs utcTime
|
||||
|
||||
-- | Builds a `DucklingTime` for timezone `tz` at current time.
|
||||
-- If no `series` found for `tz`, uses UTC.
|
||||
currentReftime :: HashMap Text TimeZoneSeries -> Text -> IO DucklingTime
|
||||
currentReftime series tz = do
|
||||
utcNow <- getCurrentTime
|
||||
return $ makeReftime series tz utcNow
|
71
Duckling/Data/TimeZone.hs
Normal file
71
Duckling/Data/TimeZone.hs
Normal file
@ -0,0 +1,71 @@
|
||||
-- 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.Data.TimeZone
|
||||
( loadTimeZoneSeries
|
||||
) where
|
||||
|
||||
import qualified Control.Exception as E
|
||||
import Control.Monad.Extra
|
||||
import Data.Either
|
||||
import Data.HashMap.Strict (HashMap)
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import qualified Data.HashSet as HashSet
|
||||
import Data.String
|
||||
import qualified Data.Text as Text
|
||||
import Data.Time (TimeZone(..))
|
||||
import Data.Text (Text)
|
||||
import Data.Time.LocalTime.TimeZone.Olson
|
||||
import Data.Time.LocalTime.TimeZone.Series
|
||||
import System.Directory
|
||||
import System.FilePath
|
||||
|
||||
import Prelude
|
||||
|
||||
-- | Reference implementation for pulling TimeZoneSeries data from local
|
||||
-- Olson files.
|
||||
-- Many linux distros have Olson data in "/usr/share/zoneinfo/"
|
||||
loadTimeZoneSeries :: FilePath -> IO (HashMap Text TimeZoneSeries)
|
||||
loadTimeZoneSeries base = do
|
||||
files <- getFiles base
|
||||
tzSeries <- mapM parseOlsonFile files
|
||||
-- This data is large, will live a long time, and essentially be constant,
|
||||
-- so it's a perfect candidate for compact regions
|
||||
return $ HashMap.fromList $ rights tzSeries
|
||||
where
|
||||
-- Multiple versions of the data can exist. We intentionally ignore the
|
||||
-- posix and right formats
|
||||
ignored_dirs = HashSet.fromList $ map (base </>)
|
||||
[ "posix", "right" ]
|
||||
|
||||
-- Recursively crawls a directory to list every file underneath it,
|
||||
-- ignoring certain directories as needed
|
||||
getFiles :: FilePath -> IO [FilePath]
|
||||
getFiles dir = do
|
||||
fsAll <- getDirectoryContents dir
|
||||
let
|
||||
fs = filter notDotFile fsAll
|
||||
full_fs = map (dir </>) fs
|
||||
(dirs, files) <- partitionM doesDirectoryExist full_fs
|
||||
|
||||
subdirs <- concatMapM getFiles
|
||||
[ d | d <- dirs, not $ HashSet.member d ignored_dirs ]
|
||||
|
||||
return $ files ++ subdirs
|
||||
|
||||
-- Attempts to read a file in Olson format and returns its
|
||||
-- canonical name (file path relative to the base) and the data
|
||||
parseOlsonFile :: FilePath
|
||||
-> IO (Either E.ErrorCall (Text, TimeZoneSeries))
|
||||
parseOlsonFile f = E.try $ do
|
||||
r <- getTimeZoneSeriesFromOlsonFile f
|
||||
return (Text.pack $ makeRelative base f, r)
|
||||
|
||||
notDotFile s = not $ elem s [".", ".."]
|
83
Duckling/Debug.hs
Normal file
83
Duckling/Debug.hs
Normal file
@ -0,0 +1,83 @@
|
||||
-- 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 NamedFieldPuns #-}
|
||||
{-# LANGUAGE NoRebindableSyntax #-}
|
||||
|
||||
module Duckling.Debug
|
||||
( allParses
|
||||
, debug
|
||||
, fullParses
|
||||
, ptree
|
||||
) where
|
||||
|
||||
import qualified Data.HashSet as HashSet
|
||||
import Data.Maybe
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as Text
|
||||
import qualified Data.Text.IO as Text
|
||||
import Prelude
|
||||
|
||||
import Duckling.Api
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Engine
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Rules
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.Types
|
||||
|
||||
-- -----------------------------------------------------------------
|
||||
-- API
|
||||
|
||||
debug :: Lang -> Text -> [Some Dimension] -> IO [Entity]
|
||||
debug l = debugContext testContext {lang = l}
|
||||
|
||||
allParses :: Lang -> Text -> [Some Dimension] -> IO [Entity]
|
||||
allParses l sentence targets = debugTokens sentence $ parses l sentence targets
|
||||
|
||||
fullParses :: Lang -> Text -> [Some Dimension] -> IO [Entity]
|
||||
fullParses l sentence targets = debugTokens sentence .
|
||||
filter (\(Resolved {range = Range start end}) -> start == 0 && end == n) $
|
||||
parses l sentence targets
|
||||
where
|
||||
n = Text.length sentence
|
||||
|
||||
ptree :: Text -> ResolvedToken -> IO ()
|
||||
ptree sentence Resolved {node} = pnode sentence 0 node
|
||||
|
||||
-- -----------------------------------------------------------------
|
||||
-- Internals
|
||||
|
||||
parses :: Lang -> Text -> [Some Dimension] -> [ResolvedToken]
|
||||
parses l sentence targets = flip filter tokens $
|
||||
\(Resolved {node = Node{token = (Token d _)}}) ->
|
||||
case targets of
|
||||
[] -> True
|
||||
_ -> elem (Some d) targets
|
||||
where
|
||||
tokens = parseAndResolve rules sentence testContext {lang = l}
|
||||
rules = rulesFor l $ HashSet.fromList targets
|
||||
|
||||
debugContext :: Context -> Text -> [Some Dimension] -> IO [Entity]
|
||||
debugContext context sentence targets =
|
||||
debugTokens sentence . analyze sentence context $ HashSet.fromList targets
|
||||
|
||||
debugTokens :: Text -> [ResolvedToken] -> IO [Entity]
|
||||
debugTokens sentence tokens = do
|
||||
mapM_ (ptree sentence) tokens
|
||||
return $ map (formatToken sentence) tokens
|
||||
|
||||
pnode :: Text -> Int -> Node -> IO ()
|
||||
pnode sentence depth Node {children, rule, nodeRange = Range start end} = do
|
||||
Text.putStrLn out
|
||||
mapM_ (pnode sentence (depth + 1)) children
|
||||
where
|
||||
out = Text.concat [ Text.replicate depth "-- ", name, " (", body, ")" ]
|
||||
name = fromMaybe "regex" rule
|
||||
body = Text.drop start $ Text.take end sentence
|
99
Duckling/Dimensions.hs
Normal file
99
Duckling/Dimensions.hs
Normal file
@ -0,0 +1,99 @@
|
||||
-- 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 NoRebindableSyntax #-}
|
||||
|
||||
module Duckling.Dimensions
|
||||
( allDimensions
|
||||
, explicitDimensions
|
||||
) where
|
||||
import Data.HashSet (HashSet)
|
||||
import qualified Data.HashSet as HashSet
|
||||
import Prelude
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import qualified Duckling.Dimensions.Common as CommonDimensions
|
||||
import qualified Duckling.Dimensions.AR as ARDimensions
|
||||
import qualified Duckling.Dimensions.DA as DADimensions
|
||||
import qualified Duckling.Dimensions.DE as DEDimensions
|
||||
import qualified Duckling.Dimensions.EN as ENDimensions
|
||||
import qualified Duckling.Dimensions.ES as ESDimensions
|
||||
import qualified Duckling.Dimensions.ET as ETDimensions
|
||||
import qualified Duckling.Dimensions.FR as FRDimensions
|
||||
import qualified Duckling.Dimensions.GA as GADimensions
|
||||
import qualified Duckling.Dimensions.ID as IDDimensions
|
||||
import qualified Duckling.Dimensions.IT as ITDimensions
|
||||
import qualified Duckling.Dimensions.JA as JADimensions
|
||||
import qualified Duckling.Dimensions.KO as KODimensions
|
||||
import qualified Duckling.Dimensions.MY as MYDimensions
|
||||
import qualified Duckling.Dimensions.NB as NBDimensions
|
||||
import qualified Duckling.Dimensions.NL as NLDimensions
|
||||
import qualified Duckling.Dimensions.PL as PLDimensions
|
||||
import qualified Duckling.Dimensions.PT as PTDimensions
|
||||
import qualified Duckling.Dimensions.RO as RODimensions
|
||||
import qualified Duckling.Dimensions.RU as RUDimensions
|
||||
import qualified Duckling.Dimensions.SV as SVDimensions
|
||||
import qualified Duckling.Dimensions.TR as TRDimensions
|
||||
import qualified Duckling.Dimensions.UK as UKDimensions
|
||||
import qualified Duckling.Dimensions.VI as VIDimensions
|
||||
import qualified Duckling.Dimensions.ZH as ZHDimensions
|
||||
import Duckling.Lang
|
||||
|
||||
allDimensions :: Lang -> [Some Dimension]
|
||||
allDimensions lang = CommonDimensions.allDimensions ++ langDimensions lang
|
||||
|
||||
-- | Augments `targets` with all dependent dimensions.
|
||||
explicitDimensions :: HashSet (Some Dimension) -> HashSet (Some Dimension)
|
||||
explicitDimensions targets = HashSet.union targets deps
|
||||
where
|
||||
deps = HashSet.unions . map dependents $ HashSet.toList targets
|
||||
|
||||
-- | Ordinal depends on DNumber for JA, KO, and ZH.
|
||||
dependents :: Some Dimension -> HashSet (Some Dimension)
|
||||
dependents (Some Distance) = HashSet.singleton (Some DNumber)
|
||||
dependents (Some Duration) = HashSet.fromList [Some DNumber, Some TimeGrain]
|
||||
dependents (Some DNumber) = HashSet.empty
|
||||
dependents (Some Email) = HashSet.empty
|
||||
dependents (Some Finance) = HashSet.singleton (Some DNumber)
|
||||
dependents (Some Ordinal) = HashSet.singleton (Some DNumber)
|
||||
dependents (Some PhoneNumber) = HashSet.empty
|
||||
dependents (Some Quantity) = HashSet.singleton (Some DNumber)
|
||||
dependents (Some RegexMatch) = HashSet.empty
|
||||
dependents (Some Temperature) = HashSet.singleton (Some DNumber)
|
||||
dependents (Some Time) =
|
||||
HashSet.fromList [Some DNumber, Some Duration, Some Ordinal, Some TimeGrain]
|
||||
dependents (Some TimeGrain) = HashSet.empty
|
||||
dependents (Some Url) = HashSet.empty
|
||||
dependents (Some Volume) = HashSet.singleton (Some DNumber)
|
||||
|
||||
langDimensions :: Lang -> [Some Dimension]
|
||||
langDimensions AR = ARDimensions.allDimensions
|
||||
langDimensions DA = DADimensions.allDimensions
|
||||
langDimensions DE = DEDimensions.allDimensions
|
||||
langDimensions EN = ENDimensions.allDimensions
|
||||
langDimensions ES = ESDimensions.allDimensions
|
||||
langDimensions ET = ETDimensions.allDimensions
|
||||
langDimensions FR = FRDimensions.allDimensions
|
||||
langDimensions GA = GADimensions.allDimensions
|
||||
langDimensions ID = IDDimensions.allDimensions
|
||||
langDimensions IT = ITDimensions.allDimensions
|
||||
langDimensions JA = JADimensions.allDimensions
|
||||
langDimensions KO = KODimensions.allDimensions
|
||||
langDimensions MY = MYDimensions.allDimensions
|
||||
langDimensions NB = NBDimensions.allDimensions
|
||||
langDimensions NL = NLDimensions.allDimensions
|
||||
langDimensions PL = PLDimensions.allDimensions
|
||||
langDimensions PT = PTDimensions.allDimensions
|
||||
langDimensions RO = RODimensions.allDimensions
|
||||
langDimensions RU = RUDimensions.allDimensions
|
||||
langDimensions SV = SVDimensions.allDimensions
|
||||
langDimensions TR = TRDimensions.allDimensions
|
||||
langDimensions UK = UKDimensions.allDimensions
|
||||
langDimensions VI = VIDimensions.allDimensions
|
||||
langDimensions ZH = ZHDimensions.allDimensions
|
19
Duckling/Dimensions/AR.hs
Normal file
19
Duckling/Dimensions/AR.hs
Normal file
@ -0,0 +1,19 @@
|
||||
-- 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.Dimensions.AR
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some DNumber
|
||||
, Some Ordinal
|
||||
]
|
21
Duckling/Dimensions/Common.hs
Normal file
21
Duckling/Dimensions/Common.hs
Normal file
@ -0,0 +1,21 @@
|
||||
-- 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.Dimensions.Common
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Email
|
||||
, Some Finance
|
||||
, Some PhoneNumber
|
||||
, Some Url
|
||||
]
|
21
Duckling/Dimensions/DA.hs
Normal file
21
Duckling/Dimensions/DA.hs
Normal file
@ -0,0 +1,21 @@
|
||||
-- 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.Dimensions.DA
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Time
|
||||
]
|
21
Duckling/Dimensions/DE.hs
Normal file
21
Duckling/Dimensions/DE.hs
Normal file
@ -0,0 +1,21 @@
|
||||
-- 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.Dimensions.DE
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Time
|
||||
]
|
25
Duckling/Dimensions/EN.hs
Normal file
25
Duckling/Dimensions/EN.hs
Normal file
@ -0,0 +1,25 @@
|
||||
-- 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.Dimensions.EN
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Distance
|
||||
, Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Quantity
|
||||
, Some Temperature
|
||||
, Some Time
|
||||
, Some Volume
|
||||
]
|
24
Duckling/Dimensions/ES.hs
Normal file
24
Duckling/Dimensions/ES.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.Dimensions.ES
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Distance
|
||||
, Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Temperature
|
||||
, Some Time
|
||||
, Some Volume
|
||||
]
|
19
Duckling/Dimensions/ET.hs
Normal file
19
Duckling/Dimensions/ET.hs
Normal file
@ -0,0 +1,19 @@
|
||||
-- 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.Dimensions.ET
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some DNumber
|
||||
, Some Ordinal
|
||||
]
|
25
Duckling/Dimensions/FR.hs
Normal file
25
Duckling/Dimensions/FR.hs
Normal file
@ -0,0 +1,25 @@
|
||||
-- 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.Dimensions.FR
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Distance
|
||||
, Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Quantity
|
||||
, Some Temperature
|
||||
, Some Time
|
||||
, Some Volume
|
||||
]
|
24
Duckling/Dimensions/GA.hs
Normal file
24
Duckling/Dimensions/GA.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.Dimensions.GA
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Distance
|
||||
, Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Temperature
|
||||
, Some Time
|
||||
, Some Volume
|
||||
]
|
19
Duckling/Dimensions/ID.hs
Normal file
19
Duckling/Dimensions/ID.hs
Normal file
@ -0,0 +1,19 @@
|
||||
-- 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.Dimensions.ID
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some DNumber
|
||||
, Some Ordinal
|
||||
]
|
21
Duckling/Dimensions/IT.hs
Normal file
21
Duckling/Dimensions/IT.hs
Normal file
@ -0,0 +1,21 @@
|
||||
-- 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.Dimensions.IT
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Time
|
||||
]
|
22
Duckling/Dimensions/JA.hs
Normal file
22
Duckling/Dimensions/JA.hs
Normal 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.Dimensions.JA
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Temperature
|
||||
, Some Time
|
||||
]
|
25
Duckling/Dimensions/KO.hs
Normal file
25
Duckling/Dimensions/KO.hs
Normal file
@ -0,0 +1,25 @@
|
||||
-- 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.Dimensions.KO
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Distance
|
||||
, Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Quantity
|
||||
, Some Temperature
|
||||
, Some Time
|
||||
, Some Volume
|
||||
]
|
18
Duckling/Dimensions/MY.hs
Normal file
18
Duckling/Dimensions/MY.hs
Normal file
@ -0,0 +1,18 @@
|
||||
-- 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.Dimensions.MY
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some DNumber
|
||||
]
|
21
Duckling/Dimensions/NB.hs
Normal file
21
Duckling/Dimensions/NB.hs
Normal file
@ -0,0 +1,21 @@
|
||||
-- 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.Dimensions.NB
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Time
|
||||
]
|
21
Duckling/Dimensions/NL.hs
Normal file
21
Duckling/Dimensions/NL.hs
Normal file
@ -0,0 +1,21 @@
|
||||
-- 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.Dimensions.NL
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Distance
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Volume
|
||||
]
|
21
Duckling/Dimensions/PL.hs
Normal file
21
Duckling/Dimensions/PL.hs
Normal file
@ -0,0 +1,21 @@
|
||||
-- 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.Dimensions.PL
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Time
|
||||
]
|
25
Duckling/Dimensions/PT.hs
Normal file
25
Duckling/Dimensions/PT.hs
Normal file
@ -0,0 +1,25 @@
|
||||
-- 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.Dimensions.PT
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Distance
|
||||
, Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Quantity
|
||||
, Some Temperature
|
||||
, Some Time
|
||||
, Some Volume
|
||||
]
|
25
Duckling/Dimensions/RO.hs
Normal file
25
Duckling/Dimensions/RO.hs
Normal file
@ -0,0 +1,25 @@
|
||||
-- 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.Dimensions.RO
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Distance
|
||||
, Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Quantity
|
||||
, Some Temperature
|
||||
, Some Time
|
||||
, Some Volume
|
||||
]
|
19
Duckling/Dimensions/RU.hs
Normal file
19
Duckling/Dimensions/RU.hs
Normal file
@ -0,0 +1,19 @@
|
||||
-- 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.Dimensions.RU
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some DNumber
|
||||
, Some Ordinal
|
||||
]
|
21
Duckling/Dimensions/SV.hs
Normal file
21
Duckling/Dimensions/SV.hs
Normal file
@ -0,0 +1,21 @@
|
||||
-- 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.Dimensions.SV
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Time
|
||||
]
|
19
Duckling/Dimensions/TR.hs
Normal file
19
Duckling/Dimensions/TR.hs
Normal file
@ -0,0 +1,19 @@
|
||||
-- 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.Dimensions.TR
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some DNumber
|
||||
, Some Ordinal
|
||||
]
|
44
Duckling/Dimensions/Tests.hs
Normal file
44
Duckling/Dimensions/Tests.hs
Normal file
@ -0,0 +1,44 @@
|
||||
-- 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.Dimensions.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
import Test.Tasty
|
||||
|
||||
import qualified Duckling.Distance.Tests as Distance
|
||||
import qualified Duckling.Duration.Tests as Duration
|
||||
import qualified Duckling.Email.Tests as Email
|
||||
import qualified Duckling.Finance.Tests as Finance
|
||||
import qualified Duckling.Number.Tests as Number
|
||||
import qualified Duckling.Ordinal.Tests as Ordinal
|
||||
import qualified Duckling.PhoneNumber.Tests as PhoneNumber
|
||||
import qualified Duckling.Quantity.Tests as Quantity
|
||||
import qualified Duckling.Temperature.Tests as Temperature
|
||||
import qualified Duckling.Time.Tests as Time
|
||||
import qualified Duckling.Volume.Tests as Volume
|
||||
import qualified Duckling.Url.Tests as Url
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "Dimensions Tests"
|
||||
[ Distance.tests
|
||||
, Duration.tests
|
||||
, Email.tests
|
||||
, Finance.tests
|
||||
, Number.tests
|
||||
, Ordinal.tests
|
||||
, PhoneNumber.tests
|
||||
, Quantity.tests
|
||||
, Temperature.tests
|
||||
, Time.tests
|
||||
, Volume.tests
|
||||
, Url.tests
|
||||
]
|
168
Duckling/Dimensions/Types.hs
Normal file
168
Duckling/Dimensions/Types.hs
Normal file
@ -0,0 +1,168 @@
|
||||
-- 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 DeriveAnyClass #-}
|
||||
{-# LANGUAGE ExistentialQuantification #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE GADTs #-}
|
||||
{-# LANGUAGE NoRebindableSyntax #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE StandaloneDeriving #-}
|
||||
|
||||
module Duckling.Dimensions.Types
|
||||
( Some(..)
|
||||
, Dimension(..)
|
||||
, dimEq
|
||||
) where
|
||||
|
||||
import Data.Hashable
|
||||
import Data.Maybe
|
||||
-- Intentionally limit use of Typeable to avoid casting or typeOf usage
|
||||
import Data.Typeable ((:~:)(..))
|
||||
import TextShow (TextShow(..))
|
||||
import qualified TextShow as TS
|
||||
import Prelude
|
||||
|
||||
import Duckling.Distance.Types (DistanceData)
|
||||
import Duckling.Duration.Types (DurationData)
|
||||
import Duckling.Email.Types (EmailData)
|
||||
import Duckling.Finance.Types (FinanceData)
|
||||
import Duckling.Number.Types (NumberData)
|
||||
import Duckling.Ordinal.Types (OrdinalData)
|
||||
import Duckling.PhoneNumber.Types (PhoneNumberData)
|
||||
import Duckling.Quantity.Types (QuantityData)
|
||||
import Duckling.Regex.Types (GroupMatch)
|
||||
import Duckling.Temperature.Types (TemperatureData)
|
||||
import Duckling.Time.Types (TimeData)
|
||||
import Duckling.TimeGrain.Types (Grain)
|
||||
import Duckling.Url.Types (UrlData)
|
||||
import Duckling.Volume.Types (VolumeData)
|
||||
|
||||
-- -----------------------------------------------------------------
|
||||
-- Wrapper to house the existential
|
||||
|
||||
-- TODO: get rid of this t14593551
|
||||
data Some t = forall a . Some (t a)
|
||||
|
||||
-- -----------------------------------------------------------------
|
||||
-- Dimension
|
||||
|
||||
-- | GADT for differentiating between dimensions
|
||||
-- Each dimension should have its own constructor and provide the data structure
|
||||
-- for its parsed data
|
||||
data Dimension a where
|
||||
RegexMatch :: Dimension GroupMatch
|
||||
Distance :: Dimension DistanceData
|
||||
Duration :: Dimension DurationData
|
||||
Email :: Dimension EmailData
|
||||
Finance :: Dimension FinanceData
|
||||
DNumber :: Dimension NumberData
|
||||
Ordinal :: Dimension OrdinalData
|
||||
PhoneNumber :: Dimension PhoneNumberData
|
||||
Quantity :: Dimension QuantityData
|
||||
Temperature :: Dimension TemperatureData
|
||||
Time :: Dimension TimeData
|
||||
TimeGrain :: Dimension Grain
|
||||
Url :: Dimension UrlData
|
||||
Volume :: Dimension VolumeData
|
||||
|
||||
-- Show
|
||||
deriving instance Show (Some Dimension)
|
||||
instance Show (Dimension a) where
|
||||
show RegexMatch = "regex"
|
||||
show Distance = "distance"
|
||||
show Duration = "duration"
|
||||
show Email = "email"
|
||||
show Finance = "amount-of-money"
|
||||
show DNumber = "number"
|
||||
show Ordinal = "ordinal"
|
||||
show PhoneNumber = "phone-number"
|
||||
show Quantity = "quantity"
|
||||
show Temperature = "temperature"
|
||||
show Time = "time"
|
||||
show TimeGrain = "time-grain"
|
||||
show Url = "url"
|
||||
show Volume = "volume"
|
||||
|
||||
-- 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
|
||||
|
||||
-- Hashable
|
||||
instance Hashable (Some Dimension) where
|
||||
hashWithSalt s (Some a) = hashWithSalt s a
|
||||
instance Hashable (Dimension a) where
|
||||
hashWithSalt s RegexMatch = hashWithSalt s (0::Int)
|
||||
hashWithSalt s Distance = hashWithSalt s (1::Int)
|
||||
hashWithSalt s Duration = hashWithSalt s (2::Int)
|
||||
hashWithSalt s Email = hashWithSalt s (3::Int)
|
||||
hashWithSalt s Finance = hashWithSalt s (4::Int)
|
||||
hashWithSalt s DNumber = hashWithSalt s (5::Int)
|
||||
hashWithSalt s Ordinal = hashWithSalt s (6::Int)
|
||||
hashWithSalt s PhoneNumber = hashWithSalt s (7::Int)
|
||||
hashWithSalt s Quantity = hashWithSalt s (8::Int)
|
||||
hashWithSalt s Temperature = hashWithSalt s (9::Int)
|
||||
hashWithSalt s Time = hashWithSalt s (10::Int)
|
||||
hashWithSalt s TimeGrain = hashWithSalt s (11::Int)
|
||||
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 DNumber, "")]
|
||||
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 DNumber DNumber = Just Refl
|
||||
dimEq DNumber _ = 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
|
19
Duckling/Dimensions/UK.hs
Normal file
19
Duckling/Dimensions/UK.hs
Normal file
@ -0,0 +1,19 @@
|
||||
-- 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.Dimensions.UK
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some DNumber
|
||||
, Some Ordinal
|
||||
]
|
18
Duckling/Dimensions/VI.hs
Normal file
18
Duckling/Dimensions/VI.hs
Normal file
@ -0,0 +1,18 @@
|
||||
-- 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.Dimensions.VI
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some DNumber
|
||||
]
|
22
Duckling/Dimensions/ZH.hs
Normal file
22
Duckling/Dimensions/ZH.hs
Normal 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.Dimensions.ZH
|
||||
( allDimensions
|
||||
) where
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
|
||||
allDimensions :: [Some Dimension]
|
||||
allDimensions =
|
||||
[ Some Duration
|
||||
, Some DNumber
|
||||
, Some Ordinal
|
||||
, Some Temperature
|
||||
, Some Time
|
||||
]
|
43
Duckling/Distance/EN/Corpus.hs
Normal file
43
Duckling/Distance/EN/Corpus.hs
Normal file
@ -0,0 +1,43 @@
|
||||
-- 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.EN.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Distance.Types
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DistanceValue Kilometre 3)
|
||||
[ "3 kilometers"
|
||||
, "3 km"
|
||||
, "3km"
|
||||
, "3k"
|
||||
, "3.0 km"
|
||||
]
|
||||
, examples (DistanceValue Mile 8)
|
||||
[ "8 miles"
|
||||
, "eight mile"
|
||||
]
|
||||
, examples (DistanceValue M 9)
|
||||
[ "9m"
|
||||
]
|
||||
, examples (DistanceValue Centimetre 2)
|
||||
[ "2cm"
|
||||
, "2 centimeters"
|
||||
]
|
||||
]
|
86
Duckling/Distance/EN/Rules.hs
Normal file
86
Duckling/Distance/EN/Rules.hs
Normal file
@ -0,0 +1,86 @@
|
||||
-- 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.EN.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 qualified Duckling.Distance.Types as TDistance
|
||||
import Duckling.Types
|
||||
|
||||
ruleDistanceFeetInch :: Rule
|
||||
ruleDistanceFeetInch = Rule
|
||||
{ name = "<distance|feet> <distance|inch>"
|
||||
, pattern =
|
||||
[ unitDistance TDistance.Foot
|
||||
, unitDistance TDistance.Inch
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance DistanceData {TDistance.value = feet}:
|
||||
Token Distance DistanceData {TDistance.value = inches}:
|
||||
_) -> Just . Token Distance . withUnit TDistance.Inch . distance $
|
||||
feet * 12 + inches
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDistanceFeetAndInch :: Rule
|
||||
ruleDistanceFeetAndInch = Rule
|
||||
{ name = "<distance|feet> and <distance|inch>"
|
||||
, pattern =
|
||||
[ unitDistance TDistance.Foot
|
||||
, regex "and"
|
||||
, unitDistance TDistance.Inch
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance DistanceData {TDistance.value = feet}:
|
||||
_:
|
||||
Token Distance DistanceData {TDistance.value = inches}:
|
||||
_) -> Just . Token Distance . withUnit TDistance.Inch . distance $
|
||||
feet * 12 + inches
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
distances :: [(Text, String, TDistance.Unit)]
|
||||
distances = [ ("<latent dist> km", "k(ilo)?m?(eter)?s?", TDistance.Kilometre)
|
||||
, ("<latent dist> feet", "('|f(oo|ee)?ts?)", TDistance.Foot)
|
||||
, ("<latent dist> inch", "(''|inch(es)?)", TDistance.Inch)
|
||||
, ("<latent dist> yard", "y(ar)?ds?", TDistance.Yard)
|
||||
, ("<dist> meters", "meters?", TDistance.Metre)
|
||||
, ("<dist> centimeters", "cm|centimeters?", TDistance.Centimetre)
|
||||
, ("<dist> miles", "miles?", TDistance.Mile)
|
||||
, ("<dist> m (ambiguous miles or meters)", "m", TDistance.M)
|
||||
]
|
||||
|
||||
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 =
|
||||
[ ruleDistanceFeetInch
|
||||
, ruleDistanceFeetAndInch
|
||||
]
|
||||
++ ruleDistances
|
23
Duckling/Distance/EN/Tests.hs
Normal file
23
Duckling/Distance/EN/Tests.hs
Normal 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.Distance.EN.Tests
|
||||
( tests ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Distance.EN.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "EN Tests"
|
||||
[ makeCorpusTest [Some Distance] corpus
|
||||
]
|
48
Duckling/Distance/ES/Corpus.hs
Normal file
48
Duckling/Distance/ES/Corpus.hs
Normal file
@ -0,0 +1,48 @@
|
||||
-- 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.ES.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Distance.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = ES}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DistanceValue Kilometre 3)
|
||||
[ "3 kilómetros"
|
||||
, "3 kilometros"
|
||||
, "3 km"
|
||||
, "3km"
|
||||
, "3k"
|
||||
]
|
||||
, examples (DistanceValue Kilometre 3.0)
|
||||
[ "3,0 km"
|
||||
]
|
||||
, examples (DistanceValue Mile 8)
|
||||
[ "8 miles"
|
||||
]
|
||||
, examples (DistanceValue Metre 9)
|
||||
[ "9m"
|
||||
, "9 metros"
|
||||
]
|
||||
, examples (DistanceValue Centimetre 2)
|
||||
[ "2cm"
|
||||
, "2 centímetros"
|
||||
]
|
||||
]
|
81
Duckling/Distance/ES/Rules.hs
Normal file
81
Duckling/Distance/ES/Rules.hs
Normal 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.ES.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(il(\x00f3|o))?m?(etro)?s?"
|
||||
]
|
||||
, 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(etros?)?"
|
||||
]
|
||||
, 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|cent(\x00ed|i)m(etros?))"
|
||||
]
|
||||
, 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 "miles?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Mile dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDistCentimeters
|
||||
, ruleDistMeters
|
||||
, ruleDistMiles
|
||||
, ruleLatentDistKm
|
||||
]
|
23
Duckling/Distance/ES/Tests.hs
Normal file
23
Duckling/Distance/ES/Tests.hs
Normal 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.Distance.ES.Tests
|
||||
( tests ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Testing.Asserts
|
||||
import Duckling.Distance.ES.Corpus
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "ES Tests"
|
||||
[ makeCorpusTest [Some Distance] corpus
|
||||
]
|
48
Duckling/Distance/FR/Corpus.hs
Normal file
48
Duckling/Distance/FR/Corpus.hs
Normal file
@ -0,0 +1,48 @@
|
||||
-- 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.FR.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Distance.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = FR}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DistanceValue Kilometre 3)
|
||||
[ "3 kilomètres"
|
||||
, "3 kilometres"
|
||||
, "3 km"
|
||||
, "3km"
|
||||
, "3k"
|
||||
]
|
||||
, examples (DistanceValue Kilometre 3.0)
|
||||
[ "3,0 km"
|
||||
]
|
||||
, examples (DistanceValue Mile 8)
|
||||
[ "8 miles"
|
||||
]
|
||||
, examples (DistanceValue Metre 9)
|
||||
[ "9 metres"
|
||||
, "9m"
|
||||
]
|
||||
, examples (DistanceValue Centimetre 2)
|
||||
[ "2cm"
|
||||
, "2 centimetres"
|
||||
]
|
||||
]
|
81
Duckling/Distance/FR/Rules.hs
Normal file
81
Duckling/Distance/FR/Rules.hs
Normal 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.FR.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?((e|\x00e9|\x00e8)tre)?s?"
|
||||
]
|
||||
, 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((e|\x00e9|\x00e8)tres?)?"
|
||||
]
|
||||
, 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|centim(e|\x00e9|\x00e8)tres?"
|
||||
]
|
||||
, 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 "miles?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Mile dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDistCentimeters
|
||||
, ruleDistMeters
|
||||
, ruleDistMiles
|
||||
, ruleLatentDistKm
|
||||
]
|
21
Duckling/Distance/FR/Tests.hs
Normal file
21
Duckling/Distance/FR/Tests.hs
Normal file
@ -0,0 +1,21 @@
|
||||
-- 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.FR.Tests
|
||||
( tests ) where
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Testing.Asserts
|
||||
import Duckling.Distance.FR.Corpus
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "FR Tests"
|
||||
[ makeCorpusTest [Some Distance] corpus
|
||||
]
|
47
Duckling/Distance/GA/Corpus.hs
Normal file
47
Duckling/Distance/GA/Corpus.hs
Normal file
@ -0,0 +1,47 @@
|
||||
-- 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.GA.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Distance.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = GA}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DistanceValue Kilometre 3)
|
||||
[ "3 ciliméadair"
|
||||
, "3 km"
|
||||
, "3km"
|
||||
, "3k"
|
||||
]
|
||||
, examples (DistanceValue Kilometre 3.0)
|
||||
[ "3.0 km"
|
||||
]
|
||||
, examples (DistanceValue Mile 8)
|
||||
[ "8 mhíle"
|
||||
, "8 míle"
|
||||
]
|
||||
, examples (DistanceValue M 9)
|
||||
[ "9m"
|
||||
]
|
||||
, examples (DistanceValue Centimetre 2)
|
||||
[ "2cm"
|
||||
, "2 cheintiméadar"
|
||||
]
|
||||
]
|
123
Duckling/Distance/GA/Rules.hs
Normal file
123
Duckling/Distance/GA/Rules.hs
Normal file
@ -0,0 +1,123 @@
|
||||
-- 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.GA.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
|
||||
|
||||
ruleDistMeters :: Rule
|
||||
ruleDistMeters = Rule
|
||||
{ name = "<dist> meters"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "mh?(e|\x00e9)adai?r"
|
||||
]
|
||||
, 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 "(c\\.?m\\.?|g?ch?eintimh?(e|\x00e9)adai?r)"
|
||||
]
|
||||
, 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 "mh?(\x00ed|i)lt?e"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Mile dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistKm :: Rule
|
||||
ruleLatentDistKm = Rule
|
||||
{ name = "<latent dist> km"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "(k\\.?(m\\.?)?|g?ch?ilim(e|\x00e9)adai?r)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Kilometre dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistTroigh :: Rule
|
||||
ruleLatentDistTroigh = Rule
|
||||
{ name = "<latent dist> troigh"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "('|d?th?roi[tg]he?|tr\\.?)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Foot dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistOrlach :: Rule
|
||||
ruleLatentDistOrlach = Rule
|
||||
{ name = "<latent dist> orlach"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "(''|([nth]-?)?orl(ach|aigh|a(\x00ed|i)|\\.))"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Inch dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDistMAmbiguousMilesOrMeters :: Rule
|
||||
ruleDistMAmbiguousMilesOrMeters = Rule
|
||||
{ name = "<dist> m (ambiguous miles or meters)"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "m"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.M dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDistCentimeters
|
||||
, ruleDistMAmbiguousMilesOrMeters
|
||||
, ruleDistMeters
|
||||
, ruleDistMiles
|
||||
, ruleLatentDistKm
|
||||
, ruleLatentDistOrlach
|
||||
, ruleLatentDistTroigh
|
||||
]
|
23
Duckling/Distance/GA/Tests.hs
Normal file
23
Duckling/Distance/GA/Tests.hs
Normal 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.Distance.GA.Tests
|
||||
( tests ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Distance.GA.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "GA Tests"
|
||||
[ makeCorpusTest [Some Distance] corpus
|
||||
]
|
41
Duckling/Distance/Helpers.hs
Normal file
41
Duckling/Distance/Helpers.hs
Normal file
@ -0,0 +1,41 @@
|
||||
-- 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.Helpers
|
||||
( distance
|
||||
, unitDistance
|
||||
, withUnit
|
||||
) where
|
||||
|
||||
|
||||
import Prelude
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Distance.Types (DistanceData(..))
|
||||
import qualified Duckling.Distance.Types as TDistance
|
||||
import Duckling.Types
|
||||
|
||||
-- -----------------------------------------------------------------
|
||||
-- Patterns
|
||||
|
||||
unitDistance :: TDistance.Unit -> PatternItem
|
||||
unitDistance value = Predicate $ \x -> case x of
|
||||
(Token Distance DistanceData {TDistance.unit = Just unit}) -> value == unit
|
||||
_ -> False
|
||||
|
||||
-- -----------------------------------------------------------------
|
||||
-- Production
|
||||
|
||||
distance :: Double -> DistanceData
|
||||
distance x = DistanceData {TDistance.value = x, TDistance.unit = Nothing}
|
||||
|
||||
withUnit :: TDistance.Unit -> DistanceData -> DistanceData
|
||||
withUnit value dd = dd {TDistance.unit = Just value}
|
56
Duckling/Distance/KO/Corpus.hs
Normal file
56
Duckling/Distance/KO/Corpus.hs
Normal file
@ -0,0 +1,56 @@
|
||||
-- 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.KO.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Distance.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = KO}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DistanceValue Kilometre 3)
|
||||
[ "3 킬로미터"
|
||||
, "3 킬로"
|
||||
, "3 키로"
|
||||
, "3 km"
|
||||
, "3km"
|
||||
]
|
||||
, examples (DistanceValue Kilometre 3.0)
|
||||
[ "3.0 km"
|
||||
]
|
||||
, examples (DistanceValue Mile 8)
|
||||
[ "8 miles"
|
||||
, "8 마일"
|
||||
, "8 마일즈"
|
||||
]
|
||||
, examples (DistanceValue Metre 9)
|
||||
[ "9m"
|
||||
, "9미터"
|
||||
, "9메터"
|
||||
, "구메터"
|
||||
]
|
||||
, examples (DistanceValue Centimetre 2)
|
||||
[ "2cm"
|
||||
, "2 센치"
|
||||
, "이센치"
|
||||
, "2 센티"
|
||||
, "2 센티미터"
|
||||
, "2 센치미터"
|
||||
]
|
||||
]
|
154
Duckling/Distance/KO/Rules.hs
Normal file
154
Duckling/Distance/KO/Rules.hs
Normal file
@ -0,0 +1,154 @@
|
||||
-- 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.KO.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.Number.Types (NumberData (..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Types
|
||||
|
||||
ruleLatentDistYard :: Rule
|
||||
ruleLatentDistYard = Rule
|
||||
{ name = "<latent dist> yard"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "y(ar)?ds?|\xc57c\xb4dc"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Yard dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDistCentimeters :: Rule
|
||||
ruleDistCentimeters = Rule
|
||||
{ name = "<dist> centimeters"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "cm|\xc13c(\xd2f0|\xce58)((\xbbf8|\xba54)\xd130)?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Centimetre dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistFeetAndLatentDistInch :: Rule
|
||||
ruleLatentDistFeetAndLatentDistInch = Rule
|
||||
{ name = "<latent dist> feet and <latent dist> inch "
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "('|f(oo|ee)?ts?)|\xd53c\xd2b8"
|
||||
, dimension Distance
|
||||
, regex "(''|inch(es)?)|\xc778\xce58"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Foot dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDistMeters :: Rule
|
||||
ruleDistMeters = Rule
|
||||
{ name = "<dist> meters"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "m|(\xbbf8|\xba54|\xb9e4)\xd130"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Metre dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistFeet :: Rule
|
||||
ruleLatentDistFeet = Rule
|
||||
{ name = "<latent dist> feet"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "('|f(oo|ee)?ts?)|\xd53c\xd2b8"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Foot dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistKm :: Rule
|
||||
ruleLatentDistKm = Rule
|
||||
{ name = "<latent dist> km"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "km|(\xd0ac|\xd0a4)\xb85c((\xbbf8|\xba54)\xd130)?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Kilometre dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleHalf :: Rule
|
||||
ruleHalf = Rule
|
||||
{ name = "half"
|
||||
, pattern =
|
||||
[ regex "\xbc18"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber NumberData {TNumber.value = v}:_) ->
|
||||
Just . Token Distance $ distance v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDistMiles :: Rule
|
||||
ruleDistMiles = Rule
|
||||
{ name = "<dist> miles"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "miles?|\xb9c8\xc77c(\xc988)?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Mile dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistInch :: Rule
|
||||
ruleLatentDistInch = Rule
|
||||
{ name = "<latent dist> inch"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "(''|inch(es)?)|\xc778\xce58"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Inch dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDistCentimeters
|
||||
, ruleDistMeters
|
||||
, ruleDistMiles
|
||||
, ruleHalf
|
||||
, ruleLatentDistFeet
|
||||
, ruleLatentDistFeetAndLatentDistInch
|
||||
, ruleLatentDistInch
|
||||
, ruleLatentDistKm
|
||||
, ruleLatentDistYard
|
||||
]
|
23
Duckling/Distance/KO/Tests.hs
Normal file
23
Duckling/Distance/KO/Tests.hs
Normal 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.Distance.KO.Tests
|
||||
( tests ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Testing.Asserts
|
||||
import Duckling.Distance.KO.Corpus
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "KO Tests"
|
||||
[ makeCorpusTest [Some Distance] corpus
|
||||
]
|
50
Duckling/Distance/NL/Corpus.hs
Normal file
50
Duckling/Distance/NL/Corpus.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 OverloadedStrings #-}
|
||||
|
||||
module Duckling.Distance.NL.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Distance.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = NL}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DistanceValue Kilometre 3)
|
||||
[ "3 kilometer"
|
||||
, "3 km"
|
||||
, "3km"
|
||||
, "3k"
|
||||
]
|
||||
, examples (DistanceValue Kilometre 3.0)
|
||||
[ "3,0 km"
|
||||
, "3,0km"
|
||||
]
|
||||
, examples (DistanceValue Mile 8)
|
||||
[ "8 mijl"
|
||||
]
|
||||
, examples (DistanceValue Metre 9)
|
||||
[ "9m"
|
||||
, "9 m"
|
||||
, "9 meter"
|
||||
]
|
||||
, examples (DistanceValue Centimetre 2)
|
||||
[ "2cm"
|
||||
, "2 cm"
|
||||
, "2 centimeter"
|
||||
]
|
||||
]
|
81
Duckling/Distance/NL/Rules.hs
Normal file
81
Duckling/Distance/NL/Rules.hs
Normal 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.NL.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?(eter)?s?"
|
||||
]
|
||||
, 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(eter)?"
|
||||
]
|
||||
, 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 "(c(enti)?m(eter)?s?)"
|
||||
]
|
||||
, 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 "mijl?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Mile dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDistCentimeters
|
||||
, ruleDistMeters
|
||||
, ruleDistMiles
|
||||
, ruleLatentDistKm
|
||||
]
|
23
Duckling/Distance/NL/Tests.hs
Normal file
23
Duckling/Distance/NL/Tests.hs
Normal 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.Distance.NL.Tests
|
||||
( tests ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Testing.Asserts
|
||||
import Duckling.Distance.NL.Corpus
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "NL Tests"
|
||||
[ makeCorpusTest [Some Distance] corpus
|
||||
]
|
48
Duckling/Distance/PT/Corpus.hs
Normal file
48
Duckling/Distance/PT/Corpus.hs
Normal file
@ -0,0 +1,48 @@
|
||||
-- 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.PT.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Distance.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = PT}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DistanceValue Kilometre 3)
|
||||
[ "3 kilómetros"
|
||||
, "3 kilometros"
|
||||
, "3 km"
|
||||
, "3km"
|
||||
, "3k"
|
||||
]
|
||||
, examples (DistanceValue Kilometre 3.0)
|
||||
[ "3,0 km"
|
||||
]
|
||||
, examples (DistanceValue Mile 8)
|
||||
[ "8 milhas"
|
||||
]
|
||||
, examples (DistanceValue Metre 9)
|
||||
[ "9m"
|
||||
, "9 metros"
|
||||
]
|
||||
, examples (DistanceValue Centimetre 2)
|
||||
[ "2cm"
|
||||
, "2 centímetros"
|
||||
]
|
||||
]
|
81
Duckling/Distance/PT/Rules.hs
Normal file
81
Duckling/Distance/PT/Rules.hs
Normal 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.PT.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(il(\x00f3|o))?m?(etro)?s?"
|
||||
]
|
||||
, 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(etros?)?"
|
||||
]
|
||||
, 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|cent(\x00ed|i)m(etros?))"
|
||||
]
|
||||
, 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 "milhas?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Mile dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDistCentimeters
|
||||
, ruleDistMeters
|
||||
, ruleDistMiles
|
||||
, ruleLatentDistKm
|
||||
]
|
23
Duckling/Distance/PT/Tests.hs
Normal file
23
Duckling/Distance/PT/Tests.hs
Normal 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.Distance.PT.Tests
|
||||
( tests ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Testing.Asserts
|
||||
import Duckling.Distance.PT.Corpus
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "PT Tests"
|
||||
[ makeCorpusTest [Some Distance] corpus
|
||||
]
|
47
Duckling/Distance/RO/Corpus.hs
Normal file
47
Duckling/Distance/RO/Corpus.hs
Normal file
@ -0,0 +1,47 @@
|
||||
-- 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.RO.Corpus
|
||||
( corpus ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Distance.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = RO}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DistanceValue Kilometre 3)
|
||||
[ "3 kilometri"
|
||||
, "3 km"
|
||||
, "3km"
|
||||
, "3,0 km"
|
||||
]
|
||||
, examples (DistanceValue Mile 8)
|
||||
[ "8 mile"
|
||||
]
|
||||
, examples (DistanceValue Metre 9)
|
||||
[ "9m"
|
||||
, "9 m"
|
||||
]
|
||||
, examples (DistanceValue Centimetre 2)
|
||||
[ "2cm"
|
||||
, "2 centimetri"
|
||||
]
|
||||
, examples (DistanceValue Foot 10)
|
||||
[ "zece picioare"
|
||||
]
|
||||
]
|
123
Duckling/Distance/RO/Rules.hs
Normal file
123
Duckling/Distance/RO/Rules.hs
Normal file
@ -0,0 +1,123 @@
|
||||
-- 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.RO.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 "(kilometr[iu]|km)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Kilometre dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistPicioare :: Rule
|
||||
ruleLatentDistPicioare = Rule
|
||||
{ name = "<latent dist> picioare"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "(picio(are|r))"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Foot dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistInch :: Rule
|
||||
ruleLatentDistInch = Rule
|
||||
{ name = "<latent dist> inch"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "(inch|inci|inchi)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Inch dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleLatentDistYarzi :: Rule
|
||||
ruleLatentDistYarzi = Rule
|
||||
{ name = "<latent dist> yarzi"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "y(ar)?(zi|d)?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Yard dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDistMeters :: Rule
|
||||
ruleDistMeters = Rule
|
||||
{ name = "<dist> meters"
|
||||
, pattern =
|
||||
[ dimension Distance
|
||||
, regex "(metr[ui]|m)"
|
||||
]
|
||||
, 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 "(centimetr[iu]|cm)"
|
||||
]
|
||||
, 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(e|a|\x0103)"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token Distance dd:_) ->
|
||||
Just . Token Distance $ withUnit TDistance.Mile dd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDistCentimeters
|
||||
, ruleDistMeters
|
||||
, ruleDistMiles
|
||||
, ruleLatentDistInch
|
||||
, ruleLatentDistKm
|
||||
, ruleLatentDistPicioare
|
||||
, ruleLatentDistYarzi
|
||||
]
|
23
Duckling/Distance/RO/Tests.hs
Normal file
23
Duckling/Distance/RO/Tests.hs
Normal 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.Distance.RO.Tests
|
||||
( tests ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Testing.Asserts
|
||||
import Duckling.Distance.RO.Corpus
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "RO Tests"
|
||||
[ makeCorpusTest [Some Distance] corpus
|
||||
]
|
41
Duckling/Distance/Rules.hs
Normal file
41
Duckling/Distance/Rules.hs
Normal file
@ -0,0 +1,41 @@
|
||||
-- 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.Rules
|
||||
( rules
|
||||
) where
|
||||
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Distance.Helpers
|
||||
import Duckling.Number.Types (NumberData (..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Types
|
||||
|
||||
ruleNumberAsDistance :: Rule
|
||||
ruleNumberAsDistance = Rule
|
||||
{ name = "number as distance"
|
||||
, pattern =
|
||||
[ dimension DNumber
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber NumberData {TNumber.value = v}:_) ->
|
||||
Just . Token Distance $ distance v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleNumberAsDistance
|
||||
]
|
34
Duckling/Distance/Tests.hs
Normal file
34
Duckling/Distance/Tests.hs
Normal file
@ -0,0 +1,34 @@
|
||||
-- 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.Tests (tests) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import qualified Duckling.Distance.EN.Tests as EN
|
||||
import qualified Duckling.Distance.ES.Tests as ES
|
||||
import qualified Duckling.Distance.FR.Tests as FR
|
||||
import qualified Duckling.Distance.GA.Tests as GA
|
||||
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
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "Distance Tests"
|
||||
[ EN.tests
|
||||
, ES.tests
|
||||
, FR.tests
|
||||
, GA.tests
|
||||
, KO.tests
|
||||
, NL.tests
|
||||
, PT.tests
|
||||
, RO.tests
|
||||
]
|
65
Duckling/Distance/Types.hs
Normal file
65
Duckling/Distance/Types.hs
Normal file
@ -0,0 +1,65 @@
|
||||
-- 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 DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE NoRebindableSyntax #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
|
||||
module Duckling.Distance.Types where
|
||||
|
||||
import Control.DeepSeq
|
||||
import Data.Aeson
|
||||
import Data.Hashable
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as Text
|
||||
import GHC.Generics
|
||||
import Prelude
|
||||
|
||||
import Duckling.Resolve (Resolve(..))
|
||||
|
||||
data Unit
|
||||
= Foot
|
||||
| Centimetre
|
||||
| Kilometre
|
||||
| Inch
|
||||
| M -- ambiguous between Mile and Metre
|
||||
| Metre
|
||||
| Mile
|
||||
| Yard
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, NFData)
|
||||
|
||||
instance ToJSON Unit where
|
||||
toJSON = String . Text.toLower . Text.pack . show
|
||||
|
||||
data DistanceData = DistanceData
|
||||
{ unit :: Maybe Unit
|
||||
, value :: Double
|
||||
}
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, NFData)
|
||||
|
||||
instance Resolve DistanceData where
|
||||
type ResolvedValue DistanceData = DistanceValue
|
||||
resolve _ DistanceData {unit = Nothing} = Nothing
|
||||
resolve _ DistanceData {unit = Just unit, value} =
|
||||
Just DistanceValue {vValue = value, vUnit = unit}
|
||||
|
||||
data DistanceValue = DistanceValue
|
||||
{ vUnit :: Unit
|
||||
, vValue :: Double
|
||||
}
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
instance ToJSON DistanceValue where
|
||||
toJSON (DistanceValue unit value) = object
|
||||
[ "type" .= ("value" :: Text)
|
||||
, "value" .= value
|
||||
, "unit" .= unit
|
||||
]
|
142
Duckling/Duration/DA/Rules.hs
Normal file
142
Duckling/Duration/DA/Rules.hs
Normal file
@ -0,0 +1,142 @@
|
||||
-- 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.Duration.DA.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import qualified Data.Text as Text
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Helpers (parseInt)
|
||||
import Duckling.Number.Types (NumberData (..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Regex.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleExactlyDuration :: Rule
|
||||
ruleExactlyDuration = Rule
|
||||
{ name = "exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "pr(\x00e6)cis"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
-- TODO(jodent) +precision exact
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntegerAndAnHalfHours :: Rule
|
||||
ruleIntegerAndAnHalfHours = Rule
|
||||
{ name = "<integer> and an half hours"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "og (en )?halv timer?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):_) ->
|
||||
Just . Token Duration . duration TG.Minute $ 30 + 60 * floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAUnitofduration :: Rule
|
||||
ruleAUnitofduration = Rule
|
||||
{ name = "a <unit-of-duration>"
|
||||
, pattern =
|
||||
[ regex "en|et?"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntegerMoreUnitofduration :: Rule
|
||||
ruleIntegerMoreUnitofduration = Rule
|
||||
{ name = "<integer> more <unit-of-duration>"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, dimension TimeGrain
|
||||
, regex "mere|mindre"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):
|
||||
Token TimeGrain grain:
|
||||
_) -> Just . Token Duration . duration grain $ floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleFortnight :: Rule
|
||||
ruleFortnight = Rule
|
||||
{ name = "fortnight"
|
||||
, pattern =
|
||||
[ regex "(a|one)? fortnight"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Day 14
|
||||
}
|
||||
|
||||
ruleAboutDuration :: Rule
|
||||
ruleAboutDuration = Rule
|
||||
{ name = "about <duration>"
|
||||
, pattern =
|
||||
[ regex "(omkring|cirka|ca.)"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
-- TODO(jodent) +precision approximate
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleNumbernumberHours :: Rule
|
||||
ruleNumbernumberHours = Rule
|
||||
{ name = "number.number hours"
|
||||
, pattern =
|
||||
[ regex "(\\d+)\\,(\\d+)"
|
||||
, regex "timer?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (h:d:_)):_) -> do
|
||||
hh <- parseInt h
|
||||
dec <- parseInt d
|
||||
let divisor = floor $ (fromIntegral (10 :: Integer) :: Float) **
|
||||
fromIntegral (Text.length d - 1)
|
||||
numerator = fromIntegral $ 6 * dec
|
||||
Just . Token Duration . duration TG.Minute $
|
||||
60 * hh + quot numerator divisor
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleHalfAnHour :: Rule
|
||||
ruleHalfAnHour = Rule
|
||||
{ name = "half an hour"
|
||||
, pattern =
|
||||
[ regex "(1/2|en halv) time"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleAUnitofduration
|
||||
, ruleAboutDuration
|
||||
, ruleExactlyDuration
|
||||
, ruleFortnight
|
||||
, ruleHalfAnHour
|
||||
, ruleIntegerAndAnHalfHours
|
||||
, ruleIntegerMoreUnitofduration
|
||||
, ruleNumbernumberHours
|
||||
]
|
140
Duckling/Duration/DE/Rules.hs
Normal file
140
Duckling/Duration/DE/Rules.hs
Normal file
@ -0,0 +1,140 @@
|
||||
-- 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.Duration.DE.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import qualified Data.Text as Text
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Helpers (parseInt)
|
||||
import Duckling.Number.Types (NumberData (..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Regex.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleHalfAnHour :: Rule
|
||||
ruleHalfAnHour = Rule
|
||||
{ name = "half an hour"
|
||||
, pattern =
|
||||
[ regex "(1/2\\s?|(einer )halbe?n? )stunde"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleFortnight :: Rule
|
||||
ruleFortnight = Rule
|
||||
{ name = "fortnight"
|
||||
, pattern =
|
||||
[ regex "(a|one)? fortnight"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Day 14
|
||||
}
|
||||
|
||||
ruleIntegerMoreUnitofduration :: Rule
|
||||
ruleIntegerMoreUnitofduration = Rule
|
||||
{ name = "<integer> more <unit-of-duration>"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "mehr|weniger"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):
|
||||
_:
|
||||
Token TimeGrain grain:
|
||||
_) -> Just . Token Duration . duration grain $ floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleNumbernumberHours :: Rule
|
||||
ruleNumbernumberHours = Rule
|
||||
{ name = "number.number hours"
|
||||
, pattern =
|
||||
[ regex "(\\d+)\\.(\\d+) stunden?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (h:d:_)):_) -> do
|
||||
hh <- parseInt h
|
||||
dec <- parseInt d
|
||||
let divisor = floor $ (fromIntegral (10 :: Integer) :: Float) **
|
||||
fromIntegral (Text.length d - 1)
|
||||
numerator = fromIntegral $ 6 * dec
|
||||
Just . Token Duration . duration TG.Minute $
|
||||
60 * hh + quot numerator divisor
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntegerAndAnHalfHours :: Rule
|
||||
ruleIntegerAndAnHalfHours = Rule
|
||||
{ name = "<integer> and an half hours"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "ein ?halb stunden?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):_) ->
|
||||
Just . Token Duration . duration TG.Minute $ 30 + 60 * floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAUnitofduration :: Rule
|
||||
ruleAUnitofduration = Rule
|
||||
{ name = "a <unit-of-duration>"
|
||||
, pattern =
|
||||
[ regex "eine?(r|n)?"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAboutDuration :: Rule
|
||||
ruleAboutDuration = Rule
|
||||
{ name = "about <duration>"
|
||||
, pattern =
|
||||
[ regex "ungef\x00e4hr|zirka"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleExactlyDuration :: Rule
|
||||
ruleExactlyDuration = Rule
|
||||
{ name = "exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "genau|exakt"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleAUnitofduration
|
||||
, ruleAboutDuration
|
||||
, ruleExactlyDuration
|
||||
, ruleFortnight
|
||||
, ruleHalfAnHour
|
||||
, ruleIntegerAndAnHalfHours
|
||||
, ruleIntegerMoreUnitofduration
|
||||
, ruleNumbernumberHours
|
||||
]
|
65
Duckling/Duration/EN/Corpus.hs
Normal file
65
Duckling/Duration/EN/Corpus.hs
Normal file
@ -0,0 +1,65 @@
|
||||
-- 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.Duration.EN.Corpus
|
||||
( corpus
|
||||
, negativeCorpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext, allExamples)
|
||||
|
||||
negativeCorpus :: NegativeCorpus
|
||||
negativeCorpus = (testContext, examples)
|
||||
where
|
||||
examples =
|
||||
[ "for months"
|
||||
, "in days"
|
||||
, "secretary"
|
||||
, "minutes"
|
||||
, "I second that"
|
||||
]
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "one sec"
|
||||
, "1 second"
|
||||
, "1\""
|
||||
]
|
||||
, examples (DurationData 2 Minute)
|
||||
[ "2 mins"
|
||||
, "two minutes"
|
||||
, "2'"
|
||||
]
|
||||
, examples (DurationData 30 Day)
|
||||
[ "30 days"
|
||||
]
|
||||
, examples (DurationData 7 Week)
|
||||
[ "seven weeks"
|
||||
]
|
||||
, examples (DurationData 1 Month)
|
||||
[ "1 month"
|
||||
, "a month"
|
||||
]
|
||||
, examples (DurationData 3 Quarter)
|
||||
[ "3 quarters"
|
||||
]
|
||||
, examples (DurationData 2 Year)
|
||||
[ "2 years"
|
||||
]
|
||||
]
|
154
Duckling/Duration/EN/Rules.hs
Normal file
154
Duckling/Duration/EN/Rules.hs
Normal file
@ -0,0 +1,154 @@
|
||||
-- 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.Duration.EN.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import qualified Data.Text as Text
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Helpers (parseInt)
|
||||
import Duckling.Number.Types (NumberData(..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Regex.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleDurationQuarterOfAnHour :: Rule
|
||||
ruleDurationQuarterOfAnHour = Rule
|
||||
{ name = "quarter of an hour"
|
||||
, pattern = [ regex "(1/4\\s?h(our)?|(a\\s)?quarter of an hour)" ]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 15
|
||||
}
|
||||
|
||||
ruleDurationHalfAnHour :: Rule
|
||||
ruleDurationHalfAnHour = Rule
|
||||
{ name = "half an hour"
|
||||
, pattern = [regex "(1/2\\s?h(our)?|half an? hour)"]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleDurationThreeQuartersOfAnHour :: Rule
|
||||
ruleDurationThreeQuartersOfAnHour = Rule
|
||||
{ name = "three-quarters of an hour"
|
||||
, pattern = [regex "(3/4\\s?h(our)?|three(\\s|-)quarters of an hour)"]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 45
|
||||
}
|
||||
|
||||
ruleDurationFortnight :: Rule
|
||||
ruleDurationFortnight = Rule
|
||||
{ name = "fortnight"
|
||||
, pattern = [regex "(a|one)? fortnight"]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Day 14
|
||||
}
|
||||
|
||||
ruleNumberQuotes :: Rule
|
||||
ruleNumberQuotes = Rule
|
||||
{ name = "<integer> + '\""
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "(['\"])"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):
|
||||
Token RegexMatch (GroupMatch (x:_)):
|
||||
_) -> case x of
|
||||
"'" -> Just . Token Duration . duration TG.Minute $ floor v
|
||||
"\"" -> Just . Token Duration . duration TG.Second $ floor v
|
||||
_ -> Nothing
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationNumberMore :: Rule
|
||||
ruleDurationNumberMore = Rule
|
||||
{ name = "<integer> more <unit-of-duration>"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "more|less"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber nd:_:Token TimeGrain grain:_) ->
|
||||
Just . Token Duration . duration grain . floor $ TNumber.value nd
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationDotNumberHours :: Rule
|
||||
ruleDurationDotNumberHours = Rule
|
||||
{ name = "number.number hours"
|
||||
, pattern = [regex "(\\d+)\\.(\\d+) *hours?"]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (h:d:_)):_) -> do
|
||||
hh <- parseInt h
|
||||
dec <- parseInt d
|
||||
let divisor = floor $ (fromIntegral (10 :: Integer) :: Float) **
|
||||
fromIntegral (Text.length d - 1)
|
||||
numerator = fromIntegral $ 6 * dec
|
||||
Just . Token Duration . duration TG.Minute $
|
||||
60 * hh + quot numerator divisor
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationAndHalfHour :: Rule
|
||||
ruleDurationAndHalfHour = Rule
|
||||
{ name = "<integer> and an half hour"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "and (an? )?half hours?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):_) ->
|
||||
Just . Token Duration . duration TG.Minute $ 30 + 60 * floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleDurationA :: Rule
|
||||
ruleDurationA = Rule
|
||||
{ name = "a <unit-of-duration>"
|
||||
, pattern =
|
||||
[ regex "an?"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
-- TODO(jodent) precision t13807342
|
||||
ruleDurationPrecision :: Rule
|
||||
ruleDurationPrecision = Rule
|
||||
{ name = "about|exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "(about|around|approximately|exactly)"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleDurationQuarterOfAnHour
|
||||
, ruleDurationHalfAnHour
|
||||
, ruleDurationThreeQuartersOfAnHour
|
||||
, ruleDurationFortnight
|
||||
, ruleDurationNumberMore
|
||||
, ruleDurationDotNumberHours
|
||||
, ruleDurationAndHalfHour
|
||||
, ruleDurationA
|
||||
, ruleDurationPrecision
|
||||
, ruleNumberQuotes
|
||||
]
|
25
Duckling/Duration/EN/Tests.hs
Normal file
25
Duckling/Duration/EN/Tests.hs
Normal file
@ -0,0 +1,25 @@
|
||||
-- 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.Duration.EN.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.EN.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "EN Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
, makeNegativeCorpusTest [Some Duration] negativeCorpus
|
||||
]
|
66
Duckling/Duration/FR/Corpus.hs
Normal file
66
Duckling/Duration/FR/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.Duration.FR.Corpus
|
||||
( corpus
|
||||
, negativeCorpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = FR}, allExamples)
|
||||
|
||||
negativeCorpus :: NegativeCorpus
|
||||
negativeCorpus = (testContext {lang = FR}, examples)
|
||||
where
|
||||
examples =
|
||||
[ "les jours"
|
||||
, "en secondaire"
|
||||
, "minutes"
|
||||
, "pendant des mois"
|
||||
]
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "une sec"
|
||||
, "1 seconde"
|
||||
, "1\""
|
||||
]
|
||||
, examples (DurationData 2 Minute)
|
||||
[ "2 mins"
|
||||
, "deux minutes"
|
||||
, "2'"
|
||||
]
|
||||
, examples (DurationData 30 Day)
|
||||
[ "30 jours"
|
||||
]
|
||||
, examples (DurationData 7 Week)
|
||||
[ "sept semaines"
|
||||
]
|
||||
, examples (DurationData 1 Month)
|
||||
[ "1 mois"
|
||||
, "un mois"
|
||||
]
|
||||
, examples (DurationData 3 Quarter)
|
||||
[ "3 trimestres"
|
||||
]
|
||||
, examples (DurationData 2 Year)
|
||||
[ "2 ans"
|
||||
]
|
||||
]
|
105
Duckling/Duration/FR/Rules.hs
Normal file
105
Duckling/Duration/FR/Rules.hs
Normal file
@ -0,0 +1,105 @@
|
||||
-- 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.Duration.FR.Rules
|
||||
( rules ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Types (NumberData(..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Regex.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleNumberQuotes :: Rule
|
||||
ruleNumberQuotes = Rule
|
||||
{ name = "<integer> + '\""
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "(['\"])"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):
|
||||
Token RegexMatch (GroupMatch (x:_)):
|
||||
_) -> case x of
|
||||
"'" -> Just . Token Duration . duration TG.Minute $ floor v
|
||||
"\"" -> Just . Token Duration . duration TG.Second $ floor v
|
||||
_ -> Nothing
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleUneUnitofduration :: Rule
|
||||
ruleUneUnitofduration = Rule
|
||||
{ name = "une <unit-of-duration>"
|
||||
, pattern =
|
||||
[ regex "une|la|le?"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:
|
||||
Token TimeGrain grain:
|
||||
_) -> Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleUnQuartDHeure :: Rule
|
||||
ruleUnQuartDHeure = Rule
|
||||
{ name = "un quart d'heure"
|
||||
, pattern =
|
||||
[ regex "(1/4\\s?h(eure)?|(un|1) quart d'heure)"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 15
|
||||
}
|
||||
|
||||
ruleUneDemiHeure :: Rule
|
||||
ruleUneDemiHeure = Rule
|
||||
{ name = "une demi heure"
|
||||
, pattern =
|
||||
[ regex "(1/2\\s?h(eure)?|(1|une) demi(e)?(\\s|-)heure)"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleTroisQuartsDHeure :: Rule
|
||||
ruleTroisQuartsDHeure = Rule
|
||||
{ name = "trois quarts d'heure"
|
||||
, pattern =
|
||||
[ regex "(3/4\\s?h(eure)?|(3|trois) quart(s)? d'heure)"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 45
|
||||
}
|
||||
|
||||
-- TODO(jodent) precision t13807342
|
||||
ruleDurationEnviron :: Rule
|
||||
ruleDurationEnviron = Rule
|
||||
{ name = "environ <duration>"
|
||||
, pattern =
|
||||
[ regex "environ"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
-- TODO(jodent) +precision approximate
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleUneUnitofduration
|
||||
, ruleUnQuartDHeure
|
||||
, ruleUneDemiHeure
|
||||
, ruleTroisQuartsDHeure
|
||||
, ruleDurationEnviron
|
||||
, ruleNumberQuotes
|
||||
]
|
25
Duckling/Duration/FR/Tests.hs
Normal file
25
Duckling/Duration/FR/Tests.hs
Normal file
@ -0,0 +1,25 @@
|
||||
-- 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.Duration.FR.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.FR.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "FR Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
, makeNegativeCorpusTest [Some Duration] negativeCorpus
|
||||
]
|
42
Duckling/Duration/GA/Corpus.hs
Normal file
42
Duckling/Duration/GA/Corpus.hs
Normal 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 OverloadedStrings #-}
|
||||
|
||||
module Duckling.Duration.GA.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = GA}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "aon soicind amhain"
|
||||
, "aon soicind"
|
||||
, "1 tshoicindi"
|
||||
, "1 tsoicind"
|
||||
]
|
||||
, examples (DurationData 30 Minute)
|
||||
[ "leathuair"
|
||||
, "30 noimead"
|
||||
]
|
||||
, examples (DurationData 14 Day)
|
||||
[ "coicís"
|
||||
]
|
||||
]
|
78
Duckling/Duration/GA/Rules.hs
Normal file
78
Duckling/Duration/GA/Rules.hs
Normal file
@ -0,0 +1,78 @@
|
||||
-- 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.Duration.GA.Rules
|
||||
( rules ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Types (NumberData(..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleCoics :: Rule
|
||||
ruleCoics = Rule
|
||||
{ name = "coicís"
|
||||
, pattern =
|
||||
[ regex "coic(\x00ed|i)s(\x00ed|i|e)?"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Day 14
|
||||
}
|
||||
|
||||
ruleLeathuair :: Rule
|
||||
ruleLeathuair = Rule
|
||||
{ name = "leathuair"
|
||||
, pattern =
|
||||
[ regex "leathuair(e|eanta)?"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleAonDurationAmhain :: Rule
|
||||
ruleAonDurationAmhain = Rule
|
||||
{ name = "aon X amhain"
|
||||
, pattern =
|
||||
[ isNumberWith TNumber.value (== 1)
|
||||
, dimension TimeGrain
|
||||
, isNumberWith TNumber.value (== 1)
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntegerUnitofdurationInteger :: Rule
|
||||
ruleIntegerUnitofdurationInteger = Rule
|
||||
{ name = "<unit-integer> <unit-of-duration> <tens-integer>"
|
||||
, pattern =
|
||||
[ isNumberWith TNumber.value (< 10)
|
||||
, dimension TimeGrain
|
||||
, isNumberWith TNumber.value (`elem` [10, 20 .. 50])
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v1}):
|
||||
Token TimeGrain grain:
|
||||
Token DNumber (NumberData {TNumber.value = v2}):
|
||||
_) -> Just . Token Duration . duration grain . floor $ v1 + v2
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleCoics
|
||||
, ruleIntegerUnitofdurationInteger
|
||||
, ruleLeathuair
|
||||
, ruleAonDurationAmhain
|
||||
]
|
24
Duckling/Duration/GA/Tests.hs
Normal file
24
Duckling/Duration/GA/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.Duration.GA.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.GA.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "GA Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
]
|
50
Duckling/Duration/Helpers.hs
Normal file
50
Duckling/Duration/Helpers.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.Duration.Helpers
|
||||
( duration
|
||||
, isGrain
|
||||
, isNatural
|
||||
, isNumberWith
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Types (DurationData (DurationData))
|
||||
import qualified Duckling.Duration.Types as TDuration
|
||||
import Duckling.Number.Types (NumberData (NumberData))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
-- -----------------------------------------------------------------
|
||||
-- Patterns
|
||||
|
||||
isGrain :: TG.Grain -> Predicate
|
||||
isGrain value (Token TimeGrain grain) = grain == value
|
||||
isGrain _ _ = False
|
||||
|
||||
isNatural :: Predicate
|
||||
isNatural (Token DNumber NumberData {TNumber.value = x}) =
|
||||
TNumber.isNatural x
|
||||
isNatural _ = False
|
||||
|
||||
isNumberWith :: (NumberData -> t) -> (t -> Bool) -> PatternItem
|
||||
isNumberWith f pred = Predicate $ \x -> case x of
|
||||
(Token DNumber x) -> pred $ f x
|
||||
_ -> False
|
||||
|
||||
-- -----------------------------------------------------------------
|
||||
-- Production
|
||||
|
||||
duration :: TG.Grain -> Int -> DurationData
|
||||
duration grain n = DurationData {TDuration.grain = grain, TDuration.value = n}
|
68
Duckling/Duration/IT/Rules.hs
Normal file
68
Duckling/Duration/IT/Rules.hs
Normal file
@ -0,0 +1,68 @@
|
||||
-- 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.Duration.IT.Rules
|
||||
( rules ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleUneUnitofduration :: Rule
|
||||
ruleUneUnitofduration = Rule
|
||||
{ name = "une <unit-of-duration>"
|
||||
, pattern =
|
||||
[ regex "un[a']?"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleUnQuartoDora :: Rule
|
||||
ruleUnQuartoDora = Rule
|
||||
{ name = "un quarto d'ora"
|
||||
, pattern =
|
||||
[ regex "un quarto d['i] ?ora"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 15
|
||||
}
|
||||
|
||||
ruleMezzOra :: Rule
|
||||
ruleMezzOra = Rule
|
||||
{ name = "mezz'ora"
|
||||
, pattern =
|
||||
[ regex "mezz[a'] ?ora"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleTreQuartiDora :: Rule
|
||||
ruleTreQuartiDora = Rule
|
||||
{ name = "tre quarti d'ora"
|
||||
, pattern =
|
||||
[ regex "(3|tre) quarti d['i] ?ora"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 45
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleUneUnitofduration
|
||||
, ruleUnQuartoDora
|
||||
, ruleMezzOra
|
||||
, ruleTreQuartiDora
|
||||
]
|
40
Duckling/Duration/JA/Corpus.hs
Normal file
40
Duckling/Duration/JA/Corpus.hs
Normal 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.Duration.JA.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = JA}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "1 秒"
|
||||
, "一 秒間"
|
||||
]
|
||||
, examples (DurationData 4 Minute)
|
||||
[ "四 分間"
|
||||
]
|
||||
, examples (DurationData 100 Day)
|
||||
[ "百 日"
|
||||
, "百 日間"
|
||||
]
|
||||
]
|
24
Duckling/Duration/JA/Tests.hs
Normal file
24
Duckling/Duration/JA/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.Duration.JA.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.JA.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "JA Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
]
|
40
Duckling/Duration/KO/Corpus.hs
Normal file
40
Duckling/Duration/KO/Corpus.hs
Normal 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.Duration.KO.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = KO}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "1 초"
|
||||
]
|
||||
, examples (DurationData 30 Minute)
|
||||
[ "시간반"
|
||||
, "시반"
|
||||
, "서른분"
|
||||
]
|
||||
, examples (DurationData 66 Minute)
|
||||
[ "1.1 시간"
|
||||
]
|
||||
]
|
112
Duckling/Duration/KO/Rules.hs
Normal file
112
Duckling/Duration/KO/Rules.hs
Normal file
@ -0,0 +1,112 @@
|
||||
-- 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.Duration.KO.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import qualified Data.Text as Text
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Helpers (parseInt)
|
||||
import Duckling.Number.Types (NumberData (..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Regex.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleHalfAnHour :: Rule
|
||||
ruleHalfAnHour = Rule
|
||||
{ name = "half an hour"
|
||||
, pattern =
|
||||
[ Predicate $ isGrain TG.Hour
|
||||
, regex "\xbc18"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleADay :: Rule
|
||||
ruleADay = Rule
|
||||
{ name = "a day - 하루"
|
||||
, pattern =
|
||||
[ regex "\xd558\xb8e8"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Day 1
|
||||
}
|
||||
|
||||
ruleNumbernumberHours :: Rule
|
||||
ruleNumbernumberHours = Rule
|
||||
{ name = "number.number hours"
|
||||
, pattern =
|
||||
[ regex "(\\d+)\\.(\\d+)"
|
||||
, regex "\xc2dc\xac04"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (m1:m2:_)):_) -> do
|
||||
hh <- parseInt m1
|
||||
dec <- parseInt m2
|
||||
let divisor = floor $ (fromIntegral (10 :: Integer) :: Float) **
|
||||
fromIntegral (Text.length m2 - 1)
|
||||
numerator = fromIntegral $ 6 * dec
|
||||
Just . Token Duration . duration TG.Minute $
|
||||
60 * hh + quot numerator divisor
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntegerAndAnHalfHours :: Rule
|
||||
ruleIntegerAndAnHalfHours = Rule
|
||||
{ name = "<integer> and an half hours"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "\xc2dc\xac04\xbc18"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):_) ->
|
||||
Just . Token Duration . duration TG.Minute $ 30 + 60 * floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAboutDuration :: Rule
|
||||
ruleAboutDuration = Rule
|
||||
{ name = "about <duration>"
|
||||
, pattern =
|
||||
[ regex "\xb300\xcda9|\xc57d"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleExactlyDuration :: Rule
|
||||
ruleExactlyDuration = Rule
|
||||
{ name = "exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "\xc815\xd655\xd788"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleADay
|
||||
, ruleAboutDuration
|
||||
, ruleExactlyDuration
|
||||
, ruleHalfAnHour
|
||||
, ruleIntegerAndAnHalfHours
|
||||
, ruleNumbernumberHours
|
||||
]
|
24
Duckling/Duration/KO/Tests.hs
Normal file
24
Duckling/Duration/KO/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.Duration.KO.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.KO.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "KO Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
]
|
47
Duckling/Duration/NB/Corpus.hs
Normal file
47
Duckling/Duration/NB/Corpus.hs
Normal file
@ -0,0 +1,47 @@
|
||||
-- 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.Duration.NB.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = NB}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "1 sek"
|
||||
, "en sek"
|
||||
, "ett sekund"
|
||||
, "e sekunder"
|
||||
]
|
||||
, examples (DurationData 30 Minute)
|
||||
[ "tredve min"
|
||||
, "30 minutt"
|
||||
, "30 minutter"
|
||||
, "1/2 time"
|
||||
, "en halv time"
|
||||
]
|
||||
, examples (DurationData 2 Day)
|
||||
[ "et par dager"
|
||||
, "2 dag"
|
||||
, "to dag"
|
||||
]
|
||||
]
|
129
Duckling/Duration/NB/Rules.hs
Normal file
129
Duckling/Duration/NB/Rules.hs
Normal file
@ -0,0 +1,129 @@
|
||||
-- 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.Duration.NB.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import qualified Data.Text as Text
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Helpers (parseInt)
|
||||
import Duckling.Number.Types (NumberData (..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Regex.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleHalfAnHour :: Rule
|
||||
ruleHalfAnHour = Rule
|
||||
{ name = "half an hour"
|
||||
, pattern =
|
||||
[ regex "(1/2|en halv) time"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleIntegerMoreUnitofduration :: Rule
|
||||
ruleIntegerMoreUnitofduration = Rule
|
||||
{ name = "<integer> more <unit-of-duration>"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, dimension TimeGrain
|
||||
, regex "mere?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):
|
||||
Token TimeGrain grain:
|
||||
_) -> Just . Token Duration . duration grain $ floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleNumbernumberHours :: Rule
|
||||
ruleNumbernumberHours = Rule
|
||||
{ name = "number.number hours"
|
||||
, pattern =
|
||||
[ regex "(\\d+)\\,(\\d+) *timer?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (h:d:_)):_) -> do
|
||||
hh <- parseInt h
|
||||
dec <- parseInt d
|
||||
let divisor = floor $ (fromIntegral (10 :: Integer) :: Float) **
|
||||
fromIntegral (Text.length d - 1)
|
||||
numerator = fromIntegral $ 6 * dec
|
||||
Just . Token Duration $ duration TG.Minute $
|
||||
60 * hh + quot numerator divisor
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntegerAndAnHalfHours :: Rule
|
||||
ruleIntegerAndAnHalfHours = Rule
|
||||
{ name = "<integer> and an half hours"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "og (en )?halv time?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):_) ->
|
||||
Just . Token Duration . duration TG.Minute $ 30 + 60 * floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAUnitofduration :: Rule
|
||||
ruleAUnitofduration = Rule
|
||||
{ name = "a <unit-of-duration>"
|
||||
, pattern =
|
||||
[ regex "en|ett|et?"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAboutDuration :: Rule
|
||||
ruleAboutDuration = Rule
|
||||
{ name = "about <duration>"
|
||||
, pattern =
|
||||
[ regex "(omkring|cirka|ca.|ca)"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleExactlyDuration :: Rule
|
||||
ruleExactlyDuration = Rule
|
||||
{ name = "exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "(precis|akkurat)"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleAUnitofduration
|
||||
, ruleAboutDuration
|
||||
, ruleExactlyDuration
|
||||
, ruleHalfAnHour
|
||||
, ruleIntegerAndAnHalfHours
|
||||
, ruleIntegerMoreUnitofduration
|
||||
, ruleNumbernumberHours
|
||||
]
|
24
Duckling/Duration/NB/Tests.hs
Normal file
24
Duckling/Duration/NB/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.Duration.NB.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.NB.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "NB Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
]
|
49
Duckling/Duration/PL/Corpus.hs
Normal file
49
Duckling/Duration/PL/Corpus.hs
Normal file
@ -0,0 +1,49 @@
|
||||
-- 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.Duration.PL.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = PL}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "1s"
|
||||
, "1 sekund"
|
||||
, "jeden sekundzie"
|
||||
, "pojedynczy sekundach"
|
||||
]
|
||||
, examples (DurationData 30 Minute)
|
||||
[ "pol godziny"
|
||||
, "pół godziny"
|
||||
, "30m"
|
||||
, "30 minut"
|
||||
, "trzydzieści minutami"
|
||||
]
|
||||
, examples (DurationData 5 Day)
|
||||
[ "pięciu dniach"
|
||||
]
|
||||
, examples (DurationData 100 Day)
|
||||
[ "sto dzień"
|
||||
, "setki dnią"
|
||||
]
|
||||
]
|
131
Duckling/Duration/PL/Rules.hs
Normal file
131
Duckling/Duration/PL/Rules.hs
Normal file
@ -0,0 +1,131 @@
|
||||
-- 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.Duration.PL.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import qualified Data.Text as Text
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Helpers (parseInt)
|
||||
import Duckling.Number.Types (NumberData (..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Regex.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleHalfAnHour :: Rule
|
||||
ruleHalfAnHour = Rule
|
||||
{ name = "half an hour"
|
||||
, pattern =
|
||||
[ regex "p(o|\x00f3)(l|\x0142) godziny"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleIntegerMoreUnitofduration :: Rule
|
||||
ruleIntegerMoreUnitofduration = Rule
|
||||
{ name = "<integer> more <unit-of-duration>"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "more|less"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):
|
||||
_:
|
||||
Token TimeGrain grain:
|
||||
_) -> Just . Token Duration . duration grain $ floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleNumbernumberHours :: Rule
|
||||
ruleNumbernumberHours = Rule
|
||||
{ name = "number.number hours"
|
||||
, pattern =
|
||||
[ regex "(\\d+)\\.(\\d+)"
|
||||
, regex "godzin(y)?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (h:d:_)):_) -> do
|
||||
hh <- parseInt h
|
||||
dec <- parseInt d
|
||||
let divisor = floor $ (fromIntegral (10 :: Integer) :: Float) **
|
||||
fromIntegral (Text.length d - 1)
|
||||
numerator = fromIntegral $ 6 * dec
|
||||
Just . Token Duration . duration TG.Minute $
|
||||
60 * hh + quot numerator divisor
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntegerAndAnHalfHours :: Rule
|
||||
ruleIntegerAndAnHalfHours = Rule
|
||||
{ name = "<integer> and an half hours"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "i (p(o|\x00f3)(l|\x0142)) godziny"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):_) ->
|
||||
Just . Token Duration . duration TG.Minute $ 30 + 60 * floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleUnitofdurationAsADuration :: Rule
|
||||
ruleUnitofdurationAsADuration = Rule
|
||||
{ name = "<unit-of-duration> as a duration"
|
||||
, pattern =
|
||||
[ dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token TimeGrain grain:_) ->
|
||||
Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAboutDuration :: Rule
|
||||
ruleAboutDuration = Rule
|
||||
{ name = "about <duration>"
|
||||
, pattern =
|
||||
[ regex "(oko(l|\x0142)o|miej wi(\x0119|e)cej|jakie(s|\x015b))"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleExactlyDuration :: Rule
|
||||
ruleExactlyDuration = Rule
|
||||
{ name = "exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "r(o|\x00f3)wno|dok(l|\x0142)adnie"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleAboutDuration
|
||||
, ruleExactlyDuration
|
||||
, ruleHalfAnHour
|
||||
, ruleIntegerAndAnHalfHours
|
||||
, ruleIntegerMoreUnitofduration
|
||||
, ruleNumbernumberHours
|
||||
, ruleUnitofdurationAsADuration
|
||||
]
|
24
Duckling/Duration/PL/Tests.hs
Normal file
24
Duckling/Duration/PL/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.Duration.PL.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.PL.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "PL Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
]
|
41
Duckling/Duration/PT/Corpus.hs
Normal file
41
Duckling/Duration/PT/Corpus.hs
Normal file
@ -0,0 +1,41 @@
|
||||
-- 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.Duration.PT.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = PT}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "um segundo"
|
||||
, "uma seg"
|
||||
]
|
||||
, examples (DurationData 2 Minute)
|
||||
[ "duas mins"
|
||||
, "dois minutos"
|
||||
]
|
||||
, examples (DurationData 20 Day)
|
||||
[ "20 dias"
|
||||
, "vinte días"
|
||||
]
|
||||
]
|
23
Duckling/Duration/PT/Tests.hs
Normal file
23
Duckling/Duration/PT/Tests.hs
Normal 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.Duration.PT.Tests
|
||||
( tests ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.PT.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "PT Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
]
|
52
Duckling/Duration/RO/Corpus.hs
Normal file
52
Duckling/Duration/RO/Corpus.hs
Normal 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.Duration.RO.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = RO}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "o sec"
|
||||
, "1 secunda"
|
||||
]
|
||||
, examples (DurationData 30 Minute)
|
||||
[ "jumatate ora"
|
||||
, "1/2h"
|
||||
, "treizeci minute"
|
||||
]
|
||||
, examples (DurationData 45 Minute)
|
||||
[ "trei sferturi de oră"
|
||||
, "45min"
|
||||
]
|
||||
, examples (DurationData 12 Week)
|
||||
[ "doișpe saptamanile"
|
||||
, "doisprezece saptămâni"
|
||||
]
|
||||
, examples (DurationData 2 Month)
|
||||
[ "2 luni"
|
||||
]
|
||||
, examples (DurationData 1 Quarter)
|
||||
[ "un trimestru"
|
||||
]
|
||||
]
|
81
Duckling/Duration/RO/Rules.hs
Normal file
81
Duckling/Duration/RO/Rules.hs
Normal 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.Duration.RO.Rules
|
||||
( rules ) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleQuarterOfAnHour :: Rule
|
||||
ruleQuarterOfAnHour = Rule
|
||||
{ name = "quarter of an hour"
|
||||
, pattern =
|
||||
[ regex "(1/4\\s?(h|or(a|\x0103))|sfert de or(a|\x0103))"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 15
|
||||
}
|
||||
|
||||
ruleJumatateDeOra :: Rule
|
||||
ruleJumatateDeOra = Rule
|
||||
{ name = "jumatate de ora"
|
||||
, pattern =
|
||||
[ regex "(1/2\\s?(h|or(a|\x0103))|jum(a|\x0103)tate (de )?or(a|\x0103))"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleTreiSferturiDeOra :: Rule
|
||||
ruleTreiSferturiDeOra = Rule
|
||||
{ name = "trei sferturi de ora"
|
||||
, pattern =
|
||||
[ regex "(3/4\\s?(h|or(a|\x0103))|trei sferturi de or(a|\x0103))"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 45
|
||||
}
|
||||
|
||||
ruleOUnitofduration :: Rule
|
||||
ruleOUnitofduration = Rule
|
||||
{ name = "o <unit-of-duration>"
|
||||
, pattern =
|
||||
[ regex "o|un"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) -> Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleExactInJurDeDuration :: Rule
|
||||
ruleExactInJurDeDuration = Rule
|
||||
{ name = "exact|in jur de <duration>"
|
||||
, pattern =
|
||||
[ regex "(exact|aproximativ|(i|\x00ee)n jur de)"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleExactInJurDeDuration
|
||||
, ruleJumatateDeOra
|
||||
, ruleOUnitofduration
|
||||
, ruleQuarterOfAnHour
|
||||
, ruleTreiSferturiDeOra
|
||||
]
|
24
Duckling/Duration/RO/Tests.hs
Normal file
24
Duckling/Duration/RO/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.Duration.RO.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.RO.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "RO Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
]
|
42
Duckling/Duration/Rules.hs
Normal file
42
Duckling/Duration/Rules.hs
Normal 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 OverloadedStrings #-}
|
||||
|
||||
module Duckling.Duration.Rules
|
||||
( rules
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Types (NumberData(..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Types
|
||||
|
||||
ruleIntegerUnitofduration :: Rule
|
||||
ruleIntegerUnitofduration = Rule
|
||||
{ name = "<integer> <unit-of-duration>"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):
|
||||
Token TimeGrain grain:
|
||||
_) -> Just . Token Duration . duration grain $ floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleIntegerUnitofduration
|
||||
]
|
48
Duckling/Duration/SV/Corpus.hs
Normal file
48
Duckling/Duration/SV/Corpus.hs
Normal file
@ -0,0 +1,48 @@
|
||||
-- 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.Duration.SV.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext {lang = SV}, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "enkel sek"
|
||||
, "1 sekund fler"
|
||||
, "1 sekunder mer"
|
||||
, "en sekunderna"
|
||||
, "et sek"
|
||||
, "ett sek"
|
||||
]
|
||||
, examples (DurationData 30 Minute)
|
||||
[ "1/2 timme"
|
||||
, "en halv timme"
|
||||
, "0,5 timmar"
|
||||
, "30 minuterna"
|
||||
, "trettio min"
|
||||
]
|
||||
, examples (DurationData 5 Year)
|
||||
[ "5 år"
|
||||
, "fem år"
|
||||
]
|
||||
]
|
131
Duckling/Duration/SV/Rules.hs
Normal file
131
Duckling/Duration/SV/Rules.hs
Normal file
@ -0,0 +1,131 @@
|
||||
-- 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.Duration.SV.Rules
|
||||
( rules ) where
|
||||
|
||||
import Control.Monad (join)
|
||||
import qualified Data.Text as Text
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.Helpers
|
||||
import Duckling.Number.Helpers (parseInt)
|
||||
import Duckling.Number.Types (NumberData(..))
|
||||
import qualified Duckling.Number.Types as TNumber
|
||||
import Duckling.Regex.Types
|
||||
import qualified Duckling.TimeGrain.Types as TG
|
||||
import Duckling.Types
|
||||
|
||||
ruleHalfAnHour :: Rule
|
||||
ruleHalfAnHour = Rule
|
||||
{ name = "half an hour"
|
||||
, pattern =
|
||||
[ regex "(1/2|en halv) timme"
|
||||
]
|
||||
, prod = \_ -> Just . Token Duration $ duration TG.Minute 30
|
||||
}
|
||||
|
||||
ruleIntegerMoreUnitofduration :: Rule
|
||||
ruleIntegerMoreUnitofduration = Rule
|
||||
{ name = "<integer> more <unit-of-duration>"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, dimension TimeGrain
|
||||
, regex "fler|mer"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):
|
||||
Token TimeGrain grain:
|
||||
_) -> Just . Token Duration . duration grain $ floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleNumbernumberHours :: Rule
|
||||
ruleNumbernumberHours = Rule
|
||||
{ name = "number.number hours"
|
||||
, pattern =
|
||||
[ regex "(\\d+)\\,(\\d+)"
|
||||
, regex "timm(e|ar)?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token RegexMatch (GroupMatch (h:d:_)):_) -> do
|
||||
hh <- parseInt h
|
||||
dec <- parseInt d
|
||||
let divisor = floor $ (fromIntegral (10 :: Integer) :: Float) **
|
||||
fromIntegral (Text.length d - 1)
|
||||
numerator = fromIntegral $ 6 * dec
|
||||
Just . Token Duration . duration TG.Minute $
|
||||
60 * hh + quot numerator divisor
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleIntegerAndAnHalfHours :: Rule
|
||||
ruleIntegerAndAnHalfHours = Rule
|
||||
{ name = "<integer> and an half hours"
|
||||
, pattern =
|
||||
[ Predicate isNatural
|
||||
, regex "och (en )?halv timme?"
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(Token DNumber (NumberData {TNumber.value = v}):_) ->
|
||||
Just . Token Duration . duration TG.Minute $ 30 + 60 * floor v
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAUnitofduration :: Rule
|
||||
ruleAUnitofduration = Rule
|
||||
{ name = "a <unit-of-duration>"
|
||||
, pattern =
|
||||
[ regex "en|ett?"
|
||||
, dimension TimeGrain
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:Token TimeGrain grain:_) ->
|
||||
Just . Token Duration $ duration grain 1
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleAboutDuration :: Rule
|
||||
ruleAboutDuration = Rule
|
||||
{ name = "about <duration>"
|
||||
, pattern =
|
||||
[ regex "(omkring|cirka|ca.|ca|runt)"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
ruleExactlyDuration :: Rule
|
||||
ruleExactlyDuration = Rule
|
||||
{ name = "exactly <duration>"
|
||||
, pattern =
|
||||
[ regex "(precis|exakt)"
|
||||
, dimension Duration
|
||||
]
|
||||
, prod = \tokens -> case tokens of
|
||||
(_:token:_) -> Just token
|
||||
_ -> Nothing
|
||||
}
|
||||
|
||||
rules :: [Rule]
|
||||
rules =
|
||||
[ ruleAUnitofduration
|
||||
, ruleAboutDuration
|
||||
, ruleExactlyDuration
|
||||
, ruleHalfAnHour
|
||||
, ruleIntegerAndAnHalfHours
|
||||
, ruleIntegerMoreUnitofduration
|
||||
, ruleNumbernumberHours
|
||||
]
|
24
Duckling/Duration/SV/Tests.hs
Normal file
24
Duckling/Duration/SV/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.Duration.SV.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.SV.Corpus
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "SV Tests"
|
||||
[ makeCorpusTest [Some Duration] corpus
|
||||
]
|
42
Duckling/Duration/Tests.hs
Normal file
42
Duckling/Duration/Tests.hs
Normal 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.
|
||||
|
||||
|
||||
module Duckling.Duration.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
|
||||
import qualified Duckling.Duration.EN.Tests as EN
|
||||
import qualified Duckling.Duration.FR.Tests as FR
|
||||
import qualified Duckling.Duration.GA.Tests as GA
|
||||
import qualified Duckling.Duration.JA.Tests as JA
|
||||
import qualified Duckling.Duration.KO.Tests as KO
|
||||
import qualified Duckling.Duration.NB.Tests as NB
|
||||
import qualified Duckling.Duration.PL.Tests as PL
|
||||
import qualified Duckling.Duration.PT.Tests as PT
|
||||
import qualified Duckling.Duration.RO.Tests as RO
|
||||
import qualified Duckling.Duration.SV.Tests as SV
|
||||
import qualified Duckling.Duration.ZH.Tests as ZH
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "Duration Tests"
|
||||
[ EN.tests
|
||||
, FR.tests
|
||||
, GA.tests
|
||||
, JA.tests
|
||||
, KO.tests
|
||||
, NB.tests
|
||||
, PL.tests
|
||||
, PT.tests
|
||||
, RO.tests
|
||||
, SV.tests
|
||||
, ZH.tests
|
||||
]
|
48
Duckling/Duration/Types.hs
Normal file
48
Duckling/Duration/Types.hs
Normal file
@ -0,0 +1,48 @@
|
||||
-- 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 DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
{-# LANGUAGE NoRebindableSyntax #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeFamilies #-}
|
||||
|
||||
module Duckling.Duration.Types where
|
||||
|
||||
import Control.DeepSeq
|
||||
import Data.Aeson
|
||||
import Data.Hashable
|
||||
import Data.Text (Text)
|
||||
import GHC.Generics
|
||||
import TextShow (showt)
|
||||
import Prelude
|
||||
|
||||
import Duckling.Resolve (Resolve(..))
|
||||
import Duckling.TimeGrain.Types (Grain(..), inSeconds)
|
||||
|
||||
data DurationData = DurationData
|
||||
{ value :: Int
|
||||
, grain :: Grain
|
||||
}
|
||||
deriving (Eq, Generic, Hashable, Show, Ord, NFData)
|
||||
|
||||
instance Resolve DurationData where
|
||||
type ResolvedValue DurationData = DurationData
|
||||
resolve _ x = Just x
|
||||
|
||||
instance ToJSON DurationData where
|
||||
toJSON DurationData {value, grain} = object
|
||||
[ "value" .= value
|
||||
, "unit" .= grain
|
||||
, showt grain .= value
|
||||
, "normalized" .= object
|
||||
[ "unit" .= ("second" :: Text)
|
||||
, "value" .= inSeconds grain value
|
||||
]
|
||||
]
|
39
Duckling/Duration/ZH/Corpus.hs
Normal file
39
Duckling/Duration/ZH/Corpus.hs
Normal 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.Duration.ZH.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Duration.Types
|
||||
import Duckling.Testing.Types
|
||||
import Duckling.TimeGrain.Types (Grain(..))
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (DurationData 1 Second)
|
||||
[ "1 秒钟"
|
||||
, "一 秒鐘"
|
||||
]
|
||||
, examples (DurationData 5 Day)
|
||||
[ "5 天"
|
||||
, "五 天"
|
||||
]
|
||||
, examples (DurationData 10 Month)
|
||||
[ "10 月"
|
||||
, "十 月"
|
||||
]
|
||||
]
|
31
Duckling/Duration/ZH/Tests.hs
Normal file
31
Duckling/Duration/ZH/Tests.hs
Normal file
@ -0,0 +1,31 @@
|
||||
-- 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.Duration.ZH.Tests
|
||||
( tests
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
import Test.Tasty
|
||||
import Test.Tasty.HUnit
|
||||
|
||||
import Duckling.Dimensions.Types
|
||||
import Duckling.Duration.ZH.Corpus
|
||||
import Duckling.Lang
|
||||
import Duckling.Resolve
|
||||
import Duckling.Testing.Asserts
|
||||
|
||||
tests :: TestTree
|
||||
tests = testGroup "ZH Tests"
|
||||
[ testCase "Corpus Tests" $
|
||||
mapM_ (analyzedFirstTest context {lang = ZH} . withTargets [Some Duration])
|
||||
xs
|
||||
]
|
||||
where
|
||||
(context, xs) = corpus
|
47
Duckling/Email/Corpus.hs
Normal file
47
Duckling/Email/Corpus.hs
Normal file
@ -0,0 +1,47 @@
|
||||
-- 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.Email.Corpus
|
||||
( corpus
|
||||
, negativeCorpus
|
||||
) where
|
||||
|
||||
import Prelude
|
||||
import Data.String
|
||||
|
||||
import Duckling.Email.Types
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext, allExamples)
|
||||
|
||||
negativeCorpus :: NegativeCorpus
|
||||
negativeCorpus = (testContext, examples)
|
||||
where
|
||||
examples =
|
||||
[ "hey@6"
|
||||
, "hey@you"
|
||||
]
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (EmailData "alice@exAmple.io")
|
||||
[ "alice@exAmple.io"
|
||||
]
|
||||
, examples (EmailData "yo+yo@blah.org")
|
||||
[ "yo+yo@blah.org"
|
||||
]
|
||||
, examples (EmailData "1234+abc@x.net")
|
||||
[ "1234+abc@x.net"
|
||||
]
|
||||
, examples (EmailData "jean-jacques@stuff.co.uk")
|
||||
[ "jean-jacques@stuff.co.uk"
|
||||
]
|
||||
]
|
38
Duckling/Email/EN/Corpus.hs
Normal file
38
Duckling/Email/EN/Corpus.hs
Normal 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.Email.EN.Corpus
|
||||
( corpus
|
||||
) where
|
||||
|
||||
import Data.String
|
||||
import Prelude
|
||||
|
||||
import Duckling.Email.Types
|
||||
import Duckling.Testing.Types
|
||||
|
||||
corpus :: Corpus
|
||||
corpus = (testContext, allExamples)
|
||||
|
||||
allExamples :: [Example]
|
||||
allExamples = concat
|
||||
[ examples (EmailData "alice@exAmple.io")
|
||||
[ "alice at exAmple.io"
|
||||
]
|
||||
, examples (EmailData "yo+yo@blah.org")
|
||||
[ "yo+yo at blah.org"
|
||||
]
|
||||
, examples (EmailData "1234+abc@x.net")
|
||||
[ "1234+abc at x.net"
|
||||
]
|
||||
, examples (EmailData "jean-jacques@stuff.co.uk")
|
||||
[ "jean-jacques at stuff.co.uk"
|
||||
]
|
||||
]
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue
Block a user