mirror of
https://github.com/facebook/duckling.git
synced 2024-12-01 16:26:20 +03:00
3f8e52e70a
fbshipit-source-id: 301a10f448e9623aa1c953544f42de562909e192
154 lines
3.5 KiB
Haskell
154 lines
3.5 KiB
Haskell
-- Copyright (c) 2016-present, Facebook, Inc.
|
|
-- All rights reserved.
|
|
--
|
|
-- This source code is licensed under the BSD-style license found in the
|
|
-- LICENSE file in the root directory of this source tree. An additional grant
|
|
-- of patent rights can be found in the PATENTS file in the same directory.
|
|
|
|
|
|
{-# LANGUAGE GADTs #-}
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
module Duckling.Finance.VI.Rules
|
|
( rules ) where
|
|
|
|
import Data.Maybe
|
|
import Prelude
|
|
import Data.String
|
|
|
|
import Duckling.Dimensions.Types
|
|
import Duckling.Finance.Helpers
|
|
import Duckling.Finance.Types (Currency(..), FinanceData (..))
|
|
import qualified Duckling.Finance.Types as TFinance
|
|
import Duckling.Number.Types (NumberData (..))
|
|
import qualified Duckling.Number.Types as TNumber
|
|
import Duckling.Types
|
|
|
|
ruleNg :: Rule
|
|
ruleNg = Rule
|
|
{ name = "đồng"
|
|
, pattern =
|
|
[ regex "\x0111\x1ed3ng?"
|
|
]
|
|
, prod = \_ -> Just . Token Finance $ currencyOnly VND
|
|
}
|
|
|
|
ruleDollar :: Rule
|
|
ruleDollar = Rule
|
|
{ name = "$"
|
|
, pattern =
|
|
[ regex "\x0111\x00f4 la|\x0111\x00f4 m\x1ef9|\x0111(\x00f4)?"
|
|
]
|
|
, prod = \_ -> Just . Token Finance $ currencyOnly Dollar
|
|
}
|
|
|
|
ruleVnd :: Rule
|
|
ruleVnd = Rule
|
|
{ name = "VNĐ"
|
|
, pattern =
|
|
[ regex "vn(\x0110|\\$)"
|
|
]
|
|
, prod = \_ -> Just . Token Finance $ currencyOnly VND
|
|
}
|
|
|
|
ruleCent :: Rule
|
|
ruleCent = Rule
|
|
{ name = "cent"
|
|
, pattern =
|
|
[ regex "xen|xu?|penn(y|ies)"
|
|
]
|
|
, prod = \_ -> Just . Token Finance $ currencyOnly Cent
|
|
}
|
|
|
|
rulePounds :: Rule
|
|
rulePounds = Rule
|
|
{ name = "£"
|
|
, pattern =
|
|
[ regex "pounds?"
|
|
]
|
|
, prod = \_ -> Just . Token Finance $ currencyOnly Pound
|
|
}
|
|
|
|
ruleIntersect :: Rule
|
|
ruleIntersect = Rule
|
|
{ name = "intersect"
|
|
, pattern =
|
|
[ financeWith TFinance.value isJust
|
|
, dimension DNumber
|
|
]
|
|
, prod = \tokens -> case tokens of
|
|
(Token Finance fd:
|
|
Token DNumber (NumberData {TNumber.value = c}):
|
|
_) -> Just . Token Finance $ withCents c fd
|
|
_ -> Nothing
|
|
}
|
|
|
|
ruleIntersectAndNumber :: Rule
|
|
ruleIntersectAndNumber = Rule
|
|
{ name = "intersect and number"
|
|
, pattern =
|
|
[ financeWith TFinance.value isJust
|
|
, regex "v\x00e0"
|
|
, dimension DNumber
|
|
]
|
|
, prod = \tokens -> case tokens of
|
|
(Token Finance fd:
|
|
_:
|
|
Token DNumber (NumberData {TNumber.value = c}):
|
|
_) -> Just . Token Finance $ withCents c fd
|
|
_ -> Nothing
|
|
}
|
|
|
|
ruleIntersectXXuxen :: Rule
|
|
ruleIntersectXXuxen = Rule
|
|
{ name = "intersect (X xu|xen)"
|
|
, pattern =
|
|
[ financeWith TFinance.value isJust
|
|
, financeWith TFinance.currency (== Cent)
|
|
]
|
|
, prod = \tokens -> case tokens of
|
|
(Token Finance fd:
|
|
Token Finance (FinanceData {TFinance.value = Just c}):
|
|
_) -> Just . Token Finance $ withCents c fd
|
|
_ -> Nothing
|
|
}
|
|
|
|
ruleIntersectVXXuxen :: Rule
|
|
ruleIntersectVXXuxen = Rule
|
|
{ name = "intersect (và X xu|xen)"
|
|
, pattern =
|
|
[ financeWith TFinance.value isJust
|
|
, regex "v\x00e0"
|
|
, financeWith TFinance.currency (== Cent)
|
|
]
|
|
, prod = \tokens -> case tokens of
|
|
(Token Finance fd:
|
|
_:
|
|
Token Finance (FinanceData {TFinance.value = Just c}):
|
|
_) -> Just . Token Finance $ withCents c fd
|
|
_ -> Nothing
|
|
}
|
|
|
|
ruleDirham :: Rule
|
|
ruleDirham = Rule
|
|
{ name = "AED"
|
|
, pattern =
|
|
[ regex "AED\\.|dirhams?"
|
|
]
|
|
, prod = \_ -> Just . Token Finance $ currencyOnly AED
|
|
}
|
|
|
|
rules :: [Rule]
|
|
rules =
|
|
[ ruleCent
|
|
, ruleDirham
|
|
, ruleDollar
|
|
, ruleIntersect
|
|
, ruleIntersectAndNumber
|
|
, ruleIntersectVXXuxen
|
|
, ruleIntersectXXuxen
|
|
, ruleNg
|
|
, rulePounds
|
|
, ruleVnd
|
|
]
|