snaplet-ses-html-0.1.1.0: Snaplet for the ses-html package

Safe HaskellNone
LanguageHaskell2010

Snap.Snaplet.SES

Contents

Synopsis

Initialization

initAWSKeys :: SnapletInit a AWSKeys Source

Initialize snaplet

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
{-# LANGUAGE TemplateHaskell   #-}
module Main ( main ) where

import           Control.Lens
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy.Char8 as BL8
import           Snap
import           Snap.Snaplet.SES

data App = App {
   _awsKeys :: Snaplet AWSKeys
}

makeLenses ''App

initApp :: SnapletInit App App
initApp = makeSnaplet "name" "description" Nothing $ do
            _awsKeys <- nestSnaplet "ses-html" awsKeys initAWSKeys
            addRoutes [("/", handleKeys)]
            return App {..}
  where
    handleKeys = method GET $ do
      with awsKeys $ withKeys $ liftIO . print
      result <- with awsKeys $ sendEmail ["david@solidtranslate.com"] "cookie-crisp" "<h1>TEST</h1>"
      liftIO $ print result
      writeBS "done"

main :: IO ()
main = do (_, app, _) <- runSnaplet Nothing initApp
          httpServe config app
  where
    config = setAccessLog ConfigNoLog $
             setErrorLog ConfigNoLog $
             defaultConfig

./snaplets/ses-html/devel.cfg

public = "publickey"
secret = "secretkey"
region = "us-east-1"
sender = "sender@verifiedaddress.com"

sendEmail Source

Arguments

:: HasAWSKeys m 
=> To

Who the email is intended for

-> Subject

email Subject

-> ByteString

email Body

-> m SESResult 

Send a ByteString of HTML from a Snap Handler

sendEmailBlaze Source

Arguments

:: HasAWSKeys m 
=> To

Who the email is intended for

-> Subject

Email Subject

-> Html

Email Body

-> m SESResult 

Send Blaze email from a snap handler

withKeys Source

Arguments

:: HasAWSKeys m 
=> (AWSKeys -> IO a)

Function operating on Keys

-> m a 

Helper function for operating on AWSKeys inside of HasAWSKeys constrained Monads

Types

data AWSKeys Source

Type to hold AWS Config Information

Constructors

AWSKeys 

Fields

publicKey :: PublicKey

AWS Public Key

secretKey :: SecretKey

AWS Secret Key

region :: Region

AWS Region Key

sender :: Text

AWS Verified Sender Email

class MonadIO m => HasAWSKeys m where Source

Class to allow extraction of AWSKeys from arbitrary Monads constrained by MonadIO

Methods

getKeys :: m AWSKeys Source

Module Re-export