Copyright | (c) 2013-2023 Brendan Hay |
---|---|
License | Mozilla Public License, v. 2.0. |
Maintainer | Brendan Hay <brendan.g.hay+amazonka@gmail.com> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- getFileSize :: MonadIO m => FilePath -> m Integer
- newtype ResponseBody = ResponseBody {
- body :: ConduitM () ByteString (ResourceT IO) ()
- _ResponseBody :: Iso' ResponseBody (ConduitM () ByteString (ResourceT IO) ())
- fuseStream :: ResponseBody -> ConduitM ByteString ByteString (ResourceT IO) () -> ResponseBody
- sinkBody :: MonadIO m => ResponseBody -> ConduitM ByteString Void (ResourceT IO) a -> m a
- newtype ChunkSize = ChunkSize Int
- _ChunkSize :: Iso' ChunkSize Int
- defaultChunkSize :: ChunkSize
- data ChunkedBody = ChunkedBody {}
- chunkedBody_size :: Lens' ChunkedBody ChunkSize
- chunkedBody_length :: Lens' ChunkedBody Integer
- chunkedBody_body :: Lens' ChunkedBody (ConduitM () ByteString (ResourceT IO) ())
- fuseChunks :: ChunkedBody -> ConduitM ByteString ByteString (ResourceT IO) () -> ChunkedBody
- fullChunks :: ChunkedBody -> Integer
- remainderBytes :: ChunkedBody -> Maybe Integer
- chunkedFile :: MonadIO m => ChunkSize -> FilePath -> m RequestBody
- chunkedFileRange :: MonadIO m => ChunkSize -> FilePath -> Integer -> Integer -> m RequestBody
- unsafeChunkedBody :: ChunkSize -> Integer -> ConduitM () ByteString (ResourceT IO) () -> RequestBody
- sourceFileChunks :: MonadResource m => ChunkSize -> FilePath -> ConduitM () ByteString m ()
- sourceFileRangeChunks :: MonadResource m => ChunkSize -> FilePath -> Integer -> Integer -> ConduitM () ByteString m ()
- data HashedBody
- = HashedStream (Digest SHA256) !Integer (ConduitM () ByteString (ResourceT IO) ())
- | HashedBytes (Digest SHA256) ByteString
- sha256Base16 :: HashedBody -> ByteString
- hashedFile :: MonadIO m => FilePath -> m HashedBody
- hashedFileRange :: MonadIO m => FilePath -> Integer -> Integer -> m HashedBody
- hashedBody :: Digest SHA256 -> Integer -> ConduitM () ByteString (ResourceT IO) () -> HashedBody
- data RequestBody
- md5Base64 :: RequestBody -> Maybe ByteString
- isStreaming :: RequestBody -> Bool
- toRequestBody :: RequestBody -> RequestBody
- contentLength :: RequestBody -> Integer
- class ToHashedBody a where
- toHashed :: a -> HashedBody
- class ToBody a where
- toBody :: a -> RequestBody
Documentation
getFileSize :: MonadIO m => FilePath -> m Integer Source #
Convenience function for obtaining the size of a file.
newtype ResponseBody Source #
A streaming, exception safe response body.
newtype
for show/orhpan instance purposes.
ResponseBody | |
|
Instances
Generic ResponseBody Source # | |
Defined in Amazonka.Data.Body type Rep ResponseBody :: Type -> Type # from :: ResponseBody -> Rep ResponseBody x # to :: Rep ResponseBody x -> ResponseBody # | |
Show ResponseBody Source # | |
Defined in Amazonka.Data.Body showsPrec :: Int -> ResponseBody -> ShowS # show :: ResponseBody -> String # showList :: [ResponseBody] -> ShowS # | |
type Rep ResponseBody Source # | |
Defined in Amazonka.Data.Body type Rep ResponseBody = D1 ('MetaData "ResponseBody" "Amazonka.Data.Body" "amazonka-core-2.0-BFuA7FRvuklLoYhn4b6A6p" 'True) (C1 ('MetaCons "ResponseBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "body") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConduitM () ByteString (ResourceT IO) ())))) |
_ResponseBody :: Iso' ResponseBody (ConduitM () ByteString (ResourceT IO) ()) Source #
fuseStream :: ResponseBody -> ConduitM ByteString ByteString (ResourceT IO) () -> ResponseBody Source #
sinkBody :: MonadIO m => ResponseBody -> ConduitM ByteString Void (ResourceT IO) a -> m a Source #
Connect a Sink
to a response stream.
Specifies the transmitted size of the 'Transfer-Encoding' chunks.
See: defaultChunk
.
Instances
ToLog ChunkSize Source # | |
Defined in Amazonka.Data.Body build :: ChunkSize -> ByteStringBuilder Source # | |
Enum ChunkSize Source # | |
Defined in Amazonka.Data.Body succ :: ChunkSize -> ChunkSize # pred :: ChunkSize -> ChunkSize # fromEnum :: ChunkSize -> Int # enumFrom :: ChunkSize -> [ChunkSize] # enumFromThen :: ChunkSize -> ChunkSize -> [ChunkSize] # enumFromTo :: ChunkSize -> ChunkSize -> [ChunkSize] # enumFromThenTo :: ChunkSize -> ChunkSize -> ChunkSize -> [ChunkSize] # | |
Num ChunkSize Source # | |
Integral ChunkSize Source # | |
Defined in Amazonka.Data.Body | |
Real ChunkSize Source # | |
Defined in Amazonka.Data.Body toRational :: ChunkSize -> Rational # | |
Show ChunkSize Source # | |
Eq ChunkSize Source # | |
Ord ChunkSize Source # | |
Defined in Amazonka.Data.Body |
defaultChunkSize :: ChunkSize Source #
The default chunk size of 128 KB. The minimum chunk size accepted by AWS is 8 KB, unless the entirety of the request is below this threshold.
A chunk size of 64 KB or higher is recommended for performance reasons.
data ChunkedBody Source #
An opaque request body which will be transmitted via
Transfer-Encoding: chunked
.
Invariant: Only services that support chunked encoding can
accept a ChunkedBody
. (Currently S3.) This is enforced by the type
signatures emitted by the generator.
Instances
ToBody ChunkedBody Source # | |
Defined in Amazonka.Data.Body toBody :: ChunkedBody -> RequestBody Source # | |
Show ChunkedBody Source # | |
Defined in Amazonka.Data.Body showsPrec :: Int -> ChunkedBody -> ShowS # show :: ChunkedBody -> String # showList :: [ChunkedBody] -> ShowS # |
chunkedBody_body :: Lens' ChunkedBody (ConduitM () ByteString (ResourceT IO) ()) Source #
fuseChunks :: ChunkedBody -> ConduitM ByteString ByteString (ResourceT IO) () -> ChunkedBody Source #
fullChunks :: ChunkedBody -> Integer Source #
remainderBytes :: ChunkedBody -> Maybe Integer Source #
chunkedFile :: MonadIO m => ChunkSize -> FilePath -> m RequestBody Source #
Construct a ChunkedBody
from a FilePath
, where the contents will be
read and signed incrementally in chunks if the target service supports it.
Will intelligently revert to HashedBody
if the file is smaller than the
specified ChunkSize
.
See: ToBody
.
:: MonadIO m | |
=> ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> m RequestBody |
Construct a ChunkedBody
from a FilePath
, specifying the range of bytes
to read. This can be useful for constructing multiple requests from a single
file, say for S3 multipart uploads.
See: chunkedFile
.
:: ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> Integer | The size of the stream in bytes. |
-> ConduitM () ByteString (ResourceT IO) () | |
-> RequestBody |
Unsafely construct a ChunkedBody
.
This function is marked unsafe because it does nothing to enforce the chunk size.
Typically for conduit IO
functions, it's whatever ByteString's
defaultBufferSize
is, around 32 KB. If the chunk size is less than 8 KB,
the request will error. 64 KB or higher chunk size is recommended for
performance reasons.
Note that it will always create a chunked body even if the request is too small.
See: ToBody
.
sourceFileChunks :: MonadResource m => ChunkSize -> FilePath -> ConduitM () ByteString m () Source #
sourceFileRangeChunks Source #
:: MonadResource m | |
=> ChunkSize | The idealized size of chunks that will be yielded downstream. |
-> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> ConduitM () ByteString m () |
data HashedBody Source #
An opaque request body containing a SHA256
hash.
HashedStream (Digest SHA256) !Integer (ConduitM () ByteString (ResourceT IO) ()) | |
HashedBytes (Digest SHA256) ByteString |
Instances
ToBody HashedBody Source # | |
Defined in Amazonka.Data.Body toBody :: HashedBody -> RequestBody Source # | |
ToHashedBody HashedBody Source # | |
Defined in Amazonka.Data.Body toHashed :: HashedBody -> HashedBody Source # | |
IsString HashedBody Source # | |
Defined in Amazonka.Data.Body fromString :: String -> HashedBody # | |
Show HashedBody Source # | |
Defined in Amazonka.Data.Body showsPrec :: Int -> HashedBody -> ShowS # show :: HashedBody -> String # showList :: [HashedBody] -> ShowS # |
sha256Base16 :: HashedBody -> ByteString Source #
:: MonadIO m | |
=> FilePath | The file path to read. |
-> m HashedBody |
Construct a HashedBody
from a FilePath
, calculating the SHA256
hash
and file size.
Note: While this function will perform in constant space, it will enumerate the entirety of the file contents twice. Firstly to calculate the SHA256 and lastly to stream the contents to the socket during sending.
See: ToHashedBody
.
:: MonadIO m | |
=> FilePath | The file path to read. |
-> Integer | The byte offset at which to start reading. |
-> Integer | The maximum number of bytes to read. |
-> m HashedBody |
Construct a HashedBody
from a FilePath
, specifying the range of bytes
to read. This can be useful for constructing multiple requests from a single
file, say for S3 multipart uploads.
See: hashedFile
, sourceFileRange
.
:: Digest SHA256 | A SHA256 hash of the file contents. |
-> Integer | The size of the stream in bytes. |
-> ConduitM () ByteString (ResourceT IO) () | |
-> HashedBody |
Construct a HashedBody
from a Source
, manually specifying the SHA256
hash and file size. It's left up to the caller to calculate these correctly,
otherwise AWS will return signing errors.
See: ToHashedBody
.
data RequestBody Source #
Invariant: only services that support both standard and
chunked signing expose RequestBody
as a parameter.
Chunked ChunkedBody | Currently S3 only, see |
Hashed HashedBody |
Instances
ToBody RequestBody Source # | |
Defined in Amazonka.Data.Body toBody :: RequestBody -> RequestBody Source # | |
IsString RequestBody Source # | |
Defined in Amazonka.Data.Body fromString :: String -> RequestBody # | |
Show RequestBody Source # | |
Defined in Amazonka.Data.Body showsPrec :: Int -> RequestBody -> ShowS # show :: RequestBody -> String # showList :: [RequestBody] -> ShowS # |
md5Base64 :: RequestBody -> Maybe ByteString Source #
isStreaming :: RequestBody -> Bool Source #
contentLength :: RequestBody -> Integer Source #
class ToHashedBody a where Source #
Anything that can be safely converted to a HashedBody
.
toHashed :: a -> HashedBody Source #
Convert a value to a hashed request body.
Instances
Anything that can be converted to a streaming request Body
.
Nothing
toBody :: a -> RequestBody Source #
Convert a value to a request body.
default toBody :: ToHashedBody a => a -> RequestBody Source #