-- 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.US.Corpus
  ( allExamples
  ) where

import Data.String
import Prelude

import Duckling.Testing.Types hiding (examples)
import Duckling.Time.Corpus
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
11, Int
28, 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
11, Int
27, 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
11, Int
22, 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
11, Int
24, 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
11, Int
23, 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
2012, Int
11, Int
26, Int
0, Int
0, Pico
0) Grain
Day Text
"Cyber Monday")
             [ Text
"last cyber monday"
             , Text
"cyber monday 2012"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2017, Int
11, Int
27, Int
0, Int
0, Pico
0) Grain
Day Text
"Cyber Monday")
             [ Text
"cyber monday 2017"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
5, Int
27, Int
0, Int
0, Pico
0) Grain
Day Text
"Memorial Day")
             [ Text
"memorial day"
             , Text
"Next Memorial Day"
             , Text
"decoration 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
28, Int
0, Int
0, Pico
0) Grain
Day Text
"Memorial Day")
             [ Text
"last memorial day"
             , Text
"memorial day of last year"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Text -> Context -> TimeValue
datetimeIntervalHoliday ((Integer
2013, Int
5, Int
24, Int
18, Int
0, Pico
0), (Integer
2013, Int
5, Int
28, Int
0, Int
0, Pico
0)) Grain
Hour Text
"Memorial Day weekend")
             [ Text
"memorial day week-end"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
7, Int
4, Int
0, Int
0, Pico
0) Grain
Day Text
"Independence Day")
             [ Text
"independence day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
11, Int
11, Int
0, Int
0, Pico
0) Grain
Day Text
"Veterans Day")
             [ Text
"veterans day"
             , Text
"veteran day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
5, Int
1, Int
0, Int
0, Pico
0) Grain
Day Text
"Loyalty Day")
             [ Text
"law day"
             , Text
"Lei Day"
             , Text
"loyalty day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
2, Int
18, Int
0, Int
0, Pico
0) Grain
Day Text
"President's Day")
             [ Text
"George Washington Day"
             , Text
"washington's birthday"
             , Text
"presidents' day"
             , Text
"president day 2013"
             , Text
"Daisy Gatson Bates Day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
2, Int
12, Int
0, Int
0, Pico
0) Grain
Day Text
"Lincoln's Birthday")
             [ Text
"Lincolns birthday"
             , Text
"Abraham Lincoln's birthday"
             , Text
"Lincoln birthday"
             , Text
"Lincolns' birthday"
             ]
  , (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
2019, Int
9, Int
8, Int
0, Int
0, Pico
0) Grain
Day Text
"National Grandparents Day")
             [ Text
"national grandparents day 2019"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2018, Int
5, Int
11, Int
0, Int
0, Pico
0) Grain
Day Text
"Military Spouse Day")
             [ Text
"Military Spouse 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
2013, Int
9, Int
2, Int
0, Int
0, Pico
0) Grain
Day Text
"Labor 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
"Labor Day")
             [ Text
"labor day of last year"
             , Text
"Labor 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
"Labor 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
2011, Int
4, Int
15, Int
0, Int
0, Pico
0) Grain
Day Text
"Emancipation Day")
             [ Text
"emancipation day 2011"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2012, Int
4, Int
16, Int
0, Int
0, Pico
0) Grain
Day Text
"Emancipation Day")
             [ Text
"emancipation day 2012"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2017, Int
4, Int
17, Int
0, Int
0, Pico
0) Grain
Day Text
"Emancipation Day")
             [ Text
"emancipation day 2017"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2011, Int
4, Int
18, Int
0, Int
0, Pico
0) Grain
Day Text
"Tax Day")
             [ Text
"tax day 2011"
             , Text
"tax day two years ago"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2012, Int
4, Int
17, Int
0, Int
0, Pico
0) Grain
Day Text
"Tax Day")
             [ Text
"tax day 2012"
             , Text
"tax day last year"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
4, Int
15, Int
0, Int
0, Pico
0) Grain
Day Text
"Tax Day")
             [ Text
"next tax day"
             , Text
"tax day 2013"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2017, Int
4, Int
18, Int
0, Int
0, Pico
0) Grain
Day Text
"Tax Day")
             [ Text
"tax day 2017"
             , Text
"tax day in 4 years"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
4, Int
10, Int
0, Int
0, Pico
0) Grain
Day Text
"Siblings Day")
             [ Text
"siblings day"
             , Text
"national sibling day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2016, Int
4, Int
27, Int
0, Int
0, Pico
0) Grain
Day Text
"Administrative Professionals' Day")
             [ Text
"administrative professionals' day 2016"
             , Text
"administrative professionals day 2016"
             , Text
"administrative professional day 2016"
             , Text
"administrative professional's day of 2016"
             , Text
"secretaries' day 2016"
             , Text
"admins day 2016"
             ]
  , (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
"administrative professionals' day 2019"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Text -> Context -> TimeValue
datetimeIntervalHoliday ((Integer
2013, Int
4, Int
26, Int
0, Int
0, Pico
0), (Integer
2013, Int
4, Int
29, Int
0, Int
0, Pico
0)) Grain
Day Text
"Global Youth Service Day")
             [ Text
"national youth service day"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Text -> Context -> TimeValue
datetimeIntervalHoliday ((Integer
2018, Int
5, Int
20, Int
0, Int
0, Pico
0), (Integer
2018, Int
5, Int
27, Int
0, Int
0, Pico
0)) Grain
Day Text
"Emergency Medical Services Week")
             [ Text
"ems week 2018"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2018, Int
5, Int
23, Int
0, Int
0, Pico
0) Grain
Day Text
"Emergency Medical Services for Children Day")
             [ Text
"emsc day 2018"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2017, Int
3, Int
12, Int
0, Int
0, Pico
0) Grain
Day Text
"Daylight Saving Start Day")
             [ Text
"daylight saving start day 2017"
             , Text
"daylight saving start 2017"
             , Text
"daylight savings start day 2017"
             , Text
"daylight savings start 2017"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2017, Int
11, Int
5, Int
0, Int
0, Pico
0) Grain
Day Text
"Daylight Saving End Day")
             [ Text
"daylight saving end day 2017"
             , Text
"daylight saving end 2017"
             , Text
"daylight savings end day 2017"
             , Text
"daylight savings end 2017"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2008, Int
2, Int
5, Int
0, Int
0, Pico
0) Grain
Day Text
"Super Tuesday")
             [ Text
"super tuesday 2008"
             , Text
"giga Tuesday"
             , Text
"mega giga Tuesday"
             , Text
"Tsunami Tuesday in 2008"
             , Text
"Super Duper Tuesday"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2012, Int
3, Int
6, Int
0, Int
0, Pico
0) Grain
Day Text
"Super Tuesday")
             [ Text
"super tuesday 2012"
             , Text
"last super tuesday"
             , Text
"super tuesday last year"
             , Text
"the second closest super tuesday to the third Sunday of 2015"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2016, Int
3, Int
1, Int
0, Int
0, Pico
0) Grain
Day Text
"Super Tuesday")
             [ Text
"super tuesday 2016"
             , Text
"next super tuesday"
             , Text
"super tuesday"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2020, Int
3, Int
3, Int
0, Int
0, Pico
0) Grain
Day Text
"Super Tuesday")
             [ Text
"super tuesday 2020"
             , Text
"super tuesday in seven years"
             , Text
"the first super tue. after 2019"
             , Text
"the 2nd Super Tuesday after next year"
             , Text
"the closest super tuesday to 2019"
             , Text
"the closest super tuesday to March 6, 2019"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2004, Int
2, Int
3, Int
0, Int
0, Pico
0) Grain
Day Text
"Mini-Tuesday")
             [ Text
"mini-tuesday"
             , Text
"Mini - Tuesday 2004"
             , Text
"mini tuesday nine yrs ago"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2004, Int
3, Int
2, Int
0, Int
0, Pico
0) Grain
Day Text
"Super Tuesday")
             [ Text
"the closest super tuesday to mini-tuesday"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2000, Int
3, Int
7, Int
0, Int
0, Pico
0) Grain
Day Text
"Super Tuesday")
             [ Text
"the second closest super tuesday to mini-tuesday"
             ]
  , (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2008, Int
2, Int
5, Int
0, Int
0, Pico
0) Grain
Day Text
"Super Tuesday")
             [ Text
"the 3rd closest super tuesday to mini-tuesday"
             , Text
"the first closest Super Tuesday to tax day 2006"
             ]
  ]