{-# LANGUAGE OverloadedStrings #-}
module Duckling.Time.VI.Corpus
( corpus
, negativeCorpus
) where
import Data.String
import Prelude
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types hiding (examples)
import Duckling.Time.Corpus
import Duckling.Time.Types hiding (Month, refTime)
import Duckling.TimeGrain.Types hiding (add)
negativeCorpus :: NegativeCorpus
negativeCorpus :: NegativeCorpus
negativeCorpus = (Context
context, Options
testOptions, [Text]
examples)
where
examples :: [Text]
examples =
[ Text
"có ngày chính xác"
]
corpus :: Corpus
corpus :: Corpus
corpus = (Context
context, Options
testOptions, [Example]
allExamples)
context :: Context
context :: Context
context = Context
testContext
{ locale :: Locale
locale = Lang -> Maybe Region -> Locale
makeLocale Lang
VI Maybe Region
forall a. Maybe a
Nothing
, referenceTime :: DucklingTime
referenceTime = Datetime -> Int -> DucklingTime
refTime (Integer
2017, Int
2, Int
2, Int
3, Int
55, Pico
0) (-Int
2)
}
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
2017, Int
2, Int
2, Int
3, Int
55, Pico
0) Grain
Second)
[ Text
"bây giờ"
, Text
"ngay bây giờ"
, Text
"ngay lúc này"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"hôm nay"
, Text
"ngày hôm nay"
, Text
"bữa nay"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
1, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"hôm qua"
, Text
"ngày hôm qua"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
3, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"ngày mai"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
1, Int
31, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"hôm kia"
, Text
"ngày hôm kia"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
6, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ 2"
, Text
"thứ hai"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
6, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ 2 ngày 6 tháng 2"
, Text
"thứ 2 mồng 6 tháng 2"
, Text
"thứ hai ngày 6 tháng 2"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
7, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ 3"
, Text
"thứ ba"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
5, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"chủ nhật"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
6, Int
1, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"tháng 6"
, Text
"tháng sáu"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
3, Int
1, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"ngày đầu tiên của tháng ba"
, Text
"ngày đầu tiên của tháng 3"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
3, Int
3, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"mồng 3 tháng ba"
, Text
"mồng 3 tháng 3"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
3, Int
3, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"ngày mồng 3 tháng 3 năm 2017"
, Text
"ngày 3 tháng 3 năm 2017"
, Text
"3/3/2017"
, Text
"3/3/17"
, Text
"03/03/2017"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
3, Int
7, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"ngày mồng 7 tháng 3"
, Text
"ngày 7 tháng ba"
, Text
"7/3"
, Text
"07/03"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
10, Int
1, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"tháng 10 năm 2017"
, Text
"tháng mười năm 2017"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
1991, Int
9, Int
3, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"03/09/1991"
, Text
"3/9/91"
, Text
"3/9/1991"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
10, Int
12, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"12 tháng 10 năm 2017"
, Text
"ngày 12 tháng 10 năm 2017"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
9, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ năm tuần tới"
, Text
"thứ 5 tuần sau"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
3, Int
1, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"tháng 3 tới"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
4, Int
9, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"chủ nhật ngày mồng 9 tháng 4"
, Text
"chủ nhật ngày 9 tháng 4"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
6, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ 2 ngày 6 tháng 2"
, Text
"thứ 2 ngày mồng 6 tháng 2"
, Text
"thứ hai ngày mồng 6 tháng 2"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2018, Int
4, Int
3, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ 3 ngày 3 tháng 4 năm 2018"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
1, Int
30, Int
0, Int
0, Pico
0) Grain
Week)
[ Text
"tuần này"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
1, Int
23, Int
0, Int
0, Pico
0) Grain
Week)
[ Text
"tuần trước"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
6, Int
0, Int
0, Pico
0) Grain
Week)
[ Text
"tuần sau"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"tháng trước"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
3, Int
1, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"tháng sau"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"quý này"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
4, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"quý sau"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
7, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"quý 3"
, Text
"quý ba"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2018, Int
10, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"quý 4 năm 2018"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2016, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Year)
[ Text
"năm trước"
, Text
"năm ngoái"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Year)
[ Text
"năm nay"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2018, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Year)
[ Text
"năm sau"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"quý này"
, Text
"quý nay"
, Text
"quý hiện tại"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
4, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"quý tới"
, Text
"quý tiếp"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
7, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"quý ba"
, Text
"quý 3"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2018, Int
10, Int
1, Int
0, Int
0, Pico
0) Grain
Quarter)
[ Text
"quý 4 của năm 2018"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2016, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Year)
[ Text
"năm ngoái"
, Text
"năm trước"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Year)
[ Text
"năm nay"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2018, Int
1, Int
1, Int
0, Int
0, Pico
0) Grain
Year)
[ Text
"năm tiếp theo"
, Text
"năm kế tiếp"
, Text
"năm tới"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
1, Int
31, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ ba vừa rồi"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
7, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ ba tới"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
3, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ sáu tới"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
8, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ tư tuần tới"
, Text
"thứ tư của tuần tới"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
3, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ sáu tuần này"
, Text
"thứ 6 tuần này"
, Text
"thứ 6 của tuần này"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ năm tuần này"
, Text
"thứ 5 của tuần này"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
9, Int
4, Int
0, Int
0, Pico
0) Grain
Week)
[ Text
"tuần đầu tiên của tháng 9 năm 2017"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
3, Int
2, Int
0, Pico
0) Grain
Hour)
[ Text
"vào lúc 2 giờ sáng"
, Text
"lúc 2 giờ sáng"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
3, Int
1, Int
18, Pico
0) Grain
Minute)
[ Text
"1:18 sáng"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
15, Int
0, Pico
0) Grain
Hour)
[ Text
"lúc 3 giờ tối"
, Text
"vào lúc 3 giờ chiều"
, Text
"vào đúng 3 giờ chiều"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
15, Int
0, Pico
0) Grain
Hour)
[ Text
"vào khoảng 3 giờ chiều"
, Text
"khoảng 3 giờ chiều"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
15, Int
30, Pico
0) Grain
Minute)
[ Text
"3 giờ rưỡi chiều"
, Text
"3:30 chiều"
, Text
"ba giờ rưỡi chiều"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
14, Int
30, Pico
0) Grain
Minute)
[ Text
"2:30"
, Text
"hai giờ rưỡi"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
15, Int
23, Pico
24) Grain
Second)
[ Text
"15:23:24"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
10, Int
45, Pico
0) Grain
Minute)
[ Text
"11 giờ kém 15"
, Text
"10 giờ 45 phút"
, Text
"10:45"
, Text
"10 giờ 45"
, Text
"10h45"
, Text
"10g45"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
20, Int
0, Pico
0) Grain
Hour)
[ Text
"8 giờ tối nay"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
4, Int
20, Int
19, Int
30, Pico
0) Grain
Minute)
[ Text
"vào lúc 7:30 chiều ngày 20 tháng 4 năm 2017"
, Text
"7:30 chiều ngày 20/4/2017"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
6, Int
21, Int
0, Int
0, Pico
0), (Integer
2017, Int
9, Int
24, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"mùa hè này"
, Text
"mùa hè năm nay"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2016, Int
12, Int
21, Int
0, Int
0, Pico
0), (Integer
2017, Int
3, Int
21, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"mùa đông này"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
2, Int
18, Int
0, Pico
0), (Integer
2017, Int
2, Int
3, Int
0, Int
0, Pico
0)) Grain
Hour)
[ Text
"tối nay"
, Text
"tối hôm nay"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
3, Int
18, Int
0, Pico
0), (Integer
2017, Int
2, Int
4, Int
0, Int
0, Pico
0)) Grain
Hour)
[ Text
"tối mai"
, Text
"tối ngày mai"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
3, Int
12, Int
0, Pico
0), (Integer
2017, Int
2, Int
3, Int
14, Int
0, Pico
0)) Grain
Hour)
[ Text
"trưa mai"
, Text
"trưa ngày mai"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
1, Int
18, Int
0, Pico
0), (Integer
2017, Int
2, Int
2, Int
0, Int
0, Pico
0)) Grain
Hour)
[ Text
"tối qua"
, Text
"tối hôm qua"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
5, Int
4, Int
0, Pico
0), (Integer
2017, Int
2, Int
5, Int
12, Int
0, Pico
0)) Grain
Hour)
[ Text
"sáng chủ nhật"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
2, Int
3, Int
54, Pico
58), (Integer
2017, Int
2, Int
2, Int
3, Int
55, Pico
0)) Grain
Second)
[ Text
"2 giây vừa rồi"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
2, Int
3, Int
55, Pico
1), (Integer
2017, Int
2, Int
2, Int
3, Int
55, Pico
4)) Grain
Second)
[ Text
"3 giây tới"
, Text
"3 giây tiếp theo"
, Text
"3 s tiếp theo"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
2, Int
3, Int
53, Pico
0), (Integer
2017, Int
2, Int
2, Int
3, Int
55, Pico
0)) Grain
Minute)
[ Text
"2 phút vừa rồi"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
2, Int
3, Int
56, Pico
0), (Integer
2017, Int
2, Int
2, Int
3, Int
59, Pico
0)) Grain
Minute)
[ Text
"3 phút tới"
, Text
"3 phút tiếp theo"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
2, Int
2, Int
0, Pico
0), (Integer
2017, Int
2, Int
2, Int
3, Int
0, Pico
0)) Grain
Hour)
[ Text
"một tiếng vừa rồi"
, Text
"1 giờ vừa qua"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
2, Int
4, Int
0, Pico
0), (Integer
2017, Int
2, Int
2, Int
7, Int
0, Pico
0)) Grain
Hour)
[ Text
"3 tiếng tiếp theo"
, Text
"3 giờ tới"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
1, Int
31, Int
0, Int
0, Pico
0), (Integer
2017, Int
2, Int
2, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"2 ngày vừa rồi"
, Text
"2 ngày vừa qua"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
3, Int
0, Int
0, Pico
0), (Integer
2017, Int
2, Int
6, Int
0, Int
0, Pico
0)) Grain
Day)
[ Text
"3 ngày tới"
, Text
"3 ngày tiếp theo"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2016, Int
12, Int
1, Int
0, Int
0, Pico
0), (Integer
2017, Int
2, Int
1, Int
0, Int
0, Pico
0)) Grain
Month)
[ Text
"2 tháng vừa rồi"
, Text
"2 tháng qua"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
3, Int
1, Int
0, Int
0, Pico
0), (Integer
2017, Int
6, Int
1, Int
0, Int
0, Pico
0)) Grain
Month)
[ Text
"3 tháng tới"
, Text
"ba tháng tiếp theo"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2015, Int
1, Int
1, Int
0, Int
0, Pico
0), (Integer
2017, Int
1, Int
1, Int
0, Int
0, Pico
0)) Grain
Year)
[ Text
"2 năm vừa rồi"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2018, Int
1, Int
1, Int
0, Int
0, Pico
0), (Integer
2021, Int
1, Int
1, Int
0, Int
0, Pico
0)) Grain
Year)
[ Text
"3 năm tới"
, Text
"3 năm tiếp theo"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
13, Int
0, Pico
0) Grain
Minute)
[ Text
"4pm CET"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
14, Int
0, Pico
0) Grain
Hour)
[ Text
"hôm nay lúc 2 giờ chiều"
, Text
"lúc 2 giờ chiều"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
4, Int
23, Int
16, Int
0, Pico
0) Grain
Minute)
[ Text
"lúc 4:00 chiều ngày 23/4"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
10, Int
12, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"ngày 12/10"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
4, Int
23, Int
16, Int
0, Pico
0) Grain
Hour)
[ Text
"lúc 4 giờ chiều ngày 23 tháng 4"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
3, Int
15, Int
0, Pico
0) Grain
Hour)
[ Text
"3 giờ chiều ngày mai"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
13, Int
30, Pico
0) Grain
Minute)
[ Text
"lúc 1:30 chiều"
, Text
"lúc 1 giờ 30 chiều"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
2, Int
13, Int
0, Pico
0), (Integer
2017, Int
2, Int
2, Int
17, Int
0, Pico
0)) Grain
Hour)
[ Text
"sau bữa trưa"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
2, Int
10, Int
30, Pico
0) Grain
Minute)
[ Text
"10:30"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2017, Int
2, Int
2, Int
4, Int
0, Pico
0), (Integer
2017, Int
2, Int
2, Int
12, Int
0, Pico
0)) Grain
Hour)
[ Text
"buổi sáng nay"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
2, Int
6, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"thứ hai tới"
, Text
"thứ 2 tới"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
4, Int
1, Int
0, Int
0, Pico
0) Grain
Month)
[ Text
"tháng 4"
, Text
"tháng tư"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples (Datetime -> Grain -> Context -> TimeValue
datetime (Integer
2017, Int
12, Int
25, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"giáng sinh"
, Text
"ngày giáng sinh"
]
]