amazonka-core-1.5.0: Core data types and functionality for Amazonka libraries.

Copyright(c) 2013-2017 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay+amazonka@gmail.com>
Stabilityprovisional
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.Data.Time

Contents

Description

 

Synopsis

Time

data Format Source #

Instances

Eq Format Source # 

Methods

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

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

Data Format Source # 

Methods

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

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

toConstr :: Format -> Constr #

dataTypeOf :: Format -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Format Source # 
Show Format Source # 
Generic Format Source # 

Associated Types

type Rep Format :: * -> * #

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

type Rep Format Source # 
type Rep Format = D1 (MetaData "Format" "Network.AWS.Data.Time" "amazonka-core-1.5.0-LssNx6O1J0znfQCejvUlW" False) ((:+:) ((:+:) (C1 (MetaCons "RFC822Format" PrefixI False) U1) (C1 (MetaCons "ISO8601Format" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BasicFormat" PrefixI False) U1) ((:+:) (C1 (MetaCons "AWSFormat" PrefixI False) U1) (C1 (MetaCons "POSIXFormat" PrefixI False) U1))))

data Time :: Format -> * where Source #

Constructors

Time :: UTCTime -> Time a 

Instances

FromJSON POSIX Source # 
FromJSON AWSTime Source # 
FromJSON BasicTime Source # 
FromJSON ISO8601 Source # 
FromJSON RFC822 Source # 
ToJSON POSIX Source # 
ToJSON AWSTime Source # 
ToJSON BasicTime Source # 
ToJSON ISO8601 Source # 
ToJSON RFC822 Source # 
ToText POSIX Source # 

Methods

toText :: POSIX -> Text Source #

ToText AWSTime Source # 

Methods

toText :: AWSTime -> Text Source #

ToText BasicTime Source # 
ToText ISO8601 Source # 

Methods

toText :: ISO8601 -> Text Source #

ToText RFC822 Source # 

Methods

toText :: RFC822 -> Text Source #

FromText AWSTime Source # 
FromText BasicTime Source # 
FromText ISO8601 Source # 
FromText RFC822 Source # 
ToByteString AWSTime Source # 
ToByteString BasicTime Source # 
ToByteString ISO8601 Source # 
ToByteString RFC822 Source # 
ToQuery POSIX Source # 
ToQuery AWSTime Source # 
ToQuery BasicTime Source # 
ToQuery ISO8601 Source # 
ToQuery RFC822 Source # 
ToXML AWSTime Source # 

Methods

toXML :: AWSTime -> XML Source #

ToXML BasicTime Source # 

Methods

toXML :: BasicTime -> XML Source #

ToXML ISO8601 Source # 

Methods

toXML :: ISO8601 -> XML Source #

ToXML RFC822 Source # 

Methods

toXML :: RFC822 -> XML Source #

FromXML AWSTime Source # 
FromXML BasicTime Source # 
FromXML ISO8601 Source # 
FromXML RFC822 Source # 
Eq (Time a) Source # 

Methods

(==) :: Time a -> Time a -> Bool #

(/=) :: Time a -> Time a -> Bool #

Typeable Format a => Data (Time a) Source # 

Methods

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

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

toConstr :: Time a -> Constr #

dataTypeOf :: Time a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (Time a) Source # 

Methods

compare :: Time a -> Time a -> Ordering #

(<) :: Time a -> Time a -> Bool #

(<=) :: Time a -> Time a -> Bool #

(>) :: Time a -> Time a -> Bool #

(>=) :: Time a -> Time a -> Bool #

max :: Time a -> Time a -> Time a #

min :: Time a -> Time a -> Time a #

Read (Time a) Source # 
Show (Time a) Source # 

Methods

showsPrec :: Int -> Time a -> ShowS #

show :: Time a -> String #

showList :: [Time a] -> ShowS #

Generic (Time a) Source # 

Associated Types

type Rep (Time a) :: * -> * #

Methods

from :: Time a -> Rep (Time a) x #

to :: Rep (Time a) x -> Time a #

Hashable (Time a) Source # 

Methods

hashWithSalt :: Int -> Time a -> Int #

hash :: Time a -> Int #

NFData (Time a) Source # 

Methods

rnf :: Time a -> () #

type Rep (Time a) Source # 
type Rep (Time a) = D1 (MetaData "Time" "Network.AWS.Data.Time" "amazonka-core-1.5.0-LssNx6O1J0znfQCejvUlW" False) (C1 (MetaCons "Time" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)))

Formats

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 

Methods

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

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

Data 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 
FromJSON UTCTime 
FromJSONKey UTCTime 
ToJSON UTCTime 
ToJSONKey UTCTime 
NFData UTCTime 

Methods

rnf :: UTCTime -> () #

FormatTime UTCTime 
ParseTime UTCTime 
ToByteString UTCTime Source # 
ToLog UTCTime Source #