module Aws.Aws
(
LogLevel(..)
, Logger
, defaultLog
, Configuration(..)
, baseConfiguration
, dbgConfiguration
, aws
, awsRef
, simpleAws
, simpleAwsRef
, unsafeAws
, unsafeAwsRef
, awsUri
)
where
import Aws.Core
import Control.Applicative
import Control.Monad.Trans (MonadIO(liftIO))
import Data.Attempt (attemptIO)
import Data.Conduit (runResourceT)
import Data.IORef
import Data.Monoid
import System.IO (stderr)
import qualified Control.Exception as E
import qualified Data.ByteString as B
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified Network.HTTP.Conduit as HTTP
data LogLevel
= Debug
| Info
| Warning
| Error
deriving (Show, Eq, Ord)
type Logger = LogLevel -> T.Text -> IO ()
defaultLog :: LogLevel -> Logger
defaultLog minLevel lev t | lev >= minLevel = T.hPutStrLn stderr $ T.concat [T.pack $ show lev, ": ", t]
| otherwise = return ()
data Configuration
= Configuration {
timeInfo :: TimeInfo
, credentials :: Credentials
, logger :: Logger
}
baseConfiguration :: MonadIO io => io Configuration
baseConfiguration = do
Just cr <- loadCredentialsDefault
return Configuration {
timeInfo = Timestamp
, credentials = cr
, logger = defaultLog Warning
}
dbgConfiguration :: MonadIO io => io Configuration
dbgConfiguration = do
c <- baseConfiguration
return c { logger = defaultLog Debug }
aws :: (Transaction r a, MonadIO io)
=> Configuration -> ServiceConfiguration r -> HTTP.Manager -> r -> io (Response (ResponseMetadata a) a)
aws = unsafeAws
awsRef :: (Transaction r a, MonadIO io)
=> Configuration -> ServiceConfiguration r -> HTTP.Manager -> IORef (ResponseMetadata a) -> r -> io a
awsRef = unsafeAwsRef
simpleAws :: (Transaction r a, MonadIO io)
=> Configuration -> ServiceConfiguration r -> r -> io (Response (ResponseMetadata a) a)
simpleAws cfg scfg request = liftIO $ HTTP.withManager $ \manager -> aws cfg scfg manager request
simpleAwsRef :: (Transaction r a, MonadIO io)
=> Configuration -> ServiceConfiguration r -> IORef (ResponseMetadata a) -> r -> io a
simpleAwsRef cfg scfg metadataRef request = liftIO $ HTTP.withManager $
\manager -> awsRef cfg scfg manager metadataRef request
unsafeAws
:: (ResponseConsumer r a,
Monoid (ResponseMetadata a),
SignQuery r,
MonadIO io) =>
Configuration -> ServiceConfiguration r -> HTTP.Manager -> r -> io (Response (ResponseMetadata a) a)
unsafeAws cfg scfg manager request = liftIO $ do
metadataRef <- newIORef mempty
resp <- attemptIO (id :: E.SomeException -> E.SomeException) $
unsafeAwsRef cfg scfg manager metadataRef request
metadata <- readIORef metadataRef
return $ Response metadata resp
unsafeAwsRef
:: (ResponseConsumer r a,
Monoid (ResponseMetadata a),
SignQuery r,
MonadIO io) =>
Configuration -> ServiceConfiguration r -> HTTP.Manager -> IORef (ResponseMetadata a) -> r -> io a
unsafeAwsRef cfg info manager metadataRef request = liftIO $ do
sd <- signatureData <$> timeInfo <*> credentials $ cfg
let q = signQuery request info sd
logger cfg Debug $ T.pack $ "String to sign: " ++ show (sqStringToSign q)
let httpRequest = queryToHttpRequest q
logger cfg Debug $ T.pack $ "Host: " ++ show (HTTP.host httpRequest)
resp <- runResourceT $ do
HTTP.Response status _ headers body <- HTTP.http httpRequest manager
responseConsumer request metadataRef status headers body
return resp
awsUri :: (SignQuery request, MonadIO io)
=> Configuration -> ServiceConfiguration request -> request -> io B.ByteString
awsUri cfg info request = liftIO $ do
let ti = timeInfo cfg
cr = credentials cfg
sd <- signatureData ti cr
let q = signQuery request info sd
logger cfg Debug $ T.pack $ "String to sign: " ++ show (sqStringToSign q)
return $ queryToUri q