Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Credentials = Credentials {
- cAccessKey :: Text
- cSecretKey :: Text
- fromAWSConfigFile :: Provider
- fromAWSEnv :: Provider
- fromMinioEnv :: Provider
- data ConnectInfo
- setRegion :: Region -> ConnectInfo -> ConnectInfo
- setCreds :: Credentials -> ConnectInfo -> ConnectInfo
- setCredsFrom :: [Provider] -> ConnectInfo -> IO ConnectInfo
- data MinioConn
- mkMinioConn :: ConnectInfo -> Manager -> IO MinioConn
- minioPlayCI :: ConnectInfo
- awsCI :: ConnectInfo
- gcsCI :: ConnectInfo
- data Minio a
- runMinioWith :: MinioConn -> Minio a -> IO (Either MinioErr a)
- runMinio :: ConnectInfo -> Minio a -> IO (Either MinioErr a)
- type Bucket = Text
- makeBucket :: Bucket -> Maybe Region -> Minio ()
- removeBucket :: Bucket -> Minio ()
- bucketExists :: Bucket -> Minio Bool
- type Region = Text
- getLocation :: Bucket -> Minio Region
- data BucketInfo = BucketInfo {}
- listBuckets :: Minio [BucketInfo]
- data ObjectInfo
- oiObject :: ObjectInfo -> Object
- oiModTime :: ObjectInfo -> UTCTime
- oiETag :: ObjectInfo -> ETag
- oiSize :: ObjectInfo -> Int64
- oiMetadata :: ObjectInfo -> Map Text Text
- listObjects :: Bucket -> Maybe Text -> Bool -> ConduitM () ObjectInfo Minio ()
- listObjectsV1 :: Bucket -> Maybe Text -> Bool -> ConduitM () ObjectInfo Minio ()
- type UploadId = Text
- data UploadInfo = UploadInfo {
- uiKey :: Object
- uiUploadId :: UploadId
- uiInitTime :: UTCTime
- uiSize :: Int64
- listIncompleteUploads :: Bucket -> Maybe Text -> Bool -> ConduitM () UploadInfo Minio ()
- data ObjectPartInfo = ObjectPartInfo {
- opiNumber :: PartNumber
- opiETag :: ETag
- opiSize :: Int64
- opiModTime :: UTCTime
- listIncompleteParts :: Bucket -> Object -> UploadId -> ConduitM () ObjectPartInfo Minio ()
- data Notification = Notification {}
- defaultNotification :: Notification
- data NotificationConfig = NotificationConfig {}
- type Arn = Text
- data Event
- data Filter = Filter {}
- defaultFilter :: Filter
- data FilterKey = FilterKey {
- fkKey :: FilterRules
- defaultFilterKey :: FilterKey
- data FilterRules = FilterRules {
- frFilterRules :: [FilterRule]
- defaultFilterRules :: FilterRules
- data FilterRule = FilterRule {}
- getBucketNotification :: Bucket -> Minio Notification
- putBucketNotification :: Bucket -> Notification -> Minio ()
- removeAllBucketNotification :: Bucket -> Minio ()
- type Object = Text
- fGetObject :: Bucket -> Object -> FilePath -> GetObjectOptions -> Minio ()
- fPutObject :: Bucket -> Object -> FilePath -> PutObjectOptions -> Minio ()
- putObject :: Bucket -> Object -> ConduitM () ByteString Minio () -> Maybe Int64 -> PutObjectOptions -> Minio ()
- data PutObjectOptions
- defaultPutObjectOptions :: PutObjectOptions
- pooContentType :: PutObjectOptions -> Maybe Text
- pooContentEncoding :: PutObjectOptions -> Maybe Text
- pooContentDisposition :: PutObjectOptions -> Maybe Text
- pooContentLanguage :: PutObjectOptions -> Maybe Text
- pooCacheControl :: PutObjectOptions -> Maybe Text
- pooStorageClass :: PutObjectOptions -> Maybe Text
- pooUserMetadata :: PutObjectOptions -> [(Text, Text)]
- pooNumThreads :: PutObjectOptions -> Maybe Word
- getObject :: Bucket -> Object -> GetObjectOptions -> Minio (ConduitM () ByteString Minio ())
- data GetObjectOptions
- defaultGetObjectOptions :: GetObjectOptions
- gooRange :: GetObjectOptions -> Maybe ByteRange
- gooIfMatch :: GetObjectOptions -> Maybe ETag
- gooIfNoneMatch :: GetObjectOptions -> Maybe ETag
- gooIfModifiedSince :: GetObjectOptions -> Maybe UTCTime
- gooIfUnmodifiedSince :: GetObjectOptions -> Maybe UTCTime
- copyObject :: DestinationInfo -> SourceInfo -> Minio ()
- data SourceInfo
- defaultSourceInfo :: SourceInfo
- srcBucket :: SourceInfo -> Text
- srcObject :: SourceInfo -> Text
- srcRange :: SourceInfo -> Maybe (Int64, Int64)
- srcIfMatch :: SourceInfo -> Maybe Text
- srcIfNoneMatch :: SourceInfo -> Maybe Text
- srcIfModifiedSince :: SourceInfo -> Maybe UTCTime
- srcIfUnmodifiedSince :: SourceInfo -> Maybe UTCTime
- data DestinationInfo
- defaultDestinationInfo :: DestinationInfo
- dstBucket :: DestinationInfo -> Text
- dstObject :: DestinationInfo -> Text
- statObject :: Bucket -> Object -> Minio ObjectInfo
- removeObject :: Bucket -> Object -> Minio ()
- removeIncompleteUpload :: Bucket -> Object -> Minio ()
- type UrlExpiry = Int
- presignedPutObjectUrl :: Bucket -> Object -> UrlExpiry -> RequestHeaders -> Minio ByteString
- presignedGetObjectUrl :: Bucket -> Object -> UrlExpiry -> Query -> RequestHeaders -> Minio ByteString
- presignedHeadObjectUrl :: Bucket -> Object -> UrlExpiry -> RequestHeaders -> Minio ByteString
- data PostPolicy
- data PostPolicyError
- newPostPolicy :: UTCTime -> [PostPolicyCondition] -> Either PostPolicyError PostPolicy
- presignedPostPolicy :: PostPolicy -> Minio (ByteString, Map Text ByteString)
- showPostPolicy :: PostPolicy -> ByteString
- data PostPolicyCondition
- ppCondBucket :: Bucket -> PostPolicyCondition
- ppCondContentLengthRange :: Int64 -> Int64 -> PostPolicyCondition
- ppCondContentType :: Text -> PostPolicyCondition
- ppCondKey :: Object -> PostPolicyCondition
- ppCondKeyStartsWith :: Object -> PostPolicyCondition
- ppCondSuccessActionStatus :: Int -> PostPolicyCondition
- data MinioErr
- data MErrV
- = MErrVSinglePUTSizeExceeded Int64
- | MErrVPutSizeExceeded Int64
- | MErrVETagHeaderNotFound
- | MErrVInvalidObjectInfoResponse
- | MErrVInvalidSrcObjSpec Text
- | MErrVInvalidSrcObjByteRange (Int64, Int64)
- | MErrVCopyObjSingleNoRangeAccepted
- | MErrVRegionNotSupported Text
- | MErrVXmlParse Text
- | MErrVInvalidBucketName Text
- | MErrVInvalidObjectName Text
- | MErrVInvalidUrlExpiry Int
- | MErrVJsonParse Text
- | MErrVInvalidHealPath
- | MErrVMissingCredentials
- data ServiceErr
Credentials
data Credentials Source #
Credentials | |
|
Instances
Eq Credentials Source # | |
Defined in Network.Minio.Data (==) :: Credentials -> Credentials -> Bool # (/=) :: Credentials -> Credentials -> Bool # | |
Show Credentials Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> Credentials -> ShowS # show :: Credentials -> String # showList :: [Credentials] -> ShowS # |
fromAWSConfigFile :: Provider Source #
fromAWSEnv :: Provider Source #
fromMinioEnv :: Provider Source #
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 # | |
Defined in Network.Minio.Data (==) :: ConnectInfo -> ConnectInfo -> Bool # (/=) :: ConnectInfo -> ConnectInfo -> Bool # | |
Show ConnectInfo Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> ConnectInfo -> ShowS # show :: ConnectInfo -> String # showList :: [ConnectInfo] -> ShowS # | |
IsString ConnectInfo Source # | |
Defined in Network.Minio.Data fromString :: String -> ConnectInfo # |
setRegion :: Region -> ConnectInfo -> ConnectInfo Source #
setCreds :: Credentials -> ConnectInfo -> ConnectInfo Source #
setCredsFrom :: [Provider] -> ConnectInfo -> IO ConnectInfo Source #
MinioConn holds connection info and a connection pool
mkMinioConn :: ConnectInfo -> Manager -> IO MinioConn Source #
Connection helpers
minioPlayCI :: ConnectInfo Source #
Minio Play Server ConnectInfo. Credentials are already filled in.
awsCI :: ConnectInfo Source #
Default AWS ConnectInfo. Connects to "us-east-1". Credentials should be supplied before use.
gcsCI :: ConnectInfo Source #
Default GCS 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.
Instances
Monad Minio Source # | |
Functor Minio Source # | |
Applicative Minio Source # | |
MonadIO Minio Source # | |
Defined in Network.Minio.Data | |
MonadUnliftIO Minio Source # | |
Defined in Network.Minio.Data | |
MonadResource Minio Source # | |
Defined in Network.Minio.Data liftResourceT :: ResourceT IO a -> Minio a # | |
MonadReader MinioConn Minio Source # | |
runMinio :: ConnectInfo -> Minio a -> IO (Either MinioErr a) Source #
Run the Minio action and return the result or an error.
Bucket Operations
Creation, removal and querying
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.
Represents a region TODO: This could be a Sum Type with all defined regions for AWS.
Listing
data BucketInfo Source #
BucketInfo returned for list buckets call
Instances
Eq BucketInfo Source # | |
Defined in Network.Minio.Data (==) :: BucketInfo -> BucketInfo -> Bool # (/=) :: BucketInfo -> BucketInfo -> Bool # | |
Show BucketInfo Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> BucketInfo -> ShowS # show :: BucketInfo -> String # showList :: [BucketInfo] -> ShowS # |
listBuckets :: Minio [BucketInfo] Source #
Lists buckets.
Object info type represents object metadata information.
data ObjectInfo Source #
Represents information about an object.
Instances
Eq ObjectInfo Source # | |
Defined in Network.Minio.Data (==) :: ObjectInfo -> ObjectInfo -> Bool # (/=) :: ObjectInfo -> ObjectInfo -> Bool # | |
Show ObjectInfo Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> ObjectInfo -> ShowS # show :: ObjectInfo -> String # showList :: [ObjectInfo] -> ShowS # |
oiObject :: ObjectInfo -> Object Source #
oiModTime :: ObjectInfo -> UTCTime Source #
oiETag :: ObjectInfo -> ETag Source #
oiSize :: ObjectInfo -> Int64 Source #
oiMetadata :: ObjectInfo -> Map Text Text Source #
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.
data UploadInfo Source #
Represents information about a multipart upload.
UploadInfo | |
|
Instances
Eq UploadInfo Source # | |
Defined in Network.Minio.Data (==) :: UploadInfo -> UploadInfo -> Bool # (/=) :: UploadInfo -> UploadInfo -> Bool # | |
Show UploadInfo Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> UploadInfo -> ShowS # show :: UploadInfo -> String # showList :: [UploadInfo] -> ShowS # |
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.
ObjectPartInfo | |
|
Instances
Eq ObjectPartInfo Source # | |
Defined in Network.Minio.Data (==) :: ObjectPartInfo -> ObjectPartInfo -> Bool # (/=) :: ObjectPartInfo -> ObjectPartInfo -> Bool # | |
Show ObjectPartInfo Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> ObjectPartInfo -> ShowS # show :: ObjectPartInfo -> String # showList :: [ObjectPartInfo] -> ShowS # |
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
Instances
Eq Notification Source # | |
Defined in Network.Minio.Data (==) :: Notification -> Notification -> Bool # (/=) :: Notification -> Notification -> Bool # | |
Show Notification Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> Notification -> ShowS # show :: Notification -> String # showList :: [Notification] -> ShowS # |
data NotificationConfig Source #
A data-type representing the configuration for a particular notification system. It could represent a Queue, Topic or Lambda Function configuration.
Instances
Eq NotificationConfig Source # | |
Defined in Network.Minio.Data (==) :: NotificationConfig -> NotificationConfig -> Bool # (/=) :: NotificationConfig -> NotificationConfig -> Bool # | |
Show NotificationConfig Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> NotificationConfig -> ShowS # show :: NotificationConfig -> String # showList :: [NotificationConfig] -> ShowS # |
A data-type for events that can occur in the object storage server. Reference: https://docs.aws.amazon.com/AmazonS3/latest/dev/NotificationHowTo.html#supported-notification-event-types
data FilterRules Source #
Instances
Eq FilterRules Source # | |
Defined in Network.Minio.Data (==) :: FilterRules -> FilterRules -> Bool # (/=) :: FilterRules -> FilterRules -> Bool # | |
Show FilterRules Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> FilterRules -> ShowS # show :: FilterRules -> String # showList :: [FilterRules] -> ShowS # |
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/".
Instances
Eq FilterRule Source # | |
Defined in Network.Minio.Data (==) :: FilterRule -> FilterRule -> Bool # (/=) :: FilterRule -> FilterRule -> Bool # | |
Show FilterRule Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> FilterRule -> ShowS # show :: FilterRule -> String # showList :: [FilterRule] -> ShowS # |
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
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.
Instances
Eq PutObjectOptions Source # | |
Defined in Network.Minio.Data (==) :: PutObjectOptions -> PutObjectOptions -> Bool # (/=) :: PutObjectOptions -> PutObjectOptions -> Bool # | |
Show PutObjectOptions Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> PutObjectOptions -> ShowS # show :: PutObjectOptions -> String # showList :: [PutObjectOptions] -> ShowS # |
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.
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.
data GetObjectOptions Source #
Instances
Eq GetObjectOptions Source # | |
Defined in Network.Minio.Data (==) :: GetObjectOptions -> GetObjectOptions -> Bool # (/=) :: GetObjectOptions -> GetObjectOptions -> Bool # | |
Show GetObjectOptions Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> GetObjectOptions -> ShowS # show :: GetObjectOptions -> String # showList :: [GetObjectOptions] -> ShowS # |
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.
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
Instances
Eq SourceInfo Source # | |
Defined in Network.Minio.Data (==) :: SourceInfo -> SourceInfo -> Bool # (/=) :: SourceInfo -> SourceInfo -> Bool # | |
Show SourceInfo Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> SourceInfo -> ShowS # show :: SourceInfo -> String # showList :: [SourceInfo] -> ShowS # |
srcBucket :: SourceInfo -> Text Source #
srcObject :: SourceInfo -> Text Source #
srcIfMatch :: SourceInfo -> Maybe Text Source #
srcIfNoneMatch :: SourceInfo -> Maybe Text Source #
data DestinationInfo Source #
Represents destination object in server-side copy object
Instances
Eq DestinationInfo Source # | |
Defined in Network.Minio.Data (==) :: DestinationInfo -> DestinationInfo -> Bool # (/=) :: DestinationInfo -> DestinationInfo -> Bool # | |
Show DestinationInfo Source # | |
Defined in Network.Minio.Data showsPrec :: Int -> DestinationInfo -> ShowS # show :: DestinationInfo -> String # showList :: [DestinationInfo] -> ShowS # |
dstBucket :: DestinationInfo -> Text Source #
dstObject :: DestinationInfo -> Text Source #
Querying
statObject :: Bucket -> Object -> Minio ObjectInfo Source #
Get an object's metadata from the object store.
Object removal functions
removeIncompleteUpload :: Bucket -> Object -> Minio () Source #
Removes an ongoing multipart upload of an object.
Presigned Operations
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.
Instances
Eq PostPolicy Source # | |
Defined in Network.Minio.PresignedOperations (==) :: PostPolicy -> PostPolicy -> Bool # (/=) :: PostPolicy -> PostPolicy -> Bool # | |
Show PostPolicy Source # | |
Defined in Network.Minio.PresignedOperations showsPrec :: Int -> PostPolicy -> ShowS # show :: PostPolicy -> String # showList :: [PostPolicy] -> ShowS # | |
ToJSON PostPolicy Source # | |
Defined in Network.Minio.PresignedOperations toJSON :: PostPolicy -> Value # toEncoding :: PostPolicy -> Encoding # toJSONList :: [PostPolicy] -> Value # toEncodingList :: [PostPolicy] -> Encoding # |
data PostPolicyError Source #
Possible validation errors when creating a PostPolicy.
Instances
Eq PostPolicyError Source # | |
Defined in Network.Minio.PresignedOperations (==) :: PostPolicyError -> PostPolicyError -> Bool # (/=) :: PostPolicyError -> PostPolicyError -> Bool # | |
Show PostPolicyError Source # | |
Defined in Network.Minio.PresignedOperations showsPrec :: Int -> PostPolicyError -> ShowS # show :: PostPolicyError -> String # showList :: [PostPolicyError] -> ShowS # |
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
data PostPolicyCondition Source #
Represents individual conditions in a Post Policy document.
Instances
Eq PostPolicyCondition Source # | |
Defined in Network.Minio.PresignedOperations (==) :: PostPolicyCondition -> PostPolicyCondition -> Bool # (/=) :: PostPolicyCondition -> PostPolicyCondition -> Bool # | |
Show PostPolicyCondition Source # | |
Defined in Network.Minio.PresignedOperations showsPrec :: Int -> PostPolicyCondition -> ShowS # show :: PostPolicyCondition -> String # showList :: [PostPolicyCondition] -> ShowS # | |
ToJSON PostPolicyCondition Source # | |
Defined in Network.Minio.PresignedOperations toJSON :: PostPolicyCondition -> Value # toEncoding :: PostPolicyCondition -> Encoding # toJSONList :: [PostPolicyCondition] -> Value # toEncodingList :: [PostPolicyCondition] -> Encoding # |
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.
Errors thrown by the library
Instances
Eq MinioErr Source # | |
Show MinioErr Source # | |
Exception MinioErr Source # | |
Defined in Network.Minio.Errors toException :: MinioErr -> SomeException # fromException :: SomeException -> Maybe MinioErr # displayException :: MinioErr -> String # |
Various validation errors
Instances
Eq MErrV Source # | |
Show MErrV Source # | |
Exception MErrV Source # | |
Defined in Network.Minio.Errors toException :: MErrV -> SomeException # fromException :: SomeException -> Maybe MErrV # displayException :: MErrV -> String # |
data ServiceErr Source #
Errors returned by S3 compatible service
BucketAlreadyExists | |
BucketAlreadyOwnedByYou | |
NoSuchBucket | |
InvalidBucketName | |
NoSuchKey | |
ServiceErr Text Text |
Instances
Eq ServiceErr Source # | |
Defined in Network.Minio.Errors (==) :: ServiceErr -> ServiceErr -> Bool # (/=) :: ServiceErr -> ServiceErr -> Bool # | |
Show ServiceErr Source # | |
Defined in Network.Minio.Errors showsPrec :: Int -> ServiceErr -> ShowS # show :: ServiceErr -> String # showList :: [ServiceErr] -> ShowS # | |
Exception ServiceErr Source # | |
Defined in Network.Minio.Errors toException :: ServiceErr -> SomeException # fromException :: SomeException -> Maybe ServiceErr # displayException :: ServiceErr -> String # |