{-# LANGUAGE Safe #-}{-# OPTIONS -fno-warn-orphans #-}moduleData.Time.Format.Format.Instances()whereimportControl.Applicative((<|>))importData.CharimportData.FixedimportData.Time.Calendar.CalendarDiffDays importData.Time.Calendar.Days importData.Time.Calendar.Gregorian importData.Time.Calendar.Month importData.Time.Calendar.OrdinalDate importData.Time.Calendar.Private importData.Time.Calendar.Week importData.Time.Calendar.WeekDate importData.Time.Clock.Internal.DiffTime importData.Time.Clock.Internal.NominalDiffTime importData.Time.Clock.Internal.UTCTime importData.Time.Clock.Internal.UniversalTime importData.Time.Clock.POSIX importData.Time.Format.Format.Class importData.Time.Format.Locale importData.Time.LocalTime.Internal.CalendarDiffTime importData.Time.LocalTime.Internal.LocalTime importData.Time.LocalTime.Internal.TimeOfDay importData.Time.LocalTime.Internal.TimeZone importData.Time.LocalTime.Internal.ZonedTime mapFormatCharacter ::(b ->a )->Maybe(FormatOptions ->a ->String)->Maybe(FormatOptions ->b ->String)mapFormatCharacter :: (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) mapFormatCharacter b -> a ba =((FormatOptions -> a -> String) -> FormatOptions -> b -> String) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap(((FormatOptions -> a -> String) -> FormatOptions -> b -> String) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String)) -> ((FormatOptions -> a -> String) -> FormatOptions -> b -> String) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) forall a b. (a -> b) -> a -> b $((a -> String) -> b -> String) -> (FormatOptions -> a -> String) -> FormatOptions -> b -> String forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap(((a -> String) -> b -> String) -> (FormatOptions -> a -> String) -> FormatOptions -> b -> String) -> ((a -> String) -> b -> String) -> (FormatOptions -> a -> String) -> FormatOptions -> b -> String forall a b. (a -> b) -> a -> b $\a -> String as ->a -> String as (a -> String) -> (b -> a) -> b -> String forall b c a. (b -> c) -> (a -> b) -> a -> c .b -> a ba instanceFormatTime LocalTime whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> LocalTime -> String) formatCharacter Bool _Char 'c'=(FormatOptions -> LocalTime -> String) -> Maybe (FormatOptions -> LocalTime -> String) forall a. a -> Maybe a Just((FormatOptions -> LocalTime -> String) -> Maybe (FormatOptions -> LocalTime -> String)) -> (FormatOptions -> LocalTime -> String) -> Maybe (FormatOptions -> LocalTime -> String) forall a b. (a -> b) -> a -> b $\FormatOptions fo ->TimeLocale -> String -> LocalTime -> String forall t. FormatTime t => TimeLocale -> String -> t -> String formatTime (FormatOptions -> TimeLocale foLocale FormatOptions fo )(String -> LocalTime -> String) -> String -> LocalTime -> String forall a b. (a -> b) -> a -> b $TimeLocale -> String dateTimeFmt (TimeLocale -> String) -> TimeLocale -> String forall a b. (a -> b) -> a -> b $FormatOptions -> TimeLocale foLocale FormatOptions fo formatCharacter Bool alt Char c =(LocalTime -> Day) -> Maybe (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> LocalTime -> String) forall b a. (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) mapFormatCharacter LocalTime -> Day localDay (Bool -> Char -> Maybe (FormatOptions -> Day -> String) forall t. FormatTime t => Bool -> Char -> Maybe (FormatOptions -> t -> String) formatCharacter Bool alt Char c )Maybe (FormatOptions -> LocalTime -> String) -> Maybe (FormatOptions -> LocalTime -> String) -> Maybe (FormatOptions -> LocalTime -> String) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|>(LocalTime -> TimeOfDay) -> Maybe (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> LocalTime -> String) forall b a. (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) mapFormatCharacter LocalTime -> TimeOfDay localTimeOfDay (Bool -> Char -> Maybe (FormatOptions -> TimeOfDay -> String) forall t. FormatTime t => Bool -> Char -> Maybe (FormatOptions -> t -> String) formatCharacter Bool alt Char c )todAMPM ::TimeLocale ->TimeOfDay ->StringtodAMPM :: TimeLocale -> TimeOfDay -> String todAMPM TimeLocale locale TimeOfDay day =let(String am ,String pm )=TimeLocale -> (String, String) amPm TimeLocale locale inif(TimeOfDay -> Int todHour TimeOfDay day )Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <Int 12thenString am elseString pm tod12Hour ::TimeOfDay ->Inttod12Hour :: TimeOfDay -> Int tod12Hour TimeOfDay day =(Int -> Int -> Int forall a. Integral a => a -> a -> a mod(TimeOfDay -> Int todHour TimeOfDay day Int -> Int -> Int forall a. Num a => a -> a -> a -Int 1)Int 12)Int -> Int -> Int forall a. Num a => a -> a -> a +Int 1instanceFormatTime TimeOfDay where-- AggregateformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> TimeOfDay -> String) formatCharacter Bool _Char 'R'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String) -> (TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->TimeLocale -> String -> TimeOfDay -> String forall t. FormatTime t => TimeLocale -> String -> t -> String formatTime TimeLocale locale String "%H:%M"formatCharacter Bool _Char 'T'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String) -> (TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->TimeLocale -> String -> TimeOfDay -> String forall t. FormatTime t => TimeLocale -> String -> t -> String formatTime TimeLocale locale String "%H:%M:%S"formatCharacter Bool _Char 'X'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String) -> (TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->TimeLocale -> String -> TimeOfDay -> String forall t. FormatTime t => TimeLocale -> String -> t -> String formatTime TimeLocale locale (TimeLocale -> String timeFmt TimeLocale locale )formatCharacter Bool _Char 'r'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String) -> (TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->TimeLocale -> String -> TimeOfDay -> String forall t. FormatTime t => TimeLocale -> String -> t -> String formatTime TimeLocale locale (TimeLocale -> String time12Fmt TimeLocale locale )-- AM/PMformatCharacter Bool _Char 'P'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String) -> (TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->(Char -> Char) -> String -> String forall a b. (a -> b) -> [a] -> [b] mapChar -> Char toLower(String -> String) -> (TimeOfDay -> String) -> TimeOfDay -> String forall b c a. (b -> c) -> (a -> b) -> a -> c .TimeLocale -> TimeOfDay -> String todAMPM TimeLocale locale formatCharacter Bool _Char 'p'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String) -> (TimeLocale -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->TimeLocale -> TimeOfDay -> String todAMPM TimeLocale locale -- HourformatCharacter Bool _Char 'H'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'TimeOfDay -> Int todHour formatCharacter Bool _Char 'I'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'TimeOfDay -> Int tod12Hour formatCharacter Bool _Char 'k'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char ' 'TimeOfDay -> Int todHour formatCharacter Bool _Char 'l'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char ' 'TimeOfDay -> Int tod12Hour -- MinuteformatCharacter Bool _Char 'M'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'TimeOfDay -> Int todMin -- SecondformatCharacter Bool _Char 'S'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'((TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String) -> (TimeOfDay -> Int) -> FormatOptions -> TimeOfDay -> String forall a b. (a -> b) -> a -> b $(Pico -> Int forall a b. (RealFrac a, Integral b) => a -> b floor(Pico -> Int) -> (TimeOfDay -> Pico) -> TimeOfDay -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .TimeOfDay -> Pico todSec ::TimeOfDay ->Int)formatCharacter Bool _Char 'q'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall t. Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> FormatOptions -> t -> String formatGeneral Bool TrueBool TrueInt 12Char '0'((TimeLocale -> PadOption -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String) -> (TimeLocale -> PadOption -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall a b. (a -> b) -> a -> b $\TimeLocale _PadOption pado ->PadOption -> Pico -> String forall a. HasResolution a => PadOption -> Fixed a -> String showPaddedFixedFraction PadOption pado (Pico -> String) -> (TimeOfDay -> Pico) -> TimeOfDay -> String forall b c a. (b -> c) -> (a -> b) -> a -> c .TimeOfDay -> Pico todSec formatCharacter Bool _Char 'Q'=(FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String)) -> (FormatOptions -> TimeOfDay -> String) -> Maybe (FormatOptions -> TimeOfDay -> String) forall a b. (a -> b) -> a -> b $Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall t. Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> FormatOptions -> t -> String formatGeneral Bool TrueBool FalseInt 12Char '0'((TimeLocale -> PadOption -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String) -> (TimeLocale -> PadOption -> TimeOfDay -> String) -> FormatOptions -> TimeOfDay -> String forall a b. (a -> b) -> a -> b $\TimeLocale _PadOption pado ->String -> String dotNonEmpty (String -> String) -> (TimeOfDay -> String) -> TimeOfDay -> String forall b c a. (b -> c) -> (a -> b) -> a -> c .PadOption -> Pico -> String forall a. HasResolution a => PadOption -> Fixed a -> String showPaddedFixedFraction PadOption pado (Pico -> String) -> (TimeOfDay -> Pico) -> TimeOfDay -> String forall b c a. (b -> c) -> (a -> b) -> a -> c .TimeOfDay -> Pico todSec wheredotNonEmpty :: String -> String dotNonEmpty String ""=String ""dotNonEmpty String s =Char '.'Char -> String -> String forall a. a -> [a] -> [a] :String s -- DefaultformatCharacter Bool _Char _=Maybe (FormatOptions -> TimeOfDay -> String) forall a. Maybe a NothinginstanceFormatTime ZonedTime whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> ZonedTime -> String) formatCharacter Bool _Char 'c'=(FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> ZonedTime -> String) forall a. a -> Maybe a Just((FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> ZonedTime -> String)) -> (FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> ZonedTime -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> ZonedTime -> String) -> FormatOptions -> ZonedTime -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> ZonedTime -> String) -> FormatOptions -> ZonedTime -> String) -> (TimeLocale -> ZonedTime -> String) -> FormatOptions -> ZonedTime -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->TimeLocale -> String -> ZonedTime -> String forall t. FormatTime t => TimeLocale -> String -> t -> String formatTime TimeLocale locale (TimeLocale -> String dateTimeFmt TimeLocale locale )formatCharacter Bool _Char 's'=(FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> ZonedTime -> String) forall a. a -> Maybe a Just((FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> ZonedTime -> String)) -> (FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> ZonedTime -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (ZonedTime -> Integer) -> FormatOptions -> ZonedTime -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 1Char '0'((ZonedTime -> Integer) -> FormatOptions -> ZonedTime -> String) -> (ZonedTime -> Integer) -> FormatOptions -> ZonedTime -> String forall a b. (a -> b) -> a -> b $(POSIXTime -> Integer forall a b. (RealFrac a, Integral b) => a -> b floor(POSIXTime -> Integer) -> (ZonedTime -> POSIXTime) -> ZonedTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .UTCTime -> POSIXTime utcTimeToPOSIXSeconds (UTCTime -> POSIXTime) -> (ZonedTime -> UTCTime) -> ZonedTime -> POSIXTime forall b c a. (b -> c) -> (a -> b) -> a -> c .ZonedTime -> UTCTime zonedTimeToUTC ::ZonedTime ->Integer)formatCharacter Bool alt Char c =(ZonedTime -> LocalTime) -> Maybe (FormatOptions -> LocalTime -> String) -> Maybe (FormatOptions -> ZonedTime -> String) forall b a. (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) mapFormatCharacter ZonedTime -> LocalTime zonedTimeToLocalTime (Bool -> Char -> Maybe (FormatOptions -> LocalTime -> String) forall t. FormatTime t => Bool -> Char -> Maybe (FormatOptions -> t -> String) formatCharacter Bool alt Char c )Maybe (FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> ZonedTime -> String) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|>(ZonedTime -> TimeZone) -> Maybe (FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> ZonedTime -> String) forall b a. (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) mapFormatCharacter ZonedTime -> TimeZone zonedTimeZone (Bool -> Char -> Maybe (FormatOptions -> TimeZone -> String) forall t. FormatTime t => Bool -> Char -> Maybe (FormatOptions -> t -> String) formatCharacter Bool alt Char c )instanceFormatTime TimeZone whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> TimeZone -> String) formatCharacter Bool FalseChar 'z'=(FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> TimeZone -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> TimeZone -> String)) -> (FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> TimeZone -> String) forall a b. (a -> b) -> a -> b $Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> TimeZone -> String) -> FormatOptions -> TimeZone -> String forall t. Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> FormatOptions -> t -> String formatGeneral Bool FalseBool TrueInt 4Char '0'((TimeLocale -> PadOption -> TimeZone -> String) -> FormatOptions -> TimeZone -> String) -> (TimeLocale -> PadOption -> TimeZone -> String) -> FormatOptions -> TimeZone -> String forall a b. (a -> b) -> a -> b $\TimeLocale _->Bool -> PadOption -> TimeZone -> String timeZoneOffsetString'' Bool FalseformatCharacter Bool TrueChar 'z'=(FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> TimeZone -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> TimeZone -> String)) -> (FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> TimeZone -> String) forall a b. (a -> b) -> a -> b $Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> TimeZone -> String) -> FormatOptions -> TimeZone -> String forall t. Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> FormatOptions -> t -> String formatGeneral Bool FalseBool TrueInt 5Char '0'((TimeLocale -> PadOption -> TimeZone -> String) -> FormatOptions -> TimeZone -> String) -> (TimeLocale -> PadOption -> TimeZone -> String) -> FormatOptions -> TimeZone -> String forall a b. (a -> b) -> a -> b $\TimeLocale _->Bool -> PadOption -> TimeZone -> String timeZoneOffsetString'' Bool TrueformatCharacter Bool alt Char 'Z'=(FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> TimeZone -> String) forall a. a -> Maybe a Just((FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> TimeZone -> String)) -> (FormatOptions -> TimeZone -> String) -> Maybe (FormatOptions -> TimeZone -> String) forall a b. (a -> b) -> a -> b $\FormatOptions fo TimeZone z ->letn :: String n =TimeZone -> String timeZoneName TimeZone z idef :: Int idef =ifBool alt thenInt 5elseInt 4inifString -> Bool forall (t :: * -> *) a. Foldable t => t a -> Bool nullString n thenBool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> TimeZone -> String) -> FormatOptions -> TimeZone -> String forall t. Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> FormatOptions -> t -> String formatGeneral Bool FalseBool TrueInt idef Char '0'(\TimeLocale _->Bool -> PadOption -> TimeZone -> String timeZoneOffsetString'' Bool alt )FormatOptions fo TimeZone z else(TimeLocale -> TimeZone -> String) -> FormatOptions -> TimeZone -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString (\TimeLocale _->TimeZone -> String timeZoneName )FormatOptions fo TimeZone z formatCharacter Bool _Char _=Maybe (FormatOptions -> TimeZone -> String) forall a. Maybe a NothinginstanceFormatTime DayOfWeek whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> DayOfWeek -> String) formatCharacter Bool _Char 'u'=(FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String) forall a. a -> Maybe a Just((FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String)) -> (FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 1Char '0'((DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String) -> (DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String forall a b. (a -> b) -> a -> b $DayOfWeek -> Int forall a. Enum a => a -> Int fromEnumformatCharacter Bool _Char 'w'=(FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String) forall a. a -> Maybe a Just((FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String)) -> (FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 1Char '0'((DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String) -> (DayOfWeek -> Int) -> FormatOptions -> DayOfWeek -> String forall a b. (a -> b) -> a -> b $\DayOfWeek wd ->(Int -> Int -> Int forall a. Integral a => a -> a -> a mod(DayOfWeek -> Int forall a. Enum a => a -> Int fromEnumDayOfWeek wd )Int 7)formatCharacter Bool _Char 'a'=(FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String) forall a. a -> Maybe a Just((FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String)) -> (FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> DayOfWeek -> String) -> FormatOptions -> DayOfWeek -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> DayOfWeek -> String) -> FormatOptions -> DayOfWeek -> String) -> (TimeLocale -> DayOfWeek -> String) -> FormatOptions -> DayOfWeek -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale DayOfWeek wd ->(String, String) -> String forall a b. (a, b) -> b snd((String, String) -> String) -> (String, String) -> String forall a b. (a -> b) -> a -> b $(TimeLocale -> [(String, String)] wDays TimeLocale locale )[(String, String)] -> Int -> (String, String) forall a. [a] -> Int -> a !!(Int -> Int -> Int forall a. Integral a => a -> a -> a mod(DayOfWeek -> Int forall a. Enum a => a -> Int fromEnumDayOfWeek wd )Int 7)formatCharacter Bool _Char 'A'=(FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String) forall a. a -> Maybe a Just((FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String)) -> (FormatOptions -> DayOfWeek -> String) -> Maybe (FormatOptions -> DayOfWeek -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> DayOfWeek -> String) -> FormatOptions -> DayOfWeek -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> DayOfWeek -> String) -> FormatOptions -> DayOfWeek -> String) -> (TimeLocale -> DayOfWeek -> String) -> FormatOptions -> DayOfWeek -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale DayOfWeek wd ->(String, String) -> String forall a b. (a, b) -> a fst((String, String) -> String) -> (String, String) -> String forall a b. (a -> b) -> a -> b $(TimeLocale -> [(String, String)] wDays TimeLocale locale )[(String, String)] -> Int -> (String, String) forall a. [a] -> Int -> a !!(Int -> Int -> Int forall a. Integral a => a -> a -> a mod(DayOfWeek -> Int forall a. Enum a => a -> Int fromEnumDayOfWeek wd )Int 7)formatCharacter Bool _Char _=Maybe (FormatOptions -> DayOfWeek -> String) forall a. Maybe a NothinginstanceFormatTime Month where-- Year CountformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> Month -> String) formatCharacter Bool _Char 'Y'=(FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a. a -> Maybe a Just((FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String)) -> (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Month -> Integer) -> FormatOptions -> Month -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool FalseInt 4Char '0'((Month -> Integer) -> FormatOptions -> Month -> String) -> (Month -> Integer) -> FormatOptions -> Month -> String forall a b. (a -> b) -> a -> b $\(YearMonth Integer y Int _)->Integer y formatCharacter Bool _Char 'y'=(FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a. a -> Maybe a Just((FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String)) -> (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Month -> Integer) -> FormatOptions -> Month -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'((Month -> Integer) -> FormatOptions -> Month -> String) -> (Month -> Integer) -> FormatOptions -> Month -> String forall a b. (a -> b) -> a -> b $\(YearMonth Integer y Int _)->Integer -> Integer forall i. Integral i => i -> i mod100 Integer y formatCharacter Bool _Char 'C'=(FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a. a -> Maybe a Just((FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String)) -> (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Month -> Integer) -> FormatOptions -> Month -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool FalseInt 2Char '0'((Month -> Integer) -> FormatOptions -> Month -> String) -> (Month -> Integer) -> FormatOptions -> Month -> String forall a b. (a -> b) -> a -> b $\(YearMonth Integer y Int _)->Integer -> Integer forall i. Integral i => i -> i div100 Integer y -- Month of YearformatCharacter Bool _Char 'B'=(FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a. a -> Maybe a Just((FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String)) -> (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> Month -> String) -> FormatOptions -> Month -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> Month -> String) -> FormatOptions -> Month -> String) -> (TimeLocale -> Month -> String) -> FormatOptions -> Month -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale (YearMonth Integer _Int my )->(String, String) -> String forall a b. (a, b) -> a fst((String, String) -> String) -> (String, String) -> String forall a b. (a -> b) -> a -> b $(TimeLocale -> [(String, String)] months TimeLocale locale )[(String, String)] -> Int -> (String, String) forall a. [a] -> Int -> a !!(Int my Int -> Int -> Int forall a. Num a => a -> a -> a -Int 1)formatCharacter Bool _Char 'b'=(FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a. a -> Maybe a Just((FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String)) -> (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> Month -> String) -> FormatOptions -> Month -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> Month -> String) -> FormatOptions -> Month -> String) -> (TimeLocale -> Month -> String) -> FormatOptions -> Month -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale (YearMonth Integer _Int my )->(String, String) -> String forall a b. (a, b) -> b snd((String, String) -> String) -> (String, String) -> String forall a b. (a -> b) -> a -> b $(TimeLocale -> [(String, String)] months TimeLocale locale )[(String, String)] -> Int -> (String, String) forall a. [a] -> Int -> a !!(Int my Int -> Int -> Int forall a. Num a => a -> a -> a -Int 1)formatCharacter Bool _Char 'h'=(FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a. a -> Maybe a Just((FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String)) -> (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> Month -> String) -> FormatOptions -> Month -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> Month -> String) -> FormatOptions -> Month -> String) -> (TimeLocale -> Month -> String) -> FormatOptions -> Month -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale (YearMonth Integer _Int my )->(String, String) -> String forall a b. (a, b) -> b snd((String, String) -> String) -> (String, String) -> String forall a b. (a -> b) -> a -> b $(TimeLocale -> [(String, String)] months TimeLocale locale )[(String, String)] -> Int -> (String, String) forall a. [a] -> Int -> a !!(Int my Int -> Int -> Int forall a. Num a => a -> a -> a -Int 1)formatCharacter Bool _Char 'm'=(FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a. a -> Maybe a Just((FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String)) -> (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Month -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Month -> Int) -> FormatOptions -> Month -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'((Month -> Int) -> FormatOptions -> Month -> String) -> (Month -> Int) -> FormatOptions -> Month -> String forall a b. (a -> b) -> a -> b $\(YearMonth Integer _Int m )->Int m -- DefaultformatCharacter Bool _Char _=Maybe (FormatOptions -> Month -> String) forall a. Maybe a NothinginstanceFormatTime Day where-- AggregateformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> Day -> String) formatCharacter Bool _Char 'D'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String) -> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->TimeLocale -> String -> Day -> String forall t. FormatTime t => TimeLocale -> String -> t -> String formatTime TimeLocale locale String "%m/%d/%y"formatCharacter Bool _Char 'F'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String) -> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->TimeLocale -> String -> Day -> String forall t. FormatTime t => TimeLocale -> String -> t -> String formatTime TimeLocale locale String "%Y-%m-%d"formatCharacter Bool _Char 'x'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String) -> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->TimeLocale -> String -> Day -> String forall t. FormatTime t => TimeLocale -> String -> t -> String formatTime TimeLocale locale (TimeLocale -> String dateFmt TimeLocale locale )-- Day of MonthformatCharacter Bool _Char 'd'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'((Day -> Int) -> FormatOptions -> Day -> String) -> (Day -> Int) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\(YearMonthDay Integer _Int _Int dm )->Int dm formatCharacter Bool _Char 'e'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char ' '((Day -> Int) -> FormatOptions -> Day -> String) -> (Day -> Int) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\(YearMonthDay Integer _Int _Int dm )->Int dm -- Day of YearformatCharacter Bool _Char 'j'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 3Char '0'((Day -> Int) -> FormatOptions -> Day -> String) -> (Day -> Int) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\(YearDay Integer _Int dy )->Int dy -- ISO 8601 Week DateformatCharacter Bool _Char 'G'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Integer) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool FalseInt 4Char '0'((Day -> Integer) -> FormatOptions -> Day -> String) -> (Day -> Integer) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\(YearWeekDay Integer y Int _DayOfWeek _)->Integer y formatCharacter Bool _Char 'g'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Integer) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'((Day -> Integer) -> FormatOptions -> Day -> String) -> (Day -> Integer) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\(YearWeekDay Integer y Int _DayOfWeek _)->Integer -> Integer forall i. Integral i => i -> i mod100 Integer y formatCharacter Bool _Char 'f'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Integer) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool FalseInt 2Char '0'((Day -> Integer) -> FormatOptions -> Day -> String) -> (Day -> Integer) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\(YearWeekDay Integer y Int _DayOfWeek _)->Integer -> Integer forall i. Integral i => i -> i div100 Integer y formatCharacter Bool _Char 'V'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'((Day -> Int) -> FormatOptions -> Day -> String) -> (Day -> Int) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\(YearWeekDay Integer _Int wy DayOfWeek _)->Int wy formatCharacter Bool _Char 'u'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 1Char '0'((Day -> Int) -> FormatOptions -> Day -> String) -> (Day -> Int) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\(YearWeekDay Integer _Int _DayOfWeek dw )->DayOfWeek -> Int forall a. Enum a => a -> Int fromEnumDayOfWeek dw -- Day of weekformatCharacter Bool _Char 'a'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String) -> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->(String, String) -> String forall a b. (a, b) -> b snd((String, String) -> String) -> (Day -> (String, String)) -> Day -> String forall b c a. (b -> c) -> (a -> b) -> a -> c .((TimeLocale -> [(String, String)] wDays TimeLocale locale )[(String, String)] -> Int -> (String, String) forall a. [a] -> Int -> a !!)(Int -> (String, String)) -> (Day -> Int) -> Day -> (String, String) forall b c a. (b -> c) -> (a -> b) -> a -> c .(Int, Int) -> Int forall a b. (a, b) -> b snd((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .Day -> (Int, Int) sundayStartWeek formatCharacter Bool _Char 'A'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $(TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall t. (TimeLocale -> t -> String) -> FormatOptions -> t -> String formatString ((TimeLocale -> Day -> String) -> FormatOptions -> Day -> String) -> (TimeLocale -> Day -> String) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $\TimeLocale locale ->(String, String) -> String forall a b. (a, b) -> a fst((String, String) -> String) -> (Day -> (String, String)) -> Day -> String forall b c a. (b -> c) -> (a -> b) -> a -> c .((TimeLocale -> [(String, String)] wDays TimeLocale locale )[(String, String)] -> Int -> (String, String) forall a. [a] -> Int -> a !!)(Int -> (String, String)) -> (Day -> Int) -> Day -> (String, String) forall b c a. (b -> c) -> (a -> b) -> a -> c .(Int, Int) -> Int forall a b. (a, b) -> b snd((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .Day -> (Int, Int) sundayStartWeek formatCharacter Bool _Char 'U'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'((Day -> Int) -> FormatOptions -> Day -> String) -> (Day -> Int) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $(Int, Int) -> Int forall a b. (a, b) -> a fst((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .Day -> (Int, Int) sundayStartWeek formatCharacter Bool _Char 'w'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 1Char '0'((Day -> Int) -> FormatOptions -> Day -> String) -> (Day -> Int) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $(Int, Int) -> Int forall a b. (a, b) -> b snd((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .Day -> (Int, Int) sundayStartWeek formatCharacter Bool _Char 'W'=(FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a. a -> Maybe a Just((FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String)) -> (FormatOptions -> Day -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Int -> Char -> (Day -> Int) -> FormatOptions -> Day -> String forall i t. ShowPadded i => Bool -> Int -> Char -> (t -> i) -> FormatOptions -> t -> String formatNumber Bool TrueInt 2Char '0'((Day -> Int) -> FormatOptions -> Day -> String) -> (Day -> Int) -> FormatOptions -> Day -> String forall a b. (a -> b) -> a -> b $(Int, Int) -> Int forall a b. (a, b) -> a fst((Int, Int) -> Int) -> (Day -> (Int, Int)) -> Day -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .Day -> (Int, Int) mondayStartWeek -- DefaultformatCharacter Bool alt Char c =(Day -> Month) -> Maybe (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Day -> String) forall b a. (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) mapFormatCharacter (\(MonthDay Month m Int _)->Month m )(Maybe (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Day -> String)) -> Maybe (FormatOptions -> Month -> String) -> Maybe (FormatOptions -> Day -> String) forall a b. (a -> b) -> a -> b $Bool -> Char -> Maybe (FormatOptions -> Month -> String) forall t. FormatTime t => Bool -> Char -> Maybe (FormatOptions -> t -> String) formatCharacter Bool alt Char c instanceFormatTime UTCTime whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> UTCTime -> String) formatCharacter Bool alt Char c =(UTCTime -> ZonedTime) -> Maybe (FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> UTCTime -> String) forall b a. (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) mapFormatCharacter (TimeZone -> UTCTime -> ZonedTime utcToZonedTime TimeZone utc )(Maybe (FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> UTCTime -> String)) -> Maybe (FormatOptions -> ZonedTime -> String) -> Maybe (FormatOptions -> UTCTime -> String) forall a b. (a -> b) -> a -> b $Bool -> Char -> Maybe (FormatOptions -> ZonedTime -> String) forall t. FormatTime t => Bool -> Char -> Maybe (FormatOptions -> t -> String) formatCharacter Bool alt Char c instanceFormatTime UniversalTime whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> UniversalTime -> String) formatCharacter Bool alt Char c =(UniversalTime -> LocalTime) -> Maybe (FormatOptions -> LocalTime -> String) -> Maybe (FormatOptions -> UniversalTime -> String) forall b a. (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) mapFormatCharacter (Rational -> UniversalTime -> LocalTime ut1ToLocalTime Rational 0)(Maybe (FormatOptions -> LocalTime -> String) -> Maybe (FormatOptions -> UniversalTime -> String)) -> Maybe (FormatOptions -> LocalTime -> String) -> Maybe (FormatOptions -> UniversalTime -> String) forall a b. (a -> b) -> a -> b $Bool -> Char -> Maybe (FormatOptions -> LocalTime -> String) forall t. FormatTime t => Bool -> Char -> Maybe (FormatOptions -> t -> String) formatCharacter Bool alt Char c instanceFormatTime NominalDiffTime whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> POSIXTime -> String) formatCharacter Bool _Char 'w'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Int -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String) -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $POSIXTime -> POSIXTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy (POSIXTime -> POSIXTime -> Integer) -> POSIXTime -> POSIXTime -> Integer forall a b. (a -> b) -> a -> b $POSIXTime 7POSIXTime -> POSIXTime -> POSIXTime forall a. Num a => a -> a -> a *POSIXTime 86400formatCharacter Bool _Char 'd'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Int -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String) -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $POSIXTime -> POSIXTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy POSIXTime 86400formatCharacter Bool _Char 'D'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Int -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String) -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 7(Integer -> Integer) -> (POSIXTime -> Integer) -> POSIXTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .POSIXTime -> POSIXTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy POSIXTime 86400formatCharacter Bool _Char 'h'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Int -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String) -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $POSIXTime -> POSIXTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy POSIXTime 3600formatCharacter Bool _Char 'H'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Int -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 2((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String) -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 24(Integer -> Integer) -> (POSIXTime -> Integer) -> POSIXTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .POSIXTime -> POSIXTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy POSIXTime 3600formatCharacter Bool _Char 'm'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Int -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String) -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $POSIXTime -> POSIXTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy POSIXTime 60formatCharacter Bool _Char 'M'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Int -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 2((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String) -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 60(Integer -> Integer) -> (POSIXTime -> Integer) -> POSIXTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .POSIXTime -> POSIXTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy POSIXTime 60formatCharacter Bool FalseChar 's'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Int -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String) -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $POSIXTime -> POSIXTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy POSIXTime 1formatCharacter Bool TrueChar 's'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> POSIXTime -> String) -> FormatOptions -> POSIXTime -> String forall t. Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> FormatOptions -> t -> String formatGeneral Bool TrueBool FalseInt 12Char '0'((TimeLocale -> PadOption -> POSIXTime -> String) -> FormatOptions -> POSIXTime -> String) -> (TimeLocale -> PadOption -> POSIXTime -> String) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $\TimeLocale _PadOption padf POSIXTime t ->PadOption -> PadOption -> Pico -> String forall a. HasResolution a => PadOption -> PadOption -> Fixed a -> String showPaddedFixed PadOption NoPad PadOption padf (POSIXTime -> Pico forall a b. (Real a, Fractional b) => a -> b realToFracPOSIXTime t ::Pico)formatCharacter Bool FalseChar 'S'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Int -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 2((POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String) -> (POSIXTime -> Integer) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 60(Integer -> Integer) -> (POSIXTime -> Integer) -> POSIXTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .POSIXTime -> POSIXTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy POSIXTime 1formatCharacter Bool TrueChar 'S'=(FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a. a -> Maybe a Just((FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String)) -> (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> POSIXTime -> String) forall a b. (a -> b) -> a -> b $Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> POSIXTime -> String) -> FormatOptions -> POSIXTime -> String forall t. Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> FormatOptions -> t -> String formatGeneral Bool TrueBool FalseInt 12Char '0'((TimeLocale -> PadOption -> POSIXTime -> String) -> FormatOptions -> POSIXTime -> String) -> (TimeLocale -> PadOption -> POSIXTime -> String) -> FormatOptions -> POSIXTime -> String forall a b. (a -> b) -> a -> b $\TimeLocale _PadOption padf POSIXTime t ->letpadn :: PadOption padn =casePadOption padf ofPadOption NoPad ->PadOption NoPad Pad Int _Char c ->Int -> Char -> PadOption Pad Int 2Char c inPadOption -> PadOption -> Pico -> String forall a. HasResolution a => PadOption -> PadOption -> Fixed a -> String showPaddedFixed PadOption padn PadOption padf (POSIXTime -> Pico forall a b. (Real a, Fractional b) => a -> b realToFrac(POSIXTime -> Pico) -> POSIXTime -> Pico forall a b. (a -> b) -> a -> b $POSIXTime -> POSIXTime -> POSIXTime forall a. Real a => a -> a -> a remBy POSIXTime 60POSIXTime t ::Pico)formatCharacter Bool _Char _=Maybe (FormatOptions -> POSIXTime -> String) forall a. Maybe a NothinginstanceFormatTime DiffTime whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> DiffTime -> String) formatCharacter Bool _Char 'w'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String) -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $DiffTime -> DiffTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy (DiffTime -> DiffTime -> Integer) -> DiffTime -> DiffTime -> Integer forall a b. (a -> b) -> a -> b $DiffTime 7DiffTime -> DiffTime -> DiffTime forall a. Num a => a -> a -> a *DiffTime 86400formatCharacter Bool _Char 'd'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String) -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $DiffTime -> DiffTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy DiffTime 86400formatCharacter Bool _Char 'D'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String) -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 7(Integer -> Integer) -> (DiffTime -> Integer) -> DiffTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .DiffTime -> DiffTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy DiffTime 86400formatCharacter Bool _Char 'h'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String) -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $DiffTime -> DiffTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy DiffTime 3600formatCharacter Bool _Char 'H'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 2((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String) -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 24(Integer -> Integer) -> (DiffTime -> Integer) -> DiffTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .DiffTime -> DiffTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy DiffTime 3600formatCharacter Bool _Char 'm'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String) -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $DiffTime -> DiffTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy DiffTime 60formatCharacter Bool _Char 'M'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 2((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String) -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 60(Integer -> Integer) -> (DiffTime -> Integer) -> DiffTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .DiffTime -> DiffTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy DiffTime 60formatCharacter Bool FalseChar 's'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String) -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $DiffTime -> DiffTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy DiffTime 1formatCharacter Bool TrueChar 's'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> DiffTime -> String) -> FormatOptions -> DiffTime -> String forall t. Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> FormatOptions -> t -> String formatGeneral Bool TrueBool FalseInt 12Char '0'((TimeLocale -> PadOption -> DiffTime -> String) -> FormatOptions -> DiffTime -> String) -> (TimeLocale -> PadOption -> DiffTime -> String) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $\TimeLocale _PadOption padf DiffTime t ->PadOption -> PadOption -> Pico -> String forall a. HasResolution a => PadOption -> PadOption -> Fixed a -> String showPaddedFixed PadOption NoPad PadOption padf (DiffTime -> Pico forall a b. (Real a, Fractional b) => a -> b realToFracDiffTime t ::Pico)formatCharacter Bool FalseChar 'S'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 2((DiffTime -> Integer) -> FormatOptions -> DiffTime -> String) -> (DiffTime -> Integer) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 60(Integer -> Integer) -> (DiffTime -> Integer) -> DiffTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .DiffTime -> DiffTime -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy DiffTime 1formatCharacter Bool TrueChar 'S'=(FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String)) -> (FormatOptions -> DiffTime -> String) -> Maybe (FormatOptions -> DiffTime -> String) forall a b. (a -> b) -> a -> b $Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> DiffTime -> String) -> FormatOptions -> DiffTime -> String forall t. Bool -> Bool -> Int -> Char -> (TimeLocale -> PadOption -> t -> String) -> FormatOptions -> t -> String formatGeneral Bool TrueBool FalseInt 12Char '0'((TimeLocale -> PadOption -> DiffTime -> String) -> FormatOptions -> DiffTime -> String) -> (TimeLocale -> PadOption -> DiffTime -> String) -> FormatOptions -> DiffTime -> String forall a b. (a -> b) -> a -> b $\TimeLocale _PadOption padf DiffTime t ->letpadn :: PadOption padn =casePadOption padf ofPadOption NoPad ->PadOption NoPad Pad Int _Char c ->Int -> Char -> PadOption Pad Int 2Char c inPadOption -> PadOption -> Pico -> String forall a. HasResolution a => PadOption -> PadOption -> Fixed a -> String showPaddedFixed PadOption padn PadOption padf (DiffTime -> Pico forall a b. (Real a, Fractional b) => a -> b realToFrac(DiffTime -> Pico) -> DiffTime -> Pico forall a b. (a -> b) -> a -> b $DiffTime -> DiffTime -> DiffTime forall a. Real a => a -> a -> a remBy DiffTime 60DiffTime t ::Pico)formatCharacter Bool _Char _=Maybe (FormatOptions -> DiffTime -> String) forall a. Maybe a NothinginstanceFormatTime CalendarDiffDays whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> CalendarDiffDays -> String) formatCharacter Bool _Char 'y'=(FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a. a -> Maybe a Just((FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String)) -> (FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a b. (a -> b) -> a -> b $Int -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String) -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy Integer 12(Integer -> Integer) -> (CalendarDiffDays -> Integer) -> CalendarDiffDays -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .CalendarDiffDays -> Integer cdMonths formatCharacter Bool _Char 'b'=(FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a. a -> Maybe a Just((FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String)) -> (FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a b. (a -> b) -> a -> b $Int -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String) -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall a b. (a -> b) -> a -> b $CalendarDiffDays -> Integer cdMonths formatCharacter Bool _Char 'B'=(FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a. a -> Maybe a Just((FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String)) -> (FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a b. (a -> b) -> a -> b $Int -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 2((CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String) -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 12(Integer -> Integer) -> (CalendarDiffDays -> Integer) -> CalendarDiffDays -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .CalendarDiffDays -> Integer cdMonths formatCharacter Bool _Char 'w'=(FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a. a -> Maybe a Just((FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String)) -> (FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a b. (a -> b) -> a -> b $Int -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String) -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy Integer 7(Integer -> Integer) -> (CalendarDiffDays -> Integer) -> CalendarDiffDays -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .CalendarDiffDays -> Integer cdDays formatCharacter Bool _Char 'd'=(FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a. a -> Maybe a Just((FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String)) -> (FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a b. (a -> b) -> a -> b $Int -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String) -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall a b. (a -> b) -> a -> b $CalendarDiffDays -> Integer cdDays formatCharacter Bool _Char 'D'=(FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a. a -> Maybe a Just((FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String)) -> (FormatOptions -> CalendarDiffDays -> String) -> Maybe (FormatOptions -> CalendarDiffDays -> String) forall a b. (a -> b) -> a -> b $Int -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String) -> (CalendarDiffDays -> Integer) -> FormatOptions -> CalendarDiffDays -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 7(Integer -> Integer) -> (CalendarDiffDays -> Integer) -> CalendarDiffDays -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .CalendarDiffDays -> Integer cdDays formatCharacter Bool _Char _=Maybe (FormatOptions -> CalendarDiffDays -> String) forall a. Maybe a NothinginstanceFormatTime CalendarDiffTime whereformatCharacter :: Bool -> Char -> Maybe (FormatOptions -> CalendarDiffTime -> String) formatCharacter Bool _Char 'y'=(FormatOptions -> CalendarDiffTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> CalendarDiffTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String)) -> (FormatOptions -> CalendarDiffTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (CalendarDiffTime -> Integer) -> FormatOptions -> CalendarDiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((CalendarDiffTime -> Integer) -> FormatOptions -> CalendarDiffTime -> String) -> (CalendarDiffTime -> Integer) -> FormatOptions -> CalendarDiffTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a b. (Real a, Integral b) => a -> a -> b quotBy Integer 12(Integer -> Integer) -> (CalendarDiffTime -> Integer) -> CalendarDiffTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .CalendarDiffTime -> Integer ctMonths formatCharacter Bool _Char 'b'=(FormatOptions -> CalendarDiffTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> CalendarDiffTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String)) -> (FormatOptions -> CalendarDiffTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (CalendarDiffTime -> Integer) -> FormatOptions -> CalendarDiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 1((CalendarDiffTime -> Integer) -> FormatOptions -> CalendarDiffTime -> String) -> (CalendarDiffTime -> Integer) -> FormatOptions -> CalendarDiffTime -> String forall a b. (a -> b) -> a -> b $CalendarDiffTime -> Integer ctMonths formatCharacter Bool _Char 'B'=(FormatOptions -> CalendarDiffTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String) forall a. a -> Maybe a Just((FormatOptions -> CalendarDiffTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String)) -> (FormatOptions -> CalendarDiffTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String) forall a b. (a -> b) -> a -> b $Int -> (CalendarDiffTime -> Integer) -> FormatOptions -> CalendarDiffTime -> String forall t. Int -> (t -> Integer) -> FormatOptions -> t -> String formatNumberStd Int 2((CalendarDiffTime -> Integer) -> FormatOptions -> CalendarDiffTime -> String) -> (CalendarDiffTime -> Integer) -> FormatOptions -> CalendarDiffTime -> String forall a b. (a -> b) -> a -> b $Integer -> Integer -> Integer forall a. Real a => a -> a -> a remBy Integer 12(Integer -> Integer) -> (CalendarDiffTime -> Integer) -> CalendarDiffTime -> Integer forall b c a. (b -> c) -> (a -> b) -> a -> c .CalendarDiffTime -> Integer ctMonths formatCharacter Bool alt Char c =(CalendarDiffTime -> POSIXTime) -> Maybe (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String) forall b a. (b -> a) -> Maybe (FormatOptions -> a -> String) -> Maybe (FormatOptions -> b -> String) mapFormatCharacter CalendarDiffTime -> POSIXTime ctTime (Maybe (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String)) -> Maybe (FormatOptions -> POSIXTime -> String) -> Maybe (FormatOptions -> CalendarDiffTime -> String) forall a b. (a -> b) -> a -> b $Bool -> Char -> Maybe (FormatOptions -> POSIXTime -> String) forall t. FormatTime t => Bool -> Char -> Maybe (FormatOptions -> t -> String) formatCharacter Bool alt Char c