do-spaces-0.2: DigitalOcean Spaces API bindings
Copyright(c) 2021 Rory Tyler Hayford
LicenseBSD-3-Clause
Maintainerrory.hayford@protonmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Network.DO.Spaces

Description

Interacting with DigitalOcean's Spaces API, a (largely) s3-compatible object storage platform. This module exports actions to create a Spaces client configuration as well as several convenience actions. Most of the transactions exposed through the Spaces REST API are supported here, including CRUD operations on buckets and objects, bucket CORS configuration, and manipulating ACLs.

See the README in this repository for more information on using this library

Synopsis

Documentation

runSpaces :: Spaces -> SpacesT m a -> m a Source #

Perform a transaction using your Spaces client configuration. Note that this does not perform any exception handling; if caught at the lower level, exceptions are generally re-thrown as SpacesExceptions

newSpaces :: (MonadThrow m, MonadIO m) => CredentialSource -> m Spaces Source #

Create a new Spaces by specifying a method to retrieve the region and your credentials.

Discover will first try to find a credentials file (see the notes on FromFile below) in ~.awscredentials or $XDG_CONFIG_HOMEdo-spacescredentials, in that order, using the [default] profile. Failing that, it will try the equivalent of FromEnv Nothing (see the notes below).

FromFile expects a configuration file in the same format as AWS credentials files, with the same field names. For example:

[default]
aws_access_key_id=AKIAIOSFODNN7EXAMPLE
aws_secret_access_key=wJalrXUtnFEMI/K7MDENG/bPxRfiCYEXAMPLEKEY
aws_default_region=fra1

When provided with Nothing, FromEnv will look up the following environment variables to find your region and keys:

  • For the Region:

    • AWS_DEFAULT_REGION
    • OR SPACES_DEFAULT_REGION
  • For the AccessKey:

    • AWS_ACCESS_KEY_ID
    • OR SPACES_ACCESS_KEY_ID
    • OR SPACES_ACCESS_KEY
  • For the SecretKey:

    • AWS_SECRET_ACCESS_KEY
    • OR SPACES_SECRET_ACCESS_KEY
    • OR SPACES_SECRET_KEY

Alternatively, you can directly specify a tuple of environment variables to search for.

You can also choose to provide the region and both keys yourself with Explicit

Convenience actions

The following are convenience actions. In most cases, each action is the same as applying runAction to a type that implements the Action typeclass. Information about the response is retained (SpacesMetadata) in each action. For instance:

deleteBucket myBucket

is the equivalent of

runAction KeepMetadata DeleteBucket { bucket = myBucket }

All of the underlying instances of Action are exposed and can be imported from Network.DO.Spaces.Actions and its sub-modules. The convenience actions exposed in the present module attempt to choose sane defaults where applicable.

The only major exception to the above are actions which involve uploading object data to Spaces. In the case of uploadObject, the action converts its BodyBS argument to a RequestBodyLBS. Should you choose to directly construct UploadObject, you must do this manually. multipartObject is more complicated, and takes care of chunking the request body, sending each individual request, and completing the multipart request

In addition to convenience wrappers around Action instances, this module exports several actions which may be of use, including sinking remote Object data into a file, uploading the contents of a file as an Object, and recursively listing the entire contents of a Bucket

uploadObject :: MonadSpaces m => Maybe MimeType -> Bucket -> Object -> BodyBS m -> m (SpacesResponse UploadObject) Source #

Upload an Object within a single request

multipartObject :: MonadSpaces m => Maybe MimeType -> Bucket -> Object -> Int -> BodyBS m -> m (SpacesResponse CompleteMultipart) Source #

Initiate and complete a multipart upload, using default UploadHeaders. If a SpacesException is thrown while performing the transaction, an attempt will be made to run a CancelMultipart request, and the exception will be rethrown

uploadFile :: forall m. MonadSpaces m => Bucket -> Object -> FilePath -> m (SpacesResponse UploadObject) Source #

Upload a file's contents as an Object. This will attempt to set the correct MimeType based on the file extension

getObject :: MonadSpaces m => Bucket -> Object -> m (SpacesResponse GetObject) Source #

Get an Object (retrieves the actual body of the object)

getObjectSinkFile :: MonadSpaces m => Bucket -> Object -> FilePath -> m () Source #

Get an Object's data and write it to the provided FilePath

getObjectInfo :: MonadSpaces m => Bucket -> Object -> m (SpacesResponse GetObjectInfo) Source #

Get information about an Object (does not retrieve the body of the object)

copyObject Source #

Arguments

:: MonadSpaces m 
=> Bucket

Source Bucket

-> Bucket

Destination Bucket

-> Object

Source Object

-> Object

Destination Object

-> m (SpacesResponse CopyObject) 

Copy an Object from one Bucket to another; this chooses a number of defaults to represent the most common cases and avoid a preponderance of parameters. Objects are copied using default ACLs with the COPY metadata directive.

If you'd like to use a specfic CannedACL or MetadataDirective, use CopyObject directly with runAction

copyObjectWithin Source #

Arguments

:: MonadSpaces m 
=> Bucket 
-> Object

Source Object

-> Object

Destination Object

-> m (SpacesResponse CopyObject) 

Copy an Object within the same Bucket, using defaults for the MetadataDirective and CannedACL

overwriteObject :: MonadSpaces m => Bucket -> Object -> m (SpacesResponse CopyObject) Source #

Copy an Object to itself, overwriting its associated metadata

getObjectACLs :: MonadSpaces m => Bucket -> Object -> m (SpacesResponse GetObjectACLs) Source #

Get an Object's Access Control Lists

setObjectACLs :: MonadSpaces m => Bucket -> Object -> Owner -> [Grant] -> m (SpacesResponse SetObjectACLs) Source #

Set an Object's Access Control Lists

Bucket operations

createBucket Source #

Arguments

:: MonadSpaces m 
=> Bucket 
-> Maybe Region

Overrides the Region in your Spaces configuration

-> Maybe CannedACL 
-> m (SpacesResponse CreateBucket) 

Create a new Bucket

listAllBuckets :: MonadSpaces m => m (SpacesResponse ListAllBuckets) Source #

List every Bucket associated with your Spaces account

listBucket :: MonadSpaces m => Bucket -> m (SpacesResponse ListBucket) Source #

List the Objects of a Bucket, without grouping, delimiting, or limiting the keys (i.e. list all Objects non-hierarchically, up to the Spaces limit)

listBucketGrouped Source #

Arguments

:: MonadSpaces m 
=> Bucket 
-> Char

Delimiter

-> Text

Prefix used to group object keys

-> m (SpacesResponse ListBucket) 

List the Objects of a Bucket, using a delimiter and prefix to group objects. For example / can be used as a delimiter to treat objects as directories within the bucket, which can further be combined with a text prefix

listBucketRec :: MonadSpaces m => Bucket -> m (Seq ObjectInfo) Source #

Recursively list all Objects in a Bucket, calling ListBucket until isTruncated is False. This operation may take some time, depending on the total number of objects in your bucket

getBucketCORS :: MonadSpaces m => Bucket -> m (SpacesResponse GetBucketCORS) Source #

Get the CORSRules configured for a given Bucket

deleteBucketCORS :: MonadSpaces m => Bucket -> m (SpacesResponse DeleteBucketCORS) Source #

Delete the existing configured CORSRules for a given Bucket

getBucketACLs :: MonadSpaces m => Bucket -> m (SpacesResponse GetBucketACLs) Source #

Get a Bucket's Access Control Lists

setBucketACLs :: MonadSpaces m => Bucket -> [Grant] -> Owner -> m (SpacesResponse SetBucketACLs) Source #

Set a Bucket's Access Control Lists. Spaces only allows a limited subset of s3 ACLs at the moment. It may be preferable to use a CannedACL when creating new resources rather than using this action, which is provided for the sake of completeness.

Note that to allow public read-only access to your bucket, you must simultaneously set full owner control.

getBucketLifecycleRules :: MonadSpaces m => Bucket -> m (SpacesResponse GetBucketLifecycle) Source #

Get a Bucket's LifecycleRule configuration . Note that unless you have explicitly configured lifecycle rules, this will fail with a 404 status and an error code of NoSuchLifecycleConfiguration

Re-exports

data Spaces Source #

A client for interacting with the DO Spaces API

Instances

Instances details
Generic Spaces Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep Spaces :: Type -> Type #

Methods

from :: Spaces -> Rep Spaces x #

to :: Rep Spaces x -> Spaces #

HasHttpManager Spaces Source # 
Instance details

Defined in Network.DO.Spaces.Types

Monad m => MonadReader Spaces (SpacesT m) Source # 
Instance details

Defined in Network.DO.Spaces.Types

Methods

ask :: SpacesT m Spaces #

local :: (Spaces -> Spaces) -> SpacesT m a -> SpacesT m a #

reader :: (Spaces -> a) -> SpacesT m a #

type Rep Spaces Source # 
Instance details

Defined in Network.DO.Spaces.Types

data SpacesResponse a Source #

Instances

Instances details
(HasField' name (SpacesResponse a) s, s ~ t, a ~ b) => HasField name (SpacesResponse a) (SpacesResponse b) s t Source # 
Instance details

Defined in Network.DO.Spaces.Types

Methods

field :: Lens (SpacesResponse a) (SpacesResponse b) s t #

Show (ConsumedResponse a) => Show (SpacesResponse a) Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic (SpacesResponse a) Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep (SpacesResponse a) :: Type -> Type #

type Rep (SpacesResponse a) Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep (SpacesResponse a) = D1 ('MetaData "SpacesResponse" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "SpacesResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "result") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (ConsumedResponse a)) :*: S1 ('MetaSel ('Just "metadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe SpacesMetadata))))

data SpacesMetadata Source #

Metadata and other response information returned from each Spaces API transaction; it can be helpful to retain this at times

Instances

Instances details
Eq SpacesMetadata Source # 
Instance details

Defined in Network.DO.Spaces.Types

Show SpacesMetadata Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic SpacesMetadata Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep SpacesMetadata :: Type -> Type #

type Rep SpacesMetadata Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep SpacesMetadata = D1 ('MetaData "SpacesMetadata" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "SpacesMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "requestID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe RequestID)) :*: (S1 ('MetaSel ('Just "date") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Status))))

type MonadSpaces m = (MonadReader Spaces m, MonadIO m, MonadUnliftIO m, MonadCatch m) Source #

A synonym for the constraints necessary to run SpacesT actions

data Bucket Source #

The name of a single storage bucket

Instances

Instances details
Eq Bucket Source # 
Instance details

Defined in Network.DO.Spaces.Types

Methods

(==) :: Bucket -> Bucket -> Bool #

(/=) :: Bucket -> Bucket -> Bool #

Show Bucket Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic Bucket Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep Bucket :: Type -> Type #

Methods

from :: Bucket -> Rep Bucket x #

to :: Rep Bucket x -> Bucket #

ToHttpApiData Bucket Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep Bucket Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep Bucket = D1 ('MetaData "Bucket" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'True) (C1 ('MetaCons "Bucket" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

mkBucket :: MonadThrow m => Text -> m Bucket Source #

Smart constructor for Buckets; names must conform to the following rules:

This function ensures that names are valid and will also convert the Text to lowercase

data Object Source #

The name of a "key", in AWS parlance

Instances

Instances details
Eq Object Source # 
Instance details

Defined in Network.DO.Spaces.Types

Methods

(==) :: Object -> Object -> Bool #

(/=) :: Object -> Object -> Bool #

Show Object Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic Object Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep Object :: Type -> Type #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

ToHttpApiData Object Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep Object Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep Object = D1 ('MetaData "Object" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'True) (C1 ('MetaCons "Object" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

mkObject :: MonadThrow m => Text -> m Object Source #

Smart constructor for Objects; names must not be empty

data Region Source #

DO regions where Spaces is available (only a subset of all regions)

Constructors

NewYork

NYC3

Amsterdam

AMS3

SanFrancisco

SFO3

Singapore

SGP1

Frankfurt

FRA1

Instances

Instances details
Eq Region Source # 
Instance details

Defined in Network.DO.Spaces.Types

Methods

(==) :: Region -> Region -> Bool #

(/=) :: Region -> Region -> Bool #

Show Region Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic Region Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep Region :: Type -> Type #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

type Rep Region Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep Region = D1 ('MetaData "Region" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) ((C1 ('MetaCons "NewYork" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Amsterdam" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SanFrancisco" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Singapore" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Frankfurt" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype AccessKey Source #

Spaces access key

Constructors

AccessKey 

Instances

Instances details
Eq AccessKey Source # 
Instance details

Defined in Network.DO.Spaces.Types

Show AccessKey Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic AccessKey Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep AccessKey :: Type -> Type #

type Rep AccessKey Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep AccessKey = D1 ('MetaData "AccessKey" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'True) (C1 ('MetaCons "AccessKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAccessKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

newtype SecretKey Source #

Spaces secret key

Constructors

SecretKey 

Instances

Instances details
Eq SecretKey Source # 
Instance details

Defined in Network.DO.Spaces.Types

Show SecretKey Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic SecretKey Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep SecretKey :: Type -> Type #

type Rep SecretKey Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep SecretKey = D1 ('MetaData "SecretKey" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'True) (C1 ('MetaCons "SecretKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSecretKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

data CredentialSource Source #

How to discover the Region, AccessKey, and SecretKey when creating a new Spaces client.

Constructors

Discover

Try a sequence of different sources until one succeeds

FromEnv (Maybe (Text, Text, Text))

Region, AccessKey and SecretKey env vars

FromFile FilePath (Maybe Profile)

Load your credentials from a file, optionally providing the profile to use (or default as the... default).

Explicit Region AccessKey SecretKey

Provide all values explicitly

type Profile = Text Source #

The name of a per-project configuration profile to select when loading credentials from a file

data CORSRule Source #

Cross-origin resource sharing rules

Instances

Instances details
Eq CORSRule Source # 
Instance details

Defined in Network.DO.Spaces.Types

Show CORSRule Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic CORSRule Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep CORSRule :: Type -> Type #

Methods

from :: CORSRule -> Rep CORSRule x #

to :: Rep CORSRule x -> CORSRule #

type Rep CORSRule Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep CORSRule = D1 ('MetaData "CORSRule" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "CORSRule" 'PrefixI 'True) (S1 ('MetaSel ('Just "allowedOrigin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "allowedMethods") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Method]) :*: S1 ('MetaSel ('Just "allowedHeaders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [HeaderName]))))

mkCORSRule :: MonadThrow m => Text -> [Method] -> [HeaderName] -> m CORSRule Source #

Smart constructor for CORSRule. Ensures that both origins and header names contain a maximum of one wildcard and removes duplicates from both headers and methods

data Grant Source #

An individual access grant

Instances

Instances details
Eq Grant Source # 
Instance details

Defined in Network.DO.Spaces.Types

Methods

(==) :: Grant -> Grant -> Bool #

(/=) :: Grant -> Grant -> Bool #

Show Grant Source # 
Instance details

Defined in Network.DO.Spaces.Types

Methods

showsPrec :: Int -> Grant -> ShowS #

show :: Grant -> String #

showList :: [Grant] -> ShowS #

Generic Grant Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep Grant :: Type -> Type #

Methods

from :: Grant -> Rep Grant x #

to :: Rep Grant x -> Grant #

type Rep Grant Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep Grant = D1 ('MetaData "Grant" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "Grant" 'PrefixI 'True) (S1 ('MetaSel ('Just "permission") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Permission) :*: S1 ('MetaSel ('Just "grantee") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Grantee)))

data Grantee Source #

Information about who an access grant applies to

Constructors

Group

Nominally contains a URI value, but Spaces only supports a single value for group access grants

CanonicalUser Owner 

Instances

Instances details
Eq Grantee Source # 
Instance details

Defined in Network.DO.Spaces.Types

Methods

(==) :: Grantee -> Grantee -> Bool #

(/=) :: Grantee -> Grantee -> Bool #

Show Grantee Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic Grantee Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep Grantee :: Type -> Type #

Methods

from :: Grantee -> Rep Grantee x #

to :: Rep Grantee x -> Grantee #

type Rep Grantee Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep Grantee = D1 ('MetaData "Grantee" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "Group" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CanonicalUser" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Owner)))

data Permission Source #

Access grant level; Spaces currently only supports these two levels

Constructors

ReadOnly 
FullControl 

Instances

Instances details
Eq Permission Source # 
Instance details

Defined in Network.DO.Spaces.Types

Ord Permission Source # 
Instance details

Defined in Network.DO.Spaces.Types

Show Permission Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic Permission Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep Permission :: Type -> Type #

type Rep Permission Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep Permission = D1 ('MetaData "Permission" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "ReadOnly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FullControl" 'PrefixI 'False) (U1 :: Type -> Type))

data LifecycleID Source #

A unique ID for a LifecycleRule

Instances

Instances details
Eq LifecycleID Source # 
Instance details

Defined in Network.DO.Spaces.Types

Show LifecycleID Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic LifecycleID Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep LifecycleID :: Type -> Type #

type Rep LifecycleID Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep LifecycleID = D1 ('MetaData "LifecycleID" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'True) (C1 ('MetaCons "LifecycleID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

mkLifecycleID :: MonadThrow m => Text -> m LifecycleID Source #

Smart constructor for LifecycleID, which may contain a maximum of 255 characters, including spaces

data ClientException Source #

An exception generated within the Spaces client

Instances

Instances details
Eq ClientException Source # 
Instance details

Defined in Network.DO.Spaces.Types

Show ClientException Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic ClientException Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep ClientException :: Type -> Type #

Exception ClientException Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep ClientException Source # 
Instance details

Defined in Network.DO.Spaces.Types

data APIException Source #

An s3-compatible API error response, sent as XML

Instances

Instances details
Eq APIException Source # 
Instance details

Defined in Network.DO.Spaces.Types

Show APIException Source # 
Instance details

Defined in Network.DO.Spaces.Types

Generic APIException Source # 
Instance details

Defined in Network.DO.Spaces.Types

Associated Types

type Rep APIException :: Type -> Type #

Exception APIException Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep APIException Source # 
Instance details

Defined in Network.DO.Spaces.Types

type Rep APIException = D1 ('MetaData "APIException" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "APIException" 'PrefixI 'True) ((S1 ('MetaSel ('Just "status") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Status) :*: S1 ('MetaSel ('Just "code") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "requestID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RequestID) :*: S1 ('MetaSel ('Just "hostID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text))))