-- 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.EN.JM.Corpus
  ( allExamples
  , negativeExamples
  ) where

import Data.String
import Data.Text (Text)
import Prelude

import Duckling.AmountOfMoney.Types
import Duckling.Testing.Types

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
JMD Double
1000)
             [ Text
"a grand"
             , Text
"1 grand"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
JMD Double
10000)
             [ Text
"10 grand"
             , Text
"two hundred thousand nickels"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
JMD Double
1)
             [ Text
"four quarters"
             , Text
"ten dimes"
             , Text
"twenty nickels"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
JMD Double
0.1)
             [ Text
"dime"
             , Text
"a dime"
             , Text
"two nickels"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
JMD Double
0.25)
             [ Text
"quarter"
             , Text
"a quarter"
             , Text
"five nickels"
             ]
  , AmountOfMoneyValue -> [Text] -> [Example]
forall a. ToJSON a => a -> [Text] -> [Example]
examples (Currency -> Double -> AmountOfMoneyValue
simple Currency
JMD Double
0.05)
             [ Text
"nickel"
             , Text
"a nickel"
             ]
  ]
negativeExamples :: [Text]
negativeExamples :: [Text]
negativeExamples =
  [ Text
"grand"
  ]