{-# LANGUAGE OverloadedStrings #-}
module Duckling.Duration.HI.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
HI 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
15 Grain
Minute)
[ Text
"पंद्रह मिनट"
, Text
"लगभग पंद्रह मिनट"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
30 Grain
Minute)
[ Text
"आधा घंटा"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
1 Grain
Day)
[ Text
"दिवस"
, Text
"एक दिन"
, Text
"बिल्कुल एक दिन"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
14 Grain
Day)
[ Text
"पखवाड़ा"
, Text
"एक पखवाड़ा"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
1 Grain
Year)
[ Text
"एक साल"
, Text
"केवल एक वर्ष"
, Text
"लगभग एक साल"
, Text
"एक बरस"
, Text
"केवल एक साल"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
21 Grain
Month)
[ Text
"पौने 2 साल"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
105 Grain
Minute)
[ Text
"पौने 2 घंटा"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
27 Grain
Month)
[ Text
"सवा 2 साल"
, Text
"2 साल और 3 महीना"
, Text
"2 साल, 3 महीना"
, Text
"2 साल 3 महीना"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
135 Grain
Minute)
[ Text
"सवा 2 घंटा"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
42 Grain
Month)
[ Text
"साड़े 3 साल"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
210 Grain
Minute)
[ Text
"साड़े 3 घंटा"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
31719604 Grain
Second)
[ Text
"1 साल, 2 दिन, 3 घंटा और 4 सेकंड"
, Text
"1 साल 2 दिन 3 घंटा और 4 सेकंड"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
30 Grain
Month)
[ Text
"ढाई साल"
]
, DurationData -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Int -> Grain -> DurationData
DurationData Int
90 Grain
Minute)
[ Text
"डेढ़ घंटा"
]
]