utc-0.2.0.1: A pragmatic time and date library.

Safe HaskellSafe-Inferred
LanguageHaskell98

Data.UTC

Contents

Synopsis

Introduction

Quick Start

Just import the main module and use the DateTime type! It supports all functions you'll find below. Use Maybe for all occurences of m.

Prelude> import Data.UTC
Prelude Data.UTC> type MT = Maybe (Local DateTime)
Prelude Data.UTC> type MS = Maybe String
Prelude Data.UTC> (parseRfc3339 "2014-12-24T13:37:00Z" :: MT) >>= addHours 25 >>= setMonth 1 >>= renderRfc3339 :: MS
Just "2014-01-25T14:37:00Z"

General Concepts

Handling Exceptions

The library's main idea is to make it hard to use it wrong. It should be impossible by the API's design to construct invalid date or time values.

Furthermore, the library is safe in the sense that its functions don't do anything that is not visible in the functions signature. Escpecially, none of the functions throw exceptions via error or undefined.

Whenever a function cannot be total, its result is wrapped in a type variable with a MonadThrow restriction on it which works nicely even in complex monad transformer stacks. You can always just use Maybe and fromMaybe to obtain a plain value:

fromMaybe epoch (addDays 24 epoch) :: Date
> 1970-01-25

Using another MonadThrow instance might give you additional information in case of failure:

setHour 10 epoch >>= setMinute 61 :: IO Time
> *** Exception: UtcException "Time: setMinute 61 10:00:00"

setHour 10 epoch >>= setMinute 61 :: Either Control.Exception.SomeException Time
> Left (UtcException "Time: setMinute 61 10:00:00")

Integer vs. Int

This library uses Integer instead of Int. This bears the advantage of easier reasoning about the code's correctness and the ability to work on date and time with arbitrary range and precision.

One might think that Integer is slower, but indeed it uses Int internally unless its range is exceeded. The dispatching should not take more than a few cycles. Using Int in the first place can rightly be considered premature optimisation. If this really is your application's bottle neck you should first consider creating your own time type (i.e. a newtyped Int representing Unixtime) and making it an instance of the relevant classes. Do the critical operations on the bare type. If that is not an option consider using a more specialised library.

Leap Seconds

As most other date and time libraries this library does not support handling of leap seconds.

The problem is not so much that this task would be tedious and difficult, but rather that future leap seconds are not known in advance and are announced just a few weeks before they occur. How should a library deal with this? Changing the function's semantic from version to version whenever a leap second occured? Probably not desireable. The only sane answer seems to be: Not at all!

In reality the problem is less severe than it seems: Your system clock is most probably counting unix seconds and does not know about leap seconds either. So chances are that when dealing with computer generated timestamps you'll never encounter problems with leap seconds.

Interfaces

Date

class Epoch t => IsDate t where Source

This class captures the behaviour of the Proleptic Gregorian Calendar.

Without any exception the following holds:

  • A regular year has 365 days and the corresponding February has 28 days.
  • A leap year has 366 days and the corresponding February has 29 days.
  • A year that is a multiple of 400 is a leap year.
  • A year that is a multiple of 100 but not of 400 is not a leap year.
  • A year that is a multiple of 4 but not of 100 is a leap year.

Minimal complete definition

year, month, day, setYear, setMonth, setDay

Methods

year :: t -> Integer Source

year  "2014-⁠12-⁠24" == 2014

For negative years the function assumes astronomical year numbering (year 1 ~ 1 AD, year 0 ~ 1 BC, year -1 ~ 2 BC etc). Note that 1 BC and 5 BC are therefore leap years.

month :: t -> Integer Source

month "2014-⁠12-⁠24" == 12

The function only returns values ranging from 1 to 12.

day :: t -> Integer Source

day   "2014-⁠12-⁠24" == 24

The function only returns values ranging from 1 to 31.

setYear :: MonadThrow m => Integer -> t -> m t Source

Sets the year and fails if the result would be invalid.

setYear 2005 "2004-02-28" :: Maybe Date
> Just 2005-02-28
setYear 2005 "2004-02-29" :: Maybe Date
> Nothing

setMonth :: MonadThrow m => Integer -> t -> m t Source

Sets the month of year and fails if the result would be invalid.

The function only accepts input ranging from 1 to 12.

setDay :: MonadThrow m => Integer -> t -> m t Source

Sets the day of month and fails if the result would be invalid.

The function only accepts input ranging from 1 to 31 (or less depending on month and year).

addYears :: MonadThrow m => Integer -> t -> m t Source

A year is a relative amount of time. The function's semantic is a follows:

  • The years (positive or negative) are added.
  • If the target date is invalid then days are subtracted until the date gets valid.
  • If the resulting date is out of the instance type's range, the function fails (cannot happen for Date and DateTime as they use multiprecision integers).
addYears 4 "2000-02-29" :: Maybe Date
> Just 2004-02-29
addYears 1 "2000-02-29" :: Maybe Date
> Just 2001-02-28

addMonths :: MonadThrow m => Integer -> t -> m t Source

A month is a relative amount of time. The function's semantic is equivalent to that of addYears.

The function fails if the resulting date is out of the instance type's range (cannot happen for Date and DateTime as they use multiprecision integers).

addMonths (-13) "1970-01-01" :: Maybe Date
> Just 1968-12-01

addDays :: MonadThrow m => Integer -> t -> m t Source

A day is an absolute amount of time. There is no surprise to expect.

The function fails if the resulting date is out of the instance type's range (cannot happen for Date and DateTime as they use multiprecision integers).

addDays 365 "1970-01-01" :: Maybe Date
> Just 1971-01-01
addDays 365 "2000-01-01" :: Maybe Date
> Just 2000-12-31

Time

class IsTime t where Source

This class captures the concept of a 24-hour clock time during a day.

Methods

hour :: t -> Integer Source

Returns values in the range 0 to 23.

minute :: t -> Integer Source

Returns values in the range 0 to 59.

second :: t -> Integer Source

Returns values in the range 0 to 59.

secondFraction :: t -> Rational Source

Returns values in the range 0.0 <= x < 1.0.

setHour :: MonadThrow m => Integer -> t -> m t Source

Accepts values in the range 0 to 23.

The function fails if the result cannot be represented by the type (cannot happen for Time and DateTime).

setMinute :: MonadThrow m => Integer -> t -> m t Source

Accepts values in the range 0 to 59.

The function fails if the result cannot be represented by the type (cannot happen for Time and DateTime).

setSecond :: MonadThrow m => Integer -> t -> m t Source

Accepts values in the range 0 to 59.

The function fails if the result cannot be represented by the type (cannot happen for Time and DateTime).

setSecondFraction :: MonadThrow m => Rational -> t -> m t Source

Accepts values in the range 0.0 <= x < 1.0.

The function fails if the result cannot be represented by the type (cannot happen for Time and DateTime).

addHours :: MonadThrow m => Integer -> t -> m t Source

Adds an arbitrary count of hours (positive or negative).

  • Full days flow over to addDays if the type is also an instance of IsDate (this is the case for DateTime).
  • Types not implementing the IsDate class should just ignore the days part on overflow (like Time does).
  • Fails if the result cannot be represented by the type (cannot happen for Time and DateTime).

addMinutes :: MonadThrow m => Integer -> t -> m t Source

Adds an arbitrary count of minutes (positive or negative).

  • Full hours flow over to addHours.
  • Fails if the result cannot be represented by the type (cannot happen for Time and DateTime).

addSeconds :: MonadThrow m => Integer -> t -> m t Source

Adds an arbitrary count of seconds (positive or negative).

  • Full minutes flow over to addMinutes.
  • Fails if the result cannot be represented by the type (cannot happen for Time and DateTime).

addSecondFractions :: MonadThrow m => Rational -> t -> m t Source

Adds an arbitrary second fraction (positive or negative).

  • Full seconds flow over to addSeconds.
  • Instances of this class are not required to preserve full precision (although Time and DateTime do so).
  • Fails if the result cannot be represented by the type (cannot happen for Time and DateTime).

Unix Time

class IsUnixTime t where Source

This class is for types that have a well-defined mapping to and from the Unix Time system (based on UTC).

Beware: It is a common misconception that the Unix time in general counts SI seconds since 1970-01-01T00:00:00Z. There is a common definition that may be called Unix time based on UTC: In general, the second boundaries match with UTC, but in the event of a positive (or negative) leap second the Unix second has a duration of 2 (or 0) SI seconds. This library is in accordance with this definition. This definition can also be understood as "ignoring leap seconds" (a Unix day therefore always has 86400 Unix seconds).

The concrete behaviour of your system clock is implementation dependant.

Epoch

class Epoch t where Source

The instant in time also known as the epoch: 1970-01-01T00:00:00Z

Methods

epoch :: t Source

Instances

Getting (Current) Timestamps

class HasUnixTime m where Source

This class defines an interface for contexts that can be asked for a timestamp.

Most users are likely to just need the IO instance, but you might think of other instances:

  • A wrapper around the system clock with internal state that ensures strict monotonically increasing values.
  • A custom monadic computation that needs time, but should not be given IO access.
  • Testing contexts where you might want to inject and test specific timestamps.

Methods

getUnixTime :: (Monad m, IsUnixTime a) => m a Source

Get a timestamp from the surrounding context. The IO instance gives access to the system clock and is what most users are probably looking for.

Beware: The IO instance does not guarantee that subsequent calls are monotonically increasing. The system's clock might stop or even go backwards when synchronised manually or via NTP or when adapting to a leap second.

Example:

import Data.UTC

printCurrentYear :: IO ()
printCurrentYear
  = do now <- getUnixTime :: IO DateTime
       print (year now)

Instances

Generic Date/Time Types

Date

data Date Source

This type represents dates in the Proleptic Gregorian Calendar.

  • It can represent any date in the past and in the future by using Integer internally.
  • The internal structure is not exposed to avoid the construction of invalid values. Use epoch or a parser to construct values.
  • The instance of Show is only meant for debugging purposes and is subject to change.
> show (epoch :: Date)
1970-01-01

Time

data Time Source

This type represents time instants during a day (00:00:00 - 23:59:59.999..) with arbitrary precision (uses Integer internally).

  • The internal structure is not exposed to avoid the creation of invalid values. Use epoch or a parser to construct values.
  • The instance of Show is only meant for debugging purposes and is subject to change.
> show (epoch :: Time)
00:00:00

DateTime

data DateTime Source

A time representation based on a Date and the Time of the day.

  • The type uses multiprecision integers internally and is able to represent any UTC date in the past and in the future with arbitrary precision (apart from the time span within a leap second).
  • The instance of Show is only meant for debugging purposes. Don't rely on its behaviour!
> show (epoch :: DateTime)
1970-01-01T00:00:00

Constructors

DateTime 

Fields

date :: Date
 
time :: Time
 

Local Time

data Local time Source

This type is used to extend UTC time types by a local offset in seconds (positive or negative).

Beware: A local offset is not a time zone. It is just a fix period of time. In contrast to a time zone this does not take summer or winter time into account.

Constructors

Local 

Fields

offset :: Maybe Rational
Nothing
The local offset is unknown (behaves like Western European Time)
Just 0
UTC+00:00 (Western European Time)
Just 3600
UTC+01:00 (Central European Time)
utc :: time

The time to be interpreted as UTC+00:00 (Western European Time)

Instances

Exception

data UtcException Source

All non-total functions within this library throw a UtcException exception within a MonadThrow context. Use MonadCatch to specifically catch this exception.

The String contains information that might be useful for debugging, but its specific form is undefined and must not be relied on.

Constructors

UtcException String 

Formatting

RFC 3339

Parsing

Rendering

class Rfc3339Renderer string where Source

setYear 1987 (epoch :: DateTime) 
  >>= setMonth 7 
  >>= setDay 10 
  >>= setHour 12 
  >>= setMinute 4 
  >>= return . (flip Local) (Just 0) 
  >>= renderRfc3339 :: Maybe String
> Just "1987-07-10T12:04:00Z"

Methods

renderRfc3339 :: (MonadThrow m, IsDate t, IsTime t, Epoch t) => Local t -> m string Source

ISO 8601

Rendering

class Iso8601Renderer string where Source

Methods

renderIso8601CalendarDate :: (MonadThrow m, IsDate t) => t -> m string Source

YYYYMMDD

renderIso8601CalendarDate' :: (MonadThrow m, IsDate t) => t -> m string Source

YYYY-MM-DD (extended format)

renderIso8601TimeHms :: (MonadThrow m, IsTime t) => t -> m string Source

hhmmss

renderIso8601TimeHms' :: (MonadThrow m, IsTime t) => t -> m string Source

hh:mm:ss (extended format)

renderIso8601TimeHm :: (MonadThrow m, IsTime t) => t -> m string Source

hhmm

renderIso8601TimeHm' :: (MonadThrow m, IsTime t) => t -> m string Source

hh:mm (extended format)