{-# LANGUAGE OverloadedStrings #-}
module Duckling.AmountOfMoney.KO.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
KO 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
"십달러"
             , Text
"십불"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Cent Double
10)
             [ Text
"십센트"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
10000)
             [ Text
"만달러"
             , Text
"만불"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
1.23)
             [ Text
"일점이삼달러"
             , Text
"일쩜이삼달러"
             , Text
"일점이삼불"
             , Text
"일쩜이삼불"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
2.23)
             [ Text
"이달러이십삼센트"
             , Text
"이불이십삼센트"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
EUR Double
20)
             [ Text
"이십유로"
             , Text
"EUR 20"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
EUR Double
29.99)
             [ Text
"이십구점구구유로"
             , Text
"EUR29.99"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Pound Double
9)
             [ Text
"구파운드"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
KRW Double
27350000)
             [ Text
"이천칠백삼십오만원"
             , Text
"27,350,000원"
             , Text
"27350000원"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
KRW Double
27000)
             [ Text
"이만칠천원"
             , Text
"27,000원"
             , Text
"27000원"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
KRW Double
100)
             [ Text
"백원"
             , Text
"100원"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
KRW Double
10)
             [ Text
"십원"
             , Text
"10원"
             , Text
"10₩"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> (Double, Double) -> AmountOfMoneyValue
between Currency
KRW (Double
25000, Double
30000))
             [ Text
"25000 - 30000원"
             , Text
"25000원 - 30000원"
             , Text
"이만오천원 - 삼만원"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
above Currency
KRW Double
5000)
             [ Text
"5000원 이상"
             , Text
"5000원 초과"
             , Text
"오천원 이상"
             , Text
"오천원 초과"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
under Currency
KRW Double
10000)
             [ Text
"10000원 이하"
             , Text
"10000원 미만"
             , Text
"만원 이하"
             , Text
"만원 미만"
             ]
  , 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
"십달러 - 이십달러"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
above Currency
Dollar Double
10)
             [ Text
"10달러 이상"
             , Text
"10달러 초과"
             , Text
"십달러 이상"
             , Text
"십달러 초과"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
under Currency
Dollar Double
10)
             [ Text
"10달러 이하"
             , Text
"10달러 미만"
             , Text
"십달러 이하"
             , Text
"십달러 미만"
             ]
  ]