{-# LANGUAGE CPP                 #-}
{-# LANGUAGE DeriveFoldable      #-}
{-# LANGUAGE DeriveFunctor       #-}
{-# LANGUAGE DeriveTraversable   #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE RankNTypes          #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell     #-}
module Network.API.Mandrill.Types where

import           Control.Applicative
import           Control.Monad                 (mzero)
import           Data.Char
import           Data.Maybe
import           Data.Time
import           Lens.Micro.TH (makeLenses)
import           Network.API.Mandrill.Utils
import           Test.QuickCheck
import           Text.Email.Validate
#if MIN_VERSION_time(1,5,0)
import           Data.Time.Format              (TimeLocale, defaultTimeLocale)
#else
import           System.Locale                 (TimeLocale, defaultTimeLocale)
#endif
import           Data.Aeson
import           Data.Aeson.TH
import           Data.Aeson.Types
import qualified Data.ByteString               as B
import qualified Data.ByteString.Base64        as Base64
#if !MIN_VERSION_base(4,8,0)
import           Data.Foldable
import           Data.Traversable
#endif
import qualified Data.HashMap.Strict           as H
import           Data.Monoid
import qualified Data.Text                     as T
import qualified Data.Text.Encoding            as TL
import qualified Data.Text.Lazy                as TL
import qualified Text.Blaze.Html               as Blaze
import qualified Text.Blaze.Html.Renderer.Text as Blaze
import qualified Text.Email.Validate           as TEV

timeParse :: ParseTime t => TimeLocale -> String -> String -> Maybe t
#if MIN_VERSION_time(1,5,0)
timeParse :: TimeLocale -> String -> String -> Maybe t
timeParse = Bool -> TimeLocale -> String -> String -> Maybe t
forall (m :: * -> *) t.
(MonadFail m, ParseTime t) =>
Bool -> TimeLocale -> String -> String -> m t
parseTimeM Bool
True
#else
timeParse = parseTime
#endif

--------------------------------------------------------------------------------
data MandrillError = MandrillError {
    MandrillError -> Text
_merr_status  :: !T.Text
  , MandrillError -> Int
_merr_code    :: !Int
  , MandrillError -> Text
_merr_name    :: !T.Text
  , MandrillError -> Text
_merr_message :: !T.Text
  } deriving (Int -> MandrillError -> ShowS
[MandrillError] -> ShowS
MandrillError -> String
(Int -> MandrillError -> ShowS)
-> (MandrillError -> String)
-> ([MandrillError] -> ShowS)
-> Show MandrillError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillError] -> ShowS
$cshowList :: [MandrillError] -> ShowS
show :: MandrillError -> String
$cshow :: MandrillError -> String
showsPrec :: Int -> MandrillError -> ShowS
$cshowsPrec :: Int -> MandrillError -> ShowS
Show, MandrillError -> MandrillError -> Bool
(MandrillError -> MandrillError -> Bool)
-> (MandrillError -> MandrillError -> Bool) -> Eq MandrillError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MandrillError -> MandrillError -> Bool
$c/= :: MandrillError -> MandrillError -> Bool
== :: MandrillError -> MandrillError -> Bool
$c== :: MandrillError -> MandrillError -> Bool
Eq)

makeLenses ''MandrillError
deriveJSON defaultOptions { fieldLabelModifier = drop 6 } ''MandrillError


--------------------------------------------------------------------------------
data MandrillEmailStatus = ES_Sent
                         | ES_Queued
                         | ES_Scheduled
                         | ES_Rejected
                         | ES_Invalid deriving Int -> MandrillEmailStatus -> ShowS
[MandrillEmailStatus] -> ShowS
MandrillEmailStatus -> String
(Int -> MandrillEmailStatus -> ShowS)
-> (MandrillEmailStatus -> String)
-> ([MandrillEmailStatus] -> ShowS)
-> Show MandrillEmailStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillEmailStatus] -> ShowS
$cshowList :: [MandrillEmailStatus] -> ShowS
show :: MandrillEmailStatus -> String
$cshow :: MandrillEmailStatus -> String
showsPrec :: Int -> MandrillEmailStatus -> ShowS
$cshowsPrec :: Int -> MandrillEmailStatus -> ShowS
Show

deriveJSON defaultOptions { constructorTagModifier = map toLower . drop 3 } ''MandrillEmailStatus


--------------------------------------------------------------------------------
data MandrillRejectReason = RR_HardBounce
                          | RR_SoftBounce
                          | RR_Spam
                          | RR_Unsub
                          | RR_Custom
                          | RR_InvalidSender
                          | RR_Invalid
                          | RR_TestModeLimit
                          | RR_Unsigned
                          | RR_Rule deriving Int -> MandrillRejectReason -> ShowS
[MandrillRejectReason] -> ShowS
MandrillRejectReason -> String
(Int -> MandrillRejectReason -> ShowS)
-> (MandrillRejectReason -> String)
-> ([MandrillRejectReason] -> ShowS)
-> Show MandrillRejectReason
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillRejectReason] -> ShowS
$cshowList :: [MandrillRejectReason] -> ShowS
show :: MandrillRejectReason -> String
$cshow :: MandrillRejectReason -> String
showsPrec :: Int -> MandrillRejectReason -> ShowS
$cshowsPrec :: Int -> MandrillRejectReason -> ShowS
Show

deriveJSON defaultOptions {
  constructorTagModifier = modRejectReason . drop 3
  } ''MandrillRejectReason


--------------------------------------------------------------------------------
-- | The main datatypes which models the response from the Mandrill API,
-- which can be either a success or a failure.
data MandrillResponse k =
    MandrillSuccess k
  | MandrillFailure MandrillError deriving (Int -> MandrillResponse k -> ShowS
[MandrillResponse k] -> ShowS
MandrillResponse k -> String
(Int -> MandrillResponse k -> ShowS)
-> (MandrillResponse k -> String)
-> ([MandrillResponse k] -> ShowS)
-> Show (MandrillResponse k)
forall k. Show k => Int -> MandrillResponse k -> ShowS
forall k. Show k => [MandrillResponse k] -> ShowS
forall k. Show k => MandrillResponse k -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillResponse k] -> ShowS
$cshowList :: forall k. Show k => [MandrillResponse k] -> ShowS
show :: MandrillResponse k -> String
$cshow :: forall k. Show k => MandrillResponse k -> String
showsPrec :: Int -> MandrillResponse k -> ShowS
$cshowsPrec :: forall k. Show k => Int -> MandrillResponse k -> ShowS
Show, MandrillResponse k -> MandrillResponse k -> Bool
(MandrillResponse k -> MandrillResponse k -> Bool)
-> (MandrillResponse k -> MandrillResponse k -> Bool)
-> Eq (MandrillResponse k)
forall k. Eq k => MandrillResponse k -> MandrillResponse k -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MandrillResponse k -> MandrillResponse k -> Bool
$c/= :: forall k. Eq k => MandrillResponse k -> MandrillResponse k -> Bool
== :: MandrillResponse k -> MandrillResponse k -> Bool
$c== :: forall k. Eq k => MandrillResponse k -> MandrillResponse k -> Bool
Eq, a -> MandrillResponse b -> MandrillResponse a
(a -> b) -> MandrillResponse a -> MandrillResponse b
(forall a b. (a -> b) -> MandrillResponse a -> MandrillResponse b)
-> (forall a b. a -> MandrillResponse b -> MandrillResponse a)
-> Functor MandrillResponse
forall a b. a -> MandrillResponse b -> MandrillResponse a
forall a b. (a -> b) -> MandrillResponse a -> MandrillResponse b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> MandrillResponse b -> MandrillResponse a
$c<$ :: forall a b. a -> MandrillResponse b -> MandrillResponse a
fmap :: (a -> b) -> MandrillResponse a -> MandrillResponse b
$cfmap :: forall a b. (a -> b) -> MandrillResponse a -> MandrillResponse b
Functor, MandrillResponse a -> Bool
(a -> m) -> MandrillResponse a -> m
(a -> b -> b) -> b -> MandrillResponse a -> b
(forall m. Monoid m => MandrillResponse m -> m)
-> (forall m a. Monoid m => (a -> m) -> MandrillResponse a -> m)
-> (forall m a. Monoid m => (a -> m) -> MandrillResponse a -> m)
-> (forall a b. (a -> b -> b) -> b -> MandrillResponse a -> b)
-> (forall a b. (a -> b -> b) -> b -> MandrillResponse a -> b)
-> (forall b a. (b -> a -> b) -> b -> MandrillResponse a -> b)
-> (forall b a. (b -> a -> b) -> b -> MandrillResponse a -> b)
-> (forall a. (a -> a -> a) -> MandrillResponse a -> a)
-> (forall a. (a -> a -> a) -> MandrillResponse a -> a)
-> (forall a. MandrillResponse a -> [a])
-> (forall a. MandrillResponse a -> Bool)
-> (forall a. MandrillResponse a -> Int)
-> (forall a. Eq a => a -> MandrillResponse a -> Bool)
-> (forall a. Ord a => MandrillResponse a -> a)
-> (forall a. Ord a => MandrillResponse a -> a)
-> (forall a. Num a => MandrillResponse a -> a)
-> (forall a. Num a => MandrillResponse a -> a)
-> Foldable MandrillResponse
forall a. Eq a => a -> MandrillResponse a -> Bool
forall a. Num a => MandrillResponse a -> a
forall a. Ord a => MandrillResponse a -> a
forall m. Monoid m => MandrillResponse m -> m
forall a. MandrillResponse a -> Bool
forall a. MandrillResponse a -> Int
forall a. MandrillResponse a -> [a]
forall a. (a -> a -> a) -> MandrillResponse a -> a
forall m a. Monoid m => (a -> m) -> MandrillResponse a -> m
forall b a. (b -> a -> b) -> b -> MandrillResponse a -> b
forall a b. (a -> b -> b) -> b -> MandrillResponse a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: MandrillResponse a -> a
$cproduct :: forall a. Num a => MandrillResponse a -> a
sum :: MandrillResponse a -> a
$csum :: forall a. Num a => MandrillResponse a -> a
minimum :: MandrillResponse a -> a
$cminimum :: forall a. Ord a => MandrillResponse a -> a
maximum :: MandrillResponse a -> a
$cmaximum :: forall a. Ord a => MandrillResponse a -> a
elem :: a -> MandrillResponse a -> Bool
$celem :: forall a. Eq a => a -> MandrillResponse a -> Bool
length :: MandrillResponse a -> Int
$clength :: forall a. MandrillResponse a -> Int
null :: MandrillResponse a -> Bool
$cnull :: forall a. MandrillResponse a -> Bool
toList :: MandrillResponse a -> [a]
$ctoList :: forall a. MandrillResponse a -> [a]
foldl1 :: (a -> a -> a) -> MandrillResponse a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> MandrillResponse a -> a
foldr1 :: (a -> a -> a) -> MandrillResponse a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> MandrillResponse a -> a
foldl' :: (b -> a -> b) -> b -> MandrillResponse a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> MandrillResponse a -> b
foldl :: (b -> a -> b) -> b -> MandrillResponse a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> MandrillResponse a -> b
foldr' :: (a -> b -> b) -> b -> MandrillResponse a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> MandrillResponse a -> b
foldr :: (a -> b -> b) -> b -> MandrillResponse a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> MandrillResponse a -> b
foldMap' :: (a -> m) -> MandrillResponse a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> MandrillResponse a -> m
foldMap :: (a -> m) -> MandrillResponse a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> MandrillResponse a -> m
fold :: MandrillResponse m -> m
$cfold :: forall m. Monoid m => MandrillResponse m -> m
Foldable, Functor MandrillResponse
Foldable MandrillResponse
Functor MandrillResponse
-> Foldable MandrillResponse
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> MandrillResponse a -> f (MandrillResponse b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    MandrillResponse (f a) -> f (MandrillResponse a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> MandrillResponse a -> m (MandrillResponse b))
-> (forall (m :: * -> *) a.
    Monad m =>
    MandrillResponse (m a) -> m (MandrillResponse a))
-> Traversable MandrillResponse
(a -> f b) -> MandrillResponse a -> f (MandrillResponse b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
MandrillResponse (m a) -> m (MandrillResponse a)
forall (f :: * -> *) a.
Applicative f =>
MandrillResponse (f a) -> f (MandrillResponse a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MandrillResponse a -> m (MandrillResponse b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MandrillResponse a -> f (MandrillResponse b)
sequence :: MandrillResponse (m a) -> m (MandrillResponse a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
MandrillResponse (m a) -> m (MandrillResponse a)
mapM :: (a -> m b) -> MandrillResponse a -> m (MandrillResponse b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MandrillResponse a -> m (MandrillResponse b)
sequenceA :: MandrillResponse (f a) -> f (MandrillResponse a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
MandrillResponse (f a) -> f (MandrillResponse a)
traverse :: (a -> f b) -> MandrillResponse a -> f (MandrillResponse b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MandrillResponse a -> f (MandrillResponse b)
$cp2Traversable :: Foldable MandrillResponse
$cp1Traversable :: Functor MandrillResponse
Traversable)

instance FromJSON k => FromJSON (MandrillResponse k) where
  parseJSON :: Value -> Parser (MandrillResponse k)
parseJSON Value
v = case ((Value -> Parser k) -> Value -> Maybe k
forall a b. (a -> Parser b) -> a -> Maybe b
parseMaybe Value -> Parser k
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v) :: Maybe k of
    Just k
r -> MandrillResponse k -> Parser (MandrillResponse k)
forall (m :: * -> *) a. Monad m => a -> m a
return (MandrillResponse k -> Parser (MandrillResponse k))
-> MandrillResponse k -> Parser (MandrillResponse k)
forall a b. (a -> b) -> a -> b
$ k -> MandrillResponse k
forall k. k -> MandrillResponse k
MandrillSuccess k
r
    Maybe k
Nothing -> do
    -- try to parse it as an error
      case ((Value -> Parser MandrillError) -> Value -> Maybe MandrillError
forall a b. (a -> Parser b) -> a -> Maybe b
parseMaybe Value -> Parser MandrillError
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v) :: Maybe MandrillError of
        Just MandrillError
e -> MandrillResponse k -> Parser (MandrillResponse k)
forall (m :: * -> *) a. Monad m => a -> m a
return (MandrillResponse k -> Parser (MandrillResponse k))
-> MandrillResponse k -> Parser (MandrillResponse k)
forall a b. (a -> b) -> a -> b
$ MandrillError -> MandrillResponse k
forall k. MandrillError -> MandrillResponse k
MandrillFailure MandrillError
e
        Maybe MandrillError
Nothing -> String -> Parser (MandrillResponse k)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser (MandrillResponse k))
-> String -> Parser (MandrillResponse k)
forall a b. (a -> b) -> a -> b
$ Value -> String
forall a. Show a => a -> String
show Value
v String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" is neither a MandrillSuccess or a MandrillError."


--------------------------------------------------------------------------------
data MandrillRecipientTag = To | Cc | Bcc deriving Int -> MandrillRecipientTag -> ShowS
[MandrillRecipientTag] -> ShowS
MandrillRecipientTag -> String
(Int -> MandrillRecipientTag -> ShowS)
-> (MandrillRecipientTag -> String)
-> ([MandrillRecipientTag] -> ShowS)
-> Show MandrillRecipientTag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillRecipientTag] -> ShowS
$cshowList :: [MandrillRecipientTag] -> ShowS
show :: MandrillRecipientTag -> String
$cshow :: MandrillRecipientTag -> String
showsPrec :: Int -> MandrillRecipientTag -> ShowS
$cshowsPrec :: Int -> MandrillRecipientTag -> ShowS
Show

deriveJSON defaultOptions { constructorTagModifier = map toLower } ''MandrillRecipientTag


--------------------------------------------------------------------------------
newtype MandrillEmail = MandrillEmail EmailAddress deriving Int -> MandrillEmail -> ShowS
[MandrillEmail] -> ShowS
MandrillEmail -> String
(Int -> MandrillEmail -> ShowS)
-> (MandrillEmail -> String)
-> ([MandrillEmail] -> ShowS)
-> Show MandrillEmail
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillEmail] -> ShowS
$cshowList :: [MandrillEmail] -> ShowS
show :: MandrillEmail -> String
$cshow :: MandrillEmail -> String
showsPrec :: Int -> MandrillEmail -> ShowS
$cshowsPrec :: Int -> MandrillEmail -> ShowS
Show

instance ToJSON MandrillEmail where
  toJSON :: MandrillEmail -> Value
toJSON (MandrillEmail EmailAddress
e) = Text -> Value
String (Text -> Value) -> (EmailAddress -> Text) -> EmailAddress -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
TL.decodeUtf8 (ByteString -> Text)
-> (EmailAddress -> ByteString) -> EmailAddress -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EmailAddress -> ByteString
toByteString (EmailAddress -> Value) -> EmailAddress -> Value
forall a b. (a -> b) -> a -> b
$ EmailAddress
e

instance FromJSON MandrillEmail where
  parseJSON :: Value -> Parser MandrillEmail
parseJSON (String Text
s) = case ByteString -> Either String EmailAddress
validate (Text -> ByteString
TL.encodeUtf8 Text
s) of
    Left String
err -> String -> Parser MandrillEmail
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
err
    Right EmailAddress
v  -> MandrillEmail -> Parser MandrillEmail
forall (m :: * -> *) a. Monad m => a -> m a
return (MandrillEmail -> Parser MandrillEmail)
-> (EmailAddress -> MandrillEmail)
-> EmailAddress
-> Parser MandrillEmail
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EmailAddress -> MandrillEmail
MandrillEmail (EmailAddress -> Parser MandrillEmail)
-> EmailAddress -> Parser MandrillEmail
forall a b. (a -> b) -> a -> b
$ EmailAddress
v
  parseJSON Value
o = String -> Value -> Parser MandrillEmail
forall a. String -> Value -> Parser a
typeMismatch String
"Expecting a String for MandrillEmail." Value
o


--------------------------------------------------------------------------------
-- | An array of recipient information.
data MandrillRecipient = MandrillRecipient {
    MandrillRecipient -> MandrillEmail
_mrec_email :: MandrillEmail
    -- ^ The email address of the recipient
  , MandrillRecipient -> Maybe Text
_mrec_name  :: Maybe T.Text
    -- ^ The optional display name to use for the recipient
  , MandrillRecipient -> Maybe MandrillRecipientTag
_mrec_type  :: Maybe MandrillRecipientTag
    -- ^ The header type to use for the recipient.
    --   defaults to "to" if not provided
  } deriving Int -> MandrillRecipient -> ShowS
[MandrillRecipient] -> ShowS
MandrillRecipient -> String
(Int -> MandrillRecipient -> ShowS)
-> (MandrillRecipient -> String)
-> ([MandrillRecipient] -> ShowS)
-> Show MandrillRecipient
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillRecipient] -> ShowS
$cshowList :: [MandrillRecipient] -> ShowS
show :: MandrillRecipient -> String
$cshow :: MandrillRecipient -> String
showsPrec :: Int -> MandrillRecipient -> ShowS
$cshowsPrec :: Int -> MandrillRecipient -> ShowS
Show

makeLenses ''MandrillRecipient
deriveJSON defaultOptions { fieldLabelModifier = drop 6 } ''MandrillRecipient

newRecipient :: EmailAddress -> MandrillRecipient
newRecipient :: EmailAddress -> MandrillRecipient
newRecipient EmailAddress
email = MandrillEmail
-> Maybe Text -> Maybe MandrillRecipientTag -> MandrillRecipient
MandrillRecipient (EmailAddress -> MandrillEmail
MandrillEmail EmailAddress
email) Maybe Text
forall a. Maybe a
Nothing Maybe MandrillRecipientTag
forall a. Maybe a
Nothing

instance Arbitrary MandrillRecipient where
  arbitrary :: Gen MandrillRecipient
arbitrary = MandrillRecipient -> Gen MandrillRecipient
forall (f :: * -> *) a. Applicative f => a -> f a
pure MandrillRecipient :: MandrillEmail
-> Maybe Text -> Maybe MandrillRecipientTag -> MandrillRecipient
MandrillRecipient {
      _mrec_email :: MandrillEmail
_mrec_email = EmailAddress -> MandrillEmail
MandrillEmail (EmailAddress -> MandrillEmail) -> EmailAddress -> MandrillEmail
forall a b. (a -> b) -> a -> b
$ Maybe EmailAddress -> EmailAddress
forall a. HasCallStack => Maybe a -> a
fromJust (ByteString -> Maybe EmailAddress
emailAddress ByteString
"test@example.com")
    , _mrec_name :: Maybe Text
_mrec_name  =  Maybe Text
forall a. Maybe a
Nothing
    , _mrec_type :: Maybe MandrillRecipientTag
_mrec_type  =  Maybe MandrillRecipientTag
forall a. Maybe a
Nothing
    }

--------------------------------------------------------------------------------
newtype MandrillHtml = MandrillHtml Blaze.Html

unsafeMkMandrillHtml :: T.Text -> MandrillHtml
unsafeMkMandrillHtml :: Text -> MandrillHtml
unsafeMkMandrillHtml = Html -> MandrillHtml
MandrillHtml (Html -> MandrillHtml) -> (Text -> Html) -> Text -> MandrillHtml
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Html
forall a. ToMarkup a => a -> Html
Blaze.preEscapedToHtml

-- This might be slightly hairy because it violates
-- the nice encapsulation that newtypes offer.
mkMandrillHtml :: Blaze.Html -> MandrillHtml
mkMandrillHtml :: Html -> MandrillHtml
mkMandrillHtml = Html -> MandrillHtml
MandrillHtml

#if MIN_VERSION_base(4,11,0)
instance Semigroup MandrillHtml where
  MandrillHtml Html
m1 <> :: MandrillHtml -> MandrillHtml -> MandrillHtml
<> MandrillHtml Html
m2 = Html -> MandrillHtml
MandrillHtml (Html
m1 Html -> Html -> Html
forall a. Semigroup a => a -> a -> a
<> Html
m2)
#endif

instance Monoid MandrillHtml where
  mempty :: MandrillHtml
mempty = Html -> MandrillHtml
MandrillHtml Html
forall a. Monoid a => a
mempty
  mappend :: MandrillHtml -> MandrillHtml -> MandrillHtml
mappend (MandrillHtml Html
m1) (MandrillHtml Html
m2) = Html -> MandrillHtml
MandrillHtml (Html
m1 Html -> Html -> Html
forall a. Semigroup a => a -> a -> a
<> Html
m2)

instance Show MandrillHtml where
  show :: MandrillHtml -> String
show (MandrillHtml Html
h) = Text -> String
forall a. Show a => a -> String
show (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Html -> Text
Blaze.renderHtml Html
h

instance ToJSON MandrillHtml where
  toJSON :: MandrillHtml -> Value
toJSON (MandrillHtml Html
h) = Text -> Value
String (Text -> Value) -> (Html -> Text) -> Html -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.toStrict (Text -> Text) -> (Html -> Text) -> Html -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Html -> Text
Blaze.renderHtml (Html -> Value) -> Html -> Value
forall a b. (a -> b) -> a -> b
$ Html
h

instance FromJSON MandrillHtml where
  parseJSON :: Value -> Parser MandrillHtml
parseJSON (String Text
h) = MandrillHtml -> Parser MandrillHtml
forall (m :: * -> *) a. Monad m => a -> m a
return (MandrillHtml -> Parser MandrillHtml)
-> MandrillHtml -> Parser MandrillHtml
forall a b. (a -> b) -> a -> b
$ Html -> MandrillHtml
MandrillHtml (Text -> Html
forall a. ToMarkup a => a -> Html
Blaze.preEscapedToHtml Text
h)
  parseJSON Value
v = String -> Value -> Parser MandrillHtml
forall a. String -> Value -> Parser a
typeMismatch String
"Expecting a String for MandrillHtml" Value
v

instance Arbitrary MandrillHtml where
  arbitrary :: Gen MandrillHtml
arbitrary = MandrillHtml -> Gen MandrillHtml
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MandrillHtml -> Gen MandrillHtml)
-> MandrillHtml -> Gen MandrillHtml
forall a b. (a -> b) -> a -> b
$ Html -> MandrillHtml
mkMandrillHtml Html
"<p><b>FooBar</b></p>"

--------------------------------------------------------------------------------
type MandrillTags = T.Text


--------------------------------------------------------------------------------
type MandrillHeaders = Object


--------------------------------------------------------------------------------

data MergeVar = MergeVar {
      MergeVar -> Text
_mv_name    :: !T.Text
    , MergeVar -> Value
_mv_content :: Value
    } deriving Int -> MergeVar -> ShowS
[MergeVar] -> ShowS
MergeVar -> String
(Int -> MergeVar -> ShowS)
-> (MergeVar -> String) -> ([MergeVar] -> ShowS) -> Show MergeVar
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MergeVar] -> ShowS
$cshowList :: [MergeVar] -> ShowS
show :: MergeVar -> String
$cshow :: MergeVar -> String
showsPrec :: Int -> MergeVar -> ShowS
$cshowsPrec :: Int -> MergeVar -> ShowS
Show

makeLenses ''MergeVar
deriveJSON defaultOptions { fieldLabelModifier = drop 4 } ''MergeVar

--------------------------------------------------------------------------------
data MandrillMergeVars = MandrillMergeVars {
    MandrillMergeVars -> Text
_mmvr_rcpt :: !T.Text
  , MandrillMergeVars -> [MergeVar]
_mmvr_vars :: [MergeVar]
  } deriving Int -> MandrillMergeVars -> ShowS
[MandrillMergeVars] -> ShowS
MandrillMergeVars -> String
(Int -> MandrillMergeVars -> ShowS)
-> (MandrillMergeVars -> String)
-> ([MandrillMergeVars] -> ShowS)
-> Show MandrillMergeVars
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillMergeVars] -> ShowS
$cshowList :: [MandrillMergeVars] -> ShowS
show :: MandrillMergeVars -> String
$cshow :: MandrillMergeVars -> String
showsPrec :: Int -> MandrillMergeVars -> ShowS
$cshowsPrec :: Int -> MandrillMergeVars -> ShowS
Show

makeLenses ''MandrillMergeVars
deriveJSON defaultOptions { fieldLabelModifier = drop 6 } ''MandrillMergeVars

--------------------------------------------------------------------------------
data MandrillMetadata = MandrillMetadata {
    MandrillMetadata -> Text
_mmdt_rcpt   :: !T.Text
  , MandrillMetadata -> Object
_mmdt_values :: Object
  } deriving Int -> MandrillMetadata -> ShowS
[MandrillMetadata] -> ShowS
MandrillMetadata -> String
(Int -> MandrillMetadata -> ShowS)
-> (MandrillMetadata -> String)
-> ([MandrillMetadata] -> ShowS)
-> Show MandrillMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillMetadata] -> ShowS
$cshowList :: [MandrillMetadata] -> ShowS
show :: MandrillMetadata -> String
$cshow :: MandrillMetadata -> String
showsPrec :: Int -> MandrillMetadata -> ShowS
$cshowsPrec :: Int -> MandrillMetadata -> ShowS
Show

makeLenses ''MandrillMetadata
deriveJSON defaultOptions { fieldLabelModifier = drop 6 } ''MandrillMetadata


data Base64ByteString =
    EncodedB64BS B.ByteString
  -- ^ An already-encoded Base64 ByteString.
  | PlainBS B.ByteString
  -- ^ A plain Base64 ByteString which requires encoding.
  deriving Int -> Base64ByteString -> ShowS
[Base64ByteString] -> ShowS
Base64ByteString -> String
(Int -> Base64ByteString -> ShowS)
-> (Base64ByteString -> String)
-> ([Base64ByteString] -> ShowS)
-> Show Base64ByteString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Base64ByteString] -> ShowS
$cshowList :: [Base64ByteString] -> ShowS
show :: Base64ByteString -> String
$cshow :: Base64ByteString -> String
showsPrec :: Int -> Base64ByteString -> ShowS
$cshowsPrec :: Int -> Base64ByteString -> ShowS
Show

instance ToJSON Base64ByteString where
  toJSON :: Base64ByteString -> Value
toJSON (PlainBS ByteString
bs)      = Text -> Value
String (Text -> Value) -> (ByteString -> Text) -> ByteString -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
TL.decodeUtf8 (ByteString -> Text)
-> (ByteString -> ByteString) -> ByteString -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
Base64.encode (ByteString -> Value) -> ByteString -> Value
forall a b. (a -> b) -> a -> b
$ ByteString
bs
  toJSON (EncodedB64BS ByteString
bs) = Text -> Value
String (Text -> Value) -> (ByteString -> Text) -> ByteString -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
TL.decodeUtf8 (ByteString -> Value) -> ByteString -> Value
forall a b. (a -> b) -> a -> b
$ ByteString
bs

instance FromJSON Base64ByteString where
  parseJSON :: Value -> Parser Base64ByteString
parseJSON (String Text
v) = Base64ByteString -> Parser Base64ByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Base64ByteString -> Parser Base64ByteString)
-> Base64ByteString -> Parser Base64ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> Base64ByteString
EncodedB64BS (Text -> ByteString
TL.encodeUtf8 Text
v)
  parseJSON Value
rest = String -> Value -> Parser Base64ByteString
forall a. String -> Value -> Parser a
typeMismatch String
"Base64ByteString must be a String." Value
rest

--------------------------------------------------------------------------------
data MandrillWebContent = MandrillWebContent {
    MandrillWebContent -> Text
_mwct_type    :: !T.Text
  , MandrillWebContent -> Text
_mwct_name    :: !T.Text
    -- ^ [for images] the Content ID of the image
    -- - use <img src="cid:THIS_VALUE"> to reference the image
    -- in your HTML content
  , MandrillWebContent -> Base64ByteString
_mwct_content :: !Base64ByteString
  } deriving Int -> MandrillWebContent -> ShowS
[MandrillWebContent] -> ShowS
MandrillWebContent -> String
(Int -> MandrillWebContent -> ShowS)
-> (MandrillWebContent -> String)
-> ([MandrillWebContent] -> ShowS)
-> Show MandrillWebContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillWebContent] -> ShowS
$cshowList :: [MandrillWebContent] -> ShowS
show :: MandrillWebContent -> String
$cshow :: MandrillWebContent -> String
showsPrec :: Int -> MandrillWebContent -> ShowS
$cshowsPrec :: Int -> MandrillWebContent -> ShowS
Show

makeLenses ''MandrillWebContent
deriveJSON defaultOptions { fieldLabelModifier = drop 6 } ''MandrillWebContent

--------------------------------------------------------------------------------
-- | The information on the message to send
data MandrillMessage = MandrillMessage {
   MandrillMessage -> MandrillHtml
_mmsg_html                      :: MandrillHtml
   -- ^ The full HTML content to be sent
 , MandrillMessage -> Maybe Text
_mmsg_text                      :: Maybe T.Text
   -- ^ Optional full text content to be sent
 , MandrillMessage -> Maybe Text
_mmsg_subject                   :: !(Maybe T.Text)
   -- ^ The message subject
 , MandrillMessage -> Maybe MandrillEmail
_mmsg_from_email                :: Maybe MandrillEmail
   -- ^ The sender email address
 , MandrillMessage -> Maybe Text
_mmsg_from_name                 :: Maybe T.Text
   -- ^ Optional from name to be used
 , MandrillMessage -> [MandrillRecipient]
_mmsg_to                        :: [MandrillRecipient]
   -- ^ A list of recipient information
 , MandrillMessage -> Object
_mmsg_headers                   :: MandrillHeaders
   -- ^ optional extra headers to add to the message (most headers are allowed)
 , MandrillMessage -> Maybe Bool
_mmsg_important                 :: Maybe Bool
   -- ^ whether or not this message is important, and should be delivered ahead
   -- of non-important messages
 , MandrillMessage -> Maybe Bool
_mmsg_track_opens               :: Maybe Bool
   -- ^ whether or not to turn on open tracking for the message
 , MandrillMessage -> Maybe Bool
_mmsg_track_clicks              :: Maybe Bool
   -- ^ whether or not to turn on click tracking for the message
 , MandrillMessage -> Maybe Bool
_mmsg_auto_text                 :: Maybe Bool
   -- ^ whether or not to automatically generate a text part for messages that are not given text
 , MandrillMessage -> Maybe Bool
_mmsg_auto_html                 :: Maybe Bool
   -- ^ whether or not to automatically generate an HTML part for messages that are not given HTML
 , MandrillMessage -> Maybe Bool
_mmsg_inline_css                :: Maybe Bool
   -- ^ whether or not to automatically inline all CSS styles provided in the message HTML
   -- - only for HTML documents less than 256KB in size
 , MandrillMessage -> Maybe Bool
_mmsg_url_strip_qs              :: Maybe Bool
   -- ^ whether or not to strip the query string from URLs when aggregating tracked URL data
 , MandrillMessage -> Maybe Bool
_mmsg_preserve_recipients       :: Maybe Bool
   -- ^ whether or not to expose all recipients in to "To" header for each email
 , MandrillMessage -> Maybe Bool
_mmsg_view_content_link         :: Maybe Bool
   -- ^ set to false to remove content logging for sensitive emails
 , MandrillMessage -> Maybe Text
_mmsg_bcc_address               :: Maybe T.Text
   -- ^ an optional address to receive an exact copy of each recipient's email
 , MandrillMessage -> Maybe Text
_mmsg_tracking_domain           :: Maybe T.Text
   -- ^ a custom domain to use for tracking opens and clicks instead of mandrillapp.com
 , MandrillMessage -> Maybe Bool
_mmsg_signing_domain            :: Maybe Bool
   -- ^ a custom domain to use for SPF/DKIM signing instead of mandrill
   -- (for "via" or "on behalf of" in email clients)
 , MandrillMessage -> Maybe Bool
_mmsg_return_path_domain        :: Maybe Bool
   -- ^ a custom domain to use for the messages's return-path
 , MandrillMessage -> Maybe Bool
_mmsg_merge                     :: Maybe Bool
   -- ^ whether to evaluate merge tags in the message.
   -- Will automatically be set to true if either merge_vars
   -- or global_merge_vars are provided.
 , MandrillMessage -> [MergeVar]
_mmsg_global_merge_vars         :: [MergeVar]
   -- ^ global merge variables to use for all recipients. You can override these per recipient.
 , MandrillMessage -> [MandrillMergeVars]
_mmsg_merge_vars                :: [MandrillMergeVars]
   -- ^ per-recipient merge variables, which override global merge variables with the same name.
 , MandrillMessage -> [Text]
_mmsg_tags                      :: [MandrillTags]
   -- ^ an array of string to tag the message with. Stats are accumulated using tags,
   -- though we only store the first 100 we see, so this should not be unique
   -- or change frequently. Tags should be 50 characters or less.
   -- Any tags starting with an underscore are reserved for internal use
   -- and will cause errors.
 , MandrillMessage -> Maybe Text
_mmsg_subaccount                :: Maybe T.Text
   -- ^ the unique id of a subaccount for this message
   -- - must already exist or will fail with an error
 , MandrillMessage -> [Text]
_mmsg_google_analytics_domains  :: [T.Text]
   -- ^ an array of strings indicating for which any matching URLs
   -- will automatically have Google Analytics parameters appended
   -- to their query string automatically.
 , MandrillMessage -> Maybe Text
_mmsg_google_analytics_campaign :: Maybe T.Text
   -- ^ optional string indicating the value to set for the utm_campaign
   -- tracking parameter. If this isn't provided the email's from address
   -- will be used instead.
 , MandrillMessage -> Object
_mmsg_metadata                  :: Object
   -- ^ metadata an associative array of user metadata. Mandrill will store
   -- this metadata and make it available for retrieval.
   -- In addition, you can select up to 10 metadata fields to index
   -- and make searchable using the Mandrill search api.
 , MandrillMessage -> [MandrillMetadata]
_mmsg_recipient_metadata        :: [MandrillMetadata]
   -- ^ Per-recipient metadata that will override the global values
   -- specified in the metadata parameter.
 , MandrillMessage -> [MandrillWebContent]
_mmsg_attachments               :: [MandrillWebContent]
   -- ^ an array of supported attachments to add to the message
 , MandrillMessage -> [MandrillWebContent]
_mmsg_images                    :: [MandrillWebContent]
   -- ^ an array of embedded images to add to the message
 } deriving Int -> MandrillMessage -> ShowS
[MandrillMessage] -> ShowS
MandrillMessage -> String
(Int -> MandrillMessage -> ShowS)
-> (MandrillMessage -> String)
-> ([MandrillMessage] -> ShowS)
-> Show MandrillMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillMessage] -> ShowS
$cshowList :: [MandrillMessage] -> ShowS
show :: MandrillMessage -> String
$cshow :: MandrillMessage -> String
showsPrec :: Int -> MandrillMessage -> ShowS
$cshowsPrec :: Int -> MandrillMessage -> ShowS
Show

makeLenses ''MandrillMessage
deriveJSON defaultOptions { fieldLabelModifier = drop 6 } ''MandrillMessage

instance Arbitrary MandrillMessage where
  arbitrary :: Gen MandrillMessage
arbitrary = MandrillHtml
-> Maybe Text
-> Maybe Text
-> Maybe MandrillEmail
-> Maybe Text
-> [MandrillRecipient]
-> Object
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> [MergeVar]
-> [MandrillMergeVars]
-> [Text]
-> Maybe Text
-> [Text]
-> Maybe Text
-> Object
-> [MandrillMetadata]
-> [MandrillWebContent]
-> [MandrillWebContent]
-> MandrillMessage
MandrillMessage (MandrillHtml
 -> Maybe Text
 -> Maybe Text
 -> Maybe MandrillEmail
 -> Maybe Text
 -> [MandrillRecipient]
 -> Object
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Text
 -> Maybe Text
 -> Maybe Bool
 -> Maybe Bool
 -> Maybe Bool
 -> [MergeVar]
 -> [MandrillMergeVars]
 -> [Text]
 -> Maybe Text
 -> [Text]
 -> Maybe Text
 -> Object
 -> [MandrillMetadata]
 -> [MandrillWebContent]
 -> [MandrillWebContent]
 -> MandrillMessage)
-> Gen MandrillHtml
-> Gen
     (Maybe Text
      -> Maybe Text
      -> Maybe MandrillEmail
      -> Maybe Text
      -> [MandrillRecipient]
      -> Object
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen MandrillHtml
forall a. Arbitrary a => Gen a
arbitrary
                              Gen
  (Maybe Text
   -> Maybe Text
   -> Maybe MandrillEmail
   -> Maybe Text
   -> [MandrillRecipient]
   -> Object
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Text)
-> Gen
     (Maybe Text
      -> Maybe MandrillEmail
      -> Maybe Text
      -> [MandrillRecipient]
      -> Object
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Text -> Gen (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
                              Gen
  (Maybe Text
   -> Maybe MandrillEmail
   -> Maybe Text
   -> [MandrillRecipient]
   -> Object
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Text)
-> Gen
     (Maybe MandrillEmail
      -> Maybe Text
      -> [MandrillRecipient]
      -> Object
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Text -> Gen (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Test Subject")
                              Gen
  (Maybe MandrillEmail
   -> Maybe Text
   -> [MandrillRecipient]
   -> Object
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe MandrillEmail)
-> Gen
     (Maybe Text
      -> [MandrillRecipient]
      -> Object
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe MandrillEmail -> Gen (Maybe MandrillEmail)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (EmailAddress -> MandrillEmail
MandrillEmail (EmailAddress -> MandrillEmail)
-> Maybe EmailAddress -> Maybe MandrillEmail
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe EmailAddress
emailAddress ByteString
"sender@example.com")
                              Gen
  (Maybe Text
   -> [MandrillRecipient]
   -> Object
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Text)
-> Gen
     ([MandrillRecipient]
      -> Object
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Text -> Gen (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
                              Gen
  ([MandrillRecipient]
   -> Object
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen [MandrillRecipient]
-> Gen
     (Object
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Gen [MandrillRecipient] -> Gen [MandrillRecipient]
forall a. Int -> Gen a -> Gen a
resize Int
2 Gen [MandrillRecipient]
forall a. Arbitrary a => Gen a
arbitrary
                              Gen
  (Object
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen Object
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object -> Gen Object
forall (f :: * -> *) a. Applicative f => a -> f a
pure Object
forall k v. HashMap k v
H.empty
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Text
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Text
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Text)
-> Gen
     (Maybe Text
      -> Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Text -> Gen (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
                              Gen
  (Maybe Text
   -> Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Text)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Text -> Gen (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     (Maybe Bool
      -> [MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  (Maybe Bool
   -> [MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Bool)
-> Gen
     ([MergeVar]
      -> [MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Bool -> Gen (Maybe Bool)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Bool
forall a. Maybe a
Nothing
                              Gen
  ([MergeVar]
   -> [MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen [MergeVar]
-> Gen
     ([MandrillMergeVars]
      -> [Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [MergeVar] -> Gen [MergeVar]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
                              Gen
  ([MandrillMergeVars]
   -> [Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen [MandrillMergeVars]
-> Gen
     ([Text]
      -> Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [MandrillMergeVars] -> Gen [MandrillMergeVars]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
                              Gen
  ([Text]
   -> Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen [Text]
-> Gen
     (Maybe Text
      -> [Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Text] -> Gen [Text]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
                              Gen
  (Maybe Text
   -> [Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Text)
-> Gen
     ([Text]
      -> Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Text -> Gen (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
                              Gen
  ([Text]
   -> Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen [Text]
-> Gen
     (Maybe Text
      -> Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Text] -> Gen [Text]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
                              Gen
  (Maybe Text
   -> Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen (Maybe Text)
-> Gen
     (Object
      -> [MandrillMetadata]
      -> [MandrillWebContent]
      -> [MandrillWebContent]
      -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Text -> Gen (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
                              Gen
  (Object
   -> [MandrillMetadata]
   -> [MandrillWebContent]
   -> [MandrillWebContent]
   -> MandrillMessage)
-> Gen Object
-> Gen
     ([MandrillMetadata]
      -> [MandrillWebContent] -> [MandrillWebContent] -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object -> Gen Object
forall (f :: * -> *) a. Applicative f => a -> f a
pure Object
forall k v. HashMap k v
H.empty
                              Gen
  ([MandrillMetadata]
   -> [MandrillWebContent] -> [MandrillWebContent] -> MandrillMessage)
-> Gen [MandrillMetadata]
-> Gen
     ([MandrillWebContent] -> [MandrillWebContent] -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [MandrillMetadata] -> Gen [MandrillMetadata]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
                              Gen
  ([MandrillWebContent] -> [MandrillWebContent] -> MandrillMessage)
-> Gen [MandrillWebContent]
-> Gen ([MandrillWebContent] -> MandrillMessage)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [MandrillWebContent] -> Gen [MandrillWebContent]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
                              Gen ([MandrillWebContent] -> MandrillMessage)
-> Gen [MandrillWebContent] -> Gen MandrillMessage
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [MandrillWebContent] -> Gen [MandrillWebContent]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []

--------------------------------------------------------------------------------
-- | Key value pair for replacing content in templates via 'Editable Regions'
data MandrillTemplateContent = MandrillTemplateContent {
    MandrillTemplateContent -> Text
_mtc_name    :: T.Text
  , MandrillTemplateContent -> Text
_mtc_content :: T.Text
  } deriving Int -> MandrillTemplateContent -> ShowS
[MandrillTemplateContent] -> ShowS
MandrillTemplateContent -> String
(Int -> MandrillTemplateContent -> ShowS)
-> (MandrillTemplateContent -> String)
-> ([MandrillTemplateContent] -> ShowS)
-> Show MandrillTemplateContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillTemplateContent] -> ShowS
$cshowList :: [MandrillTemplateContent] -> ShowS
show :: MandrillTemplateContent -> String
$cshow :: MandrillTemplateContent -> String
showsPrec :: Int -> MandrillTemplateContent -> ShowS
$cshowsPrec :: Int -> MandrillTemplateContent -> ShowS
Show

makeLenses ''MandrillTemplateContent
deriveJSON defaultOptions { fieldLabelModifier = drop 5 } ''MandrillTemplateContent

--------------------------------------------------------------------------------
type MandrillKey = T.Text
type MandrillTemplate = T.Text

newtype MandrillDate = MandrillDate {
  MandrillDate -> UTCTime
fromMandrillDate :: UTCTime
  } deriving Int -> MandrillDate -> ShowS
[MandrillDate] -> ShowS
MandrillDate -> String
(Int -> MandrillDate -> ShowS)
-> (MandrillDate -> String)
-> ([MandrillDate] -> ShowS)
-> Show MandrillDate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MandrillDate] -> ShowS
$cshowList :: [MandrillDate] -> ShowS
show :: MandrillDate -> String
$cshow :: MandrillDate -> String
showsPrec :: Int -> MandrillDate -> ShowS
$cshowsPrec :: Int -> MandrillDate -> ShowS
Show

instance ToJSON MandrillDate where
  toJSON :: MandrillDate -> Value
toJSON = UTCTime -> Value
forall a. ToJSON a => a -> Value
toJSON (UTCTime -> Value)
-> (MandrillDate -> UTCTime) -> MandrillDate -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MandrillDate -> UTCTime
fromMandrillDate

instance FromJSON MandrillDate where
  parseJSON :: Value -> Parser MandrillDate
parseJSON = String
-> (Text -> Parser MandrillDate) -> Value -> Parser MandrillDate
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"MandrillDate" ((Text -> Parser MandrillDate) -> Value -> Parser MandrillDate)
-> (Text -> Parser MandrillDate) -> Value -> Parser MandrillDate
forall a b. (a -> b) -> a -> b
$ \Text
t ->
      case TimeLocale -> String -> String -> Maybe UTCTime
forall t. ParseTime t => TimeLocale -> String -> String -> Maybe t
timeParse TimeLocale
defaultTimeLocale String
"%Y-%m-%d %H:%M:%S%Q" (Text -> String
T.unpack Text
t) of
        Just UTCTime
d -> MandrillDate -> Parser MandrillDate
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MandrillDate -> Parser MandrillDate)
-> MandrillDate -> Parser MandrillDate
forall a b. (a -> b) -> a -> b
$ UTCTime -> MandrillDate
MandrillDate UTCTime
d
        Maybe UTCTime
_      -> String -> Parser MandrillDate
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"could not parse Mandrill date"