{-# LANGUAGE OverloadedStrings #-}
module Duckling.AmountOfMoney.BG.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
BG 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
BGN Double
1)
[ Text
"1 лв"
, Text
"един лев"
, Text
"1 Лев"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
BGN Double
10)
[ Text
"10 лв"
, Text
"десет лева"
, Text
"10лв"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
BGN Double
15.50)
[ Text
"15лв и 50ст"
, Text
"петнадесет лева и петдесет стотинки"
, Text
"15 Лв и 50 Ст"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
1)
[ Text
"$1"
, Text
"един долар"
, Text
"1 долар"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
10)
[ Text
"$10"
, Text
"$ 10"
, Text
"10$"
, Text
"10 Долара"
, Text
"десет долара"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Cent Double
10)
[ Text
"10 цента"
, Text
"десет пенита"
, Text
"десет цента"
, Text
"10¢"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Cent Double
50)
[ Text
"50 ст"
, Text
"петдесет стотинки"
, Text
"50ст"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
1e4)
[ Text
"$10К"
, Text
"10к$"
, Text
"$10,000"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
USD Double
3.14)
[ Text
"USD3.14"
, Text
"3.14US$"
, Text
"US$ 3.14"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
EUR Double
20)
[ Text
"20\x20ac"
, Text
"20 евро"
, Text
"20 Евро"
, Text
"EUR 20"
, Text
"EUR 20.0"
, Text
"20€"
, Text
"20 €ur"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Pound Double
10)
[ Text
"\x00a3\&10"
, Text
"десет паунда"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
20.43)
[ Text
"$20 и 43ц"
, Text
"$20 43"
, Text
"20 долара 43ц"
, Text
"20 долара 43 цента"
, Text
"двадесет долара 43 цента"
, Text
"20 долара 43"
, Text
"двадесет долара и 43"
]
, 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"
, Text
"3 GBP 1 пени"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> (Double, Double) -> AmountOfMoneyValue
between Currency
Dollar (Double
10, Double
20))
[ Text
"между 10 и 20 долара"
, Text
"от 10 до 20 долара"
, Text
"около 10-20 долара"
, Text
"между 10 и 20 долара"
, Text
"около $10-$20"
, Text
"10-20 долара"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
under Currency
EUR Double
7)
[ Text
"под седем евро"
, Text
"по-малко от 7 Евро"
, Text
"под 7€"
]
, AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
above Currency
Dollar Double
1.42)
[ Text
"над 1 долар и четиридесет и два цента"
, Text
"поне $1.42"
, Text
"над 1.42 долара"
]
]