-- 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.


{-# LANGUAGE GADTs #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE OverloadedStrings #-}

module Duckling.Time.EN.NZ.Rules
  ( rules
  ) where

import Data.Maybe
import Prelude

import Duckling.Dimensions.Types
import Duckling.Numeral.Helpers (parseInt)
import Duckling.Regex.Types
import Duckling.Time.Computed (easterSunday)
import Duckling.Time.Helpers
import Duckling.Time.Types (TimeData (..))
import Duckling.Types
import qualified Duckling.TimeGrain.Types as TG

ruleDDMM :: Rule
ruleDDMM :: Rule
ruleDDMM = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"dd/mm"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex String
"(3[01]|[12]\\d|0?[1-9])\\s?[/-]\\s?(1[0-2]|0?[1-9])"
    ]
  , prod :: Production
prod = \[Token]
tokens -> case [Token]
tokens of
      (Token Dimension a
RegexMatch (GroupMatch (dd:mm:_)):[Token]
_) -> do
        Int
d <- Text -> Maybe Int
parseInt Text
dd
        Int
m <- Text -> Maybe Int
parseInt Text
mm
        TimeData -> Maybe Token
tt (TimeData -> Maybe Token) -> TimeData -> Maybe Token
forall a b. (a -> b) -> a -> b
$ Int -> Int -> TimeData
monthDay Int
m Int
d
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }

ruleDDMMYYYY :: Rule
ruleDDMMYYYY :: Rule
ruleDDMMYYYY = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"dd/mm/yyyy"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex String
"(3[01]|[12]\\d|0?[1-9])[-/\\s](1[0-2]|0?[1-9])[-/\\s](\\d{2,4})"
    ]
  , prod :: Production
prod = \[Token]
tokens -> case [Token]
tokens of
      (Token Dimension a
RegexMatch (GroupMatch (dd:mm:yy:_)):[Token]
_) -> do
        Int
y <- Text -> Maybe Int
parseInt Text
yy
        Int
d <- Text -> Maybe Int
parseInt Text
dd
        Int
m <- Text -> Maybe Int
parseInt Text
mm
        TimeData -> Maybe Token
tt (TimeData -> Maybe Token) -> TimeData -> Maybe Token
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> TimeData
yearMonthDay Int
y Int
m Int
d
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }

-- Clashes with HHMMSS, hence only 4-digit years
ruleDDMMYYYYDot :: Rule
ruleDDMMYYYYDot :: Rule
ruleDDMMYYYYDot = Rule :: Text -> Pattern -> Production -> Rule
Rule
  { name :: Text
name = Text
"dd.mm.yyyy"
  , pattern :: Pattern
pattern =
    [ String -> PatternItem
regex String
"(3[01]|[12]\\d|0?[1-9])\\.(1[0-2]|0?[1-9])\\.(\\d{4})"
    ]
  , prod :: Production
prod = \[Token]
tokens -> case [Token]
tokens of
      (Token Dimension a
RegexMatch (GroupMatch (dd:mm:yy:_)):[Token]
_) -> do
        Int
y <- Text -> Maybe Int
parseInt Text
yy
        Int
d <- Text -> Maybe Int
parseInt Text
dd
        Int
m <- Text -> Maybe Int
parseInt Text
mm
        TimeData -> Maybe Token
tt (TimeData -> Maybe Token) -> TimeData -> Maybe Token
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> TimeData
yearMonthDay Int
y Int
m Int
d
      [Token]
_ -> Maybe Token
forall a. Maybe a
Nothing
  }

rulePeriodicHolidays :: [Rule]
rulePeriodicHolidays :: [Rule]
rulePeriodicHolidays = [(Text, String, TimeData)] -> [Rule]
mkRuleHolidays
  -- Fixed dates, year over year
  [ ( Text
"ANZAC Day", String
"anzac day", Int -> Int -> TimeData
monthDay Int
4 Int
25 )
  , ( Text
"Guy Fawkes Night", String
"guy fawkes night", Int -> Int -> TimeData
monthDay Int
11 Int
5 )
  , ( Text
"Waitangi Day", String
"waitangi day", Int -> Int -> TimeData
monthDay Int
2 Int
6 )

  -- Fixed day/week/month, year over year
  , ( Text
"Administrative Professionals' Day"
    , String
"(administrative professional|secretarie|admin)('?s'?)? day"
    , Int -> Int -> Int -> TimeData
nthDOWOfMonth Int
3 Int
3 Int
4 )
  , ( Text
"Father's Day", String
"father'?s?'? day", Int -> Int -> Int -> TimeData
nthDOWOfMonth Int
1 Int
7 Int
9 )
  , ( Text
"Labour Day", String
"labour day", Int -> Int -> Int -> TimeData
nthDOWOfMonth Int
4 Int
1 Int
10 )
  , ( Text
"Mother's Day", String
"mother'?s?'? day", Int -> Int -> Int -> TimeData
nthDOWOfMonth Int
2 Int
7 Int
5 )
  , ( Text
"Queen's birthday", String
"queen's birthday", Int -> Int -> Int -> TimeData
nthDOWOfMonth Int
1 Int
1 Int
6 )
  , ( Text
"Thanksgiving Day", String
"thanks?giving( day)?", Int -> Int -> Int -> TimeData
nthDOWOfMonth Int
4 Int
4 Int
11 )
  ]

ruleComputedHolidays :: [Rule]
ruleComputedHolidays :: [Rule]
ruleComputedHolidays = [(Text, String, TimeData)] -> [Rule]
mkRuleHolidays
  [ ( Text
"Easter Tuesday", String
"easter\\s+tue(sday)?"
    , Bool -> Grain -> Int -> TimeData -> TimeData
cycleNthAfter Bool
False Grain
TG.Day Int
2 TimeData
easterSunday )
  ]

rules :: [Rule]
rules :: [Rule]
rules =
  [ Rule
ruleDDMM
  , Rule
ruleDDMMYYYY
  , Rule
ruleDDMMYYYYDot
  ]
  [Rule] -> [Rule] -> [Rule]
forall a. [a] -> [a] -> [a]
++ [Rule]
ruleComputedHolidays
  [Rule] -> [Rule] -> [Rule]
forall a. [a] -> [a] -> [a]
++ [Rule]
rulePeriodicHolidays