time-1.8.0.2: A time library

Safe HaskellSafe
LanguageHaskell2010

Data.Time.Clock

Contents

Description

Types and functions for UTC and UT1

Synopsis

Universal Time

Time as measured by the Earth.

newtype UniversalTime Source #

The Modified Julian Date is the day with the fraction of the day, measured from UT midnight. It's used to represent UT1, which is time as measured by the earth's rotation, adjusted for various wobbles.

Constructors

ModJulianDate 
Instances
Eq UniversalTime Source # 
Instance details
Data UniversalTime Source # 
Instance details

Methods

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

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

toConstr :: UniversalTime -> Constr Source #

dataTypeOf :: UniversalTime -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord UniversalTime Source # 
Instance details
Read UniversalTime # 
Instance details
Show UniversalTime # 
Instance details
NFData UniversalTime Source # 
Instance details

Methods

rnf :: UniversalTime -> () Source #

ParseTime UniversalTime Source # 
Instance details
FormatTime UniversalTime Source # 
Instance details

Absolute intervals

data DiffTime Source #

This is a length of time, as measured by a clock. Conversion functions will treat it as seconds. It has a precision of 10^-12 s.

Instances
Enum DiffTime Source # 
Instance details
Eq DiffTime Source # 
Instance details
Fractional DiffTime Source # 
Instance details
Data DiffTime Source # 
Instance details

Methods

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

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

toConstr :: DiffTime -> Constr Source #

dataTypeOf :: DiffTime -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Num DiffTime Source # 
Instance details
Ord DiffTime Source # 
Instance details
Real DiffTime Source # 
Instance details
RealFrac DiffTime Source # 
Instance details
Show DiffTime Source # 
Instance details
NFData DiffTime Source # 
Instance details

Methods

rnf :: DiffTime -> () Source #

secondsToDiffTime :: Integer -> DiffTime Source #

Create a DiffTime which represents an integral number of seconds.

picosecondsToDiffTime :: Integer -> DiffTime Source #

Create a DiffTime from a number of picoseconds.

diffTimeToPicoseconds :: DiffTime -> Integer Source #

Get the number of picoseconds in a DiffTime.

UTC

UTC is time as measured by a clock, corrected to keep pace with the earth by adding or removing occasional seconds, known as "leap seconds". These corrections are not predictable and are announced with six month's notice. No table of these corrections is provided, as any program compiled with it would become out of date in six months.

If you don't care about leap seconds, use UTCTime and NominalDiffTime for your clock calculations, and you'll be fine.

data UTCTime Source #

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.

Constructors

UTCTime 

Fields

Instances
Eq UTCTime Source # 
Instance details

Methods

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

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

Data UTCTime Source # 
Instance details

Methods

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

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

toConstr :: UTCTime -> Constr Source #

dataTypeOf :: UTCTime -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord UTCTime Source # 
Instance details
Read UTCTime # 
Instance details
Show UTCTime # 
Instance details
NFData UTCTime Source # 
Instance details

Methods

rnf :: UTCTime -> () Source #

ParseTime UTCTime Source # 
Instance details
FormatTime UTCTime Source # 
Instance details

data NominalDiffTime Source #

This is a length of time, as measured by UTC. Conversion functions will treat it as seconds. It has a precision of 10^-12 s. It ignores leap-seconds, so it's not necessarily a fixed amount of clock time. For instance, 23:00 UTC + 2 hours of NominalDiffTime = 01:00 UTC (+ 1 day), regardless of whether a leap-second intervened.

Instances
Enum NominalDiffTime Source # 
Instance details
Eq NominalDiffTime Source # 
Instance details
Fractional NominalDiffTime Source # 
Instance details
Data NominalDiffTime Source # 
Instance details

Methods

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

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

toConstr :: NominalDiffTime -> Constr Source #

dataTypeOf :: NominalDiffTime -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Num NominalDiffTime Source # 
Instance details
Ord NominalDiffTime Source # 
Instance details
Real NominalDiffTime Source # 
Instance details
RealFrac NominalDiffTime Source # 
Instance details
Show NominalDiffTime Source # 
Instance details
NFData NominalDiffTime Source # 
Instance details

Methods

rnf :: NominalDiffTime -> () Source #

addUTCTime :: NominalDiffTime -> UTCTime -> UTCTime Source #

addUTCTime a b = a + b

diffUTCTime :: UTCTime -> UTCTime -> NominalDiffTime Source #

diffUTCTime a b = a - b

getCurrentTime :: IO UTCTime Source #

Get the current UTCTime from the system clock.

getTime_resolution :: DiffTime Source #

The resolution of getSystemTime, getCurrentTime, getPOSIXTime