Skip to content

Commit

Permalink
DE: Distance + Volume
Browse files Browse the repository at this point in the history
Summary: Pull Request resolved: facebook#311

Reviewed By: patapizza

Differential Revision: D13683766

Pulled By: chinmay87

fbshipit-source-id: a18c5ab656d26eb2b83d9340f307baae89da56f6
  • Loading branch information
Martin Ring authored and facebook-github-bot committed Jan 28, 2019
1 parent 8b344b9 commit fc7f2c7
Show file tree
Hide file tree
Showing 11 changed files with 570 additions and 8 deletions.
4 changes: 3 additions & 1 deletion Duckling/Dimensions/DE.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,10 @@ import Duckling.Dimensions.Types

allDimensions :: [Some Dimension]
allDimensions =
[ This Duration
[ This Distance
, This Duration
, This Numeral
, This Ordinal
, This Time
, This Volume
]
75 changes: 75 additions & 0 deletions Duckling/Distance/DE/Corpus.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,75 @@
-- 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.DE.Corpus
( corpus
) where

import Data.String
import Prelude

import Duckling.Distance.Types
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types

corpus :: Corpus
corpus = (testContext {locale = makeLocale DE Nothing}, testOptions, allExamples)

allExamples :: [Example]
allExamples = concat
[ examples (simple Kilometre 3)
[ "3 kilometer"
, "3 km"
, "3km"
, "3,0 km"
]
, examples (simple Mile 8)
[ "acht meilen"
, "8 meilen"
]
, examples (simple Metre 9)
[ "9m"
]
, examples (simple Centimetre 2)
[ "2cm"
, "2 zentimeter"
]
, examples (simple Inch 5)
[ "5''"
, "fünf zoll"
, "5\""
]
, examples (simple Metre 1.87)
[ "1,87 meter"
]
, examples (between Kilometre (3, 5))
[ "zwischen 3 und 5 kilometern"
, "von 3km bis 5km"
, "um die 3-5 kilometer"
, "etwa 3km-5km"
, "3-5 kilometer"
]
, examples (under Mile 3.5)
[ "unter 3,5 meilen"
, "weniger als 3,5meilen"
--, "niedriger als dreikommafünf meilen"
]
, examples (above Inch 5)
[ "mehr als fünf zoll"
, "mindestens 5''"
, "über 5\""
]
, examples (between Millimetre (5, 6))
[ "zwischen 5 und sechs Millimetern"
, "zwischen 5 und sechs millimeter"
, "5-6 mm"
]
]
173 changes: 173 additions & 0 deletions Duckling/Distance/DE/Rules.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,173 @@
-- Copyright (c) 2016-present, Facebook, Inc.
-- All rights reserved.
--
-- This source code is licensed under the BSD-style license found in the
-- LICENSE file in the root directory of this source tree. An additional grant
-- of patent rights can be found in the PATENTS file in the same directory.


{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Duckling.Distance.DE.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.Numeral.Helpers
import Duckling.Numeral.Types (NumeralData(..))
import qualified Duckling.Numeral.Types as TNumeral
import Duckling.Types

distances :: [(Text, String, TDistance.Unit)]
distances =
[ -- Imperial
("miles", "meilen?", TDistance.Mile)
, ("inch", "(\"|''|zoll)", TDistance.Inch)
-- Metric
, ("km", "k(ilo)?m(etern?)?", TDistance.Kilometre)
, ("meters", "m(etern?)?", TDistance.Metre)
, ("centimeters", "(cm|[zc]entimetern?)", TDistance.Centimetre)
, ("millimeters", "(mm|millimetern?)", TDistance.Millimetre)
]

rulePrecision :: Rule
rulePrecision = Rule
{ name = "about|exactly <dist>"
, pattern =
[ regex "genau|exakt|präzise|ungefähr|(in )?etwa|nahe?( an)?|um( die)?|fast|rund|gut"
, dimension Distance
]
, prod = \case
(_:token:_) -> Just token
_ -> Nothing
}

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 = \case
(Token Distance dd:_) -> Just . Token Distance $ withUnit u dd
_ -> Nothing
}

ruleIntervalBetweenNumeral :: Rule
ruleIntervalBetweenNumeral = Rule
{ name = "between|from <numeral> to|and <dist>"
, pattern =
[ regex "zwischen|von"
, Predicate isPositive
, regex "bis|und"
, Predicate isSimpleDistance
]
, prod = \case
(_:
Token Numeral NumeralData{TNumeral.value = from}:
_:
Token Distance DistanceData{TDistance.value = Just to, TDistance.unit = Just u}:
_) | from < to ->
Just . Token Distance . withInterval (from, to) $ unitOnly u
_ -> Nothing
}

ruleIntervalBetween :: Rule
ruleIntervalBetween = Rule
{ name = "between|from <dist> to|and <dist>"
, pattern =
[ regex "zwischen|von"
, Predicate isSimpleDistance
, regex "und|bis"
, Predicate isSimpleDistance
]
, prod = \case
(_:
Token Distance DistanceData{TDistance.value = Just from, TDistance.unit = Just u1}:
_:
Token Distance DistanceData{TDistance.value = Just to, TDistance.unit = Just u2}:
_) | from < to && u1 == u2 ->
Just . Token Distance . withInterval (from, to) $ unitOnly u1
_ -> Nothing
}

ruleIntervalNumeralDash :: Rule
ruleIntervalNumeralDash = Rule
{ name = "<numeral> - <dist>"
, pattern =
[ Predicate isPositive
, regex "-"
, Predicate isSimpleDistance
]
, prod = \case
(Token Numeral NumeralData{TNumeral.value = from}:
_:
Token Distance DistanceData{TDistance.value = Just to, TDistance.unit = Just u}:
_) | from < to ->
Just . Token Distance . withInterval (from, to) $ unitOnly u
_ -> Nothing
}

ruleIntervalDash :: Rule
ruleIntervalDash = Rule
{ name = "<dist> - <dist>"
, pattern =
[ Predicate isSimpleDistance
, regex "-"
, Predicate isSimpleDistance
]
, prod = \case
(Token Distance DistanceData{TDistance.value = Just from, TDistance.unit = Just u1}:
_:
Token Distance DistanceData{TDistance.value = Just to, TDistance.unit = Just u2}:
_) | from < to && u1 == u2 ->
Just . Token Distance . withInterval (from, to) $ unitOnly u1
_ -> Nothing
}

ruleIntervalMax :: Rule
ruleIntervalMax = Rule
{ name = "under/less/lower/no more than <dist>"
, pattern =
[ regex "unter|höchstens|maximal|(weniger|nicht mehr) als"
, Predicate isSimpleDistance
]
, prod = \case
(_:
Token Distance DistanceData{TDistance.value = Just to, TDistance.unit = Just u}:
_) -> Just . Token Distance . withMax to $ unitOnly u
_ -> Nothing
}

ruleIntervalMin :: Rule
ruleIntervalMin = Rule
{ name = "over/above/at least/more than <dist>"
, pattern =
[ regex "über|(mehr|nicht weniger) als|mindestens|wenigstens|minimal"
, Predicate isSimpleDistance
]
, prod = \case
(_:
Token Distance DistanceData{TDistance.value = Just to, TDistance.unit = Just u}:
_) -> Just . Token Distance . withMin to $ unitOnly u
_ -> Nothing
}

rules :: [Rule]
rules =
[ ruleIntervalBetweenNumeral
, ruleIntervalBetween
, ruleIntervalMax
, ruleIntervalMin
, ruleIntervalNumeralDash
, ruleIntervalDash
, rulePrecision
]
++ ruleDistances
14 changes: 7 additions & 7 deletions Duckling/Rules/DE.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,23 +7,23 @@


{-# LANGUAGE GADTs #-}


module Duckling.Rules.DE
( defaultRules
, langRules
, localeRules
) where

import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.Distance.DE.Rules as Distance
import qualified Duckling.Duration.DE.Rules as Duration
import qualified Duckling.Email.DE.Rules as Email
import qualified Duckling.Ordinal.DE.Rules as Ordinal
import Duckling.Locale
import qualified Duckling.Numeral.DE.Rules as Numeral
import qualified Duckling.Ordinal.DE.Rules as Ordinal
import qualified Duckling.Time.DE.Rules as Time
import qualified Duckling.TimeGrain.DE.Rules as TimeGrain
import Duckling.Types
import qualified Duckling.Volume.DE.Rules as Volume

defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules
Expand All @@ -35,7 +35,7 @@ localeRules _ _ = []
langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = []
langRules (This CreditCardNumber) = []
langRules (This Distance) = []
langRules (This Distance) = Distance.rules
langRules (This Duration) = Duration.rules
langRules (This Email) = Email.rules
langRules (This Numeral) = Numeral.rules
Expand All @@ -47,5 +47,5 @@ langRules (This Temperature) = []
langRules (This Time) = Time.rules
langRules (This TimeGrain) = TimeGrain.rules
langRules (This Url) = []
langRules (This Volume) = []
langRules (This Volume) = Volume.rules
langRules (This (CustomDimension dim)) = dimLangRules DE dim
86 changes: 86 additions & 0 deletions Duckling/Volume/DE/Corpus.hs
Original file line number Diff line number Diff line change
@@ -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 OverloadedStrings #-}

module Duckling.Volume.DE.Corpus
( corpus ) where

import Data.String
import Prelude

import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.Volume.Types

corpus :: Corpus
corpus = (testContext {locale = makeLocale DE Nothing}, testOptions, allExamples)

allExamples :: [Example]
allExamples = concat
[ examples (simple Litre 1)
[ "1 liter"
--, "ein liter"
]
, examples (simple Litre 2)
[ "2 liter"
, "2l"
]
, examples (simple Litre 1000)
[ "1000 liter"
, "tausend liter"
]
, examples (simple Litre 0.5)
[ "halber liter"
, "ein halber liter"
]
, examples (simple Litre 0.25)
[ "viertel liter"
, "ein viertel liter"
]
, examples (simple Millilitre 1)
[ "ein milliliter"
, "ein ml"
, "1ml"
]
, examples (simple Millilitre 250)
[ "250 milliliter"
, "250ml"
, "250 ml"
]
, examples (simple Hectolitre 3)
[ "3 hektoliter"
]
, examples (between Litre (100,1000))
[ "zwischen 100 und 1000 litern"
, "100-1000 liter"
, "von 100 bis 1000 l"
, "100 - 1000 l"
]
, examples (between Litre (2,7))
[ "etwa 2 -7 l"
, "~2-7 liter"
, "von 2 bis 7 l"
, "zwischen 2,0 l und ungefähr 7,0 l"
, "zwischen 2l und etwa 7l"
, "2 - ~7 liter"
]
, examples (under Hectolitre 2)
[ "nicht mehr als 2 hektoliter"
, "höchstens zwei hektoliter"
, "unter 2 hektolitern"
, "weniger als 2 hektoliter"
]
, examples (above Millilitre 4)
[ "mehr als 4 ml"
, "wenigstens 4,0 ml"
, "über vier milliliter"
, "mindestens vier ml"
]
]
Loading

0 comments on commit fc7f2c7

Please sign in to comment.