-- 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 OverloadedStrings #-}

module Duckling.Time.EN.CA.Corpus
  ( allExamples
  ) where

import Data.String
import Prelude

import Duckling.Testing.Types hiding (examples)
import Duckling.Time.Corpus
import Duckling.Time.Types hiding (Month)
import Duckling.TimeGrain.Types hiding (add)

allExamples :: [Example]
allExamples :: [Example]
allExamples = [[Example]] -> [Example]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  [ (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
2, Int
15, Int
0, Int
0, Pico
0) Grain
Day)
             [ Text
"2/15"
             , Text
"on 2/15"
             , Text
"2 / 15"
             , Text
"2-15"
             , Text
"2 - 15"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
1974, Int
10, Int
31, Int
0, Int
0, Pico
0) Grain
Day)
             [ Text
"10/31/1974"
             , Text
"10/31/74"
             , Text
"10-31-74"
             , Text
"10.31.1974"
             , Text
"10 31 1974"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2013, Int
4, Int
25, Int
16, Int
0, Pico
0) Grain
Minute)
             [ Text
"4/25 at 4:00pm"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
10, Int
14, Int
0, Int
0, Pico
0) Grain
Day Text
"Thanksgiving Day")
             [ Text
"thanksgiving day"
             , Text
"thanksgiving"
             , Text
"thanksgiving 2013"
             , Text
"this thanksgiving"
             , Text
"next thanksgiving day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2014, Int
10, Int
13, Int
0, Int
0, Pico
0) Grain
Day Text
"Thanksgiving Day")
             [ Text
"thanksgiving of next year"
             , Text
"thanksgiving 2014"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2012, Int
10, Int
8, Int
0, Int
0, Pico
0) Grain
Day Text
"Thanksgiving Day")
             [ Text
"last thanksgiving"
             , Text
"thanksgiving day 2012"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2016, Int
10, Int
10, Int
0, Int
0, Pico
0) Grain
Day Text
"Thanksgiving Day")
             [ Text
"thanksgiving 2016"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2017, Int
10, Int
9, Int
0, Int
0, Pico
0) Grain
Day Text
"Thanksgiving Day")
             [ Text
"thanksgiving 2017"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
7, Int
1, Int
0, Int
0, Pico
0) Grain
Day Text
"Memorial Day")
             [ Text
"canada day"
             , Text
"memorial day"
             , Text
"dominion day"
             , Text
"Next Memorial Day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
4, Int
9, Int
0, Int
0, Pico
0) Grain
Day Text
"Vimy Ridge Day")
             [ Text
"vimy ridge day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
7, Int
12, Int
0, Int
0, Pico
0) Grain
Day Text
"The Twelfth")
             [ Text
"the Glorious Twelfth"
             , Text
"Orangemen's Day"
             , Text
"the twelfth"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
6, Int
24, Int
0, Int
0, Pico
0) Grain
Day Text
"Discovery Day")
             [ Text
"discovery day"
             , Text
"next discovery  day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2018, Int
6, Int
25, Int
0, Int
0, Pico
0) Grain
Day Text
"Discovery Day")
             [ Text
"discovery day 2018"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2020, Int
6, Int
22, Int
0, Int
0, Pico
0) Grain
Day Text
"Discovery Day")
             [ Text
"discovery   day 2020"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
6, Int
16, Int
0, Int
0, Pico
0) Grain
Day Text
"Father's Day")
             [ Text
"Father's Day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2012, Int
6, Int
17, Int
0, Int
0, Pico
0) Grain
Day Text
"Father's Day")
             [ Text
"last fathers day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
1996, Int
6, Int
16, Int
0, Int
0, Pico
0) Grain
Day Text
"Father's Day")
             [ Text
"fathers day 1996"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2018, Int
5, Int
21, Int
0, Int
0, Pico
0) Grain
Day Text
"Victoria Day")
             [ Text
"Victoria day 2018"
             , Text
"Sovereign's birthday 2018"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
8, Int
5, Int
0, Int
0, Pico
0) Grain
Day Text
"Civic Holiday")
             [ Text
"Civic Holiday"
             , Text
"British Columbia Day"
             , Text
"Natal Day"
             , Text
"New Brunswick Day"
             , Text
"Saskatchewan Day"
             , Text
"Terry Fox Day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2018, Int
2, Int
19, Int
0, Int
0, Pico
0) Grain
Day Text
"Family Day")
             [ Text
"family day 2018"
             , Text
"islander day 2018"
             , Text
"louis riel day 2018"
             , Text
"nova scotia heritage day 2018"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
5, Int
12, Int
0, Int
0, Pico
0) Grain
Day Text
"Mother's Day")
             [ Text
"Mother's Day"
             , Text
"next mothers day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2012, Int
5, Int
13, Int
0, Int
0, Pico
0) Grain
Day Text
"Mother's Day")
             [ Text
"last mothers day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2014, Int
5, Int
11, Int
0, Int
0, Pico
0) Grain
Day Text
"Mother's Day")
             [ Text
"mothers day 2014"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2017, Int
5, Int
22, Int
0, Int
0, Pico
0) Grain
Day Text
"National Patriots' Day")
             [ Text
"national patriots' day 2017"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2018, Int
5, Int
21, Int
0, Int
0, Pico
0) Grain
Day Text
"National Patriots' Day")
             [ Text
"national patriots' day 2018"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2019, Int
5, Int
20, Int
0, Int
0, Pico
0) Grain
Day Text
"National Patriots' Day")
             [ Text
"national patriots' day 2019"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
9, Int
2, Int
0, Int
0, Pico
0) Grain
Day Text
"Labour Day")
             [ Text
"labor day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2012, Int
9, Int
3, Int
0, Int
0, Pico
0) Grain
Day Text
"Labour Day")
             [ Text
"labor day of last year"
             , Text
"Labour Day 2012"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Text -> Context -> TimeValue
datetimeIntervalHoliday ((Integer
2013, Int
8, Int
30, Int
18, Int
0, Pico
0), (Integer
2013, Int
9, Int
3, Int
0, Int
0, Pico
0)) Grain
Hour Text
"Labour Day weekend")
             [ Text
"labor day weekend"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
2, Int
2, Int
0, Int
0, Pico
0) Grain
Day Text
"Groundhog Day")
             [ Text
"Groundhog day"
             , Text
"groundhogs day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2010, Int
4, Int
21, Int
0, Int
0, Pico
0) Grain
Day Text
"Administrative Professionals' Day")
             [ Text
"administrative professionals' day 2010"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2019, Int
4, Int
24, Int
0, Int
0, Pico
0) Grain
Day Text
"Administrative Professionals' Day")
             [ Text
"admin day 2019"
             , Text
"secretaries day in six years"
             ]
  ]