Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
ISO 8601 Ordinal Date format
Synopsis
- data Day
- type Year = Integer
- type DayOfYear = Int
- type WeekOfYear = Int
- pattern YearDay :: Year -> DayOfYear -> Day
- fromMondayStartWeek :: Year -> WeekOfYear -> Int -> Day
- fromMondayStartWeekValid :: Year -> WeekOfYear -> Int -> Maybe Day
- fromOrdinalDate :: Year -> DayOfYear -> Day
- fromOrdinalDateValid :: Year -> DayOfYear -> Maybe Day
- fromSundayStartWeek :: Year -> WeekOfYear -> Int -> Day
- fromSundayStartWeekValid :: Year -> WeekOfYear -> Int -> Maybe Day
- isLeapYear :: Year -> Bool
- mondayStartWeek :: Day -> (WeekOfYear, Int)
- showOrdinalDate :: Day -> String
- sundayStartWeek :: Day -> (WeekOfYear, Int)
- toOrdinalDate :: Day -> (Year, DayOfYear)
Documentation
The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17.
Instances
NFData Day Source # | |||||
Defined in Data.Time.Calendar.Days | |||||
Data Day Source # | |||||
Defined in Data.Time.Calendar.Days gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Day -> c Day # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Day # dataTypeOf :: Day -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Day) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Day) # gmapT :: (forall b. Data b => b -> b) -> Day -> Day # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r # gmapQ :: (forall d. Data d => d -> u) -> Day -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Day -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Day -> m Day # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day # | |||||
Enum Day Source # | |||||
Generic Day Source # | |||||
Defined in Data.Time.Calendar.Days
| |||||
Ix Day Source # | |||||
Read Day Source # | |||||
Show Day Source # | |||||
Eq Day Source # | |||||
Ord Day Source # | |||||
DayPeriod Day Source # | |||||
FormatTime Day Source # | |||||
Defined in Data.Time.Format.Format.Instances formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> Day -> String) Source # | |||||
ISO8601 Day Source # |
| ||||
Defined in Data.Time.Format.ISO8601 | |||||
ParseTime Day Source # | |||||
Defined in Data.Time.Format.Parse.Instances substituteTimeSpecifier :: Proxy Day -> TimeLocale -> Char -> Maybe String Source # parseTimeSpecifier :: Proxy Day -> TimeLocale -> Maybe ParseNumericPadding -> Char -> ReadP String Source # buildTime :: TimeLocale -> [(Char, String)] -> Maybe Day Source # | |||||
Lift Day Source # | |||||
type Rep Day Source # | |||||
Defined in Data.Time.Calendar.Days |
Day of year, in range 1 (January 1st) to 366. December 31st is 365 in a common year, 366 in a leap year.
type WeekOfYear = Int Source #
Week of year, by various reckonings, generally in range 0-53 depending on reckoning.
pattern YearDay :: Year -> DayOfYear -> Day Source #
Bidirectional abstract constructor for ISO 8601 Ordinal Date format. Invalid day numbers will be clipped to the correct range (1 to 365 or 366).
:: Year | Year. |
-> WeekOfYear | Monday-starting week number (as |
-> Int | Day of week.
Monday is 1, Sunday is 7 (as |
-> Day |
The inverse of mondayStartWeek
. Get a Day
given the year,
the number of the Monday-starting week, and the day of the week.
The first Monday is the first day of week 1, any earlier days in the year
are week 0 (as %W
in formatTime
).
fromMondayStartWeekValid Source #
:: Year | Year. |
-> WeekOfYear | Monday-starting week number (as |
-> Int | Day of week.
Monday is 1, Sunday is 7 (as |
-> Maybe Day |
fromOrdinalDate :: Year -> DayOfYear -> Day Source #
Convert from ISO 8601 Ordinal Date format. Invalid day numbers will be clipped to the correct range (1 to 365 or 366).
fromOrdinalDateValid :: Year -> DayOfYear -> Maybe Day Source #
Convert from ISO 8601 Ordinal Date format.
Invalid day numbers return Nothing
:: Year | Year. |
-> WeekOfYear | Sunday-starting week number (as |
-> Int | Day of week
Sunday is 0, Saturday is 6 (as |
-> Day |
The inverse of sundayStartWeek
. Get a Day
given the year and
the number of the day of a Sunday-starting week.
The first Sunday is the first day of week 1, any earlier days in the
year are week 0 (as %U
in formatTime
).
fromSundayStartWeekValid Source #
:: Year | Year. |
-> WeekOfYear | Sunday-starting week number (as |
-> Int | Day of week.
Sunday is 0, Saturday is 6 (as |
-> Maybe Day |
isLeapYear :: Year -> Bool Source #
Is this year a leap year according to the proleptic Gregorian calendar?
mondayStartWeek :: Day -> (WeekOfYear, Int) Source #
Get the number of the Monday-starting week in the year and the day of the week.
The first Monday is the first day of week 1, any earlier days in the year are week 0 (as %W
in formatTime
).
Monday is 1, Sunday is 7 (as %u
in formatTime
).
showOrdinalDate :: Day -> String Source #
Show in ISO 8601 Ordinal Date format (yyyy-ddd)
sundayStartWeek :: Day -> (WeekOfYear, Int) Source #
Get the number of the Sunday-starting week in the year and the day of the week.
The first Sunday is the first day of week 1, any earlier days in the year are week 0 (as %U
in formatTime
).
Sunday is 0, Saturday is 6 (as %w
in formatTime
).