Copyright | (c) 2021 Rory Tyler Hayford |
---|---|
License | BSD-3-Clause |
Maintainer | rory.hayford@protonmail.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- newtype SpacesT m a = SpacesT (ReaderT Spaces m a)
- runSpacesT :: SpacesT m a -> Spaces -> m a
- data Spaces = Spaces {}
- type MonadSpaces m = (MonadReader Spaces m, MonadIO m, MonadUnliftIO m, MonadCatch m)
- class Monad m => Action m a where
- type ConsumedResponse a :: Type
- buildRequest :: a -> m SpacesRequestBuilder
- consumeResponse :: RawResponse m -> m (ConsumedResponse a)
- data CredentialSource
- type Profile = Text
- newtype AccessKey = AccessKey {}
- newtype SecretKey = SecretKey {}
- newtype Object = Object Text
- mkObject :: MonadThrow m => Text -> m Object
- newtype Bucket = Bucket Text
- mkBucket :: MonadThrow m => Text -> m Bucket
- data BucketInfo = BucketInfo {
- name :: Bucket
- creationDate :: UTCTime
- newtype OwnerID = OwnerID Int
- type DisplayName = OwnerID
- data Owner = Owner {}
- data ObjectInfo = ObjectInfo {}
- data ObjectMetadata = ObjectMetadata {
- contentLength :: Int
- contentType :: MimeType
- etag :: ETag
- lastModified :: UTCTime
- type ETag = Text
- data SpacesRequest = SpacesRequest {
- request :: Request
- spaces :: Spaces
- headers :: [Header]
- method :: Method
- payloadHash :: Hashed
- canonicalRequest :: Canonicalized Request
- time :: UTCTime
- data SpacesResponse a = SpacesResponse {}
- data SpacesRequestBuilder = SpacesRequestBuilder {}
- data SpacesMetadata = SpacesMetadata {}
- data WithMetadata
- data RawResponse m = RawResponse {}
- type BodyBS m = ConduitT () ByteString m ()
- data Method
- data Region
- type RequestID = Text
- type CacheControl = Text
- type ContentDisposition = Text
- type ContentEncoding = Text
- type UserMetadata = [(Text, Text)]
- data UploadHeaders = UploadHeaders {}
- data CannedACL
- data CORSRule = CORSRule {
- allowedOrigin :: Text
- allowedMethods :: [Method]
- allowedHeaders :: [HeaderName]
- mkCORSRule :: MonadThrow m => Text -> [Method] -> [HeaderName] -> m CORSRule
- data Grant = Grant {}
- data Permission
- data Grantee
- data ACLResponse = ACLResponse {
- owner :: Owner
- accessControlList :: [Grant]
- data LifecycleRule = LifecycleRule {}
- data LifecycleExpiration
- newtype LifecycleID = LifecycleID Text
- mkLifecycleID :: MonadThrow m => Text -> m LifecycleID
- newtype Canonicalized a = Canonicalized ByteString
- 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
- type StringToSign = Computed 'StrToSign
- type Hashed = Computed 'Hash
- type Signature = Computed 'Sig
- type Credentials = Computed 'Cred
- type Authorization = Computed 'Auth
- uncompute :: Computed a -> ByteString
- data SpacesException
- data ClientException
- data APIException = APIException {}
- type Days = Word16
Spaces
Instances
Monad m => MonadReader Spaces (SpacesT m) Source # | |
Monad m => Monad (SpacesT m) Source # | |
Functor m => Functor (SpacesT m) Source # | |
Applicative m => Applicative (SpacesT m) Source # | |
MonadIO m => MonadIO (SpacesT m) Source # | |
Defined in Network.DO.Spaces.Types | |
MonadUnliftIO m => MonadUnliftIO (SpacesT m) Source # | |
Defined in Network.DO.Spaces.Types | |
MonadThrow m => MonadThrow (SpacesT m) Source # | |
Defined in Network.DO.Spaces.Types | |
MonadCatch m => MonadCatch (SpacesT m) Source # | |
Generic (SpacesT m a) Source # | |
type Rep (SpacesT m a) Source # | |
Defined in Network.DO.Spaces.Types |
runSpacesT :: SpacesT m a -> Spaces -> m a Source #
A client for interacting with the DO Spaces API
Instances
Generic Spaces Source # | |
HasHttpManager Spaces Source # | |
Defined in Network.DO.Spaces.Types getHttpManager :: Spaces -> Manager # | |
Monad m => MonadReader Spaces (SpacesT m) Source # | |
type Rep Spaces Source # | |
Defined in Network.DO.Spaces.Types type Rep Spaces = D1 ('MetaData "Spaces" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "Spaces" 'PrefixI 'True) ((S1 ('MetaSel ('Just "accessKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccessKey) :*: S1 ('MetaSel ('Just "secretKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SecretKey)) :*: (S1 ('MetaSel ('Just "region") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Region) :*: S1 ('MetaSel ('Just "manager") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Manager)))) |
type MonadSpaces m = (MonadReader Spaces m, MonadIO m, MonadUnliftIO m, MonadCatch m) Source #
A synonym for the constraints necessary to run SpacesT
actions
class Monad m => Action m a where Source #
type ConsumedResponse a :: Type Source #
buildRequest :: a -> m SpacesRequestBuilder Source #
consumeResponse :: RawResponse m -> m (ConsumedResponse a) Source #
Instances
data CredentialSource Source #
The name of a per-project configuration profile to select when loading credentials from a file
Spaces access key
Instances
Eq AccessKey Source # | |
Show AccessKey Source # | |
Generic AccessKey Source # | |
type Rep AccessKey Source # | |
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))) |
Spaces secret key
Instances
Eq SecretKey Source # | |
Show SecretKey Source # | |
Generic SecretKey Source # | |
type Rep SecretKey Source # | |
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))) |
Buckets and Objects
The name of a "key", in AWS parlance
Instances
Eq Object Source # | |
Show Object Source # | |
Generic Object Source # | |
ToHttpApiData Object Source # | |
Defined in Network.DO.Spaces.Types toUrlPiece :: Object -> Text # toEncodedUrlPiece :: Object -> Builder # toHeader :: Object -> ByteString # toQueryParam :: Object -> Text # | |
type Rep Object Source # | |
Defined in Network.DO.Spaces.Types |
mkObject :: MonadThrow m => Text -> m Object Source #
Smart constructor for Object
s; names must not be empty
The name of a single storage bucket
Instances
Eq Bucket Source # | |
Show Bucket Source # | |
Generic Bucket Source # | |
ToHttpApiData Bucket Source # | |
Defined in Network.DO.Spaces.Types toUrlPiece :: Bucket -> Text # toEncodedUrlPiece :: Bucket -> Builder # toHeader :: Bucket -> ByteString # toQueryParam :: Bucket -> Text # | |
type Rep Bucket Source # | |
Defined in Network.DO.Spaces.Types |
mkBucket :: MonadThrow m => Text -> m Bucket Source #
Smart constructor for Bucket
s; names must conform to the following rules:
- They must be between 3 and 63 characters in length
- They may only contain lowercase letters, digits, dots, and hyphens
- They must begin and end in a number or letter See more at: https://docs.aws.amazon.com/AmazonS3/latest/userguide/bucketnamingrules.html.
This function ensures that names are valid and will also convert the Text
to lowercase
data BucketInfo Source #
Information about a single Bucket
BucketInfo | |
|
Instances
Eq BucketInfo Source # | |
Defined in Network.DO.Spaces.Types (==) :: BucketInfo -> BucketInfo -> Bool # (/=) :: BucketInfo -> BucketInfo -> Bool # | |
Show BucketInfo Source # | |
Defined in Network.DO.Spaces.Types showsPrec :: Int -> BucketInfo -> ShowS # show :: BucketInfo -> String # showList :: [BucketInfo] -> ShowS # | |
Generic BucketInfo Source # | |
Defined in Network.DO.Spaces.Types type Rep BucketInfo :: Type -> Type # from :: BucketInfo -> Rep BucketInfo x # to :: Rep BucketInfo x -> BucketInfo # | |
type Rep BucketInfo Source # | |
Defined in Network.DO.Spaces.Types type Rep BucketInfo = D1 ('MetaData "BucketInfo" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "BucketInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bucket) :*: S1 ('MetaSel ('Just "creationDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UTCTime))) |
The ID of an Owner
; also serves as a display name in Spaces
Instances
Eq OwnerID Source # | |
Num OwnerID Source # | |
Show OwnerID Source # | |
Generic OwnerID Source # | |
ToHttpApiData OwnerID Source # | |
Defined in Network.DO.Spaces.Types toUrlPiece :: OwnerID -> Text # toEncodedUrlPiece :: OwnerID -> Builder # toHeader :: OwnerID -> ByteString # toQueryParam :: OwnerID -> Text # | |
type Rep OwnerID Source # | |
Defined in Network.DO.Spaces.Types |
type DisplayName = OwnerID Source #
The display name is always equivalent to the owner's ID; Spaces includes it for AWS compatibility
The resource owner
Instances
Eq Owner Source # | |
Show Owner Source # | |
Generic Owner Source # | |
type Rep Owner Source # | |
Defined in Network.DO.Spaces.Types type Rep Owner = D1 ('MetaData "Owner" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "Owner" 'PrefixI 'True) (S1 ('MetaSel ('Just "ownerID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OwnerID) :*: S1 ('MetaSel ('Just "displayName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DisplayName))) |
data ObjectInfo Source #
Instances
data ObjectMetadata Source #
Metadata returned when querying information about an Object
ObjectMetadata | |
|
Instances
Requests and responses
data SpacesRequest Source #
SpacesRequest | |
|
Instances
data SpacesResponse a Source #
A ConsumedResponse
with optional SpacesMetadata
SpacesResponse | |
|
Instances
data SpacesRequestBuilder Source #
SpacesRequestBuilder | |
|
Instances
data SpacesMetadata Source #
Metadata and other response information returned from each Spaces API transaction; it can be helpful to retain this at times
Instances
data WithMetadata Source #
Whether or not to retain SpacesMetadata
when consuming responses
Instances
Eq WithMetadata Source # | |
Defined in Network.DO.Spaces.Types (==) :: WithMetadata -> WithMetadata -> Bool # (/=) :: WithMetadata -> WithMetadata -> Bool # | |
Show WithMetadata Source # | |
Defined in Network.DO.Spaces.Types showsPrec :: Int -> WithMetadata -> ShowS # show :: WithMetadata -> String # showList :: [WithMetadata] -> ShowS # | |
Generic WithMetadata Source # | |
Defined in Network.DO.Spaces.Types type Rep WithMetadata :: Type -> Type # from :: WithMetadata -> Rep WithMetadata x # to :: Rep WithMetadata x -> WithMetadata # | |
type Rep WithMetadata Source # | |
data RawResponse m Source #
Instances
Generic (RawResponse m) Source # | |
Defined in Network.DO.Spaces.Types type Rep (RawResponse m) :: Type -> Type # from :: RawResponse m -> Rep (RawResponse m) x # to :: Rep (RawResponse m) x -> RawResponse m # | |
type Rep (RawResponse m) Source # | |
Defined in Network.DO.Spaces.Types type Rep (RawResponse m) = D1 ('MetaData "RawResponse" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "RawResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "headers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Header]) :*: S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (BodyBS m)))) |
type BodyBS m = ConduitT () ByteString m () Source #
A request or response body
HTTP request methods, to avoid using http-client
's stringly-typed Method
synonym
Instances
Eq Method Source # | |
Ord Method Source # | |
Read Method Source # | |
Show Method Source # | |
Generic Method Source # | |
type Rep Method Source # | |
Defined in Network.DO.Spaces.Types type Rep Method = D1 ('MetaData "Method" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) ((C1 ('MetaCons "GET" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "POST" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PUT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DELETE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HEAD" 'PrefixI 'False) (U1 :: Type -> Type)))) |
DO regions where Spaces is available (only a subset of all regions)
NewYork | NYC3 |
Amsterdam | AMS3 |
SanFrancisco | SFO3 |
Singapore | SGP1 |
Frankfurt | FRA1 |
Instances
Eq Region Source # | |
Show Region Source # | |
Generic Region Source # | |
type Rep Region Source # | |
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)))) |
type CacheControl = Text Source #
Cache-Control
request header value
type ContentDisposition = Text Source #
Content-Disposition
request header value
type ContentEncoding = Text Source #
Content-Encoding
request header value
type UserMetadata = [(Text, Text)] Source #
Arbitrary key-value pairs supplied by the user, for use in PUT
or POST
requests. Each pair expands into x-amz-meta-*
, e.g.
x-amz-meta-s3cmd-attrs: uid:1000/gname:asb...
data UploadHeaders Source #
Optional headers when uploading objects
Instances
"Canned" access controls; Spaces doesn't support the full range offered by s3
Private | No unauthenticated public access |
PublicRead | Unauthenticated public read access permitted |
Cross-origin resource sharing rules
CORSRule | |
|
Instances
Eq CORSRule Source # | |
Show CORSRule Source # | |
Generic CORSRule Source # | |
type Rep CORSRule Source # | |
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
An individual access grant
Grant | |
|
Instances
Eq Grant Source # | |
Show Grant Source # | |
Generic Grant Source # | |
type Rep Grant Source # | |
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 Permission Source #
Access grant level; Spaces currently only supports these two levels
Instances
Eq Permission Source # | |
Defined in Network.DO.Spaces.Types (==) :: Permission -> Permission -> Bool # (/=) :: Permission -> Permission -> Bool # | |
Ord Permission Source # | |
Defined in Network.DO.Spaces.Types compare :: Permission -> Permission -> Ordering # (<) :: Permission -> Permission -> Bool # (<=) :: Permission -> Permission -> Bool # (>) :: Permission -> Permission -> Bool # (>=) :: Permission -> Permission -> Bool # max :: Permission -> Permission -> Permission # min :: Permission -> Permission -> Permission # | |
Show Permission Source # | |
Defined in Network.DO.Spaces.Types showsPrec :: Int -> Permission -> ShowS # show :: Permission -> String # showList :: [Permission] -> ShowS # | |
Generic Permission Source # | |
Defined in Network.DO.Spaces.Types type Rep Permission :: Type -> Type # from :: Permission -> Rep Permission x # to :: Rep Permission x -> Permission # | |
type Rep Permission Source # | |
Information about who an access grant applies to
Group | Nominally contains a URI value, but Spaces only supports a single value for group access grants |
CanonicalUser Owner |
Instances
Eq Grantee Source # | |
Show Grantee Source # | |
Generic Grantee Source # | |
type Rep Grantee Source # | |
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 ACLResponse Source #
ACLResponse | |
|
Instances
Eq ACLResponse Source # | |
Defined in Network.DO.Spaces.Types (==) :: ACLResponse -> ACLResponse -> Bool # (/=) :: ACLResponse -> ACLResponse -> Bool # | |
Show ACLResponse Source # | |
Defined in Network.DO.Spaces.Types showsPrec :: Int -> ACLResponse -> ShowS # show :: ACLResponse -> String # showList :: [ACLResponse] -> ShowS # | |
Generic ACLResponse Source # | |
Defined in Network.DO.Spaces.Types type Rep ACLResponse :: Type -> Type # from :: ACLResponse -> Rep ACLResponse x # to :: Rep ACLResponse x -> ACLResponse # | |
type Rep ACLResponse Source # | |
Defined in Network.DO.Spaces.Types type Rep ACLResponse = D1 ('MetaData "ACLResponse" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'False) (C1 ('MetaCons "ACLResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "owner") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Owner) :*: S1 ('MetaSel ('Just "accessControlList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Grant]))) |
data LifecycleRule Source #
Lifecycle configuration for a Bucket
LifecycleRule | |
|
Instances
data LifecycleExpiration Source #
Configuration for automatically deleting expire Object
s
Instances
newtype LifecycleID Source #
A unique ID for a LifecycleRule
Instances
Eq LifecycleID Source # | |
Defined in Network.DO.Spaces.Types (==) :: LifecycleID -> LifecycleID -> Bool # (/=) :: LifecycleID -> LifecycleID -> Bool # | |
Show LifecycleID Source # | |
Defined in Network.DO.Spaces.Types showsPrec :: Int -> LifecycleID -> ShowS # show :: LifecycleID -> String # showList :: [LifecycleID] -> ShowS # | |
Generic LifecycleID Source # | |
Defined in Network.DO.Spaces.Types type Rep LifecycleID :: Type -> Type # from :: LifecycleID -> Rep LifecycleID x # to :: Rep LifecycleID x -> LifecycleID # | |
type Rep LifecycleID Source # | |
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
Signature calculation
newtype Canonicalized a Source #
Represents some resource that has been canonicalized according to the Spaces/AWS v4 spec
Instances
Eq (Canonicalized a) Source # | |
Defined in Network.DO.Spaces.Types (==) :: Canonicalized a -> Canonicalized a -> Bool # (/=) :: Canonicalized a -> Canonicalized a -> Bool # | |
Show (Canonicalized a) Source # | |
Defined in Network.DO.Spaces.Types showsPrec :: Int -> Canonicalized a -> ShowS # show :: Canonicalized a -> String # showList :: [Canonicalized a] -> ShowS # | |
Generic (Canonicalized a) Source # | |
Defined in Network.DO.Spaces.Types type Rep (Canonicalized a) :: Type -> Type # from :: Canonicalized a -> Rep (Canonicalized a) x # to :: Rep (Canonicalized a) x -> Canonicalized a # | |
type Rep (Canonicalized a) Source # | |
Defined in Network.DO.Spaces.Types type Rep (Canonicalized a) = D1 ('MetaData "Canonicalized" "Network.DO.Spaces.Types" "do-spaces-0.2-6plBREpGHjL7zr5f6tFOCc" 'True) (C1 ('MetaCons "Canonicalized" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
data Computed (a :: ComputedTag) where Source #
A strict ByteString
that has been computed according to some part of
the AWS v4 spec. The AWS v4 signature is calculated from a series of
interdependent computations. It would be possible to represent these all as
ByteString
s; this approach, however, would make it easy to confuse two
sequences that are not semantically equivalent, leading to the generation of
malformed singatures. The promiscuous use of ByteString
s also makes for
unclear type signatures. Using a GADT with type synonyms is simpler than
creating a newtype
for each type of computation
Hashed :: ByteString -> Computed Hash | |
StringToSign :: ByteString -> Computed StrToSign | Represents a "string to sign" that has been computed according to the Spaces/AWS v4 spec |
Signature :: ByteString -> Computed Sig | Signed hash of a |
Credentials :: ByteString -> Computed Cred | |
Authorization :: ByteString -> Computed Auth | Authorization string containing information about your |
type StringToSign = Computed 'StrToSign Source #
type Credentials = Computed 'Cred Source #
type Authorization = Computed 'Auth Source #
uncompute :: Computed a -> ByteString Source #
Extract the ByteString
from something Computed
Exceptions
data SpacesException Source #
The base Exception
type for both ClientException
s and APIException
s
Instances
Show SpacesException Source # | |
Defined in Network.DO.Spaces.Types showsPrec :: Int -> SpacesException -> ShowS # show :: SpacesException -> String # showList :: [SpacesException] -> ShowS # | |
Exception SpacesException Source # | |
Defined in Network.DO.Spaces.Types |
data ClientException Source #
An exception generated within the Spaces
client
InvalidRequest Text | |
InvalidResponse Text | |
InvalidXML Text | |
ConfigurationError Text | |
HTTPStatus Status ByteString | This includes the raw |
OtherError Text |
Instances
data APIException Source #
An s3-compatible API error response, sent as XML