Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Data.Time.LocalTime
Contents
Synopsis
- data TimeZone = TimeZone {}
- timeZoneOffsetString :: TimeZone -> String
- timeZoneOffsetString' :: Maybe Char -> TimeZone -> String
- minutesToTimeZone :: Int -> TimeZone
- hoursToTimeZone :: Int -> TimeZone
- utc :: TimeZone
- getTimeZone :: UTCTime -> IO TimeZone
- getCurrentTimeZone :: IO TimeZone
- dayFractionToTimeOfDay :: Rational -> TimeOfDay
- daysAndTimeOfDayToTime :: Integer -> TimeOfDay -> NominalDiffTime
- localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay)
- makeTimeOfDayValid :: Int -> Int -> Pico -> Maybe TimeOfDay
- midday :: TimeOfDay
- midnight :: TimeOfDay
- pastMidnight :: DiffTime -> TimeOfDay
- sinceMidnight :: TimeOfDay -> DiffTime
- timeOfDayToDayFraction :: TimeOfDay -> Rational
- timeOfDayToTime :: TimeOfDay -> DiffTime
- timeToDaysAndTimeOfDay :: NominalDiffTime -> (Integer, TimeOfDay)
- timeToTimeOfDay :: DiffTime -> TimeOfDay
- utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay)
- data TimeOfDay = TimeOfDay {}
- calendarTimeDays :: CalendarDiffDays -> CalendarDiffTime
- calendarTimeTime :: NominalDiffTime -> CalendarDiffTime
- scaleCalendarDiffTime :: Integer -> CalendarDiffTime -> CalendarDiffTime
- data CalendarDiffTime = CalendarDiffTime {}
- addLocalTime :: NominalDiffTime -> LocalTime -> LocalTime
- diffLocalTime :: LocalTime -> LocalTime -> NominalDiffTime
- localTimeToUT1 :: Rational -> LocalTime -> UniversalTime
- localTimeToUTC :: TimeZone -> LocalTime -> UTCTime
- ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime
- utcToLocalTime :: TimeZone -> UTCTime -> LocalTime
- data LocalTime = LocalTime {}
- getZonedTime :: IO ZonedTime
- utcToLocalZonedTime :: UTCTime -> IO ZonedTime
- utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime
- zonedTimeToUTC :: ZonedTime -> UTCTime
- data ZonedTime = ZonedTime {}
Time zones
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
NFData TimeZone Source # | |||||
Defined in Data.Time.LocalTime.Internal.TimeZone | |||||
Data TimeZone Source # | |||||
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 :: forall r r'. (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 # | |||||
Generic TimeZone Source # | |||||
Defined in Data.Time.LocalTime.Internal.TimeZone Associated Types
| |||||
Read TimeZone Source # | This only works for | ||||
Show TimeZone Source # | This only shows the time zone name, or offset if the name is empty. | ||||
Eq TimeZone Source # | |||||
Ord TimeZone Source # | |||||
Defined in Data.Time.LocalTime.Internal.TimeZone | |||||
FormatTime TimeZone Source # | |||||
Defined in Data.Time.Format.Format.Instances Methods formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> TimeZone -> String) Source # | |||||
ISO8601 TimeZone Source # |
| ||||
Defined in Data.Time.Format.ISO8601 Methods | |||||
ParseTime TimeZone Source # | |||||
Defined in Data.Time.Format.Parse.Instances Methods substituteTimeSpecifier :: Proxy TimeZone -> TimeLocale -> Char -> Maybe String Source # parseTimeSpecifier :: Proxy TimeZone -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source # buildTime :: TimeLocale -> [(Char, String)] -> Maybe TimeZone Source # | |||||
type Rep TimeZone Source # | |||||
Defined in Data.Time.LocalTime.Internal.TimeZone type Rep TimeZone = D1 ('MetaData "TimeZone" "Data.Time.LocalTime.Internal.TimeZone" "time-1.14-40b8" 'False) (C1 ('MetaCons "TimeZone" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeZoneMinutes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "timeZoneSummerOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "timeZoneName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) |
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.
getTimeZone :: UTCTime -> IO TimeZone Source #
Get the configured time-zone for a given time (varying as per summertime adjustments).
On Unix systems the output of this function depends on:
- The value of
TZ
environment variable (if set) - The system time zone (usually configured by
/etc/localtime
symlink)
For details see tzset(3) and localtime(3).
Example:
> let t =UTCTime
(fromGregorian
2021 7 1) 0 >getTimeZone
t CEST >setEnv
"TZ" "America/New_York" >>getTimeZone
t EDT >setEnv
"TZ" "Europe/Berlin" >>getTimeZone
t CEST
On Windows systems the output of this function depends on:
- The value of
TZ
environment variable (if set). See here for how Windows interprets this variable. - The system time zone, configured in Settings
getCurrentTimeZone :: IO TimeZone Source #
Get the configured time-zone for the current time.
dayFractionToTimeOfDay :: Rational -> TimeOfDay Source #
Get the time of day given the fraction of a day since midnight.
daysAndTimeOfDayToTime :: Integer -> TimeOfDay -> NominalDiffTime Source #
Convert a count of days and a time of day since midnight into a period of time.
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.
pastMidnight :: DiffTime -> TimeOfDay Source #
Same as timeToTimeOfDay
.
sinceMidnight :: TimeOfDay -> DiffTime Source #
Same as timeOfDayToTime
.
timeOfDayToDayFraction :: TimeOfDay -> Rational Source #
Get the fraction of a day since midnight given a time of day.
timeOfDayToTime :: TimeOfDay -> DiffTime Source #
Get the time since midnight for a given time of day.
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.
timeToTimeOfDay :: DiffTime -> TimeOfDay Source #
Get the time of day given a time since midnight. Time more than 24h will be converted to leap-seconds.
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.
Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.
TimeOfDay 24 0 0
is considered invalid for the purposes of makeTimeOfDayValid
, as well as reading and parsing,
but valid for ISO 8601 parsing in Data.Time.Format.ISO8601.
Constructors
TimeOfDay | |
Instances
scaleCalendarDiffTime :: Integer -> CalendarDiffTime -> CalendarDiffTime Source #
Scale by a factor. Note that scaleCalendarDiffTime (-1)
will not perfectly invert a duration, due to variable month lengths.
data CalendarDiffTime Source #
Constructors
CalendarDiffTime | |
Fields
|
Instances
NFData CalendarDiffTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime Methods rnf :: CalendarDiffTime -> () Source # | |||||
Monoid CalendarDiffTime Source # | Additive | ||||
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime Methods mappend :: CalendarDiffTime -> CalendarDiffTime -> CalendarDiffTime # mconcat :: [CalendarDiffTime] -> CalendarDiffTime # | |||||
Semigroup CalendarDiffTime Source # | Additive | ||||
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime Methods (<>) :: CalendarDiffTime -> CalendarDiffTime -> CalendarDiffTime # sconcat :: NonEmpty CalendarDiffTime -> CalendarDiffTime # stimes :: Integral b => b -> CalendarDiffTime -> CalendarDiffTime # | |||||
Data CalendarDiffTime Source # | Since: time-1.9.2 | ||||
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime 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 :: forall r r'. (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 # | |||||
Generic CalendarDiffTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime Associated Types
Methods from :: CalendarDiffTime -> Rep CalendarDiffTime x # to :: Rep CalendarDiffTime x -> CalendarDiffTime # | |||||
Read CalendarDiffTime Source # | |||||
Defined in Data.Time.Format.ISO8601 Methods readsPrec :: Int -> ReadS CalendarDiffTime # readList :: ReadS [CalendarDiffTime] # | |||||
Show CalendarDiffTime Source # | |||||
Defined in Data.Time.Format.ISO8601 Methods showsPrec :: Int -> CalendarDiffTime -> ShowS # show :: CalendarDiffTime -> String # showList :: [CalendarDiffTime] -> ShowS # | |||||
Eq CalendarDiffTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime Methods (==) :: CalendarDiffTime -> CalendarDiffTime -> Bool # (/=) :: CalendarDiffTime -> CalendarDiffTime -> Bool # | |||||
FormatTime CalendarDiffTime Source # | |||||
Defined in Data.Time.Format.Format.Instances Methods formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> CalendarDiffTime -> String) Source # | |||||
ISO8601 CalendarDiffTime Source # |
| ||||
Defined in Data.Time.Format.ISO8601 Methods | |||||
ParseTime CalendarDiffTime Source # | |||||
Defined in Data.Time.Format.Parse.Instances Methods substituteTimeSpecifier :: Proxy CalendarDiffTime -> TimeLocale -> Char -> Maybe String Source # parseTimeSpecifier :: Proxy CalendarDiffTime -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source # buildTime :: TimeLocale -> [(Char, String)] -> Maybe CalendarDiffTime Source # | |||||
type Rep CalendarDiffTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.CalendarDiffTime type Rep CalendarDiffTime = D1 ('MetaData "CalendarDiffTime" "Data.Time.LocalTime.Internal.CalendarDiffTime" "time-1.14-40b8" 'False) (C1 ('MetaCons "CalendarDiffTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "ctMonths") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "ctTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime))) |
addLocalTime :: NominalDiffTime -> LocalTime -> LocalTime Source #
addLocalTime a b = a + b
diffLocalTime :: LocalTime -> LocalTime -> NominalDiffTime Source #
diffLocalTime a b = a - b
localTimeToUT1 :: Rational -> LocalTime -> UniversalTime Source #
Get the UT1 time of a local time on a particular meridian (in degrees, positive is East).
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).
utcToLocalTime :: TimeZone -> UTCTime -> LocalTime Source #
Get the local time of a UTC time in a time zone.
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 | |
Fields
|
Instances
NFData LocalTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.LocalTime | |||||
Data LocalTime Source # | |||||
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 :: forall r r'. (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 # | |||||
Generic LocalTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.LocalTime Associated Types
| |||||
Read LocalTime Source # | |||||
Show LocalTime Source # | |||||
Eq LocalTime Source # | |||||
Ord LocalTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.LocalTime | |||||
FormatTime LocalTime Source # | |||||
Defined in Data.Time.Format.Format.Instances Methods formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> LocalTime -> String) Source # | |||||
ISO8601 LocalTime Source # |
| ||||
Defined in Data.Time.Format.ISO8601 Methods | |||||
ParseTime LocalTime Source # | |||||
Defined in Data.Time.Format.Parse.Instances Methods substituteTimeSpecifier :: Proxy LocalTime -> TimeLocale -> Char -> Maybe String Source # parseTimeSpecifier :: Proxy LocalTime -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source # buildTime :: TimeLocale -> [(Char, String)] -> Maybe LocalTime Source # | |||||
type Rep LocalTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.LocalTime type Rep LocalTime = D1 ('MetaData "LocalTime" "Data.Time.LocalTime.Internal.LocalTime" "time-1.14-40b8" 'False) (C1 ('MetaCons "LocalTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "localDay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Just "localTimeOfDay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeOfDay))) |
zonedTimeToUTC :: ZonedTime -> UTCTime Source #
A local time together with a time zone.
There is no Eq
instance for ZonedTime
.
If you want to compare local times, use zonedTimeToLocalTime
.
If you want to compare absolute times, use zonedTimeToUTC
.
Constructors
ZonedTime | |
Fields |
Instances
NFData ZonedTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.ZonedTime | |||||
Data ZonedTime Source # | |||||
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 :: forall r r'. (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 # | |||||
Generic ZonedTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.ZonedTime Associated Types
| |||||
Read ZonedTime Source # | This only works for a | ||||
Show ZonedTime Source # | For the time zone, this only shows the name, or offset if the name is empty. | ||||
FormatTime ZonedTime Source # | |||||
Defined in Data.Time.Format.Format.Instances Methods formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> ZonedTime -> String) Source # | |||||
ISO8601 ZonedTime Source # |
| ||||
Defined in Data.Time.Format.ISO8601 Methods | |||||
ParseTime ZonedTime Source # | |||||
Defined in Data.Time.Format.Parse.Instances Methods substituteTimeSpecifier :: Proxy ZonedTime -> TimeLocale -> Char -> Maybe String Source # parseTimeSpecifier :: Proxy ZonedTime -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source # buildTime :: TimeLocale -> [(Char, String)] -> Maybe ZonedTime Source # | |||||
type Rep ZonedTime Source # | |||||
Defined in Data.Time.LocalTime.Internal.ZonedTime type Rep ZonedTime = D1 ('MetaData "ZonedTime" "Data.Time.LocalTime.Internal.ZonedTime" "time-1.14-40b8" 'False) (C1 ('MetaCons "ZonedTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "zonedTimeToLocalTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalTime) :*: S1 ('MetaSel ('Just "zonedTimeZone") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeZone))) |