Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data S3Authorization
- data RequestStyle
- data S3SignPayloadMode
- data S3SignVersion
- data S3Configuration qt = S3Configuration {}
- s3EndpointUsClassic :: ByteString
- s3EndpointUsWest :: ByteString
- s3EndpointUsWest2 :: ByteString
- s3EndpointEu :: ByteString
- s3EndpointEuWest2 :: ByteString
- s3EndpointApSouthEast :: ByteString
- s3EndpointApSouthEast2 :: ByteString
- s3EndpointApNorthEast :: ByteString
- s3 :: Protocol -> ByteString -> Bool -> S3Configuration qt
- s3v4 :: Protocol -> ByteString -> Bool -> S3SignPayloadMode -> S3Configuration qt
- type ErrorCode = Text
- data S3Error = S3Error {}
- data S3Metadata = S3Metadata {}
- data S3Query = S3Query {}
- hAmzDate :: HeaderName
- hAmzContentSha256 :: HeaderName
- hAmzAlgorithm :: HeaderName
- hAmzCredential :: HeaderName
- hAmzExpires :: HeaderName
- hAmzSignedHeaders :: HeaderName
- hAmzSignature :: HeaderName
- hAmzSecurityToken :: HeaderName
- s3SignQuery :: S3Query -> S3Configuration qt -> SignatureData -> SignedQuery
- s3UriEncode :: Bool -> ByteString -> ByteString
- s3RenderQuery :: Bool -> Query -> ByteString
- s3ExtractRegion :: ByteString -> ByteString
- s3ResponseConsumer :: HTTPResponseConsumer a -> IORef S3Metadata -> HTTPResponseConsumer a
- s3BinaryResponseConsumer :: HTTPResponseConsumer a -> IORef S3Metadata -> HTTPResponseConsumer a
- s3XmlResponseConsumer :: (Cursor -> Response S3Metadata a) -> IORef S3Metadata -> HTTPResponseConsumer a
- s3ErrorResponseConsumer :: HTTPResponseConsumer a
- type CanonicalUserId = Text
- data UserInfo = UserInfo {}
- parseUserInfo :: MonadThrow m => Cursor -> m UserInfo
- data CannedAcl
- writeCannedAcl :: CannedAcl -> Text
- data StorageClass
- parseStorageClass :: Text -> StorageClass
- writeStorageClass :: StorageClass -> Text
- data ServerSideEncryption = AES256
- parseServerSideEncryption :: MonadThrow m => Text -> m ServerSideEncryption
- writeServerSideEncryption :: ServerSideEncryption -> Text
- type Bucket = Text
- data BucketInfo = BucketInfo {}
- type Object = Text
- data ObjectId = ObjectId {}
- data ObjectVersionInfo
- = ObjectVersion { }
- | DeleteMarker {
- oviKey :: Text
- oviVersionId :: Text
- oviIsLatest :: Bool
- oviLastModified :: UTCTime
- oviOwner :: Maybe UserInfo
- parseObjectVersionInfo :: MonadThrow m => Cursor -> m ObjectVersionInfo
- data ObjectInfo = ObjectInfo {}
- parseObjectInfo :: MonadThrow m => Cursor -> m ObjectInfo
- data ObjectMetadata = ObjectMetadata {}
- parseObjectMetadata :: MonadThrow m => ResponseHeaders -> m ObjectMetadata
- type LocationConstraint = Text
- locationUsClassic :: LocationConstraint
- locationUsWest :: LocationConstraint
- locationUsWest2 :: LocationConstraint
- locationEu :: LocationConstraint
- locationEuWest2 :: LocationConstraint
- locationEuFrankfurt :: LocationConstraint
- locationApSouthEast :: LocationConstraint
- locationApSouthEast2 :: LocationConstraint
- locationApNorthEast :: LocationConstraint
- locationSA :: LocationConstraint
- normaliseLocation :: LocationConstraint -> LocationConstraint
Documentation
data S3Authorization Source #
Instances
Show S3Authorization Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> S3Authorization -> ShowS # show :: S3Authorization -> String # showList :: [S3Authorization] -> ShowS # |
data RequestStyle Source #
PathStyle | Requires correctly setting region endpoint, but allows non-DNS compliant bucket names in the US standard region. |
BucketStyle | Bucket name must be DNS compliant. |
VHostStyle |
Instances
Show RequestStyle Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> RequestStyle -> ShowS # show :: RequestStyle -> String # showList :: [RequestStyle] -> ShowS # |
data S3SignPayloadMode Source #
AlwaysUnsigned | Always use the "UNSIGNED-PAYLOAD" option. |
SignWithEffort | Sign the payload when |
AlwaysSigned | Always sign the payload. Note: |
Instances
Eq S3SignPayloadMode Source # | |
Defined in Aws.S3.Core (==) :: S3SignPayloadMode -> S3SignPayloadMode -> Bool # (/=) :: S3SignPayloadMode -> S3SignPayloadMode -> Bool # | |
Read S3SignPayloadMode Source # | |
Defined in Aws.S3.Core | |
Show S3SignPayloadMode Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> S3SignPayloadMode -> ShowS # show :: S3SignPayloadMode -> String # showList :: [S3SignPayloadMode] -> ShowS # |
data S3SignVersion Source #
Instances
Eq S3SignVersion Source # | |
Defined in Aws.S3.Core (==) :: S3SignVersion -> S3SignVersion -> Bool # (/=) :: S3SignVersion -> S3SignVersion -> Bool # | |
Read S3SignVersion Source # | |
Defined in Aws.S3.Core readsPrec :: Int -> ReadS S3SignVersion # readList :: ReadS [S3SignVersion] # | |
Show S3SignVersion Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> S3SignVersion -> ShowS # show :: S3SignVersion -> String # showList :: [S3SignVersion] -> ShowS # |
data S3Configuration qt Source #
Instances
Show (S3Configuration qt) Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> S3Configuration qt -> ShowS # show :: S3Configuration qt -> String # showList :: [S3Configuration qt] -> ShowS # | |
DefaultServiceConfiguration (S3Configuration UriOnlyQuery) Source # | |
DefaultServiceConfiguration (S3Configuration NormalQuery) Source # | |
s3 :: Protocol -> ByteString -> Bool -> S3Configuration qt Source #
s3v4 :: Protocol -> ByteString -> Bool -> S3SignPayloadMode -> S3Configuration qt Source #
Instances
Show S3Error Source # | |
Exception S3Error Source # | |
Defined in Aws.S3.Core toException :: S3Error -> SomeException # fromException :: SomeException -> Maybe S3Error # displayException :: S3Error -> String # |
data S3Metadata Source #
Instances
Show S3Metadata Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> S3Metadata -> ShowS # show :: S3Metadata -> String # showList :: [S3Metadata] -> ShowS # | |
Semigroup S3Metadata Source # | |
Defined in Aws.S3.Core (<>) :: S3Metadata -> S3Metadata -> S3Metadata # sconcat :: NonEmpty S3Metadata -> S3Metadata # stimes :: Integral b => b -> S3Metadata -> S3Metadata # | |
Monoid S3Metadata Source # | |
Defined in Aws.S3.Core mempty :: S3Metadata # mappend :: S3Metadata -> S3Metadata -> S3Metadata # mconcat :: [S3Metadata] -> S3Metadata # | |
Loggable S3Metadata Source # | |
Defined in Aws.S3.Core toLogText :: S3Metadata -> Text Source # |
s3SignQuery :: S3Query -> S3Configuration qt -> SignatureData -> SignedQuery Source #
:: Bool | Whether encode slash characters |
-> ByteString | |
-> ByteString |
Custom UriEncode function see http://docs.aws.amazon.com/AmazonS3/latest/API/sig-v4-header-based-auth.html
:: Bool | Whether prepend a question mark |
-> Query | |
-> ByteString |
s3BinaryResponseConsumer :: HTTPResponseConsumer a -> IORef S3Metadata -> HTTPResponseConsumer a Source #
s3XmlResponseConsumer :: (Cursor -> Response S3Metadata a) -> IORef S3Metadata -> HTTPResponseConsumer a Source #
type CanonicalUserId = Text Source #
parseUserInfo :: MonadThrow m => Cursor -> m UserInfo Source #
writeCannedAcl :: CannedAcl -> Text Source #
data StorageClass Source #
Instances
Show StorageClass Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> StorageClass -> ShowS # show :: StorageClass -> String # showList :: [StorageClass] -> ShowS # |
parseStorageClass :: Text -> StorageClass Source #
writeStorageClass :: StorageClass -> Text Source #
data ServerSideEncryption Source #
Instances
Show ServerSideEncryption Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> ServerSideEncryption -> ShowS # show :: ServerSideEncryption -> String # showList :: [ServerSideEncryption] -> ShowS # |
parseServerSideEncryption :: MonadThrow m => Text -> m ServerSideEncryption Source #
data BucketInfo Source #
Instances
Show BucketInfo Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> BucketInfo -> ShowS # show :: BucketInfo -> String # showList :: [BucketInfo] -> ShowS # |
data ObjectVersionInfo Source #
ObjectVersion | |
| |
DeleteMarker | |
|
Instances
Show ObjectVersionInfo Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> ObjectVersionInfo -> ShowS # show :: ObjectVersionInfo -> String # showList :: [ObjectVersionInfo] -> ShowS # | |
ListResponse GetBucketObjectVersionsResponse ObjectVersionInfo Source # | |
parseObjectVersionInfo :: MonadThrow m => Cursor -> m ObjectVersionInfo Source #
data ObjectInfo Source #
Instances
Show ObjectInfo Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> ObjectInfo -> ShowS # show :: ObjectInfo -> String # showList :: [ObjectInfo] -> ShowS # | |
ListResponse GetBucketResponse ObjectInfo Source # | |
Defined in Aws.S3.Commands.GetBucket listResponse :: GetBucketResponse -> [ObjectInfo] Source # |
parseObjectInfo :: MonadThrow m => Cursor -> m ObjectInfo Source #
data ObjectMetadata Source #
Instances
Show ObjectMetadata Source # | |
Defined in Aws.S3.Core showsPrec :: Int -> ObjectMetadata -> ShowS # show :: ObjectMetadata -> String # showList :: [ObjectMetadata] -> ShowS # |
parseObjectMetadata :: MonadThrow m => ResponseHeaders -> m ObjectMetadata Source #
type LocationConstraint = Text Source #