duckling/Duckling/Rules/IT.hs
Ziyang Liu 5460d8df0e Support custom dimensions
Summary:
Support custom dimensions

Had to move the definition of `Dimension` from `Duckling.Dimensions.Types` to `Duckling.Types` to avoid cyclic imports between these two modules.

A sample custom dimension is in `exe/CustomDimensionExample.hs`.

Limitations of custom dimensions:

- All rules for a custom dimension must be in the same module with the definition of the custom dimension. Otherwise there will be cyclic imports, because the definition of the dimension and the rules refer to each other.
- The custom dimension must be specified when using `parse`, since there's no way to get all the existing custom dimensions.

Reviewed By: patapizza

Differential Revision: D7630360

fbshipit-source-id: 30e12dcb33611f5692c4f5949de377bf61b75e1e
2018-04-19 15:30:51 -07:00

53 lines
1.7 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 #-}
module Duckling.Rules.IT
( defaultRules
, langRules
, localeRules
) where
import Duckling.Dimensions.Types
import Duckling.Locale
import Duckling.Types
import qualified Duckling.Duration.IT.Rules as Duration
import qualified Duckling.Email.IT.Rules as Email
import qualified Duckling.Numeral.IT.Rules as Numeral
import qualified Duckling.Ordinal.IT.Rules as Ordinal
import qualified Duckling.Temperature.IT.Rules as Temperature
import qualified Duckling.Time.IT.Rules as Time
import qualified Duckling.TimeGrain.IT.Rules as TimeGrain
import qualified Duckling.Volume.IT.Rules as Volume
defaultRules :: Some Dimension -> [Rule]
defaultRules = langRules
localeRules :: Region -> Some Dimension -> [Rule]
localeRules region (This (CustomDimension dim)) = dimLocaleRules region dim
localeRules _ _ = []
langRules :: Some Dimension -> [Rule]
langRules (This AmountOfMoney) = []
langRules (This Distance) = []
langRules (This Duration) = Duration.rules
langRules (This Email) = Email.rules
langRules (This Numeral) = Numeral.rules
langRules (This Ordinal) = Ordinal.rules
langRules (This PhoneNumber) = []
langRules (This Quantity) = []
langRules (This RegexMatch) = []
langRules (This Temperature) = Temperature.rules
langRules (This Time) = Time.rules
langRules (This TimeGrain) = TimeGrain.rules
langRules (This Url) = []
langRules (This Volume) = Volume.rules
langRules (This (CustomDimension dim)) = dimLangRules IT dim