minio-hs-1.5.2: A MinIO Haskell Library for Amazon S3 compatible cloud storage.

Copyright(c) 2017-2019 MinIO Dev Team
LicenseApache 2.0
MaintainerMinIO Dev Team <dev@min.io>
Safe HaskellNone
LanguageHaskell2010

Network.Minio

Contents

Description

Types and functions to conveniently access S3 compatible object storage servers like MinIO.

Synopsis

Credentials

data Credentials Source #

Contains access key and secret key to access object storage.

Constructors

Credentials 
Instances
Eq Credentials Source # 
Instance details

Defined in Network.Minio.Data

Show Credentials Source # 
Instance details

Defined in Network.Minio.Data

Credential providers

Run actions that retrieve Credentials from the environment or files or other custom sources.

type Provider = IO (Maybe Credentials) Source #

A Provider is an action that may return Credentials. Providers may be chained together using findFirst.

fromAWSConfigFile :: Provider Source #

This Provider loads Credentials from ~/.aws/credentials

fromAWSEnv :: Provider Source #

This Provider loads Credentials from AWS_ACCESS_KEY_ID and AWS_SECRET_ACCESS_KEY environment variables.

fromMinioEnv :: Provider Source #

This Provider loads Credentials from MINIO_ACCESS_KEY and MINIO_SECRET_KEY environment variables.

findFirst :: [Provider] -> Provider Source #

Combines the given list of providers, by calling each one in order until Credentials are found.

Connecting to object storage

data ConnectInfo Source #

Connection Info data type. To create a ConnectInfo value, enable the OverloadedStrings language extension and use the IsString instance to provide a URL, for example:

let c :: ConnectInfo = "https://play.min.io"
Instances
Eq ConnectInfo Source # 
Instance details

Defined in Network.Minio.Data

Show ConnectInfo Source # 
Instance details

Defined in Network.Minio.Data

IsString ConnectInfo Source # 
Instance details

Defined in Network.Minio.Data

setRegion :: Region -> ConnectInfo -> ConnectInfo Source #

Set the S3 region parameter in the ConnectInfo

setCreds :: Credentials -> ConnectInfo -> ConnectInfo Source #

setCreds sets the given Credentials in the ConnectInfo.

setCredsFrom :: [Provider] -> ConnectInfo -> IO ConnectInfo Source #

setCredsFrom retrieves access credentials from the first Provider form the given list that succeeds and sets it in the ConnectInfo.

isConnectInfoSecure :: ConnectInfo -> Bool Source #

Check if the connection to object storage server is secure (i.e. uses TLS)

disableTLSCertValidation :: ConnectInfo -> ConnectInfo Source #

Disable TLS certificate validation completely! This makes TLS insecure! Use only for testing with self-signed or temporary certificates. Note that this option has no effect, if you provide your own Manager in mkMinioConn.

data MinioConn Source #

MinioConn holds connection info and a connection pool to allow for efficient resource re-use.

Instances
MonadReader MinioConn Minio Source # 
Instance details

Defined in Network.Minio.Data

Methods

ask :: Minio MinioConn #

local :: (MinioConn -> MinioConn) -> Minio a -> Minio a #

reader :: (MinioConn -> a) -> Minio a #

mkMinioConn :: ConnectInfo -> Manager -> IO MinioConn Source #

Given ConnectInfo and a HTTP connection manager, create a MinioConn.

Connection helpers

These are helpers to construct ConnectInfo values for common cases.

minioPlayCI :: ConnectInfo Source #

MinIO Play Server ConnectInfo. Credentials are already filled in.

awsCI :: ConnectInfo Source #

Default AWS S3 ConnectInfo. Connects to "us-east-1". Credentials should be supplied before use.

gcsCI :: ConnectInfo Source #

Default Google Compute Storage ConnectInfo. Works only for "Simple Migration" use-case with interoperability mode enabled on GCP console. For more information - https://cloud.google.com/storage/docs/migrating

Credentials should be supplied before use.

Minio Monad

The Minio Monad provides connection-reuse, bucket-location caching, resource management and simpler error handling functionality. All actions on object storage are performed within this Monad.

data Minio a Source #

The Minio Monad - all computations accessing object storage happens in it.

Instances
Monad Minio Source # 
Instance details

Defined in Network.Minio.Data

Methods

(>>=) :: Minio a -> (a -> Minio b) -> Minio b #

(>>) :: Minio a -> Minio b -> Minio b #

return :: a -> Minio a #

fail :: String -> Minio a #

Functor Minio Source # 
Instance details

Defined in Network.Minio.Data

Methods

fmap :: (a -> b) -> Minio a -> Minio b #

(<$) :: a -> Minio b -> Minio a #

Applicative Minio Source # 
Instance details

Defined in Network.Minio.Data

Methods

pure :: a -> Minio a #

(<*>) :: Minio (a -> b) -> Minio a -> Minio b #

liftA2 :: (a -> b -> c) -> Minio a -> Minio b -> Minio c #

(*>) :: Minio a -> Minio b -> Minio b #

(<*) :: Minio a -> Minio b -> Minio a #

MonadIO Minio Source # 
Instance details

Defined in Network.Minio.Data

Methods

liftIO :: IO a -> Minio a #

MonadUnliftIO Minio Source # 
Instance details

Defined in Network.Minio.Data

Methods

askUnliftIO :: Minio (UnliftIO Minio) #

withRunInIO :: ((forall a. Minio a -> IO a) -> IO b) -> Minio b #

MonadResource Minio Source # 
Instance details

Defined in Network.Minio.Data

Methods

liftResourceT :: ResourceT IO a -> Minio a #

MonadReader MinioConn Minio Source # 
Instance details

Defined in Network.Minio.Data

Methods

ask :: Minio MinioConn #

local :: (MinioConn -> MinioConn) -> Minio a -> Minio a #

reader :: (MinioConn -> a) -> Minio a #

runMinioWith :: MinioConn -> Minio a -> IO (Either MinioErr a) Source #

Run the computation accessing object storage using the given MinioConn. This reuses connections, but otherwise it is similar to runMinio.

runMinio :: ConnectInfo -> Minio a -> IO (Either MinioErr a) Source #

Run the Minio action and return the result or an error.

runMinioResWith :: MinioConn -> Minio a -> ResourceT IO (Either MinioErr a) Source #

Similar to runMinioWith. Allows applications to allocate/release its resources along side MinIO's internal resources.

runMinioRes :: ConnectInfo -> Minio a -> ResourceT IO (Either MinioErr a) Source #

Similar to runMinio. Allows applications to allocate/release its resources along side MinIO's internal resources.

Bucket Operations

Creation, removal and querying

type Bucket = Text Source #

Represents a bucket in the object store

makeBucket :: Bucket -> Maybe Region -> Minio () Source #

Creates a new bucket in the object store. The Region can be optionally specified. If not specified, it will use the region configured in ConnectInfo, which is by default, the US Standard Region.

removeBucket :: Bucket -> Minio () Source #

Removes a bucket from the object store.

bucketExists :: Bucket -> Minio Bool Source #

Query the object store if a given bucket is present.

type Region = Text Source #

Represents a region

getLocation :: Bucket -> Minio Region Source #

Fetch bucket location (region)

Listing buckets

data BucketInfo Source #

BucketInfo returned for list buckets call

Constructors

BucketInfo 
Instances
Eq BucketInfo Source # 
Instance details

Defined in Network.Minio.Data

Show BucketInfo Source # 
Instance details

Defined in Network.Minio.Data

listBuckets :: Minio [BucketInfo] Source #

Lists buckets.

Listing objects

listObjects :: Bucket -> Maybe Text -> Bool -> ConduitM () ListItem Minio () Source #

listObjects bucket prefix recurse lists objects in a bucket similar to a file system tree traversal.

If prefix is not Nothing, only items with the given prefix are listed, otherwise items under the bucket are returned.

If recurse is set to True all directories under the prefix are recursively traversed and only objects are returned.

If recurse is set to False, objects and directories immediately under the given prefix are returned (no recursive traversal is performed).

listObjectsV1 :: Bucket -> Maybe Text -> Bool -> ConduitM () ListItem Minio () Source #

Lists objects - similar to listObjects, however uses the older V1 AWS S3 API. Prefer listObjects to this.

data ListItem Source #

Represents a list output item - either an object or an object prefix (i.e. a directory).

Instances
Eq ListItem Source # 
Instance details

Defined in Network.Minio.ListOps

Show ListItem Source # 
Instance details

Defined in Network.Minio.ListOps

data ObjectInfo Source #

Represents information about an object.

Instances
Eq ObjectInfo Source # 
Instance details

Defined in Network.Minio.Data

Show ObjectInfo Source # 
Instance details

Defined in Network.Minio.Data

oiModTime :: ObjectInfo -> UTCTime Source #

Modification time of the object

oiETag :: ObjectInfo -> ETag Source #

ETag of the object

oiSize :: ObjectInfo -> Int64 Source #

Size of the object in bytes

oiUserMetadata :: ObjectInfo -> HashMap Text Text Source #

A map of user-metadata pairs stored with an object (keys will not have the X-Amz-Meta- prefix).

oiMetadata :: ObjectInfo -> HashMap Text Text Source #

A map of metadata key-value pairs (not including the user-metadata pairs)

Listing incomplete uploads

listIncompleteUploads :: Bucket -> Maybe Text -> Bool -> ConduitM () UploadInfo Minio () Source #

List incomplete uploads in a bucket matching the given prefix. If recurse is set to True incomplete uploads for the given prefix are recursively listed.

type UploadId = Text Source #

A type alias to represent an upload-id for multipart upload

data UploadInfo Source #

Represents information about a multipart upload.

Instances
Eq UploadInfo Source # 
Instance details

Defined in Network.Minio.Data

Show UploadInfo Source # 
Instance details

Defined in Network.Minio.Data

listIncompleteParts :: Bucket -> Object -> UploadId -> ConduitM () ObjectPartInfo Minio () Source #

List object parts of an ongoing multipart upload for given bucket, object and uploadId.

data ObjectPartInfo Source #

Represents information about an object part in an ongoing multipart upload.

Bucket Notifications

getBucketNotification :: Bucket -> Minio Notification Source #

Retrieve the notification configuration on a bucket.

putBucketNotification :: Bucket -> Notification -> Minio () Source #

Set the notification configuration on a bucket.

removeAllBucketNotification :: Bucket -> Minio () Source #

Remove all notifications configured on a bucket.

data Notification Source #

A data-type to represent bucket notification configuration. It is a collection of queue, topic or lambda function configurations. The structure of the types follow closely the XML representation described at https://docs.aws.amazon.com/AmazonS3/latest/API/RESTBucketPUTnotification.html

Instances
Eq Notification Source # 
Instance details

Defined in Network.Minio.Data

Show Notification Source # 
Instance details

Defined in Network.Minio.Data

defaultNotification :: Notification Source #

The default notification configuration is empty.

data NotificationConfig Source #

A data-type representing the configuration for a particular notification system. It could represent a Queue, Topic or Lambda Function configuration.

Constructors

NotificationConfig 

Fields

type Arn = Text Source #

Arn is an alias of Text

data Filter Source #

Filter data type - part of notification configuration

Constructors

Filter 

Fields

Instances
Eq Filter Source # 
Instance details

Defined in Network.Minio.Data

Methods

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

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

Show Filter Source # 
Instance details

Defined in Network.Minio.Data

defaultFilter :: Filter Source #

defaultFilter is empty, used to create a notification configuration.

data FilterKey Source #

FilterKey contains FilterRules, and is part of a Filter.

Constructors

FilterKey 

Fields

Instances
Eq FilterKey Source # 
Instance details

Defined in Network.Minio.Data

Show FilterKey Source # 
Instance details

Defined in Network.Minio.Data

defaultFilterKey :: FilterKey Source #

defaultFilterKey is empty, used to create notification configuration.

data FilterRules Source #

FilterRules represents a collection of FilterRules.

Constructors

FilterRules 
Instances
Eq FilterRules Source # 
Instance details

Defined in Network.Minio.Data

Show FilterRules Source # 
Instance details

Defined in Network.Minio.Data

defaultFilterRules :: FilterRules Source #

defaultFilterRules is empty, used to create notification configuration.

data FilterRule Source #

A filter rule that can act based on the suffix or prefix of an object. As an example, let's create two filter rules:

let suffixRule = FilterRule "suffix" ".jpg"
let prefixRule = FilterRule "prefix" "images/"

The suffixRule restricts the notification to be triggered only for objects having a suffix of ".jpg", and the prefixRule restricts it to objects having a prefix of "images/".

Constructors

FilterRule 

Fields

Instances
Eq FilterRule Source # 
Instance details

Defined in Network.Minio.Data

Show FilterRule Source # 
Instance details

Defined in Network.Minio.Data

Object Operations

type Object = Text Source #

Represents an object name

File-based operations

fGetObject :: Bucket -> Object -> FilePath -> GetObjectOptions -> Minio () Source #

Fetch the object and write it to the given file safely. The object is first written to a temporary file in the same directory and then moved to the given path.

fPutObject :: Bucket -> Object -> FilePath -> PutObjectOptions -> Minio () Source #

Upload the given file to the given object.

Conduit-based streaming operations

putObject :: Bucket -> Object -> ConduitM () ByteString Minio () -> Maybe Int64 -> PutObjectOptions -> Minio () Source #

Put an object from a conduit source. The size can be provided if known; this helps the library select optimal part sizes to perform a multipart upload. If not specified, it is assumed that the object can be potentially 5TiB and selects multipart sizes appropriately.

data PutObjectOptions Source #

Data type for options in PutObject call. Start with the empty defaultPutObjectOptions and use various the various poo* accessors.

pooContentType :: PutObjectOptions -> Maybe Text Source #

Set a standard MIME type describing the format of the object.

pooContentEncoding :: PutObjectOptions -> Maybe Text Source #

Set what content encodings have been applied to the object and thus what decoding mechanisms must be applied to obtain the media-type referenced by the Content-Type header field.

pooContentDisposition :: PutObjectOptions -> Maybe Text Source #

Set presentational information for the object.

pooContentLanguage :: PutObjectOptions -> Maybe Text Source #

Set to describe the language(s) intended for the audience.

pooCacheControl :: PutObjectOptions -> Maybe Text Source #

Set to specify caching behavior for the object along the request/reply chain.

pooStorageClass :: PutObjectOptions -> Maybe Text Source #

Set to STANDARD or REDUCED_REDUNDANCY depending on your performance needs, storage class is STANDARD by default (i.e when Nothing is passed).

pooUserMetadata :: PutObjectOptions -> [(Text, Text)] Source #

Set user defined metadata to store with the object.

pooNumThreads :: PutObjectOptions -> Maybe Word Source #

Set number of worker threads used to upload an object.

pooSSE :: PutObjectOptions -> Maybe SSE Source #

Set object encryption parameters for the request.

getObject :: Bucket -> Object -> GetObjectOptions -> Minio GetObjectResponse Source #

Get an object from the object store.

data GetObjectOptions Source #

Data type for options when getting an object from the service. Start with the empty defaultGetObjectOptions and modify it using the goo* functions.

gooRange :: GetObjectOptions -> Maybe ByteRange Source #

Set object's data of given offset begin and end, [ByteRangeFromTo 0 9] means first ten bytes of the source object.

gooIfMatch :: GetObjectOptions -> Maybe ETag Source #

Set matching ETag condition, GetObject which matches the following ETag.

gooIfNoneMatch :: GetObjectOptions -> Maybe ETag Source #

Set matching ETag none condition, GetObject which does not match the following ETag.

gooIfModifiedSince :: GetObjectOptions -> Maybe UTCTime Source #

Set object modified condition, GetObject modified since given time.

gooIfUnmodifiedSince :: GetObjectOptions -> Maybe UTCTime Source #

Set object unmodified condition, GetObject unmodified since given time.

data GetObjectResponse Source #

Data type returned by getObject representing the object being retrieved. Use the gor* functions to access its contents.

gorObjectInfo :: GetObjectResponse -> ObjectInfo Source #

ObjectInfo of the object being retrieved.

gorObjectStream :: GetObjectResponse -> ConduitM () ByteString Minio () Source #

A conduit of the bytes of the object.

Server-side object copying

copyObject :: DestinationInfo -> SourceInfo -> Minio () Source #

Perform a server-side copy operation to create an object based on the destination specification in DestinationInfo from the source specification in SourceInfo. This function performs a multipart copy operation if the new object is to be greater than 5GiB in size.

data SourceInfo Source #

Represents source object in server-side copy object

Instances
Eq SourceInfo Source # 
Instance details

Defined in Network.Minio.Data

Show SourceInfo Source # 
Instance details

Defined in Network.Minio.Data

srcBucket :: SourceInfo -> Text Source #

Bucket containing the source object

srcObject :: SourceInfo -> Text Source #

Source object key

srcRange :: SourceInfo -> Maybe (Int64, Int64) Source #

Source object byte-range (inclusive)

srcIfMatch :: SourceInfo -> Maybe Text Source #

ETag condition on source - object is copied only if the source object's ETag matches this value.

srcIfNoneMatch :: SourceInfo -> Maybe Text Source #

ETag not match condition on source - object is copied if ETag does not match this value.

srcIfModifiedSince :: SourceInfo -> Maybe UTCTime Source #

Copy source object only if the source has been modified since this time.

srcIfUnmodifiedSince :: SourceInfo -> Maybe UTCTime Source #

Copy source object only if the source has been un-modified since this given time.

data DestinationInfo Source #

Represents destination object in server-side copy object

dstBucket :: DestinationInfo -> Text Source #

Destination bucket

dstObject :: DestinationInfo -> Text Source #

Destination object key

Querying object info

statObject :: Bucket -> Object -> GetObjectOptions -> Minio ObjectInfo Source #

Get an object's metadata from the object store. It accepts the same options as GetObject.

Object removal operations

removeObject :: Bucket -> Object -> Minio () Source #

Remove an object from the object store.

removeIncompleteUpload :: Bucket -> Object -> Minio () Source #

Removes an ongoing multipart upload of an object.

Select Object Content with SQL

The selectObjectContent allows querying CSV, JSON or Parquet format objects in AWS S3 and in MinIO using SQL Select statements. This allows significant reduction of data transfer from object storage for computation-intensive tasks, as relevant data is filtered close to the storage.

selectObjectContent :: Bucket -> Object -> SelectRequest -> Minio (ConduitT () EventMessage Minio ()) Source #

selectObjectContent calls the SelectRequest on the given object. It returns a Conduit of event messages that can be consumed by the client.

data SelectRequest Source #

SelectRequest represents the Select API call. Use the selectRequest function to create a value of this type.

selectRequest :: Text -> InputSerialization -> OutputSerialization -> SelectRequest Source #

selectRequest is used to build a SelectRequest value. selectRequest query inputSer outputSer represents a SelectRequest with the SQL query text given by query, the input serialization settings (compression format and format information) inputSer and the output serialization settings outputSer.

Input Serialization

data InputSerialization Source #

InputSerialization represents format information of the input object being queried. Use one of the smart constructors such as defaultCsvInput as a starting value, and add compression info using setInputCompressionType

defaultCsvInput :: InputSerialization Source #

defaultCsvInput returns InputSerialization with default CSV format, and without any compression setting.

linesJsonInput :: InputSerialization Source #

linesJsonInput returns InputSerialization with JSON line based format with no compression setting.

documentJsonInput :: InputSerialization Source #

documentJsonInput returns InputSerialization with JSON document based format with no compression setting.

defaultParquetInput :: InputSerialization Source #

defaultParquetInput returns InputSerialization with Parquet format, and no compression setting.

setInputCSVProps :: CSVProp -> InputSerialization -> InputSerialization Source #

Set the CSV format properties in the InputSerialization.

data CompressionType Source #

Data type representing the compression setting in a Select request.

setInputCompressionType :: CompressionType -> SelectRequest -> SelectRequest Source #

setInputCompressionType sets the compression type for the input of the SelectRequest

CSV Format details

CSV format options such as delimiters and quote characters are specified using using the functions below. Options are combined monoidally.

data CSVProp Source #

CSVProp represents CSV format properties. It is built up using the Monoid instance.

Instances
Eq CSVProp Source # 
Instance details

Defined in Network.Minio.Data

Methods

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

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

Show CSVProp Source # 
Instance details

Defined in Network.Minio.Data

Semigroup CSVProp Source # 
Instance details

Defined in Network.Minio.Data

Monoid CSVProp Source # 
Instance details

Defined in Network.Minio.Data

recordDelimiter :: Text -> CSVProp Source #

Specify the CSV record delimiter property.

fieldDelimiter :: Text -> CSVProp Source #

Specify the CSV field delimiter property.

quoteCharacter :: Text -> CSVProp Source #

Specify the CSV quote character property.

quoteEscapeCharacter :: Text -> CSVProp Source #

Specify the CSV quote-escape character property.

commentCharacter :: Text -> CSVProp Source #

Specify the CSV comment character property. Lines starting with this character are ignored by the server.

allowQuotedRecordDelimiter :: CSVProp Source #

Allow quoted record delimiters inside a row using this property.

data FileHeaderInfo Source #

FileHeaderInfo specifies information about column headers for CSV format.

Constructors

FileHeaderNone

No column headers are present

FileHeaderUse

Headers are present and they should be used

FileHeaderIgnore

Header are present, but should be ignored

fileHeaderInfo :: FileHeaderInfo -> CSVProp Source #

Specify the CSV file header info property.

data QuoteFields Source #

Represent the QuoteField setting.

Instances
Eq QuoteFields Source # 
Instance details

Defined in Network.Minio.Data

Show QuoteFields Source # 
Instance details

Defined in Network.Minio.Data

quoteFields :: QuoteFields -> CSVProp Source #

quoteFields is an output serialization parameter

Output Serialization

data OutputSerialization Source #

OutputSerialization represents output serialization settings for the SelectRequest. Use defaultCsvOutput or defaultJsonOutput as a starting point.

defaultCsvOutput :: OutputSerialization Source #

defaultCsvOutput returns OutputSerialization with default CSV format.

defaultJsonOutput :: OutputSerialization Source #

defaultJsonInput returns OutputSerialization with default JSON format.

outputCSVFromProps :: CSVProp -> OutputSerialization Source #

Set the CSV format properties in the OutputSerialization.

outputJSONFromRecordDelimiter :: Text -> OutputSerialization Source #

Set the output record delimiter for JSON format

Progress messages

setRequestProgressEnabled :: Bool -> SelectRequest -> SelectRequest Source #

setRequestProgressEnabled sets the flag for turning on progress messages when the Select response is being streamed back to the client.

Interpreting Select output

The conduit returned by selectObjectContent returns values of the EventMessage data type. This returns the query output messages formatted according to the chosen output serialization, interleaved with progress messages (if enabled by setRequestProgressEnabled), and at the end a statistics message.

If the application is interested in only the payload, then getPayloadBytes can be used. For example to simply print the payload to stdout:

resultConduit <- selectObjectContent bucket object mySelectRequest
runConduit $ resultConduit .| getPayloadBytes .| stdoutC

Note that runConduit, the connect operator (.|) and stdoutC are all from the "conduit" package.

getPayloadBytes :: MonadIO m => ConduitT EventMessage ByteString m () Source #

A helper conduit that returns only the record payload bytes.

data EventMessage Source #

An EventMessage represents each kind of message received from the server.

Instances
Eq EventMessage Source # 
Instance details

Defined in Network.Minio.Data

Show EventMessage Source # 
Instance details

Defined in Network.Minio.Data

data Progress Source #

Represent the progress event returned in the Select response.

Instances
Eq Progress Source # 
Instance details

Defined in Network.Minio.Data

Show Progress Source # 
Instance details

Defined in Network.Minio.Data

type Stats = Progress Source #

Represent the stats event returned at the end of the Select response.

Server-Side Encryption Helpers

mkSSECKey :: MonadThrow m => ByteString -> m SSECKey Source #

Validates that the given ByteString is 32 bytes long and creates an encryption key.

data SSECKey Source #

Data type to represent an object encryption key. Create one using the mkSSECKey function.

Instances
Eq SSECKey Source # 
Instance details

Defined in Network.Minio.Data

Methods

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

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

Show SSECKey Source # 
Instance details

Defined in Network.Minio.Data

data SSE where Source #

Data type to represent Server-Side-Encryption settings

Constructors

SSE :: SSE

Specifies SSE S3 encryption - server manages encryption keys

SSEKMS :: ToJSON a => Maybe ByteString -> Maybe a -> SSE

Specifies that KMS service should be used. The first argument to the constructor is the Key Id to be used by the server (if not specified, the default KMS key id is used). The second argument is the optional KMS context that must have a ToJSON instance - please refer to the AWS S3 documentation for detailed information.

SSEC :: SSECKey -> SSE

Specifies server-side encryption with customer provided key. The argument is the encryption key to be used.

Presigned Operations

presignedPutObjectUrl :: Bucket -> Object -> UrlExpiry -> RequestHeaders -> Minio ByteString Source #

Generate a URL with authentication signature to PUT (upload) an object. Any extra headers if passed, are signed, and so they are required when the URL is used to upload data. This could be used, for example, to set user-metadata on the object.

For a list of possible headers to pass, please refer to the PUT object REST API AWS S3 documentation.

presignedGetObjectUrl :: Bucket -> Object -> UrlExpiry -> Query -> RequestHeaders -> Minio ByteString Source #

Generate a URL with authentication signature to GET (download) an object. All extra query parameters and headers passed here will be signed and are required when the generated URL is used. Query parameters could be used to change the response headers sent by the server. Headers can be used to set Etag match conditions among others.

For a list of possible request parameters and headers, please refer to the GET object REST API AWS S3 documentation.

presignedHeadObjectUrl :: Bucket -> Object -> UrlExpiry -> RequestHeaders -> Minio ByteString Source #

Generate a URL with authentication signature to make a HEAD request on an object. This is used to fetch metadata about an object. All extra headers passed here will be signed and are required when the generated URL is used.

For a list of possible headers to pass, please refer to the HEAD object REST API AWS S3 documentation.

type UrlExpiry = Int Source #

Time to expire for a presigned URL. It interpreted as a number of seconds. The maximum duration that can be specified is 7 days.

POST (browser) upload helpers

newPostPolicy :: UTCTime -> [PostPolicyCondition] -> Either PostPolicyError PostPolicy Source #

This function creates a PostPolicy after validating its arguments.

presignedPostPolicy :: PostPolicy -> Minio (ByteString, HashMap Text ByteString) Source #

Generate a presigned URL and POST policy to upload files via a browser. On success, this function returns a URL and POST form-data.

showPostPolicy :: PostPolicy -> ByteString Source #

Convert Post Policy to a string (e.g. for printing).

data PostPolicy Source #

A PostPolicy is required to perform uploads via browser forms.

Post Policy condition helpers

ppCondBucket :: Bucket -> PostPolicyCondition Source #

Set the bucket name that the upload should use.

ppCondContentLengthRange :: Int64 -> Int64 -> PostPolicyCondition Source #

Set the content length range constraint with minimum and maximum byte count values.

ppCondContentType :: Text -> PostPolicyCondition Source #

Set the content-type header for the upload.

ppCondKey :: Object -> PostPolicyCondition Source #

Set the object name constraint for the upload.

ppCondKeyStartsWith :: Object -> PostPolicyCondition Source #

Set the object name prefix constraint for the upload.

ppCondSuccessActionStatus :: Int -> PostPolicyCondition Source #

Status code that the S3-server should send on a successful POST upload

Error handling

Data types representing various errors that may occur while working with an object storage service.