{-# LANGUAGE OverloadedStrings #-}
module Duckling.Time.ZH.MO.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
10, Int
1, Int
0, Int
0, Pico
0) Grain
Day)
[ Text
"国庆"
, Text
"國慶"
, Text
"国庆节"
, Text
"国庆節"
, Text
"國慶节"
, Text
"國慶節"
]
, (Context -> TimeValue) -> [Text] -> [Example]
forall a. ToJSON a => (Context -> a) -> [Text] -> [Example]
examples ((Datetime, Datetime) -> Grain -> Context -> TimeValue
datetimeInterval ((Integer
2013, Int
10, Int
1, Int
18, Int
0, Pico
0), (Integer
2013, Int
10, Int
2, Int
0, Int
0, Pico
0)) Grain
Hour)
[ Text
"国庆节晚上"
, Text
"國慶節晚上"
]
]