-- 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.HE.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
HE 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
ILS Double
10)
             [ Text
"עשר שקל"
             , Text
"עשרה שקלים"
             , Text
"עשר ש״ח"
             , Text
"עשר שח"
             , Text
"10₪"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ILS Double
10000)
             [ Text
"עשר אלף שקל"
             , Text
"10000 שקלים"
             , Text
"10 אשח"
             , Text
"10 אש״ח"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ILS Double
10000000)
             [ Text
"10 מיליון שקלים"
             , Text
"10 משח"
             , Text
"10 מש״ח"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ILS Double
0.01)
             [ Text
"אגורה"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ILS Double
1)
             [ Text
"שקל"
             , Text
"שקל אחד"
             , Text
"שקל בודד"
             , Text
"100 אגורות"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ILS Double
0.05)
             [ Text
"חמש אגורות"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ILS Double
0)
             [ Text
"אפס ש״ח"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ILS Double
1.5)
             [ Text
"שקל וחצי"
             , Text
"1.5 ש״ח"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
ILS Double
2)
             [ Text
"שנקל"
             , Text
"2 שקל"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
10)
             [ Text
"$10"
             , Text
"10$"
             , Text
"עשר דולר"
             , Text
"עשרה דולר"
             , Text
"עשרה דולרים"
             , Text
"עשר דולרים"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
20)
             [ Text
"עשרים דולר"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Dollar Double
2.23)
             [ Text
"2 דולר ו23 סנט"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
EUR Double
20)
             [ Text
"20€"
             , Text
"20 יורו"
             , Text
"EUR 20"
             , Text
"20 אירו"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
EUR Double
29.99)
             [ Text
"29.99 יורו"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
Pound Double
9)
             [ Text
"£9"
             , Text
"תשע פאונד"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
GBP Double
1)
             [ Text
"לירה שטרלינג"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
GBP Double
10)
             [ Text
"10 לירות שטרלינג"
             ]
  , 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
"מעשר עד עשרים דולר"
             , 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
"פחות מ7 יורו"
             , Text
"עד 7 יורו"
             , Text
"לא יותר מ7 יורו"
             , Text
"מתחת ל7 יורו"
             , Text
"לא מעל 7 יורו"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
above Currency
Dollar Double
5)
             [ Text
"יותר מ5 דולר"
             , Text
"מעל 5 דולר"
             , Text
"מ5 דולר"
             , Text
"לא פחות מ5 דולר"
             , Text
"לא מתחת ל5 דולר"
             ]
    ]