Skip to the content.

Using Amazonka 2.0

by @pbrisbin on September 22, 2023

A few months ago, those of us at the intersection of Haskell and AWS received a gift. Amazonka, the de-facto AWS SDK for Haskell, released its much-anticipated 2.0 rewrite to Hackage. At Freckle, we had been testing the release candidates in a few apps, and once the official version landed we began migrating apps across Freckle in earnest.

The upgrade experience has been wonderful, primarily due to the new module organization and record naming conventions. Once a basic understanding of how it works is achieved, the SDK is intuitive and discoverable to use; far more than it used to be.

The culture at Freckle is one of strong conventions applied uniformly to cut out noise and uncertainty and streamline development. Amazonka’s newfound consistency has reinforced our own strong opinions about how to best use the library, which we’ll describe in this post in the hopes they prove useful to others.

Setting Up

We import the Amazonka module qualified and always use discover to construct an Env:

import qualified Amazonka

main :: IO ()
main = do
    env <- Amazonka.newEnv Amazonka.discover

    -- ...

Using discover ensures a consistent experience between any language’s SDK and the AWS CLI itself.

Your app will work with any of the following:

The constructed Env can be further modified to change global behaviors such as how errors are handled or to override the discovered region. For example, we make sure that Amazonka uses our app-wide logger. The documentation on the Amazonka module also contains a more detailed example.

Sending Requests

Once you have an Env, there are three ways to make requests: send, paginate, and await

-- send will make one request and give you back a response full of data
response <- runResourceT $ Amazonka.send env someRequest

-- paginate makes requests for all pages as a Conduit that yields each
responses <- runResourceT $ runConduit $ Amazonka.paginate env req .| sinkList

-- await will continually make requests until some a condition is met (such as
-- an update or create has finished) and returns an "Accept", which is just an
-- enumeration to represent if it succeeded or not (or should be retried)
accept <- runResourceT $ Amazonka.await env someWaiter someRequest

NOTE: All requests must be sent in runResourceT to satisfy their MonadResource constraint.

These un-suffixed versions will throw any Errors as exceptions (see Error Handling), but there are also Either-suffixed versions for each of these that place any Error values in Left.

Now that we have the basics down, let’s talk to some services.

Importing Services

Amazonka-2.0 did a fantastic job standardizing all its module, record, and type naming to be easily guessable if you know the AWS concepts they map to. In the sections that follow, we’ll describe how that works and show some examples. If you are familiar with AWS APIs, you may be able to use Amazonka straight away by guessing everything.

One simple way to use Amazonka is to import the top-level Amazonka.{Service}:

import Amazonka.S3

This gives you access to all possible errors, operations, and types used to interact with this service. It’s very convenient and good for simple use-cases where a small module only interacts with one AWS service and doesn’t do much else. Freckle prefers a more explicit way, which is to import specific Amazonka.{Service}.{Operation} and Amazonka.{Service}.Types.{Type} modules as necessary.

import Amazonka.S3 (_NoSuchKey, BucketName)
import Amazonka.S3.ListBuckets
import Amazonka.S3.Types.Bucket

NOTE: There are a few unavoidable times to use the top-level module, as shown above.

We’ve found that importing smaller modules, but still open, is the best balance of convenience and explicitness. Provided we keep our AWS-focused modules free of non-AWS concerns, the open imports don’t cause any problems.

Even when using more explicit imports, the documentation for the top-level service modules are an extremely good organization of all that’s available.

Operations

Every AWS API operation is implemented as a consistently-named group of types and functions in the corresponding Amazonka.{Service}.{Operation} module:

Here’s an example; notice how well all the naming aligns:

import qualified Amazonka

--     Amazonka.{Service}.{Operation}
import Amazonka.S3.ListBuckets

example :: Amazonka.Env -> IO ()
example env = do
    --                                       new{Operation}
    resp <- runResourceT $ Amazonka.send env newListBuckets

    --              {operation}Response_{field}
    print $ resp ^. listBucketsResponse_buckets

All names within an {Operation} module agree with AWS’s actual API_{Operation} documentation (modulo uniform casing and prefix changes, of course).

Types

Request and response types are of course made of nested records of other types. Most (but not all) of these types are implemented in an Amazonka.{Service}.Types.{Type} module:

Here’s how we might extend our example to make use of Bucket:

import qualified Amazonka
import Amazonka.S3.ListBuckets
import Amazonka.S3.Types.Bucket

example :: Amazonka.Env -> IO ()
example env = do
    resp <- runResourceT $ Amazonka.send env newListBuckets

    --              {Type}
    let buckets :: [Bucket]
        buckets = fromMaybe [] $ resp ^. listBucketsResponse_buckets

    --              {type}_{field}
    print $ map (^. bucket_name) buckets

Again, all names in a Types.{Type} module agree with AWS’s actual API_{Type} documentation.

Newtypes & Prisms

Amazonka is full of textual newtypes. You should generally use instances like IsString, FromJSON, ToText, etc to construct or extract these. For example:

import Amazonka.Data.Text

exampleToText :: Amazonka.Env -> IO Text
exampleToText env = do
    bucket <- getFirstBucket env
    pure $ toText $ bucket ^. bucket_name

getFirstBucket :: Amazonka.Env -> IO Bucket
getFirstBucket = {- challenge: can you write this? -}

For times you need to explicitly extract the Text (vs using toText), you should use its _{Type} prism. The prisms can be nice for composing with (.) too:

examplePrism :: Env -> IO Text
examplePrism env = do
    bucket <- getFirstBucket env
    pure $ bucket ^. bucket_name . _BucketName

Enumerations & Patterns

Here’s a little secret: all enumerations in Amazonka are newtypes over Text too.

One of the biggest headaches in Amazonka 1.x was when AWS would add a new value to some enumeration and suddenly your Amazonka-using-code would fail to parse any responses because it didn’t know about it – even if you never cared about that field to begin with! The solution in Amazonka 2.0 is very elegant: enumerations are Text values underneath, but with pattern synonyms that allow you to use them naturally in a case.

So, in Amazonka.{Service}.Types.{Enum}, you can find:

For example,

import Amazonka.CloudFormation.Types.StackStatus

prettyStackStatus :: StackStatus -> Text
prettyStackStatus = \case
    StackStatus_CREATE_COMPLETE -> "Yay created!"
    x -> "Unknown status: " <> fromStackStatus x

Error Handling

Each Amazonka.{Service} module defines a list of error prisms. These should be used with functions like handling or trying. These -ing functions are exported by Amazonka, but with one caveat: they come from lens and so add a MonadCatch constraint. At Freckle, we do not use MonadCatch and have standardized on MonadUnliftIO instead. Therefore, we import the same functions from UnliftIO.Exception.Lens (another one of my contributions):

import qualified Amazonka
import Amazonka.S3 (_NoSuchKey)
import Amazonka.S3.GetObject
import UnliftIO.Exception.Lens

example
    :: MonadUnliftIO m
    => Amazonka.Env
    -> Bucket
    -> ObjectKey
    -> m (Maybe GetObjectResponse)
example env bucket key =
  handling_ _NoSuchKey (pure Nothing) $ Just <$> send newGetObject bucket key

Not all possible errors have out-of-the box prisms defined, but it’s easy to make your own:

import Amazonka (AsError, ServiceError _MatchServiceError)
import qualified Amazonka.CloudFormation as CloudFormation
import Control.Lens (Getting)
import Data.Monoid (First)

_ThrottlingError :: AsError a => Getting (First ServiceError) a ServiceError
_ThrottlingError = _MatchServiceError CloudFormation.defaultService "Throttling"

What About MonadAWS?

Amazonka-2.0 dropped its monadic interface. All request functions (e.g. send) accept an explicit Env as their first argument. If you are of the Boring Haskell ilk, or are only using AWS in limited places in your application, this is probably preferred. However, if your App is primarily about AWS interactions, this can get very, very tedious.

At Freckle, we follow the ReaderT Design Pattern pioneered by FPComplete and RIO, albeit with our own implementation. Therefore, we made use of the MonadAWS constraint and would prefer a send function that uses an Env from the global reader context.

So, as part of moving to Amazonka-2.0, we wrote and released amazonka-mtl, which makes it possible to seamlessly have AWS effects among others in your MTL-style functions:

import Amazonka.Data.Text (ToText(..))
import Amazonka.S3.ListObjects
import Amazonka.S3.Types.Object
import Blammo.Logging
import Conduit
import Control.Lens hiding ((.=))
import Control.Monad.AWS as AWS

someAction
  :: ( MonadIO m
     , MonadLogger m
     , MonadAWS m
     , MonadReader env m
     , HasSettings env
     )
  => m ()
someAction = do
  Settings {..} <- view settingsL

  keys <-
    runConduit
      $ paginate (newListObjects settingsBucketName)
      .| concatMapC (^. listObjectsResponse_contents)
      .| concatC
      .| mapC (^. object_key . to toText)
      .| iterMC (\k -> logDebug $ k :# []) -- <-- the m here is your m!
      .| sinkList

  logInfo $ "Bucket contents" :# ["keys" .= keys]

The library implements a number of ways to satisfy the MonadAWS constraint, our preferred way being to implement HasEnv for your App type:

import qualified Control.Monad.AWS.ViaReader as AWS

data App = App
  { -- ...
  , appAWS :: AWS.Env
  }

instance AWS.HasEnv App where
  envL = lens appAWS $ \x y -> x { appAWS = y }

So you can derive it on your AppT transformer via ReaderAWS:

{-# LANGUAGE DerivingVia #-}

import Control.Monad.AWS
import Control.Monad.AWS.ViaReader

newtype AppT m a = AppT
  { -- ...
  }
  deriving newtype
    ( ...
    , MonadReader App
    )
  deriving MonadAWS via (ReaderAWS (AppT m))

Thanks

Before we go, we want to extend a huge thanks to all the Amazonka maintainers, particularly @brendanhay and @endgame on GitHub, for all their work on Amazonka and seeing this massive 2.0 release over the line.