| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Control.Monad.AWS.ViaReader
Description
DerivingVia machinery for adding Amazonka functionality to a reader-like
transformer
This is useful when you have a ReaderT-IO-like stack implemented with an
AppT wrapper to which you will add the MonadAWS instance:
newtype AppT m a = AppT -- ... deriving MonadAWS via (ReaderAWS (AppT m))
Complete example:
{-# LANGUAGE DerivingVia #-}
module Main (main) where
import qualified Amazonka
import Control.Lens
import Control.Monad.AWS
import Control.Monad.AWS.ViaReader
import Control.Monad.Reader
import Control.Monad.Trans.Resource
data App = App
{ -- ...
, appAWS :: Env'
}
instance HasEnv App where
envL = lens appAWS $ x y -> x { appAWS = y }
newtype AppT m a = AppT
{ unAppT :: ReaderT App (ResourceT m) a
}
deriving newtype
( Functor
, Applicative
, Monad
, MonadIO
, MonadUnliftIO
, MonadResource
, MonadReader App
)
deriving MonadAWS via (ReaderAWS (AppT m))
runAppT :: MonadUnliftIO m => AppT m a -> App -> m a
runAppT f app = runResourceT $ runReaderT (unAppT f) app
main :: IO ()
main = do
app <- undefined
runAppT someAction app
someAction :: (MonadIO m, MonadAWS m) => m ()
someAction = do
resp <- send newListBuckets
liftIO $ print resp
Documentation
An environment with auth credentials. Most AWS requests need one
of these, and you can create one with newEnv.
newtype ReaderAWS m a Source #
Since: 0.1.0.0
Constructors
| ReaderAWS | |
Fields
| |
Instances
| MonadReader env m => MonadReader env (ReaderAWS m) Source # | |
| (MonadResource m, MonadReader env m, HasEnv env) => MonadAWS (ReaderAWS m) Source # | |
Defined in Control.Monad.AWS.ViaReader Methods sendEither :: (AWSRequest a, Typeable a, Typeable (AWSResponse a)) => a -> ReaderAWS m (Either Error (AWSResponse a)) Source # awaitEither :: (AWSRequest a, Typeable a) => Wait a -> a -> ReaderAWS m (Either Error Accept) Source # withAuth :: (AuthEnv -> ReaderAWS m a) -> ReaderAWS m a Source # localEnv :: (Env -> Env) -> ReaderAWS m a -> ReaderAWS m a Source # | |
| MonadIO m => MonadIO (ReaderAWS m) Source # | |
Defined in Control.Monad.AWS.ViaReader | |
| Applicative m => Applicative (ReaderAWS m) Source # | |
Defined in Control.Monad.AWS.ViaReader | |
| Functor m => Functor (ReaderAWS m) Source # | |
| Monad m => Monad (ReaderAWS m) Source # | |
| MonadResource m => MonadResource (ReaderAWS m) Source # | |
Defined in Control.Monad.AWS.ViaReader Methods liftResourceT :: ResourceT IO a -> ReaderAWS m a # | |