time-1.6.0.1: 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 # 
Data TimeZone Source # 

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 # 
Show TimeZone Source # 
NFData TimeZone Source # 

Methods

rnf :: TimeZone -> () #

ParseTime TimeZone Source # 
FormatTime TimeZone Source # 

timeZoneOffsetString :: TimeZone -> String Source #

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

timeZoneOffsetString' :: NumericPadOption -> 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 # 
Data TimeOfDay Source # 

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 # 
Show TimeOfDay Source # 
NFData TimeOfDay Source # 

Methods

rnf :: TimeOfDay -> () #

ParseTime TimeOfDay Source # 
FormatTime TimeOfDay Source # 

midday :: TimeOfDay Source #

Hour twelve

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

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

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

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

timeToTimeOfDay :: DiffTime -> TimeOfDay Source #

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

timeOfDayToTime :: TimeOfDay -> DiffTime Source #

Find out how much time since midnight a given TimeOfDay is.

dayFractionToTimeOfDay :: Rational -> TimeOfDay Source #

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

timeOfDayToDayFraction :: TimeOfDay -> Rational Source #

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

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 # 
Data LocalTime Source # 

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 # 
Show LocalTime Source # 
NFData LocalTime Source # 

Methods

rnf :: LocalTime -> () #

ParseTime LocalTime Source # 
FormatTime LocalTime Source # 

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

show a UTC time in a given time zone as a LocalTime

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

find out what UTC time a given LocalTime in a given time zone is

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

1st arg is observation meridian in degrees, positive is East

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

1st arg is observation meridian in degrees, positive is East

data ZonedTime Source #

A local time together with a TimeZone.

Instances

Data ZonedTime Source # 

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 Source # 
NFData ZonedTime Source # 

Methods

rnf :: ZonedTime -> () #

ParseTime ZonedTime Source # 
FormatTime ZonedTime Source #