[Haskell-cafe] Amazon SES email issues
Yuri de Wit
ydewit at gmail.com
Fri Apr 29 15:20:11 UTC 2016
Also, make sure the time on the machine you are running this client didn't
drift too far from the server's time. If this delta crosses a threshold,
you will see similar issues.
On Fri, Apr 29, 2016 at 11:07 AM, David Johnson <djohnson.m at gmail.com>
wrote:
> I think that package is using an outdated version of the AWS Signing
> algorithm.
>
> "AWS3-HTTPS"
> I think AWS is migrating most of their APIs (who have domains / services created after a certain date) to require using the V4 Signature algorithm for all API requests.
>
> The amazonka-ses would probably work better.
>
>
> On Fri, Apr 29, 2016 at 1:45 AM, David Escobar <davidescobar at ieee.org>
> wrote:
>
>> Hi everyone,
>> I'm having issues with sending email through Amazon SES. I'm using the
>> *Network.Mail.Mime.SES* package. The error I get is:
>>
>> *email-test-exe: SESException {seStatus = Status {statusCode = 403,
>> statusMessage = "Forbidden"}, seCode = "SignatureDoesNotMatch", seMessage =
>> "The request signature we calculated does not match the signature you
>> provided. Check your AWS Secret Access Key and signing method. Consult the
>> service documentation for details.", seRequestId =
>> "8ceb250a-0dd3-11e6-892c-4fb1a14d4732"}*
>>
>> What's confusing is that I'm using the same SES settings in a Rails app
>> as well as a small Rust console program without any issues (it works from
>> the same machine too). The only thing I can think of is that with this
>> Haskell package, I haven't found where to set certain things like the port
>> number (587) and so maybe it's that? Here is a small sample app that
>> illustrates the problem. What am I missing? Thanks.
>>
>>
>>
>> *{-# LANGUAGE OverloadedStrings #-}{-# LANGUAGE QuasiQuotes #-}*
>> *module Main where*
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>>
>> *import Data.Function ((&))import GHC.Genericsimport
>> Network.HTTP.Clientimport Network.HTTP.Client.TLSimport
>> Network.Mail.Mimeimport Network.Mail.Mime.SESimport Text.Hamlet
>> (shamlet)import Text.Blaze.Html.Renderer.String (renderHtml)import
>> qualified Data.ByteString.Char8 as C8import qualified Data.Text as Timport
>> qualified Data.Text.Lazy as LTmain :: IO ()main = do manager <- newManager
>> tlsManagerSettings let sesConfig = SES { sesFrom = C8.pack
>> "de at somewhere.com <de at somewhere.com>", sesTo = [
>> C8.pack "someone.else at somewhereelse.com <someone.else at somewhereelse.com>"
>> ], sesAccessKey = "SOMEAWSACCESSKEY",
>> sesSecretKey = "ANEVENLONGERAWSSECRETKEY1234567890",
>> sesRegion = usEast1 } email = Mail { mailFrom = Address (Just
>> "David Escobar") "de at somewhere.com <de at somewhere.com>",
>> mailTo = [ Address (Just "Someone Else") "someone.else at somewhereelse.com
>> <someone.else at somewhereelse.com>" ], mailParts = [ [
>> htmlPart testEmail ] ], mailCc = [],
>> mailBcc = [], mailHeaders = [ ("subject", "Some Test
>> Email"), ("Content-Type", "text/html;
>> charset=ISO-8859-1") ] } renderSendMailSES manager sesConfig
>> emailtestEmail :: LT.TexttestEmail = let rows = [ [ "1", "2", "3" ], [
>> "4", "5", "6" ]] in renderHtml [shamlet| $doctype 5 <html>
>> <body> <table style="border: 1px solid black; border-collapse:
>> collapse; margin: 25px 0; width: 100%;"> <tr> <th
>> style="background-color: #072a2d; color: white; font-weight: bold;
>> border-right: 1px solid white; padding: 5px 10px; width: 33%;">
>> Column 1 <th style="background-color: #072a2d; color:
>> white; font-weight: bold; border-right: 1px solid white; padding: 5px 10px;
>> width: 33%;"> Column 2 <th
>> style="background-color: #072a2d; color: white; font-weight: bold;
>> border-right: 1px solid white; padding: 5px 10px; width: 33%;">
>> Column 3 $forall row <- rows <tr
>> style="background-color: #f8f9ee;"> <td style="border: 1px
>> solid black; padding: 5px 10px; text-align: left; width: 33%;">
>> #{T.pack $ row !! 0} <td style="border: 1px solid
>> black; padding: 5px 10px; text-align: left; width: 33%;">
>> #{T.pack $ row !! 1} <td style="border: 1px solid black;
>> padding: 5px 10px; text-align: left; width: 33%;">
>> #{T.pack $ row !! 2} |] & LT.pack*
>>
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>
>>
>
>
> --
> Cell: 1.630.740.8204
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160429/50eed2dc/attachment.html>
More information about the Haskell-Cafe
mailing list