Copyright | (c) 2014 Vincent Hanquez <vincent@snarc.org> |
---|---|
License | BSD-style |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell2010 |
Data.Hourglass
Description
Time-related types and functions.
Basic types for representing points in time are Elapsed
and ElapsedP
. The
'P' is short for 'precise'. Elapsed
represents numbers of seconds elapsed
since the start of the Unix epoch (1970-01-01 00:00:00 UTC). ElapsedP
represents numbers of seconds and nanoseconds elapsed.
Values of other types representing points in time can be converted to and from
values of the Elapsed
and ElapsedP
types. For example:
d = timeGetElapsed (Date 1955 April 18) :: Elapsed timeFromElapsed d :: DateTime
Local time is represented by LocalTime
t
, parameterised by any other type
representing time (for example, Elapsed
, Date
or DateTime
). A local
time value is augmented by a timezone offset in minutes. For example:
localTime (Date 2014 May 4) 600 -- local time at UTC+10 of 4th May 2014
Synopsis
- newtype NanoSeconds = NanoSeconds Int64
- newtype Seconds = Seconds Int64
- newtype Minutes = Minutes Int64
- newtype Hours = Hours Int64
- data Month
- data WeekDay
- newtype Elapsed = Elapsed Seconds
- data ElapsedP = ElapsedP !Elapsed !NanoSeconds
- data Date = Date {}
- data TimeOfDay = TimeOfDay {}
- data DateTime = DateTime {}
- data LocalTime t
- class Timezone tz where
- timezoneOffset :: tz -> Int
- timezoneName :: tz -> String
- newtype TimezoneOffset = TimezoneOffset {}
- timezoneOffsetToSeconds :: TimezoneOffset -> Seconds
- data UTC = UTC
- timezone_UTC :: TimezoneOffset
- newtype TimezoneMinutes = TimezoneMinutes Int
- localTime :: Time t => TimezoneOffset -> t -> LocalTime t
- localTimeFromGlobal :: Time t => t -> LocalTime t
- localTimeSetTimezone :: Time t => TimezoneOffset -> LocalTime t -> LocalTime t
- localTimeUnwrap :: LocalTime t -> t
- localTimeGetTimezone :: LocalTime t -> TimezoneOffset
- isLeapYear :: Int -> Bool
- getWeekDay :: Date -> WeekDay
- getDayOfTheYear :: Date -> Int
- daysInMonth :: Int -> Month -> Int
- data Duration = Duration {}
- data Period = Period {
- periodYears :: !Int
- periodMonths :: !Int
- periodDays :: !Int
- timeAdd :: (Time t, TimeInterval ti) => t -> ti -> t
- timeDiff :: (Timeable t1, Timeable t2) => t1 -> t2 -> Seconds
- timeDiffP :: (Timeable t1, Timeable t2) => t1 -> t2 -> (Seconds, NanoSeconds)
- dateAddPeriod :: Date -> Period -> Date
- class Timeable t => Time t where
- timeFromElapsedP :: ElapsedP -> t
- timeFromElapsed :: Elapsed -> t
- class Timeable t where
- timeGetElapsedP :: t -> ElapsedP
- timeGetElapsed :: t -> Elapsed
- timeGetNanoSeconds :: t -> NanoSeconds
- timeConvert :: (Timeable t1, Time t2) => t1 -> t2
- timeGetDate :: Timeable t => t -> Date
- timeGetDateTimeOfDay :: Timeable t => t -> DateTime
- timeGetTimeOfDay :: Timeable t => t -> TimeOfDay
- localTimeConvert :: (Time t1, Time t2) => LocalTime t1 -> LocalTime t2
- localTimeToGlobal :: Time t => LocalTime t -> t
- class TimeInterval i where
- toSeconds :: i -> Seconds
- fromSeconds :: Seconds -> (i, Seconds)
- data TimeFormatElem
- = Format_Year2
- | Format_Year4
- | Format_Year
- | Format_Month
- | Format_Month2
- | Format_MonthName_Short
- | Format_DayYear
- | Format_Day
- | Format_Day2
- | Format_Hour
- | Format_Minute
- | Format_Second
- | Format_UnixSecond
- | Format_MilliSecond
- | Format_MicroSecond
- | Format_NanoSecond
- | Format_Precision Int
- | Format_TimezoneName
- | Format_TzHM_Colon_Z
- | Format_TzHM_Colon
- | Format_TzHM
- | Format_Tz_Offset
- | Format_Spaces
- | Format_Text Char
- | Format_Fct TimeFormatFct
- data TimeFormatFct = TimeFormatFct {
- timeFormatFctName :: String
- timeFormatParse :: DateTime -> String -> Either String (DateTime, String)
- timeFormatPrint :: DateTime -> String
- newtype TimeFormatString = TimeFormatString [TimeFormatElem]
- class TimeFormat format where
- toFormat :: format -> TimeFormatString
- data ISO8601_Date = ISO8601_Date
- data ISO8601_DateAndTime = ISO8601_DateAndTime
- timePrint :: (TimeFormat format, Timeable t) => format -> t -> String
- timeParse :: TimeFormat format => format -> String -> Maybe DateTime
- timeParseE :: TimeFormat format => format -> String -> Either (TimeFormatElem, String) (DateTime, String)
- localTimePrint :: (TimeFormat format, Timeable t) => format -> LocalTime t -> String
- localTimeParse :: TimeFormat format => format -> String -> Maybe (LocalTime DateTime)
- localTimeParseE :: TimeFormat format => format -> String -> Either (TimeFormatElem, String) (LocalTime DateTime, String)
Time units
newtype NanoSeconds Source #
Type representing numbers of nanoseconds.
Constructors
NanoSeconds Int64 |
Instances
Type representing numbers of seconds.
Instances
Data Seconds Source # | |
Defined in Time.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seconds -> c Seconds # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Seconds # toConstr :: Seconds -> Constr # dataTypeOf :: Seconds -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Seconds) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Seconds) # gmapT :: (forall b. Data b => b -> b) -> Seconds -> Seconds # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seconds -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seconds -> r # gmapQ :: (forall d. Data d => d -> u) -> Seconds -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Seconds -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seconds -> m Seconds # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seconds -> m Seconds # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seconds -> m Seconds # | |
Enum Seconds Source # | |
Num Seconds Source # | |
Read Seconds Source # | |
Integral Seconds Source # | |
Defined in Time.Types | |
Real Seconds Source # | |
Defined in Time.Types Methods toRational :: Seconds -> Rational # | |
Show Seconds Source # | |
NFData Seconds Source # | |
Defined in Time.Types | |
Eq Seconds Source # | |
Ord Seconds Source # | |
TimeInterval Seconds Source # | |
Type representing numbers of minutes.
Instances
Data Minutes Source # | |
Defined in Time.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Minutes -> c Minutes # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Minutes # toConstr :: Minutes -> Constr # dataTypeOf :: Minutes -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Minutes) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Minutes) # gmapT :: (forall b. Data b => b -> b) -> Minutes -> Minutes # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Minutes -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Minutes -> r # gmapQ :: (forall d. Data d => d -> u) -> Minutes -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Minutes -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Minutes -> m Minutes # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Minutes -> m Minutes # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Minutes -> m Minutes # | |
Enum Minutes Source # | |
Num Minutes Source # | |
Read Minutes Source # | |
Integral Minutes Source # | |
Defined in Time.Types | |
Real Minutes Source # | |
Defined in Time.Types Methods toRational :: Minutes -> Rational # | |
Show Minutes Source # | |
NFData Minutes Source # | |
Defined in Time.Types | |
Eq Minutes Source # | |
Ord Minutes Source # | |
TimeInterval Minutes Source # | |
Type representing numbers of hours.
Instances
Data Hours Source # | |
Defined in Time.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Hours -> c Hours # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Hours # dataTypeOf :: Hours -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Hours) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Hours) # gmapT :: (forall b. Data b => b -> b) -> Hours -> Hours # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hours -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hours -> r # gmapQ :: (forall d. Data d => d -> u) -> Hours -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Hours -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Hours -> m Hours # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Hours -> m Hours # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Hours -> m Hours # | |
Enum Hours Source # | |
Num Hours Source # | |
Read Hours Source # | |
Integral Hours Source # | |
Real Hours Source # | |
Defined in Time.Types Methods toRational :: Hours -> Rational # | |
Show Hours Source # | |
NFData Hours Source # | |
Defined in Time.Types | |
Eq Hours Source # | |
Ord Hours Source # | |
TimeInterval Hours Source # | |
Calendar enumerations
Type representing months of the Julian or Gregorian year.
Instances
Data Month Source # | |
Defined in Time.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Month -> c Month # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Month # dataTypeOf :: Month -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Month) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Month) # gmapT :: (forall b. Data b => b -> b) -> Month -> Month # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Month -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Month -> r # gmapQ :: (forall d. Data d => d -> u) -> Month -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Month -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Month -> m Month # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Month -> m Month # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Month -> m Month # | |
Bounded Month Source # | |
Enum Month Source # | |
Read Month Source # | |
Show Month Source # | |
Eq Month Source # | |
Ord Month Source # | |
Type representing days of the week. The enumeration starts on Sunday.
Instances
Data WeekDay Source # | |
Defined in Time.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WeekDay -> c WeekDay # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WeekDay # toConstr :: WeekDay -> Constr # dataTypeOf :: WeekDay -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WeekDay) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WeekDay) # gmapT :: (forall b. Data b => b -> b) -> WeekDay -> WeekDay # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WeekDay -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WeekDay -> r # gmapQ :: (forall d. Data d => d -> u) -> WeekDay -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WeekDay -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WeekDay -> m WeekDay # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WeekDay -> m WeekDay # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WeekDay -> m WeekDay # | |
Bounded WeekDay Source # | |
Enum WeekDay Source # | |
Read WeekDay Source # | |
Show WeekDay Source # | |
Eq WeekDay Source # | |
Ord WeekDay Source # | |
Points in time
Elapsed time since the start of the Unix epoch
Type representing numbers of seconds elapsed since the start of the Unix epoch (1970-01-01 00:00:00 UTC).
Instances
Data Elapsed Source # | |
Defined in Time.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Elapsed -> c Elapsed # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Elapsed # toConstr :: Elapsed -> Constr # dataTypeOf :: Elapsed -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Elapsed) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Elapsed) # gmapT :: (forall b. Data b => b -> b) -> Elapsed -> Elapsed # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Elapsed -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Elapsed -> r # gmapQ :: (forall d. Data d => d -> u) -> Elapsed -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Elapsed -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Elapsed -> m Elapsed # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Elapsed -> m Elapsed # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Elapsed -> m Elapsed # | |
Num Elapsed Source # | |
Read Elapsed Source # | |
Show Elapsed Source # | |
NFData Elapsed Source # | |
Defined in Time.Types | |
Eq Elapsed Source # | |
Ord Elapsed Source # | |
Time Elapsed Source # | |
Timeable Elapsed Source # | |
Type representing numbers of seconds and nanoseconds elapsed since the start of the Unix epoch (1970-01-01 00:00:00 UTC).
Constructors
ElapsedP !Elapsed !NanoSeconds |
Instances
Data ElapsedP Source # | |
Defined in Time.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ElapsedP -> c ElapsedP # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ElapsedP # toConstr :: ElapsedP -> Constr # dataTypeOf :: ElapsedP -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ElapsedP) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ElapsedP) # gmapT :: (forall b. Data b => b -> b) -> ElapsedP -> ElapsedP # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ElapsedP -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ElapsedP -> r # gmapQ :: (forall d. Data d => d -> u) -> ElapsedP -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ElapsedP -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ElapsedP -> m ElapsedP # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ElapsedP -> m ElapsedP # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ElapsedP -> m ElapsedP # | |
Num ElapsedP Source # | |
Read ElapsedP Source # | |
Real ElapsedP Source # | |
Defined in Time.Types Methods toRational :: ElapsedP -> Rational # | |
Show ElapsedP Source # | |
NFData ElapsedP Source # | |
Defined in Time.Types | |
Eq ElapsedP Source # | |
Ord ElapsedP Source # | |
Defined in Time.Types | |
Time ElapsedP Source # | |
Timeable ElapsedP Source # | |
Date, time, and date and time
Type representing dates in the proleptic Gregorian calendar (the common calendar).
Constructors
Date | |
Instances
Data Date Source # | |
Defined in Time.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Date -> c Date # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Date # dataTypeOf :: Date -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Date) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date) # gmapT :: (forall b. Data b => b -> b) -> Date -> Date # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r # gmapQ :: (forall d. Data d => d -> u) -> Date -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Date -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Date -> m Date # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Date -> m Date # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Date -> m Date # | |
Read Date Source # | |
Show Date Source # | |
NFData Date Source # | |
Defined in Time.Types | |
Eq Date Source # | |
Ord Date Source # | |
Time Date Source # | |
Timeable Date Source # | |
Defined in Time.Time Methods timeGetElapsedP :: Date -> ElapsedP Source # timeGetElapsed :: Date -> Elapsed Source # timeGetNanoSeconds :: Date -> NanoSeconds Source # |
Type representing times as hour, minutes, seconds and nanoseconds.
Constructors
TimeOfDay | |
Instances
Data TimeOfDay Source # | |
Defined in Time.Types 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 :: forall r r'. (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 # | |
Read TimeOfDay Source # | |
Show TimeOfDay Source # | |
NFData TimeOfDay Source # | |
Defined in Time.Types | |
Eq TimeOfDay Source # | |
Ord TimeOfDay Source # | |
Type representing date and time.
Instances
Data DateTime Source # | |
Defined in Time.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DateTime -> c DateTime # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DateTime # toConstr :: DateTime -> Constr # dataTypeOf :: DateTime -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DateTime) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateTime) # gmapT :: (forall b. Data b => b -> b) -> DateTime -> DateTime # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DateTime -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DateTime -> r # gmapQ :: (forall d. Data d => d -> u) -> DateTime -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DateTime -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DateTime -> m DateTime # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DateTime -> m DateTime # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DateTime -> m DateTime # | |
Read DateTime Source # | |
Show DateTime Source # | |
NFData DateTime Source # | |
Defined in Time.Types | |
Eq DateTime Source # | |
Ord DateTime Source # | |
Defined in Time.Types | |
Time DateTime Source # | |
Timeable DateTime Source # | |
Local time and timezone-related
Type representing local times.
Instances
Functor LocalTime Source # | |
Show t => Show (LocalTime t) Source # | |
Eq t => Eq (LocalTime t) Source # | |
(Ord t, Time t) => Ord (LocalTime t) Source # | |
Defined in Time.LocalTime |
class Timezone tz where Source #
A type class promising timezone-related functionality.
Minimal complete definition
Methods
timezoneOffset :: tz -> Int Source #
Offset in minutes from UTC. Valid values should be between -12 * 60
and
+14 * 60
.
timezoneName :: tz -> String Source #
The name of the timezone.
Default implementation is an +-HH:MM encoding of the timezoneOffset
.
Instances
Timezone TimezoneMinutes Source # | |
Defined in Time.Timezone Methods timezoneOffset :: TimezoneMinutes -> Int Source # timezoneName :: TimezoneMinutes -> String Source # | |
Timezone UTC Source # | |
Defined in Time.Timezone |
newtype TimezoneOffset Source #
Type representing offsets in minutes against UTC to obtain local time from UTC. A positive number represents a location east of where UTC is local time and a negative number represents a location west of where UTC is local time.
LocalTime t (-300) -- t represents a time at UTC-5
LocalTime t (+480) -- t represents a time at UTC+8
Should be between (-12 * 60)
and (+14 * 60)
.
For example, in timezone AEDT (Australian Eastern Daylight Time) (UTC+11),
local time is 15:47. Consequently, UTC time is 04:47 and the timezone offset
is TimezoneOffset
660
(in minutes).
Constructors
TimezoneOffset | |
Fields
|
Instances
timezoneOffsetToSeconds :: TimezoneOffset -> Seconds Source #
For the given timezone offset, yield the corresponding number of seconds.
Type representing Universal Time Coordinated (UTC).
Constructors
UTC |
timezone_UTC :: TimezoneOffset Source #
The UTC timezone.
timezoneOffsetToMinutes timezone_UTC == 0 -- True
newtype TimezoneMinutes Source #
Simple timezone containing the number of minutes difference with UTC.
Valid values should be between -12 * 60
and +14 * 60
.
Constructors
TimezoneMinutes Int |
Instances
Show TimezoneMinutes Source # | |
Defined in Time.Timezone Methods showsPrec :: Int -> TimezoneMinutes -> ShowS # show :: TimezoneMinutes -> String # showList :: [TimezoneMinutes] -> ShowS # | |
Eq TimezoneMinutes Source # | |
Defined in Time.Timezone Methods (==) :: TimezoneMinutes -> TimezoneMinutes -> Bool # (/=) :: TimezoneMinutes -> TimezoneMinutes -> Bool # | |
Ord TimezoneMinutes Source # | |
Defined in Time.Timezone Methods compare :: TimezoneMinutes -> TimezoneMinutes -> Ordering # (<) :: TimezoneMinutes -> TimezoneMinutes -> Bool # (<=) :: TimezoneMinutes -> TimezoneMinutes -> Bool # (>) :: TimezoneMinutes -> TimezoneMinutes -> Bool # (>=) :: TimezoneMinutes -> TimezoneMinutes -> Bool # max :: TimezoneMinutes -> TimezoneMinutes -> TimezoneMinutes # min :: TimezoneMinutes -> TimezoneMinutes -> TimezoneMinutes # | |
Timezone TimezoneMinutes Source # | |
Defined in Time.Timezone Methods timezoneOffset :: TimezoneMinutes -> Int Source # timezoneName :: TimezoneMinutes -> String Source # |
Constructors
Arguments
:: Time t | |
=> TimezoneOffset | |
-> t | The local time. |
-> LocalTime t |
For the given timezone offset and time value (assumed to be the local time), yield the corresponding local time.
localTimeFromGlobal :: Time t => t -> LocalTime t Source #
For the given time value, yield the corresponding LocalTime
value
assuming that there is no timezone offset.
localTimeSetTimezone :: Time t => TimezoneOffset -> LocalTime t -> LocalTime t Source #
For the given timezone offset and local time, yield the corresponding local time.
Accessors
localTimeUnwrap :: LocalTime t -> t Source #
The local time.
localTimeGetTimezone :: LocalTime t -> TimezoneOffset Source #
The timezone offset.
Miscellaneous calandar functions
For the given year in the Gregorian calendar, is it a leap year (366 days long)?
getWeekDay :: Date -> WeekDay Source #
For the given date in the proleptic Gregorian calendar, yield the day of the week it falls on.
getDayOfTheYear :: Date -> Int Source #
For the given date in the proleptic Gregorian calendar, yield the number of
days before the date in the same year. For example, there are 0
days before
1st January.
For the given year and month in the proleptic Gregorian calendar, yield the number of days in the month.
Periods of time
Type represeting periods of time in hours, minutes, seconds and
nanoseconds. See Period
for periods of time in years, months and days.
Constructors
Duration | |
Fields
|
Instances
Data Duration Source # | |
Defined in Time.Diff Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Duration -> c Duration # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Duration # toConstr :: Duration -> Constr # dataTypeOf :: Duration -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Duration) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration) # gmapT :: (forall b. Data b => b -> b) -> Duration -> Duration # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Duration -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Duration -> r # gmapQ :: (forall d. Data d => d -> u) -> Duration -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Duration -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Duration -> m Duration # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Duration -> m Duration # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Duration -> m Duration # | |
Monoid Duration Source # | |
Semigroup Duration Source # | |
Read Duration Source # | |
Show Duration Source # | |
NFData Duration Source # | |
Eq Duration Source # | |
Ord Duration Source # | |
Defined in Time.Diff | |
TimeInterval Duration Source # | |
Type representing periods of time in years, months and days.
See Duration
for periods of time hours, minutes, seconds and nanoseconds.
Constructors
Period | |
Fields
|
Instances
Data Period Source # | |
Defined in Time.Diff Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Period -> c Period # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Period # toConstr :: Period -> Constr # dataTypeOf :: Period -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Period) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Period) # gmapT :: (forall b. Data b => b -> b) -> Period -> Period # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r # gmapQ :: (forall d. Data d => d -> u) -> Period -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Period -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Period -> m Period # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Period -> m Period # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Period -> m Period # | |
Monoid Period Source # | |
Semigroup Period Source # | |
Read Period Source # | |
Show Period Source # | |
NFData Period Source # | |
Eq Period Source # | |
Ord Period Source # | |
timeAdd :: (Time t, TimeInterval ti) => t -> ti -> t Source #
Add the given period of time to the given value for a point time.
Example:
t1 `timeAdd` mempty { durationHours = 12 }
timeDiff :: (Timeable t1, Timeable t2) => t1 -> t2 -> Seconds Source #
For the two given points in time, yields the difference in seconds between them.
Effectively:
t2 `timeDiff` t1 = t2 - t1
timeDiffP :: (Timeable t1, Timeable t2) => t1 -> t2 -> (Seconds, NanoSeconds) Source #
For the two given points in time, yields the difference in seconds and nanoseconds between them.
Effectively:
@t2 `timeDiffP` t1 = t2 - t1
Conversion of points in time
class Timeable t => Time t where Source #
A type class promising functionality for converting ElapsedP
values
and Elapsed
values to values of the type in question.
Minimal complete definition
Methods
timeFromElapsedP :: ElapsedP -> t Source #
Convert from a number of elapsed seconds and nanoseconds since the start of the Unix epoch (1970-01-01 00:00:00 UTC).
timeFromElapsed :: Elapsed -> t Source #
Convert from a number of elapsed seconds since the start of the Unix epoch (1970-01-01 00:00:00 UTC).
Defaults to timeFromElapsedP
.
Instances
Time CTime Source # | |
Time Date Source # | |
Time DateTime Source # | |
Time Elapsed Source # | |
Time ElapsedP Source # | |
Epoch epoch => Time (ElapsedSince epoch) Source # | |
Defined in Time.Epoch Methods timeFromElapsedP :: ElapsedP -> ElapsedSince epoch Source # timeFromElapsed :: Elapsed -> ElapsedSince epoch Source # | |
Epoch epoch => Time (ElapsedSinceP epoch) Source # | |
Defined in Time.Epoch Methods timeFromElapsedP :: ElapsedP -> ElapsedSinceP epoch Source # timeFromElapsed :: Elapsed -> ElapsedSinceP epoch Source # |
class Timeable t where Source #
A type class promising functionality for:
Minimal complete definition
Methods
timeGetElapsedP :: t -> ElapsedP Source #
Convert the given value to the number of elapsed seconds and nanoseconds since the start of the Unix epoch (1970-01-01 00:00:00 UTC).
timeGetElapsed :: t -> Elapsed Source #
Convert the given value to the number of elapsed seconds since the start of the Unix epoch (1970-01-01 00:00:00 UTC).
Defaults to timeGetElapsedP
.
timeGetNanoSeconds :: t -> NanoSeconds Source #
Optionally, for the given value, yield the number of nanoseconds component.
If the type in question does not provide sub-second precision, should yield
0
.
Defaults to timeGetElapsedP
. For efficiency, if the type in question does
not provide sub-second precision, it is a good idea to override this
method.
Instances
Timeable CTime Source # | |
Timeable Date Source # | |
Defined in Time.Time Methods timeGetElapsedP :: Date -> ElapsedP Source # timeGetElapsed :: Date -> Elapsed Source # timeGetNanoSeconds :: Date -> NanoSeconds Source # | |
Timeable DateTime Source # | |
Timeable Elapsed Source # | |
Timeable ElapsedP Source # | |
Epoch epoch => Timeable (ElapsedSince epoch) Source # | |
Defined in Time.Epoch Methods timeGetElapsedP :: ElapsedSince epoch -> ElapsedP Source # timeGetElapsed :: ElapsedSince epoch -> Elapsed Source # timeGetNanoSeconds :: ElapsedSince epoch -> NanoSeconds Source # | |
Epoch epoch => Timeable (ElapsedSinceP epoch) Source # | |
Defined in Time.Epoch Methods timeGetElapsedP :: ElapsedSinceP epoch -> ElapsedP Source # timeGetElapsed :: ElapsedSinceP epoch -> Elapsed Source # timeGetNanoSeconds :: ElapsedSinceP epoch -> NanoSeconds Source # |
timeConvert :: (Timeable t1, Time t2) => t1 -> t2 Source #
Convert from one time representation to another. This will not compile unless the compiler can infer the types.
Specialized functions are available for built-in types:
timeGetDate :: Timeable t => t -> Date Source #
For the given value of a point in time, yield the corresponding date (a
specialization of timeConvert
).
timeGetDateTimeOfDay :: Timeable t => t -> DateTime Source #
For the given value for a point in time, yield the corresponding date and
time (a specialization of timeConvert
).
timeGetTimeOfDay :: Timeable t => t -> TimeOfDay Source #
For the given value for a point in time, yield the corresponding time
(a specialization of timeConvert
).
localTimeConvert :: (Time t1, Time t2) => LocalTime t1 -> LocalTime t2 Source #
For the given local time of one type, yield the corresponding local time of a different type. This will not compile unless the compiler can infer the types of the two local times.
localTimeToGlobal :: Time t => LocalTime t -> t Source #
For the given LocalTime
value, yield the corresponding global time.
Conversion of periods of time
class TimeInterval i where Source #
Type class promising functionality for:
- converting a value of the type in question to a number of seconds; and
- converting a
Seconds
value to a pair of a value of the type in question and a remaining number of seconds.
Methods
toSeconds :: i -> Seconds Source #
For the given value, yield a corresponding number of seconds.
fromSeconds :: Seconds -> (i, Seconds) Source #
For the given number of seconds, yield a pair of the corresponding value of the type in queston and a remaining number of seconds.
Instances
TimeInterval Duration Source # | |
TimeInterval Hours Source # | |
TimeInterval Minutes Source # | |
TimeInterval NanoSeconds Source # | |
Defined in Time.Types Methods toSeconds :: NanoSeconds -> Seconds Source # fromSeconds :: Seconds -> (NanoSeconds, Seconds) Source # | |
TimeInterval Seconds Source # | |
Parsing and Printing
Format strings
data TimeFormatElem Source #
Type representing formatters that can be part of a time format string.
Constructors
Format_Year2 | 2 digit years (70 is 1970, 69 is 2069). |
Format_Year4 | 4 digits years. |
Format_Year | Any digits years. |
Format_Month | Months (1 to 12). |
Format_Month2 | Months padded to 2 characters (01 to 12). |
Format_MonthName_Short | Short name of nthe month ('Jan', 'Feb' ..). |
Format_DayYear | Day of the year (1 to 365, 366 for leap years). |
Format_Day | Day of the month (1 to 31). |
Format_Day2 | Day of the month padded to 2 characters (01 to 31). |
Format_Hour | Hours (0 to 23). |
Format_Minute | Minutes (0 to 59). |
Format_Second | sSeconds (0 to 59, 60 for leap seconds). |
Format_UnixSecond | Number of seconds since the start of the Unix epoch (1970-01-01 00:00:00 UTC). |
Format_MilliSecond | Milliseconds padded to 3 characters (000 to 999). |
Format_MicroSecond | MicroSeconds padded to 6 characters (000000 to 999999). |
Format_NanoSecond | NanoSeconds padded to 9 characters (000000000 to 999999999). |
Format_Precision Int | Sub seconds display with a precision of n digits, with n between |
Format_TimezoneName | Timezone name (e.g. GMT, PST). Not yet implemented. Format_TimezoneOffset ^ Timezone offset offset (+02:00). |
Format_TzHM_Colon_Z | Zero UTC offset (Z) or timezone offset with colon (+02:00). |
Format_TzHM_Colon | Timezone offset with colon (+02:00). |
Format_TzHM | Timezone offset without colon (+0200). |
Format_Tz_Offset | Timezone offset in minutes. |
Format_Spaces | One or more space-like chars. |
Format_Text Char | A verbatim character. |
Format_Fct TimeFormatFct | Not implemented. |
Instances
Show TimeFormatElem Source # | |
Defined in Time.Format Methods showsPrec :: Int -> TimeFormatElem -> ShowS # show :: TimeFormatElem -> String # showList :: [TimeFormatElem] -> ShowS # | |
Eq TimeFormatElem Source # | |
Defined in Time.Format Methods (==) :: TimeFormatElem -> TimeFormatElem -> Bool # (/=) :: TimeFormatElem -> TimeFormatElem -> Bool # | |
TimeFormat [TimeFormatElem] Source # | |
Defined in Time.Format Methods toFormat :: [TimeFormatElem] -> TimeFormatString Source # |
data TimeFormatFct Source #
Type representing format functions.
Constructors
TimeFormatFct | |
Fields
|
Instances
Show TimeFormatFct Source # | |
Defined in Time.Format Methods showsPrec :: Int -> TimeFormatFct -> ShowS # show :: TimeFormatFct -> String # showList :: [TimeFormatFct] -> ShowS # | |
Eq TimeFormatFct Source # | |
Defined in Time.Format Methods (==) :: TimeFormatFct -> TimeFormatFct -> Bool # (/=) :: TimeFormatFct -> TimeFormatFct -> Bool # |
newtype TimeFormatString Source #
Type representing time format strings, composed of list
of TimeFormatElem
.
Constructors
TimeFormatString [TimeFormatElem] |
Instances
Show TimeFormatString Source # | |
Defined in Time.Format Methods showsPrec :: Int -> TimeFormatString -> ShowS # show :: TimeFormatString -> String # showList :: [TimeFormatString] -> ShowS # | |
Eq TimeFormatString Source # | |
Defined in Time.Format Methods (==) :: TimeFormatString -> TimeFormatString -> Bool # (/=) :: TimeFormatString -> TimeFormatString -> Bool # | |
TimeFormat TimeFormatString Source # | |
Defined in Time.Format Methods |
class TimeFormat format where Source #
A type class promising the ability to convert values to
a TimeFormatString
.
Methods
toFormat :: format -> TimeFormatString Source #
Instances
TimeFormat ISO8601_Date Source # | |
Defined in Time.Format Methods | |
TimeFormat ISO8601_DateAndTime Source # | |
Defined in Time.Format Methods toFormat :: ISO8601_DateAndTime -> TimeFormatString Source # | |
TimeFormat TimeFormatString Source # | |
Defined in Time.Format Methods | |
TimeFormat String Source # | |
Defined in Time.Format Methods toFormat :: String -> TimeFormatString Source # | |
TimeFormat [TimeFormatElem] Source # | |
Defined in Time.Format Methods toFormat :: [TimeFormatElem] -> TimeFormatString Source # |
Common built-in formats
data ISO8601_Date Source #
A type representing a ISO8601 date format string.
e.g. 2014-04-05
Constructors
ISO8601_Date |
Instances
Show ISO8601_Date Source # | |
Defined in Time.Format Methods showsPrec :: Int -> ISO8601_Date -> ShowS # show :: ISO8601_Date -> String # showList :: [ISO8601_Date] -> ShowS # | |
Eq ISO8601_Date Source # | |
Defined in Time.Format | |
TimeFormat ISO8601_Date Source # | |
Defined in Time.Format Methods |
data ISO8601_DateAndTime Source #
A type representing a ISO8601 date and time format string.
e.g. 2014-04-05T17:25:04+00:00 or 2014-04-05T17:25:04Z.
Constructors
ISO8601_DateAndTime |
Instances
Show ISO8601_DateAndTime Source # | |
Defined in Time.Format Methods showsPrec :: Int -> ISO8601_DateAndTime -> ShowS # show :: ISO8601_DateAndTime -> String # showList :: [ISO8601_DateAndTime] -> ShowS # | |
Eq ISO8601_DateAndTime Source # | |
Defined in Time.Format Methods (==) :: ISO8601_DateAndTime -> ISO8601_DateAndTime -> Bool # (/=) :: ISO8601_DateAndTime -> ISO8601_DateAndTime -> Bool # | |
TimeFormat ISO8601_DateAndTime Source # | |
Defined in Time.Format Methods toFormat :: ISO8601_DateAndTime -> TimeFormatString Source # |
Format methods
Arguments
:: (TimeFormat format, Timeable t) | |
=> format | The format to use for printing. |
-> t | The time to print. |
-> String |
Given the specified format, pretty print the given time.
timeParse :: TimeFormat format => format -> String -> Maybe DateTime Source #
Like localTimeParse
but the time value is automatically converted to
global time.
timeParseE :: TimeFormat format => format -> String -> Either (TimeFormatElem, String) (DateTime, String) Source #
Like localTimeParseE
but the time value is automatically converted to
global time.
Arguments
:: (TimeFormat format, Timeable t) | |
=> format | The format to use for printing. |
-> LocalTime t | The local time to print. |
-> String |
Given the specified format, pretty print the given local time.
Arguments
:: TimeFormat format | |
=> format | The format to use for parsing. |
-> String | The string to parse. |
-> Maybe (LocalTime DateTime) |
Given the specified format, try to parse the given string as time value.
On failure, returns Nothing
.
If successful, yields Just
the parsed value.
For more elaborate needs use localTimeParseE
.
Arguments
:: TimeFormat format | |
=> format | The format to use for parsing. |
-> String | The string to parse. |
-> Either (TimeFormatElem, String) (LocalTime DateTime, String) |
Given the specified format, try to parse the given string as time value.
On failure, the parsing function returns the reason of the failure.
If successful, yield the parsed value and the remaining unparsed string.