module Aws.Aws
(
LogLevel(..)
, Logger
, defaultLog
, Configuration(..)
, baseConfiguration
, dbgConfiguration
, aws
, awsRef
, pureAws
, memoryAws
, simpleAws
, unsafeAws
, unsafeAwsRef
, awsUri
, awsIteratedSource
, awsIteratedSource'
, awsIteratedList
, awsIteratedList'
)
where
import Aws.Core
import Control.Applicative
import qualified Control.Exception.Lifted as E
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans
import Control.Monad.Trans.Resource
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
import qualified Data.CaseInsensitive as CI
import qualified Data.Conduit as C
import qualified Data.Conduit.List as CL
import Data.IORef
import Data.Monoid
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.IO as T
import qualified Network.HTTP.Conduit as HTTP
import System.IO (stderr)
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 = liftIO $ do
cr <- loadCredentialsDefault
case cr of
Nothing -> E.throw $ NoCredentialsException "could not locate aws credentials"
Just cr' -> 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)
=> Configuration
-> ServiceConfiguration r NormalQuery
-> HTTP.Manager
-> r
-> ResourceT IO (Response (ResponseMetadata a) a)
aws = unsafeAws
awsRef :: (Transaction r a)
=> Configuration
-> ServiceConfiguration r NormalQuery
-> HTTP.Manager
-> IORef (ResponseMetadata a)
-> r
-> ResourceT IO a
awsRef = unsafeAwsRef
pureAws :: (Transaction r a)
=> Configuration
-> ServiceConfiguration r NormalQuery
-> HTTP.Manager
-> r
-> ResourceT IO a
pureAws cfg scfg mgr req = readResponseIO =<< aws cfg scfg mgr req
memoryAws :: (Transaction r a, AsMemoryResponse a, MonadIO io)
=> Configuration
-> ServiceConfiguration r NormalQuery
-> HTTP.Manager
-> r
-> io (MemoryResponse a)
memoryAws cfg scfg mgr req = liftIO $ runResourceT $ loadToMemory =<< readResponseIO =<< aws cfg scfg mgr req
simpleAws :: (Transaction r a, AsMemoryResponse a, MonadIO io)
=> Configuration
-> ServiceConfiguration r NormalQuery
-> r
-> io (MemoryResponse a)
simpleAws cfg scfg request
= liftIO $ HTTP.withManager $ \manager ->
loadToMemory =<< readResponseIO =<< aws cfg scfg manager request
unsafeAws
:: (ResponseConsumer r a,
Monoid (ResponseMetadata a),
Loggable (ResponseMetadata a),
SignQuery r) =>
Configuration -> ServiceConfiguration r NormalQuery -> HTTP.Manager -> r -> ResourceT IO (Response (ResponseMetadata a) a)
unsafeAws cfg scfg manager request = do
metadataRef <- liftIO $ newIORef mempty
let catchAll :: ResourceT IO a -> ResourceT IO (Either E.SomeException a)
catchAll = E.handle (return . Left) . fmap Right
resp <- catchAll $
unsafeAwsRef cfg scfg manager metadataRef request
metadata <- liftIO $ readIORef metadataRef
liftIO $ logger cfg Info $ "Response metadata: " `mappend` toLogText metadata
return $ Response metadata resp
unsafeAwsRef
:: (ResponseConsumer r a,
Monoid (ResponseMetadata a),
SignQuery r) =>
Configuration -> ServiceConfiguration r NormalQuery -> HTTP.Manager -> IORef (ResponseMetadata a) -> r -> ResourceT IO a
unsafeAwsRef cfg info manager metadataRef request = do
sd <- liftIO $ signatureData <$> timeInfo <*> credentials $ cfg
let !q = signQuery request info sd
let logDebug = liftIO . logger cfg Debug . T.pack
logDebug $ "String to sign: " ++ show (sqStringToSign q)
!httpRequest <- liftIO $ queryToHttpRequest q
logDebug $ "Host: " ++ show (HTTP.host httpRequest)
logDebug $ "Path: " ++ show (HTTP.path httpRequest)
logDebug $ "Query string: " ++ show (HTTP.queryString httpRequest)
case HTTP.requestBody httpRequest of
HTTP.RequestBodyLBS lbs -> logDebug $ "Body: " ++ show (L.take 1000 lbs)
HTTP.RequestBodyBS bs -> logDebug $ "Body: " ++ show (B.take 1000 bs)
_ -> return ()
hresp <- HTTP.http httpRequest manager
logDebug $ "Response status: " ++ show (HTTP.responseStatus hresp)
forM_ (HTTP.responseHeaders hresp) $ \(hname,hvalue) -> liftIO $
logger cfg Debug $ T.decodeUtf8 $ "Response header '" `mappend` CI.original hname `mappend` "': '" `mappend` hvalue `mappend` "'"
responseConsumer request metadataRef hresp
awsUri :: (SignQuery request, MonadIO io)
=> Configuration -> ServiceConfiguration request UriOnlyQuery -> 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
awsIteratedSource
:: (IteratedTransaction r a)
=> Configuration
-> ServiceConfiguration r NormalQuery
-> HTTP.Manager
-> r
-> C.Producer (ResourceT IO) (Response (ResponseMetadata a) a)
awsIteratedSource cfg scfg manager req_ = awsIteratedSource' run req_
where
run r = do
res <- aws cfg scfg manager r
a <- readResponseIO res
return (a, res)
awsIteratedList
:: (IteratedTransaction r a, ListResponse a i)
=> Configuration
-> ServiceConfiguration r NormalQuery
-> HTTP.Manager
-> r
-> C.Producer (ResourceT IO) i
awsIteratedList cfg scfg manager req = awsIteratedList' run req
where
run r = readResponseIO =<< aws cfg scfg manager r
awsIteratedSource'
:: (Monad m, IteratedTransaction r a)
=> (r -> m (a, b))
-> r
-> C.Producer m b
awsIteratedSource' run r0 = go r0
where
go q = do
(a, b) <- lift $ run q
C.yield b
case nextIteratedRequest q a of
Nothing -> return ()
Just q' -> go q'
awsIteratedList'
:: (Monad m, IteratedTransaction r b, ListResponse b c)
=> (r -> m b)
-> r
-> C.Producer m c
awsIteratedList' run r0 =
awsIteratedSource' run' r0 C.=$=
CL.concatMap listResponse
where
dupl a = (a,a)
run' r = dupl `liftM` run r