| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Antiope.S3
Synopsis
- s3ObjectSource :: (MonadAWS m, MonadResource m) => BucketName -> ObjectKey -> m (ConduitT () ByteString m ())
- putFile :: MonadAWS m => BucketName -> ObjectKey -> FilePath -> m (Maybe ETag)
- putFile' :: MonadAWS m => S3Uri -> FilePath -> m (Maybe ETag)
- putContent :: MonadAWS m => BucketName -> ObjectKey -> ByteString -> m (Maybe ETag)
- putContent' :: MonadAWS m => S3Uri -> ByteString -> m (Maybe ETag)
- copySingle :: MonadAWS m => BucketName -> ObjectKey -> BucketName -> ObjectKey -> m ()
- fromS3Uri :: Text -> Maybe S3Uri
- toS3Uri :: BucketName -> ObjectKey -> Text
- lsBucketResponseStream :: MonadAWS m => ListObjectsV2 -> ConduitM a ListObjectsV2Response m ()
- lsBucketStream :: MonadAWS m => ListObjectsV2 -> ConduitM a Object m ()
- lsEntries :: MonadAWS m => BucketName -> ObjectKey -> m [ObjectKey]
- lsPrefix :: MonadAWS m => BucketName -> Prefix -> m [S3Uri]
- deleteFiles :: MonadAWS m => BucketName -> [ObjectKey] -> m [S3Uri]
- deleteFilesExcept :: MonadAWS m => BucketName -> Prefix -> [ObjectKey] -> m [S3Uri]
- fileExists :: MonadAWS m => S3Uri -> m Bool
- data Region
- newtype BucketName = BucketName Text
- newtype ObjectKey = ObjectKey Text
- data DownloadResult a
- newtype ETag = ETag ByteString
- data S3Uri = S3Uri BucketName ObjectKey
- data UTCTime
Documentation
s3ObjectSource :: (MonadAWS m, MonadResource m) => BucketName -> ObjectKey -> m (ConduitT () ByteString m ()) Source #
Arguments
| :: MonadAWS m | |
| => BucketName | Target bucket |
| -> ObjectKey | File name on S3 |
| -> FilePath | Source file path |
| -> m (Maybe ETag) | Etag when the operation is successful |
Puts file into a specified S3 bucket
putContent :: MonadAWS m => BucketName -> ObjectKey -> ByteString -> m (Maybe ETag) Source #
putContent' :: MonadAWS m => S3Uri -> ByteString -> m (Maybe ETag) Source #
Arguments
| :: MonadAWS m | |
| => BucketName | Source bucket name |
| -> ObjectKey | Source key |
| -> BucketName | Target bucket name |
| -> ObjectKey | Target key |
| -> m () |
Copies a single object within S3
lsBucketResponseStream :: MonadAWS m => ListObjectsV2 -> ConduitM a ListObjectsV2Response m () Source #
Streams all pages of the result (ListObjectsV2Responses) of a ListObjectsV2 request from S3. lsBucketResponseStream :: MonadAWS m => ListObjectsV2 -> ConduitT i ListObjectsV2Response m ()
lsBucketStream :: MonadAWS m => ListObjectsV2 -> ConduitM a Object m () Source #
Streams all Objects from all pages of the result of a ListObjectsV2 request from S3. lsBucketStream :: MonadAWS m => ListObjectsV2 -> ConduitT i Object m ()
lsEntries :: MonadAWS m => BucketName -> ObjectKey -> m [ObjectKey] Source #
Lists the specified objects in a bucket, non-recursively.
lsPrefix :: MonadAWS m => BucketName -> Prefix -> m [S3Uri] Source #
Lists the specified prefix in a bucket, recursively.
deleteFiles :: MonadAWS m => BucketName -> [ObjectKey] -> m [S3Uri] Source #
Deletes specified keys in a bucket. Returns a list of keys that were successfully deleted.
Will fail monadically (using fail) if the response indicates any errors.
deleteFilesExcept :: MonadAWS m => BucketName -> Prefix -> [ObjectKey] -> m [S3Uri] Source #
Deletes all the keys in a specified prefix EXCEPT the specified ones. Returns a list of objects that were successfully deleted.
The available AWS regions.
Constructors
| NorthVirginia | US East ('us-east-1'). |
| Ohio | US East ('us-east-2'). |
| NorthCalifornia | US West ('us-west-1'). |
| Oregon | US West ('us-west-2'). |
| Montreal | Canada ('ca-central-1'). |
| Tokyo | Asia Pacific ('ap-northeast-1'). |
| Seoul | Asia Pacific ('ap-northeast-2'). |
| Mumbai | Asia Pacific ('ap-south-1'). |
| Singapore | Asia Pacific ('ap-southeast-1'). |
| Sydney | Asia Pacific ('ap-southeast-2'). |
| SaoPaulo | South America ('sa-east-1'). |
| Ireland | EU ('eu-west-1'). |
| London | EU ('eu-west-2'). |
| Frankfurt | EU ('eu-central-1'). |
| GovCloud | US GovCloud ('us-gov-west-1'). |
| GovCloudFIPS | US GovCloud FIPS (S3 Only, 'fips-us-gov-west-1'). |
| Beijing | China ('cn-north-1'). |
Instances
| Bounded Region | |
| Enum Region | |
Defined in Network.AWS.Types | |
| Eq Region | |
| Data Region | |
Defined in Network.AWS.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Region -> c Region # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Region # toConstr :: Region -> Constr # dataTypeOf :: Region -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Region) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region) # gmapT :: (forall b. Data b => b -> b) -> Region -> Region # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQ :: (forall d. Data d => d -> u) -> Region -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Region -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # | |
| Ord Region | |
| Read Region | |
| Show Region | |
| Generic Region | |
| Hashable Region | |
Defined in Network.AWS.Types | |
| ToJSON Region | |
Defined in Network.AWS.Types | |
| FromJSON Region | |
| ToText Region | |
Defined in Network.AWS.Types | |
| FromText Region | |
Defined in Network.AWS.Types | |
| ToByteString Region | |
Defined in Network.AWS.Types Methods toBS :: Region -> ByteString # | |
| ToLog Region | |
Defined in Network.AWS.Types | |
| FromXML Region | |
| ToXML Region | |
Defined in Network.AWS.Types | |
| NFData Region | |
Defined in Network.AWS.Types | |
| type Rep Region | |
Defined in Network.AWS.Types type Rep Region = D1 (MetaData "Region" "Network.AWS.Types" "amazonka-core-1.6.0-IjsZgmToaeeK4XE4GdosxH" False) ((((C1 (MetaCons "NorthVirginia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ohio" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NorthCalifornia" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Oregon" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Montreal" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Tokyo" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Seoul" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mumbai" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "Singapore" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sydney" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "SaoPaulo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ireland" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "London" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Frankfurt" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "GovCloud" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "GovCloudFIPS" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Beijing" PrefixI False) (U1 :: Type -> Type)))))) | |
newtype BucketName #
Constructors
| BucketName Text |
Instances
Instances
data DownloadResult a Source #
Constructors
| NotFound S3Uri | |
| NotModified S3Uri | |
| Downloaded UTCTime S3Uri a |
Instances
Constructors
| ETag ByteString |
Instances
| Eq ETag | |
| Data ETag | |
Defined in Network.AWS.S3.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ETag -> c ETag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ETag # dataTypeOf :: ETag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ETag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ETag) # gmapT :: (forall b. Data b => b -> b) -> ETag -> ETag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ETag -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ETag -> r # gmapQ :: (forall d. Data d => d -> u) -> ETag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ETag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ETag -> m ETag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ETag -> m ETag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ETag -> m ETag # | |
| Ord ETag | |
| Read ETag | |
| Show ETag | |
| IsString ETag | |
Defined in Network.AWS.S3.Internal Methods fromString :: String -> ETag # | |
| Generic ETag | |
| Hashable ETag | |
Defined in Network.AWS.S3.Internal | |
| ToText ETag | |
Defined in Network.AWS.S3.Internal | |
| FromText ETag | |
Defined in Network.AWS.S3.Internal | |
| ToByteString ETag | |
Defined in Network.AWS.S3.Internal Methods toBS :: ETag -> ByteString # | |
| ToLog ETag | |
Defined in Network.AWS.S3.Internal | |
| FromXML ETag | |
| ToXML ETag | |
Defined in Network.AWS.S3.Internal | |
| ToQuery ETag | |
Defined in Network.AWS.S3.Internal Methods toQuery :: ETag -> QueryString # | |
| NFData ETag | |
Defined in Network.AWS.S3.Internal | |
| type Rep ETag | |
Defined in Network.AWS.S3.Internal type Rep ETag = D1 (MetaData "ETag" "Network.AWS.S3.Internal" "amazonka-s3-1.6.0-9RGABA1eCvPKnJK6dboHmb" True) (C1 (MetaCons "ETag" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) | |
Constructors
| S3Uri BucketName ObjectKey |
Instances
| Eq S3Uri Source # | |
| Ord S3Uri Source # | |
| Read S3Uri Source # | |
| Show S3Uri Source # | |
| Generic S3Uri Source # | |
| ToJSON S3Uri Source # | |
Defined in Antiope.S3.Types | |
| FromJSON S3Uri Source # | |
| ToText S3Uri Source # | |
Defined in Antiope.S3.Types | |
| FromText S3Uri Source # | |
Defined in Antiope.S3.Types | |
| NFData S3Uri Source # | |
Defined in Antiope.S3.Types | |
| type Rep S3Uri Source # | |
Defined in Antiope.S3.Types type Rep S3Uri = D1 (MetaData "S3Uri" "Antiope.S3.Types" "antiope-s3-7.5.3-A1ZBi3IAqPQInRhyiv93kE" False) (C1 (MetaCons "S3Uri" PrefixI True) (S1 (MetaSel (Just "bucket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BucketName) :*: S1 (MetaSel (Just "objectKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ObjectKey))) | |
This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.
Instances
| Eq UTCTime | |
| Data UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime # toConstr :: UTCTime -> Constr # dataTypeOf :: UTCTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) # gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r # gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime # | |
| Ord UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
| ToJSON UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
| ToJSONKey UTCTime | |
Defined in Data.Aeson.Types.ToJSON | |
| FromJSON UTCTime | |
| FromJSONKey UTCTime | |
Defined in Data.Aeson.Types.FromJSON Methods | |
| ToByteString UTCTime | |
Defined in Network.AWS.Data.ByteString Methods toBS :: UTCTime -> ByteString # | |
| ToLog UTCTime | |
Defined in Network.AWS.Data.Log | |
| NFData UTCTime | |
Defined in Data.Time.Clock.Internal.UTCTime | |
| ParseTime UTCTime | |
Defined in Data.Time.Format.Parse | |