{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE RecordWildCards #-}
module Smtpbz.Internal.Api
( user
, userStats
, userDomains
, userDomain
, userIPs
, userIP
, LogMessages(..)
, logMessages
, logMessage
, Unsubscribe(..)
, unsubscribe
, unsubscribeAdd
, unsubscribeRemove
, unsubscribeRemoveAll
, SmtpSend(..)
, sendSmtp
, checkEmail
, successfulCall
, debugPrintResponse
) where
import Data.Bool (bool)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as Lazy (ByteString)
import qualified Data.ByteString.Lazy.Char8 as ByteString.Lazy
import Data.Maybe (mapMaybe)
import Data.String (fromString)
import qualified Network.HTTP.Conduit as Http
import qualified Network.HTTP.Types as Http
import Text.Printf (printf)
import Smtpbz.Internal.Has (Has(..))
user :: Has smtpbz => smtpbz -> IO (Http.Response Lazy.ByteString)
user :: forall smtpbz. Has smtpbz => smtpbz -> IO (Response ByteString)
user smtpbz
smtpbz =
smtpbz -> String -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
simpleApiCall smtpbz
smtpbz String
"user"
userStats :: Has smtpbz => smtpbz -> IO (Http.Response Lazy.ByteString)
userStats :: forall smtpbz. Has smtpbz => smtpbz -> IO (Response ByteString)
userStats smtpbz
smtpbz =
smtpbz -> String -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
simpleApiCall smtpbz
smtpbz String
"user/stats"
userDomains :: Has smtpbz => smtpbz -> IO (Http.Response Lazy.ByteString)
userDomains :: forall smtpbz. Has smtpbz => smtpbz -> IO (Response ByteString)
userDomains smtpbz
smtpbz =
smtpbz -> String -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
simpleApiCall smtpbz
smtpbz String
"user/domain"
userDomain :: Has smtpbz => smtpbz -> String -> IO (Http.Response Lazy.ByteString)
userDomain :: forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
userDomain smtpbz
smtpbz String
domain =
smtpbz -> String -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
simpleApiCall smtpbz
smtpbz (String -> String -> String
forall r. PrintfType r => String -> r
printf String
"user/domain/%s" String
domain)
userIPs :: Has smtpbz => smtpbz -> IO (Http.Response Lazy.ByteString)
userIPs :: forall smtpbz. Has smtpbz => smtpbz -> IO (Response ByteString)
userIPs smtpbz
smtpbz =
smtpbz -> String -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
simpleApiCall smtpbz
smtpbz String
"user/ip"
userIP :: Has smtpbz => smtpbz -> String -> IO (Http.Response Lazy.ByteString)
userIP :: forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
userIP smtpbz
smtpbz String
ip = do
smtpbz -> String -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
simpleApiCall smtpbz
smtpbz (String -> String -> String
forall r. PrintfType r => String -> r
printf String
"user/ip/%s" String
ip)
data LogMessages = LogMessages
{ LogMessages -> Maybe Int
limit :: Maybe Int
, LogMessages -> Maybe Int
offset :: Maybe Int
, LogMessages -> Maybe ByteString
from :: Maybe ByteString
, LogMessages -> Maybe ByteString
to :: Maybe ByteString
, LogMessages -> Maybe Bool
isOpen :: Maybe Bool
, LogMessages -> Maybe ByteString
tag :: Maybe ByteString
} deriving (Int -> LogMessages -> String -> String
[LogMessages] -> String -> String
LogMessages -> String
(Int -> LogMessages -> String -> String)
-> (LogMessages -> String)
-> ([LogMessages] -> String -> String)
-> Show LogMessages
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> LogMessages -> String -> String
showsPrec :: Int -> LogMessages -> String -> String
$cshow :: LogMessages -> String
show :: LogMessages -> String
$cshowList :: [LogMessages] -> String -> String
showList :: [LogMessages] -> String -> String
Show, LogMessages -> LogMessages -> Bool
(LogMessages -> LogMessages -> Bool)
-> (LogMessages -> LogMessages -> Bool) -> Eq LogMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogMessages -> LogMessages -> Bool
== :: LogMessages -> LogMessages -> Bool
$c/= :: LogMessages -> LogMessages -> Bool
/= :: LogMessages -> LogMessages -> Bool
Eq)
logMessages :: Has smtpbz => smtpbz -> LogMessages -> IO (Http.Response Lazy.ByteString)
logMessages :: forall smtpbz.
Has smtpbz =>
smtpbz -> LogMessages -> IO (Response ByteString)
logMessages smtpbz
smtpbz LogMessages {Maybe Bool
Maybe Int
Maybe ByteString
$sel:limit:LogMessages :: LogMessages -> Maybe Int
$sel:offset:LogMessages :: LogMessages -> Maybe Int
$sel:from:LogMessages :: LogMessages -> Maybe ByteString
$sel:to:LogMessages :: LogMessages -> Maybe ByteString
$sel:isOpen:LogMessages :: LogMessages -> Maybe Bool
$sel:tag:LogMessages :: LogMessages -> Maybe ByteString
limit :: Maybe Int
offset :: Maybe Int
from :: Maybe ByteString
to :: Maybe ByteString
isOpen :: Maybe Bool
tag :: Maybe ByteString
..} = do
Request
req <- smtpbz -> String -> IO Request
forall smtpbz. Has smtpbz => smtpbz -> String -> IO Request
prepareApiCall smtpbz
smtpbz String
"log/message"
smtpbz -> Request -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> Request -> IO (Response ByteString)
callApi smtpbz
smtpbz ([(ByteString, Maybe ByteString)] -> Request -> Request
Http.setQueryString [(ByteString, Maybe ByteString)]
params Request
req)
where
params :: [(ByteString, Maybe ByteString)]
params =
[ (ByteString
"limit", (Int -> ByteString) -> Maybe Int -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> ByteString
forall a. IsString a => String -> a
fromString (String -> ByteString) -> (Int -> String) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) Maybe Int
limit)
, (ByteString
"offset", (Int -> ByteString) -> Maybe Int -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> ByteString
forall a. IsString a => String -> a
fromString (String -> ByteString) -> (Int -> String) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) Maybe Int
offset)
, (ByteString
"from", Maybe ByteString
from)
, (ByteString
"to", Maybe ByteString
to)
, (ByteString
"is_open", (Bool -> ByteString) -> Maybe Bool -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString -> ByteString -> Bool -> ByteString
forall a. a -> a -> Bool -> a
bool ByteString
"0" ByteString
"1") Maybe Bool
isOpen)
, (ByteString
"tag", Maybe ByteString
tag)
]
logMessage :: Has smtpbz => smtpbz -> String -> IO (Http.Response Lazy.ByteString)
logMessage :: forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
logMessage smtpbz
smtpbz String
messageID = do
smtpbz -> String -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
simpleApiCall smtpbz
smtpbz (String -> String -> String
forall r. PrintfType r => String -> r
printf String
"log/message/%s" String
messageID)
data Unsubscribe = Unsubscribe
{ Unsubscribe -> Maybe Int
limit :: Maybe Int
, Unsubscribe -> Maybe Int
offset :: Maybe Int
, Unsubscribe -> Maybe ByteString
address :: Maybe ByteString
, Unsubscribe -> Maybe ByteString
reason :: Maybe ByteString
} deriving (Int -> Unsubscribe -> String -> String
[Unsubscribe] -> String -> String
Unsubscribe -> String
(Int -> Unsubscribe -> String -> String)
-> (Unsubscribe -> String)
-> ([Unsubscribe] -> String -> String)
-> Show Unsubscribe
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Unsubscribe -> String -> String
showsPrec :: Int -> Unsubscribe -> String -> String
$cshow :: Unsubscribe -> String
show :: Unsubscribe -> String
$cshowList :: [Unsubscribe] -> String -> String
showList :: [Unsubscribe] -> String -> String
Show, Unsubscribe -> Unsubscribe -> Bool
(Unsubscribe -> Unsubscribe -> Bool)
-> (Unsubscribe -> Unsubscribe -> Bool) -> Eq Unsubscribe
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Unsubscribe -> Unsubscribe -> Bool
== :: Unsubscribe -> Unsubscribe -> Bool
$c/= :: Unsubscribe -> Unsubscribe -> Bool
/= :: Unsubscribe -> Unsubscribe -> Bool
Eq)
unsubscribe :: Has smtpbz => smtpbz -> Unsubscribe -> IO (Http.Response Lazy.ByteString)
unsubscribe :: forall smtpbz.
Has smtpbz =>
smtpbz -> Unsubscribe -> IO (Response ByteString)
unsubscribe smtpbz
smtpbz Unsubscribe {Maybe Int
Maybe ByteString
$sel:limit:Unsubscribe :: Unsubscribe -> Maybe Int
$sel:offset:Unsubscribe :: Unsubscribe -> Maybe Int
$sel:address:Unsubscribe :: Unsubscribe -> Maybe ByteString
$sel:reason:Unsubscribe :: Unsubscribe -> Maybe ByteString
limit :: Maybe Int
offset :: Maybe Int
address :: Maybe ByteString
reason :: Maybe ByteString
..} = do
Request
req <- smtpbz -> String -> IO Request
forall smtpbz. Has smtpbz => smtpbz -> String -> IO Request
prepareApiCall smtpbz
smtpbz String
"unsubscribe"
smtpbz -> Request -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> Request -> IO (Response ByteString)
callApi smtpbz
smtpbz ([(ByteString, Maybe ByteString)] -> Request -> Request
Http.setQueryString [(ByteString, Maybe ByteString)]
params Request
req)
where
params :: [(ByteString, Maybe ByteString)]
params =
[ (ByteString
"limit", (Int -> ByteString) -> Maybe Int -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> ByteString
forall a. IsString a => String -> a
fromString (String -> ByteString) -> (Int -> String) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) Maybe Int
limit)
, (ByteString
"offset", (Int -> ByteString) -> Maybe Int -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> ByteString
forall a. IsString a => String -> a
fromString (String -> ByteString) -> (Int -> String) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show) Maybe Int
offset)
, (ByteString
"address", Maybe ByteString
address)
, (ByteString
"reason", Maybe ByteString
reason)
]
unsubscribeAdd :: Has smtpbz => smtpbz -> ByteString -> IO (Http.Response Lazy.ByteString)
unsubscribeAdd :: forall smtpbz.
Has smtpbz =>
smtpbz -> ByteString -> IO (Response ByteString)
unsubscribeAdd smtpbz
smtpbz ByteString
address = do
Request
req <- smtpbz -> String -> IO Request
forall smtpbz. Has smtpbz => smtpbz -> String -> IO Request
prepareApiCall smtpbz
smtpbz String
"unsubscribe/add"
smtpbz -> Request -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> Request -> IO (Response ByteString)
callApi smtpbz
smtpbz ([(ByteString, ByteString)] -> Request -> Request
Http.urlEncodedBody [(ByteString, ByteString)]
params Request
req)
where
params :: [(ByteString, ByteString)]
params =
[ (ByteString
"address", ByteString
address)
]
unsubscribeRemove :: Has smtpbz => smtpbz -> ByteString -> IO (Http.Response Lazy.ByteString)
unsubscribeRemove :: forall smtpbz.
Has smtpbz =>
smtpbz -> ByteString -> IO (Response ByteString)
unsubscribeRemove smtpbz
smtpbz ByteString
address = do
Request
req <- smtpbz -> String -> IO Request
forall smtpbz. Has smtpbz => smtpbz -> String -> IO Request
prepareApiCall smtpbz
smtpbz String
"unsubscribe/remove"
smtpbz -> Request -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> Request -> IO (Response ByteString)
callApi smtpbz
smtpbz ([(ByteString, ByteString)] -> Request -> Request
Http.urlEncodedBody [(ByteString, ByteString)]
params Request
req)
where
params :: [(ByteString, ByteString)]
params =
[ (ByteString
"address", ByteString
address)
]
unsubscribeRemoveAll :: Has smtpbz => smtpbz -> IO (Http.Response Lazy.ByteString)
unsubscribeRemoveAll :: forall smtpbz. Has smtpbz => smtpbz -> IO (Response ByteString)
unsubscribeRemoveAll smtpbz
smtpbz = do
Request
req <- smtpbz -> String -> IO Request
forall smtpbz. Has smtpbz => smtpbz -> String -> IO Request
prepareApiCall smtpbz
smtpbz String
"unsubscribe/removeall"
smtpbz -> Request -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> Request -> IO (Response ByteString)
callApi smtpbz
smtpbz ([(ByteString, ByteString)] -> Request -> Request
Http.urlEncodedBody [] Request
req)
data SmtpSend = SmtpSend
{ SmtpSend -> ByteString
from :: ByteString
, SmtpSend -> Maybe ByteString
name :: Maybe ByteString
, SmtpSend -> ByteString
subject :: ByteString
, SmtpSend -> ByteString
to :: ByteString
, SmtpSend -> Maybe ByteString
replyTo :: Maybe ByteString
, SmtpSend -> ByteString
html :: ByteString
, SmtpSend -> Maybe ByteString
text :: Maybe ByteString
} deriving (Int -> SmtpSend -> String -> String
[SmtpSend] -> String -> String
SmtpSend -> String
(Int -> SmtpSend -> String -> String)
-> (SmtpSend -> String)
-> ([SmtpSend] -> String -> String)
-> Show SmtpSend
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> SmtpSend -> String -> String
showsPrec :: Int -> SmtpSend -> String -> String
$cshow :: SmtpSend -> String
show :: SmtpSend -> String
$cshowList :: [SmtpSend] -> String -> String
showList :: [SmtpSend] -> String -> String
Show, SmtpSend -> SmtpSend -> Bool
(SmtpSend -> SmtpSend -> Bool)
-> (SmtpSend -> SmtpSend -> Bool) -> Eq SmtpSend
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SmtpSend -> SmtpSend -> Bool
== :: SmtpSend -> SmtpSend -> Bool
$c/= :: SmtpSend -> SmtpSend -> Bool
/= :: SmtpSend -> SmtpSend -> Bool
Eq)
sendSmtp :: Has smtpbz => smtpbz -> SmtpSend -> IO (Http.Response Lazy.ByteString)
sendSmtp :: forall smtpbz.
Has smtpbz =>
smtpbz -> SmtpSend -> IO (Response ByteString)
sendSmtp smtpbz
smtpbz SmtpSend {Maybe ByteString
ByteString
$sel:from:SmtpSend :: SmtpSend -> ByteString
$sel:name:SmtpSend :: SmtpSend -> Maybe ByteString
$sel:subject:SmtpSend :: SmtpSend -> ByteString
$sel:to:SmtpSend :: SmtpSend -> ByteString
$sel:replyTo:SmtpSend :: SmtpSend -> Maybe ByteString
$sel:html:SmtpSend :: SmtpSend -> ByteString
$sel:text:SmtpSend :: SmtpSend -> Maybe ByteString
from :: ByteString
name :: Maybe ByteString
subject :: ByteString
to :: ByteString
replyTo :: Maybe ByteString
html :: ByteString
text :: Maybe ByteString
..} = do
Request
req <- smtpbz -> String -> IO Request
forall smtpbz. Has smtpbz => smtpbz -> String -> IO Request
prepareApiCall smtpbz
smtpbz String
"smtp/send"
smtpbz -> Request -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> Request -> IO (Response ByteString)
callApi smtpbz
smtpbz ([(ByteString, ByteString)] -> Request -> Request
Http.urlEncodedBody ([(ByteString, Maybe ByteString)] -> [(ByteString, ByteString)]
forall a b. [(a, Maybe b)] -> [(a, b)]
collapse [(ByteString, Maybe ByteString)]
params) Request
req)
where
params :: [(ByteString, Maybe ByteString)]
params =
[ (ByteString
"from", ByteString -> Maybe ByteString
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
from)
, (ByteString
"name", Maybe ByteString
name)
, (ByteString
"subject", ByteString -> Maybe ByteString
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
subject)
, (ByteString
"to", ByteString -> Maybe ByteString
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
to)
, (ByteString
"reply", Maybe ByteString
replyTo)
, (ByteString
"html", ByteString -> Maybe ByteString
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
html)
, (ByteString
"text", Maybe ByteString
text)
]
checkEmail :: Has smtpbz => smtpbz -> String -> IO (Http.Response Lazy.ByteString)
checkEmail :: forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
checkEmail smtpbz
smtpbz String
email =
smtpbz -> String -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
simpleApiCall smtpbz
smtpbz (String -> String -> String
forall r. PrintfType r => String -> r
printf String
"check/email/%s" String
email)
simpleApiCall :: Has smtpbz => smtpbz -> String -> IO (Http.Response Lazy.ByteString)
simpleApiCall :: forall smtpbz.
Has smtpbz =>
smtpbz -> String -> IO (Response ByteString)
simpleApiCall smtpbz
smtpbz String
path = do
Request
req <- smtpbz -> String -> IO Request
forall smtpbz. Has smtpbz => smtpbz -> String -> IO Request
prepareApiCall smtpbz
smtpbz String
path
smtpbz -> Request -> IO (Response ByteString)
forall smtpbz.
Has smtpbz =>
smtpbz -> Request -> IO (Response ByteString)
callApi smtpbz
smtpbz Request
req
prepareApiCall :: Has smtpbz => smtpbz -> String -> IO Http.Request
prepareApiCall :: forall smtpbz. Has smtpbz => smtpbz -> String -> IO Request
prepareApiCall smtpbz
smtpbz String
path = do
Request
req <- String -> IO Request
forall (m :: * -> *). MonadThrow m => String -> m Request
Http.parseRequest (String -> Text -> String -> String
forall r. PrintfType r => String -> r
printf String
"%s/%s" (smtpbz -> Text
forall t. Has t => t -> Text
baseUrl smtpbz
smtpbz) String
path)
Request -> IO Request
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Request
req
{ Http.requestHeaders = ("Authorization", apiKey smtpbz) : Http.requestHeaders req
}
callApi :: Has smtpbz => smtpbz -> Http.Request -> IO (Http.Response Lazy.ByteString)
callApi :: forall smtpbz.
Has smtpbz =>
smtpbz -> Request -> IO (Response ByteString)
callApi smtpbz
smtpbz Request
req =
Request -> Manager -> IO (Response ByteString)
forall (m :: * -> *).
MonadIO m =>
Request -> Manager -> m (Response ByteString)
Http.httpLbs Request
req (smtpbz -> Manager
forall t. Has t => t -> Manager
httpMan smtpbz
smtpbz)
successfulCall :: Http.Response Lazy.ByteString -> Bool
successfulCall :: Response ByteString -> Bool
successfulCall Response ByteString
res =
case Response ByteString -> Status
forall body. Response body -> Status
Http.responseStatus Response ByteString
res of
Status
st ->
Status
Http.status200 Status -> Status -> Bool
forall a. Ord a => a -> a -> Bool
<= Status
st Bool -> Bool -> Bool
&& Status
st Status -> Status -> Bool
forall a. Ord a => a -> a -> Bool
< Status
Http.status300
debugPrintResponse :: Http.Response Lazy.ByteString -> IO ()
debugPrintResponse :: Response ByteString -> IO ()
debugPrintResponse =
ByteString -> IO ()
ByteString.Lazy.putStrLn (ByteString -> IO ())
-> (Response ByteString -> ByteString)
-> Response ByteString
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Response ByteString -> ByteString
forall body. Response body -> body
Http.responseBody
collapse :: [(a, Maybe b)] -> [(a, b)]
collapse :: forall a b. [(a, Maybe b)] -> [(a, b)]
collapse =
((a, Maybe b) -> Maybe (a, b)) -> [(a, Maybe b)] -> [(a, b)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (a, Maybe b) -> Maybe (a, b)
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => (a, m a) -> m (a, a)
sequence