hourglass-0.2.11: simple performant time related library

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Data.Hourglass

Contents

Description

Types and methods for time manipulation.

The most basic type for time representation is Elapsed, which represent a number of elapsed seconds since the unix epoch.

Every other defined types can be convert to and from Elapsed type:

timeGetElapsed (Date 1 2 3) :: Elapsed
timeFromElapsed 123         :: DateTime

Local time is represented by any other time types (Elapsed, Date, DateTime, ..), but augmented by a Timezone offset in minutes.

localTime (Date 2014 May 4) 600 -- local time at UTC+10 of May 4th 2014

Synopsis

Generic time classes

class Timeable t => Time t where Source #

Represent time types that can be created from other time types.

Every conversion happens throught ElapsedP or Elapsed types.

Minimal complete definition

timeFromElapsedP

Methods

timeFromElapsedP :: ElapsedP -> t Source #

convert from a number of elapsed seconds and nanoseconds to another time representation

timeFromElapsed :: Elapsed -> t Source #

convert from a number of elapsed seconds and nanoseconds to another time representation

defaults to timeFromElapsedP unless defined explicitely by an instance.

class Timeable t where Source #

Timeable represent every type that can be made to look like time types.

  • can be converted to ElapsedP and Elapsed
  • optionally have a timezone associated
  • have nanoseconds accessor (which can return 0 when the type is not more precise than seconds)

Minimal complete definition

timeGetElapsedP

Methods

timeGetElapsedP :: t -> ElapsedP Source #

convert a time representation to the number of elapsed seconds and nanoseconds to a specific epoch

timeGetElapsed :: t -> Elapsed Source #

convert a time representation to the number of elapsed seconds to a specific epoch.

defaults to timeGetElapsedP unless defined explicitely by an instance

timeGetNanoSeconds :: t -> NanoSeconds Source #

return the number of optional nanoseconds.

If the underlaying type is not precise enough to record nanoseconds (or any variant between seconds and nanoseconds), 0 should be returned

defaults to timeGetElapsedP unless defined explicitely by an instance, for efficiency reason, it's a good idea to override this methods if you know the type is not more precise than Seconds.

Elapsed time

newtype Elapsed Source #

A number of seconds elapsed since the unix epoch.

Constructors

Elapsed Seconds 

Instances

Eq Elapsed Source # 

Methods

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

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

Data Elapsed Source # 

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 :: (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 # 
Ord Elapsed Source # 
Read Elapsed Source # 
Show Elapsed Source # 
NFData Elapsed Source # 

Methods

rnf :: Elapsed -> () #

Time Elapsed Source # 
Timeable Elapsed Source # 

data ElapsedP Source #

A number of seconds and nanoseconds elapsed since the unix epoch.

Constructors

ElapsedP !Elapsed !NanoSeconds 

Instances

Eq ElapsedP Source # 
Data ElapsedP Source # 

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 :: (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 # 
Ord ElapsedP Source # 
Read ElapsedP Source # 
Real ElapsedP Source # 
Show ElapsedP Source # 
NFData ElapsedP Source # 

Methods

rnf :: ElapsedP -> () #

Time ElapsedP Source # 
Timeable ElapsedP Source # 

Generic conversion

timeConvert :: (Timeable t1, Time t2) => t1 -> t2 Source #

Convert one time representation into another one

The return type need to be infer by the context.

If the context cannot be infer through this, some specialized functions are available for built-in types:

Date and Time

timeGetDate :: Timeable t => t -> Date Source #

Get the calendar Date (year-month-day) from a time representation

specialization of timeConvert

timeGetDateTimeOfDay :: Timeable t => t -> DateTime Source #

Get the date and time of day from a time representation

specialization of timeConvert

timeGetTimeOfDay :: Timeable t => t -> TimeOfDay Source #

Get the day time (hours:minutes:seconds) from a time representation

specialization of timeConvert

Arithmetic

data Duration Source #

An amount of time in terms of constant value like hours (3600 seconds), minutes (60 seconds), seconds and nanoseconds.

Constructors

Duration 

Fields

Instances

Eq Duration Source # 
Data Duration Source # 

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 :: (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 #

Ord Duration Source # 
Read Duration Source # 
Show Duration Source # 
Monoid Duration Source # 
NFData Duration Source # 

Methods

rnf :: Duration -> () #

TimeInterval Duration Source # 

data Period Source #

An amount of conceptual calendar time in terms of years, months and days.

This allow calendar manipulation, representing things like days and months irrespective on how long those are related to timezone and daylight changes.

See Duration for the time-based equivalent to this class.

Constructors

Period 

Instances

Eq Period Source # 

Methods

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

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

Data Period Source # 

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 :: (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 #

Ord Period Source # 
Read Period Source # 
Show Period Source # 
Monoid Period Source # 
NFData Period Source # 

Methods

rnf :: Period -> () #

timeAdd :: (Time t, TimeInterval ti) => t -> ti -> t Source #

add some time interval to a time representation and returns this new time representation

example:

t1 `timeAdd` mempty { durationHours = 12 }

timeDiff :: (Timeable t1, Timeable t2) => t1 -> t2 -> Seconds Source #

Get the difference in seconds between two time representation

effectively:

t2 `timeDiff` t1 = t2 - t1

timeDiffP :: (Timeable t1, Timeable t2) => t1 -> t2 -> (Seconds, NanoSeconds) Source #

Get the difference in seconds and nanoseconds between two time representation

effectively:

@t2 `timeDiffP` t1 = t2 - t1

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

add a period of time to a date

Parsing and Printing

Format strings

data TimeFormatElem Source #

All the various formatter 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 chars (01 to 12)

Format_MonthName_Short

name of the month short (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 (01 to 31)

Format_Hour

hours (0 to 23)

Format_Minute

minutes (0 to 59)

Format_Second

seconds (0 to 59, 60 for leap seconds)

Format_UnixSecond

number of seconds since 1 jan 1970. unix epoch.

Format_MilliSecond

Milliseconds (000 to 999)

Format_MicroSecond

MicroSeconds (000000 to 999999)

Format_NanoSecond

NanoSeconds (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 implemented yet | Format_TimezoneOffset -- ^ timeoffset offset (+02:00)

Format_TzHM_Colon_Z

zero UTC offset (Z) or timeoffset with colon (+02:00)

Format_TzHM_Colon

timeoffset offset with colon (+02:00)

Format_TzHM

timeoffset offset (+0200)

Format_Tz_Offset

timeoffset in minutes

Format_Spaces

one or many space-like chars

Format_Text Char

a verbatim char

Format_Fct TimeFormatFct 

Common built-in formats

Format methods

timePrint Source #

Arguments

:: (TimeFormat format, Timeable t) 
=> format

the format to use for printing

-> t

the global time to print

-> String

the resulting string

Pretty print time to a string

The actual output is determined by the format used

timeParse :: TimeFormat format => format -> String -> Maybe DateTime Source #

Just like localTimeParse but the time 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

the resulting local time string

Pretty print local time to a string.

The actual output is determined by the format used.

localTimeParse Source #

Arguments

:: TimeFormat format 
=> format

the format to use for parsing

-> String

the string to parse

-> Maybe (LocalTime DateTime) 

Try parsing a string as time using the format explicitely specified

Unparsed characters are ignored and the error handling is simplified

for more elaborate need 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) 

Try parsing a string as time using the format explicitely specified

On failure, the parsing function returns the reason of the failure. If parsing is successful, return the date parsed with the remaining unparsed string

Local time

Local time type

data LocalTime t Source #

Local time representation

this is a time representation augmented by a timezone to get back to a global time, the timezoneOffset needed to be added to the local time.

Instances

Functor LocalTime Source # 

Methods

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

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

Eq t => Eq (LocalTime t) Source # 

Methods

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

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

(Ord t, Time t) => Ord (LocalTime t) Source # 
Show t => Show (LocalTime t) Source # 

Local time creation and manipulation

localTime :: Time t => TimezoneOffset -> t -> LocalTime t Source #

Create a local time type from a timezone and a time type.

The time value is assumed to be local to the timezone offset set, so no transformation is done.

localTimeUnwrap :: LocalTime t -> t Source #

unwrap the LocalTime value. the time value is local.

localTimeToGlobal :: Time t => LocalTime t -> t Source #

Get back a global time value

localTimeFromGlobal :: Time t => t -> LocalTime t Source #

create a local time value from a global one

localTimeGetTimezone :: LocalTime t -> TimezoneOffset Source #

get the timezone associated with LocalTime

localTimeSetTimezone :: Time t => TimezoneOffset -> LocalTime t -> LocalTime t Source #

Change the timezone, and adjust the local value to represent the new local value.

localTimeConvert :: (Time t1, Time t2) => LocalTime t1 -> LocalTime t2 Source #

convert the local time representation to another time representation determined by context.

class Timezone tz where Source #

standard representation for timezone

Minimal complete definition

timezoneOffset

Methods

timezoneOffset :: tz -> Int Source #

offset in minutes from UTC. valid values should be between -12*60 to +14*60

timezoneName :: tz -> String Source #

the name of the timezone. by default will be +-HH:MM encoding.

data UTC Source #

Universal Time Coordinated. The generic computer "timezone".

Constructors

UTC 

Instances

Eq UTC Source # 

Methods

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

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

Ord UTC Source # 

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 #

Show UTC Source # 

Methods

showsPrec :: Int -> UTC -> ShowS #

show :: UTC -> String #

showList :: [UTC] -> ShowS #

Timezone UTC Source # 

Calendar misc functions

isLeapYear :: Int -> Bool Source #

Return if this year is a leap year (366 days) or not (365 days in a year)

getWeekDay :: Date -> WeekDay Source #

Return the day of the week a specific date fall in

getDayOfTheYear :: Date -> Int Source #

return the day of the year where Jan 1 is 0

between 0 and 364. 365 for leap years

daysInMonth :: Int -> Month -> Int Source #

Return the number of days in a month.