time-hourglass-0.2.14: A simple and efficient time library
Copyright(c) 2014 Vincent Hanquez <vincent@snarc.org>
LicenseBSD-style
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

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

Time units

newtype NanoSeconds Source #

Type representing numbers of nanoseconds.

Constructors

NanoSeconds Int64 

Instances

Instances details
Data NanoSeconds Source # 
Instance details

Defined in Time.Types

Methods

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

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

toConstr :: NanoSeconds -> Constr #

dataTypeOf :: NanoSeconds -> DataType #

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

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

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

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

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

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

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

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

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

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

Num NanoSeconds Source # 
Instance details

Defined in Time.Types

Read NanoSeconds Source # 
Instance details

Defined in Time.Types

Show NanoSeconds Source # 
Instance details

Defined in Time.Types

NFData NanoSeconds Source # 
Instance details

Defined in Time.Types

Methods

rnf :: NanoSeconds -> () #

Eq NanoSeconds Source # 
Instance details

Defined in Time.Types

Ord NanoSeconds Source # 
Instance details

Defined in Time.Types

TimeInterval NanoSeconds Source # 
Instance details

Defined in Time.Types

newtype Seconds Source #

Type representing numbers of seconds.

Constructors

Seconds Int64 

Instances

Instances details
Data Seconds Source # 
Instance details

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

Defined in Time.Types

Num Seconds Source # 
Instance details

Defined in Time.Types

Read Seconds Source # 
Instance details

Defined in Time.Types

Integral Seconds Source # 
Instance details

Defined in Time.Types

Real Seconds Source # 
Instance details

Defined in Time.Types

Show Seconds Source # 
Instance details

Defined in Time.Types

NFData Seconds Source # 
Instance details

Defined in Time.Types

Methods

rnf :: Seconds -> () #

Eq Seconds Source # 
Instance details

Defined in Time.Types

Methods

(==) :: Seconds -> Seconds -> Bool #

(/=) :: Seconds -> Seconds -> Bool #

Ord Seconds Source # 
Instance details

Defined in Time.Types

TimeInterval Seconds Source # 
Instance details

Defined in Time.Types

newtype Minutes Source #

Type representing numbers of minutes.

Constructors

Minutes Int64 

Instances

Instances details
Data Minutes Source # 
Instance details

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

Defined in Time.Types

Num Minutes Source # 
Instance details

Defined in Time.Types

Read Minutes Source # 
Instance details

Defined in Time.Types

Integral Minutes Source # 
Instance details

Defined in Time.Types

Real Minutes Source # 
Instance details

Defined in Time.Types

Show Minutes Source # 
Instance details

Defined in Time.Types

NFData Minutes Source # 
Instance details

Defined in Time.Types

Methods

rnf :: Minutes -> () #

Eq Minutes Source # 
Instance details

Defined in Time.Types

Methods

(==) :: Minutes -> Minutes -> Bool #

(/=) :: Minutes -> Minutes -> Bool #

Ord Minutes Source # 
Instance details

Defined in Time.Types

TimeInterval Minutes Source # 
Instance details

Defined in Time.Types

newtype Hours Source #

Type representing numbers of hours.

Constructors

Hours Int64 

Instances

Instances details
Data Hours Source # 
Instance details

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 #

toConstr :: Hours -> Constr #

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

Defined in Time.Types

Num Hours Source # 
Instance details

Defined in Time.Types

Read Hours Source # 
Instance details

Defined in Time.Types

Integral Hours Source # 
Instance details

Defined in Time.Types

Real Hours Source # 
Instance details

Defined in Time.Types

Methods

toRational :: Hours -> Rational #

Show Hours Source # 
Instance details

Defined in Time.Types

Methods

showsPrec :: Int -> Hours -> ShowS #

show :: Hours -> String #

showList :: [Hours] -> ShowS #

NFData Hours Source # 
Instance details

Defined in Time.Types

Methods

rnf :: Hours -> () #

Eq Hours Source # 
Instance details

Defined in Time.Types

Methods

(==) :: Hours -> Hours -> Bool #

(/=) :: Hours -> Hours -> Bool #

Ord Hours Source # 
Instance details

Defined in Time.Types

Methods

compare :: Hours -> Hours -> Ordering #

(<) :: Hours -> Hours -> Bool #

(<=) :: Hours -> Hours -> Bool #

(>) :: Hours -> Hours -> Bool #

(>=) :: Hours -> Hours -> Bool #

max :: Hours -> Hours -> Hours #

min :: Hours -> Hours -> Hours #

TimeInterval Hours Source # 
Instance details

Defined in Time.Types

Calendar enumerations

data Month Source #

Type representing months of the Julian or Gregorian year.

Instances

Instances details
Data Month Source # 
Instance details

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 #

toConstr :: Month -> Constr #

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

Defined in Time.Types

Enum Month Source # 
Instance details

Defined in Time.Types

Read Month Source # 
Instance details

Defined in Time.Types

Show Month Source # 
Instance details

Defined in Time.Types

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

Eq Month Source # 
Instance details

Defined in Time.Types

Methods

(==) :: Month -> Month -> Bool #

(/=) :: Month -> Month -> Bool #

Ord Month Source # 
Instance details

Defined in Time.Types

Methods

compare :: Month -> Month -> Ordering #

(<) :: Month -> Month -> Bool #

(<=) :: Month -> Month -> Bool #

(>) :: Month -> Month -> Bool #

(>=) :: Month -> Month -> Bool #

max :: Month -> Month -> Month #

min :: Month -> Month -> Month #

data WeekDay Source #

Type representing days of the week. The enumeration starts on Sunday.

Instances

Instances details
Data WeekDay Source # 
Instance details

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

Defined in Time.Types

Enum WeekDay Source # 
Instance details

Defined in Time.Types

Read WeekDay Source # 
Instance details

Defined in Time.Types

Show WeekDay Source # 
Instance details

Defined in Time.Types

Eq WeekDay Source # 
Instance details

Defined in Time.Types

Methods

(==) :: WeekDay -> WeekDay -> Bool #

(/=) :: WeekDay -> WeekDay -> Bool #

Ord WeekDay Source # 
Instance details

Defined in Time.Types

Points in time

Elapsed time since the start of the Unix epoch

newtype Elapsed Source #

Type representing numbers of seconds elapsed since the start of the Unix epoch (1970-01-01 00:00:00 UTC).

Constructors

Elapsed Seconds 

Instances

Instances details
Data Elapsed Source # 
Instance details

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

Defined in Time.Types

Read Elapsed Source # 
Instance details

Defined in Time.Types

Show Elapsed Source # 
Instance details

Defined in Time.Types

NFData Elapsed Source # 
Instance details

Defined in Time.Types

Methods

rnf :: Elapsed -> () #

Eq Elapsed Source # 
Instance details

Defined in Time.Types

Methods

(==) :: Elapsed -> Elapsed -> Bool #

(/=) :: Elapsed -> Elapsed -> Bool #

Ord Elapsed Source # 
Instance details

Defined in Time.Types

Time Elapsed Source # 
Instance details

Defined in Time.Time

Timeable Elapsed Source # 
Instance details

Defined in Time.Time

data ElapsedP 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

Instances details
Data ElapsedP Source # 
Instance details

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

Defined in Time.Types

Read ElapsedP Source # 
Instance details

Defined in Time.Types

Real ElapsedP Source # 
Instance details

Defined in Time.Types

Show ElapsedP Source # 
Instance details

Defined in Time.Types

NFData ElapsedP Source # 
Instance details

Defined in Time.Types

Methods

rnf :: ElapsedP -> () #

Eq ElapsedP Source # 
Instance details

Defined in Time.Types

Ord ElapsedP Source # 
Instance details

Defined in Time.Types

Time ElapsedP Source # 
Instance details

Defined in Time.Time

Timeable ElapsedP Source # 
Instance details

Defined in Time.Time

Date, time, and date and time

data Date Source #

Type representing dates in the proleptic Gregorian calendar (the common calendar).

Constructors

Date 

Fields

Instances

Instances details
Data Date Source # 
Instance details

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 #

toConstr :: Date -> Constr #

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

Defined in Time.Types

Show Date Source # 
Instance details

Defined in Time.Types

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

NFData Date Source # 
Instance details

Defined in Time.Types

Methods

rnf :: Date -> () #

Eq Date Source # 
Instance details

Defined in Time.Types

Methods

(==) :: Date -> Date -> Bool #

(/=) :: Date -> Date -> Bool #

Ord Date Source # 
Instance details

Defined in Time.Types

Methods

compare :: Date -> Date -> Ordering #

(<) :: Date -> Date -> Bool #

(<=) :: Date -> Date -> Bool #

(>) :: Date -> Date -> Bool #

(>=) :: Date -> Date -> Bool #

max :: Date -> Date -> Date #

min :: Date -> Date -> Date #

Time Date Source # 
Instance details

Defined in Time.Time

Timeable Date Source # 
Instance details

Defined in Time.Time

data TimeOfDay Source #

Type representing times as hour, minutes, seconds and nanoseconds.

Constructors

TimeOfDay 

Fields

Instances

Instances details
Data TimeOfDay Source # 
Instance details

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

Defined in Time.Types

Show TimeOfDay Source # 
Instance details

Defined in Time.Types

NFData TimeOfDay Source # 
Instance details

Defined in Time.Types

Methods

rnf :: TimeOfDay -> () #

Eq TimeOfDay Source # 
Instance details

Defined in Time.Types

Ord TimeOfDay Source # 
Instance details

Defined in Time.Types

data DateTime Source #

Type representing date and time.

Constructors

DateTime 

Fields

Instances

Instances details
Data DateTime Source # 
Instance details

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

Defined in Time.Types

Show DateTime Source # 
Instance details

Defined in Time.Types

NFData DateTime Source # 
Instance details

Defined in Time.Types

Methods

rnf :: DateTime -> () #

Eq DateTime Source # 
Instance details

Defined in Time.Types

Ord DateTime Source # 
Instance details

Defined in Time.Types

Time DateTime Source # 
Instance details

Defined in Time.Time

Timeable DateTime Source # 
Instance details

Defined in Time.Time

Local time and timezone-related

data LocalTime t Source #

Type representing local times.

Instances

Instances details
Functor LocalTime Source # 
Instance details

Defined in Time.LocalTime

Methods

fmap :: (a -> b) -> LocalTime a -> LocalTime b #

(<$) :: a -> LocalTime b -> LocalTime a #

Show t => Show (LocalTime t) Source # 
Instance details

Defined in Time.LocalTime

Eq t => Eq (LocalTime t) Source # 
Instance details

Defined in Time.LocalTime

Methods

(==) :: LocalTime t -> LocalTime t -> Bool #

(/=) :: LocalTime t -> LocalTime t -> Bool #

(Ord t, Time t) => Ord (LocalTime t) Source # 
Instance details

Defined in Time.LocalTime

class Timezone tz where Source #

A type class promising timezone-related functionality.

Minimal complete definition

timezoneOffset

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

Instances details
Timezone TimezoneMinutes Source # 
Instance details

Defined in Time.Timezone

Timezone UTC Source # 
Instance details

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

Instances details
Data TimezoneOffset Source # 
Instance details

Defined in Time.Types

Methods

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

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

toConstr :: TimezoneOffset -> Constr #

dataTypeOf :: TimezoneOffset -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TimezoneOffset Source # 
Instance details

Defined in Time.Types

NFData TimezoneOffset Source # 
Instance details

Defined in Time.Types

Methods

rnf :: TimezoneOffset -> () #

Eq TimezoneOffset Source # 
Instance details

Defined in Time.Types

Ord TimezoneOffset Source # 
Instance details

Defined in Time.Types

timezoneOffsetToSeconds :: TimezoneOffset -> Seconds Source #

For the given timezone offset, yield the corresponding number of seconds.

data UTC Source #

Type representing Universal Time Coordinated (UTC).

Constructors

UTC 

Instances

Instances details
Show UTC Source # 
Instance details

Defined in Time.Timezone

Methods

showsPrec :: Int -> UTC -> ShowS #

show :: UTC -> String #

showList :: [UTC] -> ShowS #

Eq UTC Source # 
Instance details

Defined in Time.Timezone

Methods

(==) :: UTC -> UTC -> Bool #

(/=) :: UTC -> UTC -> Bool #

Ord UTC Source # 
Instance details

Defined in Time.Timezone

Methods

compare :: UTC -> UTC -> Ordering #

(<) :: UTC -> UTC -> Bool #

(<=) :: UTC -> UTC -> Bool #

(>) :: UTC -> UTC -> Bool #

(>=) :: UTC -> UTC -> Bool #

max :: UTC -> UTC -> UTC #

min :: UTC -> UTC -> UTC #

Timezone UTC Source # 
Instance details

Defined in Time.Timezone

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 

Constructors

localTime Source #

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.

Miscellaneous calandar functions

isLeapYear Source #

Arguments

:: Int

Year.

-> Bool 

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.

daysInMonth Source #

Arguments

:: Int

Year.

-> Month 
-> Int 

For the given year and month in the proleptic Gregorian calendar, yield the number of days in the month.

Periods of time

data Duration Source #

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

Instances details
Data Duration Source # 
Instance details

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

Defined in Time.Diff

Semigroup Duration Source # 
Instance details

Defined in Time.Diff

Read Duration Source # 
Instance details

Defined in Time.Diff

Show Duration Source # 
Instance details

Defined in Time.Diff

NFData Duration Source # 
Instance details

Defined in Time.Diff

Methods

rnf :: Duration -> () #

Eq Duration Source # 
Instance details

Defined in Time.Diff

Ord Duration Source # 
Instance details

Defined in Time.Diff

TimeInterval Duration Source # 
Instance details

Defined in Time.Diff

data Period Source #

Type representing periods of time in years, months and days. See Duration for periods of time hours, minutes, seconds and nanoseconds.

Constructors

Period 

Instances

Instances details
Data Period Source # 
Instance details

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

Defined in Time.Diff

Semigroup Period Source # 
Instance details

Defined in Time.Diff

Read Period Source # 
Instance details

Defined in Time.Diff

Show Period Source # 
Instance details

Defined in Time.Diff

NFData Period Source # 
Instance details

Defined in Time.Diff

Methods

rnf :: Period -> () #

Eq Period Source # 
Instance details

Defined in Time.Diff

Methods

(==) :: Period -> Period -> Bool #

(/=) :: Period -> Period -> Bool #

Ord Period Source # 
Instance details

Defined in Time.Diff

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

dateAddPeriod :: Date -> Period -> Date Source #

Add the given period of time to the given date.

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

timeFromElapsedP

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

Instances details
Time CTime Source # 
Instance details

Defined in Time.Time

Time Date Source # 
Instance details

Defined in Time.Time

Time DateTime Source # 
Instance details

Defined in Time.Time

Time Elapsed Source # 
Instance details

Defined in Time.Time

Time ElapsedP Source # 
Instance details

Defined in Time.Time

Epoch epoch => Time (ElapsedSince epoch) Source # 
Instance details

Defined in Time.Epoch

Epoch epoch => Time (ElapsedSinceP epoch) Source # 
Instance details

Defined in Time.Epoch

class Timeable t where Source #

A type class promising functionality for:

  • converting a value of the type in question to a Elapsed value or a ElapsedP value; and
  • yielding separately a nanoseconds component of the value of the type in question (should yield 0 when the type is less precise than seconds).

Minimal complete definition

timeGetElapsedP

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

Instances details
Timeable CTime Source # 
Instance details

Defined in Time.Time

Timeable Date Source # 
Instance details

Defined in Time.Time

Timeable DateTime Source # 
Instance details

Defined in Time.Time

Timeable Elapsed Source # 
Instance details

Defined in Time.Time

Timeable ElapsedP Source # 
Instance details

Defined in Time.Time

Epoch epoch => Timeable (ElapsedSince epoch) Source # 
Instance details

Defined in Time.Epoch

Epoch epoch => Timeable (ElapsedSinceP epoch) Source # 
Instance details

Defined in Time.Epoch

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.

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 1 and 9.

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

Instances details
Show TimeFormatElem Source # 
Instance details

Defined in Time.Format

Eq TimeFormatElem Source # 
Instance details

Defined in Time.Format

TimeFormat [TimeFormatElem] Source # 
Instance details

Defined in Time.Format

data TimeFormatFct Source #

Type representing format functions.

Constructors

TimeFormatFct 

Fields

Instances

Instances details
Show TimeFormatFct Source # 
Instance details

Defined in Time.Format

Eq TimeFormatFct Source # 
Instance details

Defined in Time.Format

newtype TimeFormatString Source #

Type representing time format strings, composed of list of TimeFormatElem.

class TimeFormat format where Source #

A type class promising the ability to convert values to a TimeFormatString.

Methods

toFormat :: format -> 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

Instances details
Show ISO8601_Date Source # 
Instance details

Defined in Time.Format

Eq ISO8601_Date Source # 
Instance details

Defined in Time.Format

TimeFormat ISO8601_Date Source # 
Instance details

Defined in Time.Format

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 

Format methods

timePrint Source #

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.

localTimePrint Source #

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.

localTimeParse Source #

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.

localTimeParseE Source #

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.