chronos-1.1.4: A high-performance 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 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

Instances details
Enum Day Source # 
Instance details

Defined in Chronos

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

Defined in Chronos

Methods

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

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

Ord Day Source # 
Instance details

Defined in Chronos

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

Defined in Chronos

Show Day Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Day -> ShowS #

show :: Day -> String #

showList :: [Day] -> ShowS #

Hashable Day Source # 
Instance details

Defined in Chronos

Methods

hashWithSalt :: Int -> Day -> Int #

hash :: Day -> Int #

ToJSON Day Source # 
Instance details

Defined in Chronos

FromJSON Day Source # 
Instance details

Defined in Chronos

Storable Day Source # 
Instance details

Defined in Chronos

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

NFData Day Source # 
Instance details

Defined in Chronos

Methods

rnf :: Day -> () #

Prim Day Source # 
Instance details

Defined in Chronos

Torsor Day Int Source # 
Instance details

Defined in Chronos

Methods

add :: Int -> Day -> Day #

difference :: Day -> Day -> Int #

newtype DayOfWeek Source #

The day of the week.

Constructors

DayOfWeek 

Fields

Instances

Instances details
Eq DayOfWeek Source # 
Instance details

Defined in Chronos

Ord DayOfWeek Source # 
Instance details

Defined in Chronos

Read DayOfWeek Source # 
Instance details

Defined in Chronos

Show DayOfWeek Source # 
Instance details

Defined in Chronos

Hashable DayOfWeek Source # 
Instance details

Defined in Chronos

NFData DayOfWeek Source # 
Instance details

Defined in Chronos

Methods

rnf :: DayOfWeek -> () #

newtype DayOfMonth Source #

The day of the month.

Constructors

DayOfMonth 

Fields

Instances

Instances details
Enum DayOfMonth Source # 
Instance details

Defined in Chronos

Eq DayOfMonth Source # 
Instance details

Defined in Chronos

Ord DayOfMonth Source # 
Instance details

Defined in Chronos

Read DayOfMonth Source # 
Instance details

Defined in Chronos

Show DayOfMonth Source # 
Instance details

Defined in Chronos

NFData DayOfMonth Source # 
Instance details

Defined in Chronos

Methods

rnf :: DayOfMonth -> () #

Prim DayOfMonth Source # 
Instance details

Defined in Chronos

Unbox DayOfMonth Source # 
Instance details

Defined in Chronos

Vector Vector DayOfMonth Source # 
Instance details

Defined in Chronos

MVector MVector DayOfMonth Source # 
Instance details

Defined in Chronos

newtype Vector DayOfMonth Source # 
Instance details

Defined in Chronos

newtype MVector s DayOfMonth Source # 
Instance details

Defined in Chronos

newtype DayOfYear Source #

The day of the year.

Constructors

DayOfYear 

Fields

Instances

Instances details
Eq DayOfYear Source # 
Instance details

Defined in Chronos

Ord DayOfYear Source # 
Instance details

Defined in Chronos

Read DayOfYear Source # 
Instance details

Defined in Chronos

Show DayOfYear Source # 
Instance details

Defined in Chronos

NFData DayOfYear Source # 
Instance details

Defined in Chronos

Methods

rnf :: DayOfYear -> () #

Prim DayOfYear Source # 
Instance details

Defined in Chronos

newtype Month Source #

The month of the year.

Constructors

Month 

Fields

Instances

Instances details
Bounded Month Source #

Month starts at 0 and ends at 11 (January to December)

Instance details

Defined in Chronos

Enum Month Source # 
Instance details

Defined in Chronos

Eq Month Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Month Source # 
Instance details

Defined in Chronos

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

Defined in Chronos

Show Month Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Month -> ShowS #

show :: Month -> String #

showList :: [Month] -> ShowS #

NFData Month Source # 
Instance details

Defined in Chronos

Methods

rnf :: Month -> () #

Prim Month Source # 
Instance details

Defined in Chronos

Unbox Month Source # 
Instance details

Defined in Chronos

Vector Vector Month Source # 
Instance details

Defined in Chronos

MVector MVector Month Source # 
Instance details

Defined in Chronos

newtype Vector Month Source # 
Instance details

Defined in Chronos

newtype MVector s Month Source # 
Instance details

Defined in Chronos

newtype Year Source #

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

Constructors

Year 

Fields

Instances

Instances details
Eq Year Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Year Source # 
Instance details

Defined in Chronos

Methods

compare :: Year -> Year -> Ordering #

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

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

(>) :: Year -> Year -> Bool #

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

max :: Year -> Year -> Year #

min :: Year -> Year -> Year #

Read Year Source # 
Instance details

Defined in Chronos

Show Year Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Year -> ShowS #

show :: Year -> String #

showList :: [Year] -> ShowS #

NFData Year Source # 
Instance details

Defined in Chronos

Methods

rnf :: Year -> () #

newtype Offset Source #

Constructors

Offset 

Fields

Instances

Instances details
Enum Offset Source # 
Instance details

Defined in Chronos

Eq Offset Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Offset Source # 
Instance details

Defined in Chronos

Read Offset Source # 
Instance details

Defined in Chronos

Show Offset Source # 
Instance details

Defined in Chronos

ToJSON Offset Source # 
Instance details

Defined in Chronos

ToJSONKey Offset Source # 
Instance details

Defined in Chronos

FromJSON Offset Source # 
Instance details

Defined in Chronos

FromJSONKey Offset Source # 
Instance details

Defined in Chronos

NFData Offset Source # 
Instance details

Defined in Chronos

Methods

rnf :: Offset -> () #

Torsor Offset Int Source # 
Instance details

Defined in Chronos

Methods

add :: Int -> Offset -> Offset #

difference :: Offset -> Offset -> Int #

newtype Time Source #

POSIX time with nanosecond resolution.

Constructors

Time 

Fields

Instances

Instances details
Bounded Time Source # 
Instance details

Defined in Chronos

Eq Time Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Time Source # 
Instance details

Defined in Chronos

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

Defined in Chronos

Show Time Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Time -> ShowS #

show :: Time -> String #

showList :: [Time] -> ShowS #

Hashable Time Source # 
Instance details

Defined in Chronos

Methods

hashWithSalt :: Int -> Time -> Int #

hash :: Time -> Int #

ToJSON Time Source # 
Instance details

Defined in Chronos

FromJSON Time Source # 
Instance details

Defined in Chronos

Storable Time Source # 
Instance details

Defined in Chronos

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

NFData Time Source # 
Instance details

Defined in Chronos

Methods

rnf :: Time -> () #

Prim Time Source # 
Instance details

Defined in Chronos

Torsor Time Timespan Source # 
Instance details

Defined in Chronos

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

newtype DayOfWeekMatch a Source #

Match a DayOfWeek. By match, we mean that a DayOfWeekMatch is a mapping from the integer value of a DayOfWeek to some value of type a. You should construct a DayOfWeekMatch with buildDayOfWeekMatch, and match it using caseDayOfWeek.

Constructors

DayOfWeekMatch 

Instances

Instances details
NFData a => NFData (DayOfWeekMatch a) Source # 
Instance details

Defined in Chronos

Methods

rnf :: DayOfWeekMatch a -> () #

newtype MonthMatch a Source #

Match a Month. By match, we mean that a MonthMatch is a mapping from the integer value of a Month to some value of type a. You should construct a MonthMatch with buildMonthMatch, and match it using caseMonth.

Constructors

MonthMatch 

Fields

Instances

Instances details
NFData a => NFData (MonthMatch a) Source # 
Instance details

Defined in Chronos

Methods

rnf :: MonthMatch a -> () #

newtype UnboxedMonthMatch a Source #

Like MonthMatch, but the matched value can have an instance of Unbox.

Instances

Instances details
NFData (UnboxedMonthMatch a) Source # 
Instance details

Defined in Chronos

Methods

rnf :: UnboxedMonthMatch a -> () #

newtype Timespan Source #

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

Constructors

Timespan 

Fields

Instances

Instances details
Eq Timespan Source # 
Instance details

Defined in Chronos

Ord Timespan Source # 
Instance details

Defined in Chronos

Read Timespan Source # 
Instance details

Defined in Chronos

Show Timespan Source # 
Instance details

Defined in Chronos

Semigroup Timespan Source # 
Instance details

Defined in Chronos

Monoid Timespan Source # 
Instance details

Defined in Chronos

ToJSON Timespan Source # 
Instance details

Defined in Chronos

FromJSON Timespan Source # 
Instance details

Defined in Chronos

NFData Timespan Source # 
Instance details

Defined in Chronos

Methods

rnf :: Timespan -> () #

Additive Timespan Source # 
Instance details

Defined in Chronos

Torsor Time Timespan Source # 
Instance details

Defined in Chronos

Methods

add :: Timespan -> Time -> Time #

difference :: Time -> Time -> Timespan #

Scaling Timespan Int64 Source # 
Instance details

Defined in Chronos

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

Instances details
Enum Date Source # 
Instance details

Defined in Chronos

Methods

succ :: Date -> Date #

pred :: Date -> Date #

toEnum :: Int -> Date #

fromEnum :: Date -> Int #

enumFrom :: Date -> [Date] #

enumFromThen :: Date -> Date -> [Date] #

enumFromTo :: Date -> Date -> [Date] #

enumFromThenTo :: Date -> Date -> Date -> [Date] #

Eq Date Source # 
Instance details

Defined in Chronos

Methods

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

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

Ord Date Source # 
Instance details

Defined in Chronos

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 #

Read Date Source # 
Instance details

Defined in Chronos

Show Date Source # 
Instance details

Defined in Chronos

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

NFData Date Source # 
Instance details

Defined in Chronos

Methods

rnf :: Date -> () #

Torsor Date Int Source # 
Instance details

Defined in Chronos

Methods

add :: Int -> Date -> Date #

difference :: Date -> Date -> Int #

data OrdinalDate Source #

An OrdinalDate is a Year and the number of days elapsed since the Year began.

Instances

Instances details
Enum OrdinalDate Source # 
Instance details

Defined in Chronos

Eq OrdinalDate Source # 
Instance details

Defined in Chronos

Ord OrdinalDate Source # 
Instance details

Defined in Chronos

Read OrdinalDate Source # 
Instance details

Defined in Chronos

Show OrdinalDate Source # 
Instance details

Defined in Chronos

NFData OrdinalDate Source # 
Instance details

Defined in Chronos

Methods

rnf :: OrdinalDate -> () #

Torsor OrdinalDate Int Source # 
Instance details

Defined in Chronos

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 

Instances

Instances details
Eq MonthDate Source # 
Instance details

Defined in Chronos

Ord MonthDate Source # 
Instance details

Defined in Chronos

Read MonthDate Source # 
Instance details

Defined in Chronos

Show MonthDate Source # 
Instance details

Defined in Chronos

NFData MonthDate Source # 
Instance details

Defined in Chronos

Methods

rnf :: MonthDate -> () #

data Datetime Source #

A Date as represented by the Gregorian calendar and a TimeOfDay. While the ToJSON instance encodes with a hyphen separator, the FromJSON instance allows any non-digit character to act as separator, using the lenient parser.

Constructors

Datetime 

Instances

Instances details
Eq Datetime Source # 
Instance details

Defined in Chronos

Ord Datetime Source # 
Instance details

Defined in Chronos

Read Datetime Source # 
Instance details

Defined in Chronos

Show Datetime Source # 
Instance details

Defined in Chronos

ToJSON Datetime Source # 
Instance details

Defined in Chronos

FromJSON Datetime Source # 
Instance details

Defined in Chronos

NFData Datetime Source # 
Instance details

Defined in Chronos

Methods

rnf :: Datetime -> () #

data TimeOfDay Source #

A time of day with nanosecond resolution.

Instances

Instances details
Eq TimeOfDay Source # 
Instance details

Defined in Chronos

Ord TimeOfDay Source # 
Instance details

Defined in Chronos

Read TimeOfDay Source # 
Instance details

Defined in Chronos

Show TimeOfDay Source # 
Instance details

Defined in Chronos

NFData TimeOfDay Source # 
Instance details

Defined in Chronos

Methods

rnf :: TimeOfDay -> () #

data DatetimeFormat Source #

The format of a Datetime. In particular this provides separators for parts of the Datetime and nothing else.

Constructors

DatetimeFormat 

Fields

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

Instances details
Bounded OffsetFormat Source # 
Instance details

Defined in Chronos

Enum OffsetFormat Source # 
Instance details

Defined in Chronos

Eq OffsetFormat Source # 
Instance details

Defined in Chronos

Ord OffsetFormat Source # 
Instance details

Defined in Chronos

Read OffsetFormat Source # 
Instance details

Defined in Chronos

Show OffsetFormat Source # 
Instance details

Defined in Chronos

Generic OffsetFormat Source # 
Instance details

Defined in Chronos

Associated Types

type Rep OffsetFormat :: Type -> Type #

NFData OffsetFormat Source # 
Instance details

Defined in Chronos

Methods

rnf :: OffsetFormat -> () #

type Rep OffsetFormat Source # 
Instance details

Defined in Chronos

type Rep OffsetFormat = D1 ('MetaData "OffsetFormat" "Chronos" "chronos-1.1.4-98yYxDoIig9K4Gs60qgupJ" 'False) ((C1 ('MetaCons "OffsetFormatColonOff" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OffsetFormatColonOn" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OffsetFormatSecondsPrecision" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OffsetFormatColonAuto" 'PrefixI 'False) (U1 :: Type -> Type)))

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

Instances

Instances details
NFData a => NFData (DatetimeLocale a) Source # 
Instance details

Defined in Chronos

Methods

rnf :: DatetimeLocale a -> () #

data MeridiemLocale a Source #

Locale-specific formatting for AM and PM.

Constructors

MeridiemLocale 

Fields

Instances

Instances details
Eq a => Eq (MeridiemLocale a) Source # 
Instance details

Defined in Chronos

Ord a => Ord (MeridiemLocale a) Source # 
Instance details

Defined in Chronos

Read a => Read (MeridiemLocale a) Source # 
Instance details

Defined in Chronos

Show a => Show (MeridiemLocale a) Source # 
Instance details

Defined in Chronos

NFData a => NFData (MeridiemLocale a) Source # 
Instance details

Defined in Chronos

Methods

rnf :: MeridiemLocale a -> () #

data TimeInterval Source #

A TimeInterval represents a start and end time. It can sometimes be more ergonomic than the Torsor API when you only care about whether or not a Time is within a certain range.

To construct a TimeInterval, it is best to use timeIntervalBuilder, which maintains the invariant that lowerBound interval <= upperBound interval (all functions that act on TimeIntervals assume this invariant).

Constructors

TimeInterval !Time !Time 

data TimeParts Source #

Holds all of the parts encoded by a Time. Can be used for formatting if what is presently in the API does not suffice.

Constructors

TimeParts 

Fields

Instances

Instances details
Eq TimeParts Source # 
Instance details

Defined in Chronos

Read TimeParts Source # 
Instance details

Defined in Chronos

Show TimeParts Source # 
Instance details

Defined in Chronos

NFData TimeParts Source # 
Instance details

Defined in Chronos

Methods

rnf :: TimeParts -> () #