{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-}
module Network.DO.Spaces.Types
(
SpacesT(..)
, runSpacesT
, Spaces(..)
, MonadSpaces
, Action(..)
, CredentialSource(..)
, Profile
, AccessKey(..)
, SecretKey(..)
, Object(..)
, mkObject
, Bucket(..)
, mkBucket
, BucketInfo(..)
, OwnerID(..)
, DisplayName
, Owner(..)
, ObjectInfo(..)
, ObjectMetadata(..)
, ETag
, SpacesRequest(..)
, SpacesResponse(..)
, SpacesRequestBuilder(..)
, SpacesMetadata(..)
, WithMetadata(..)
, RawResponse(..)
, BodyBS
, Method(..)
, Region(..)
, RequestID
, CacheControl
, ContentDisposition
, ContentEncoding
, UserMetadata
, UploadHeaders(..)
, CannedACL(..)
, CORSRule(..)
, mkCORSRule
, Grant(..)
, Permission(..)
, Grantee(..)
, ACLResponse(..)
, LifecycleRule(..)
, LifecycleExpiration(..)
, LifecycleID(..)
, mkLifecycleID
, Canonicalized(..)
, Computed(..)
, StringToSign
, Hashed
, Signature
, Credentials
, Authorization
, uncompute
, SpacesException
, ClientException(..)
, APIException(..)
, Days
) where
import Conduit ( ConduitT, MonadUnliftIO )
import Control.Exception
( Exception(toException, fromException)
, SomeException
)
import Control.Monad.Catch ( MonadCatch
, MonadThrow(throwM)
)
import Control.Monad.IO.Class ( MonadIO )
import Control.Monad.Reader ( MonadReader
, ReaderT(ReaderT, runReaderT)
)
import Data.ByteString ( ByteString )
import qualified Data.ByteString.Char8 as C
import qualified Data.ByteString.Lazy as LB
import qualified Data.CaseInsensitive as CI
import Data.Char ( isAlpha, isDigit, toLower )
import Data.Containers.ListUtils ( nubOrd )
import Data.Data ( Typeable )
import qualified Data.Generics.Product.Fields as GL
import Data.Ix ( inRange )
import Data.Kind ( Type )
import Data.Text ( Text )
import qualified Data.Text as T
import Data.Time ( UTCTime )
import Data.Typeable ( cast )
import Data.Word ( Word16 )
import GHC.Generics ( Generic )
import Network.HTTP.Client.Conduit
( HasHttpManager(..)
, Manager
, Request
, RequestBody
)
import Network.HTTP.Types ( Header, HeaderName, Query )
import Network.HTTP.Types.Status ( Status )
import Network.Mime ( MimeType )
import Web.HttpApiData ( ToHttpApiData )
newtype SpacesT m a = SpacesT (ReaderT Spaces m a)
deriving stock ( (forall x. SpacesT m a -> Rep (SpacesT m a) x)
-> (forall x. Rep (SpacesT m a) x -> SpacesT m a)
-> Generic (SpacesT m a)
forall x. Rep (SpacesT m a) x -> SpacesT m a
forall x. SpacesT m a -> Rep (SpacesT m a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (m :: * -> *) a x. Rep (SpacesT m a) x -> SpacesT m a
forall (m :: * -> *) a x. SpacesT m a -> Rep (SpacesT m a) x
$cto :: forall (m :: * -> *) a x. Rep (SpacesT m a) x -> SpacesT m a
$cfrom :: forall (m :: * -> *) a x. SpacesT m a -> Rep (SpacesT m a) x
Generic )
deriving newtype ( a -> SpacesT m b -> SpacesT m a
(a -> b) -> SpacesT m a -> SpacesT m b
(forall a b. (a -> b) -> SpacesT m a -> SpacesT m b)
-> (forall a b. a -> SpacesT m b -> SpacesT m a)
-> Functor (SpacesT m)
forall a b. a -> SpacesT m b -> SpacesT m a
forall a b. (a -> b) -> SpacesT m a -> SpacesT m b
forall (m :: * -> *) a b.
Functor m =>
a -> SpacesT m b -> SpacesT m a
forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> SpacesT m a -> SpacesT m b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> SpacesT m b -> SpacesT m a
$c<$ :: forall (m :: * -> *) a b.
Functor m =>
a -> SpacesT m b -> SpacesT m a
fmap :: (a -> b) -> SpacesT m a -> SpacesT m b
$cfmap :: forall (m :: * -> *) a b.
Functor m =>
(a -> b) -> SpacesT m a -> SpacesT m b
Functor, Functor (SpacesT m)
a -> SpacesT m a
Functor (SpacesT m)
-> (forall a. a -> SpacesT m a)
-> (forall a b. SpacesT m (a -> b) -> SpacesT m a -> SpacesT m b)
-> (forall a b c.
(a -> b -> c) -> SpacesT m a -> SpacesT m b -> SpacesT m c)
-> (forall a b. SpacesT m a -> SpacesT m b -> SpacesT m b)
-> (forall a b. SpacesT m a -> SpacesT m b -> SpacesT m a)
-> Applicative (SpacesT m)
SpacesT m a -> SpacesT m b -> SpacesT m b
SpacesT m a -> SpacesT m b -> SpacesT m a
SpacesT m (a -> b) -> SpacesT m a -> SpacesT m b
(a -> b -> c) -> SpacesT m a -> SpacesT m b -> SpacesT m c
forall a. a -> SpacesT m a
forall a b. SpacesT m a -> SpacesT m b -> SpacesT m a
forall a b. SpacesT m a -> SpacesT m b -> SpacesT m b
forall a b. SpacesT m (a -> b) -> SpacesT m a -> SpacesT m b
forall a b c.
(a -> b -> c) -> SpacesT m a -> SpacesT m b -> SpacesT m c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall (m :: * -> *). Applicative m => Functor (SpacesT m)
forall (m :: * -> *) a. Applicative m => a -> SpacesT m a
forall (m :: * -> *) a b.
Applicative m =>
SpacesT m a -> SpacesT m b -> SpacesT m a
forall (m :: * -> *) a b.
Applicative m =>
SpacesT m a -> SpacesT m b -> SpacesT m b
forall (m :: * -> *) a b.
Applicative m =>
SpacesT m (a -> b) -> SpacesT m a -> SpacesT m b
forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> SpacesT m a -> SpacesT m b -> SpacesT m c
<* :: SpacesT m a -> SpacesT m b -> SpacesT m a
$c<* :: forall (m :: * -> *) a b.
Applicative m =>
SpacesT m a -> SpacesT m b -> SpacesT m a
*> :: SpacesT m a -> SpacesT m b -> SpacesT m b
$c*> :: forall (m :: * -> *) a b.
Applicative m =>
SpacesT m a -> SpacesT m b -> SpacesT m b
liftA2 :: (a -> b -> c) -> SpacesT m a -> SpacesT m b -> SpacesT m c
$cliftA2 :: forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> c) -> SpacesT m a -> SpacesT m b -> SpacesT m c
<*> :: SpacesT m (a -> b) -> SpacesT m a -> SpacesT m b
$c<*> :: forall (m :: * -> *) a b.
Applicative m =>
SpacesT m (a -> b) -> SpacesT m a -> SpacesT m b
pure :: a -> SpacesT m a
$cpure :: forall (m :: * -> *) a. Applicative m => a -> SpacesT m a
$cp1Applicative :: forall (m :: * -> *). Applicative m => Functor (SpacesT m)
Applicative, Applicative (SpacesT m)
a -> SpacesT m a
Applicative (SpacesT m)
-> (forall a b. SpacesT m a -> (a -> SpacesT m b) -> SpacesT m b)
-> (forall a b. SpacesT m a -> SpacesT m b -> SpacesT m b)
-> (forall a. a -> SpacesT m a)
-> Monad (SpacesT m)
SpacesT m a -> (a -> SpacesT m b) -> SpacesT m b
SpacesT m a -> SpacesT m b -> SpacesT m b
forall a. a -> SpacesT m a
forall a b. SpacesT m a -> SpacesT m b -> SpacesT m b
forall a b. SpacesT m a -> (a -> SpacesT m b) -> SpacesT m b
forall (m :: * -> *). Monad m => Applicative (SpacesT m)
forall (m :: * -> *) a. Monad m => a -> SpacesT m a
forall (m :: * -> *) a b.
Monad m =>
SpacesT m a -> SpacesT m b -> SpacesT m b
forall (m :: * -> *) a b.
Monad m =>
SpacesT m a -> (a -> SpacesT m b) -> SpacesT m b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: a -> SpacesT m a
$creturn :: forall (m :: * -> *) a. Monad m => a -> SpacesT m a
>> :: SpacesT m a -> SpacesT m b -> SpacesT m b
$c>> :: forall (m :: * -> *) a b.
Monad m =>
SpacesT m a -> SpacesT m b -> SpacesT m b
>>= :: SpacesT m a -> (a -> SpacesT m b) -> SpacesT m b
$c>>= :: forall (m :: * -> *) a b.
Monad m =>
SpacesT m a -> (a -> SpacesT m b) -> SpacesT m b
$cp1Monad :: forall (m :: * -> *). Monad m => Applicative (SpacesT m)
Monad, Monad (SpacesT m)
Monad (SpacesT m)
-> (forall a. IO a -> SpacesT m a) -> MonadIO (SpacesT m)
IO a -> SpacesT m a
forall a. IO a -> SpacesT m a
forall (m :: * -> *).
Monad m -> (forall a. IO a -> m a) -> MonadIO m
forall (m :: * -> *). MonadIO m => Monad (SpacesT m)
forall (m :: * -> *) a. MonadIO m => IO a -> SpacesT m a
liftIO :: IO a -> SpacesT m a
$cliftIO :: forall (m :: * -> *) a. MonadIO m => IO a -> SpacesT m a
$cp1MonadIO :: forall (m :: * -> *). MonadIO m => Monad (SpacesT m)
MonadIO, Monad (SpacesT m)
e -> SpacesT m a
Monad (SpacesT m)
-> (forall e a. Exception e => e -> SpacesT m a)
-> MonadThrow (SpacesT m)
forall e a. Exception e => e -> SpacesT m a
forall (m :: * -> *).
Monad m -> (forall e a. Exception e => e -> m a) -> MonadThrow m
forall (m :: * -> *). MonadThrow m => Monad (SpacesT m)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> SpacesT m a
throwM :: e -> SpacesT m a
$cthrowM :: forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
e -> SpacesT m a
$cp1MonadThrow :: forall (m :: * -> *). MonadThrow m => Monad (SpacesT m)
MonadThrow
, MonadThrow (SpacesT m)
MonadThrow (SpacesT m)
-> (forall e a.
Exception e =>
SpacesT m a -> (e -> SpacesT m a) -> SpacesT m a)
-> MonadCatch (SpacesT m)
SpacesT m a -> (e -> SpacesT m a) -> SpacesT m a
forall e a.
Exception e =>
SpacesT m a -> (e -> SpacesT m a) -> SpacesT m a
forall (m :: * -> *).
MonadThrow m
-> (forall e a. Exception e => m a -> (e -> m a) -> m a)
-> MonadCatch m
forall (m :: * -> *). MonadCatch m => MonadThrow (SpacesT m)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
SpacesT m a -> (e -> SpacesT m a) -> SpacesT m a
catch :: SpacesT m a -> (e -> SpacesT m a) -> SpacesT m a
$ccatch :: forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
SpacesT m a -> (e -> SpacesT m a) -> SpacesT m a
$cp1MonadCatch :: forall (m :: * -> *). MonadCatch m => MonadThrow (SpacesT m)
MonadCatch, MonadReader Spaces, MonadIO (SpacesT m)
MonadIO (SpacesT m)
-> (forall b.
((forall a. SpacesT m a -> IO a) -> IO b) -> SpacesT m b)
-> MonadUnliftIO (SpacesT m)
((forall a. SpacesT m a -> IO a) -> IO b) -> SpacesT m b
forall b. ((forall a. SpacesT m a -> IO a) -> IO b) -> SpacesT m b
forall (m :: * -> *).
MonadIO m
-> (forall b. ((forall a. m a -> IO a) -> IO b) -> m b)
-> MonadUnliftIO m
forall (m :: * -> *). MonadUnliftIO m => MonadIO (SpacesT m)
forall (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. SpacesT m a -> IO a) -> IO b) -> SpacesT m b
withRunInIO :: ((forall a. SpacesT m a -> IO a) -> IO b) -> SpacesT m b
$cwithRunInIO :: forall (m :: * -> *) b.
MonadUnliftIO m =>
((forall a. SpacesT m a -> IO a) -> IO b) -> SpacesT m b
$cp1MonadUnliftIO :: forall (m :: * -> *). MonadUnliftIO m => MonadIO (SpacesT m)
MonadUnliftIO )
runSpacesT :: SpacesT m a -> Spaces -> m a
runSpacesT :: SpacesT m a -> Spaces -> m a
runSpacesT (SpacesT ReaderT Spaces m a
x) = ReaderT Spaces m a -> Spaces -> m a
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT Spaces m a
x
type MonadSpaces m =
(MonadReader Spaces m, MonadIO m, MonadUnliftIO m, MonadCatch m)
data Spaces = Spaces
{ Spaces -> AccessKey
accessKey :: AccessKey
, Spaces -> SecretKey
secretKey :: SecretKey
, Spaces -> Region
region :: Region
, Spaces -> Manager
manager :: Manager
}
deriving stock ( (forall x. Spaces -> Rep Spaces x)
-> (forall x. Rep Spaces x -> Spaces) -> Generic Spaces
forall x. Rep Spaces x -> Spaces
forall x. Spaces -> Rep Spaces x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Spaces x -> Spaces
$cfrom :: forall x. Spaces -> Rep Spaces x
Generic )
instance HasHttpManager Spaces where
getHttpManager :: Spaces -> Manager
getHttpManager = Spaces -> Manager
manager
data SpacesRequest = SpacesRequest
{ SpacesRequest -> Request
request :: Request
, SpacesRequest -> Spaces
spaces :: Spaces
, :: [Header]
, SpacesRequest -> Method
method :: Method
, SpacesRequest -> Hashed
payloadHash :: Hashed
, SpacesRequest -> Canonicalized Request
canonicalRequest :: Canonicalized Request
, SpacesRequest -> UTCTime
time :: UTCTime
}
deriving stock ( (forall x. SpacesRequest -> Rep SpacesRequest x)
-> (forall x. Rep SpacesRequest x -> SpacesRequest)
-> Generic SpacesRequest
forall x. Rep SpacesRequest x -> SpacesRequest
forall x. SpacesRequest -> Rep SpacesRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SpacesRequest x -> SpacesRequest
$cfrom :: forall x. SpacesRequest -> Rep SpacesRequest x
Generic )
data SpacesRequestBuilder = SpacesRequestBuilder
{ SpacesRequestBuilder -> Spaces
spaces :: Spaces
, SpacesRequestBuilder -> Maybe RequestBody
body :: Maybe RequestBody
, SpacesRequestBuilder -> Maybe Method
method :: Maybe Method
, :: [Header]
, SpacesRequestBuilder -> Maybe Bucket
bucket :: Maybe Bucket
, SpacesRequestBuilder -> Maybe Object
object :: Maybe Object
, SpacesRequestBuilder -> Maybe Query
queryString :: Maybe Query
, SpacesRequestBuilder -> Maybe Query
subresources :: Maybe Query
, SpacesRequestBuilder -> Maybe Region
overrideRegion :: Maybe Region
}
deriving stock ( (forall x. SpacesRequestBuilder -> Rep SpacesRequestBuilder x)
-> (forall x. Rep SpacesRequestBuilder x -> SpacesRequestBuilder)
-> Generic SpacesRequestBuilder
forall x. Rep SpacesRequestBuilder x -> SpacesRequestBuilder
forall x. SpacesRequestBuilder -> Rep SpacesRequestBuilder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SpacesRequestBuilder x -> SpacesRequestBuilder
$cfrom :: forall x. SpacesRequestBuilder -> Rep SpacesRequestBuilder x
Generic )
data Region
= NewYork
| Amsterdam
| SanFrancisco
| Singapore
| Frankfurt
deriving stock ( Int -> Region -> ShowS
[Region] -> ShowS
Region -> String
(Int -> Region -> ShowS)
-> (Region -> String) -> ([Region] -> ShowS) -> Show Region
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Region] -> ShowS
$cshowList :: [Region] -> ShowS
show :: Region -> String
$cshow :: Region -> String
showsPrec :: Int -> Region -> ShowS
$cshowsPrec :: Int -> Region -> ShowS
Show, Region -> Region -> Bool
(Region -> Region -> Bool)
-> (Region -> Region -> Bool) -> Eq Region
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Region -> Region -> Bool
$c/= :: Region -> Region -> Bool
== :: Region -> Region -> Bool
$c== :: Region -> Region -> Bool
Eq, (forall x. Region -> Rep Region x)
-> (forall x. Rep Region x -> Region) -> Generic Region
forall x. Rep Region x -> Region
forall x. Region -> Rep Region x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Region x -> Region
$cfrom :: forall x. Region -> Rep Region x
Generic )
data Method
= GET
| POST
| PUT
| DELETE
| HEAD
deriving stock ( Int -> Method -> ShowS
[Method] -> ShowS
Method -> String
(Int -> Method -> ShowS)
-> (Method -> String) -> ([Method] -> ShowS) -> Show Method
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Method] -> ShowS
$cshowList :: [Method] -> ShowS
show :: Method -> String
$cshow :: Method -> String
showsPrec :: Int -> Method -> ShowS
$cshowsPrec :: Int -> Method -> ShowS
Show, Method -> Method -> Bool
(Method -> Method -> Bool)
-> (Method -> Method -> Bool) -> Eq Method
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Method -> Method -> Bool
$c/= :: Method -> Method -> Bool
== :: Method -> Method -> Bool
$c== :: Method -> Method -> Bool
Eq, (forall x. Method -> Rep Method x)
-> (forall x. Rep Method x -> Method) -> Generic Method
forall x. Rep Method x -> Method
forall x. Method -> Rep Method x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Method x -> Method
$cfrom :: forall x. Method -> Rep Method x
Generic, Eq Method
Eq Method
-> (Method -> Method -> Ordering)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Bool)
-> (Method -> Method -> Method)
-> (Method -> Method -> Method)
-> Ord Method
Method -> Method -> Bool
Method -> Method -> Ordering
Method -> Method -> Method
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Method -> Method -> Method
$cmin :: Method -> Method -> Method
max :: Method -> Method -> Method
$cmax :: Method -> Method -> Method
>= :: Method -> Method -> Bool
$c>= :: Method -> Method -> Bool
> :: Method -> Method -> Bool
$c> :: Method -> Method -> Bool
<= :: Method -> Method -> Bool
$c<= :: Method -> Method -> Bool
< :: Method -> Method -> Bool
$c< :: Method -> Method -> Bool
compare :: Method -> Method -> Ordering
$ccompare :: Method -> Method -> Ordering
$cp1Ord :: Eq Method
Ord, ReadPrec [Method]
ReadPrec Method
Int -> ReadS Method
ReadS [Method]
(Int -> ReadS Method)
-> ReadS [Method]
-> ReadPrec Method
-> ReadPrec [Method]
-> Read Method
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Method]
$creadListPrec :: ReadPrec [Method]
readPrec :: ReadPrec Method
$creadPrec :: ReadPrec Method
readList :: ReadS [Method]
$creadList :: ReadS [Method]
readsPrec :: Int -> ReadS Method
$creadsPrec :: Int -> ReadS Method
Read )
newtype Bucket = Bucket Text
deriving stock ( Int -> Bucket -> ShowS
[Bucket] -> ShowS
Bucket -> String
(Int -> Bucket -> ShowS)
-> (Bucket -> String) -> ([Bucket] -> ShowS) -> Show Bucket
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bucket] -> ShowS
$cshowList :: [Bucket] -> ShowS
show :: Bucket -> String
$cshow :: Bucket -> String
showsPrec :: Int -> Bucket -> ShowS
$cshowsPrec :: Int -> Bucket -> ShowS
Show, (forall x. Bucket -> Rep Bucket x)
-> (forall x. Rep Bucket x -> Bucket) -> Generic Bucket
forall x. Rep Bucket x -> Bucket
forall x. Bucket -> Rep Bucket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Bucket x -> Bucket
$cfrom :: forall x. Bucket -> Rep Bucket x
Generic )
deriving newtype ( Bucket -> Bucket -> Bool
(Bucket -> Bucket -> Bool)
-> (Bucket -> Bucket -> Bool) -> Eq Bucket
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bucket -> Bucket -> Bool
$c/= :: Bucket -> Bucket -> Bool
== :: Bucket -> Bucket -> Bool
$c== :: Bucket -> Bucket -> Bool
Eq, Bucket -> ByteString
Bucket -> Builder
Bucket -> Text
(Bucket -> Text)
-> (Bucket -> Builder)
-> (Bucket -> ByteString)
-> (Bucket -> Text)
-> ToHttpApiData Bucket
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: Bucket -> Text
$ctoQueryParam :: Bucket -> Text
toHeader :: Bucket -> ByteString
$ctoHeader :: Bucket -> ByteString
toEncodedUrlPiece :: Bucket -> Builder
$ctoEncodedUrlPiece :: Bucket -> Builder
toUrlPiece :: Bucket -> Text
$ctoUrlPiece :: Bucket -> Text
ToHttpApiData )
mkBucket :: MonadThrow m => Text -> m Bucket
mkBucket :: Text -> m Bucket
mkBucket Text
t
| Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Int, Int) -> Int -> Bool
forall a. Ix a => (a, a) -> a -> Bool
inRange (Int
3, Int
63) Int
len =
Text -> m Bucket
forall (m :: * -> *) a. MonadThrow m => Text -> m a
bucketErr Text
"Name must be between 3-63 characters"
| Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Bool
T.all ([Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ([Bool] -> Bool) -> (Char -> [Bool]) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> [Bool]
okChars) Text
t = Text -> m Bucket
forall (m :: * -> *) a. MonadThrow m => Text -> m a
bucketErr
(Text -> m Bucket) -> Text -> m Bucket
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
"Names may only consist of "
, Text
"lowercase letters, digits, dots, and hyphens"
]
| Text -> Char
T.head Text
t Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ Char
'.', Char
'-' ] =
Text -> m Bucket
forall (m :: * -> *) a. MonadThrow m => Text -> m a
bucketErr Text
"Name must begin with a letter or digit"
| Text -> Char
T.last Text
t
Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ Char
'.', Char
'-' ] = Text -> m Bucket
forall (m :: * -> *) a. MonadThrow m => Text -> m a
bucketErr Text
"Name must end with a letter or digit"
| Bool
otherwise = Bucket -> m Bucket
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bucket -> m Bucket) -> (Text -> Bucket) -> Text -> m Bucket
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bucket
Bucket (Text -> m Bucket) -> Text -> m Bucket
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> Text -> Text
T.map Char -> Char
toLower Text
t
where
len :: Int
len = Text -> Int
T.length Text
t
okChars :: Char -> [Bool]
okChars Char
c = [ (Char
'.' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==), (Char
'-' Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==), Char -> Bool
isDigit, Char -> Bool
isAlpha ] [Char -> Bool] -> String -> [Bool]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [ Char
c ]
bucketErr :: Text -> m a
bucketErr Text
e = ClientException -> m a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ClientException -> m a)
-> (Text -> ClientException) -> Text -> m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ClientException
OtherError (Text -> m a) -> Text -> m a
forall a b. (a -> b) -> a -> b
$ Text
"Bucket: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
e
data BucketInfo = BucketInfo { BucketInfo -> Bucket
name :: Bucket, BucketInfo -> UTCTime
creationDate :: UTCTime }
deriving stock ( Int -> BucketInfo -> ShowS
[BucketInfo] -> ShowS
BucketInfo -> String
(Int -> BucketInfo -> ShowS)
-> (BucketInfo -> String)
-> ([BucketInfo] -> ShowS)
-> Show BucketInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BucketInfo] -> ShowS
$cshowList :: [BucketInfo] -> ShowS
show :: BucketInfo -> String
$cshow :: BucketInfo -> String
showsPrec :: Int -> BucketInfo -> ShowS
$cshowsPrec :: Int -> BucketInfo -> ShowS
Show, BucketInfo -> BucketInfo -> Bool
(BucketInfo -> BucketInfo -> Bool)
-> (BucketInfo -> BucketInfo -> Bool) -> Eq BucketInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BucketInfo -> BucketInfo -> Bool
$c/= :: BucketInfo -> BucketInfo -> Bool
== :: BucketInfo -> BucketInfo -> Bool
$c== :: BucketInfo -> BucketInfo -> Bool
Eq, (forall x. BucketInfo -> Rep BucketInfo x)
-> (forall x. Rep BucketInfo x -> BucketInfo) -> Generic BucketInfo
forall x. Rep BucketInfo x -> BucketInfo
forall x. BucketInfo -> Rep BucketInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BucketInfo x -> BucketInfo
$cfrom :: forall x. BucketInfo -> Rep BucketInfo x
Generic )
newtype Object = Object Text
deriving stock ( Int -> Object -> ShowS
[Object] -> ShowS
Object -> String
(Int -> Object -> ShowS)
-> (Object -> String) -> ([Object] -> ShowS) -> Show Object
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Object] -> ShowS
$cshowList :: [Object] -> ShowS
show :: Object -> String
$cshow :: Object -> String
showsPrec :: Int -> Object -> ShowS
$cshowsPrec :: Int -> Object -> ShowS
Show, (forall x. Object -> Rep Object x)
-> (forall x. Rep Object x -> Object) -> Generic Object
forall x. Rep Object x -> Object
forall x. Object -> Rep Object x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Object x -> Object
$cfrom :: forall x. Object -> Rep Object x
Generic )
deriving newtype ( Object -> Object -> Bool
(Object -> Object -> Bool)
-> (Object -> Object -> Bool) -> Eq Object
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Object -> Object -> Bool
$c/= :: Object -> Object -> Bool
== :: Object -> Object -> Bool
$c== :: Object -> Object -> Bool
Eq, Object -> ByteString
Object -> Builder
Object -> Text
(Object -> Text)
-> (Object -> Builder)
-> (Object -> ByteString)
-> (Object -> Text)
-> ToHttpApiData Object
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: Object -> Text
$ctoQueryParam :: Object -> Text
toHeader :: Object -> ByteString
$ctoHeader :: Object -> ByteString
toEncodedUrlPiece :: Object -> Builder
$ctoEncodedUrlPiece :: Object -> Builder
toUrlPiece :: Object -> Text
$ctoUrlPiece :: Object -> Text
ToHttpApiData )
mkObject :: MonadThrow m => Text -> m Object
mkObject :: Text -> m Object
mkObject Text
t
| Text -> Bool
T.null Text
t = ClientException -> m Object
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (ClientException -> m Object)
-> (Text -> ClientException) -> Text -> m Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ClientException
OtherError (Text -> m Object) -> Text -> m Object
forall a b. (a -> b) -> a -> b
$ Text
"Object: Name must not be empty"
| Bool
otherwise = Object -> m Object
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Object -> m Object) -> Object -> m Object
forall a b. (a -> b) -> a -> b
$ Text -> Object
Object Text
t
data ObjectInfo = ObjectInfo
{ ObjectInfo -> Object
object :: Object
, ObjectInfo -> UTCTime
lastModified :: UTCTime
, ObjectInfo -> Text
etag :: ETag
, ObjectInfo -> Int
size :: Int
, ObjectInfo -> Owner
owner :: Owner
}
deriving stock ( Int -> ObjectInfo -> ShowS
[ObjectInfo] -> ShowS
ObjectInfo -> String
(Int -> ObjectInfo -> ShowS)
-> (ObjectInfo -> String)
-> ([ObjectInfo] -> ShowS)
-> Show ObjectInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectInfo] -> ShowS
$cshowList :: [ObjectInfo] -> ShowS
show :: ObjectInfo -> String
$cshow :: ObjectInfo -> String
showsPrec :: Int -> ObjectInfo -> ShowS
$cshowsPrec :: Int -> ObjectInfo -> ShowS
Show, ObjectInfo -> ObjectInfo -> Bool
(ObjectInfo -> ObjectInfo -> Bool)
-> (ObjectInfo -> ObjectInfo -> Bool) -> Eq ObjectInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectInfo -> ObjectInfo -> Bool
$c/= :: ObjectInfo -> ObjectInfo -> Bool
== :: ObjectInfo -> ObjectInfo -> Bool
$c== :: ObjectInfo -> ObjectInfo -> Bool
Eq, (forall x. ObjectInfo -> Rep ObjectInfo x)
-> (forall x. Rep ObjectInfo x -> ObjectInfo) -> Generic ObjectInfo
forall x. Rep ObjectInfo x -> ObjectInfo
forall x. ObjectInfo -> Rep ObjectInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ObjectInfo x -> ObjectInfo
$cfrom :: forall x. ObjectInfo -> Rep ObjectInfo x
Generic )
data ObjectMetadata = ObjectMetadata
{ ObjectMetadata -> Int
contentLength :: Int
, ObjectMetadata -> ByteString
contentType :: MimeType
, ObjectMetadata -> Text
etag :: ETag
, ObjectMetadata -> UTCTime
lastModified :: UTCTime
}
deriving stock ( Int -> ObjectMetadata -> ShowS
[ObjectMetadata] -> ShowS
ObjectMetadata -> String
(Int -> ObjectMetadata -> ShowS)
-> (ObjectMetadata -> String)
-> ([ObjectMetadata] -> ShowS)
-> Show ObjectMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ObjectMetadata] -> ShowS
$cshowList :: [ObjectMetadata] -> ShowS
show :: ObjectMetadata -> String
$cshow :: ObjectMetadata -> String
showsPrec :: Int -> ObjectMetadata -> ShowS
$cshowsPrec :: Int -> ObjectMetadata -> ShowS
Show, ObjectMetadata -> ObjectMetadata -> Bool
(ObjectMetadata -> ObjectMetadata -> Bool)
-> (ObjectMetadata -> ObjectMetadata -> Bool) -> Eq ObjectMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectMetadata -> ObjectMetadata -> Bool
$c/= :: ObjectMetadata -> ObjectMetadata -> Bool
== :: ObjectMetadata -> ObjectMetadata -> Bool
$c== :: ObjectMetadata -> ObjectMetadata -> Bool
Eq, (forall x. ObjectMetadata -> Rep ObjectMetadata x)
-> (forall x. Rep ObjectMetadata x -> ObjectMetadata)
-> Generic ObjectMetadata
forall x. Rep ObjectMetadata x -> ObjectMetadata
forall x. ObjectMetadata -> Rep ObjectMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ObjectMetadata x -> ObjectMetadata
$cfrom :: forall x. ObjectMetadata -> Rep ObjectMetadata x
Generic )
data Owner = Owner { Owner -> OwnerID
ownerID :: OwnerID, Owner -> OwnerID
displayName :: DisplayName }
deriving stock ( Int -> Owner -> ShowS
[Owner] -> ShowS
Owner -> String
(Int -> Owner -> ShowS)
-> (Owner -> String) -> ([Owner] -> ShowS) -> Show Owner
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Owner] -> ShowS
$cshowList :: [Owner] -> ShowS
show :: Owner -> String
$cshow :: Owner -> String
showsPrec :: Int -> Owner -> ShowS
$cshowsPrec :: Int -> Owner -> ShowS
Show, Owner -> Owner -> Bool
(Owner -> Owner -> Bool) -> (Owner -> Owner -> Bool) -> Eq Owner
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Owner -> Owner -> Bool
$c/= :: Owner -> Owner -> Bool
== :: Owner -> Owner -> Bool
$c== :: Owner -> Owner -> Bool
Eq, (forall x. Owner -> Rep Owner x)
-> (forall x. Rep Owner x -> Owner) -> Generic Owner
forall x. Rep Owner x -> Owner
forall x. Owner -> Rep Owner x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Owner x -> Owner
$cfrom :: forall x. Owner -> Rep Owner x
Generic )
newtype OwnerID = OwnerID Int
deriving stock ( Int -> OwnerID -> ShowS
[OwnerID] -> ShowS
OwnerID -> String
(Int -> OwnerID -> ShowS)
-> (OwnerID -> String) -> ([OwnerID] -> ShowS) -> Show OwnerID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OwnerID] -> ShowS
$cshowList :: [OwnerID] -> ShowS
show :: OwnerID -> String
$cshow :: OwnerID -> String
showsPrec :: Int -> OwnerID -> ShowS
$cshowsPrec :: Int -> OwnerID -> ShowS
Show, (forall x. OwnerID -> Rep OwnerID x)
-> (forall x. Rep OwnerID x -> OwnerID) -> Generic OwnerID
forall x. Rep OwnerID x -> OwnerID
forall x. OwnerID -> Rep OwnerID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OwnerID x -> OwnerID
$cfrom :: forall x. OwnerID -> Rep OwnerID x
Generic )
deriving newtype ( OwnerID -> OwnerID -> Bool
(OwnerID -> OwnerID -> Bool)
-> (OwnerID -> OwnerID -> Bool) -> Eq OwnerID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OwnerID -> OwnerID -> Bool
$c/= :: OwnerID -> OwnerID -> Bool
== :: OwnerID -> OwnerID -> Bool
$c== :: OwnerID -> OwnerID -> Bool
Eq, Integer -> OwnerID
OwnerID -> OwnerID
OwnerID -> OwnerID -> OwnerID
(OwnerID -> OwnerID -> OwnerID)
-> (OwnerID -> OwnerID -> OwnerID)
-> (OwnerID -> OwnerID -> OwnerID)
-> (OwnerID -> OwnerID)
-> (OwnerID -> OwnerID)
-> (OwnerID -> OwnerID)
-> (Integer -> OwnerID)
-> Num OwnerID
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> OwnerID
$cfromInteger :: Integer -> OwnerID
signum :: OwnerID -> OwnerID
$csignum :: OwnerID -> OwnerID
abs :: OwnerID -> OwnerID
$cabs :: OwnerID -> OwnerID
negate :: OwnerID -> OwnerID
$cnegate :: OwnerID -> OwnerID
* :: OwnerID -> OwnerID -> OwnerID
$c* :: OwnerID -> OwnerID -> OwnerID
- :: OwnerID -> OwnerID -> OwnerID
$c- :: OwnerID -> OwnerID -> OwnerID
+ :: OwnerID -> OwnerID -> OwnerID
$c+ :: OwnerID -> OwnerID -> OwnerID
Num, OwnerID -> ByteString
OwnerID -> Builder
OwnerID -> Text
(OwnerID -> Text)
-> (OwnerID -> Builder)
-> (OwnerID -> ByteString)
-> (OwnerID -> Text)
-> ToHttpApiData OwnerID
forall a.
(a -> Text)
-> (a -> Builder)
-> (a -> ByteString)
-> (a -> Text)
-> ToHttpApiData a
toQueryParam :: OwnerID -> Text
$ctoQueryParam :: OwnerID -> Text
toHeader :: OwnerID -> ByteString
$ctoHeader :: OwnerID -> ByteString
toEncodedUrlPiece :: OwnerID -> Builder
$ctoEncodedUrlPiece :: OwnerID -> Builder
toUrlPiece :: OwnerID -> Text
$ctoUrlPiece :: OwnerID -> Text
ToHttpApiData )
type DisplayName = OwnerID
type ETag = Text
data =
{ :: Maybe CannedACL
, :: Maybe CacheControl
, :: Maybe ContentDisposition
, :: Maybe ContentEncoding
, :: UserMetadata
}
deriving stock ( Int -> UploadHeaders -> ShowS
[UploadHeaders] -> ShowS
UploadHeaders -> String
(Int -> UploadHeaders -> ShowS)
-> (UploadHeaders -> String)
-> ([UploadHeaders] -> ShowS)
-> Show UploadHeaders
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadHeaders] -> ShowS
$cshowList :: [UploadHeaders] -> ShowS
show :: UploadHeaders -> String
$cshow :: UploadHeaders -> String
showsPrec :: Int -> UploadHeaders -> ShowS
$cshowsPrec :: Int -> UploadHeaders -> ShowS
Show, UploadHeaders -> UploadHeaders -> Bool
(UploadHeaders -> UploadHeaders -> Bool)
-> (UploadHeaders -> UploadHeaders -> Bool) -> Eq UploadHeaders
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadHeaders -> UploadHeaders -> Bool
$c/= :: UploadHeaders -> UploadHeaders -> Bool
== :: UploadHeaders -> UploadHeaders -> Bool
$c== :: UploadHeaders -> UploadHeaders -> Bool
Eq, (forall x. UploadHeaders -> Rep UploadHeaders x)
-> (forall x. Rep UploadHeaders x -> UploadHeaders)
-> Generic UploadHeaders
forall x. Rep UploadHeaders x -> UploadHeaders
forall x. UploadHeaders -> Rep UploadHeaders x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadHeaders x -> UploadHeaders
$cfrom :: forall x. UploadHeaders -> Rep UploadHeaders x
Generic )
type CacheControl = Text
type ContentDisposition = Text
type ContentEncoding = Text
type UserMetadata = [(Text, Text)]
data CORSRule = CORSRule
{ CORSRule -> Text
allowedOrigin :: Text
, CORSRule -> [Method]
allowedMethods :: [Method]
, :: [HeaderName]
}
deriving stock ( Int -> CORSRule -> ShowS
[CORSRule] -> ShowS
CORSRule -> String
(Int -> CORSRule -> ShowS)
-> (CORSRule -> String) -> ([CORSRule] -> ShowS) -> Show CORSRule
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CORSRule] -> ShowS
$cshowList :: [CORSRule] -> ShowS
show :: CORSRule -> String
$cshow :: CORSRule -> String
showsPrec :: Int -> CORSRule -> ShowS
$cshowsPrec :: Int -> CORSRule -> ShowS
Show, CORSRule -> CORSRule -> Bool
(CORSRule -> CORSRule -> Bool)
-> (CORSRule -> CORSRule -> Bool) -> Eq CORSRule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CORSRule -> CORSRule -> Bool
$c/= :: CORSRule -> CORSRule -> Bool
== :: CORSRule -> CORSRule -> Bool
$c== :: CORSRule -> CORSRule -> Bool
Eq, (forall x. CORSRule -> Rep CORSRule x)
-> (forall x. Rep CORSRule x -> CORSRule) -> Generic CORSRule
forall x. Rep CORSRule x -> CORSRule
forall x. CORSRule -> Rep CORSRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CORSRule x -> CORSRule
$cfrom :: forall x. CORSRule -> Rep CORSRule x
Generic )
data Grant = Grant { Grant -> Permission
permission :: Permission, Grant -> Grantee
grantee :: Grantee }
deriving stock ( Int -> Grant -> ShowS
[Grant] -> ShowS
Grant -> String
(Int -> Grant -> ShowS)
-> (Grant -> String) -> ([Grant] -> ShowS) -> Show Grant
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Grant] -> ShowS
$cshowList :: [Grant] -> ShowS
show :: Grant -> String
$cshow :: Grant -> String
showsPrec :: Int -> Grant -> ShowS
$cshowsPrec :: Int -> Grant -> ShowS
Show, Grant -> Grant -> Bool
(Grant -> Grant -> Bool) -> (Grant -> Grant -> Bool) -> Eq Grant
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Grant -> Grant -> Bool
$c/= :: Grant -> Grant -> Bool
== :: Grant -> Grant -> Bool
$c== :: Grant -> Grant -> Bool
Eq, (forall x. Grant -> Rep Grant x)
-> (forall x. Rep Grant x -> Grant) -> Generic Grant
forall x. Rep Grant x -> Grant
forall x. Grant -> Rep Grant x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Grant x -> Grant
$cfrom :: forall x. Grant -> Rep Grant x
Generic )
data Permission
= ReadOnly
| FullControl
deriving stock ( Int -> Permission -> ShowS
[Permission] -> ShowS
Permission -> String
(Int -> Permission -> ShowS)
-> (Permission -> String)
-> ([Permission] -> ShowS)
-> Show Permission
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Permission] -> ShowS
$cshowList :: [Permission] -> ShowS
show :: Permission -> String
$cshow :: Permission -> String
showsPrec :: Int -> Permission -> ShowS
$cshowsPrec :: Int -> Permission -> ShowS
Show, Permission -> Permission -> Bool
(Permission -> Permission -> Bool)
-> (Permission -> Permission -> Bool) -> Eq Permission
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Permission -> Permission -> Bool
$c/= :: Permission -> Permission -> Bool
== :: Permission -> Permission -> Bool
$c== :: Permission -> Permission -> Bool
Eq, (forall x. Permission -> Rep Permission x)
-> (forall x. Rep Permission x -> Permission) -> Generic Permission
forall x. Rep Permission x -> Permission
forall x. Permission -> Rep Permission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Permission x -> Permission
$cfrom :: forall x. Permission -> Rep Permission x
Generic, Eq Permission
Eq Permission
-> (Permission -> Permission -> Ordering)
-> (Permission -> Permission -> Bool)
-> (Permission -> Permission -> Bool)
-> (Permission -> Permission -> Bool)
-> (Permission -> Permission -> Bool)
-> (Permission -> Permission -> Permission)
-> (Permission -> Permission -> Permission)
-> Ord Permission
Permission -> Permission -> Bool
Permission -> Permission -> Ordering
Permission -> Permission -> Permission
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Permission -> Permission -> Permission
$cmin :: Permission -> Permission -> Permission
max :: Permission -> Permission -> Permission
$cmax :: Permission -> Permission -> Permission
>= :: Permission -> Permission -> Bool
$c>= :: Permission -> Permission -> Bool
> :: Permission -> Permission -> Bool
$c> :: Permission -> Permission -> Bool
<= :: Permission -> Permission -> Bool
$c<= :: Permission -> Permission -> Bool
< :: Permission -> Permission -> Bool
$c< :: Permission -> Permission -> Bool
compare :: Permission -> Permission -> Ordering
$ccompare :: Permission -> Permission -> Ordering
$cp1Ord :: Eq Permission
Ord )
data Grantee
= Group
| CanonicalUser Owner
deriving stock ( Int -> Grantee -> ShowS
[Grantee] -> ShowS
Grantee -> String
(Int -> Grantee -> ShowS)
-> (Grantee -> String) -> ([Grantee] -> ShowS) -> Show Grantee
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Grantee] -> ShowS
$cshowList :: [Grantee] -> ShowS
show :: Grantee -> String
$cshow :: Grantee -> String
showsPrec :: Int -> Grantee -> ShowS
$cshowsPrec :: Int -> Grantee -> ShowS
Show, Grantee -> Grantee -> Bool
(Grantee -> Grantee -> Bool)
-> (Grantee -> Grantee -> Bool) -> Eq Grantee
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Grantee -> Grantee -> Bool
$c/= :: Grantee -> Grantee -> Bool
== :: Grantee -> Grantee -> Bool
$c== :: Grantee -> Grantee -> Bool
Eq, (forall x. Grantee -> Rep Grantee x)
-> (forall x. Rep Grantee x -> Grantee) -> Generic Grantee
forall x. Rep Grantee x -> Grantee
forall x. Grantee -> Rep Grantee x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Grantee x -> Grantee
$cfrom :: forall x. Grantee -> Rep Grantee x
Generic )
data ACLResponse =
ACLResponse { ACLResponse -> Owner
owner :: Owner, ACLResponse -> [Grant]
accessControlList :: [Grant] }
deriving stock ( Int -> ACLResponse -> ShowS
[ACLResponse] -> ShowS
ACLResponse -> String
(Int -> ACLResponse -> ShowS)
-> (ACLResponse -> String)
-> ([ACLResponse] -> ShowS)
-> Show ACLResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ACLResponse] -> ShowS
$cshowList :: [ACLResponse] -> ShowS
show :: ACLResponse -> String
$cshow :: ACLResponse -> String
showsPrec :: Int -> ACLResponse -> ShowS
$cshowsPrec :: Int -> ACLResponse -> ShowS
Show, ACLResponse -> ACLResponse -> Bool
(ACLResponse -> ACLResponse -> Bool)
-> (ACLResponse -> ACLResponse -> Bool) -> Eq ACLResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ACLResponse -> ACLResponse -> Bool
$c/= :: ACLResponse -> ACLResponse -> Bool
== :: ACLResponse -> ACLResponse -> Bool
$c== :: ACLResponse -> ACLResponse -> Bool
Eq, (forall x. ACLResponse -> Rep ACLResponse x)
-> (forall x. Rep ACLResponse x -> ACLResponse)
-> Generic ACLResponse
forall x. Rep ACLResponse x -> ACLResponse
forall x. ACLResponse -> Rep ACLResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ACLResponse x -> ACLResponse
$cfrom :: forall x. ACLResponse -> Rep ACLResponse x
Generic )
type Days = Word16
data LifecycleRule = LifecycleRule
{ LifecycleRule -> LifecycleID
lifecycleID :: LifecycleID
, LifecycleRule -> Bool
enabled :: Bool
, LifecycleRule -> Maybe Text
prefix :: Maybe Text
, LifecycleRule -> Maybe LifecycleExpiration
expiration :: Maybe LifecycleExpiration
, LifecycleRule -> Maybe Days
abortIncomplete :: Maybe Days
}
deriving stock ( Int -> LifecycleRule -> ShowS
[LifecycleRule] -> ShowS
LifecycleRule -> String
(Int -> LifecycleRule -> ShowS)
-> (LifecycleRule -> String)
-> ([LifecycleRule] -> ShowS)
-> Show LifecycleRule
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LifecycleRule] -> ShowS
$cshowList :: [LifecycleRule] -> ShowS
show :: LifecycleRule -> String
$cshow :: LifecycleRule -> String
showsPrec :: Int -> LifecycleRule -> ShowS
$cshowsPrec :: Int -> LifecycleRule -> ShowS
Show, LifecycleRule -> LifecycleRule -> Bool
(LifecycleRule -> LifecycleRule -> Bool)
-> (LifecycleRule -> LifecycleRule -> Bool) -> Eq LifecycleRule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LifecycleRule -> LifecycleRule -> Bool
$c/= :: LifecycleRule -> LifecycleRule -> Bool
== :: LifecycleRule -> LifecycleRule -> Bool
$c== :: LifecycleRule -> LifecycleRule -> Bool
Eq, (forall x. LifecycleRule -> Rep LifecycleRule x)
-> (forall x. Rep LifecycleRule x -> LifecycleRule)
-> Generic LifecycleRule
forall x. Rep LifecycleRule x -> LifecycleRule
forall x. LifecycleRule -> Rep LifecycleRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LifecycleRule x -> LifecycleRule
$cfrom :: forall x. LifecycleRule -> Rep LifecycleRule x
Generic )
data LifecycleExpiration
= AfterDays Days
| OnDate UTCTime
deriving stock ( Int -> LifecycleExpiration -> ShowS
[LifecycleExpiration] -> ShowS
LifecycleExpiration -> String
(Int -> LifecycleExpiration -> ShowS)
-> (LifecycleExpiration -> String)
-> ([LifecycleExpiration] -> ShowS)
-> Show LifecycleExpiration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LifecycleExpiration] -> ShowS
$cshowList :: [LifecycleExpiration] -> ShowS
show :: LifecycleExpiration -> String
$cshow :: LifecycleExpiration -> String
showsPrec :: Int -> LifecycleExpiration -> ShowS
$cshowsPrec :: Int -> LifecycleExpiration -> ShowS
Show, LifecycleExpiration -> LifecycleExpiration -> Bool
(LifecycleExpiration -> LifecycleExpiration -> Bool)
-> (LifecycleExpiration -> LifecycleExpiration -> Bool)
-> Eq LifecycleExpiration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LifecycleExpiration -> LifecycleExpiration -> Bool
$c/= :: LifecycleExpiration -> LifecycleExpiration -> Bool
== :: LifecycleExpiration -> LifecycleExpiration -> Bool
$c== :: LifecycleExpiration -> LifecycleExpiration -> Bool
Eq, (forall x. LifecycleExpiration -> Rep LifecycleExpiration x)
-> (forall x. Rep LifecycleExpiration x -> LifecycleExpiration)
-> Generic LifecycleExpiration
forall x. Rep LifecycleExpiration x -> LifecycleExpiration
forall x. LifecycleExpiration -> Rep LifecycleExpiration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LifecycleExpiration x -> LifecycleExpiration
$cfrom :: forall x. LifecycleExpiration -> Rep LifecycleExpiration x
Generic )
newtype LifecycleID = LifecycleID Text
deriving stock ( Int -> LifecycleID -> ShowS
[LifecycleID] -> ShowS
LifecycleID -> String
(Int -> LifecycleID -> ShowS)
-> (LifecycleID -> String)
-> ([LifecycleID] -> ShowS)
-> Show LifecycleID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LifecycleID] -> ShowS
$cshowList :: [LifecycleID] -> ShowS
show :: LifecycleID -> String
$cshow :: LifecycleID -> String
showsPrec :: Int -> LifecycleID -> ShowS
$cshowsPrec :: Int -> LifecycleID -> ShowS
Show, LifecycleID -> LifecycleID -> Bool
(LifecycleID -> LifecycleID -> Bool)
-> (LifecycleID -> LifecycleID -> Bool) -> Eq LifecycleID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LifecycleID -> LifecycleID -> Bool
$c/= :: LifecycleID -> LifecycleID -> Bool
== :: LifecycleID -> LifecycleID -> Bool
$c== :: LifecycleID -> LifecycleID -> Bool
Eq, (forall x. LifecycleID -> Rep LifecycleID x)
-> (forall x. Rep LifecycleID x -> LifecycleID)
-> Generic LifecycleID
forall x. Rep LifecycleID x -> LifecycleID
forall x. LifecycleID -> Rep LifecycleID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LifecycleID x -> LifecycleID
$cfrom :: forall x. LifecycleID -> Rep LifecycleID x
Generic )
mkLifecycleID :: MonadThrow m => Text -> m LifecycleID
mkLifecycleID :: Text -> m LifecycleID
mkLifecycleID Text
t
| Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
255 = ClientException -> m LifecycleID
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM
(ClientException -> m LifecycleID)
-> ClientException -> m LifecycleID
forall a b. (a -> b) -> a -> b
$ Text -> ClientException
OtherError Text
"LifecycleID: ID exceeds maximum length (255 chars)"
| Bool
otherwise = LifecycleID -> m LifecycleID
forall (f :: * -> *) a. Applicative f => a -> f a
pure (LifecycleID -> m LifecycleID) -> LifecycleID -> m LifecycleID
forall a b. (a -> b) -> a -> b
$ Text -> LifecycleID
LifecycleID Text
t
mkCORSRule :: MonadThrow m => Text -> [Method] -> [HeaderName] -> m CORSRule
mkCORSRule :: Text -> [Method] -> [HeaderName] -> m CORSRule
mkCORSRule Text
origin [Method]
ms [HeaderName]
hs
| Text -> Text -> Int
T.count Text
"*" Text
origin Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 = ClientException -> m CORSRule
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM
(ClientException -> m CORSRule) -> ClientException -> m CORSRule
forall a b. (a -> b) -> a -> b
$ Text -> ClientException
OtherError Text
"CORSRule: maximum of one wildcard permitted in origins"
| [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
or ((Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1) (Int -> Bool) -> (HeaderName -> Int) -> HeaderName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ByteString -> Int
C.count Char
'*' (ByteString -> Int)
-> (HeaderName -> ByteString) -> HeaderName -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HeaderName -> ByteString
forall s. CI s -> s
CI.original (HeaderName -> Bool) -> [HeaderName] -> [Bool]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [HeaderName]
hs) = ClientException -> m CORSRule
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM
(ClientException -> m CORSRule) -> ClientException -> m CORSRule
forall a b. (a -> b) -> a -> b
$ Text -> ClientException
OtherError Text
"CORSRule: maximum of one wildcard permitted in headers"
| Bool
otherwise = CORSRule -> m CORSRule
forall (f :: * -> *) a. Applicative f => a -> f a
pure CORSRule :: Text -> [Method] -> [HeaderName] -> CORSRule
CORSRule
{ $sel:allowedOrigin:CORSRule :: Text
allowedOrigin = Text
origin
, $sel:allowedMethods:CORSRule :: [Method]
allowedMethods = [Method] -> [Method]
forall a. Ord a => [a] -> [a]
nubOrd [Method]
ms
, $sel:allowedHeaders:CORSRule :: [HeaderName]
allowedHeaders = [HeaderName] -> [HeaderName]
forall a. Ord a => [a] -> [a]
nubOrd [HeaderName]
hs
}
newtype Canonicalized a = Canonicalized ByteString
deriving stock ( Int -> Canonicalized a -> ShowS
[Canonicalized a] -> ShowS
Canonicalized a -> String
(Int -> Canonicalized a -> ShowS)
-> (Canonicalized a -> String)
-> ([Canonicalized a] -> ShowS)
-> Show (Canonicalized a)
forall a. Int -> Canonicalized a -> ShowS
forall a. [Canonicalized a] -> ShowS
forall a. Canonicalized a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Canonicalized a] -> ShowS
$cshowList :: forall a. [Canonicalized a] -> ShowS
show :: Canonicalized a -> String
$cshow :: forall a. Canonicalized a -> String
showsPrec :: Int -> Canonicalized a -> ShowS
$cshowsPrec :: forall a. Int -> Canonicalized a -> ShowS
Show, Canonicalized a -> Canonicalized a -> Bool
(Canonicalized a -> Canonicalized a -> Bool)
-> (Canonicalized a -> Canonicalized a -> Bool)
-> Eq (Canonicalized a)
forall a. Canonicalized a -> Canonicalized a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Canonicalized a -> Canonicalized a -> Bool
$c/= :: forall a. Canonicalized a -> Canonicalized a -> Bool
== :: Canonicalized a -> Canonicalized a -> Bool
$c== :: forall a. Canonicalized a -> Canonicalized a -> Bool
Eq, (forall x. Canonicalized a -> Rep (Canonicalized a) x)
-> (forall x. Rep (Canonicalized a) x -> Canonicalized a)
-> Generic (Canonicalized a)
forall x. Rep (Canonicalized a) x -> Canonicalized a
forall x. Canonicalized a -> Rep (Canonicalized a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Canonicalized a) x -> Canonicalized a
forall a x. Canonicalized a -> Rep (Canonicalized a) x
$cto :: forall a x. Rep (Canonicalized a) x -> Canonicalized a
$cfrom :: forall a x. Canonicalized a -> Rep (Canonicalized a) x
Generic )
data ComputedTag
= Hash
| StrToSign
| Sig
| Cred
| Auth
deriving stock ( Int -> ComputedTag -> ShowS
[ComputedTag] -> ShowS
ComputedTag -> String
(Int -> ComputedTag -> ShowS)
-> (ComputedTag -> String)
-> ([ComputedTag] -> ShowS)
-> Show ComputedTag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ComputedTag] -> ShowS
$cshowList :: [ComputedTag] -> ShowS
show :: ComputedTag -> String
$cshow :: ComputedTag -> String
showsPrec :: Int -> ComputedTag -> ShowS
$cshowsPrec :: Int -> ComputedTag -> ShowS
Show, ComputedTag -> ComputedTag -> Bool
(ComputedTag -> ComputedTag -> Bool)
-> (ComputedTag -> ComputedTag -> Bool) -> Eq ComputedTag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComputedTag -> ComputedTag -> Bool
$c/= :: ComputedTag -> ComputedTag -> Bool
== :: ComputedTag -> ComputedTag -> Bool
$c== :: ComputedTag -> ComputedTag -> Bool
Eq )
data Computed (a :: ComputedTag) where
Hashed :: ByteString -> Computed Hash
StringToSign :: ByteString -> Computed StrToSign
Signature :: ByteString -> Computed Sig
Credentials :: ByteString -> Computed Cred
Authorization :: ByteString -> Computed Auth
deriving stock instance Show (Computed a)
deriving stock instance Eq (Computed a)
type StringToSign = Computed 'StrToSign
type Hashed = Computed 'Hash
type Signature = Computed 'Sig
type Credentials = Computed 'Cred
type Authorization = Computed 'Auth
uncompute :: Computed a -> ByteString
uncompute :: Computed a -> ByteString
uncompute = \case
Hashed ByteString
b -> ByteString
b
StringToSign ByteString
b -> ByteString
b
Signature ByteString
b -> ByteString
b
Credentials ByteString
b -> ByteString
b
Authorization ByteString
b -> ByteString
b
newtype AccessKey = AccessKey { AccessKey -> ByteString
unAccessKey :: ByteString }
deriving stock ( Int -> AccessKey -> ShowS
[AccessKey] -> ShowS
AccessKey -> String
(Int -> AccessKey -> ShowS)
-> (AccessKey -> String)
-> ([AccessKey] -> ShowS)
-> Show AccessKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccessKey] -> ShowS
$cshowList :: [AccessKey] -> ShowS
show :: AccessKey -> String
$cshow :: AccessKey -> String
showsPrec :: Int -> AccessKey -> ShowS
$cshowsPrec :: Int -> AccessKey -> ShowS
Show, AccessKey -> AccessKey -> Bool
(AccessKey -> AccessKey -> Bool)
-> (AccessKey -> AccessKey -> Bool) -> Eq AccessKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccessKey -> AccessKey -> Bool
$c/= :: AccessKey -> AccessKey -> Bool
== :: AccessKey -> AccessKey -> Bool
$c== :: AccessKey -> AccessKey -> Bool
Eq, (forall x. AccessKey -> Rep AccessKey x)
-> (forall x. Rep AccessKey x -> AccessKey) -> Generic AccessKey
forall x. Rep AccessKey x -> AccessKey
forall x. AccessKey -> Rep AccessKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccessKey x -> AccessKey
$cfrom :: forall x. AccessKey -> Rep AccessKey x
Generic )
newtype SecretKey = SecretKey { SecretKey -> ByteString
unSecretKey :: ByteString }
deriving stock ( Int -> SecretKey -> ShowS
[SecretKey] -> ShowS
SecretKey -> String
(Int -> SecretKey -> ShowS)
-> (SecretKey -> String)
-> ([SecretKey] -> ShowS)
-> Show SecretKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SecretKey] -> ShowS
$cshowList :: [SecretKey] -> ShowS
show :: SecretKey -> String
$cshow :: SecretKey -> String
showsPrec :: Int -> SecretKey -> ShowS
$cshowsPrec :: Int -> SecretKey -> ShowS
Show, SecretKey -> SecretKey -> Bool
(SecretKey -> SecretKey -> Bool)
-> (SecretKey -> SecretKey -> Bool) -> Eq SecretKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecretKey -> SecretKey -> Bool
$c/= :: SecretKey -> SecretKey -> Bool
== :: SecretKey -> SecretKey -> Bool
$c== :: SecretKey -> SecretKey -> Bool
Eq, (forall x. SecretKey -> Rep SecretKey x)
-> (forall x. Rep SecretKey x -> SecretKey) -> Generic SecretKey
forall x. Rep SecretKey x -> SecretKey
forall x. SecretKey -> Rep SecretKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SecretKey x -> SecretKey
$cfrom :: forall x. SecretKey -> Rep SecretKey x
Generic )
type Profile = Text
class Monad m => Action m a where
type ConsumedResponse a :: Type
buildRequest :: a -> m SpacesRequestBuilder
consumeResponse :: RawResponse m -> m (ConsumedResponse a)
data RawResponse m = RawResponse { :: [Header], RawResponse m -> BodyBS m
body :: BodyBS m }
deriving stock ( (forall x. RawResponse m -> Rep (RawResponse m) x)
-> (forall x. Rep (RawResponse m) x -> RawResponse m)
-> Generic (RawResponse m)
forall x. Rep (RawResponse m) x -> RawResponse m
forall x. RawResponse m -> Rep (RawResponse m) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (m :: * -> *) x. Rep (RawResponse m) x -> RawResponse m
forall (m :: * -> *) x. RawResponse m -> Rep (RawResponse m) x
$cto :: forall (m :: * -> *) x. Rep (RawResponse m) x -> RawResponse m
$cfrom :: forall (m :: * -> *) x. RawResponse m -> Rep (RawResponse m) x
Generic )
type BodyBS m = ConduitT () ByteString m ()
data SpacesMetadata = SpacesMetadata
{ SpacesMetadata -> Maybe Text
requestID :: Maybe RequestID
, SpacesMetadata -> Maybe UTCTime
date :: Maybe UTCTime
, SpacesMetadata -> Status
status :: Status
}
deriving stock ( Int -> SpacesMetadata -> ShowS
[SpacesMetadata] -> ShowS
SpacesMetadata -> String
(Int -> SpacesMetadata -> ShowS)
-> (SpacesMetadata -> String)
-> ([SpacesMetadata] -> ShowS)
-> Show SpacesMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SpacesMetadata] -> ShowS
$cshowList :: [SpacesMetadata] -> ShowS
show :: SpacesMetadata -> String
$cshow :: SpacesMetadata -> String
showsPrec :: Int -> SpacesMetadata -> ShowS
$cshowsPrec :: Int -> SpacesMetadata -> ShowS
Show, SpacesMetadata -> SpacesMetadata -> Bool
(SpacesMetadata -> SpacesMetadata -> Bool)
-> (SpacesMetadata -> SpacesMetadata -> Bool) -> Eq SpacesMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpacesMetadata -> SpacesMetadata -> Bool
$c/= :: SpacesMetadata -> SpacesMetadata -> Bool
== :: SpacesMetadata -> SpacesMetadata -> Bool
$c== :: SpacesMetadata -> SpacesMetadata -> Bool
Eq, (forall x. SpacesMetadata -> Rep SpacesMetadata x)
-> (forall x. Rep SpacesMetadata x -> SpacesMetadata)
-> Generic SpacesMetadata
forall x. Rep SpacesMetadata x -> SpacesMetadata
forall x. SpacesMetadata -> Rep SpacesMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SpacesMetadata x -> SpacesMetadata
$cfrom :: forall x. SpacesMetadata -> Rep SpacesMetadata x
Generic )
data WithMetadata
= KeepMetadata
| NoMetadata
deriving stock ( Int -> WithMetadata -> ShowS
[WithMetadata] -> ShowS
WithMetadata -> String
(Int -> WithMetadata -> ShowS)
-> (WithMetadata -> String)
-> ([WithMetadata] -> ShowS)
-> Show WithMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WithMetadata] -> ShowS
$cshowList :: [WithMetadata] -> ShowS
show :: WithMetadata -> String
$cshow :: WithMetadata -> String
showsPrec :: Int -> WithMetadata -> ShowS
$cshowsPrec :: Int -> WithMetadata -> ShowS
Show, WithMetadata -> WithMetadata -> Bool
(WithMetadata -> WithMetadata -> Bool)
-> (WithMetadata -> WithMetadata -> Bool) -> Eq WithMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WithMetadata -> WithMetadata -> Bool
$c/= :: WithMetadata -> WithMetadata -> Bool
== :: WithMetadata -> WithMetadata -> Bool
$c== :: WithMetadata -> WithMetadata -> Bool
Eq, (forall x. WithMetadata -> Rep WithMetadata x)
-> (forall x. Rep WithMetadata x -> WithMetadata)
-> Generic WithMetadata
forall x. Rep WithMetadata x -> WithMetadata
forall x. WithMetadata -> Rep WithMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WithMetadata x -> WithMetadata
$cfrom :: forall x. WithMetadata -> Rep WithMetadata x
Generic )
data SpacesResponse a = SpacesResponse
{ SpacesResponse a -> ConsumedResponse a
result :: ConsumedResponse a
, SpacesResponse a -> Maybe SpacesMetadata
metadata :: Maybe SpacesMetadata
}
deriving stock ( (forall x. SpacesResponse a -> Rep (SpacesResponse a) x)
-> (forall x. Rep (SpacesResponse a) x -> SpacesResponse a)
-> Generic (SpacesResponse a)
forall x. Rep (SpacesResponse a) x -> SpacesResponse a
forall x. SpacesResponse a -> Rep (SpacesResponse a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (SpacesResponse a) x -> SpacesResponse a
forall a x. SpacesResponse a -> Rep (SpacesResponse a) x
$cto :: forall a x. Rep (SpacesResponse a) x -> SpacesResponse a
$cfrom :: forall a x. SpacesResponse a -> Rep (SpacesResponse a) x
Generic )
deriving stock instance (Show (ConsumedResponse a)) => Show (SpacesResponse a)
instance {-# OVERLAPPING #-}( GL.HasField' name (SpacesResponse a) s
, s ~ t
, a ~ b
)
=> GL.HasField name (SpacesResponse a) (SpacesResponse b) s t where
field :: (s -> f t) -> SpacesResponse a -> f (SpacesResponse b)
field = forall s a. HasField' name s a => Lens s s a a
forall (field :: Symbol) s a. HasField' field s a => Lens s s a a
GL.field' @name
type RequestID = Text
data CredentialSource
= Discover
| FromEnv (Maybe (Text, Text, Text))
| FromFile FilePath (Maybe Profile)
| Explicit Region AccessKey SecretKey
data CannedACL
= Private
| PublicRead
deriving stock ( CannedACL -> CannedACL -> Bool
(CannedACL -> CannedACL -> Bool)
-> (CannedACL -> CannedACL -> Bool) -> Eq CannedACL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CannedACL -> CannedACL -> Bool
$c/= :: CannedACL -> CannedACL -> Bool
== :: CannedACL -> CannedACL -> Bool
$c== :: CannedACL -> CannedACL -> Bool
Eq, Int -> CannedACL -> ShowS
[CannedACL] -> ShowS
CannedACL -> String
(Int -> CannedACL -> ShowS)
-> (CannedACL -> String)
-> ([CannedACL] -> ShowS)
-> Show CannedACL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CannedACL] -> ShowS
$cshowList :: [CannedACL] -> ShowS
show :: CannedACL -> String
$cshow :: CannedACL -> String
showsPrec :: Int -> CannedACL -> ShowS
$cshowsPrec :: Int -> CannedACL -> ShowS
Show )
data SpacesException = forall e. Exception e => SpacesException e
instance Show SpacesException where
show :: SpacesException -> String
show (SpacesException e
e) = e -> String
forall a. Show a => a -> String
show e
e
instance Exception SpacesException
spsExToException :: Exception e => e -> SomeException
spsExToException :: e -> SomeException
spsExToException = SpacesException -> SomeException
forall e. Exception e => e -> SomeException
toException (SpacesException -> SomeException)
-> (e -> SpacesException) -> e -> SomeException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> SpacesException
forall e. Exception e => e -> SpacesException
SpacesException
spsExFromException :: Exception e => SomeException -> Maybe e
spsExFromException :: SomeException -> Maybe e
spsExFromException SomeException
e = do
SpacesException e
x <- SomeException -> Maybe SpacesException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e
e -> Maybe e
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast e
x
data ClientException
= InvalidRequest Text
| InvalidResponse Text
| InvalidXML Text
| ConfigurationError Text
| HTTPStatus Status LB.ByteString
| OtherError Text
deriving stock ( Int -> ClientException -> ShowS
[ClientException] -> ShowS
ClientException -> String
(Int -> ClientException -> ShowS)
-> (ClientException -> String)
-> ([ClientException] -> ShowS)
-> Show ClientException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClientException] -> ShowS
$cshowList :: [ClientException] -> ShowS
show :: ClientException -> String
$cshow :: ClientException -> String
showsPrec :: Int -> ClientException -> ShowS
$cshowsPrec :: Int -> ClientException -> ShowS
Show, ClientException -> ClientException -> Bool
(ClientException -> ClientException -> Bool)
-> (ClientException -> ClientException -> Bool)
-> Eq ClientException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClientException -> ClientException -> Bool
$c/= :: ClientException -> ClientException -> Bool
== :: ClientException -> ClientException -> Bool
$c== :: ClientException -> ClientException -> Bool
Eq, (forall x. ClientException -> Rep ClientException x)
-> (forall x. Rep ClientException x -> ClientException)
-> Generic ClientException
forall x. Rep ClientException x -> ClientException
forall x. ClientException -> Rep ClientException x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClientException x -> ClientException
$cfrom :: forall x. ClientException -> Rep ClientException x
Generic, Typeable )
instance Exception ClientException where
toException :: ClientException -> SomeException
toException = ClientException -> SomeException
forall e. Exception e => e -> SomeException
spsExToException
fromException :: SomeException -> Maybe ClientException
fromException = SomeException -> Maybe ClientException
forall e. Exception e => SomeException -> Maybe e
spsExFromException
data APIException = APIException
{ APIException -> Status
status :: Status
, APIException -> Text
code :: Text
, APIException -> Text
requestID :: RequestID
, APIException -> Text
hostID :: Text
}
deriving stock ( Int -> APIException -> ShowS
[APIException] -> ShowS
APIException -> String
(Int -> APIException -> ShowS)
-> (APIException -> String)
-> ([APIException] -> ShowS)
-> Show APIException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [APIException] -> ShowS
$cshowList :: [APIException] -> ShowS
show :: APIException -> String
$cshow :: APIException -> String
showsPrec :: Int -> APIException -> ShowS
$cshowsPrec :: Int -> APIException -> ShowS
Show, APIException -> APIException -> Bool
(APIException -> APIException -> Bool)
-> (APIException -> APIException -> Bool) -> Eq APIException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: APIException -> APIException -> Bool
$c/= :: APIException -> APIException -> Bool
== :: APIException -> APIException -> Bool
$c== :: APIException -> APIException -> Bool
Eq, (forall x. APIException -> Rep APIException x)
-> (forall x. Rep APIException x -> APIException)
-> Generic APIException
forall x. Rep APIException x -> APIException
forall x. APIException -> Rep APIException x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep APIException x -> APIException
$cfrom :: forall x. APIException -> Rep APIException x
Generic, Typeable )
instance Exception APIException where
toException :: APIException -> SomeException
toException = APIException -> SomeException
forall e. Exception e => e -> SomeException
spsExToException
fromException :: SomeException -> Maybe APIException
fromException = SomeException -> Maybe APIException
forall e. Exception e => SomeException -> Maybe e
spsExFromException