minio-hs-1.0.0: A Minio Haskell Library for Amazon S3 compatible cloud storage.

Safe HaskellNone
LanguageHaskell2010

Network.Minio

Contents

Synopsis

Connecting to object storage

data ConnectInfo Source #

Connection Info data type. To create a ConnectInfo value, use one of the provided smart constructors or override fields of the Default instance.

Instances

Eq ConnectInfo Source # 
Show ConnectInfo Source # 
Default ConnectInfo Source #

Connects to a Minio server located at localhost:9000 with access key minio and secret key minio123. It is over HTTP by default.

Methods

def :: ConnectInfo #

awsCI :: ConnectInfo Source #

Default AWS ConnectInfo. Connects to "us-east-1". Credentials should be supplied before use, for e.g.:

awsCI {
  connectAccessKey = "my-access-key"
, connectSecretKey = "my-secret-key"
}

Connection helpers

awsWithRegionCI :: Region -> Bool -> ConnectInfo Source #

AWS ConnectInfo with a specified region. It can optionally disable the automatic discovery of a bucket's region via the Boolean argument.

awsWithRegionCI "us-west-1" False {
  connectAccessKey = "my-access-key"
, connectSecretKey = "my-secret-key"
}

This restricts all operations to the "us-west-1" region and does not perform any bucket location requests.

minioPlayCI :: ConnectInfo Source #

Minio Play Server ConnectInfo. Credentials are already filled in.

minioCI :: Text -> Int -> Bool -> ConnectInfo Source #

ConnectInfo for Minio server. Takes hostname, port and a Boolean to enable TLS.

minioCI "minio.example.com" 9000 True {
  connectAccessKey = "my-access-key"
, connectSecretKey = "my-secret-key"
}

This connects to a Minio server at the given hostname and port over HTTPS.

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 #

Instances

Monad Minio Source # 

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 # 

Methods

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

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

Applicative Minio Source # 

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 # 

Methods

liftIO :: IO a -> Minio a #

MonadUnliftIO Minio Source # 

Methods

askUnliftIO :: Minio (UnliftIO Minio) #

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

MonadResource Minio Source # 

Methods

liftResourceT :: ResourceT IO a -> Minio a #

MonadThrow Minio Source # 

Methods

throwM :: Exception e => e -> Minio a #

MonadCatch Minio Source # 

Methods

catch :: Exception e => Minio a -> (e -> Minio a) -> Minio a #

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

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

def :: Default a => a #

The default value for this type.

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 TODO: This could be a Sum Type with all defined regions for AWS.

getLocation :: Bucket -> Minio Region Source #

Fetch bucket location (region)

Listing

data BucketInfo Source #

BucketInfo returned for list buckets call

Constructors

BucketInfo 

listBuckets :: Minio [BucketInfo] Source #

Lists buckets.

Object info type represents object metadata information.

data ObjectInfo Source #

Represents information about an object.

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

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

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

List objects in a bucket matching the given prefix. If recurse is set to True objects matching 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.

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.

data ObjectPartInfo Source #

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

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

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

Bucket Notifications

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

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 #

data Filter Source #

Constructors

Filter 

Fields

Instances

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

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.

Object Operations

type Object = Text Source #

Represents an object name

File 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.

Input data type represents PutObject options.

data PutObjectOptions Source #

Data type represents various options specified for PutObject call. To specify PutObject options use the poo* accessors.

getObject :: Bucket -> Object -> GetObjectOptions -> Minio (ConduitM () ByteString Minio ()) Source #

Get an object from the object store as a resumable source (conduit).

Input data type represents GetObject options.

gooRange :: GetObjectOptions -> Maybe ByteRange Source #

ByteRangeFromTo 0 9
means first ten bytes of the source object.

Server-side 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

Querying

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

Get an object's metadata from the object store.

Object removal functions

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.

Presigned Operations

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.

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.

Utilities for POST (browser) uploads

data PostPolicy Source #

A PostPolicy is required to perform uploads via browser forms.

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

This function creates a PostPolicy after validating its arguments.

presignedPostPolicy :: PostPolicy -> Minio (ByteString, Map 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).

Utilities to specify Post Policy conditions

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.