chronos-1.0.2: A performant time library

Safe HaskellNone
LanguageHaskell2010

Chronos.Types

Description

Data types for representing different date and time-related information.

Internally, the types Int and Int64 are used to represent everything. These are used even when negative values are not appropriate and even if a smaller fixed-size integer could hold the information. The only cases when Int64 is used are when it is neccessary to represent values with numbers 2^29 or higher. These are typically fields that represent nanoseconds.

Unlike the types in the venerable time library, the types here do not allow the user to work with all dates. Since this library uses fixed-precision integral values instead of Integer, all of the usual problems with overflow should be considered. Notably, PosixTime and TaiTime can only be used to represent time between the years 1680 and 2260. All other types in this library correctly represent time a million years before or after 1970.

The vector unbox instances, not yet available, will store data in a reasonably compact manner. For example, the instance for Day has three unboxed vectors: Int for the year, Int8 for the month, and Int8 for the day. This only causes corruption of data if the user is trying to use out-of-bounds values for the month and the day. Users are advised to not use the data types provided here to model non-existent times.

Synopsis

Documentation

newtype Day Source #

A day represented as the modified Julian date, the number of days since midnight on November 17, 1858.

Constructors

Day 

Fields

Instances

Enum Day Source # 

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

enumFromThen :: Day -> Day -> [Day] #

enumFromTo :: Day -> Day -> [Day] #

enumFromThenTo :: Day -> Day -> Day -> [Day] #

Eq Day Source # 

Methods

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

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

Ord Day Source # 

Methods

compare :: Day -> Day -> Ordering #

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

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

(>) :: Day -> Day -> Bool #

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

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Read Day Source # 
Show Day Source # 

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

Hashable Day Source # 

Methods

hashWithSalt :: Int -> Day -> Int #

hash :: Day -> Int #

ToJSON Day Source # 
FromJSON Day Source # 
Storable Day Source # 

Methods

sizeOf :: Day -> Int #

alignment :: Day -> Int #

peekElemOff :: Ptr Day -> Int -> IO Day #

pokeElemOff :: Ptr Day -> Int -> Day -> IO () #

peekByteOff :: Ptr b -> Int -> IO Day #

pokeByteOff :: Ptr b -> Int -> Day -> IO () #

peek :: Ptr Day -> IO Day #

poke :: Ptr Day -> Day -> IO () #

Prim Day Source # 
Torsor Day Int Source # 

Methods

add :: Int -> Day -> Day #

difference :: Day -> Day -> Int #

newtype DayOfMonth Source #

The day of the month.

Constructors

DayOfMonth 

Fields

Instances

Enum DayOfMonth Source # 
Eq DayOfMonth Source # 
Ord DayOfMonth Source # 
Read DayOfMonth Source # 
Show DayOfMonth Source # 
Prim DayOfMonth Source # 
Unbox DayOfMonth Source # 
Vector Vector DayOfMonth Source # 
MVector MVector DayOfMonth Source # 
data Vector DayOfMonth Source # 
data MVector s DayOfMonth Source # 

newtype DayOfYear Source #

The day of the year.

Constructors

DayOfYear 

Fields

newtype Month Source #

The month of the year.

Constructors

Month 

Fields

Instances

Bounded Month Source # 
Enum Month Source # 
Eq Month Source # 

Methods

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

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

Ord Month Source # 

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 #

Read Month Source # 
Show Month Source # 

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

Prim Month Source # 
Unbox Month Source # 
Vector Vector Month Source # 
MVector MVector Month Source # 
data Vector Month Source # 
data MVector s Month Source # 

newtype Year Source #

The number of years elapsed since the beginning of the Common Era.

Constructors

Year 

Fields

Instances

newtype Offset Source #

Constructors

Offset 

Fields

Instances

Enum Offset Source # 
Eq Offset Source # 

Methods

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

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

Ord Offset Source # 
Read Offset Source # 
Show Offset Source # 
ToJSON Offset Source # 
ToJSONKey Offset Source # 
FromJSON Offset Source # 
FromJSONKey Offset Source # 
Torsor Offset Int Source # 

Methods

add :: Int -> Offset -> Offset #

difference :: Offset -> Offset -> Int #

newtype Time Source #

POSIX time with nanosecond resolution.

Constructors

Time 

Fields

Instances

Eq Time Source # 

Methods

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

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

Ord Time Source # 

Methods

compare :: Time -> Time -> Ordering #

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

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

(>) :: Time -> Time -> Bool #

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

max :: Time -> Time -> Time #

min :: Time -> Time -> Time #

Read Time Source # 
Show Time Source # 

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Hashable Time Source # 

Methods

hashWithSalt :: Int -> Time -> Int #

hash :: Time -> Int #

ToJSON Time Source # 
FromJSON Time Source # 
Storable Time Source # 

Methods

sizeOf :: Time -> Int #

alignment :: Time -> Int #

peekElemOff :: Ptr Time -> Int -> IO Time #

pokeElemOff :: Ptr Time -> Int -> Time -> IO () #

peekByteOff :: Ptr b -> Int -> IO Time #

pokeByteOff :: Ptr b -> Int -> Time -> IO () #

peek :: Ptr Time -> IO Time #

poke :: Ptr Time -> Time -> IO () #

Prim Time Source # 
Torsor Time Timespan Source # 

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

newtype DayOfWeekMatch a Source #

Constructors

DayOfWeekMatch 

newtype MonthMatch a Source #

Constructors

MonthMatch 

Fields

newtype Timespan Source #

A timespan. This is represented internally as a number of nanoseconds.

Constructors

Timespan 

Fields

Instances

Eq Timespan Source # 
Ord Timespan Source # 
Read Timespan Source # 
Show Timespan Source # 
Monoid Timespan Source # 
ToJSON Timespan Source # 
FromJSON Timespan Source # 
Additive Timespan Source # 
Torsor Time Timespan Source # 

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

Scaling Timespan Int64 Source # 

Methods

scale :: Int64 -> Timespan -> Timespan #

data SubsecondPrecision Source #

The precision used when encoding seconds to a human-readable format.

Constructors

SubsecondPrecisionAuto

Rounds to second, millisecond, microsecond, or nanosecond

SubsecondPrecisionFixed !Int

Specify number of places after decimal

data Date Source #

A date as represented by the Gregorian calendar.

Constructors

Date 

Instances

data OrdinalDate Source #

The year and number of days elapsed since the beginning it began.

data MonthDate Source #

A month and the day of the month. This does not actually represent a specific date, since this recurs every year.

Constructors

MonthDate 

data OffsetFormat Source #

Formatting settings for a timezone offset.

Constructors

OffsetFormatColonOff

%z (e.g., -0400)

OffsetFormatColonOn

%:z (e.g., -04:00)

OffsetFormatSecondsPrecision

%::z (e.g., -04:00:00)

OffsetFormatColonAuto

%:::z (e.g., -04, +05:30)

Instances

Bounded OffsetFormat Source # 
Enum OffsetFormat Source # 
Eq OffsetFormat Source # 
Ord OffsetFormat Source # 
Read OffsetFormat Source # 
Show OffsetFormat Source # 
Generic OffsetFormat Source # 

Associated Types

type Rep OffsetFormat :: * -> * #

type Rep OffsetFormat Source # 
type Rep OffsetFormat = D1 * (MetaData "OffsetFormat" "Chronos" "chronos-1.0.2-LX5OBW1NR1W5ko6b7nIgd6" False) ((:+:) * ((:+:) * (C1 * (MetaCons "OffsetFormatColonOff" PrefixI False) (U1 *)) (C1 * (MetaCons "OffsetFormatColonOn" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "OffsetFormatSecondsPrecision" PrefixI False) (U1 *)) (C1 * (MetaCons "OffsetFormatColonAuto" PrefixI False) (U1 *))))

data DatetimeLocale a Source #

Locale-specific formatting for weekdays and months. The type variable will likely be instantiated to Text or ByteString.

Constructors

DatetimeLocale 

Fields