antiope-s3-7.5.3: Please see the README on Github at <https://github.com/arbor/antiope#readme>

Safe HaskellNone
LanguageHaskell2010

Antiope.S3

Synopsis

Documentation

putFile 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

putFile' Source #

Arguments

:: MonadAWS m 
=> S3Uri

S3 URI

-> FilePath

Source file path

-> m (Maybe ETag)

Etag when the operation is successful

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

fileExists :: MonadAWS m => S3Uri -> m Bool Source #

Checks if the file exists on S3

data Region #

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 
Instance details

Defined in Network.AWS.Types

Enum Region 
Instance details

Defined in Network.AWS.Types

Eq Region 
Instance details

Defined in Network.AWS.Types

Methods

(==) :: Region -> Region -> Bool #

(/=) :: Region -> Region -> Bool #

Data Region 
Instance details

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 
Instance details

Defined in Network.AWS.Types

Read Region 
Instance details

Defined in Network.AWS.Types

Show Region 
Instance details

Defined in Network.AWS.Types

Generic Region 
Instance details

Defined in Network.AWS.Types

Associated Types

type Rep Region :: Type -> Type #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Hashable Region 
Instance details

Defined in Network.AWS.Types

Methods

hashWithSalt :: Int -> Region -> Int #

hash :: Region -> Int #

ToJSON Region 
Instance details

Defined in Network.AWS.Types

FromJSON Region 
Instance details

Defined in Network.AWS.Types

ToText Region 
Instance details

Defined in Network.AWS.Types

Methods

toText :: Region -> Text #

FromText Region 
Instance details

Defined in Network.AWS.Types

Methods

parser :: Parser Region #

ToByteString Region 
Instance details

Defined in Network.AWS.Types

Methods

toBS :: Region -> ByteString #

ToLog Region 
Instance details

Defined in Network.AWS.Types

Methods

build :: Region -> Builder #

FromXML Region 
Instance details

Defined in Network.AWS.Types

ToXML Region 
Instance details

Defined in Network.AWS.Types

Methods

toXML :: Region -> XML #

NFData Region 
Instance details

Defined in Network.AWS.Types

Methods

rnf :: Region -> () #

type Rep Region 
Instance details

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
Eq BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Data BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BucketName -> c BucketName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BucketName #

toConstr :: BucketName -> Constr #

dataTypeOf :: BucketName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BucketName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BucketName) #

gmapT :: (forall b. Data b => b -> b) -> BucketName -> BucketName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BucketName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BucketName -> r #

gmapQ :: (forall d. Data d => d -> u) -> BucketName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BucketName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BucketName -> m BucketName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BucketName -> m BucketName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BucketName -> m BucketName #

Ord BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Read BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Show BucketName 
Instance details

Defined in Network.AWS.S3.Internal

IsString BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Generic BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Associated Types

type Rep BucketName :: Type -> Type #

Hashable BucketName 
Instance details

Defined in Network.AWS.S3.Internal

FromJSON BucketName 
Instance details

Defined in Network.AWS.S3.Internal

ToText BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toText :: BucketName -> Text #

FromText BucketName 
Instance details

Defined in Network.AWS.S3.Internal

ToByteString BucketName 
Instance details

Defined in Network.AWS.S3.Internal

ToLog BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Methods

build :: BucketName -> Builder #

FromXML BucketName 
Instance details

Defined in Network.AWS.S3.Internal

ToXML BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toXML :: BucketName -> XML #

ToQuery BucketName 
Instance details

Defined in Network.AWS.S3.Internal

NFData BucketName 
Instance details

Defined in Network.AWS.S3.Internal

Methods

rnf :: BucketName -> () #

type Rep BucketName 
Instance details

Defined in Network.AWS.S3.Internal

type Rep BucketName = D1 (MetaData "BucketName" "Network.AWS.S3.Internal" "amazonka-s3-1.6.0-9RGABA1eCvPKnJK6dboHmb" True) (C1 (MetaCons "BucketName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ObjectKey #

Constructors

ObjectKey Text 
Instances
Eq ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Data ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjectKey -> c ObjectKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjectKey #

toConstr :: ObjectKey -> Constr #

dataTypeOf :: ObjectKey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjectKey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjectKey) #

gmapT :: (forall b. Data b => b -> b) -> ObjectKey -> ObjectKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjectKey -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjectKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> ObjectKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjectKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjectKey -> m ObjectKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectKey -> m ObjectKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjectKey -> m ObjectKey #

Ord ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Read ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Show ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

IsString ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Generic ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Associated Types

type Rep ObjectKey :: Type -> Type #

Hashable ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

ToText ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toText :: ObjectKey -> Text #

FromText ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

ToByteString ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toBS :: ObjectKey -> ByteString #

ToLog ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Methods

build :: ObjectKey -> Builder #

FromXML ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

ToXML ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toXML :: ObjectKey -> XML #

ToPath ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

ToQuery ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

NFData ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

Methods

rnf :: ObjectKey -> () #

type Rep ObjectKey 
Instance details

Defined in Network.AWS.S3.Internal

type Rep ObjectKey = D1 (MetaData "ObjectKey" "Network.AWS.S3.Internal" "amazonka-s3-1.6.0-9RGABA1eCvPKnJK6dboHmb" True) (C1 (MetaCons "ObjectKey" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ETag #

Constructors

ETag ByteString 
Instances
Eq ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

(==) :: ETag -> ETag -> Bool #

(/=) :: ETag -> ETag -> Bool #

Data ETag 
Instance details

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 #

toConstr :: ETag -> Constr #

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 
Instance details

Defined in Network.AWS.S3.Internal

Methods

compare :: ETag -> ETag -> Ordering #

(<) :: ETag -> ETag -> Bool #

(<=) :: ETag -> ETag -> Bool #

(>) :: ETag -> ETag -> Bool #

(>=) :: ETag -> ETag -> Bool #

max :: ETag -> ETag -> ETag #

min :: ETag -> ETag -> ETag #

Read ETag 
Instance details

Defined in Network.AWS.S3.Internal

Show ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

showsPrec :: Int -> ETag -> ShowS #

show :: ETag -> String #

showList :: [ETag] -> ShowS #

IsString ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

fromString :: String -> ETag #

Generic ETag 
Instance details

Defined in Network.AWS.S3.Internal

Associated Types

type Rep ETag :: Type -> Type #

Methods

from :: ETag -> Rep ETag x #

to :: Rep ETag x -> ETag #

Hashable ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

hashWithSalt :: Int -> ETag -> Int #

hash :: ETag -> Int #

ToText ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toText :: ETag -> Text #

FromText ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

parser :: Parser ETag #

ToByteString ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toBS :: ETag -> ByteString #

ToLog ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

build :: ETag -> Builder #

FromXML ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

parseXML :: [Node] -> Either String ETag #

ToXML ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toXML :: ETag -> XML #

ToQuery ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

toQuery :: ETag -> QueryString #

NFData ETag 
Instance details

Defined in Network.AWS.S3.Internal

Methods

rnf :: ETag -> () #

type Rep ETag 
Instance details

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)))

data S3Uri Source #

Constructors

S3Uri BucketName ObjectKey 
Instances
Eq S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

Methods

(==) :: S3Uri -> S3Uri -> Bool #

(/=) :: S3Uri -> S3Uri -> Bool #

Ord S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

Methods

compare :: S3Uri -> S3Uri -> Ordering #

(<) :: S3Uri -> S3Uri -> Bool #

(<=) :: S3Uri -> S3Uri -> Bool #

(>) :: S3Uri -> S3Uri -> Bool #

(>=) :: S3Uri -> S3Uri -> Bool #

max :: S3Uri -> S3Uri -> S3Uri #

min :: S3Uri -> S3Uri -> S3Uri #

Read S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

Show S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

Methods

showsPrec :: Int -> S3Uri -> ShowS #

show :: S3Uri -> String #

showList :: [S3Uri] -> ShowS #

Generic S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

Associated Types

type Rep S3Uri :: Type -> Type #

Methods

from :: S3Uri -> Rep S3Uri x #

to :: Rep S3Uri x -> S3Uri #

ToJSON S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

FromJSON S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

ToText S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

Methods

toText :: S3Uri -> Text #

FromText S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

Methods

parser :: Parser S3Uri #

NFData S3Uri Source # 
Instance details

Defined in Antiope.S3.Types

Methods

rnf :: S3Uri -> () #

type Rep S3Uri Source # 
Instance details

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 UTCTime #

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 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Data UTCTime 
Instance details

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 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToByteString UTCTime 
Instance details

Defined in Network.AWS.Data.ByteString

Methods

toBS :: UTCTime -> ByteString #

ToLog UTCTime 
Instance details

Defined in Network.AWS.Data.Log

Methods

build :: UTCTime -> Builder #

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

ParseTime UTCTime 
Instance details

Defined in Data.Time.Format.Parse