Copyright | (c) 20021 Gautier DI FOLCO |
---|---|
License | ISC |
Maintainer | Gautier DI FOLCO <gautier.difolco@gmail.com> |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe |
Language | Haskell2010 |
Simple type-safe wrapper for time's Data.Time.Format.
You are are to represent a sound formatting at type-level:
myInput ::FormattedTime
RFC822
Synopsis
- data NoPadding (a :: k)
- data SpacesPadding (a :: k)
- data ZerosPadding (a :: k)
- data ToUpperCase (a :: k)
- data ToLowerCase (a :: k)
- data Width (w :: Nat) (a :: k)
- data Alternate (a :: Specifier)
- data Specifier
- = Percent
- | Tab
- | Newline
- | TimeZoneOffset
- | TimeZoneName
- | EpochSeconds
- | LocalDateTile
- | HoursMinutes
- | HoursMinutesSeconds
- | LocaleHoursMinutesSeconds
- | LocaleTwelveHoursMinutesSecondsPicos
- | LocaleLowercaseDayHalf
- | LocaleUppercaseDayHalf
- | PaddedTwentyFourHours
- | NoPaddedTwentyFourHours
- | PaddedTwelveHours
- | NoPaddedTwelveHours
- | PaddedMinutes
- | PaddedSeconds
- | PaddedPicoseconds
- | SecondsFraction
- | WeekDayNumberFormat
- | WeekDayNumber
- | WeekDayShort
- | WeekDayLong
- | Year
- | YearCentury
- | Century
- | MonthLong
- | MonthShort
- | MonthNumber
- | DateUs
- | DateIso
- | DateLocale
- | DayZeroPadded
- | DaySpacePadded
- | DayOfYear
- | CenturyFormat
- | WeekOfYearFormat
- | WeekOfYearNumberSunday
- | WeekOfYearNumberMonday
- | WholeWeeks
- | WholeDays
- | WholeDaysOfWeek
- | WholeHours
- | WholeHoursOfDay
- | WholeMinutes
- | WholeMinutesOfDay
- | WholeSeconds
- | WholeSecondsOfDay
- | DiffYears
- | DiffMonths
- | DiffMonthsOfYear
- | DiffWeeksWithoutMonths
- | DiffDaysWithoutMonths
- | DiffDaysOfWeek
- | CalendarDiffHoursWithoutMonths
- | CalendarDiffHours
- | CalendarDiffMinutes
- | CalendarDiffMinutesWithoutMonths
- | CalendarDiffSecondsWithoutMonths
- | CalendarDiffSeconds
- | TwoDigits
- | FourDigits
- data (left :: k0) :<> (right :: k1)
- newtype FormattedTime a = FormattedTime {}
- formatTime' :: forall f t. (FormatTime t, Formatter f, Printable f, SupportedFormatting t f) => TimeLocale -> t -> FormattedTime f
- parseTimeM' :: forall m f t. (MonadFail m, ParseTime t, Formatter f, Parsable f, SupportedFormatting t f) => Bool -> TimeLocale -> FormattedTime f -> m t
- class Formatter a where
- class Printable a
- class Parsable a
- class SupportedFormatting t f
Documentation
Formatting types
data NoPadding (a :: k) Source #
UNIX format representation
See https://hackage.haskell.org/package/time-1.11.1.2/docs/Data-Time-Format.html#v:formatTime
%-z
Instances
SupportedFormatting t a => SupportedFormatting (t :: k1) (NoPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Parsable a => Parsable (NoPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Printable a => Printable (NoPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Formatter a => Formatter (NoPadding a :: Type) Source # | |
data SpacesPadding (a :: k) Source #
%_z
Instances
SupportedFormatting t a => SupportedFormatting (t :: k1) (SpacesPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Parsable a => Parsable (SpacesPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Printable a => Printable (SpacesPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Formatter a => Formatter (SpacesPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed |
data ZerosPadding (a :: k) Source #
%0z
Instances
SupportedFormatting t a => SupportedFormatting (t :: k1) (ZerosPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Parsable a => Parsable (ZerosPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Printable a => Printable (ZerosPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Formatter a => Formatter (ZerosPadding a :: Type) Source # | |
Defined in Data.Time.Format.Typed |
data ToUpperCase (a :: k) Source #
%^z
Instances
SupportedFormatting t a => SupportedFormatting (t :: k1) (ToUpperCase a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Parsable a => Parsable (ToUpperCase a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Printable a => Printable (ToUpperCase a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Formatter a => Formatter (ToUpperCase a :: Type) Source # | |
Defined in Data.Time.Format.Typed |
data ToLowerCase (a :: k) Source #
%#z
Instances
SupportedFormatting t a => SupportedFormatting (t :: k1) (ToLowerCase a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Parsable a => Parsable (ToLowerCase a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Printable a => Printable (ToLowerCase a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Formatter a => Formatter (ToLowerCase a :: Type) Source # | |
Defined in Data.Time.Format.Typed |
data Width (w :: Nat) (a :: k) Source #
%nz
Instances
SupportedFormatting t a => SupportedFormatting (t :: k1) (Width n a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Parsable a => Parsable (Width n a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Printable a => Printable (Width n a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
(KnownNat n, Formatter a) => Formatter (Width n a :: Type) Source # | |
data Alternate (a :: Specifier) Source #
%Ez
Instances
SupportedFormatting t a => SupportedFormatting (t :: k) (Alternate a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Parsable a => Parsable (Alternate a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Printable a => Printable (Alternate a :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
Formatter a => Formatter (Alternate a :: Type) Source # | |
Instances
data (left :: k0) :<> (right :: k1) infixr 4 Source #
Concatenation
Instances
(SupportedFormatting t a, SupportedFormatting t b) => SupportedFormatting (t :: k) (a :<> b :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
(Parsable a, Parsable b) => Parsable (a :<> b :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
(Printable a, Printable b) => Printable (a :<> b :: Type) Source # | |
Defined in Data.Time.Format.Typed | |
(Formatter a, Formatter b) => Formatter (a :<> b :: Type) Source # | |
Format holders
newtype FormattedTime a Source #
Formatted time String
Instances
Eq (FormattedTime a) Source # | |
Defined in Data.Time.Format.Typed (==) :: FormattedTime a -> FormattedTime a -> Bool # (/=) :: FormattedTime a -> FormattedTime a -> Bool # | |
Show (FormattedTime a) Source # | |
Defined in Data.Time.Format.Typed showsPrec :: Int -> FormattedTime a -> ShowS # show :: FormattedTime a -> String # showList :: [FormattedTime a] -> ShowS # |
Formatting functions
formatTime' :: forall f t. (FormatTime t, Formatter f, Printable f, SupportedFormatting t f) => TimeLocale -> t -> FormattedTime f Source #
Type version of formatTime
parseTimeM' :: forall m f t. (MonadFail m, ParseTime t, Formatter f, Parsable f, SupportedFormatting t f) => Bool -> TimeLocale -> FormattedTime f -> m t Source #
Type version of parseTimeM
Typeclasses
class Formatter a where Source #
Instances
Instances
Instances
class SupportedFormatting t f Source #