{-# LANGUAGE OverloadedStrings #-}
module Duckling.AmountOfMoney.VI.Corpus
( corpus
) where
import Data.String
import Prelude
import Duckling.AmountOfMoney.Types
import Duckling.Locale
import Duckling.Resolve
import Duckling.Testing.Types
corpus :: Corpus
corpus :: Corpus
corpus = (Context
testContext {locale :: Locale
locale = Lang -> Maybe Region -> Locale
makeLocale Lang
VI 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
[ AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
10)
[ Text
"$10"
, Text
"10$"
, Text
"mười đô"
, Text
"mười đô la"
, Text
"mười đô mỹ"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Cent Double
10)
[ Text
"mười xen"
, Text
"mười xu"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
10000)
[ Text
"$10.000"
, Text
"10K$"
, Text
"$10k"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
USD Double
1.23)
[ Text
"USD1,23"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
2.23)
[ Text
"2 đô la và 23 xen"
, Text
"hai đô la và 23 xen"
, Text
"2 đô 23 xu"
, Text
"hai đô 23"
, Text
"2 chấm 23 đô la"
, Text
"hai phẩy 23 đô"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
VND Double
10)
[ Text
"mười đồng"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
VND Double
10000)
[ Text
"10.000 đồng"
, Text
"10K đồng"
, Text
"10k đồng"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
VND Double
1000)
[ Text
"1000 VNĐ"
, Text
"VN$1000"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
EUR Double
20)
[ Text
"20€"
, Text
"20 euros"
, Text
"20 Euro"
, Text
"20 Euros"
, Text
"EUR 20"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
EUR Double
29.99)
[ Text
"EUR29,99"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
INR Double
20)
[ Text
"Rs. 20"
, Text
"Rs 20"
, Text
"20 Rupees"
, Text
"20Rs"
, Text
"Rs20"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
INR Double
20.43)
[ Text
"20 Rupees 43"
, Text
"hai mươi rupees 43"
, Text
"hai mươi rupees 43 xen"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
INR Double
33)
[ Text
"INR33"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Pound Double
9)
[ Text
"£9"
, Text
"chín pounds"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
GBP Double
3.01)
[ Text
"GBP3,01"
, Text
"GBP 3,01"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
AED Double
1)
[ Text
"1 AED."
, Text
"1 dirham"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> (Double, Double) -> AmountOfMoneyValue
between Currency
VND (Double
1000, Double
2000))
[ Text
"giữa 1000 và 2000 đồng"
, Text
"giữa 1000 đồng và 2000 đồng"
, Text
"từ 1000 đồng đến 2000 đồng"
, Text
"từ 1000 VNĐ tới 2000 VNĐ"
, Text
"từ 1000 đến 2000 đồng"
, Text
"khoảng 1000-2000 đồng"
, Text
"khoảng chừng từ 1000 đến 2000 đồng"
, Text
"tầm khoảng 1000 tới 2000 đồng"
, Text
"xấp xỉ VND1000-VND2000"
, Text
"1000-2000 đồng"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> (Double, Double) -> AmountOfMoneyValue
between Currency
Dollar (Double
1.1, Double
1.3))
[ Text
"giữa 1,1 và 1,3 đô la"
, Text
"từ 1 phẩy 1 đến một chấm ba đô la"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
under Currency
VND Double
7000)
[ Text
"dưới bảy ngàn đồng"
, Text
"ít hơn bảy nghìn đồng"
, Text
"kém hơn 7k đồng"
, Text
"không tới 7000 đồng"
, Text
"không cao hơn 7000 đồng"
, Text
"không hơn 7.000 đồng"
, Text
"không quá 7.000 đồng"
, Text
"từ 7000 đồng trở xuống"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
above Currency
Dollar Double
1.42)
[ Text
"nhiều hơn 1 đô la và bốn mươi hai xen"
, Text
"ít nhất $1,42"
, Text
"hơn 1,42 đô la"
, Text
"trên một đô la và 42 xu"
, Text
"không ít hơn 1,42 đô la"
, Text
"cao hơn $1,42"
, Text
"từ $1,42 trở lên"
]
]