minio-hs-0.1.0: A Minio client library, compatible with S3 like services.

Safe HaskellNone
LanguageHaskell2010

Network.Minio

Contents

Synopsis

Documentation

data ConnectInfo Source #

Connection Info data type. Use the Default instance to create connection info for your service.

awsCI :: ConnectInfo Source #

Default aws ConnectInfo. Credentials should be supplied before use.

minioPlayCI :: ConnectInfo Source #

Default minio play server ConnectInfo. Credentials are already filled.

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 #

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

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

MonadIO Minio Source # 

Methods

liftIO :: IO a -> Minio a #

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 #

MonadBase IO Minio Source # 

Methods

liftBase :: IO α -> Minio α #

MonadBaseControl IO Minio Source # 

Associated Types

type StM (Minio :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase Minio IO -> IO a) -> Minio a #

restoreM :: StM Minio a -> Minio a #

type StM Minio a Source # 
type StM Minio a = a

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

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

runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a #

Unwrap a ResourceT transformer, and call all registered release actions.

Note that there is some reference counting involved due to resourceForkIO. If multiple threads are sharing the same collection of resources, only the last call to runResourceT will deallocate the resources.

Since 0.3.0

Error handling

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

Data Types

Data types representing various object store concepts.

type Bucket = Text Source #

Represents a bucket in the object store

type Object = Text Source #

Represents an object name

data BucketInfo Source #

BucketInfo returned for list buckets call

Constructors

BucketInfo 

data ObjectInfo Source #

Represents information about an object.

Constructors

ObjectInfo 

data UploadInfo Source #

Represents information about a multipart upload.

Constructors

UploadInfo 

data ListPartInfo Source #

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

type UploadId = Text Source #

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

data ObjectData m Source #

A data-type to represent the source data for an object. A file-path or a producer-conduit may be provided.

For files, a size may be provided - this is useful in cases when the file size cannot be automatically determined or if only some prefix of the file is desired.

For streams also, a size may be provided. This is useful to limit the input - if it is not provided, upload will continue until the stream ends or the object reaches maxObjectsize size.

Constructors

ODFile FilePath (Maybe Int64)

Takes filepath and optional size.

ODStream (Producer m ByteString) (Maybe Int64)

Pass size in bytes as maybe if known.

Bucket Operations

getService :: Minio [BucketInfo] Source #

Fetch all buckets from the service.

getLocation :: Bucket -> Minio Region Source #

Fetch bucket location (region)

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.

listObjects :: Bucket -> Maybe Text -> Bool -> Producer Minio ObjectInfo Source #

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

listIncompleteUploads :: Bucket -> Maybe Text -> Bool -> Producer Minio UploadInfo 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.

listIncompleteParts :: Bucket -> Object -> UploadId -> Producer Minio ListPartInfo Source #

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

Object Operations

fGetObject :: Bucket -> Object -> FilePath -> 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 -> Minio () Source #

Upload the given file to the given object.

putObjectFromSource :: Bucket -> Object -> Producer Minio ByteString -> Maybe Int64 -> 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 performing a multipart upload. If not specified, it is assumed that the object can be potentially 5TiB and selects multipart sizes appropriately.

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

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

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

Get an object's metadata from the object store.