-- 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.AmountOfMoney.NB.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
NB 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
"ti dollar"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Cent Double
10)
             [ Text
"ti øre"
             ]
  , 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
NOK Double
10)
             [ Text
"10kroner"
             , Text
"10kr"
             , Text
"ti kroner"
             , Text
"10 NOK"
             , Text
"ti norske kroner"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
SEK Double
10)
             [ Text
"10kronor"
             , Text
"10 svenske kroner"
             , Text
"10 svenske kr"
             , Text
"10 svenske kronor"
             , Text
"ti kronor"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
DKK Double
10)
             [ Text
"10 danske kroner"
             , Text
"ti danske kroner"
             , Text
"ti danske kr"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
AUD Double
10)
             [ Text
"10 australske dollar"
             , Text
"10 australske dollars"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
CAD Double
10)
             [ Text
"10 kanadiske dollar"
             , Text
"10 kanadiske dollars"
             , Text
"10 canadiske dollar"
             , Text
"10 canadiske dollars"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
CHF Double
10)
             [ Text
"10 sveitsiske franc"
             , Text
"10 sveitsiske francs"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
CNY Double
10)
             [ Text
"10 yuan"
             , Text
"10 kinesiske yuan"
             , Text
"10 kinesisk yuan"
             , Text
"10 renminbi"
             , Text
"10 kinesiske renminbi"
             , Text
"10 kinesisk renminbi"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
CZK Double
10)
             [ Text
"10 koruna"
             , Text
"10 tsjekkiske koruna"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
INR Double
10)
             [ Text
"10 rupi"
             , Text
"10 rupier"
             , Text
"10 rupee"
             , Text
"10 rupees"
             , Text
"10 indisk rupi"
             , Text
"10 indiske rupi"
             , Text
"10 indiske rupee"
             , Text
"10 indiske rupees"
             , Text
"10 indiske rupier"
             , Text
"10 indisk rupier"
             , Text
"ti rupi"
             , Text
"ti rupier"
             , Text
"ti indisk rupi"
             , Text
"ti indiske rupi"
             , Text
"ti indiske rupee"
             , Text
"ti indiske rupees"
             , Text
"ti indiske rupier"
             , Text
"ti indisk rupier"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
JPY Double
10)
             [ Text
"10 japanske yen"
             , Text
"10 yen"
             , Text
"ti japanske yen"
             , Text
"ti yen"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
PKR Double
10)
             [ Text
"10 pakistansk rupi"
             , Text
"10 pakistanske rupi"
             , Text
"10 pakistanske rupee"
             , Text
"10 pakistanske rupees"
             , Text
"10 pakistanske rupier"
             , Text
"10 pakistansk rupier"
             , Text
"ti pakistansk rupi"
             , Text
"ti pakistanske rupi"
             , Text
"ti pakistanske rupee"
             , Text
"ti pakistanske rupees"
             , Text
"ti pakistanske rupier"
             , Text
"ti pakistansk rupier"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
PLN Double
10)
             [ Text
"10 zloty"
             , Text
"10 sloty"
             , Text
"10 polske zloty"
             , Text
"10 polske sloty"
             , Text
"ti zloty"
             , Text
"ti sloty"
             , Text
"ti polske zloty"
             , Text
"ti polske sloty"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
SGD Double
10)
             [ Text
"10 singapore dollar"
             , Text
"10 singapore dollars"
             , Text
"10 singaporske dollar"
             , Text
"10 singaporske dollars"
             , Text
"ti singapore dollar"
             , Text
"ti singapore dollars"
             , Text
"ti singaporske dollar"
             , Text
"ti singaporske dollars"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
THB Double
10)
             [ Text
"10 bhat"
             , Text
"10 thai baht"
             , Text
"10 thai bhat"
             , Text
"10 thailand baht"
             , Text
"10 thailand bhat"
             , Text
"10 thailandske baht"
             , Text
"10 thailandske bhat"
             , Text
"ti baht"
             , Text
"ti bhat"
             , Text
"ti thai baht"
             , Text
"ti thai bhat"
             , Text
"ti thailand baht"
             , Text
"ti thailand bhat"
             , Text
"ti thailandske baht"
             , Text
"ti thailandske bhat"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ZAR Double
10)
             [ Text
"10 rand"
             , Text
"10 sørafrikanske rand"
             , Text
"10 sør-afrikanske rand"
             , Text
"10 rand"
             , Text
"10 sørafrikanske rand"
             , Text
"10 sør-afrikanske rand"
             , Text
"ti rand"
             , Text
"ti sørafrikanske rand"
             , Text
"ti sør-afrikanske rand"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
NOK Double
2.23)
             [ Text
"2 kroner og 23 øre"
             , Text
"to kroner 23 øre"
             , Text
"to kroner og 23 øre"
             , Text
"to kr 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
SEK Double
2.23)
             [ Text
"2 kronor og 23 öre"
             , Text
"to kronor 23 öre"
             , Text
"to svenske kronor 23 öre"
             , Text
"to svenske kroner 23 öre"
             , Text
"to svenske kroner 23 øre"
             , Text
"to kronor og 23 öre"
             , Text
"to svenske kronor og 23 öre"
             , Text
"to svenske kroner og 23 öre"
             , Text
"to svenske kroner og 23 øre"
             , Text
"to svensk kroner og 23 øre"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
DKK Double
2.23)
             [ Text
"2 danske kroner og 23 øre"
             , Text
"to danske kroner 23 øre"
             , Text
"to danske kroner og 23 øre"
             , Text
"to danske kr 23"
             , Text
"to dansk kr 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
USD Double
2.23)
             [ Text
"2 amerikanske dollar og 23 cent"
             , Text
"2 amerikanske dollars og 23 cent"
             , Text
"2 amerikanske dollar og 23 cents"
             , Text
"2 amerikanske dollars og 23 cents"
             , Text
"to amerikanske dollar 23 cent"
             , Text
"to amerikanske dollars 23 cent"
             , Text
"to amerikanske dollar 23 cents"
             , Text
"to amerikanske dollars 23 cents"
             , Text
"to amerikanske dollar og 23 cent"
             , Text
"to amerikanske dollars og 23 cent"
             , Text
"to amerikanske dollar og 23 cents"
             , Text
"to amerikanske dollars og 23 cents"
             , Text
"to amerikanske dollar 23"
             , Text
"to amerikanske dollars 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
AUD Double
2.23)
             [ Text
"2 australske dollar og 23 cent"
             , Text
"2 australske dollars og 23 cent"
             , Text
"2 australske dollar og 23 cents"
             , Text
"2 australske dollars og 23 cents"
             , Text
"to australske dollar 23 cent"
             , Text
"to australske dollars 23 cent"
             , Text
"to australske dollar 23 cents"
             , Text
"to australske dollars 23 cents"
             , Text
"to australske dollar og 23 cent"
             , Text
"to australske dollars og 23 cent"
             , Text
"to australske dollar og 23 cents"
             , Text
"to australske dollars og 23 cents"
             , Text
"to australske dollar 23"
             , Text
"to australske dollars 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
CAD Double
2.23)
             [ Text
"2 kanadiske dollar og 23 cent"
             , Text
"2 kanadiske dollars og 23 cent"
             , Text
"2 canadiske dollar og 23 cent"
             , Text
"2 canadiske dollars og 23 cent"
             , Text
"2 kanadiske dollar og 23 cents"
             , Text
"2 kanadiske dollars og 23 cents"
             , Text
"2 canadiske dollar og 23 cents"
             , Text
"2 canadiske dollars og 23 cents"
             , Text
"to kanadiske dollar 23 cent"
             , Text
"to kanadiske dollars 23 cent"
             , Text
"to canadiske dollar 23 cent"
             , Text
"to canadiske dollars 23 cent"
             , Text
"to kanadiske dollar 23 cents"
             , Text
"to kanadiske dollars 23 cents"
             , Text
"to canadiske dollar 23 cents"
             , Text
"to canadiske dollars 23 cents"
             , Text
"to kanadiske dollar og 23 cent"
             , Text
"to kanadiske dollars og 23 cent"
             , Text
"to canadiske dollar og 23 cent"
             , Text
"to canadiske dollars og 23 cent"
             , Text
"to kanadiske dollar og 23 cents"
             , Text
"to kanadiske dollars og 23 cents"
             , Text
"to canadiske dollar og 23 cents"
             , Text
"to canadiske dollars og 23 cents"
             , Text
"to kanadiske dollar 23"
             , Text
"to kanadiske dollars 23"
             , Text
"to canadiske dollar 23"
             , Text
"to canadiske dollars 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
CHF Double
2.23)
             [ Text
"2 sveitsiske franc og 23 rappen"
             , Text
"2 sveitsiske francs og 23 rappen"
             , Text
"2 sveitsiske franc og 23 rp"
             , Text
"2 sveitsiske francs og 23 rp"
             , Text
"2 sveitsiske franc og 23 centime"
             , Text
"2 sveitsiske francs og 23 centime"
             , Text
"2 sveitsiske franc og 23 c"
             , Text
"2 sveitsiske francs og 23 c"
             , Text
"2 sveitsiske franc og 23 centesimo"
             , Text
"2 sveitsiske francs og 23 centesimo"
             , Text
"2 sveitsiske franc og 23 ct"
             , Text
"2 sveitsiske francs og 23 ct"
             , Text
"2 sveitsiske franc og 23 rap"
             , Text
"2 sveitsiske francs og 23 rap"
             , Text
"to sveitsiske franc 23 rappen"
             , Text
"to sveitsiske francs 23 rappen"
             , Text
"to sveitsiske franc 23 rp"
             , Text
"to sveitsiske francs 23 rp"
             , Text
"to sveitsiske franc 23 centime"
             , Text
"to sveitsiske francs 23 centime"
             , Text
"to sveitsiske franc 23 c"
             , Text
"to sveitsiske francs 23 c"
             , Text
"to sveitsiske franc 23 centesimo"
             , Text
"to sveitsiske francs 23 centesimo"
             , Text
"to sveitsiske franc 23 ct"
             , Text
"to sveitsiske francs 23 ct"
             , Text
"to sveitsiske franc 23 rap"
             , Text
"to sveitsiske francs 23 rap"
             , Text
"to sveitsiske franc og 23 rappen"
             , Text
"to sveitsiske francs og 23 rappen"
             , Text
"to sveitsiske franc og 23 rp"
             , Text
"to sveitsiske francs og 23 rp"
             , Text
"to sveitsiske franc og 23 centime"
             , Text
"to sveitsiske francs og 23 centime"
             , Text
"to sveitsiske franc og 23 c"
             , Text
"to sveitsiske francs og 23 c"
             , Text
"to sveitsiske franc og 23 centesimo"
             , Text
"to sveitsiske francs og 23 centesimo"
             , Text
"to sveitsiske franc og 23 ct"
             , Text
"to sveitsiske francs og 23 ct"
             , Text
"to sveitsiske franc og 23 rap"
             , Text
"to sveitsiske francs og 23 rap"
             , Text
"to sveitsiske franc 23"
             , Text
"to sveitsiske francs 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
CNY Double
2.23)
             [ Text
"2 yuan og 23 fen"
             , Text
"2 kinesiske yuan og 23 fen"
             , Text
"2 renminbi og 23 fen"
             , Text
"2 kinesiske renminbi og 23 fen"
             , Text
"to yuan 23 fen"
             , Text
"to kinesiske yuan 23 fen"
             , Text
"to renminbi 23 fen"
             , Text
"to kinesiske renminbi 23 fen"
             , Text
"to yuan og 23 fen"
             , Text
"to kinesiske yuan og 23 fen"
             , Text
"to renminbi og 23 fen"
             , Text
"to kinesiske renminbi og 23 fen"
             , Text
"to yuan 23"
             , Text
"to kinesiske yuan 23"
             , Text
"to renminbi 23"
             , Text
"to kinesiske renminbi 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
CZK Double
2.23)
             [ Text
"2 koruna og 23 haleru"
             , Text
"2 tsjekkiske koruna og 23 haleru"
             , Text
"to koruna 23 haleru"
             , Text
"to tsjekkiske koruna 23 haleru"
             , Text
"to koruna og 23 haleru"
             , Text
"to tsjekkiske koruna og 23 haleru"
             , Text
"to koruna 23"
             , Text
"to tsjekkiske koruna 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
HKD Double
2.23)
             [ Text
"2 hong kong dollar og 23 cent"
             , Text
"2 hong kong dollar og 23 cents"
             , Text
"2 hong kong dollars og 23 cent"
             , Text
"2 hong kong dollars og 23 cents"
             , Text
"2 hong kong dollar og 23 cents"
             , Text
"2 hong kong dollars og 23 cents"
             , Text
"to hong kong dollar 23 cent"
             , Text
"to hong kong dollars 23 cent"
             , Text
"to hong kong dollar 23 cents"
             , Text
"to hong kong dollars 23 cents"
             , Text
"to hong kong dollar og 23 cent"
             , Text
"to hong kong dollars og 23 cent"
             , Text
"to hong kong dollar og 23 cents"
             , Text
"to hong kong dollars og 23 cents"
             , Text
"to hong kong dollar 23"
             , Text
"to hong kong dollars 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
INR Double
2.23)
             [ Text
"2 indiske rupi og 23 paise"
             , Text
"2 indiske rupier og 23 paise"
             , Text
"to indiske rupi 23 paise"
             , Text
"to indiske rupier 23 paise"
             , Text
"to indiske rupier 23 paise"
             , Text
"to indiske rupi og 23 paise"
             , Text
"to indiske rupier og 23 paise"
             , Text
"to indiske rupi 23"
             , Text
"to indiske rupier 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
NZD Double
2.23)
             [ Text
"2 new zealand dollar og 23 cent"
             , Text
"2 new zealand dollars og 23 cent"
             , Text
"2 new zealand dollars og 23 cents"
             , Text
"2 new zealandske dollar og 23 cent"
             , Text
"2 new zealandske dollars og 23 cent"
             , Text
"2 new zealandske dollars og 23 cents"
             , Text
"2 new zealand dollar og 23 cents"
             , Text
"2 new zealand dollars og 23 cents"
             , Text
"2 nz dollar og 23 cents"
             , Text
"2 nz dollars og 23 cents"
             , Text
"to new zealand dollar 23 cent"
             , Text
"to new zealand dollars 23 cent"
             , Text
"to new zealand dollars 23 cents"
             , Text
"to new zealandske dollar 23 cent"
             , Text
"to new zealandske dollars 23 cent"
             , Text
"to new zealandske dollars 23 cents"
             , Text
"to new zealand dollar 23 cents"
             , Text
"to new zealand dollars 23 cents"
             , Text
"to new zealand dollars 23 cent"
             , Text
"to new zealand dollar og 23 cent"
             , Text
"to new zealand dollars og 23 cent"
             , Text
"to new zealandske dollar og 23 cent"
             , Text
"to new zealandske dollars og 23 cent"
             , Text
"to new zealandske dollars og 23 cents"
             , Text
"to new zealand dollar og 23 cents"
             , Text
"to new zealand dollars og 23 cent"
             , Text
"to new zealand dollars og 23 cents"
             , Text
"to new zealand dollar 23"
             , Text
"to new zealand dollars 23"
             , Text
"to new zealandske dollar 23"
             , Text
"to new zealandske dollars 23"
             , Text
"to nz dollar 23"
             , Text
"to nz dollars 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
PLN Double
2.23)
             [ Text
"2 zloty og 23 groszy"
             , Text
"2 sloty og 23 groszy"
             , Text
"2 polske zloty og 23 groszy"
             , Text
"2 polske sloty og 23 groszy"
             , Text
"to zloty 23 groszy"
             , Text
"to sloty 23 groszy"
             , Text
"to polske zloty 23 groszy"
             , Text
"to polske sloty 23 groszy"
             , Text
"to zloty og 23 groszy"
             , Text
"to sloty og 23 groszy"
             , Text
"to polske zloty og 23 groszy"
             , Text
"to polske sloty og 23 groszy"
             , Text
"to zloty 23"
             , Text
"to sloty 23"
             , Text
"to polske zloty 23"
             , Text
"to polske sloty 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
SGD Double
2.23)
             [ Text
"2 singapore dollar og 23 cent"
             , Text
"2 singapore dollars og 23 cent"
             , Text
"2 singaporske dollar og 23 cent"
             , Text
"2 singaporske dollars og 23 cent"
             , Text
"2 singapore dollar og 23 cents"
             , Text
"2 singapore dollars og 23 cents"
             , Text
"to singapore dollar 23 cent"
             , Text
"to singapore dollars 23 cent"
             , Text
"to singaporske dollar 23 cent"
             , Text
"to singaporske dollars 23 cent"
             , Text
"to singapore dollar 23 cents"
             , Text
"to singapore dollars 23 cents"
             , Text
"to singapore dollar og 23 cent"
             , Text
"to singapore dollars og 23 cent"
             , Text
"to singaporske dollar og 23 cent"
             , Text
"to singaporske dollars og 23 cent"
             , Text
"to singapore dollar og 23 cents"
             , Text
"to singapore dollars og 23 cents"
             , Text
"to singapore dollar 23"
             , Text
"to singapore dollars 23"
             , Text
"to singaporske dollar 23"
             , Text
"to singaporske dollars 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ZAR Double
2.23)
             [ Text
"2 rand og 23 cent"
             , Text
"2 sørafrikanske rand og 23 cent"
             , Text
"2 sørafrikanske rand og 23 cents"
             , Text
"2 sør-afrikanske rand og 23 cent"
             , Text
"2 sør-afrikanske rand og 23 cents"
             , Text
"to rand 23 cent"
             , Text
"to sørafrikanske rand 23 cent"
             , Text
"to sørafrikanske rand 23 cents"
             , Text
"to sør-afrikanske rand 23 cent"
             , Text
"to sør-afrikanske rand 23 cents"
             , Text
"to rand og 23 cent"
             , Text
"to sørafrikanske rand og 23 cent"
             , Text
"to sørafrikanske rand og 23 cents"
             , Text
"to sør-afrikanske rand og 23 cent"
             , Text
"to sør-afrikanske rand og 23 cents"
             , Text
"to rand 23"
             , Text
"to sørafrikanske rand 23"
             , Text
"to sør-afrikanske rand 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
THB Double
2.23)
             [ Text
"2 baht og 23 satang"
             , Text
"2 bhat og 23 satang"
             , Text
"2 thai baht og 23 satang"
             , Text
"2 thai bhat og 23 satang"
             , Text
"2 thailandske baht og 23 satang"
             , Text
"2 thailandske bhat og 23 satang"
             , Text
"to baht 23 satang"
             , Text
"to bhat 23 satang"
             , Text
"to thai baht 23 satang"
             , Text
"to thai bhat 23 satang"
             , Text
"to thailandske baht 23 satang"
             , Text
"to thailandske bhat 23 satang"
             , Text
"to baht og 23 satang"
             , Text
"to bhat og 23 satang"
             , Text
"to thai baht og 23 satang"
             , Text
"to thai bhat og 23 satang"
             , Text
"to thailandske baht og 23 satang"
             , Text
"to thailandske bhat og 23 satang"
             , Text
"to baht 23"
             , Text
"to bhat 23"
             , Text
"to thai baht 23"
             , Text
"to thai bhat 23"
             , Text
"to thailandske baht 23"
             , Text
"to thailandske bhat 23"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Cent Double
10)
             [ Text
"ti cent"
             , Text
"ti cents"
             , Text
"ti pence"
             , Text
"ti penny"
             , Text
"ti pennies"
             , Text
"10 cent"
             , Text
"10 cents"
             , Text
"10 cents"
             , Text
"10 pence"
             , Text
"10 penny"
             , Text
"10 øre"
             , Text
"10 ører"
             , Text
"10 öre"
             , Text
"10 örer"
             , Text
"10 p"
             , Text
"10 c"
             , Text
"10 fen"
             , Text
"10 haleru"
             , Text
"10 groszy"
             , Text
"10 paise"
             , Text
"10 paisa"
             , Text
"10 centesimo"
             , Text
"10 centesimi"
             , Text
"10 centime"
             , Text
"10 centimes"
             , Text
"10 ct"
             , Text
"10 rap"
             , Text
"10 rappen"
             , Text
"10 rappens"
             , Text
"10 rp"
             , Text
"10 satang"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
EUR Double
20)
             [ Text
"20€"
             , Text
"20 euro"
             , 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"
             , Text
"INR20"
             ]
  , 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
"tjue rupees 43"
             , Text
"tjue rupees 43¢"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Pound Double
9)
             [ Text
"£9"
             , Text
"ni pund"
             ]
  , 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"
             ]
  ]