hodatime-0.2.2.1: A fully featured date/time library based on Nodatime
Copyright(C) 2017 Jason Johnson
LicenseBSD-style (see the file LICENSE)
MaintainerJason Johnson <jason.johnson.081@gmail.com>
Stabilityexperimental
PortabilityPOSIX, Windows
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.HodaTime.CalendarDateTime

Description

This is the module for CalendarDateTime. A CalendarDateTime represents a date and time within the calendar system that is part of its type. It has no reference to a particular time zone and is therefor not a globally unique value as June 3rd 2020 10:05pm occurred at different Instants around the world.

Construction

To construct one of these types you will need a CalendarDate and a LocalTime

Synopsis

Types

data CalendarDateTime calendar Source #

Represents a specific date and time within its calendar system. NOTE: a CalendarDateTime does *not* represent a specific time on the global time line because e.g. "10.March.2006 4pm" is a different instant in most time zones. Convert it to a ZonedDateTime first if you wish to convert to an instant (or use a convenience function).

Instances

Instances details
Show (CalendarDateTime calendar) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

Methods

showsPrec :: Int -> CalendarDateTime calendar -> ShowS #

show :: CalendarDateTime calendar -> String #

showList :: [CalendarDateTime calendar] -> ShowS #

Eq (CalendarDateTime calendar) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

Methods

(==) :: CalendarDateTime calendar -> CalendarDateTime calendar -> Bool #

(/=) :: CalendarDateTime calendar -> CalendarDateTime calendar -> Bool #

Ord (CalendarDateTime calendar) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

Methods

compare :: CalendarDateTime calendar -> CalendarDateTime calendar -> Ordering #

(<) :: CalendarDateTime calendar -> CalendarDateTime calendar -> Bool #

(<=) :: CalendarDateTime calendar -> CalendarDateTime calendar -> Bool #

(>) :: CalendarDateTime calendar -> CalendarDateTime calendar -> Bool #

(>=) :: CalendarDateTime calendar -> CalendarDateTime calendar -> Bool #

max :: CalendarDateTime calendar -> CalendarDateTime calendar -> CalendarDateTime calendar #

min :: CalendarDateTime calendar -> CalendarDateTime calendar -> CalendarDateTime calendar #

IsCalendar cal => HasDate (CalendarDateTime cal) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

Associated Types

type DoW (CalendarDateTime cal) Source #

type MoY (CalendarDateTime cal) Source #

IsCalendar cal => HasLocalTime (CalendarDateTime cal) Source # 
Instance details

Defined in Data.HodaTime.LocalTime.Internal

type DoW (CalendarDateTime cal) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

type DoW (CalendarDateTime cal) = DayOfWeek cal
type MoY (CalendarDateTime cal) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

type MoY (CalendarDateTime cal) = Month cal

class IsCalendar cal where Source #

Associated Types

type Date cal Source #

data DayOfWeek cal Source #

data Month cal Source #

Methods

day' :: Functor f => (DayOfMonth -> f DayOfMonth) -> CalendarDate cal -> f (CalendarDate cal) Source #

month' :: CalendarDate cal -> Month cal Source #

monthl' :: Functor f => (Int -> f Int) -> CalendarDate cal -> f (CalendarDate cal) Source #

year' :: Functor f => (Year -> f Year) -> CalendarDate cal -> f (CalendarDate cal) Source #

dayOfWeek' :: CalendarDate cal -> DayOfWeek cal Source #

next' :: Int -> DayOfWeek cal -> CalendarDate cal -> CalendarDate cal Source #

previous' :: Int -> DayOfWeek cal -> CalendarDate cal -> CalendarDate cal Source #

Instances

Instances details
IsCalendar Gregorian Source # 
Instance details

Defined in Data.HodaTime.Calendar.Gregorian.Internal

IsCalendar Julian Source # 
Instance details

Defined in Data.HodaTime.Calendar.Julian

Associated Types

type Date Julian Source #

data DayOfWeek Julian Source #

data Month Julian Source #

class HasDate d where Source #

Associated Types

type DoW d Source #

type MoY d Source #

Methods

day :: Functor f => (DayOfMonth -> f DayOfMonth) -> d -> f d Source #

Lens for the day component of a HasDate. Please note that days are not clamped: if you add e.g. 400 days then the month and year will roll

month :: d -> MoY d Source #

Accessor for the Month component of a HasDate.

monthl :: Functor f => (Int -> f Int) -> d -> f d Source #

Lens for interacting with the month component of a HasDate. Please note that we convert the month to an Int so meaningful math can be done on it. Also please note that the day will be unaffected except in the case of "end of month" days which may clamp. Note that this clamping will only occur as a final step, so that

>>> modify monthl (+ 2) <$> Gregorian.calendarDate 31 January 2000
Just (CalendarDate 31 March 2000)

and not 29th of March as would happen with some libraries.

year :: Functor f => (Year -> f Year) -> d -> f d Source #

Lens for the year component of a HasDate. Please note that the rest of the date is left as is, with two exceptions: Feb 29 will clamp to 28 in a non-leapyear and if the new year is earlier than the earliest supported year it will clamp back to that year

dayOfWeek :: d -> DoW d Source #

Accessor for the Day of the week enum of a HasDate, for example:

>>> dayOfWeek . fromJust $ Gregorian.calendarDate 31 January 2000
Monday

next :: Int -> DoW d -> d -> d Source #

Returns a HasDate shifted to the nth next Day of Week from the current HasDate, for example:

>>> next 1 Monday . fromJust $ Gregorian.calendarDate 31 January 2000
CalendarDate 7 February 2000

previous :: Int -> DoW d -> d -> d Source #

Returns a HasDate shifted to the nth previous Day of Week from the current HasDate, for example:

>>> previous 1 Monday . fromJust $ Gregorian.calendarDate 31 January 2000
CalendarDate 24 January 2000

Instances

Instances details
IsCalendar cal => HasDate (CalendarDate cal) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

Associated Types

type DoW (CalendarDate cal) Source #

type MoY (CalendarDate cal) Source #

IsCalendar cal => HasDate (CalendarDateTime cal) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

Associated Types

type DoW (CalendarDateTime cal) Source #

type MoY (CalendarDateTime cal) Source #

Constructors

atStartOfDay :: CalendarDate cal -> CalendarDateTime cal Source #

Returns the first valid time in the day specified by CalendarDate within the given TimeZone