time-1.8.0.2: A time library

Safe HaskellSafe
LanguageHaskell2010

Data.Time.LocalTime

Contents

Synopsis

Time zones

data TimeZone Source #

A TimeZone is a whole number of minutes offset from UTC, together with a name and a "just for summer" flag.

Constructors

TimeZone 

Fields

Instances
Eq TimeZone Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Data TimeZone Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Methods

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

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

toConstr :: TimeZone -> Constr #

dataTypeOf :: TimeZone -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TimeZone Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Read TimeZone # 
Instance details

Defined in Data.Time.Format.Parse

Show TimeZone Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

NFData TimeZone Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Methods

rnf :: TimeZone -> () #

ParseTime TimeZone Source # 
Instance details

Defined in Data.Time.Format.Parse

FormatTime TimeZone Source # 
Instance details

Defined in Data.Time.Format

timeZoneOffsetString :: TimeZone -> String Source #

Text representing the offset of this timezone, such as "-0800" or "+0400" (like %z in formatTime).

timeZoneOffsetString' :: Maybe Char -> TimeZone -> String Source #

Text representing the offset of this timezone, such as "-0800" or "+0400" (like %z in formatTime), with arbitrary padding.

minutesToTimeZone :: Int -> TimeZone Source #

Create a nameless non-summer timezone for this number of minutes.

hoursToTimeZone :: Int -> TimeZone Source #

Create a nameless non-summer timezone for this number of hours.

utc :: TimeZone Source #

The UTC time zone.

getTimeZone :: UTCTime -> IO TimeZone Source #

Get the local time-zone for a given time (varying as per summertime adjustments).

getCurrentTimeZone :: IO TimeZone Source #

Get the current time-zone.

Time of day

data TimeOfDay Source #

Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.

Constructors

TimeOfDay 

Fields

  • todHour :: Int

    range 0 - 23

  • todMin :: Int

    range 0 - 59

  • todSec :: Pico

    Note that 0 <= todSec < 61, accomodating leap seconds. Any local minute may have a leap second, since leap seconds happen in all zones simultaneously

Instances
Eq TimeOfDay Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Data TimeOfDay Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

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

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

toConstr :: TimeOfDay -> Constr #

dataTypeOf :: TimeOfDay -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TimeOfDay Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Read TimeOfDay # 
Instance details

Defined in Data.Time.Format.Parse

Show TimeOfDay Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

NFData TimeOfDay Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

rnf :: TimeOfDay -> () #

ParseTime TimeOfDay Source # 
Instance details

Defined in Data.Time.Format.Parse

FormatTime TimeOfDay Source # 
Instance details

Defined in Data.Time.Format

midday :: TimeOfDay Source #

Hour twelve

utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) Source #

Convert a time of day in UTC to a time of day in some timezone, together with a day adjustment.

localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay) Source #

Convert a time of day in some timezone to a time of day in UTC, together with a day adjustment.

timeToTimeOfDay :: DiffTime -> TimeOfDay Source #

Get the time of day given a time since midnight. Time more than 24h will be converted to leap-seconds.

timeOfDayToTime :: TimeOfDay -> DiffTime Source #

Get the time since midnight for a given time of day.

dayFractionToTimeOfDay :: Rational -> TimeOfDay Source #

Get the time of day given the fraction of a day since midnight.

timeOfDayToDayFraction :: TimeOfDay -> Rational Source #

Get the fraction of a day since midnight given a time of day.

Local Time

data LocalTime Source #

A simple day and time aggregate, where the day is of the specified parameter, and the time is a TimeOfDay. Conversion of this (as local civil time) to UTC depends on the time zone. Conversion of this (as local mean time) to UT1 depends on the longitude.

Constructors

LocalTime 
Instances
Eq LocalTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Data LocalTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

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

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

toConstr :: LocalTime -> Constr #

dataTypeOf :: LocalTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LocalTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Read LocalTime # 
Instance details

Defined in Data.Time.Format.Parse

Show LocalTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

NFData LocalTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

rnf :: LocalTime -> () #

ParseTime LocalTime Source # 
Instance details

Defined in Data.Time.Format.Parse

FormatTime LocalTime Source # 
Instance details

Defined in Data.Time.Format

utcToLocalTime :: TimeZone -> UTCTime -> LocalTime Source #

Get the local time of a UTC time in a time zone.

localTimeToUTC :: TimeZone -> LocalTime -> UTCTime Source #

Get the UTC time of a local time in a time zone.

ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime Source #

Get the local time of a UT1 time on a particular meridian (in degrees, positive is East).

localTimeToUT1 :: Rational -> LocalTime -> UniversalTime Source #

Get the UT1 time of a local time on a particular meridian (in degrees, positive is East).

data ZonedTime Source #

A local time together with a time zone.

Instances
Data ZonedTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Methods

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

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

toConstr :: ZonedTime -> Constr #

dataTypeOf :: ZonedTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ZonedTime # 
Instance details

Defined in Data.Time.Format.Parse

Show ZonedTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

NFData ZonedTime Source # 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Methods

rnf :: ZonedTime -> () #

ParseTime ZonedTime Source # 
Instance details

Defined in Data.Time.Format.Parse

FormatTime ZonedTime Source # 
Instance details

Defined in Data.Time.Format