module Duckling.Quantity.EN.Rules
( rules ) where
import qualified Data.Text as Text
import Prelude
import Data.String
import qualified Duckling.Numeral.Types as TNumeral
import Duckling.Quantity.Helpers
import qualified Duckling.Quantity.Types as TQuantity
import Duckling.Regex.Types
import Duckling.Dimensions.Types
import Duckling.Types
ruleNumeralQuantity :: Rule
ruleNumeralQuantity = Rule
{ name = "<number> <quantity>"
, pattern =
[ dimension Numeral
, regex "(pound|cup)s?"
]
, prod = \tokens -> case tokens of
(Token Numeral nd:
Token RegexMatch (GroupMatch (match:_)):
_) -> case Text.toLower match of
"cup" -> Just . Token Quantity . quantity TQuantity.Cup $ TNumeral.value nd
"cups" -> Just . Token Quantity . quantity TQuantity.Cup $ TNumeral.value nd
"pound" -> Just . Token Quantity . quantity TQuantity.Pound $ TNumeral.value nd
"pounds" -> Just . Token Quantity . quantity TQuantity.Pound $ TNumeral.value nd
_ -> Nothing
_ -> Nothing
}
ruleAQuantity :: Rule
ruleAQuantity = Rule
{ name = "a quantity"
, pattern = [ regex "a (pound|cup)s?"]
, prod = \tokens -> case tokens of
(Token RegexMatch (GroupMatch (match:_)):_) -> case Text.toLower match of
"cup" -> Just . Token Quantity $ quantity TQuantity.Cup 1
"cups" -> Just . Token Quantity $ quantity TQuantity.Cup 1
"pound" -> Just . Token Quantity $ quantity TQuantity.Pound 1
"pounds" -> Just . Token Quantity $ quantity TQuantity.Pound 1
_ -> Nothing
_ -> Nothing
}
ruleQuantityOfProduct :: Rule
ruleQuantityOfProduct = Rule
{ name = "<quantity> of product"
, pattern =
[ dimension Quantity
, regex "of (meat|sugar)"
]
, prod = \tokens -> case tokens of
(Token Quantity qd:Token RegexMatch (GroupMatch (product:_)):_) ->
Just . Token Quantity $ withProduct product qd
_ -> Nothing
}
rules :: [Rule]
rules =
[ ruleNumeralQuantity
, ruleAQuantity
, ruleQuantityOfProduct
]