| Copyright | (C) Richard Cook 2018 |
|---|---|
| License | MIT |
| Maintainer | rcook@rcook.org |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Network.AWS.Easy.TH
Description
This module provides Template Haskell helper functions for generating type-safe service/session wrappers for amazonka.
Documentation
Arguments
| :: Name | Name of the amazonka |
| -> String | Name of the service type to generate |
| -> String | Name of the session type to generate |
| -> Q [Dec] | Declarations for splicing into source file |
Generates type-safe AWS service and session wrapper types for use with
connect and withAWS functions
Example top-level invocation:
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
module MyApp.Services
( DynamoDBService
, DynamoDBSession
, dynamoDBService
) where
import Network.AWS.DynamoDB (dynamoDB)
import Network.AWS.Easy (wrapAWSService)
wrapAWSService 'dynamoDB "DynamoDBService" "DynamoDBSession"
This will generate boilerplate like the following:
data DynamoDBService = DynamoDBService Service
data DynamoDBSession = DynamoDBSession Session
instance ServiceClass DynamoDBService where
type TypedSession DynamoDBService = DynamoDBSession
rawService (DynamoDBService x) = x
wrappedSession = DynamoDBSession
instance SessionClass DynamoDBSession where
rawSession (DynamoDBSession x) = x
dynamoDBService :: DynamoDBService
dynamoDBService = DynamoDBService dynamoDB