| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Antiope.S3.Strict
Synopsis
- unsafeDownload :: (MonadAWS m, MonadUnliftIO m) => BucketName -> ObjectKey -> m ByteString
- download :: (MonadAWS m, MonadUnliftIO m) => BucketName -> ObjectKey -> m (Maybe ByteString)
- downloadIfModifiedSince :: (MonadAWS m, MonadUnliftIO m) => S3Uri -> Maybe UTCTime -> m (DownloadResult ByteString)
- downloadFromS3Uri :: (MonadAWS m, MonadUnliftIO m) => S3Uri -> m (Maybe ByteString)
- unsafeDownloadMap :: (MonadAWS m, MonadUnliftIO m) => (ByteString -> ByteString) -> BucketName -> ObjectKey -> m ByteString
- downloadMap :: (MonadAWS m, MonadUnliftIO m) => (ByteString -> ByteString) -> BucketName -> ObjectKey -> m (Maybe ByteString)
- downloadMapFromS3Uri :: (MonadAWS m, MonadUnliftIO m) => (ByteString -> ByteString) -> S3Uri -> m (Maybe ByteString)
- data DownloadResult a
- data S3Uri = S3Uri BucketName ObjectKey
- data BucketName
- data ObjectKey
- data UTCTime
Documentation
unsafeDownload :: (MonadAWS m, MonadUnliftIO m) => BucketName -> ObjectKey -> m ByteString Source #
download :: (MonadAWS m, MonadUnliftIO m) => BucketName -> ObjectKey -> m (Maybe ByteString) Source #
downloadIfModifiedSince :: (MonadAWS m, MonadUnliftIO m) => S3Uri -> Maybe UTCTime -> m (DownloadResult ByteString) Source #
downloadFromS3Uri :: (MonadAWS m, MonadUnliftIO m) => S3Uri -> m (Maybe ByteString) Source #
unsafeDownloadMap :: (MonadAWS m, MonadUnliftIO m) => (ByteString -> ByteString) -> BucketName -> ObjectKey -> m ByteString Source #
downloadMap :: (MonadAWS m, MonadUnliftIO m) => (ByteString -> ByteString) -> BucketName -> ObjectKey -> m (Maybe ByteString) Source #
downloadMapFromS3Uri :: (MonadAWS m, MonadUnliftIO m) => (ByteString -> ByteString) -> S3Uri -> m (Maybe ByteString) Source #
data DownloadResult a Source #
Constructors
| NotFound S3Uri | |
| NotModified S3Uri | |
| Downloaded UTCTime S3Uri a |
Instances
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))) | |
data BucketName #
Instances
Instances
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 | |