hodatime-0.1.1.1: A fully featured date/time library based on Nodatime

Safe HaskellSafe
LanguageHaskell2010

Data.HodaTime.CalendarDate

Synopsis

Documentation

type Year = Int Source #

data CalendarDate calendar Source #

Represents a specific date within its calendar system, with no reference to any time zone or time of day. Note: We keep the date in 2 formats, redundantly. We depend on lazy evaluation to only produce the portion that is actually used

Instances

Eq (CalendarDate calendar) Source # 

Methods

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

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

Ord (CalendarDate calendar) Source # 

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 #

Show (CalendarDate calendar) Source # 

Methods

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

show :: CalendarDate calendar -> String #

showList :: [CalendarDate calendar] -> ShowS #

IsCalendar cal => HasDate (CalendarDate cal) Source # 

Associated Types

type DoW (CalendarDate cal) :: * Source #

type MoY (CalendarDate cal) :: * Source #

type DoW (CalendarDate cal) Source # 
type DoW (CalendarDate cal) = DayOfWeek cal
type MoY (CalendarDate cal) Source # 
type MoY (CalendarDate cal) = Month cal

class HasDate d where Source #

Minimal complete definition

day, month, monthl, year, dayOfWeek, next, previous

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 (+ 2) monthl $ Gregorian.calendarDate 31 January 2000
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 #

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

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

Instances

IsCalendar cal => HasDate (CalendarDateTime cal) Source # 
IsCalendar cal => HasDate (CalendarDate cal) Source # 

Associated Types

type DoW (CalendarDate cal) :: * Source #

type MoY (CalendarDate cal) :: * Source #