Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- addDays :: Integer -> Day -> Day
- diffDays :: Day -> Day -> Integer
- periodAllDays :: DayPeriod p => p -> [Day]
- periodFromDay :: DayPeriod p => Day -> (p, Int)
- periodLength :: DayPeriod p => p -> Int
- periodToDay :: DayPeriod p => p -> Int -> Day
- periodToDayValid :: DayPeriod p => p -> Int -> Maybe Day
- newtype Day = ModifiedJulianDay {}
- class Ord p => DayPeriod p where
- periodFirstDay :: p -> Day
- periodLastDay :: p -> Day
- dayPeriod :: Day -> p
- calendarDay :: CalendarDiffDays
- calendarMonth :: CalendarDiffDays
- calendarWeek :: CalendarDiffDays
- calendarYear :: CalendarDiffDays
- scaleCalendarDiffDays :: Integer -> CalendarDiffDays -> CalendarDiffDays
- data CalendarDiffDays = CalendarDiffDays {}
- pattern YearMonthDay :: Year -> MonthOfYear -> DayOfMonth -> Day
- addGregorianDurationClip :: CalendarDiffDays -> Day -> Day
- addGregorianDurationRollOver :: CalendarDiffDays -> Day -> Day
- addGregorianMonthsClip :: Integer -> Day -> Day
- addGregorianMonthsRollOver :: Integer -> Day -> Day
- addGregorianYearsClip :: Integer -> Day -> Day
- addGregorianYearsRollOver :: Integer -> Day -> Day
- diffGregorianDurationClip :: Day -> Day -> CalendarDiffDays
- diffGregorianDurationRollOver :: Day -> Day -> CalendarDiffDays
- fromGregorian :: Year -> MonthOfYear -> DayOfMonth -> Day
- fromGregorianValid :: Year -> MonthOfYear -> DayOfMonth -> Maybe Day
- gregorianMonthLength :: Year -> MonthOfYear -> DayOfMonth
- showGregorian :: Day -> String
- toGregorian :: Day -> (Year, MonthOfYear, DayOfMonth)
- isLeapYear :: Year -> Bool
- pattern April :: MonthOfYear
- pattern August :: MonthOfYear
- pattern BeforeCommonEra :: Integer -> Year
- pattern CommonEra :: Integer -> Year
- pattern December :: MonthOfYear
- pattern February :: MonthOfYear
- pattern January :: MonthOfYear
- pattern July :: MonthOfYear
- pattern June :: MonthOfYear
- pattern March :: MonthOfYear
- pattern May :: MonthOfYear
- pattern November :: MonthOfYear
- pattern October :: MonthOfYear
- pattern September :: MonthOfYear
- type DayOfMonth = Int
- type MonthOfYear = Int
- type Year = Integer
- dayOfWeek :: Day -> DayOfWeek
- dayOfWeekDiff :: DayOfWeek -> DayOfWeek -> Int
- firstDayOfWeekOnAfter :: DayOfWeek -> Day -> Day
- weekAllDays :: DayOfWeek -> Day -> [Day]
- weekFirstDay :: DayOfWeek -> Day -> Day
- weekLastDay :: DayOfWeek -> Day -> Day
- data DayOfWeek
Documentation
periodAllDays :: DayPeriod p => p -> [Day] Source #
A list of all the days in this period.
Since: time-1.12.1
periodFromDay :: DayPeriod p => Day -> (p, Int) Source #
Get the period this day is in, with the 1-based day number within the period.
periodFromDay (periodFirstDay p) = (p,1)
Since: time-1.12.1
periodLength :: DayPeriod p => p -> Int Source #
The number of days in this period.
Since: time-1.12.1
periodToDay :: DayPeriod p => p -> Int -> Day Source #
Inverse of periodFromDay
.
Since: time-1.12.1
periodToDayValid :: DayPeriod p => p -> Int -> Maybe Day Source #
Validating inverse of periodFromDay
.
Since: time-1.12.1
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 |
class Ord p => DayPeriod p where Source #
The class of types which can be represented as a period of days.
Since: time-1.12.1
periodFirstDay :: p -> Day Source #
Returns the first Day
in a period of days.
periodLastDay :: p -> Day Source #
Returns the last Day
in a period of days.
dayPeriod :: Day -> p Source #
Get the period this day is in.
scaleCalendarDiffDays :: Integer -> CalendarDiffDays -> CalendarDiffDays Source #
Scale by a factor. Note that scaleCalendarDiffDays (-1)
will not perfectly invert a duration, due to variable month lengths.
data CalendarDiffDays Source #
Instances
pattern YearMonthDay :: Year -> MonthOfYear -> DayOfMonth -> Day Source #
Bidirectional abstract constructor for the proleptic Gregorian calendar. Invalid values will be clipped to the correct range, month first, then day.
addGregorianDurationClip :: CalendarDiffDays -> Day -> Day Source #
Add months (clipped to last day), then add days
addGregorianDurationRollOver :: CalendarDiffDays -> Day -> Day Source #
Add months (rolling over to next month), then add days
addGregorianMonthsClip :: Integer -> Day -> Day Source #
Add months, with days past the last day of the month clipped to the last day. For instance, 2005-01-30 + 1 month = 2005-02-28.
addGregorianMonthsRollOver :: Integer -> Day -> Day Source #
Add months, with days past the last day of the month rolling over to the next month. For instance, 2005-01-30 + 1 month = 2005-03-02.
addGregorianYearsClip :: Integer -> Day -> Day Source #
Add years, matching month and day, with Feb 29th clipped to Feb 28th if necessary. For instance, 2004-02-29 + 2 years = 2006-02-28.
addGregorianYearsRollOver :: Integer -> Day -> Day Source #
Add years, matching month and day, with Feb 29th rolled over to Mar 1st if necessary. For instance, 2004-02-29 + 2 years = 2006-03-01.
diffGregorianDurationClip :: Day -> Day -> CalendarDiffDays Source #
Calendrical difference, with as many whole months as possible
diffGregorianDurationRollOver :: Day -> Day -> CalendarDiffDays Source #
Calendrical difference, with as many whole months as possible.
fromGregorian :: Year -> MonthOfYear -> DayOfMonth -> Day Source #
Convert from proleptic Gregorian calendar. Invalid values will be clipped to the correct range, month first, then day.
fromGregorianValid :: Year -> MonthOfYear -> DayOfMonth -> Maybe Day Source #
Convert from proleptic Gregorian calendar. Invalid values will return Nothing
gregorianMonthLength :: Year -> MonthOfYear -> DayOfMonth Source #
The number of days in a given month according to the proleptic Gregorian calendar.
showGregorian :: Day -> String Source #
Show in ISO 8601 format (yyyy-mm-dd)
toGregorian :: Day -> (Year, MonthOfYear, DayOfMonth) Source #
Convert to proleptic Gregorian calendar.
isLeapYear :: Year -> Bool Source #
Is this year a leap year according to the proleptic Gregorian calendar?
pattern April :: MonthOfYear Source #
pattern August :: MonthOfYear Source #
pattern BeforeCommonEra :: Integer -> Year Source #
Also known as Before Christ.
Note that Year 1 = 1 CE, and the previous Year 0 = 1 BCE.
CommonEra
and BeforeCommonEra
form a COMPLETE
set.
pattern December :: MonthOfYear Source #
The twelve MonthOfYear
patterns form a COMPLETE
set.
pattern February :: MonthOfYear Source #
pattern January :: MonthOfYear Source #
pattern July :: MonthOfYear Source #
pattern June :: MonthOfYear Source #
pattern March :: MonthOfYear Source #
pattern May :: MonthOfYear Source #
pattern November :: MonthOfYear Source #
pattern October :: MonthOfYear Source #
pattern September :: MonthOfYear Source #
type DayOfMonth = Int Source #
Day of month, in range 1 to 31.
type MonthOfYear = Int Source #
Month of year, in range 1 (January) to 12 (December).
dayOfWeekDiff :: DayOfWeek -> DayOfWeek -> Int Source #
dayOfWeekDiff a b = a - b
in range 0 to 6.
The number of days from b to the next a.
weekAllDays :: DayOfWeek -> Day -> [Day] Source #
Returns a week containing the given Day
where the first day is the
DayOfWeek
specified.
Examples:
>>>
weekAllDays Sunday (YearMonthDay 2022 02 21)
[YearMonthDay 2022 2 20 .. YearMonthDay 2022 2 26]
>>>
weekAllDays Monday (YearMonthDay 2022 02 21)
[YearMonthDay 2022 2 21 .. YearMonthDay 2022 2 27]
>>>
weekAllDays Tuesday (YearMonthDay 2022 02 21)
[YearMonthDay 2022 2 15 .. YearMonthDay 2022 2 21]
Since: time-1.12.2
weekFirstDay :: DayOfWeek -> Day -> Day Source #
Returns the first day of a week containing the given Day
.
Examples:
>>>
weekFirstDay Sunday (YearMonthDay 2022 02 21)
YearMonthDay 2022 2 20
>>>
weekFirstDay Monday (YearMonthDay 2022 02 21)
YearMonthDay 2022 2 21
>>>
weekFirstDay Tuesday (YearMonthDay 2022 02 21)
YearMonthDay 2022 2 15
Since: time-1.12.2
weekLastDay :: DayOfWeek -> Day -> Day Source #
Returns the last day of a week containing the given Day
.
Examples:
>>>
weekLastDay Sunday (YearMonthDay 2022 02 21)
YearMonthDay 2022 2 26
>>>
weekLastDay Monday (YearMonthDay 2022 02 21)
YearMonthDay 2022 2 27
>>>
weekLastDay Tuesday (YearMonthDay 2022 02 21)
YearMonthDay 2022 2 21
Since: time-1.12.2
Instances
NFData DayOfWeek Source # | |||||
Defined in Data.Time.Calendar.Week | |||||
Data DayOfWeek Source # | |||||
Defined in Data.Time.Calendar.Week 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 :: forall r r'. (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 # | |||||
Enum DayOfWeek Source # | "Circular", so for example | ||||
Defined in Data.Time.Calendar.Week succ :: DayOfWeek -> DayOfWeek # pred :: DayOfWeek -> DayOfWeek # fromEnum :: DayOfWeek -> Int # enumFrom :: DayOfWeek -> [DayOfWeek] # enumFromThen :: DayOfWeek -> DayOfWeek -> [DayOfWeek] # enumFromTo :: DayOfWeek -> DayOfWeek -> [DayOfWeek] # enumFromThenTo :: DayOfWeek -> DayOfWeek -> DayOfWeek -> [DayOfWeek] # | |||||
Generic DayOfWeek Source # | |||||
Defined in Data.Time.Calendar.Week
| |||||
Ix DayOfWeek Source # | |||||
Defined in Data.Time.Calendar.Week range :: (DayOfWeek, DayOfWeek) -> [DayOfWeek] # index :: (DayOfWeek, DayOfWeek) -> DayOfWeek -> Int # unsafeIndex :: (DayOfWeek, DayOfWeek) -> DayOfWeek -> Int # inRange :: (DayOfWeek, DayOfWeek) -> DayOfWeek -> Bool # rangeSize :: (DayOfWeek, DayOfWeek) -> Int # unsafeRangeSize :: (DayOfWeek, DayOfWeek) -> Int # | |||||
Read DayOfWeek Source # | |||||
Show DayOfWeek Source # | |||||
Eq DayOfWeek Source # | |||||
Ord DayOfWeek Source # | |||||
Defined in Data.Time.Calendar.Week | |||||
FormatTime DayOfWeek Source # | |||||
Defined in Data.Time.Format.Format.Instances formatCharacter :: Bool -> Char -> Maybe (FormatOptions -> DayOfWeek -> String) Source # | |||||
Lift DayOfWeek Source # | |||||
type Rep DayOfWeek Source # | |||||
Defined in Data.Time.Calendar.Week type Rep DayOfWeek = D1 ('MetaData "DayOfWeek" "Data.Time.Calendar.Week" "time-1.14-4f98" 'False) ((C1 ('MetaCons "Monday" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Tuesday" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Wednesday" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Thursday" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Friday" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Saturday" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sunday" 'PrefixI 'False) (U1 :: Type -> Type)))) |