{-# LANGUAGE OverloadedStrings #-}
module Duckling.Time.EN.PH.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
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
2013, Int
12, Int
30, Int
0, Int
0, Pico
0) Grain
Day Text
"Rizal Day")
[ Text
"Rizal day"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
6, Int
12, 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
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
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
5, Int
1, Int
0, Int
0, Pico
0) Grain
Day Text
"Labour Day")
[ Text
"labour 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
1, Int
0, Int
0, Pico
0) Grain
Day Text
"Labour Day")
[ Text
"labour day of last year"
, Text
"Labour Day 2012"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Text -> Context -> TimeValue
datetimeHoliday (Integer
2013, Int
8, Int
26, Int
0, Int
0, Pico
0) Grain
Day Text
"National Heroes' Day")
[ Text
"national heroes' day"
]
]