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.CalendarDate

Description

This is the module for CalendarDate. A CalendarDate represents a date within the calendar system that is part of its type. It has no reference to a particular time zone or time of day.

Construction

To construct one of these types, see the Calendar module you wish to construct the date in (typically Data.HodaTime.Calendar.Gregorian)

Synopsis

Documentation

data DayNth Source #

Used by several smart constructors to chose a day relative to the start or end of the month.

type Year = Int Source #

data CalendarDate calendar Source #

Instances

Instances details
Show (CalendarDate calendar) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

Methods

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

show :: CalendarDate calendar -> String #

showList :: [CalendarDate calendar] -> ShowS #

Eq (CalendarDate calendar) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

Methods

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

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

Ord (CalendarDate calendar) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

Methods

compare :: CalendarDate calendar -> CalendarDate calendar -> Ordering #

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

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

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

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

max :: CalendarDate calendar -> CalendarDate calendar -> CalendarDate calendar #

min :: CalendarDate calendar -> CalendarDate calendar -> CalendarDate calendar #

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 #

type DoW (CalendarDate cal) Source # 
Instance details

Defined in Data.HodaTime.CalendarDateTime.Internal

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

Defined in Data.HodaTime.CalendarDateTime.Internal

type MoY (CalendarDate cal) = Month cal

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 #