| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Data.Time.LocalTime
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
 - data TimeOfDay = TimeOfDay {}
 - midnight :: TimeOfDay
 - midday :: TimeOfDay
 - makeTimeOfDayValid :: Int -> Int -> Pico -> Maybe TimeOfDay
 - timeToDaysAndTimeOfDay :: NominalDiffTime -> (Integer, TimeOfDay)
 - daysAndTimeOfDayToTime :: Integer -> TimeOfDay -> NominalDiffTime
 - utcToLocalTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay)
 - localToUTCTimeOfDay :: TimeZone -> TimeOfDay -> (Integer, TimeOfDay)
 - timeToTimeOfDay :: DiffTime -> TimeOfDay
 - pastMidnight :: DiffTime -> TimeOfDay
 - timeOfDayToTime :: TimeOfDay -> DiffTime
 - sinceMidnight :: TimeOfDay -> DiffTime
 - dayFractionToTimeOfDay :: Rational -> TimeOfDay
 - timeOfDayToDayFraction :: TimeOfDay -> Rational
 - calendarTimeDays :: CalendarDiffDays -> CalendarDiffTime
 - calendarTimeTime :: NominalDiffTime -> CalendarDiffTime
 - scaleCalendarDiffTime :: Integer -> CalendarDiffTime -> CalendarDiffTime
 - data CalendarDiffTime = CalendarDiffTime {}
 - data LocalTime = LocalTime {}
 - addLocalTime :: NominalDiffTime -> LocalTime -> LocalTime
 - diffLocalTime :: LocalTime -> LocalTime -> NominalDiffTime
 - utcToLocalTime :: TimeZone -> UTCTime -> LocalTime
 - localTimeToUTC :: TimeZone -> LocalTime -> UTCTime
 - ut1ToLocalTime :: Rational -> UniversalTime -> LocalTime
 - localTimeToUT1 :: Rational -> LocalTime -> UniversalTime
 - data ZonedTime = ZonedTime {}
 - utcToZonedTime :: TimeZone -> UTCTime -> ZonedTime
 - zonedTimeToUTC :: ZonedTime -> UTCTime
 - getZonedTime :: IO ZonedTime
 - utcToLocalZonedTime :: UTCTime -> IO 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
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeZone Source # toConstr :: TimeZone -> Constr Source # dataTypeOf :: TimeZone -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeZone) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeZone) Source # gmapT :: (forall b. Data b => b -> b) -> TimeZone -> TimeZone Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeZone -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeZone -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TimeZone -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeZone -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeZone -> m TimeZone Source #  | |
| Read TimeZone Source # | This only works for   | 
| Show TimeZone Source # | This only shows the time zone name, or offset if the name is empty.  | 
| NFData TimeZone Source # | |
Defined in Data.Time.LocalTime.Internal.TimeZone  | |
| Eq TimeZone Source # | |
| Ord TimeZone Source # | |
Defined in Data.Time.LocalTime.Internal.TimeZone  | |
| FormatTime TimeZone Source # | |
Defined in Data.Time.Format.Format.Instances  | |
| ISO8601 TimeZone Source # | 
  | 
Defined in Data.Time.Format.ISO8601 Methods  | |
| ParseTime TimeZone Source # | |
Defined in Data.Time.Format.Parse.Instances  | |
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 local time-zone for a given time (varying as per summertime adjustments).
getCurrentTimeZone :: IO TimeZone Source #
Get the current time-zone.
Time of day
Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.
Constructors
| TimeOfDay | |
Instances
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) 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.
pastMidnight :: DiffTime -> TimeOfDay Source #
Same as timeToTimeOfDay.
timeOfDayToTime :: TimeOfDay -> DiffTime Source #
Get the time since midnight for a given time of day.
sinceMidnight :: TimeOfDay -> DiffTime Source #
Same as timeOfDayToTime.
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.
Calendar Duration
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
Local Time
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
addLocalTime :: NominalDiffTime -> LocalTime -> LocalTime Source #
addLocalTime a b = a + b
diffLocalTime :: LocalTime -> LocalTime -> NominalDiffTime Source #
diffLocalTime a b = a - b
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).
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
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ZonedTime Source # toConstr :: ZonedTime -> Constr Source # dataTypeOf :: ZonedTime -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ZonedTime) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ZonedTime) Source # gmapT :: (forall b. Data b => b -> b) -> ZonedTime -> ZonedTime Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZonedTime -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ZonedTime -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ZonedTime -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZonedTime -> m ZonedTime Source #  | |
| Read ZonedTime Source # | This only works for a   | 
| Show ZonedTime Source # | |
| NFData ZonedTime Source # | |
Defined in Data.Time.LocalTime.Internal.ZonedTime  | |
| FormatTime ZonedTime Source # | |
Defined in Data.Time.Format.Format.Instances  | |
| ISO8601 ZonedTime Source # | 
  | 
Defined in Data.Time.Format.ISO8601 Methods  | |
| ParseTime ZonedTime Source # | |
Defined in Data.Time.Format.Parse.Instances  | |
zonedTimeToUTC :: ZonedTime -> UTCTime Source #