time-1.11: A time library

Safe HaskellSafe
LanguageHaskell2010

Data.Time.Calendar.WeekDate

Contents

Description

Week-based calendars

Synopsis

Documentation

type Year = Integer Source #

Year of Common Era.

type WeekOfYear = Int Source #

Week of year, by various reckonings, generally in range 0-53 depending on reckoning

data DayOfWeek Source #

Instances
Enum DayOfWeek Source #

"Circular", so for example [Tuesday ..] gives an endless sequence. Also: fromEnum gives [1 .. 7] for [Monday .. Sunday], and toEnum performs mod 7 to give a cycle of days.

Instance details

Defined in Data.Time.Calendar.Week

Eq DayOfWeek Source # 
Instance details

Defined in Data.Time.Calendar.Week

Data DayOfWeek Source # 
Instance details

Defined in Data.Time.Calendar.Week

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DayOfWeek -> c DayOfWeek #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DayOfWeek #

toConstr :: DayOfWeek -> Constr #

dataTypeOf :: DayOfWeek -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DayOfWeek) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DayOfWeek) #

gmapT :: (forall b. Data b => b -> b) -> DayOfWeek -> DayOfWeek #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DayOfWeek -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DayOfWeek -> r #

gmapQ :: (forall d. Data d => d -> u) -> DayOfWeek -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DayOfWeek -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DayOfWeek -> m DayOfWeek #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DayOfWeek -> m DayOfWeek #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DayOfWeek -> m DayOfWeek #

Ord DayOfWeek Source # 
Instance details

Defined in Data.Time.Calendar.Week

Read DayOfWeek Source # 
Instance details

Defined in Data.Time.Calendar.Week

Show DayOfWeek Source # 
Instance details

Defined in Data.Time.Calendar.Week

FormatTime DayOfWeek Source # 
Instance details

Defined in Data.Time.Format.Format.Instances

Methods

formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> DayOfWeek -> String) Source #

data FirstWeekType Source #

Constructors

FirstWholeWeek

first week is the first whole week of the year

FirstMostWeek

first week is the first week with four days in the year

toWeekCalendar Source #

Arguments

:: FirstWeekType

how to reckon the first week of the year

-> DayOfWeek

the first day of each week

-> Day 
-> (Year, WeekOfYear, DayOfWeek) 

Convert to the given kind of "week calendar". Note that the year number matches the weeks, and so is not always the same as the Gregorian year number.

fromWeekCalendar Source #

Arguments

:: FirstWeekType

how to reckon the first week of the year

-> DayOfWeek

the first day of each week

-> Year 
-> WeekOfYear 
-> DayOfWeek 
-> Day 

Convert from the given kind of "week calendar". Invalid week and day values will be clipped to the correct range.

fromWeekCalendarValid Source #

Arguments

:: FirstWeekType

how to reckon the first week of the year

-> DayOfWeek

the first day of each week

-> Year 
-> WeekOfYear 
-> DayOfWeek 
-> Maybe Day 

Convert from the given kind of "week calendar". Invalid week and day values will return Nothing.

ISO 8601 Week Date format

toWeekDate :: Day -> (Year, WeekOfYear, Int) Source #

Convert to ISO 8601 Week Date format. First element of result is year, second week number (1-53), third day of week (1 for Monday to 7 for Sunday). Note that "Week" years are not quite the same as Gregorian years, as the first day of the year is always a Monday. The first week of a year is the first week to contain at least four days in the corresponding Gregorian year.

fromWeekDate :: Year -> WeekOfYear -> Int -> Day Source #

Convert from ISO 8601 Week Date format. First argument is year, second week number (1-52 or 53), third day of week (1 for Monday to 7 for Sunday). Invalid week and day values will be clipped to the correct range.

pattern YearWeekDay :: Year -> WeekOfYear -> DayOfWeek -> Day Source #

Bidirectional abstract constructor for ISO 8601 Week Date format. Invalid week values will be clipped to the correct range.

fromWeekDateValid :: Year -> WeekOfYear -> Int -> Maybe Day Source #

Convert from ISO 8601 Week Date format. First argument is year, second week number (1-52 or 53), third day of week (1 for Monday to 7 for Sunday). Invalid week and day values will return Nothing.

showWeekDate :: Day -> String Source #

Show in ISO 8601 Week Date format as yyyy-Www-d (e.g. "2006-W46-3").