time-compat-1.9.2.2: Compatibility package for time

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Time.LocalTime.Compat

Contents

Synopsis

Time zones

data TimeZone #

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

Defined in Data.Time.LocalTime.Internal.TimeZone

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

Defined in Data.Time.LocalTime.Internal.TimeZone

Show TimeZone 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

NFData TimeZone 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Methods

rnf :: TimeZone -> () #

FormatTime TimeZone 
Instance details

Defined in Data.Time.Format

ParseTime TimeZone 
Instance details

Defined in Data.Time.Format.Parse

ISO8601 TimeZone Source #

±hh:mm (ISO 8601:2004(E) sec. 4.2.5.1 extended format)

Instance details

Defined in Data.Time.Format.ISO8601.Compat

timeZoneOffsetString :: TimeZone -> String #

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

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

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

minutesToTimeZone :: Int -> TimeZone #

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

hoursToTimeZone :: Int -> TimeZone #

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

utc :: TimeZone #

The UTC time zone.

getTimeZone :: UTCTime -> IO TimeZone #

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

getCurrentTimeZone :: IO TimeZone #

Get the current time-zone.

Time of day

data TimeOfDay #

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

Defined in Data.Time.LocalTime.Internal.TimeOfDay

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

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Show TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

NFData TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

rnf :: TimeOfDay -> () #

FormatTime TimeOfDay 
Instance details

Defined in Data.Time.Format

ParseTime TimeOfDay 
Instance details

Defined in Data.Time.Format.Parse

ISO8601 TimeOfDay Source #

hh:mm:ss[.sss] (ISO 8601:2004(E) sec. 4.2.2.2, 4.2.2.4(a) extended format)

Instance details

Defined in Data.Time.Format.ISO8601.Compat

midnight :: TimeOfDay #

Hour zero

midday :: TimeOfDay #

Hour twelve

timeToDaysAndTimeOfDay :: NominalDiffTime -> (Integer, TimeOfDay) Source #

Convert a period of time into a count of days and a time of day since midnight. The time of day will never have a leap second.

daysAndTimeOfDayToTime :: Integer -> TimeOfDay -> NominalDiffTime Source #

Convert a count of days and a time of day since midnight into a period of time.

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

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

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

timeToTimeOfDay :: DiffTime -> TimeOfDay #

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

timeOfDayToTime :: TimeOfDay -> DiffTime #

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

dayFractionToTimeOfDay :: Rational -> TimeOfDay #

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

timeOfDayToDayFraction :: TimeOfDay -> Rational #

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

CalendarDiffTime

data CalendarDiffTime Source #

Instances
Eq CalendarDiffTime Source # 
Instance details

Defined in Data.Time.LocalTime.Compat

Data CalendarDiffTime Source # 
Instance details

Defined in Data.Time.LocalTime.Compat

Methods

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

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

toConstr :: CalendarDiffTime -> Constr #

dataTypeOf :: CalendarDiffTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CalendarDiffTime Source # 
Instance details

Defined in Data.Time.LocalTime.Compat

Semigroup CalendarDiffTime Source #

Additive

Instance details

Defined in Data.Time.LocalTime.Compat

Monoid CalendarDiffTime Source # 
Instance details

Defined in Data.Time.LocalTime.Compat

ISO8601 CalendarDiffTime Source #

PyYmMdDThHmMs[.sss]S (ISO 8601:2004(E) sec. 4.4.3.2)

Instance details

Defined in Data.Time.Format.ISO8601.Compat

scaleCalendarDiffTime :: Integer -> CalendarDiffTime -> CalendarDiffTime Source #

Scale by a factor. Note that scaleCalendarDiffTime (-1) will not perfectly invert a duration, due to variable month lengths.

Local Time

data LocalTime #

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

Defined in Data.Time.LocalTime.Internal.LocalTime

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

Defined in Data.Time.LocalTime.Internal.LocalTime

Show LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

NFData LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

rnf :: LocalTime -> () #

FormatTime LocalTime 
Instance details

Defined in Data.Time.Format

ParseTime LocalTime 
Instance details

Defined in Data.Time.Format.Parse

ISO8601 LocalTime Source #

yyyy-mm-ddThh:mm:ss[.sss] (ISO 8601:2004(E) sec. 4.3.2 extended format)

Instance details

Defined in Data.Time.Format.ISO8601.Compat

addLocalTime :: NominalDiffTime -> LocalTime -> LocalTime Source #

addLocalTime a b = a + b

diffLocalTime :: LocalTime -> LocalTime -> NominalDiffTime Source #

diffLocalTime a b = a - b

utcToLocalTime :: TimeZone -> UTCTime -> LocalTime #

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

localTimeToUTC :: TimeZone -> LocalTime -> UTCTime #

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

ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime #

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

localTimeToUT1 :: Rational -> LocalTime -> UniversalTime #

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

Zoned Time

data ZonedTime #

A local time together with a time zone.

Instances
Data ZonedTime 
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 #

Show ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

NFData ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Methods

rnf :: ZonedTime -> () #

FormatTime ZonedTime 
Instance details

Defined in Data.Time.Format

ParseTime ZonedTime 
Instance details

Defined in Data.Time.Format.Parse

ISO8601 ZonedTime Source #

yyyy-mm-ddThh:mm:ss[.sss]±hh:mm (ISO 8601:2004(E) sec. 4.3.2 extended format)

Instance details

Defined in Data.Time.Format.ISO8601.Compat