{-# LANGUAGE DeriveGeneric, OverloadedStrings #-} module MailchimpSimple.Types ( -- * Request JSON data types Subscription(..) , EmailId(..) , MailList(..) , Filters(..) , Subscribers(..) , BatchSubscription(..) , Batch(..) , Campaign(..) , Options(..) , Content(..) , SendMail(..) , Template(..) , TemplateTypes(..) -- * Response JSON data types , SubscriptionResponse(..) , MailListResponse(..) , ListSubscribersResponse(..) , BatchSubscriptionResponse(..) , SendMailResponse(..) , TemplateResponse(..) ) where import Data.Aeson -- ( FromJSON(..), ToJSON(..), toJSON, parseJSON, (.:), (.:?), (.=), object, Value(..) ) import Data.Aeson.TH hiding ( Options ) import GHC.Generics hiding ( head ) import Control.Monad ( mzero ) import Data.Maybe ( catMaybes ) -- | JSON data structure for a single subscription data Subscription = Subscription { s_apikey :: String -- ^ API key of the Mailchimp account , s_id :: String -- ^ List ID of the mailing list, by calling , s_email :: EmailId -- ^ Example: jon@example.com , s_email_type :: String -- ^ Give html/text , s_dou_opt :: Bool , s_up_ex :: Bool , s_rep_int :: Bool , s_send :: Bool } deriving (Show) instance FromJSON Subscription where parseJSON (Object v) = do sApikey <- v .: "apikey" sID <- v .: "id" sEmail <- v .: "email" sEmailType <- v .: "email_type" sDouOpt <- v .: "double_optin" sUpEx <- v .: "update_existing" sRepInt <- v .: "replace_interests" sSent <- v .: "send_welcome" return $ Subscription sApikey sID sEmail sEmailType sDouOpt sUpEx sRepInt sSent parseJSON _ = mzero instance ToJSON Subscription where toJSON (Subscription s_apikey s_id s_email s_email_type s_dou_opt s_up_ex s_rep_int s_send) = object [ "apikey" .= s_apikey , "id" .= s_id , "email" .= s_email , "email_type" .= s_email_type , "double_optin" .= s_dou_opt , "update_existing" .= s_up_ex , "replace_interests" .= s_rep_int , "send_welcome" .= s_send ] -- | Enum type JSON data structure for Email related variables data EmailId = Email String | EmailUniqueId String | ListEmailId String deriving (Show) instance FromJSON EmailId where parseJSON (Object v) = do email <- fmap (fmap Email) $ v .:? "email" euid <- fmap (fmap EmailUniqueId) $ v .:? "euid" leid <- fmap (fmap ListEmailId) $ v .:? "leid" case catMaybes [email, euid, leid] of (x:_) -> return x _ -> mzero parseJSON _ = mzero instance ToJSON EmailId where toJSON (Email t) = object ["email" .= t] toJSON (EmailUniqueId t) = object ["euid" .= t] toJSON (ListEmailId t) = object ["leid" .= t] -- | JSON data structure for batch subscriptions data BatchSubscription = BatchSubscription { b_apikey :: String -- ^ API key of the Mailchimp account , b_id :: String -- ^ List ID of the mailing list , b_batch :: [Batch] -- ^ Array of tuples of email address and email type , b_dou_opt :: Bool , b_up_ex :: Bool , b_rep_int :: Bool } deriving (Show) instance FromJSON BatchSubscription where parseJSON (Object v) = do bApikey <- v .: "apikey" bID <- v .: "id" bBatch <- v .: "batch" bDouOpt <- v .: "double_optin" bUpEx <- v .: "update_existing" bRepInt <- v .: "replace_interests" return $ BatchSubscription bApikey bID bBatch bDouOpt bUpEx bRepInt parseJSON _ = mzero instance ToJSON BatchSubscription where toJSON (BatchSubscription b_apikey b_id b_batch b_dou_opt b_up_ex b_rep_int) = object [ "apikey" .= b_apikey , "id" .= b_id , "batch" .= b_batch , "double_optin" .= b_dou_opt , "update_existing" .= b_up_ex , "replace_interests" .= b_rep_int ] data Batch = Batch { b_email :: EmailId , b_email_type :: String } deriving (Show) instance FromJSON Batch where parseJSON (Object v) = do bEmail <- v .: "email" bEmailType <- v .: "email_type" return $ Batch bEmail bEmailType parseJSON _ = mzero instance ToJSON Batch where toJSON (Batch b_email b_email_type) = object [ "email" .= b_email , "email_type" .= b_email_type ] data MailList = MailList { l_apikey :: String -- ^ API key of the Mailchimp account , l_filters :: Filters , l_start :: Int , l_limit :: Int , l_sort_field :: String , l_sort_dir :: String } deriving (Show) instance FromJSON MailList where parseJSON (Object v) = do lApikey <- v .: "apikey" lFilters <- v .: "filters" lStart <- v .: "start" lLimit <- v .: "limit" lSortField <- v .: "sort_field" lSortDir <- v .: "sort_dir" return $ MailList lApikey lFilters lStart lLimit lSortField lSortDir parseJSON _ = mzero instance ToJSON MailList where toJSON (MailList l_apikey l_filters l_start l_limit l_sort_field l_sort_dir) = object [ "apikey" .= l_apikey , "filters" .= l_filters , "start" .= l_start , "limit" .= l_limit , "sort_field" .= l_sort_field , "sort_dir" .= l_sort_dir ] data Filters = Filters { list_id :: String , list_name :: String } deriving (Show) instance FromJSON Filters where parseJSON (Object v) = do lID <- v .: "id" lName <- v .: "name" return $ Filters lID lName parseJSON _ = mzero instance ToJSON Filters where toJSON (Filters list_id list_name) = object [ "id" .= list_id , "name" .= list_name ] data Subscribers = Subscribers { su_apikey :: String -- ^ API key of the Mailchimp account , su_id :: String -- ^ List ID of the mailing list , su_status :: String } deriving (Show) instance FromJSON Subscribers where parseJSON (Object v) = do suApikey <- v .: "apikey" suID <- v .: "id" suStatus <- v .: "status" return $ Subscribers suApikey suID suStatus parseJSON _ = mzero instance ToJSON Subscribers where toJSON (Subscribers su_apikey su_id su_status) = object [ "apikey" .= su_apikey , "id" .= su_id , "status" .= su_status] data Campaign = Campaign { c_apikey :: String , c_type :: String , c_options :: Options , c_content :: Content } deriving (Show, Generic) instance FromJSON Campaign where instance ToJSON Campaign where toJSON (Campaign c_apikey c_type c_options c_content) = object [ "apikey" .= c_apikey , "type" .= c_type , "options" .= c_options , "content" .= c_content ] data Options = Options { o_list_id :: String , o_subject :: String , o_from_email :: String , o_from_name :: String , o_to_name :: String , o_template_id :: Int } deriving (Show, Generic) instance FromJSON Options where instance ToJSON Options where toJSON (Options o_list_id o_subject o_from_email o_from_name o_to_name o_template_id) = object [ "list_id" .= o_list_id , "subject" .= o_subject , "from_email" .= o_from_email , "from_name" .= o_from_name , "to_name" .= o_to_name , "template_id" .= o_template_id ] data Content = HTML String | Text String | URL String deriving (Show) instance ToJSON Content where toJSON (HTML t) = object ["html" .= t] toJSON (Text t) = object ["text" .= t] toJSON (URL t) = object ["url" .= t] instance FromJSON Content where parseJSON (Object v) = do html <- fmap (fmap HTML) $ v .:? "html" text <- fmap (fmap Text) $ v .:? "text" url <- fmap (fmap URL) $ v .:? "url" case catMaybes [html, text, url] of (x:_) -> return x _ -> mzero parseJSON _ = mzero data SendMail = SendMail { m_apikey :: String -- ^ API key of the Mailchimp account , m_cid :: String -- ^ Campaign ID of the campaign to be sent } deriving (Show, Generic) instance FromJSON SendMail where instance ToJSON SendMail where toJSON (SendMail m_apikey m_cid) = object [ "apikey" .= m_apikey , "cid" .= m_cid ] data Template = Template { t_apikey :: String , t_types :: TemplateTypes } deriving (Show, Generic) instance FromJSON Template where instance ToJSON Template where toJSON (Template t_apikey t_types) = object [ "apikey" .= t_apikey , "types" .= t_types ] data TemplateTypes = TemplateTypes { user :: Bool , gallery :: Bool , base :: Bool } deriving (Show, Generic) instance FromJSON TemplateTypes where instance ToJSON TemplateTypes where -- | Response JSON from 'lists/subscribe.json' call data SubscriptionResponse = SubscriptionResponse { email :: String , euid :: String , leid :: String } deriving (Show) instance FromJSON SubscriptionResponse where parseJSON (Object v) = do srEmail <- v .: "email" srEuid <- v .: "euid" srLeid <- v .: "leid" return $ SubscriptionResponse srEmail srEuid srLeid parseJSON _ = mzero instance ToJSON SubscriptionResponse where toJSON (SubscriptionResponse email euid leid) = object [ "email" .= email , "euid" .= euid , "leid" .= leid ] -- | Response JSON from 'lists/list.json' call, which lists the mailing lists -- in the given account with relevant API key data MailListResponse = MailListResponse { l_name :: Maybe String -- ^ List name , l_id :: Maybe String -- ^ List ID } deriving (Show, Generic) instance FromJSON MailListResponse where instance ToJSON MailListResponse where -- | Response JSON from 'lists/members.json' call, which contains the details -- each subscriber in the given mailing list data ListSubscribersResponse = ListSubscribersResponse { s_name :: Maybe String -- ^ Subscriber's name , s_euid :: Maybe String -- ^ Subscriber's euid , s_list_name :: Maybe String , s_emailType :: Maybe String } deriving (Show, Generic) instance FromJSON ListSubscribersResponse where instance ToJSON ListSubscribersResponse where -- | Response JSON from the 'lists/batch-subscribe.json' call, which contains the -- information of the subscriptions of each newly added member data BatchSubscriptionResponse = BatchSubscriptionResponse { add_count :: Maybe Int , adds :: [Maybe SubscriptionResponse] } deriving (Show, Generic) instance FromJSON BatchSubscriptionResponse where instance ToJSON BatchSubscriptionResponse where data SendMailResponse = SendMailResponse { complete :: Bool } deriving (Show, Generic) instance FromJSON SendMailResponse where instance ToJSON SendMailResponse where data TemplateResponse = TemplateResponse { t_name :: Maybe String , t_id :: Maybe Int } deriving (Show, Generic) instance FromJSON TemplateResponse where instance ToJSON TemplateResponse where