-- 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.Duration.ZH.Corpus
  ( corpus
  ) where

import Data.String
import Prelude

import Duckling.Duration.Types
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
import Duckling.TimeGrain.Types (Grain(..))

corpus :: Corpus
corpus :: Corpus
corpus = (Context
testContext {locale :: Locale
locale = Lang -> Maybe Region -> Locale
makeLocale Lang
ZH Maybe Region
forall a. Maybe a
Nothing}, Options
testOptions, [Example]
allExamples)

allExamples :: [Example]
allExamples :: [Example]
allExamples = [[Example]] -> [Example]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
  [ DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
1 Grain
Second)
             [ Text
"1 秒钟"
             , Text
"一 秒鐘"
             , Text
"一 秒"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
1 Grain
Minute)
             [ Text
"1 分鐘"
             , Text
"一 分鐘"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
1 Grain
Hour)
             [ Text
"1 小時"
             , Text
"一 小時"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
5 Grain
Day)
             [ Text
"5 天"
             , Text
"五 天"
             , Text
"五 日"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
10 Grain
Month)
             [ Text
"10 月"
             , Text
"十 月"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
30 Grain
Minute)
             [ Text
"30分鐘"
             , Text
"半個鐘"
             , Text
"半小時"
             , Text
"三十分鐘"
             , Text
"卅分鐘"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
12 Grain
Hour)
             [ Text
"半日"
             , Text
"半天"
             , Text
"十二小時"
             , Text
"十二個鐘"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
90 Grain
Minute)
             [ Text
"一個半小時"
             , Text
"個半小時"
             , Text
"個半鐘"
             , Text
"一個半鐘"
             , Text
"1.5小時"
             , Text
"一個小時三十分鐘"
             , Text
"一小時零三十分鐘"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
130 Grain
Minute)
             [ Text
"兩小時十分"
             , Text
"一百三十分鐘"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
3615 Grain
Second)
             [ Text
"一小時零十五秒"
             , Text
"一個鐘零十五秒"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
45 Grain
Day)
             [ Text
"一個半月"
             , Text
"個半月"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
27 Grain
Month)
             [ Text
"兩年零三個月"
             , Text
"廿七個月"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
330 Grain
Second)
             [ Text
"五個半分鐘"
             , Text
"五點五分鐘"
             , Text
"5.5分鐘"
             , Text
"五分三十秒"
             , Text
"五分半鐘"
             , Text
"五分半"
             ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
90 Grain
Second)
              [ Text
"一分半鐘"
              , Text
"一分半"
              , Text
"分半鐘"
              , Text
"分半"
              ]
  , DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
15 Grain
Minute)
              [ Text
"3個字"
              , Text
"三個字"
              ]
  ]