-- 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 #-} {-# LANGUAGE OverloadedStrings #-} module Duckling.Time.EN.GB.Rules ( rules ) where import Data.Maybe import Prelude import Duckling.Dimensions.Types import Duckling.Numeral.Helpers (parseInt) import Duckling.Regex.Types import Duckling.Time.Helpers import Duckling.Time.Types (TimeData (..)) import Duckling.Types ruleDDMM :: Rule ruleDDMM = Rule { name = "dd/mm" , pattern = [ regex "(3[01]|[12]\\d|0?[1-9])\\s?[/-]\\s?(0?[1-9]|1[0-2])" ] , prod = \tokens -> case tokens of (Token RegexMatch (GroupMatch (dd:mm:_)):_) -> do d <- parseInt dd m <- parseInt mm tt $ monthDay m d _ -> Nothing } ruleDDMMYYYY :: Rule ruleDDMMYYYY = Rule { name = "dd/mm/yyyy" , pattern = [ regex "(3[01]|[12]\\d|0?[1-9])[/-](0?[1-9]|1[0-2])[-/](\\d{2,4})" ] , prod = \tokens -> case tokens of (Token RegexMatch (GroupMatch (dd:mm:yy:_)):_) -> do y <- parseInt yy d <- parseInt dd m <- parseInt mm tt $ yearMonthDay y m d _ -> Nothing } ruleThanksgiving :: Rule ruleThanksgiving = Rule { name = "Thanksgiving Day" , pattern = [ regex "thanks?giving( day)?" ] , prod = \_ -> tt $ nthDOWOfMonth 4 4 11 -- Fourth Thursday of November } rules :: [Rule] rules = [ ruleDDMM , ruleDDMMYYYY , ruleThanksgiving ]